76a7277e3b4c771e3c6b1860a3b13b6598dfe6f7
[ghc-hetmet.git] / ghc / lib / std / Random.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1995-99
3 %
4
5
6 The June 1988 (v31 #6) issue of the Communications of the ACM has an
7 article by Pierre L'Ecuyer called, "Efficient and Portable Combined
8 Random Number Generators".  Here is the Portable Combined Generator of
9 L'Ecuyer for 32-bit computers.  It has a period of roughly 2.30584e18.
10
11 Transliterator: Lennart Augustsson
12
13 sof 1/99 - code brought (kicking and screaming) into the new Random
14 world..
15
16 \begin{code}
17 module Random
18         (
19           RandomGen(next, split)
20         , StdGen
21         , mkStdGen
22         , Random ( random,   randomR,
23                    randoms,  randomRs,
24                    randomIO, randomRIO )
25         , getStdRandom
26         , getStdGen
27         , setStdGen
28         , newStdGen
29         ) where
30
31 #ifndef __HUGS__
32 import PrelGHC          ( RealWorld )
33 import PrelNum          ( fromInt )
34 import PrelShow         ( showSignedInt, showSpace )
35 import PrelRead         ( readDec )
36 import PrelIOBase       ( unsafePerformIO, stToIO )
37 import PrelArr          ( STRef, newSTRef, readSTRef, writeSTRef )
38 import PrelReal         ( toInt )
39 import PrelFloat        ( float2Double, double2Float )
40 import Time             ( getClockTime, ClockTime(..) )
41 #else
42 import PrimPrel         ( IORef
43                         , newIORef
44                         , readIORef
45                         , writeIORef
46                         , unsafePerformIO
47                         )
48 #endif
49
50 import CPUTime          ( getCPUTime )
51 import Char             ( isSpace, chr, ord )
52 \end{code}
53
54 \begin{code}
55 class RandomGen g where
56    next  :: g -> (Int, g)
57    split :: g -> (g, g)
58
59 \end{code}
60
61 \begin{code}
62 data StdGen 
63  = StdGen Int Int
64
65 instance RandomGen StdGen where
66   next  = stdNext
67   split = stdSplit
68
69 #ifdef __HUGS__
70 instance Show StdGen where
71   showsPrec p (StdGen s1 s2) = 
72      showsPrec p s1 . 
73      showChar ' ' .
74      showsPrec p s2
75 #else
76 instance Show StdGen where
77   showsPrec p (StdGen s1 s2) = 
78      showSignedInt p s1 . 
79      showSpace          . 
80      showSignedInt p s2
81 #endif
82
83 instance Read StdGen where
84   readsPrec _p = \ r ->
85      case try_read r of
86        r@[_] -> r
87        _   -> [stdFromString r] -- because it shouldn't ever fail.
88     where 
89       try_read r = do
90          (s1, r1) <- readDec (dropWhile isSpace r)
91          (s2, r2) <- readDec (dropWhile isSpace r1)
92          return (StdGen s1 s2, r2)
93
94 {-
95  If we cannot unravel the StdGen from a string, create
96  one based on the string given.
97 -}
98 stdFromString         :: String -> (StdGen, String)
99 stdFromString s        = (mkStdGen num, rest)
100         where (cs, rest) = splitAt 6 s
101               num        = foldl (\a x -> x + 3 * a) 1 (map ord cs)
102 \end{code}
103
104 \begin{code}
105 mkStdGen :: Int -> StdGen -- why not Integer ?
106 mkStdGen s
107  | s < 0     = mkStdGen (-s)
108  | otherwise = StdGen (s1+1) (s2+1)
109       where
110         (q, s1) = s `divMod` 2147483562
111         s2      = q `mod` 2147483398
112
113 createStdGen :: Integer -> StdGen
114 createStdGen s
115  | s < 0     = createStdGen (-s)
116  | otherwise = StdGen (toInt (s1+1)) (toInt (s2+1))
117       where
118         (q, s1) = s `divMod` 2147483562
119         s2      = q `mod` 2147483398
120
121 \end{code}
122
123 The class definition - see library report for details.
124
125 \begin{code}
126 class Random a where
127   -- Minimal complete definition: random and randomR
128   random  :: RandomGen g => g -> (a, g)
129   randomR :: RandomGen g => (a,a) -> g -> (a,g)
130   
131   randoms  :: RandomGen g => g -> [a]
132   randoms  g      = x : randoms g' where (x,g') = random g
133
134   randomRs :: RandomGen g => (a,a) -> g -> [a]
135   randomRs ival g = x : randomRs ival g' where (x,g') = randomR ival g
136
137   randomIO  :: IO a
138   randomIO         = getStdRandom random
139
140   randomRIO :: (a,a) -> IO a
141   randomRIO range  = getStdRandom (randomR range)
142 \end{code}
143
144 \begin{code}
145 instance Random Int where
146   randomR (a,b) g = randomIvalInteger (toInteger a, toInteger b) g
147   random g        = randomR (minBound,maxBound) g
148
149 instance Random Char where
150   randomR (a,b) g = 
151       case (randomIvalInteger (toInteger (ord a), toInteger (ord b)) g) of
152         (x,g) -> (chr x, g)
153   random g        = randomR (minBound,maxBound) g
154
155 instance Random Bool where
156   randomR (a,b) g = 
157       case (randomIvalInteger (toInteger (bool2Int a), toInteger (bool2Int b)) g) of
158         (x, g) -> (int2Bool x, g)
159        where
160          bool2Int False = 0
161          bool2Int True  = 1
162
163          int2Bool 0     = False
164          int2Bool _     = True
165
166   random g        = randomR (minBound,maxBound) g
167  
168 instance Random Integer where
169   randomR ival g = randomIvalInteger ival g
170   random g       = randomR (toInteger (minBound::Int), toInteger (maxBound::Int)) g
171
172 instance Random Double where
173   randomR ival g = randomIvalDouble ival id g
174   random g       = randomR (0::Double,1) g
175   
176 -- hah, so you thought you were saving cycles by using Float?
177
178 #ifdef __HUGS__
179 instance Random Float where
180   random g        = randomIvalDouble (0::Double,1) realToFrac g
181   randomR (a,b) g = randomIvalDouble (realToFrac a, realToFrac b) realToFrac g
182 #else
183 instance Random Float where
184   randomR (a,b) g = randomIvalDouble (float2Double a, float2Double b) double2Float g
185   random g        = randomIvalDouble (0::Double,1) double2Float g
186 #endif
187
188 \end{code}
189
190
191 \begin{code}
192 #ifdef __HUGS__
193 mkStdRNG :: Integer -> IO StdGen
194 mkStdRNG o = do
195     ct          <- getCPUTime
196     return (createStdGen (ct + o))
197 #else
198 mkStdRNG :: Integer -> IO StdGen
199 mkStdRNG o = do
200     ct          <- getCPUTime
201     (TOD sec _) <- getClockTime
202     return (createStdGen (sec * 12345 + ct + o))
203 #endif
204
205 randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
206 randomIvalInteger (l,h) rng
207  | l > h     = randomIvalInteger (h,l) rng
208  | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng')
209      where
210        k = h - l + 1
211        b = 2147483561
212        n = iLogBase b k
213
214        f 0 acc g = (acc, g)
215        f n acc g = 
216           let
217            (x,g')   = next g
218           in
219           f (n-1) (fromInt x + acc * b) g'
220
221 randomIvalDouble :: (RandomGen g, Fractional a) => (Double, Double) -> (Double -> a) -> g -> (a, g)
222 randomIvalDouble (l,h) fromDouble rng 
223   | l > h     = randomIvalDouble (h,l) fromDouble rng
224   | otherwise = 
225        case (randomIvalInteger (toInteger (minBound::Int), toInteger (maxBound::Int)) rng) of
226          (x, rng') -> 
227             let
228              scaled_x = 
229                 fromDouble ((l+h)/2) + 
230                 fromDouble ((h-l) / realToFrac intRange) *
231                 fromIntegral (x::Int)
232             in
233             (scaled_x, rng')
234
235 intRange :: Integer
236 intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)
237
238 iLogBase :: Integer -> Integer -> Integer
239 iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b)
240
241 stdNext :: StdGen -> (Int, StdGen)
242 stdNext (StdGen s1 s2) = (z', StdGen s1'' s2'')
243         where   z'   = if z < 1 then z + 2147483562 else z
244                 z    = s1'' - s2''
245
246                 k    = s1 `quot` 53668
247                 s1'  = 40014 * (s1 - k * 53668) - k * 12211
248                 s1'' = if s1' < 0 then s1' + 2147483563 else s1'
249     
250                 k'   = s2 `quot` 52774
251                 s2'  = 40692 * (s2 - k' * 52774) - k' * 3791
252                 s2'' = if s2' < 0 then s2' + 2147483399 else s2'
253
254 stdSplit            :: StdGen -> (StdGen, StdGen)
255 stdSplit std@(StdGen s1 s2)
256                      = (left, right)
257                        where
258                         -- no statistical foundation for this!
259                         left    = StdGen new_s1 t2
260                         right   = StdGen t1 new_s2
261
262                         new_s1 | s1 == 2147483562 = 1
263                                | otherwise        = s1 + 1
264
265                         new_s2 | s2 == 1          = 2147483398
266                                | otherwise        = s2 - 1
267
268                         StdGen t1 t2 = snd (next std)
269 \end{code}
270
271
272 \begin{code}
273 #ifdef __HUGS__
274
275 setStdGen :: StdGen -> IO ()
276 setStdGen sgen = writeIORef theStdGen sgen
277
278 getStdGen :: IO StdGen
279 getStdGen  = readIORef theStdGen
280
281 theStdGen :: IORef StdGen
282 theStdGen  = unsafePerformIO (newIORef (createStdGen 0))
283
284 #else
285
286 global_rng :: STRef RealWorld StdGen
287 global_rng = unsafePerformIO $ do
288    rng <- mkStdRNG 0
289    stToIO (newSTRef rng)
290
291 setStdGen :: StdGen -> IO ()
292 setStdGen sgen = stToIO (writeSTRef global_rng sgen)
293
294 getStdGen :: IO StdGen
295 getStdGen = stToIO (readSTRef global_rng)
296
297 #endif
298
299
300 newStdGen :: IO StdGen
301 newStdGen = do
302   rng <- getStdGen
303   let (a,b) = split rng
304   setStdGen a
305   return b
306
307 getStdRandom :: (StdGen -> (a,StdGen)) -> IO a
308 getStdRandom f = do
309    rng          <- getStdGen
310    let (v, new_rng) = f rng
311    setStdGen new_rng
312    return v
313 \end{code}