1 -----------------------------------------------------------------------------
3 -- Module : System.Random
4 -- Copyright : (c) The University of Glasgow 2001
5 -- License : BSD-style (see the file libraries/base/LICENSE)
7 -- Maintainer : libraries@haskell.org
9 -- Portability : portable
13 -----------------------------------------------------------------------------
20 -- * The 'RandomGen' class, and the 'StdGen' generator
22 RandomGen(next, split, genRange)
26 -- * The 'Random' class
27 , Random ( random, randomR,
31 -- * The global random number generator
48 import CPUTime ( getCPUTime )
49 import Foreign.Ptr ( Ptr, nullPtr )
51 import System.CPUTime ( getCPUTime )
52 import System.Time ( getClockTime, ClockTime(..) )
54 import Data.Char ( isSpace, chr, ord )
55 import System.IO.Unsafe ( unsafePerformIO )
57 import Numeric ( readDec )
59 -- The standard nhc98 implementation of Time.ClockTime does not match
60 -- the extended one expected in this module, so we lash-up a quick
63 data ClockTime = TOD Integer ()
64 foreign import ccall "time.h time" readtime :: Ptr () -> IO Int
65 getClockTime :: IO ClockTime
66 getClockTime = do t <- readtime nullPtr; return (TOD (toInteger t) ())
71 This library deals with the common task of pseudo-random
72 number generation. The library makes it possible to generate
73 repeatable results, by starting with a specified initial random
74 number generator; or to get different results on each run by using the
75 system-initialised generator, or by supplying a seed from some other
78 The library is split into two layers:
80 * A core /random number generator/ provides a supply of bits. The class
81 'RandomGen' provides a common interface to such generators.
83 * The class 'Random' provides a way to extract particular values from
84 a random number generator. For example, the 'Float' instance of 'Random'
85 allows one to generate random values of type 'Float'.
87 [Comment found in this file when merging with Library Report:]
89 The June 1988 (v31 \#6) issue of the Communications of the ACM has an
90 article by Pierre L'Ecuyer called, /Efficient and Portable Combined
91 Random Number Generators/. Here is the Portable Combined Generator of
92 L'Ecuyer for 32-bit computers. It has a period of roughly 2.30584e18.
94 Transliterator: Lennart Augustsson
98 -- | The class 'RandomGen' provides a common interface to random number
101 class RandomGen g where
103 -- |The 'next' operation allows one to extract at least 30 bits (one 'Int''s
104 -- worth) from the generator, returning a new generator as well. The
105 -- integer returned may be positive or negative.
106 next :: g -> (Int, g)
108 -- |The 'split' operation allows one to obtain two distinct random number
109 -- generators. This is very useful in functional programs (for example, when
110 -- passing a random number generator down to recursive calls), but very
111 -- little work has been done on statistically robust implementations of
112 -- 'split' ([1,4] are the only examples we know of).
115 -- |The 'genRange' operation yields the range of values returned by
118 -- It is required that:
120 -- * If @(a,b) = 'genRange' g@, then @a < b@.
122 -- * 'genRange' is not strict.
124 -- The second condition ensures that 'genRange' cannot examine its
125 -- argument, and hence the value it returns can be determined only by the
126 -- instance of 'RandomGen'. That in turn allows an implementation to make
127 -- a single call to 'genRange' to establish a generator's range, without
128 -- being concerned that the generator returned by (say) 'next' might have
129 -- a different range to the generator passed to 'next'.
130 genRange :: g -> (Int,Int)
133 genRange g = (minBound,maxBound)
135 {- |The "System.Random" library provides one instance of 'RandomGen', the
136 abstract data type 'StdGen'.
138 The 'StdGen' instance of 'RandomGen' has a 'genRange' of at least 30 bits.
140 The result of repeatedly using 'next' should be at least as statistically
141 robust as the /Minimal Standard Random Number Generator/ described by
142 ["System.Random\#Park", "System.Random\#Carta"].
143 Until more is known about implementations of 'split', all we require is
144 that 'split' deliver generators that are (a) not identical and
145 (b) independently robust in the sense just given.
147 The 'Show'\/'Read' instances of 'StdGen' provide a primitive way to save the
148 state of a random number generator.
149 It is required that @'read' ('show' g) == g@.
151 In addition, 'read' may be used to map an arbitrary string (not necessarily one
152 produced by 'show') onto a value of type 'StdGen'. In general, the 'read'
153 instance of 'StdGen' has the following properties:
155 * It guarantees to succeed on any string.
157 * It guarantees to consume only a finite portion of the string.
159 * Different argument strings are likely to result in different results.
166 instance RandomGen StdGen where
170 instance Show StdGen where
171 showsPrec p (StdGen s1 s2) =
176 instance Read StdGen where
177 readsPrec _p = \ r ->
180 _ -> [stdFromString r] -- because it shouldn't ever fail.
183 (s1, r1) <- readDec (dropWhile isSpace r)
184 (s2, r2) <- readDec (dropWhile isSpace r1)
185 return (StdGen s1 s2, r2)
188 If we cannot unravel the StdGen from a string, create
189 one based on the string given.
191 stdFromString :: String -> (StdGen, String)
192 stdFromString s = (mkStdGen num, rest)
193 where (cs, rest) = splitAt 6 s
194 num = foldl (\a x -> x + 3 * a) 1 (map ord cs)
198 The function 'mkStdGen' provides an alternative way of producing an initial
199 generator, by mapping an 'Int' into a generator. Again, distinct arguments
200 should be likely to produce distinct generators.
202 Programmers may, of course, supply their own instances of 'RandomGen'.
204 mkStdGen :: Int -> StdGen -- why not Integer ?
206 | s < 0 = mkStdGen (-s)
207 | otherwise = StdGen (s1+1) (s2+1)
209 (q, s1) = s `divMod` 2147483562
210 s2 = q `mod` 2147483398
212 createStdGen :: Integer -> StdGen
214 | s < 0 = createStdGen (-s)
215 | otherwise = StdGen (fromInteger (s1+1)) (fromInteger (s2+1))
217 (q, s1) = s `divMod` 2147483562
218 s2 = q `mod` 2147483398
220 -- FIXME: 1/2/3 below should be ** (vs@30082002) XXX
223 With a source of random number supply in hand, the 'Random' class allows the
224 programmer to extract random values of a variety of types.
226 Minimal complete definition: 'randomR' and 'random'.
231 -- | Takes a range /(lo,hi)/ and a random number generator
232 -- /g/, and returns a random value uniformly distributed in the closed
233 -- interval /[lo,hi]/, together with a new generator. It is unspecified
234 -- what happens if /lo>hi/. For continuous types there is no requirement
235 -- that the values /lo/ and /hi/ are ever produced, but they may be,
236 -- depending on the implementation and the interval.
237 randomR :: RandomGen g => (a,a) -> g -> (a,g)
239 -- | The same as 'randomR', but using a default range determined by the type:
241 -- * For bounded types (instances of 'Bounded', such as 'Char'),
242 -- the range is normally the whole type.
244 -- * For fractional types, the range is normally the semi-closed interval
247 -- * For 'Integer', the range is (arbitrarily) the range of 'Int'.
248 random :: RandomGen g => g -> (a, g)
250 -- | Plural variant of 'randomR', producing an infinite list of
251 -- random values instead of returning a new generator.
252 randomRs :: RandomGen g => (a,a) -> g -> [a]
253 randomRs ival g = x : randomRs ival g' where (x,g') = randomR ival g
255 -- | Plural variant of 'random', producing an infinite list of
256 -- random values instead of returning a new generator.
257 randoms :: RandomGen g => g -> [a]
258 randoms g = (\(x,g') -> x : randoms g') (random g)
260 -- | A variant of 'randomR' that uses the global random number generator
261 -- (see "System.Random#globalrng").
262 randomRIO :: (a,a) -> IO a
263 randomRIO range = getStdRandom (randomR range)
265 -- | A variant of 'random' that uses the global random number generator
266 -- (see "System.Random#globalrng").
268 randomIO = getStdRandom random
271 instance Random Int where
272 randomR (a,b) g = randomIvalInteger (toInteger a, toInteger b) g
273 random g = randomR (minBound,maxBound) g
275 instance Random Char where
277 case (randomIvalInteger (toInteger (ord a), toInteger (ord b)) g) of
279 random g = randomR (minBound,maxBound) g
281 instance Random Bool where
283 case (randomIvalInteger (toInteger (bool2Int a), toInteger (bool2Int b)) g) of
284 (x, g) -> (int2Bool x, g)
292 random g = randomR (minBound,maxBound) g
294 instance Random Integer where
295 randomR ival g = randomIvalInteger ival g
296 random g = randomR (toInteger (minBound::Int), toInteger (maxBound::Int)) g
298 instance Random Double where
299 randomR ival g = randomIvalDouble ival id g
300 random g = randomR (0::Double,1) g
302 -- hah, so you thought you were saving cycles by using Float?
303 instance Random Float where
304 random g = randomIvalDouble (0::Double,1) realToFrac g
305 randomR (a,b) g = randomIvalDouble (realToFrac a, realToFrac b) realToFrac g
307 mkStdRNG :: Integer -> IO StdGen
310 (TOD sec _) <- getClockTime
311 return (createStdGen (sec * 12345 + ct + o))
313 randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
314 randomIvalInteger (l,h) rng
315 | l > h = randomIvalInteger (h,l) rng
316 | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod` k), rng')
327 f (n-1) (fromIntegral x + acc * b) g'
329 randomIvalDouble :: (RandomGen g, Fractional a) => (Double, Double) -> (Double -> a) -> g -> (a, g)
330 randomIvalDouble (l,h) fromDouble rng
331 | l > h = randomIvalDouble (h,l) fromDouble rng
333 case (randomIvalInteger (toInteger (minBound::Int), toInteger (maxBound::Int)) rng) of
337 fromDouble ((l+h)/2) +
338 fromDouble ((h-l) / realToFrac intRange) *
339 fromIntegral (x::Int)
344 intRange = toInteger (maxBound::Int) - toInteger (minBound::Int)
346 iLogBase :: Integer -> Integer -> Integer
347 iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b)
349 stdNext :: StdGen -> (Int, StdGen)
350 stdNext (StdGen s1 s2) = (z', StdGen s1'' s2'')
351 where z' = if z < 1 then z + 2147483562 else z
355 s1' = 40014 * (s1 - k * 53668) - k * 12211
356 s1'' = if s1' < 0 then s1' + 2147483563 else s1'
359 s2' = 40692 * (s2 - k' * 52774) - k' * 3791
360 s2'' = if s2' < 0 then s2' + 2147483399 else s2'
362 stdSplit :: StdGen -> (StdGen, StdGen)
363 stdSplit std@(StdGen s1 s2)
366 -- no statistical foundation for this!
367 left = StdGen new_s1 t2
368 right = StdGen t1 new_s2
370 new_s1 | s1 == 2147483562 = 1
373 new_s2 | s2 == 1 = 2147483398
376 StdGen t1 t2 = snd (next std)
378 -- The global random number generator
380 {- $globalrng #globalrng#
382 There is a single, implicit, global random number generator of type
383 'StdGen', held in some global variable maintained by the 'IO' monad. It is
384 initialised automatically in some system-dependent fashion, for example, by
385 using the time of day, or Linux's kernel random number generator. To get
386 deterministic behaviour, use 'setStdGen'.
389 -- |Sets the global random number generator.
390 setStdGen :: StdGen -> IO ()
391 setStdGen sgen = writeIORef theStdGen sgen
393 -- |Gets the global random number generator.
394 getStdGen :: IO StdGen
395 getStdGen = readIORef theStdGen
397 theStdGen :: IORef StdGen
398 theStdGen = unsafePerformIO $ do
402 -- |Applies 'split' to the current global random generator,
403 -- updates it with one of the results, and returns the other.
404 newStdGen :: IO StdGen
407 let (a,b) = split rng
411 {- |Uses the supplied function to get a value from the current global
412 random generator, and updates the global generator with the new generator
413 returned by the function. For example, @rollDice@ gets a random integer
417 > rollDice = getStdRandom (randomR (1,6))
421 getStdRandom :: (StdGen -> (a,StdGen)) -> IO a
424 let (v, new_rng) = f rng
430 1. FW Burton and RL Page, /Distributed random number generation/,
431 Journal of Functional Programming, 2(2):203-212, April 1992.
433 2. SK #Park# Park, and KW Miller, /Random number generators -
434 good ones are hard to find/, Comm ACM 31(10), Oct 1988, pp1192-1201.
436 3. DG #Carta# Carta, /Two fast implementations of the minimal standard
437 random number generator/, Comm ACM, 33(1), Jan 1990, pp87-88.
439 4. P Hellekalek, /Don\'t trust parallel Monte Carlo/,
440 Department of Mathematics, University of Salzburg,
441 <http://random.mat.sbg.ac.at/~peter/pads98.ps>, 1998.
443 The Web site <http://random.mat.sbg.ac.at/> is a great source of information.