~ubuntu-branches/ubuntu/trusty/haskell-mersenne-random-pure64/trusty

« back to all changes in this revision

Viewing changes to System/Random/Mersenne/Pure64.hs

  • Committer: Package Import Robot
  • Author(s): Joachim Breitner
  • Date: 2012-12-09 13:43:33 UTC
  • Revision ID: package-import@ubuntu.com-20121209134333-d6wrwl64m871qfgf
Tags: upstream-0.2.0.3
ImportĀ upstreamĀ versionĀ 0.2.0.3

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
 
2
--------------------------------------------------------------------
 
3
-- |
 
4
-- Module     : System.Random.Mersenne.Pure64
 
5
-- Copyright  : Copyright (c) 2008, Don Stewart <dons@galois.com>
 
6
-- License    : BSD3
 
7
-- Maintainer : Don Stewart <dons@galois.com>
 
8
-- Stability  : experimental
 
9
-- Portability: CPP, FFI
 
10
-- Tested with: GHC 6.8.3
 
11
--
 
12
-- A purely functional binding 64 bit binding to the classic mersenne
 
13
-- twister random number generator. This is more flexible than the
 
14
-- impure 'mersenne-random' library, at the cost of being a bit slower.
 
15
-- This generator is however, many times faster than System.Random,
 
16
-- and yields high quality randoms with a long period.
 
17
--
 
18
-- This generator may be used with System.Random, however, that is
 
19
-- likely to be slower than using it directly.
 
20
--
 
21
module System.Random.Mersenne.Pure64 (
 
22
 
 
23
    -- * The random number generator
 
24
    PureMT          -- abstract: RandomGen
 
25
 
 
26
    -- * Introduction
 
27
    , pureMT        -- :: Word64 -> PureMT
 
28
    , newPureMT     -- :: IO PureMT
 
29
 
 
30
    -- $instance
 
31
 
 
32
    -- * Low level access to the generator
 
33
 
 
34
    -- $notes
 
35
    , randomInt     -- :: PureMT -> (Int   ,PureMT)
 
36
    , randomWord    -- :: PureMT -> (Word  ,PureMT)
 
37
    , randomInt64   -- :: PureMT -> (Int64 ,PureMT)
 
38
    , randomWord64  -- :: PureMT -> (Word64,PureMT)
 
39
    , randomDouble  -- :: PureMT -> (Double,PureMT)
 
40
 
 
41
    ) where
 
42
 
 
43
------------------------------------------------------------------------
 
44
 
 
45
import System.Random.Mersenne.Pure64.MTBlock
 
46
import System.Random
 
47
import Data.Word
 
48
import Data.Int
 
49
import System.Time
 
50
import System.CPUTime
 
51
 
 
52
-- | Create a PureMT generator from a 'Word64' seed.
 
53
pureMT :: Word64 -> PureMT
 
54
pureMT = mkPureMT . seedBlock . fromIntegral
 
55
 
 
56
-- | Create a new PureMT generator, using the clocktime as the base for the seed.
 
57
newPureMT :: IO PureMT
 
58
newPureMT = do
 
59
    ct             <- getCPUTime
 
60
    (TOD sec psec) <- getClockTime
 
61
    return $ pureMT (fromIntegral $ sec * 1013904242 + psec + ct)
 
62
 
 
63
------------------------------------------------------------------------
 
64
-- System.Random interface.
 
65
 
 
66
-- $instance
 
67
--
 
68
-- Being purely functional, the PureMT generator is an instance of
 
69
-- RandomGen. However, it doesn't support 'split' yet.
 
70
 
 
71
instance RandomGen PureMT where
 
72
   next  = randomInt
 
73
   split = error "System.Random.Mersenne.Pure: unable to split the mersenne twister"
 
74
 
 
75
------------------------------------------------------------------------
 
76
-- Direct access to Int, Word and Double types
 
77
 
 
78
-- | Yield a new 'Int' value from the generator, returning a new
 
79
-- generator and that 'Int'. The full 64 bits will be used on a 64 bit machine.
 
80
randomInt :: PureMT -> (Int,PureMT)
 
81
randomInt g = (fromIntegral i, g')
 
82
        where (i, g') = randomWord64 g
 
83
{-# INLINE randomInt #-}
 
84
 
 
85
-- | Yield a new 'Word' value from the generator, returning a new
 
86
-- generator and that 'Word'.
 
87
randomWord :: PureMT -> (Word,PureMT)
 
88
randomWord g = (fromIntegral i, g')
 
89
        where (i, g') = randomWord64 g
 
90
{-# INLINE randomWord #-}
 
91
 
 
92
-- | Yield a new 'Int64' value from the generator, returning a new
 
93
-- generator and that 'Int64'.
 
94
randomInt64 :: PureMT -> (Int64,PureMT)
 
95
randomInt64 g = (fromIntegral i, g')
 
96
        where (i, g') = randomWord64 g
 
97
{-# INLINE randomInt64 #-}
 
98
 
 
99
-- | Efficiently yield a new 53-bit precise 'Double' value, and a new generator.
 
100
randomDouble :: PureMT -> (Double,PureMT)
 
101
randomDouble g = (fromIntegral (i `div` 2048) / 9007199254740992, g')
 
102
        where (i, g') = randomWord64 g
 
103
{-# INLINE randomDouble #-}
 
104
 
 
105
-- | Yield a new 'Word64' value from the generator, returning a new
 
106
-- generator and that 'Word64'.
 
107
randomWord64 :: PureMT -> (Word64,PureMT)
 
108
randomWord64 (PureMT block i nxt) = (mixWord64 (block `lookupBlock` i), mt)
 
109
  where
 
110
    mt | i < blockLen-1 = PureMT block (i+1) nxt
 
111
       | otherwise      = mkPureMT nxt
 
112
{-# INLINE randomWord64 #-}
 
113
 
 
114
-- | 'PureMT', a pure mersenne twister pseudo-random number generator
 
115
--
 
116
data PureMT  = PureMT {-# UNPACK #-} !MTBlock {-# UNPACK #-} !Int MTBlock
 
117
 
 
118
instance Show PureMT where
 
119
    show _ = show "<PureMT>"
 
120
 
 
121
-- create a new PureMT from an MTBlock
 
122
mkPureMT :: MTBlock -> PureMT
 
123
mkPureMT block = PureMT block 0 (nextBlock block)