[project @ 2002-08-30 12:32:44 by stolz]
[haskell-directory.git] / System / Random.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  System.Random
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  provisional
9 -- Portability :  portable
10 --
11 -- Random numbers.
12 --
13 -----------------------------------------------------------------------------
14
15 module System.Random
16         (
17
18         -- $intro
19
20         -- * The 'RandomGen' class, and the 'StdGen' generator
21
22           RandomGen(next, split, genRange)
23         , StdGen
24         , mkStdGen
25
26         -- * The 'Random' class
27         , Random ( random,   randomR,
28                    randoms,  randomRs,
29                    randomIO, randomRIO )
30
31         -- * The global random number generator
32
33         -- $globalrng
34
35         , getStdRandom
36         , getStdGen
37         , setStdGen
38         , newStdGen
39
40         -- * References
41         -- $references
42
43         ) where
44
45 import Prelude
46
47 import System.CPUTime   ( getCPUTime )
48 import Data.Char        ( isSpace, chr, ord )
49 import System.IO.Unsafe ( unsafePerformIO )
50 import Data.IORef
51
52 #ifdef __GLASGOW_HASKELL__
53 import GHC.Show         ( showSignedInt, showSpace )
54 import Numeric          ( readDec )
55 import GHC.IOBase       ( unsafePerformIO, stToIO )
56 import System.Time      ( getClockTime, ClockTime(..) )
57 #endif
58
59 {- $intro
60
61 The "Random" library deals with the common task of pseudo-random
62 number generation. The library makes it possible to generate
63 repeatable results, by starting with a specified initial random
64 number generator; or to get different results on each run by using the 
65 system-initialised generator, or by supplying a seed from some other
66 source.
67
68 The library is split into two layers: 
69
70 * A core /random number generator/ provides a supply of bits. The class
71 'RandomGen' provides a common interface to such generators.
72
73 * The class 'Random' provides a way to extract particular values from
74 a random number generator. For example, the 'Float' instance of 'Random'
75 allows one to generate random values of type 'Float'.
76
77 [Comment found in this file when merging with Library Report:]
78
79 The June 1988 (v31 \#6) issue of the Communications of the ACM has an
80 article by Pierre L'Ecuyer called, /Efficient and Portable Combined
81 Random Number Generators/.  Here is the Portable Combined Generator of
82 L'Ecuyer for 32-bit computers.  It has a period of roughly 2.30584e18.
83
84 Transliterator: Lennart Augustsson
85
86 -}
87
88 -- |RandomGen
89 -- The class 'RandomGen' provides a common interface to random number generators.
90
91 class RandomGen g where
92
93    -- |The 'next' operation allows one to extract at least 30 bits (one 'Int''s
94    -- worth) from the generator, returning a new generator as well.  The
95    -- integer returned may be positive or negative.
96    next     :: g -> (Int, g)
97
98    -- |The 'split' operation allows one to obtain two distinct random number
99    -- generators. This is very useful in functional programs (for example, when
100    -- passing a random number generator down to recursive calls), but very
101    -- little work has been done on statistically robust implementations of
102    -- @split ([1,4]@ are the only examples we know of).
103    split    :: g -> (g, g)
104
105    genRange :: g -> (Int,Int)
106
107    -- default mathod
108    genRange g = (minBound,maxBound)
109
110 {- |The "Random" library provides one instance of 'RandomGen', the abstract data
111 type 'StdGen'.
112
113 The result of repeatedly using next should be at least as statistically robust
114 as the /Minimal Standard Random Number Generator/ described by
115 ["System.Random\#Park", "System.Random\#Carta"]. Until more
116 is known about implementations of 'split', all we require is that 'split' deliver
117 generators that are (a) not identical and (b) independently robust in the sense
118 just given.
119
120 The 'show'\/'Read' instances of 'StdGen' provide a primitive way to save the
121 state of a random number generator. It is required that @read (show g) == g@.
122
123 In addition, 'read' may be used to map an arbitrary string (not necessarily one
124 produced by 'show') onto a value of type 'StdGen'. In general, the 'read'
125 instance of 'StdGen' has the following properties: 
126
127 * It guarantees to succeed on any string. 
128
129 *It guarantees to consume only a finite portion of the string. 
130
131 * Different argument strings are likely to result in different results.
132
133 The function 'mkStdGen' provides an alternative way of producing an initial
134 generator, by mapping an 'Int' into a generator. Again, distinct arguments
135 should be likely to produce distinct generators.
136
137 Programmers may, of course, supply their own instances of 'RandomGen'.
138
139 -}
140
141 data StdGen 
142  = StdGen Int Int
143
144 instance RandomGen StdGen where
145   next  = stdNext
146   split = stdSplit
147
148 #ifdef __GLASGOW_HASKELL__
149 instance Show StdGen where
150   showsPrec p (StdGen s1 s2) = 
151      showSignedInt p s1 . 
152      showSpace          . 
153      showSignedInt p s2
154 #endif
155
156 #ifdef __HUGS__
157 instance Show StdGen where
158   showsPrec p (StdGen s1 s2) = 
159      showsPrec p s1 . 
160      showChar ' ' .
161      showsPrec p s2
162 #endif
163
164 instance Read StdGen where
165   readsPrec _p = \ r ->
166      case try_read r of
167        r@[_] -> r
168        _   -> [stdFromString r] -- because it shouldn't ever fail.
169     where 
170       try_read r = do
171          (s1, r1) <- readDec (dropWhile isSpace r)
172          (s2, r2) <- readDec (dropWhile isSpace r1)
173          return (StdGen s1 s2, r2)
174
175 {-
176  If we cannot unravel the StdGen from a string, create
177  one based on the string given.
178 -}
179 stdFromString         :: String -> (StdGen, String)
180 stdFromString s        = (mkStdGen num, rest)
181         where (cs, rest) = splitAt 6 s
182               num        = foldl (\a x -> x + 3 * a) 1 (map ord cs)
183
184
185 mkStdGen :: Int -> StdGen -- why not Integer ?
186 mkStdGen s
187  | s < 0     = mkStdGen (-s)
188  | otherwise = StdGen (s1+1) (s2+1)
189       where
190         (q, s1) = s `divMod` 2147483562
191         s2      = q `mod` 2147483398
192
193 createStdGen :: Integer -> StdGen
194 createStdGen s
195  | s < 0     = createStdGen (-s)
196  | otherwise = StdGen (fromInteger (s1+1)) (fromInteger (s2+1))
197       where
198         (q, s1) = s `divMod` 2147483562
199         s2      = q `mod` 2147483398
200
201 -- FIXME: 1/2/3 below should be ** (vs@30082002) XXX
202
203 {- |The 'Random' class
204 With a source of random number supply in hand, the 'Random' class allows the
205 programmer to extract random values of a variety of types.
206
207 * 'randomR' takes a range /(lo,hi)/ and a random number generator /g/, and returns
208 a random value uniformly distributed in the closed interval /[lo,hi]/, together
209 with a new generator. It is unspecified what happens if /lo>hi/. For continuous
210 types there is no requirement that the values /lo/ and /hi/ are ever produced,
211 but they may be, depending on the implementation and the interval.
212
213 * 'random' does the same as 'randomR', but does not take a range.
214
215 (1) For bounded types (instances of 'Bounded', such as 'Char'), the range is
216 normally the whole type.
217
218 (2) For fractional types, the range is normally the semi-closed interval @[0,1)@.
219
220 (3) For 'Integer', the range is (arbitrarily) the range of 'Int'.
221
222 * The plural versions, 'randomRs' and 'randoms', produce an infinite list of
223 random values, and do not return a new generator.
224
225 * The 'IO' versions, 'randomRIO' and 'randomIO', use the global random number
226 generator (see Section 17.3
227 <http://www.haskell.org/onlinelibrary/random.html#global-rng>).
228 -}
229
230 class Random a where
231   -- |Minimal complete definition: 'random' and 'randomR'
232   random  :: RandomGen g => g -> (a, g)
233   randomR :: RandomGen g => (a,a) -> g -> (a,g)
234
235   -- |Default methods  
236   randoms  :: RandomGen g => g -> [a]
237   randoms  g      = x : randoms g' where (x,g') = random g
238
239   randomRs :: RandomGen g => (a,a) -> g -> [a]
240   randomRs ival g = x : randomRs ival g' where (x,g') = randomR ival g
241
242   randomIO  :: IO a
243   randomIO         = getStdRandom random
244
245   randomRIO :: (a,a) -> IO a
246   randomRIO range  = getStdRandom (randomR range)
247
248
249 instance Random Int where
250   randomR (a,b) g = randomIvalInteger (toInteger a, toInteger b) g
251   random g        = randomR (minBound,maxBound) g
252
253 instance Random Char where
254   randomR (a,b) g = 
255       case (randomIvalInteger (toInteger (ord a), toInteger (ord b)) g) of
256         (x,g) -> (chr x, g)
257   random g        = randomR (minBound,maxBound) g
258
259 instance Random Bool where
260   randomR (a,b) g = 
261       case (randomIvalInteger (toInteger (bool2Int a), toInteger (bool2Int b)) g) of
262         (x, g) -> (int2Bool x, g)
263        where
264          bool2Int False = 0
265          bool2Int True  = 1
266
267          int2Bool 0     = False
268          int2Bool _     = True
269
270   random g        = randomR (minBound,maxBound) g
271  
272 instance Random Integer where
273   randomR ival g = randomIvalInteger ival g
274   random g       = randomR (toInteger (minBound::Int), toInteger (maxBound::Int)) g
275
276 instance Random Double where
277   randomR ival g = randomIvalDouble ival id g
278   random g       = randomR (0::Double,1) g
279   
280 -- hah, so you thought you were saving cycles by using Float?
281 instance Random Float where
282   random g        = randomIvalDouble (0::Double,1) realToFrac g
283   randomR (a,b) g = randomIvalDouble (realToFrac a, realToFrac b) realToFrac g
284
285 #ifdef __GLASGOW_HASKELL__
286 mkStdRNG :: Integer -> IO StdGen
287 mkStdRNG o = do
288     ct          <- getCPUTime
289     (TOD sec _) <- getClockTime
290     return (createStdGen (sec * 12345 + ct + o))
291 #endif
292
293 #ifdef __HUGS__
294 mkStdRNG :: Integer -> IO StdGen
295 mkStdRNG o = do
296     ct          <- getCPUTime
297     return (createStdGen (ct + o))
298 #endif
299
300 randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
301 randomIvalInteger (l,h) rng
302  | l > h     = randomIvalInteger (h,l) rng
303  | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng')
304      where
305        k = h - l + 1
306        b = 2147483561
307        n = iLogBase b k
308
309        f 0 acc g = (acc, g)
310        f n acc g = 
311           let
312            (x,g')   = next g
313           in
314           f (n-1) (fromIntegral x + acc * b) g'
315
316 randomIvalDouble :: (RandomGen g, Fractional a) => (Double, Double) -> (Double -> a) -> g -> (a, g)
317 randomIvalDouble (l,h) fromDouble rng 
318   | l > h     = randomIvalDouble (h,l) fromDouble rng
319   | otherwise = 
320        case (randomIvalInteger (toInteger (minBound::Int), toInteger (maxBound::Int)) rng) of
321          (x, rng') -> 
322             let
323              scaled_x = 
324                 fromDouble ((l+h)/2) + 
325                 fromDouble ((h-l) / realToFrac intRange) *
326                 fromIntegral (x::Int)
327             in
328             (scaled_x, rng')
329
330 intRange :: Integer
331 intRange  = toInteger (maxBound::Int) - toInteger (minBound::Int)
332
333 iLogBase :: Integer -> Integer -> Integer
334 iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b)
335
336 stdNext :: StdGen -> (Int, StdGen)
337 stdNext (StdGen s1 s2) = (z', StdGen s1'' s2'')
338         where   z'   = if z < 1 then z + 2147483562 else z
339                 z    = s1'' - s2''
340
341                 k    = s1 `quot` 53668
342                 s1'  = 40014 * (s1 - k * 53668) - k * 12211
343                 s1'' = if s1' < 0 then s1' + 2147483563 else s1'
344     
345                 k'   = s2 `quot` 52774
346                 s2'  = 40692 * (s2 - k' * 52774) - k' * 3791
347                 s2'' = if s2' < 0 then s2' + 2147483399 else s2'
348
349 stdSplit            :: StdGen -> (StdGen, StdGen)
350 stdSplit std@(StdGen s1 s2)
351                      = (left, right)
352                        where
353                         -- no statistical foundation for this!
354                         left    = StdGen new_s1 t2
355                         right   = StdGen t1 new_s2
356
357                         new_s1 | s1 == 2147483562 = 1
358                                | otherwise        = s1 + 1
359
360                         new_s2 | s2 == 1          = 2147483398
361                                | otherwise        = s2 - 1
362
363                         StdGen t1 t2 = snd (next std)
364
365 -- The global random number generator
366
367 {- $globalrng
368
369 There is a single, implicit, global random number generator of type
370 'StdGen', held in some global variable maintained by the 'IO' monad. It is
371 initialised automatically in some system-dependent fashion, for example, by
372 using the time of day, or Linux's kernel random number generator. To get
373 deterministic behaviour, use 'setStdGen'.
374 -}
375
376 -- |'setStdGen' sets the global random number generator.
377 setStdGen :: StdGen -> IO ()
378 setStdGen sgen = writeIORef theStdGen sgen
379
380 -- |'getStdGen' gets the global random number generator.
381 getStdGen :: IO StdGen
382 getStdGen  = readIORef theStdGen
383
384 -- |'newStdGen' applies 'split' to the current global random generator, updates it
385 -- with one of the results, and returns the other.
386 theStdGen :: IORef StdGen
387 theStdGen  = unsafePerformIO $ do
388    rng <- mkStdRNG 0
389    newIORef rng
390
391 newStdGen :: IO StdGen
392 newStdGen = do
393   rng <- getStdGen
394   let (a,b) = split rng
395   setStdGen a
396   return b
397
398 {- |'getStdRandom' uses the supplied function to get a value from the current
399 global random generator, and updates the global generator with the new generator
400 returned by the function. For example, 'rollDice' gets a random integer between 1 and 6: 
401
402 >  rollDice :: IO Int
403 >  rollDice = getStdRandom (randomR (1,6))
404
405 -}
406
407 getStdRandom :: (StdGen -> (a,StdGen)) -> IO a
408 getStdRandom f = do
409    rng          <- getStdGen
410    let (v, new_rng) = f rng
411    setStdGen new_rng
412    return v
413
414 {- $references
415
416 * [1] FW Burton and RL Page, /Distributed random number generation/,
417 Journal of Functional Programming, 2(2):203-212, April 1992.
418
419 * [2] SK #Park# Park, and KW Miller, /Random number generators -
420 good ones are hard to find/, Comm ACM 31(10), Oct 1988, pp1192-1201.
421
422 * [3] DG #Carta# Carta, /Two fast implementations of the minimal standard
423 random number generator/, Comm ACM, 33(1), Jan 1990, pp87-88.
424
425 * [4] P Hellekalek, /Don\'t trust parallel Monte Carlo/,
426 Department of Mathematics, University of Salzburg,
427 <http://random.mat.sbg.ac.at/~peter/pads98.ps>, 1998.
428
429 The Web site <http://random.mat.sbg.ac.at/> is a great source of information.
430
431 -}