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

haskell / random / 400

26 Dec 2024 12:49AM UTC coverage: 68.916% (-0.8%) from 69.751%
400

push

github

web-flow
Merge pull request #171 from haskell/lehins/use-array-for-shuffle

Implement a faster and unbiased version of list shuffling

40 of 66 new or added lines in 4 files covered. (60.61%)

61 existing lines in 2 files now uncovered.

623 of 904 relevant lines covered (68.92%)

1.3 hits per line

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

84.87
/src/System/Random/Stateful.hs
1
{-# LANGUAGE BangPatterns #-}
2
{-# LANGUAGE CPP #-}
3
{-# LANGUAGE FlexibleInstances #-}
4
{-# LANGUAGE FunctionalDependencies #-}
5
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6
{-# LANGUAGE RankNTypes #-}
7
{-# LANGUAGE ScopedTypeVariables #-}
8
{-# LANGUAGE Trustworthy #-}
9
{-# LANGUAGE TypeFamilies #-}
10
{-# LANGUAGE UndecidableInstances #-}
11
-- |
12
-- Module      :  System.Random.Stateful
13
-- Copyright   :  (c) The University of Glasgow 2001
14
-- License     :  BSD-style (see the file LICENSE in the 'random' repository)
15
-- Maintainer  :  libraries@haskell.org
16
-- Stability   :  stable
17
--
18
-- This library deals with the common task of pseudo-random number generation.
19
module System.Random.Stateful
20
  (
21
  -- * Pure Random Generator
22
  module System.Random
23
  -- * Monadic Random Generator
24
  -- $introduction
25

26
  -- * Usage
27
  -- $usagemonadic
28

29
  -- * Mutable pseudo-random number generator interfaces
30
  -- $interfaces
31
  , StatefulGen
32
      ( uniformWord32R
33
      , uniformWord64R
34
      , uniformWord8
35
      , uniformWord16
36
      , uniformWord32
37
      , uniformWord64
38
      , uniformShortByteString
39
      )
40
  , FrozenGen(..)
41
  , ThawedGen(..)
42
  , withMutableGen
43
  , withMutableGen_
44
  , withMutableSeedGen
45
  , withMutableSeedGen_
46
  , randomM
47
  , randomRM
48
  , splitGenM
49
  , splitMutableGenM
50

51
  -- ** Deprecated
52
  , RandomGenM(..)
53

54
  -- * Monadic adapters for pure pseudo-random number generators #monadicadapters#
55
  -- $monadicadapters
56

57
  -- ** Pure adapter in 'MonadState'
58
  , StateGen(..)
59
  , StateGenM(..)
60
  , runStateGen
61
  , runStateGen_
62
  , runStateGenT
63
  , runStateGenT_
64
  , runStateGenST
65
  , runStateGenST_
66
  -- ** Mutable thread-safe adapter in 'IO'
67
  , AtomicGen(..)
68
  , AtomicGenM(..)
69
  , newAtomicGenM
70
  , applyAtomicGen
71
  , globalStdGen
72
  -- ** Mutable adapter in 'IO'
73
  , IOGen(..)
74
  , IOGenM(..)
75
  , newIOGenM
76
  , applyIOGen
77
  -- ** Mutable adapter in 'ST'
78
  , STGen(..)
79
  , STGenM(..)
80
  , newSTGenM
81
  , applySTGen
82
  , runSTGen
83
  , runSTGen_
84
  -- ** Mutable thread-safe adapter in 'STM'
85
  , TGen(..)
86
  , TGenM(..)
87
  , newTGenM
88
  , newTGenMIO
89
  , applyTGen
90

91
  -- * Pseudo-random values of various types
92
  -- $uniform
93
  , Uniform(..)
94
  , uniformViaFiniteM
95
  , UniformRange(..)
96
  , isInRangeOrd
97
  , isInRangeEnum
98

99
  -- ** Lists
100
  , uniformListM
101
  , uniformListRM
102
  , uniformShuffleListM
103

104
  -- ** Generators for sequences of pseudo-random bytes
105
  , uniformByteArrayM
106
  , uniformByteStringM
107
  , uniformShortByteStringM
108

109
  -- * Helper functions for createing instances
110
  -- ** Sequences of bytes
111
  , genByteArrayST
112
  , genShortByteStringIO
113
  , genShortByteStringST
114
  , defaultUnsafeUniformFillMutableByteArray
115
  -- ** Floating point numbers
116
  , uniformDouble01M
117
  , uniformDoublePositive01M
118
  , uniformFloat01M
119
  , uniformFloatPositive01M
120
  -- ** Enum types
121
  , uniformEnumM
122
  , uniformEnumRM
123
  -- ** Word
124
  , uniformWordR
125

126
  -- * Appendix
127

128
  -- ** How to implement 'StatefulGen'
129
  -- $implemenstatefulegen
130

131
  -- ** Floating point number caveats #fpcaveats#
132
  -- $floating
133

134
  -- * References
135
  -- $references
136
  ) where
137

138
import Control.DeepSeq
139
import Control.Monad.IO.Class
140
import Control.Monad.ST
141
import GHC.Conc.Sync (STM, TVar, newTVar, newTVarIO, readTVar, writeTVar)
142
import Control.Monad.State.Strict (MonadState, state)
143
import Data.Coerce
144
import Data.IORef
145
import Data.STRef
146
import Foreign.Storable
147
import System.Random
148
import System.Random.Array (shuffleListM)
149
import System.Random.Internal
150
#if __GLASGOW_HASKELL__ >= 808
151
import GHC.IORef (atomicModifyIORef2Lazy)
152
#endif
153

154

155
-- $introduction
156
--
157
-- This module provides type classes and instances for the following concepts:
158
--
159
-- [Monadic pseudo-random number generators] 'StatefulGen' is an interface to
160
--     monadic pseudo-random number generators.
161
--
162
-- [Monadic adapters] 'StateGenM', 'AtomicGenM', 'IOGenM', 'STGenM` and 'TGenM'
163
--     turn a 'RandomGen' instance into a 'StatefulGen' instance.
164
--
165
-- [Drawing from a range] 'UniformRange' is used to generate a value of a
166
--     type uniformly within a range.
167
--
168
--     This library provides instances of 'UniformRange' for many common
169
--     numeric types.
170
--
171
-- [Drawing from the entire domain of a type] 'Uniform' is used to generate a
172
--     value of a type uniformly over all possible values of that type.
173
--
174
--     This library provides instances of 'Uniform' for many common bounded
175
--     numeric types.
176
--
177
-- $usagemonadic
178
--
179
-- In monadic code, use the relevant 'Uniform' and 'UniformRange' instances to
180
-- generate pseudo-random values via 'uniformM' and 'uniformRM', respectively.
181
--
182
-- As an example, @rollsM@ generates @n@ pseudo-random values of @Word@ in the range @[1,
183
-- 6]@ in a 'StatefulGen' context; given a /monadic/ pseudo-random number generator, you
184
-- can run this probabilistic computation using
185
-- [@mwc-random@](https://hackage.haskell.org/package/mwc-random) as follows:
186
--
187
-- >>> import Control.Monad (replicateM)
188
-- >>> :{
189
-- let rollsM :: StatefulGen g m => Int -> g -> m [Word]
190
--     rollsM n = replicateM n . uniformRM (1, 6)
191
-- :}
192
--
193
-- > import qualified System.Random.MWC as MWC
194
-- > >>> monadicGen <- MWC.create
195
-- > >>> rollsM 10 monadicGen :: IO [Word]
196
-- > [3,4,3,1,4,6,1,6,1,4]
197
--
198
-- Given a /pure/ pseudo-random number generator, you can run the monadic pseudo-random
199
-- number computation @rollsM@ in 'Control.Monad.State.Strict.StateT', 'IO', 'ST' or 'STM'
200
-- context by applying a monadic adapter like 'StateGenM', 'AtomicGenM', 'IOGenM',
201
-- 'STGenM' or 'TGenM' (see [monadic-adapters](#monadicadapters)) to the pure
202
-- pseudo-random number generator.
203
--
204
-- >>> let pureGen = mkStdGen 42
205
-- >>> newIOGenM pureGen >>= rollsM 10 :: IO [Word]
206
-- [1,1,3,2,4,5,3,4,6,2]
207

208
-------------------------------------------------------------------------------
209
-- Pseudo-random number generator interfaces
210
-------------------------------------------------------------------------------
211

212
-- $interfaces
213
--
214
-- Pseudo-random number generators come in two flavours: /pure/ and /monadic/.
215
--
216
-- ['System.Random.RandomGen': pure pseudo-random number generators]
217
--     See "System.Random" module.
218
--
219
-- ['StatefulGen': monadic pseudo-random number generators] These generators mutate their
220
--     own state as they produce pseudo-random values. They generally live in
221
--     'Control.Monad.State.Strict.StateT', 'ST', 'IO' or 'STM' or some other transformer
222
--     on top of those monads.
223
--
224

225
-------------------------------------------------------------------------------
226
-- Monadic adapters
227
-------------------------------------------------------------------------------
228

229
-- $monadicadapters
230
--
231
-- Pure pseudo-random number generators can be used in monadic code via the
232
-- adapters 'StateGenM', 'AtomicGenM', 'IOGenM', 'STGenM' and 'TGenM'
233
--
234
-- * 'StateGenM' can be used in any state monad. With strict
235
--     'Control.Monad.State.Strict.StateT' there is no performance overhead compared to
236
--     using the 'RandomGen' instance directly. 'StateGenM' is /not/ safe to use in the
237
--     presence of exceptions and concurrency.
238
--
239
-- *   'AtomicGenM' is safe in the presence of exceptions and concurrency since
240
--     it performs all actions atomically.
241
--
242
-- *   'IOGenM' is a wrapper around an 'IORef' that holds a pure generator.
243
--     'IOGenM' is safe in the presence of exceptions, but not concurrency.
244
--
245
-- *   'STGenM' is a wrapper around an 'STRef' that holds a pure generator.
246
--     'STGenM' is safe in the presence of exceptions, but not concurrency.
247
--
248
-- *   'TGenM' is a wrapper around a 'TVar' that holds a pure generator. 'TGenM'
249
--     can be used in a software transactional memory monad 'STM`. It is not as
250
--     performant as 'AtomicGenM`, but it can provide stronger guarantees in a
251
--     concurrent setting.
252

253
-- | Interface to operations on 'RandomGen' wrappers like 'IOGenM' and 'StateGenM'.
254
--
255
-- @since 1.2.0
256
class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where
257
  applyRandomGenM :: (r -> (a, r)) -> g -> m a
258
{-# DEPRECATED applyRandomGenM "In favor of `modifyGen`" #-}
259
{-# DEPRECATED RandomGenM "In favor of `FrozenGen`" #-}
260

261
instance (RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m where
262
  applyRandomGenM = applyIOGen
×
263

264
instance (RandomGen r, MonadIO m) => RandomGenM (AtomicGenM r) r m where
265
  applyRandomGenM = applyAtomicGen
×
266

267
instance (RandomGen r, MonadState r m) => RandomGenM (StateGenM r) r m where
268
  applyRandomGenM f _ = state f
×
269

270
instance RandomGen r => RandomGenM (STGenM r s) r (ST s) where
271
  applyRandomGenM = applySTGen
×
272

273
instance RandomGen r => RandomGenM (TGenM r) r STM where
274
  applyRandomGenM = applyTGen
×
275

276

277
-- | Shuffle elements of a list in a uniformly random order.
278
--
279
-- ====__Examples__
280
--
281
-- >>> import System.Random.Stateful
282
-- >>> runStateGen_ (mkStdGen 127) $ uniformShuffleListM "ELVIS"
283
-- "LIVES"
284
--
285
-- @since 1.3.0
286
uniformShuffleListM :: StatefulGen g m => [a] -> g -> m [a]
NEW
287
uniformShuffleListM xs gen = shuffleListM (`uniformWordR` gen) xs
×
288
{-# INLINE uniformShuffleListM #-}
289

290
-- | Runs a mutable pseudo-random number generator from its 'FrozenGen' state.
291
--
292
-- ====__Examples__
293
--
294
-- >>> import Data.Int (Int8)
295
-- >>> withMutableGen (IOGen (mkStdGen 217)) (uniformListM 5) :: IO ([Int8], IOGen StdGen)
296
-- ([-74,37,-50,-2,3],IOGen {unIOGen = StdGen {unStdGen = SMGen 4273268533320920145 15251669095119325999}})
297
--
298
-- @since 1.2.0
299
withMutableGen :: ThawedGen f m => f -> (MutableGen f m -> m a) -> m (a, f)
300
withMutableGen fg action = do
2✔
301
  g <- thawGen fg
2✔
302
  res <- action g
2✔
303
  fg' <- freezeGen g
2✔
304
  pure (res, fg')
2✔
305

306
-- | Same as 'withMutableGen', but only returns the generated value.
307
--
308
-- ====__Examples__
309
--
310
-- >>> import System.Random.Stateful
311
-- >>> let pureGen = mkStdGen 137
312
-- >>> withMutableGen_ (IOGen pureGen) (uniformRM (1 :: Int, 6 :: Int))
313
-- 4
314
--
315
-- @since 1.2.0
316
withMutableGen_ :: ThawedGen f m => f -> (MutableGen f m -> m a) -> m a
317
withMutableGen_ fg action = thawGen fg >>= action
2✔
318

319

320
-- | Just like `withMutableGen`, except uses a `Seed` instead of a frozen generator.
321
--
322
-- @since 1.3.0
323
withMutableSeedGen :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m (a, Seed g)
324
withMutableSeedGen seed f = withSeedM seed (`withMutableGen` f)
×
325

326
-- | Just like `withMutableSeedGen`, except it doesn't return the final generator, only
327
-- the resulting value. This is slightly more efficient, since it doesn't incur overhead
328
-- from freezeing the mutable generator
329
--
330
-- @since 1.3.0
331
withMutableSeedGen_ :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m a
332
withMutableSeedGen_ seed = withMutableGen_ (seedGen seed)
×
333

334

335
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
336
--
337
-- ====__Examples__
338
--
339
-- >>> import System.Random.Stateful
340
-- >>> let pureGen = mkStdGen 139
341
-- >>> g <- newIOGenM pureGen
342
-- >>> randomM g :: IO Double
343
-- 0.33775117339631733
344
--
345
-- You can use type applications to disambiguate the type of the generated numbers:
346
--
347
-- >>> :seti -XTypeApplications
348
-- >>> randomM @Double g
349
-- 0.9156875994165681
350
--
351
-- @since 1.2.0
352
randomM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => MutableGen g m -> m a
353
randomM = flip modifyGen random
2✔
354
{-# INLINE randomM #-}
355

356
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
357
--
358
-- ====__Examples__
359
--
360
-- >>> import System.Random.Stateful
361
-- >>> let pureGen = mkStdGen 137
362
-- >>> g <- newIOGenM pureGen
363
-- >>> randomRM (1, 100) g :: IO Int
364
-- 52
365
--
366
-- You can use type applications to disambiguate the type of the generated numbers:
367
--
368
-- >>> :seti -XTypeApplications
369
-- >>> randomRM @Int (1, 100) g
370
-- 2
371
--
372
-- @since 1.2.0
373
randomRM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => (a, a) -> MutableGen g m -> m a
374
randomRM r = flip modifyGen (randomR r)
2✔
375
{-# INLINE randomRM #-}
376

377
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator. All
378
-- operations are performed atomically.
379
--
380
-- *   'AtomicGenM' is safe in the presence of exceptions and concurrency.
381
-- *   'AtomicGenM' is the slowest of the monadic adapters due to the overhead
382
--     of its atomic operations.
383
--
384
-- @since 1.2.0
385
newtype AtomicGenM g = AtomicGenM { unAtomicGenM :: IORef g}
2✔
386

387

388
-- | Frozen version of mutable `AtomicGenM` generator
389
--
390
-- @since 1.2.0
391
newtype AtomicGen g = AtomicGen { unAtomicGen :: g}
2✔
392
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
393

394
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
395
instance SeedGen g => SeedGen (AtomicGen g) where
396
  type SeedSize (AtomicGen g) = SeedSize g
397
  seedGen = coerce (seedGen :: Seed g -> g)
×
398
  unseedGen = coerce (unseedGen :: g -> Seed g)
×
399

400
-- | Creates a new 'AtomicGenM'.
401
--
402
-- @since 1.2.0
403
newAtomicGenM :: MonadIO m => g -> m (AtomicGenM g)
404
newAtomicGenM = fmap AtomicGenM . liftIO . newIORef
2✔
405

406

407
-- | Global mutable standard pseudo-random number generator. This is the same
408
-- generator that was historically used by `randomIO` and `randomRIO` functions.
409
--
410
-- >>> import Control.Monad (replicateM)
411
-- >>> replicateM 10 (uniformRM ('a', 'z') globalStdGen)
412
-- "tdzxhyfvgr"
413
--
414
-- @since 1.2.1
415
globalStdGen :: AtomicGenM StdGen
416
globalStdGen = AtomicGenM theStdGen
×
417

418

419
instance (RandomGen g, MonadIO m) => StatefulGen (AtomicGenM g) m where
420
  uniformWord32R r = applyAtomicGen (genWord32R r)
2✔
421
  {-# INLINE uniformWord32R #-}
422
  uniformWord64R r = applyAtomicGen (genWord64R r)
2✔
423
  {-# INLINE uniformWord64R #-}
424
  uniformWord8 = applyAtomicGen genWord8
2✔
425
  {-# INLINE uniformWord8 #-}
426
  uniformWord16 = applyAtomicGen genWord16
2✔
427
  {-# INLINE uniformWord16 #-}
428
  uniformWord32 = applyAtomicGen genWord32
2✔
429
  {-# INLINE uniformWord32 #-}
430
  uniformWord64 = applyAtomicGen genWord64
2✔
431
  {-# INLINE uniformWord64 #-}
432

433

434
instance (RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m where
435
  type MutableGen (AtomicGen g) m = AtomicGenM g
436
  freezeGen = fmap AtomicGen . liftIO . readIORef . unAtomicGenM
2✔
437
  modifyGen (AtomicGenM ioRef) f =
2✔
438
    liftIO $ atomicModifyIORefHS ioRef $ \g ->
2✔
439
      case f (AtomicGen g) of
2✔
440
        (a, AtomicGen g') -> (g', a)
2✔
441
  {-# INLINE modifyGen #-}
442

443
instance (RandomGen g, MonadIO m) => ThawedGen (AtomicGen g) m where
444
  thawGen (AtomicGen g) = newAtomicGenM g
2✔
445

446
-- | Atomically applies a pure operation to the wrapped pseudo-random number
447
-- generator.
448
--
449
-- ====__Examples__
450
--
451
-- >>> import System.Random.Stateful
452
-- >>> let pureGen = mkStdGen 137
453
-- >>> g <- newAtomicGenM pureGen
454
-- >>> applyAtomicGen random g :: IO Int
455
-- 7879794327570578227
456
--
457
-- @since 1.2.0
458
applyAtomicGen :: MonadIO m => (g -> (a, g)) -> AtomicGenM g -> m a
459
applyAtomicGen op (AtomicGenM gVar) =
2✔
460
  liftIO $ atomicModifyIORefHS gVar $ \g ->
2✔
461
    case op g of
2✔
462
      (a, g') -> (g', a)
2✔
463
{-# INLINE applyAtomicGen #-}
464

465
-- HalfStrict version of atomicModifyIORef, i.e. strict in the modifcation of the contents
466
-- of the IORef, but not in the result produced.
467
atomicModifyIORefHS :: IORef a -> (a -> (a, b)) -> IO b
468
atomicModifyIORefHS ref f = do
2✔
469
#if __GLASGOW_HASKELL__ >= 808
470
  (_old, (_new, res)) <- atomicModifyIORef2Lazy ref $ \old ->
2✔
471
    case f old of
2✔
472
      r@(!_new, _res) -> r
2✔
473
  pure res
2✔
474
#else
475
  atomicModifyIORef ref $ \old ->
476
    case f old of
477
      r@(!_new, _res) -> r
478
#endif
479
{-# INLINE atomicModifyIORefHS #-}
480

481
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator.
482
--
483
-- *   'IOGenM' is safe in the presence of exceptions, but not concurrency.
484
-- *   'IOGenM' is slower than 'StateGenM' due to the extra pointer indirection.
485
-- *   'IOGenM' is faster than 'AtomicGenM' since the 'IORef' operations used by
486
--     'IOGenM' are not atomic.
487
--
488
-- An example use case is writing pseudo-random bytes into a file:
489
--
490
-- >>> import UnliftIO.Temporary (withSystemTempFile)
491
-- >>> import Data.ByteString (hPutStr)
492
-- >>> let ioGen g = withSystemTempFile "foo.bin" $ \_ h -> uniformRM (0, 100) g >>= flip uniformByteStringM g >>= hPutStr h
493
--
494
-- and then run it:
495
--
496
-- >>> newIOGenM (mkStdGen 1729) >>= ioGen
497
--
498
-- @since 1.2.0
499
newtype IOGenM g = IOGenM { unIOGenM :: IORef g }
2✔
500

501
-- | Frozen version of mutable `IOGenM` generator
502
--
503
-- @since 1.2.0
504
newtype IOGen g = IOGen { unIOGen :: g }
2✔
505
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
506

507
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
508
instance SeedGen g => SeedGen (IOGen g) where
509
  type SeedSize (IOGen g) = SeedSize g
510
  seedGen = coerce (seedGen :: Seed g -> g)
×
511
  unseedGen = coerce (unseedGen :: g -> Seed g)
×
512

513
-- | Creates a new 'IOGenM'.
514
--
515
-- @since 1.2.0
516
newIOGenM :: MonadIO m => g -> m (IOGenM g)
517
newIOGenM = fmap IOGenM . liftIO . newIORef
2✔
518

519

520

521
instance (RandomGen g, MonadIO m) => StatefulGen (IOGenM g) m where
522
  uniformWord32R r = applyIOGen (genWord32R r)
2✔
523
  {-# INLINE uniformWord32R #-}
524
  uniformWord64R r = applyIOGen (genWord64R r)
2✔
525
  {-# INLINE uniformWord64R #-}
526
  uniformWord8 = applyIOGen genWord8
2✔
527
  {-# INLINE uniformWord8 #-}
528
  uniformWord16 = applyIOGen genWord16
2✔
529
  {-# INLINE uniformWord16 #-}
530
  uniformWord32 = applyIOGen genWord32
2✔
531
  {-# INLINE uniformWord32 #-}
532
  uniformWord64 = applyIOGen genWord64
2✔
533
  {-# INLINE uniformWord64 #-}
534

535

536
instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
537
  type MutableGen (IOGen g) m = IOGenM g
538
  freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
2✔
539
  modifyGen (IOGenM ref) f = liftIO $ do
2✔
540
    g <- readIORef ref
2✔
541
    let (a, IOGen g') = f (IOGen g)
2✔
542
    g' `seq` writeIORef ref g'
2✔
543
    pure a
2✔
544
  {-# INLINE modifyGen #-}
545
  overwriteGen (IOGenM ref) = liftIO . writeIORef ref . unIOGen
2✔
546
  {-# INLINE overwriteGen #-}
547

548
instance (RandomGen g, MonadIO m) => ThawedGen (IOGen g) m where
549
  thawGen (IOGen g) = newIOGenM g
2✔
550

551
-- | Applies a pure operation to the wrapped pseudo-random number generator.
552
--
553
-- ====__Examples__
554
--
555
-- >>> import System.Random.Stateful
556
-- >>> let pureGen = mkStdGen 137
557
-- >>> g <- newIOGenM pureGen
558
-- >>> applyIOGen random g :: IO Int
559
-- 7879794327570578227
560
--
561
-- @since 1.2.0
562
applyIOGen :: MonadIO m => (g -> (a, g)) -> IOGenM g -> m a
563
applyIOGen f (IOGenM ref) = liftIO $ do
2✔
564
  g <- readIORef ref
2✔
565
  case f g of
2✔
566
    (a, !g') -> a <$ writeIORef ref g'
2✔
567
{-# INLINE applyIOGen #-}
568

569
-- | Wraps an 'STRef' that holds a pure pseudo-random number generator.
570
--
571
-- *   'STGenM' is safe in the presence of exceptions, but not concurrency.
572
-- *   'STGenM' is slower than 'StateGenM' due to the extra pointer indirection.
573
--
574
-- @since 1.2.0
575
newtype STGenM g s = STGenM { unSTGenM :: STRef s g }
2✔
576

577
-- | Frozen version of mutable `STGenM` generator
578
--
579
-- @since 1.2.0
580
newtype STGen g = STGen { unSTGen :: g }
2✔
581
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
582

583
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
584
instance SeedGen g => SeedGen (STGen g) where
585
  type SeedSize (STGen g) = SeedSize g
586
  seedGen = coerce (seedGen :: Seed g -> g)
×
587
  unseedGen = coerce (unseedGen :: g -> Seed g)
×
588

589
-- | Creates a new 'STGenM'.
590
--
591
-- @since 1.2.0
592
newSTGenM :: g -> ST s (STGenM g s)
593
newSTGenM = fmap STGenM . newSTRef
2✔
594

595

596
instance RandomGen g => StatefulGen (STGenM g s) (ST s) where
597
  uniformWord32R r = applySTGen (genWord32R r)
2✔
598
  {-# INLINE uniformWord32R #-}
599
  uniformWord64R r = applySTGen (genWord64R r)
2✔
600
  {-# INLINE uniformWord64R #-}
601
  uniformWord8 = applySTGen genWord8
2✔
602
  {-# INLINE uniformWord8 #-}
603
  uniformWord16 = applySTGen genWord16
2✔
604
  {-# INLINE uniformWord16 #-}
605
  uniformWord32 = applySTGen genWord32
2✔
606
  {-# INLINE uniformWord32 #-}
607
  uniformWord64 = applySTGen genWord64
2✔
608
  {-# INLINE uniformWord64 #-}
609

610
instance RandomGen g => FrozenGen (STGen g) (ST s) where
611
  type MutableGen (STGen g) (ST s) = STGenM g s
612
  freezeGen = fmap STGen . readSTRef . unSTGenM
2✔
613
  modifyGen (STGenM ref) f = do
2✔
614
    g <- readSTRef ref
2✔
615
    let (a, STGen g') = f (STGen g)
2✔
616
    g' `seq` writeSTRef ref g'
2✔
617
    pure a
2✔
618
  {-# INLINE modifyGen #-}
619
  overwriteGen (STGenM ref) = writeSTRef ref . unSTGen
2✔
620
  {-# INLINE overwriteGen #-}
621

622
instance RandomGen g => ThawedGen (STGen g) (ST s) where
623
  thawGen (STGen g) = newSTGenM g
2✔
624

625

626
-- | Applies a pure operation to the wrapped pseudo-random number generator.
627
--
628
-- ====__Examples__
629
--
630
-- >>> import System.Random.Stateful
631
-- >>> let pureGen = mkStdGen 137
632
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
633
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
634
--
635
-- @since 1.2.0
636
applySTGen :: (g -> (a, g)) -> STGenM g s -> ST s a
637
applySTGen f (STGenM ref) = do
2✔
638
  g <- readSTRef ref
2✔
639
  case f g of
2✔
640
    (a, !g') -> a <$ writeSTRef ref g'
2✔
641
{-# INLINE applySTGen #-}
642

643
-- | Runs a monadic generating action in the `ST` monad using a pure
644
-- pseudo-random number generator.
645
--
646
-- ====__Examples__
647
--
648
-- >>> import System.Random.Stateful
649
-- >>> let pureGen = mkStdGen 137
650
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
651
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
652
--
653
-- @since 1.2.0
654
runSTGen :: RandomGen g => g -> (forall s . STGenM g s -> ST s a) -> (a, g)
655
runSTGen g action = unSTGen <$> runST (withMutableGen (STGen g) action)
1✔
656

657
-- | Runs a monadic generating action in the `ST` monad using a pure
658
-- pseudo-random number generator. Returns only the resulting pseudo-random
659
-- value.
660
--
661
-- ====__Examples__
662
--
663
-- >>> import System.Random.Stateful
664
-- >>> let pureGen = mkStdGen 137
665
-- >>> (runSTGen_ pureGen (\g -> applySTGen random g)) :: Int
666
-- 7879794327570578227
667
--
668
-- @since 1.2.0
669
runSTGen_ :: RandomGen g => g -> (forall s . STGenM g s -> ST s a) -> a
670
runSTGen_ g action = fst $ runSTGen g action
2✔
671

672

673
-- | Wraps a 'TVar' that holds a pure pseudo-random number generator.
674
--
675
-- @since 1.2.1
676
newtype TGenM g = TGenM { unTGenM :: TVar g }
2✔
677

678
-- | Frozen version of mutable `TGenM` generator
679
--
680
-- @since 1.2.1
681
newtype TGen g = TGen { unTGen :: g }
2✔
682
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
683

684
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
685
instance SeedGen g => SeedGen (TGen g) where
686
  type SeedSize (TGen g) = SeedSize g
687
  seedGen = coerce (seedGen :: Seed g -> g)
×
688
  unseedGen = coerce (unseedGen :: g -> Seed g)
×
689

690
-- | Creates a new 'TGenM' in `STM`.
691
--
692
-- @since 1.2.1
693
newTGenM :: g -> STM (TGenM g)
694
newTGenM = fmap TGenM . newTVar
2✔
695

696

697
-- | Creates a new 'TGenM' in `IO`.
698
--
699
-- @since 1.2.1
700
newTGenMIO :: MonadIO m => g -> m (TGenM g)
701
newTGenMIO g = liftIO (TGenM <$> newTVarIO g)
×
702

703

704
-- | @since 1.2.1
705
instance RandomGen g => StatefulGen (TGenM g) STM where
706
  uniformWord32R r = applyTGen (genWord32R r)
2✔
707
  {-# INLINE uniformWord32R #-}
708
  uniformWord64R r = applyTGen (genWord64R r)
2✔
709
  {-# INLINE uniformWord64R #-}
710
  uniformWord8 = applyTGen genWord8
2✔
711
  {-# INLINE uniformWord8 #-}
712
  uniformWord16 = applyTGen genWord16
2✔
713
  {-# INLINE uniformWord16 #-}
714
  uniformWord32 = applyTGen genWord32
2✔
715
  {-# INLINE uniformWord32 #-}
716
  uniformWord64 = applyTGen genWord64
2✔
717
  {-# INLINE uniformWord64 #-}
718

719
-- | @since 1.2.1
720
instance RandomGen g => FrozenGen (TGen g) STM where
721
  type MutableGen (TGen g) STM = TGenM g
722
  freezeGen = fmap TGen . readTVar . unTGenM
2✔
723
  modifyGen (TGenM ref) f = do
2✔
724
    g <- readTVar ref
2✔
725
    let (a, TGen g') = f (TGen g)
2✔
726
    g' `seq` writeTVar ref g'
2✔
727
    pure a
2✔
728
  {-# INLINE modifyGen #-}
729
  overwriteGen (TGenM ref) = writeTVar ref . unTGen
2✔
730
  {-# INLINE overwriteGen #-}
731

732
instance RandomGen g => ThawedGen (TGen g) STM where
733
  thawGen (TGen g) = newTGenM g
2✔
734

735

736
-- | Applies a pure operation to the wrapped pseudo-random number generator.
737
--
738
-- ====__Examples__
739
--
740
-- >>> import Control.Concurrent.STM
741
-- >>> import System.Random.Stateful
742
-- >>> import Data.Int (Int32)
743
-- >>> let pureGen = mkStdGen 137
744
-- >>> stmGen <- newTGenMIO pureGen
745
-- >>> atomically $ applyTGen uniform stmGen :: IO Int32
746
-- 637238067
747
--
748
-- @since 1.2.1
749
applyTGen :: (g -> (a, g)) -> TGenM g -> STM a
750
applyTGen f (TGenM tvar) = do
2✔
751
  g <- readTVar tvar
2✔
752
  case f g of
2✔
753
    (a, !g') -> a <$ writeTVar tvar g'
2✔
754
{-# INLINE applyTGen #-}
755

756
-- $uniform
757
--
758
-- This library provides two type classes to generate pseudo-random values:
759
--
760
-- *   'UniformRange' is used to generate a value of a type uniformly within a
761
--     range.
762
-- *   'Uniform' is used to generate a value of a type uniformly over all
763
--     possible values of that type.
764
--
765
-- Types may have instances for both or just one of 'UniformRange' and
766
-- 'Uniform'. A few examples illustrate this:
767
--
768
-- *   'Int', 'Data.Word.Word16' and 'Bool' are instances of both 'UniformRange' and
769
--     'Uniform'.
770
-- *   'Integer', 'Float' and 'Double' each have an instance for 'UniformRange'
771
--     but no 'Uniform' instance.
772
-- *   A hypothetical type @Radian@ representing angles by taking values in the
773
--     range @[0, 2π)@ has a trivial 'Uniform' instance, but no 'UniformRange'
774
--     instance: the problem is that two given @Radian@ values always span /two/
775
--     ranges, one clockwise and one anti-clockwise.
776
-- *   It is trivial to construct a @Uniform (a, b)@ instance given
777
--     @Uniform a@ and @Uniform b@ (and this library provides this tuple
778
--     instance).
779
-- *   On the other hand, there is no correct way to construct a
780
--     @UniformRange (a, b)@ instance based on just @UniformRange a@ and
781
--     @UniformRange b@.
782

783
-------------------------------------------------------------------------------
784
-- Notes
785
-------------------------------------------------------------------------------
786

787
-- $floating
788
--
789
-- The 'UniformRange' instances for 'Float' and 'Double' use the following
790
-- procedure to generate a random value in a range for @uniformRM (a, b) g@:
791
--
792
-- If \(a = b\), return \(a\). Otherwise:
793
--
794
-- 1.  Generate \(x\) uniformly such that \(0 \leq x \leq 1\).
795
--
796
--     The method by which \(x\) is sampled does not cover all representable
797
--     floating point numbers in the unit interval. The method never generates
798
--     denormal floating point numbers, for example.
799
--
800
-- 2.  Return \(x \cdot a + (1 - x) \cdot b\).
801
--
802
--     Due to rounding errors, floating point operations are neither
803
--     associative nor distributive the way the corresponding operations on
804
--     real numbers are. Additionally, floating point numbers admit special
805
--     values @NaN@ as well as negative and positive infinity.
806
--
807
-- For pathological values, step 2 can yield surprising results.
808
--
809
-- *   The result may be greater than @max a b@.
810
--
811
--     >>> :{
812
--     let (a, b, x) = (-2.13238e-29, -2.1323799e-29, 0.27736077)
813
--         result = x * a + (1 - x) * b :: Float
814
--     in (result, result > max a b)
815
--     :}
816
--     (-2.1323797e-29,True)
817
--
818
-- *   The result may be smaller than @min a b@.
819
--
820
--     >>> :{
821
--     let (a, b, x) = (-1.9087862, -1.908786, 0.4228573)
822
--         result = x * a + (1 - x) * b :: Float
823
--     in (result, result < min a b)
824
--     :}
825
--     (-1.9087863,True)
826
--
827
-- What happens when @NaN@ or @Infinity@ are given to 'uniformRM'? We first
828
-- define them as constants:
829
--
830
-- >>> nan = read "NaN" :: Float
831
-- >>> inf = read "Infinity" :: Float
832
--
833
-- *   If at least one of \(a\) or \(b\) is @NaN@, the result is @NaN@.
834
--
835
--     >>> let (a, b, x) = (nan, 1, 0.5) in x * a + (1 - x) * b
836
--     NaN
837
--     >>> let (a, b, x) = (-1, nan, 0.5) in x * a + (1 - x) * b
838
--     NaN
839
--
840
-- *   If \(a\) is @-Infinity@ and \(b\) is @Infinity@, the result is @NaN@.
841
--
842
--     >>> let (a, b, x) = (-inf, inf, 0.5) in x * a + (1 - x) * b
843
--     NaN
844
--
845
-- *   Otherwise, if \(a\) is @Infinity@ or @-Infinity@, the result is \(a\).
846
--
847
--     >>> let (a, b, x) = (inf, 1, 0.5) in x * a + (1 - x) * b
848
--     Infinity
849
--     >>> let (a, b, x) = (-inf, 1, 0.5) in x * a + (1 - x) * b
850
--     -Infinity
851
--
852
-- *   Otherwise, if \(b\) is @Infinity@ or @-Infinity@, the result is \(b\).
853
--
854
--     >>> let (a, b, x) = (1, inf, 0.5) in x * a + (1 - x) * b
855
--     Infinity
856
--     >>> let (a, b, x) = (1, -inf, 0.5) in x * a + (1 - x) * b
857
--     -Infinity
858
--
859
-- Note that the [GCC 10.1.0 C++ standard library](https://gcc.gnu.org/git/?p=gcc.git;a=blob;f=libstdc%2B%2B-v3/include/bits/random.h;h=19307fbc3ca401976ef6823e8fda893e4a263751;hb=63fa67847628e5f358e7e2e7edb8314f0ee31f30#l1859),
860
-- the [Java 10 standard library](https://docs.oracle.com/javase/10/docs/api/java/util/Random.html#doubles%28double,double%29)
861
-- and [CPython 3.8](https://github.com/python/cpython/blob/3.8/Lib/random.py#L417)
862
-- use the same procedure to generate floating point values in a range.
863
--
864
-- $implemenstatefulegen
865
--
866
-- Typically, a monadic pseudo-random number generator has facilities to save
867
-- and restore its internal state in addition to generating pseudo-random numbers.
868
--
869
-- Here is an example instance for the monadic pseudo-random number generator
870
-- from the @mwc-random@ package:
871
--
872
-- > import qualified System.Random.MWC as MWC
873
-- > import qualified Data.Vector.Generic as G
874
--
875
-- > instance (s ~ PrimState m, PrimMonad m) => StatefulGen (MWC.Gen s) m where
876
-- >   uniformWord8 = MWC.uniform
877
-- >   uniformWord16 = MWC.uniform
878
-- >   uniformWord32 = MWC.uniform
879
-- >   uniformWord64 = MWC.uniform
880
-- >   uniformByteArrayM isPinned n g = stToPrim (genByteArrayST isPinned n (MWC.uniform g))
881
--
882
-- > instance PrimMonad m => FrozenGen MWC.Seed m where
883
-- >   type MutableGen MWC.Seed m = MWC.Gen (PrimState m)
884
-- >   freezeGen = MWC.save
885
-- >   overwriteGen (Gen mv) (Seed v) = G.copy mv v
886
--
887
-- > instance PrimMonad m => ThawedGen MWC.Seed m where
888
-- >   thawGen = MWC.restore
889
--
890
-- === @FrozenGen@
891
--
892
-- `FrozenGen` gives us ability to use most of stateful pseudo-random number generator in
893
-- its immutable form, if one exists that is.  The biggest benefit that can be drawn from
894
-- a polymorphic access to a stateful pseudo-random number generator in a frozen form is
895
-- the ability to serialize, deserialize and possibly even use the stateful generator in a
896
-- pure setting without knowing the actual type of a generator ahead of time. For example
897
-- we can write a function that accepts a frozen state of some pseudo-random number
898
-- generator and produces a short list with random even integers.
899
--
900
-- >>> import Data.Int (Int8)
901
-- >>> import Control.Monad (replicateM)
902
-- >>> :{
903
-- myCustomRandomList :: ThawedGen f m => f -> m [Int8]
904
-- myCustomRandomList f =
905
--   withMutableGen_ f $ \gen -> do
906
--     len <- uniformRM (5, 10) gen
907
--     replicateM len $ do
908
--       x <- uniformM gen
909
--       pure $ if even x then x else x + 1
910
-- :}
911
--
912
-- and later we can apply it to a frozen version of a stateful generator, such as `STGen`:
913
--
914
-- >>> print $ runST $ myCustomRandomList (STGen (mkStdGen 217))
915
-- [-50,-2,4,-8,-58,-40,24,-32,-110,24]
916
--
917
-- Alternatively, instead of discarding the final state of the generator, as it happens
918
-- above, we could have used `withMutableGen`, which together with the result would give
919
-- us back its frozen form. This would allow us to store the end state of our generator
920
-- somewhere for the later reuse.
921
--
922
--
923
-- $references
924
--
925
-- 1. Guy L. Steele, Jr., Doug Lea, and Christine H. Flood. 2014. Fast
926
-- splittable pseudorandom number generators. In Proceedings of the 2014 ACM
927
-- International Conference on Object Oriented Programming Systems Languages &
928
-- Applications (OOPSLA '14). ACM, New York, NY, USA, 453-472. DOI:
929
-- <https://doi.org/10.1145/2660193.2660195>
930

931
-- $setup
932
-- >>> writeIORef theStdGen $ mkStdGen 2021
933
--
934
-- >>> :seti -XFlexibleContexts
935
-- >>> :seti -XFlexibleInstances
936
-- >>> :seti -XMultiParamTypeClasses
937
-- >>> :seti -XTypeFamilies
938
-- >>> :seti -XUndecidableInstances
939
--
940
--
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