• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

haskell / random / 295

27 Nov 2023 12:22AM UTC coverage: 71.879% (-0.1%) from 71.978%
295

push

github

web-flow
Merge pull request #155 from haskell/lehins/mkStdGen64

Add `mkStdGen64`.

0 of 1 new or added line in 1 file covered. (0.0%)

3 existing lines in 1 file now uncovered.

524 of 729 relevant lines covered (71.88%)

1.36 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

96.77
/src/System/Random.hs
1
{-# LANGUAGE CPP #-}
2
{-# LANGUAGE DefaultSignatures #-}
3
{-# LANGUAGE Trustworthy #-}
4

5
-- |
6
-- Module      :  System.Random
7
-- Copyright   :  (c) The University of Glasgow 2001
8
-- License     :  BSD-style (see the file LICENSE in the 'random' repository)
9
-- Maintainer  :  libraries@haskell.org
10
-- Stability   :  stable
11
--
12
-- This library deals with the common task of pseudo-random number generation.
13
module System.Random
14
  (
15
  -- * Introduction
16
  -- $introduction
17

18
  -- * Usage
19
  -- $usagepure
20

21
  -- * Pure number generator interface
22
  -- $interfaces
23
    RandomGen
24
      ( split
25
      , genWord8
26
      , genWord16
27
      , genWord32
28
      , genWord64
29
      , genWord32R
30
      , genWord64R
31
      , unsafeUniformFillMutableByteArray
32
      )
33
  , uniform
34
  , uniformR
35
  , Random(..)
36
  , Uniform
37
  , UniformRange
38
  , Finite
39
  -- * Generators for sequences of pseudo-random bytes
40
  -- ** Lists
41
  , uniforms
42
  , uniformRs
43
  , uniformList
44
  , uniformListR
45
  -- ** Bytes
46
  , uniformByteArray
47
  , uniformByteString
48
  , uniformFillMutableByteArray
49
  , genByteString
50
  , genShortByteString
51

52
  -- ** Standard pseudo-random number generator
53
  , StdGen
54
  , mkStdGen
55
  , mkStdGen64
56
  , initStdGen
57

58
  -- ** Global standard pseudo-random number generator
59
  -- $globalstdgen
60
  , getStdRandom
61
  , getStdGen
62
  , setStdGen
63
  , newStdGen
64
  , randomIO
65
  , randomRIO
66

67
  -- * Compatibility and reproducibility
68
  -- ** Backwards compatibility and deprecations
69
  , genRange
70
  , next
71
  -- $deprecations
72

73
  -- ** Reproducibility
74
  -- $reproducibility
75

76
  -- * Notes for pseudo-random number generator implementors
77
  -- ** How to implement 'RandomGen'
78
  -- $implementrandomgen
79

80
  -- * References
81
  -- $references
82
  ) where
83

84
import Control.Arrow
85
import Control.Monad.IO.Class
86
import Control.Monad.State.Strict
87
import Data.ByteString (ByteString)
88
import Data.Int
89
import Data.IORef
90
import Data.Word
91
import Foreign.C.Types
92
import GHC.Exts
93
import System.Random.GFinite (Finite)
94
import System.Random.Internal
95
import qualified System.Random.SplitMix as SM
96

97
-- $introduction
98
--
99
-- This module provides type classes and instances for the following concepts:
100
--
101
-- [Pure pseudo-random number generators] 'RandomGen' is an interface to pure
102
--     pseudo-random number generators.
103
--
104
--     'StdGen', the standard pseudo-random number generator provided in this
105
--     library, is an instance of 'RandomGen'. It uses the SplitMix
106
--     implementation provided by the
107
--     <https://hackage.haskell.org/package/splitmix splitmix> package.
108
--     Programmers may, of course, supply their own instances of 'RandomGen'.
109
--
110
-- $usagepure
111
--
112
-- In pure code, use 'uniform' and 'uniformR' to generate pseudo-random values
113
-- with a pure pseudo-random number generator like 'StdGen'.
114
--
115
-- >>> :{
116
-- let rolls :: RandomGen g => Int -> g -> [Word]
117
--     rolls n = fst . uniformListR n (1, 6)
118
--     pureGen = mkStdGen 137
119
-- in
120
--     rolls 10 pureGen :: [Word]
121
-- :}
122
-- [4,2,6,1,6,6,5,1,1,5]
123
--
124
-- To run use a /monadic/ pseudo-random computation in pure code with a pure
125
-- pseudo-random number generator, use 'runStateGen' and its variants.
126
--
127
-- >>> :{
128
-- let rollsM :: StatefulGen g m => Int -> g -> m [Word]
129
--     rollsM n = uniformListRM n (1, 6)
130
--     pureGen = mkStdGen 137
131
-- in
132
--     runStateGen_ pureGen (rollsM 10) :: [Word]
133
-- :}
134
-- [4,2,6,1,6,6,5,1,1,5]
135

136
-------------------------------------------------------------------------------
137
-- Pseudo-random number generator interfaces
138
-------------------------------------------------------------------------------
139

140
-- $interfaces
141
--
142
-- Pseudo-random number generators come in two flavours: /pure/ and /monadic/.
143
--
144
-- ['RandomGen': pure pseudo-random number generators] These generators produce
145
--     a new pseudo-random value together with a new instance of the
146
--     pseudo-random number generator.
147
--
148
--     Pure pseudo-random number generators should implement 'split' if they
149
--     are /splittable/, that is, if there is an efficient method to turn one
150
--     generator into two. The pseudo-random numbers produced by the two
151
--     resulting generators should not be correlated. See [1] for some
152
--     background on splittable pseudo-random generators.
153
--
154
-- ['System.Random.Stateful.StatefulGen': monadic pseudo-random number generators]
155
--     See "System.Random.Stateful" module
156
--
157

158
-- | Generates a value uniformly distributed over all possible values of that
159
-- type.
160
--
161
-- This is a pure version of 'System.Random.Stateful.uniformM'.
162
--
163
-- ====__Examples__
164
--
165
-- >>> import System.Random
166
-- >>> let pureGen = mkStdGen 137
167
-- >>> uniform pureGen :: (Bool, StdGen)
168
-- (True,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
169
--
170
-- You can use type applications to disambiguate the type of the generated numbers:
171
--
172
-- >>> :set -XTypeApplications
173
-- >>> uniform @Bool pureGen
174
-- (True,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
175
--
176
-- @since 1.2.0
177
uniform :: (Uniform a, RandomGen g) => g -> (a, g)
178
uniform g = runStateGen g uniformM
2✔
179
{-# INLINE uniform #-}
180

181
-- | Generates a value uniformly distributed over the provided range, which
182
-- is interpreted as inclusive in the lower and upper bound.
183
--
184
-- *   @uniformR (1 :: Int, 4 :: Int)@ generates values uniformly from the set
185
--     \(\{1,2,3,4\}\)
186
--
187
-- *   @uniformR (1 :: Float, 4 :: Float)@ generates values uniformly from the
188
--     set \(\{x\;|\;1 \le x \le 4\}\)
189
--
190
-- The following law should hold to make the function always defined:
191
--
192
-- > uniformR (a, b) = uniformR (b, a)
193
--
194
-- This is a pure version of 'System.Random.Stateful.uniformRM'.
195
--
196
-- ====__Examples__
197
--
198
-- >>> import System.Random
199
-- >>> let pureGen = mkStdGen 137
200
-- >>> uniformR (1 :: Int, 4 :: Int) pureGen
201
-- (4,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
202
--
203
-- You can use type applications to disambiguate the type of the generated numbers:
204
--
205
-- >>> :set -XTypeApplications
206
-- >>> uniformR @Int (1, 4) pureGen
207
-- (4,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
208
--
209
-- @since 1.2.0
210
uniformR :: (UniformRange a, RandomGen g) => (a, a) -> g -> (a, g)
211
uniformR r g = runStateGen g (uniformRM r)
2✔
212
{-# INLINE uniformR #-}
213

214
-- | Produce an infinite list of pseudo-random values. Integrates nicely with list
215
-- fusion. Naturally, there is no way to recover the final generator, therefore either use
216
-- `split` before calling `uniforms` or use `uniformList` instead.
217
--
218
-- Similar to `randoms`, except it relies on `Uniform` type class instead of `Random`
219
--
220
-- ====__Examples__
221
--
222
-- >>> let gen = mkStdGen 2023
223
-- >>> import Data.Word (Word16)
224
-- >>> take 5 $ uniforms gen :: [Word16]
225
-- [56342,15850,25292,14347,13919]
226
--
227
-- @since 1.3.0
228
uniforms :: (Uniform a, RandomGen g) => g -> [a]
229
uniforms g0 =
2✔
230
  build $ \cons _nil ->
2✔
231
    let go g =
2✔
232
          case uniform g of
2✔
233
            (x, g') -> x `seq` (x `cons` go g')
2✔
234
     in go g0
2✔
235
{-# INLINE uniforms #-}
236

237
-- | Produce an infinite list of pseudo-random values in a specified range. Same as
238
-- `uniforms`, integrates nicely with list fusion. There is no way to recover the final
239
-- generator, therefore either use `split` before calling `uniformRs` or use
240
-- `uniformListR` instead.
241
--
242
-- Similar to `randomRs`, except it relies on `UniformRange` type class instead of
243
-- `Random`.
244
--
245
-- ====__Examples__
246
--
247
-- >>> let gen = mkStdGen 2023
248
-- >>> take 5 $ uniformRs (10, 100) gen :: [Int]
249
-- [32,86,21,57,39]
250
--
251
-- @since 1.3.0
252
uniformRs :: (UniformRange a, RandomGen g) => (a, a) -> g -> [a]
253
uniformRs range g0 =
2✔
254
  build $ \cons _nil ->
2✔
255
    let go g =
2✔
256
          case uniformR range g of
2✔
257
            (x, g') -> x `seq` (x `cons` go g')
2✔
258
     in go g0
2✔
259
{-# INLINE uniformRs #-}
260

261
-- | Produce a list of the supplied length with elements generated uniformly.
262
--
263
-- See `uniformListM` for a stateful counterpart.
264
--
265
-- ====__Examples__
266
--
267
-- >>> let gen = mkStdGen 2023
268
-- >>> import Data.Word (Word16)
269
-- >>> uniformList 5 gen :: ([Word16], StdGen)
270
-- ([56342,15850,25292,14347,13919],StdGen {unStdGen = SMGen 6446154349414395371 1920468677557965761})
271
--
272
-- @since 1.3.0
273
uniformList :: (Uniform a, RandomGen g) => Int -> g -> ([a], g)
274
uniformList n g = runStateGen g (uniformListM n)
2✔
275
{-# INLINE uniformList #-}
276

277
-- | Produce a list of the supplied length with elements generated uniformly.
278
--
279
-- See `uniformListM` for a stateful counterpart.
280
--
281
-- ====__Examples__
282
--
283
-- >>> let gen = mkStdGen 2023
284
-- >>> uniformListR 10 (20, 30) gen :: ([Int], StdGen)
285
-- ([26,30,27,24,30,25,27,21,27,27],StdGen {unStdGen = SMGen 12965503083958398648 1920468677557965761})
286
--
287
-- @since 1.3.0
288
uniformListR :: (UniformRange a, RandomGen g) => Int -> (a, a) -> g -> ([a], g)
289
uniformListR n r g = runStateGen g (uniformListRM n r)
2✔
290
{-# INLINE uniformListR #-}
291

292
-- | Generates a 'ByteString' of the specified size using a pure pseudo-random
293
-- number generator. See 'uniformByteStringM' for the monadic version.
294
--
295
-- ====__Examples__
296
--
297
-- >>> import System.Random
298
-- >>> import Data.ByteString
299
-- >>> let pureGen = mkStdGen 137
300
-- >>> unpack . fst . genByteString 10 $ pureGen
301
-- [51,123,251,37,49,167,90,109,1,4]
302
--
303
-- /Note/ - This function is equivalet to `uniformByteString` and will be deprecated in
304
-- the next major release.
305
--
306
-- @since 1.2.0
307
genByteString :: RandomGen g => Int -> g -> (ByteString, g)
308
genByteString n g = runStateGenST g (uniformByteStringM n)
2✔
309
{-# INLINE genByteString #-}
310

311
-- | The class of types for which random values can be generated. Most
312
-- instances of `Random` will produce values that are uniformly distributed on the full
313
-- range, but for those types without a well-defined "full range" some sensible default
314
-- subrange will be selected.
315
--
316
-- 'Random' exists primarily for backwards compatibility with version 1.1 of
317
-- this library. In new code, use the better specified 'Uniform' and
318
-- 'UniformRange' instead.
319
--
320
-- @since 1.0.0
321
class Random a where
322

323
  -- | Takes a range /(lo,hi)/ and a pseudo-random number generator
324
  -- /g/, and returns a pseudo-random value uniformly distributed over the
325
  -- closed interval /[lo,hi]/, together with a new generator. It is unspecified
326
  -- what happens if /lo>hi/, but usually the values will simply get swapped.
327
  --
328
  -- >>> let gen = mkStdGen 2021
329
  -- >>> fst $ randomR ('a', 'z') gen
330
  -- 't'
331
  -- >>> fst $ randomR ('z', 'a') gen
332
  -- 't'
333
  --
334
  -- For continuous types there is no requirement that the values /lo/ and /hi/ are ever
335
  -- produced, but they may be, depending on the implementation and the interval.
336
  --
337
  -- There is no requirement to follow the @Ord@ instance and the concept of range can be
338
  -- defined on per type basis. For example product types will treat their values
339
  -- independently:
340
  --
341
  -- >>> fst $ randomR (('a', 5.0), ('z', 10.0)) $ mkStdGen 2021
342
  -- ('t',6.240232662366563)
343
  --
344
  -- In case when a lawful range is desired `uniformR` should be used
345
  -- instead.
346
  --
347
  -- @since 1.0.0
348
  {-# INLINE randomR #-}
349
  randomR :: RandomGen g => (a, a) -> g -> (a, g)
350
  default randomR :: (RandomGen g, UniformRange a) => (a, a) -> g -> (a, g)
351
  randomR r g = runStateGen g (uniformRM r)
2✔
352

353
  -- | The same as 'randomR', but using a default range determined by the type:
354
  --
355
  -- * For bounded types (instances of 'Bounded', such as 'Char'),
356
  --   the range is normally the whole type.
357
  --
358
  -- * For floating point types, the range is normally the closed interval @[0,1]@.
359
  --
360
  -- * For 'Integer', the range is (arbitrarily) the range of 'Int'.
361
  --
362
  -- @since 1.0.0
363
  {-# INLINE random #-}
364
  random  :: RandomGen g => g -> (a, g)
365
  default random :: (RandomGen g, Uniform a) => g -> (a, g)
366
  random g = runStateGen g uniformM
2✔
367

368
  -- | Plural variant of 'randomR', producing an infinite list of
369
  -- pseudo-random values instead of returning a new generator.
370
  --
371
  -- @since 1.0.0
372
  {-# INLINE randomRs #-}
373
  randomRs :: RandomGen g => (a,a) -> g -> [a]
374
  randomRs ival g = build (\cons _nil -> buildRandoms cons (randomR ival) g)
2✔
375

376
  -- | Plural variant of 'random', producing an infinite list of
377
  -- pseudo-random values instead of returning a new generator.
378
  --
379
  -- @since 1.0.0
380
  {-# INLINE randoms #-}
381
  randoms  :: RandomGen g => g -> [a]
382
  randoms  g      = build (\cons _nil -> buildRandoms cons random g)
2✔
383

384

385
-- | Produce an infinite list-equivalent of pseudo-random values.
386
--
387
-- ====__Examples__
388
--
389
-- >>> import System.Random
390
-- >>> let pureGen = mkStdGen 137
391
-- >>> (take 4 . buildRandoms (:) random $ pureGen) :: [Int]
392
-- [7879794327570578227,6883935014316540929,-1519291874655152001,2353271688382626589]
393
--
394
{-# INLINE buildRandoms #-}
395
buildRandoms :: RandomGen g
396
             => (a -> as -> as)  -- ^ E.g. @(:)@ but subject to fusion
397
             -> (g -> (a,g))     -- ^ E.g. 'random'
398
             -> g                -- ^ A 'RandomGen' instance
399
             -> as
400
buildRandoms cons rand = go
2✔
401
  where
402
    -- The seq fixes part of #4218 and also makes fused Core simpler:
403
    -- https://gitlab.haskell.org/ghc/ghc/-/issues/4218
404
    go g = x `seq` (x `cons` go g') where (x,g') = rand g
2✔
405

406
-- | /Note/ - `random` generates values in the `Int` range
407
instance Random Integer where
408
  random = first (toInteger :: Int -> Integer) . random
2✔
409
  {-# INLINE random #-}
410
instance Random Int8
411
instance Random Int16
412
instance Random Int32
413
instance Random Int64
414
instance Random Int
415
instance Random Word
416
instance Random Word8
417
instance Random Word16
418
instance Random Word32
419
instance Random Word64
420
#if __GLASGOW_HASKELL__ >= 802
421
instance Random CBool
422
#endif
423
instance Random CChar
424
instance Random CSChar
425
instance Random CUChar
426
instance Random CShort
427
instance Random CUShort
428
instance Random CInt
429
instance Random CUInt
430
instance Random CLong
431
instance Random CULong
432
instance Random CPtrdiff
433
instance Random CSize
434
instance Random CWchar
435
instance Random CSigAtomic
436
instance Random CLLong
437
instance Random CULLong
438
instance Random CIntPtr
439
instance Random CUIntPtr
440
instance Random CIntMax
441
instance Random CUIntMax
442
-- | /Note/ - `random` produces values in the closed range @[0,1]@.
443
instance Random CFloat where
444
  randomR r = coerce . randomR (coerce r :: (Float, Float))
2✔
445
  {-# INLINE randomR #-}
446
  random = first CFloat . random
2✔
447
  {-# INLINE random #-}
448
-- | /Note/ - `random` produces values in the closed range @[0,1]@.
449
instance Random CDouble where
450
  randomR r = coerce . randomR (coerce r :: (Double, Double))
2✔
451
  {-# INLINE randomR #-}
452
  random = first CDouble . random
2✔
453
  {-# INLINE random #-}
454

455
instance Random Char
456
instance Random Bool
457
-- | /Note/ - `random` produces values in the closed range @[0,1]@.
458
instance Random Double where
459
  randomR r g = runStateGen g (uniformRM r)
2✔
460
  {-# INLINE randomR #-}
461
  -- We return 1 - uniformDouble01M here for backwards compatibility with
462
  -- v1.2.0. Just return the result of uniformDouble01M in the next major
463
  -- version.
464
  random g = runStateGen g (fmap (1 -) . uniformDouble01M)
2✔
465
  {-# INLINE random #-}
466
-- | /Note/ - `random` produces values in the closed range @[0,1]@.
467
instance Random Float where
468
  randomR r g = runStateGen g (uniformRM r)
2✔
469
  {-# INLINE randomR #-}
470
  -- We return 1 - uniformFloat01M here for backwards compatibility with
471
  -- v1.2.0. Just return the result of uniformFloat01M in the next major
472
  -- version.
473
  random g = runStateGen g (fmap (1 -) . uniformFloat01M)
2✔
474
  {-# INLINE random #-}
475

476

477

478
-- | Initialize 'StdGen' using system entropy (i.e. @\/dev\/urandom@) when it is
479
-- available, while falling back on using system time as the seed.
480
--
481
-- @since 1.2.1
482
initStdGen :: MonadIO m => m StdGen
UNCOV
483
initStdGen = liftIO (StdGen <$> SM.initSMGen)
×
484

485

486
-- | /Note/ - `randomR` treats @a@ and @b@ types independently
487
instance (Random a, Random b) => Random (a, b) where
488
  randomR ((al, bl), (ah, bh)) = runState $
2✔
489
    (,) <$> state (randomR (al, ah)) <*> state (randomR (bl, bh))
2✔
490
  {-# INLINE randomR #-}
491
  random = runState $ (,) <$> state random <*> state random
2✔
492
  {-# INLINE random #-}
493

494
-- | /Note/ - `randomR` treats @a@, @b@ and @c@ types independently
495
instance (Random a, Random b, Random c) => Random (a, b, c) where
496
  randomR ((al, bl, cl), (ah, bh, ch)) = runState $
2✔
497
    (,,) <$> state (randomR (al, ah))
2✔
498
         <*> state (randomR (bl, bh))
2✔
499
         <*> state (randomR (cl, ch))
2✔
500
  {-# INLINE randomR #-}
501
  random = runState $ (,,) <$> state random <*> state random <*> state random
2✔
502
  {-# INLINE random #-}
503

504
-- | /Note/ - `randomR` treats @a@, @b@, @c@ and @d@ types independently
505
instance (Random a, Random b, Random c, Random d) => Random (a, b, c, d) where
506
  randomR ((al, bl, cl, dl), (ah, bh, ch, dh)) = runState $
2✔
507
    (,,,) <$> state (randomR (al, ah))
2✔
508
          <*> state (randomR (bl, bh))
2✔
509
          <*> state (randomR (cl, ch))
2✔
510
          <*> state (randomR (dl, dh))
2✔
511
  {-# INLINE randomR #-}
512
  random = runState $
2✔
513
    (,,,) <$> state random <*> state random <*> state random <*> state random
2✔
514
  {-# INLINE random #-}
515

516
-- | /Note/ - `randomR` treats @a@, @b@, @c@, @d@ and @e@ types independently
517
instance (Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e) where
518
  randomR ((al, bl, cl, dl, el), (ah, bh, ch, dh, eh)) = runState $
2✔
519
    (,,,,) <$> state (randomR (al, ah))
2✔
520
           <*> state (randomR (bl, bh))
2✔
521
           <*> state (randomR (cl, ch))
2✔
522
           <*> state (randomR (dl, dh))
2✔
523
           <*> state (randomR (el, eh))
2✔
524
  {-# INLINE randomR #-}
525
  random = runState $
2✔
526
    (,,,,) <$> state random <*> state random <*> state random <*> state random <*> state random
2✔
527
  {-# INLINE random #-}
528

529
-- | /Note/ - `randomR` treats @a@, @b@, @c@, @d@, @e@ and @f@ types independently
530
instance (Random a, Random b, Random c, Random d, Random e, Random f) =>
531
  Random (a, b, c, d, e, f) where
532
  randomR ((al, bl, cl, dl, el, fl), (ah, bh, ch, dh, eh, fh)) = runState $
2✔
533
    (,,,,,) <$> state (randomR (al, ah))
2✔
534
            <*> state (randomR (bl, bh))
2✔
535
            <*> state (randomR (cl, ch))
2✔
536
            <*> state (randomR (dl, dh))
2✔
537
            <*> state (randomR (el, eh))
2✔
538
            <*> state (randomR (fl, fh))
2✔
539
  {-# INLINE randomR #-}
540
  random = runState $
2✔
541
    (,,,,,) <$> state random
2✔
542
            <*> state random
2✔
543
            <*> state random
2✔
544
            <*> state random
2✔
545
            <*> state random
2✔
546
            <*> state random
2✔
547
  {-# INLINE random #-}
548

549
-- | /Note/ - `randomR` treats @a@, @b@, @c@, @d@, @e@, @f@ and @g@ types independently
550
instance (Random a, Random b, Random c, Random d, Random e, Random f, Random g) =>
551
  Random (a, b, c, d, e, f, g) where
552
  randomR ((al, bl, cl, dl, el, fl, gl), (ah, bh, ch, dh, eh, fh, gh)) = runState $
2✔
553
    (,,,,,,) <$> state (randomR (al, ah))
2✔
554
             <*> state (randomR (bl, bh))
2✔
555
             <*> state (randomR (cl, ch))
2✔
556
             <*> state (randomR (dl, dh))
2✔
557
             <*> state (randomR (el, eh))
2✔
558
             <*> state (randomR (fl, fh))
2✔
559
             <*> state (randomR (gl, gh))
2✔
560
  {-# INLINE randomR #-}
561
  random = runState $
2✔
562
    (,,,,,,) <$> state random
2✔
563
             <*> state random
2✔
564
             <*> state random
2✔
565
             <*> state random
2✔
566
             <*> state random
2✔
567
             <*> state random
2✔
568
             <*> state random
2✔
569
  {-# INLINE random #-}
570

571
-------------------------------------------------------------------------------
572
-- Global pseudo-random number generator
573
-------------------------------------------------------------------------------
574

575
-- $globalstdgen
576
--
577
-- There is a single, implicit, global pseudo-random number generator of type
578
-- 'StdGen', held in a global mutable variable that can be manipulated from
579
-- within the 'IO' monad. It is also available as
580
-- 'System.Random.Stateful.globalStdGen', therefore it is recommended to use the
581
-- new "System.Random.Stateful" interface to explicitly operate on the global
582
-- pseudo-random number generator.
583
--
584
-- It is initialised with 'initStdGen', although it is possible to override its
585
-- value with 'setStdGen'. All operations on the global pseudo-random number
586
-- generator are thread safe, however in presence of concurrency they are
587
-- naturally become non-deterministic. Moreover, relying on the global mutable
588
-- state makes it hard to know which of the dependent libraries are using it as
589
-- well, making it unpredictable in the local context. Precisely of this reason,
590
-- the global pseudo-random number generator is only suitable for uses in
591
-- applications, test suites, etc. and is advised against in development of
592
-- reusable libraries.
593
--
594
-- It is also important to note that either using 'StdGen' with pure functions
595
-- from other sections of this module or by relying on
596
-- 'System.Random.Stateful.runStateGen' from stateful interface does not only
597
-- give us deterministic behaviour without requiring 'IO', but it is also more
598
-- efficient.
599

600

601
-- | Sets the global pseudo-random number generator. Overwrites the contents of
602
-- 'System.Random.Stateful.globalStdGen'
603
--
604
-- @since 1.0.0
605
setStdGen :: MonadIO m => StdGen -> m ()
UNCOV
606
setStdGen = liftIO . writeIORef theStdGen
×
607

608
-- | Gets the global pseudo-random number generator. Extracts the contents of
609
-- 'System.Random.Stateful.globalStdGen'
610
--
611
-- @since 1.0.0
612
getStdGen :: MonadIO m => m StdGen
613
getStdGen = liftIO $ readIORef theStdGen
2✔
614

615
-- | Applies 'split' to the current global pseudo-random generator
616
-- 'System.Random.Stateful.globalStdGen', updates it with one of the results,
617
-- and returns the other.
618
--
619
-- @since 1.0.0
620
newStdGen :: MonadIO m => m StdGen
621
newStdGen = liftIO $ atomicModifyIORef' theStdGen split
2✔
622

623
-- | Uses the supplied function to get a value from the current global
624
-- random generator, and updates the global generator with the new generator
625
-- returned by the function. For example, @rollDice@ produces a pseudo-random integer
626
-- between 1 and 6:
627
--
628
-- >>> rollDice = getStdRandom (randomR (1, 6))
629
-- >>> replicateM 10 (rollDice :: IO Int)
630
-- [5,6,6,1,1,6,4,2,4,1]
631
--
632
-- This is an outdated function and it is recommended to switch to its
633
-- equivalent 'System.Random.Stateful.applyAtomicGen' instead, possibly with the
634
-- 'System.Random.Stateful.globalStdGen' if relying on the global state is
635
-- acceptable.
636
--
637
-- >>> import System.Random.Stateful
638
-- >>> rollDice = applyAtomicGen (uniformR (1, 6)) globalStdGen
639
-- >>> replicateM 10 (rollDice :: IO Int)
640
-- [4,6,1,1,4,4,3,2,1,2]
641
--
642
-- @since 1.0.0
643
getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a
644
getStdRandom f = liftIO $ atomicModifyIORef' theStdGen (swap . f)
2✔
645
  where swap (v, g) = (g, v)
2✔
646

647

648
-- | A variant of 'System.Random.Stateful.randomRM' that uses the global
649
-- pseudo-random number generator 'System.Random.Stateful.globalStdGen'
650
--
651
-- >>> randomRIO (2020, 2100) :: IO Int
652
-- 2040
653
--
654
-- Similar to 'randomIO', this function is equivalent to @'getStdRandom'
655
-- 'randomR'@ and is included in this interface for historical reasons and
656
-- backwards compatibility. It is recommended to use
657
-- 'System.Random.Stateful.uniformRM' instead, possibly with the
658
-- 'System.Random.Stateful.globalStdGen' if relying on the global state is
659
-- acceptable.
660
--
661
-- >>> import System.Random.Stateful
662
-- >>> uniformRM (2020, 2100) globalStdGen :: IO Int
663
-- 2079
664
--
665
-- @since 1.0.0
666
randomRIO :: (Random a, MonadIO m) => (a, a) -> m a
UNCOV
667
randomRIO range = getStdRandom (randomR range)
×
668

669
-- | A variant of 'System.Random.Stateful.randomM' that uses the global
670
-- pseudo-random number generator 'System.Random.Stateful.globalStdGen'.
671
--
672
-- >>> import Data.Int
673
-- >>> randomIO :: IO Int32
674
-- -1580093805
675
--
676
-- This function is equivalent to @'getStdRandom' 'random'@ and is included in
677
-- this interface for historical reasons and backwards compatibility. It is
678
-- recommended to use 'System.Random.Stateful.uniformM' instead, possibly with
679
-- the 'System.Random.Stateful.globalStdGen' if relying on the global state is
680
-- acceptable.
681
--
682
-- >>> import System.Random.Stateful
683
-- >>> uniformM globalStdGen :: IO Int32
684
-- -1649127057
685
--
686
-- @since 1.0.0
687
randomIO :: (Random a, MonadIO m) => m a
688
randomIO = getStdRandom random
2✔
689

690
-------------------------------------------------------------------------------
691
-- Notes
692
-------------------------------------------------------------------------------
693

694
-- $implementrandomgen
695
--
696
-- Consider these points when writing a 'RandomGen' instance for a given pure
697
-- pseudo-random number generator:
698
--
699
-- *   If the pseudo-random number generator has a power-of-2 modulus, that is,
700
--     it natively outputs @2^n@ bits of randomness for some @n@, implement
701
--     'genWord8', 'genWord16', 'genWord32' and 'genWord64'. See below for more
702
--     details.
703
--
704
-- *   If the pseudo-random number generator does not have a power-of-2
705
--     modulus, implement 'next' and 'genRange'. See below for more details.
706
--
707
-- *   If the pseudo-random number generator is splittable, implement 'split'.
708
--     If there is no suitable implementation, 'split' should fail with a
709
--     helpful error message.
710
--
711
-- === How to implement 'RandomGen' for a pseudo-random number generator with power-of-2 modulus
712
--
713
-- Suppose you want to implement a [permuted congruential
714
-- generator](https://en.wikipedia.org/wiki/Permuted_congruential_generator).
715
--
716
-- >>> data PCGen = PCGen !Word64 !Word64
717
--
718
-- It produces a full 'Word32' of randomness per iteration.
719
--
720
-- >>> import Data.Bits
721
-- >>> :{
722
-- let stepGen :: PCGen -> (Word32, PCGen)
723
--     stepGen (PCGen state inc) = let
724
--       newState = state * 6364136223846793005 + (inc .|. 1)
725
--       xorShifted = fromIntegral (((state `shiftR` 18) `xor` state) `shiftR` 27) :: Word32
726
--       rot = fromIntegral (state `shiftR` 59) :: Word32
727
--       out = (xorShifted `shiftR` (fromIntegral rot)) .|. (xorShifted `shiftL` fromIntegral ((-rot) .&. 31))
728
--       in (out, PCGen newState inc)
729
-- :}
730
--
731
-- >>> fst $ stepGen $ snd $ stepGen (PCGen 17 29)
732
-- 3288430965
733
--
734
-- You can make it an instance of 'RandomGen' as follows:
735
--
736
-- >>> :{
737
-- instance RandomGen PCGen where
738
--   genWord32 = stepGen
739
--   split _ = error "PCG is not splittable"
740
-- :}
741
--
742
--
743
-- === How to implement 'RandomGen' for a pseudo-random number generator without a power-of-2 modulus
744
--
745
-- __We do not recommend you implement any new pseudo-random number generators without a power-of-2 modulus.__
746
--
747
-- Pseudo-random number generators without a power-of-2 modulus perform
748
-- /significantly worse/ than pseudo-random number generators with a power-of-2
749
-- modulus with this library. This is because most functionality in this
750
-- library is based on generating and transforming uniformly pseudo-random
751
-- machine words, and generating uniformly pseudo-random machine words using a
752
-- pseudo-random number generator without a power-of-2 modulus is expensive.
753
--
754
-- The pseudo-random number generator from
755
-- <https://dl.acm.org/doi/abs/10.1145/62959.62969 L’Ecuyer (1988)> natively
756
-- generates an integer value in the range @[1, 2147483562]@. This is the
757
-- generator used by this library before it was replaced by SplitMix in version
758
-- 1.2.
759
--
760
-- >>> data LegacyGen = LegacyGen !Int32 !Int32
761
-- >>> :{
762
-- let legacyNext :: LegacyGen -> (Int, LegacyGen)
763
--     legacyNext (LegacyGen s1 s2) = (fromIntegral z', LegacyGen s1'' s2'') where
764
--       z' = if z < 1 then z + 2147483562 else z
765
--       z = s1'' - s2''
766
--       k = s1 `quot` 53668
767
--       s1'  = 40014 * (s1 - k * 53668) - k * 12211
768
--       s1'' = if s1' < 0 then s1' + 2147483563 else s1'
769
--       k' = s2 `quot` 52774
770
--       s2' = 40692 * (s2 - k' * 52774) - k' * 3791
771
--       s2'' = if s2' < 0 then s2' + 2147483399 else s2'
772
-- :}
773
--
774
-- You can make it an instance of 'RandomGen' as follows:
775
--
776
-- >>> :{
777
-- instance RandomGen LegacyGen where
778
--   next = legacyNext
779
--   genRange _ = (1, 2147483562)
780
--   split _ = error "Not implemented"
781
-- :}
782
--
783
-- $deprecations
784
--
785
-- Version 1.2 mostly maintains backwards compatibility with version 1.1. This
786
-- has a few consequences users should be aware of:
787
--
788
-- *   The type class 'Random' is only provided for backwards compatibility.
789
--     New code should use 'Uniform' and 'UniformRange' instead.
790
--
791
-- *   The methods 'next' and 'genRange' in 'RandomGen' are deprecated and only
792
--     provided for backwards compatibility. New instances of 'RandomGen' should
793
--     implement word-based methods instead. See below for more information
794
--     about how to write a 'RandomGen' instance.
795
--
796
-- *   This library provides instances for 'Random' for some unbounded types
797
--     for backwards compatibility. For an unbounded type, there is no way
798
--     to generate a value with uniform probability out of its entire domain, so
799
--     the 'random' implementation for unbounded types actually generates a
800
--     value based on some fixed range.
801
--
802
--     For 'Integer', 'random' generates a value in the 'Int' range. For 'Float'
803
--     and 'Double', 'random' generates a floating point value in the range @[0,
804
--     1)@.
805
--
806
--     This library does not provide 'Uniform' instances for any unbounded
807
--     types.
808
--
809
-- $reproducibility
810
--
811
-- If you have two builds of a particular piece of code against this library,
812
-- any deterministic function call should give the same result in the two
813
-- builds if the builds are
814
--
815
-- *   compiled against the same major version of this library
816
-- *   on the same architecture (32-bit or 64-bit)
817
--
818
-- $references
819
--
820
-- 1. Guy L. Steele, Jr., Doug Lea, and Christine H. Flood. 2014. Fast
821
-- splittable pseudorandom number generators. In Proceedings of the 2014 ACM
822
-- International Conference on Object Oriented Programming Systems Languages &
823
-- Applications (OOPSLA '14). ACM, New York, NY, USA, 453-472. DOI:
824
-- <https://doi.org/10.1145/2660193.2660195>
825

826
-- $setup
827
--
828
-- >>> import Control.Monad (replicateM)
829
-- >>> import Data.List (unfoldr)
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc