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

haskell / random / 429

05 Jul 2025 06:41PM UTC coverage: 69.035% (+0.3%) from 68.696%
429

push

github

web-flow
Merge 4e091cbf2 into 1592c8382

141 of 209 new or added lines in 6 files covered. (67.46%)

98 existing lines in 6 files now uncovered.

651 of 943 relevant lines covered (69.03%)

1.3 hits per line

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

85.25
/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
-- |
13
-- Module      :  System.Random.Stateful
14
-- Copyright   :  (c) The University of Glasgow 2001
15
-- License     :  BSD-style (see the file LICENSE in the 'random' repository)
16
-- Maintainer  :  libraries@haskell.org
17
-- Stability   :  stable
18
--
19
-- This library deals with the common task of pseudo-random number generation.
20
module System.Random.Stateful (
21
  -- * Monadic Random Generator
22
  -- $introduction
23

24
  -- * Usage
25
  -- $usagemonadic
26

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

49
  -- ** Deprecated
50
  RandomGenM (..),
51

52
  -- * Monadic adapters for pure pseudo-random number generators #monadicadapters#
53
  -- $monadicadapters
54

55
  -- ** Pure adapter in 'MonadState'
56
  StateGen (..),
57
  StateGenM (..),
58
  runStateGen,
59
  runStateGen_,
60
  runStateGenT,
61
  runStateGenT_,
62
  runStateGenST,
63
  runStateGenST_,
64

65
  -- ** Mutable thread-safe adapter in 'IO'
66
  AtomicGen (..),
67
  AtomicGenM (..),
68
  newAtomicGenM,
69
  applyAtomicGen,
70
  globalStdGen,
71

72
  -- ** Mutable adapter in 'IO'
73
  IOGen (..),
74
  IOGenM (..),
75
  newIOGenM,
76
  applyIOGen,
77

78
  -- ** Mutable adapter in 'ST'
79
  STGen (..),
80
  STGenM (..),
81
  newSTGenM,
82
  applySTGen,
83
  runSTGen,
84
  runSTGen_,
85

86
  -- ** Mutable thread-safe adapter in 'STM'
87
  TGen (..),
88
  TGenM (..),
89
  newTGenM,
90
  newTGenMIO,
91
  applyTGen,
92

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

101
  -- ** Lists
102
  uniformListM,
103
  uniformListRM,
104
  uniformShuffleListM,
105

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

111
  -- * Helper functions for createing instances
112

113
  -- ** Sequences of bytes
114
  fillByteArrayST,
115
  genShortByteStringIO,
116
  genShortByteStringST,
117
  defaultUnsafeUniformFillMutableByteArray,
118

119
  -- ** Floating point numbers
120
  uniformDouble01M,
121
  uniformDoublePositive01M,
122
  uniformFloat01M,
123
  uniformFloatPositive01M,
124

125
  -- ** Enum types
126
  uniformEnumM,
127
  uniformEnumRM,
128

129
  -- ** Word
130
  uniformWordR,
131

132
  -- * Appendix
133

134
  -- ** How to implement 'StatefulGen'
135
  -- $implemenstatefulegen
136

137
  -- ** Floating point number caveats #fpcaveats#
138
  scaleFloating,
139
  -- $floating
140

141
  -- * References
142
  -- $references
143

144
  -- * Pure Random Generator
145
  module System.Random,
146
) where
147

148
import Control.DeepSeq
149
import Control.Monad.IO.Class
150
import Control.Monad.ST
151
import Control.Monad.State.Strict (MonadState, state)
152
import Data.ByteString (ByteString)
153
import Data.Coerce
154
import Data.IORef
155
import Data.STRef
156
import Foreign.Storable
157
import GHC.Conc.Sync (STM, TVar, newTVar, newTVarIO, readTVar, writeTVar)
158
import System.Random hiding (uniformShortByteString)
159
import System.Random.Array (shortByteStringToByteString, shuffleListM)
160
import System.Random.Internal
161
#if __GLASGOW_HASKELL__ >= 808
162
import GHC.IORef (atomicModifyIORef2Lazy)
163
#endif
164

165
-- $introduction
166
--
167
-- This module provides type classes and instances for the following concepts:
168
--
169
-- [Monadic pseudo-random number generators] 'StatefulGen' is an interface to
170
--     monadic pseudo-random number generators.
171
--
172
-- [Monadic adapters] 'StateGenM', 'AtomicGenM', 'IOGenM', 'STGenM` and 'TGenM'
173
--     turn a 'RandomGen' instance into a 'StatefulGen' instance.
174
--
175
-- [Drawing from a range] 'UniformRange' is used to generate a value of a
176
--     type uniformly within a range.
177
--
178
--     This library provides instances of 'UniformRange' for many common
179
--     numeric types.
180
--
181
-- [Drawing from the entire domain of a type] 'Uniform' is used to generate a
182
--     value of a type uniformly over all possible values of that type.
183
--
184
--     This library provides instances of 'Uniform' for many common bounded
185
--     numeric types.
186

187
-- $usagemonadic
188
--
189
-- In monadic code, use the relevant 'Uniform' and 'UniformRange' instances to
190
-- generate pseudo-random values via 'uniformM' and 'uniformRM', respectively.
191
--
192
-- As an example, @rollsM@ generates @n@ pseudo-random values of @Word@ in the range @[1,
193
-- 6]@ in a 'StatefulGen' context; given a /monadic/ pseudo-random number generator, you
194
-- can run this probabilistic computation using
195
-- [@mwc-random@](https://hackage.haskell.org/package/mwc-random) as follows:
196
--
197
-- >>> import Control.Monad (replicateM)
198
-- >>> :{
199
-- let rollsM :: StatefulGen g m => Int -> g -> m [Word]
200
--     rollsM n = replicateM n . uniformRM (1, 6)
201
-- :}
202
--
203
-- > import qualified System.Random.MWC as MWC
204
-- > >>> monadicGen <- MWC.create
205
-- > >>> rollsM 10 monadicGen :: IO [Word]
206
-- > [3,4,3,1,4,6,1,6,1,4]
207
--
208
-- Given a /pure/ pseudo-random number generator, you can run the monadic pseudo-random
209
-- number computation @rollsM@ in 'Control.Monad.State.Strict.StateT', 'IO', 'ST' or 'STM'
210
-- context by applying a monadic adapter like 'StateGenM', 'AtomicGenM', 'IOGenM',
211
-- 'STGenM' or 'TGenM' (see [monadic-adapters](#monadicadapters)) to the pure
212
-- pseudo-random number generator.
213
--
214
-- >>> let pureGen = mkStdGen 42
215
-- >>> newIOGenM pureGen >>= rollsM 10 :: IO [Word]
216
-- [1,1,3,2,4,5,3,4,6,2]
217

218
-------------------------------------------------------------------------------
219
-- Pseudo-random number generator interfaces
220
-------------------------------------------------------------------------------
221

222
-- $interfaces
223
--
224
-- Pseudo-random number generators come in two flavours: /pure/ and /monadic/.
225
--
226
-- ['System.Random.RandomGen': pure pseudo-random number generators]
227
--     See "System.Random" module.
228
--
229
-- ['StatefulGen': monadic pseudo-random number generators] These generators mutate their
230
--     own state as they produce pseudo-random values. They generally live in
231
--     'Control.Monad.State.Strict.StateT', 'ST', 'IO' or 'STM' or some other transformer
232
--     on top of those monads.
233

234
-------------------------------------------------------------------------------
235
-- Monadic adapters
236
-------------------------------------------------------------------------------
237

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

262
-- | Interface to operations on 'RandomGen' wrappers like 'IOGenM' and 'StateGenM'.
263
--
264
-- @since 1.2.0
265
class (RandomGen r, StatefulGen g m) => RandomGenM g r m | g -> r where
266
  applyRandomGenM :: (r -> (a, r)) -> g -> m a
267

268
{-# DEPRECATED applyRandomGenM "In favor of `modifyGen`" #-}
269

270
{-# DEPRECATED RandomGenM "In favor of `FrozenGen`" #-}
271

272
instance (RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m where
UNCOV
273
  applyRandomGenM = applyIOGen
×
274

275
instance (RandomGen r, MonadIO m) => RandomGenM (AtomicGenM r) r m where
UNCOV
276
  applyRandomGenM = applyAtomicGen
×
277

278
instance (RandomGen r, MonadState r m) => RandomGenM (StateGenM r) r m where
UNCOV
279
  applyRandomGenM f _ = state f
×
280

281
instance RandomGen r => RandomGenM (STGenM r s) r (ST s) where
UNCOV
282
  applyRandomGenM = applySTGen
×
283

284
instance RandomGen r => RandomGenM (TGenM r) r STM where
UNCOV
285
  applyRandomGenM = applyTGen
×
286

287
-- | Shuffle elements of a list in a uniformly random order.
288
--
289
-- ====__Examples__
290
--
291
-- >>> import System.Random.Stateful
292
-- >>> runStateGen_ (mkStdGen 127) $ uniformShuffleListM "ELVIS"
293
-- "LIVES"
294
--
295
-- @since 1.3.0
296
uniformShuffleListM :: StatefulGen g m => [a] -> g -> m [a]
UNCOV
297
uniformShuffleListM xs gen = shuffleListM (`uniformWordR` gen) xs
×
298
{-# INLINE uniformShuffleListM #-}
299

300
-- | Runs a mutable pseudo-random number generator from its 'FrozenGen' state.
301
--
302
-- ====__Examples__
303
--
304
-- >>> import Data.Int (Int8)
305
-- >>> withMutableGen (IOGen (mkStdGen 217)) (uniformListM 5) :: IO ([Int8], IOGen StdGen)
306
-- ([-74,37,-50,-2,3],IOGen {unIOGen = StdGen {unStdGen = SMGen 4273268533320920145 15251669095119325999}})
307
--
308
-- @since 1.2.0
309
withMutableGen :: ThawedGen f m => f -> (MutableGen f m -> m a) -> m (a, f)
310
withMutableGen fg action = do
2✔
311
  g <- thawGen fg
2✔
312
  res <- action g
2✔
313
  fg' <- freezeGen g
2✔
314
  pure (res, fg')
2✔
315

316
-- | Same as 'withMutableGen', but only returns the generated value.
317
--
318
-- ====__Examples__
319
--
320
-- >>> import System.Random.Stateful
321
-- >>> let pureGen = mkStdGen 137
322
-- >>> withMutableGen_ (IOGen pureGen) (uniformRM (1 :: Int, 6 :: Int))
323
-- 4
324
--
325
-- @since 1.2.0
326
withMutableGen_ :: ThawedGen f m => f -> (MutableGen f m -> m a) -> m a
327
withMutableGen_ fg action = thawGen fg >>= action
2✔
328

329
-- | Just like `withMutableGen`, except uses a `Seed` instead of a frozen generator.
330
--
331
-- ====__Examples__
332
--
333
-- Here is good example of how `withSeedMutableGen` can be used with `withSeedFile`, which uses a locally stored seed.
334
--
335
-- First we define a @reportSeed@ function that will print the contents of a seed file as a list of bytes:
336
--
337
-- >>> import Data.ByteString as BS (readFile, writeFile, unpack)
338
-- >>> :seti -XOverloadedStrings
339
-- >>> let reportSeed fp = print . ("Seed: " <>) . show . BS.unpack =<< BS.readFile fp
340
--
341
-- Given a file path, write an `StdGen` seed into the file:
342
--
343
-- >>> :seti -XFlexibleContexts -XScopedTypeVariables
344
-- >>> let writeInitSeed fp = BS.writeFile fp (unSeedToByteString (toSeed (mkStdGen 2025)))
345
--
346
-- Apply a `StatefulGen` monadic action that uses @`IOGen` `StdGen`@, restored from the seed in the given path:
347
--
348
-- >>> let withMutableSeedFile fp action = withSeedFile fp (\(seed :: Seed (IOGen StdGen)) -> withSeedMutableGen seed action)
349
--
350
-- Given a path and an action initialize the seed file and apply the action using that seed:
351
--
352
-- >>> let withInitSeedFile fp action = writeInitSeed fp *> reportSeed fp *> withMutableSeedFile fp action <* reportSeed fp
353
--
354
-- For the sake of example we will use a temporary directory for storing the seed. Here we
355
-- report the contents of the seed file before and after we shuffle a list:
356
--
357
-- >>> import UnliftIO.Temporary (withSystemTempDirectory)
358
-- >>> withSystemTempDirectory "random" (\fp -> withInitSeedFile (fp ++ "/seed.bin") (uniformShuffleListM [1..10]))
359
-- "Seed: [183,178,143,77,132,163,109,14,157,105,82,99,148,82,109,173]"
360
-- "Seed: [60,105,117,203,187,138,69,39,157,105,82,99,148,82,109,173]"
361
-- [7,5,4,3,1,8,10,6,9,2]
362
--
363
-- @since 1.3.0
364
withSeedMutableGen ::
365
  (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m (a, Seed g)
UNCOV
366
withSeedMutableGen seed f = withSeedM seed (`withMutableGen` f)
×
367

368
-- | Just like `withSeedMutableGen`, except it doesn't return the final generator, only
369
-- the resulting value. This is slightly more efficient, since it doesn't incur overhead
370
-- from freezeing the mutable generator
371
--
372
-- @since 1.3.0
373
withSeedMutableGen_ :: (SeedGen g, ThawedGen g m) => Seed g -> (MutableGen g m -> m a) -> m a
UNCOV
374
withSeedMutableGen_ seed = withMutableGen_ (fromSeed seed)
×
375

376
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
377
--
378
-- ====__Examples__
379
--
380
-- >>> import System.Random.Stateful
381
-- >>> let pureGen = mkStdGen 139
382
-- >>> g <- newIOGenM pureGen
383
-- >>> randomM g :: IO Double
384
-- 0.33775117339631733
385
--
386
-- You can use type applications to disambiguate the type of the generated numbers:
387
--
388
-- >>> :seti -XTypeApplications
389
-- >>> randomM @Double g
390
-- 0.9156875994165681
391
--
392
-- @since 1.2.0
393
randomM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => MutableGen g m -> m a
394
randomM = flip modifyGen random
2✔
395
{-# INLINE randomM #-}
396

397
-- | Generates a pseudo-random value using monadic interface and `Random` instance.
398
--
399
-- ====__Examples__
400
--
401
-- >>> import System.Random.Stateful
402
-- >>> let pureGen = mkStdGen 137
403
-- >>> g <- newIOGenM pureGen
404
-- >>> randomRM (1, 100) g :: IO Int
405
-- 52
406
--
407
-- You can use type applications to disambiguate the type of the generated numbers:
408
--
409
-- >>> :seti -XTypeApplications
410
-- >>> randomRM @Int (1, 100) g
411
-- 2
412
--
413
-- @since 1.2.0
414
randomRM :: forall a g m. (Random a, RandomGen g, FrozenGen g m) => (a, a) -> MutableGen g m -> m a
415
randomRM r = flip modifyGen (randomR r)
2✔
416
{-# INLINE randomRM #-}
417

418
-- | Generates a pseudo-random 'ByteString' of the specified size.
419
--
420
-- @since 1.2.0
421
uniformByteStringM :: StatefulGen g m => Int -> g -> m ByteString
422
uniformByteStringM n g =
2✔
423
  shortByteStringToByteString . byteArrayToShortByteString
2✔
424
    <$> uniformByteArrayM True n g
2✔
425
{-# INLINE uniformByteStringM #-}
426

427
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator. All
428
-- operations are performed atomically.
429
--
430
-- *   'AtomicGenM' is safe in the presence of exceptions and concurrency.
431
-- *   'AtomicGenM' is the slowest of the monadic adapters due to the overhead
432
--     of its atomic operations.
433
--
434
-- @since 1.2.0
435
newtype AtomicGenM g = AtomicGenM {unAtomicGenM :: IORef g}
2✔
436

437
-- | Frozen version of mutable `AtomicGenM` generator
438
--
439
-- @since 1.2.0
440
newtype AtomicGen g = AtomicGen {unAtomicGen :: g}
2✔
441
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
442

443
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
444
instance SeedGen g => SeedGen (AtomicGen g) where
445
  type SeedSize (AtomicGen g) = SeedSize g
UNCOV
446
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
447
  toSeed = coerce (toSeed :: g -> Seed g)
×
448

449
-- | Creates a new 'AtomicGenM'.
450
--
451
-- @since 1.2.0
452
newAtomicGenM :: MonadIO m => g -> m (AtomicGenM g)
453
newAtomicGenM = fmap AtomicGenM . liftIO . newIORef
2✔
454

455
-- | Global mutable standard pseudo-random number generator. This is the same
456
-- generator that was historically used by `randomIO` and `randomRIO` functions.
457
--
458
-- >>> import Control.Monad (replicateM)
459
-- >>> replicateM 10 (uniformRM ('a', 'z') globalStdGen)
460
-- "tdzxhyfvgr"
461
--
462
-- @since 1.2.1
463
globalStdGen :: AtomicGenM StdGen
UNCOV
464
globalStdGen = AtomicGenM theStdGen
×
465

466
instance (RandomGen g, MonadIO m) => StatefulGen (AtomicGenM g) m where
467
  uniformWord32R r = applyAtomicGen (genWord32R r)
2✔
468
  {-# INLINE uniformWord32R #-}
469
  uniformWord64R r = applyAtomicGen (genWord64R r)
2✔
470
  {-# INLINE uniformWord64R #-}
471
  uniformWord8 = applyAtomicGen genWord8
2✔
472
  {-# INLINE uniformWord8 #-}
473
  uniformWord16 = applyAtomicGen genWord16
2✔
474
  {-# INLINE uniformWord16 #-}
475
  uniformWord32 = applyAtomicGen genWord32
2✔
476
  {-# INLINE uniformWord32 #-}
477
  uniformWord64 = applyAtomicGen genWord64
2✔
478
  {-# INLINE uniformWord64 #-}
479

480
instance (RandomGen g, MonadIO m) => FrozenGen (AtomicGen g) m where
481
  type MutableGen (AtomicGen g) m = AtomicGenM g
482
  freezeGen = fmap AtomicGen . liftIO . readIORef . unAtomicGenM
2✔
483
  modifyGen (AtomicGenM ioRef) f =
2✔
484
    liftIO $ atomicModifyIORefHS ioRef $ \g ->
2✔
485
      case f (AtomicGen g) of
2✔
486
        (a, AtomicGen g') -> (g', a)
2✔
487
  {-# INLINE modifyGen #-}
488

489
instance (RandomGen g, MonadIO m) => ThawedGen (AtomicGen g) m where
490
  thawGen (AtomicGen g) = newAtomicGenM g
2✔
491

492
-- | Atomically applies a pure operation to the wrapped pseudo-random number
493
-- generator.
494
--
495
-- ====__Examples__
496
--
497
-- >>> import System.Random.Stateful
498
-- >>> let pureGen = mkStdGen 137
499
-- >>> g <- newAtomicGenM pureGen
500
-- >>> applyAtomicGen random g :: IO Int
501
-- 7879794327570578227
502
--
503
-- @since 1.2.0
504
applyAtomicGen :: MonadIO m => (g -> (a, g)) -> AtomicGenM g -> m a
505
applyAtomicGen op (AtomicGenM gVar) =
2✔
506
  liftIO $ atomicModifyIORefHS gVar $ \g ->
2✔
507
    case op g of
2✔
508
      (a, g') -> (g', a)
2✔
509
{-# INLINE applyAtomicGen #-}
510

511
-- HalfStrict version of atomicModifyIORef, i.e. strict in the modifcation of the contents
512
-- of the IORef, but not in the result produced.
513
atomicModifyIORefHS :: IORef a -> (a -> (a, b)) -> IO b
514
atomicModifyIORefHS ref f = do
2✔
515
#if __GLASGOW_HASKELL__ >= 808
516
  (_old, (_new, res)) <- atomicModifyIORef2Lazy ref $ \old ->
2✔
517
    case f old of
2✔
518
      r@(!_new, _res) -> r
2✔
519
  pure res
2✔
520
#else
521
  atomicModifyIORef ref $ \old ->
522
    case f old of
523
      r@(!_new, _res) -> r
524
#endif
525
{-# INLINE atomicModifyIORefHS #-}
526

527
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator.
528
--
529
-- *   'IOGenM' is safe in the presence of exceptions, but not concurrency.
530
-- *   'IOGenM' is slower than 'StateGenM' due to the extra pointer indirection.
531
-- *   'IOGenM' is faster than 'AtomicGenM' since the 'IORef' operations used by
532
--     'IOGenM' are not atomic.
533
--
534
-- An example use case is writing pseudo-random bytes into a file:
535
--
536
-- >>> import UnliftIO.Temporary (withSystemTempFile)
537
-- >>> import Data.ByteString (hPutStr)
538
-- >>> let ioGen g = withSystemTempFile "foo.bin" $ \_ h -> uniformRM (0, 100) g >>= flip uniformByteStringM g >>= hPutStr h
539
--
540
-- and then run it:
541
--
542
-- >>> newIOGenM (mkStdGen 1729) >>= ioGen
543
--
544
-- @since 1.2.0
545
newtype IOGenM g = IOGenM {unIOGenM :: IORef g}
2✔
546

547
-- | Frozen version of mutable `IOGenM` generator
548
--
549
-- @since 1.2.0
550
newtype IOGen g = IOGen {unIOGen :: g}
2✔
551
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
552

553
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
554
instance SeedGen g => SeedGen (IOGen g) where
555
  type SeedSize (IOGen g) = SeedSize g
UNCOV
556
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
557
  toSeed = coerce (toSeed :: g -> Seed g)
×
558

559
-- | Creates a new 'IOGenM'.
560
--
561
-- @since 1.2.0
562
newIOGenM :: MonadIO m => g -> m (IOGenM g)
563
newIOGenM = fmap IOGenM . liftIO . newIORef
2✔
564

565
instance (RandomGen g, MonadIO m) => StatefulGen (IOGenM g) m where
566
  uniformWord32R r = applyIOGen (genWord32R r)
2✔
567
  {-# INLINE uniformWord32R #-}
568
  uniformWord64R r = applyIOGen (genWord64R r)
2✔
569
  {-# INLINE uniformWord64R #-}
570
  uniformWord8 = applyIOGen genWord8
2✔
571
  {-# INLINE uniformWord8 #-}
572
  uniformWord16 = applyIOGen genWord16
2✔
573
  {-# INLINE uniformWord16 #-}
574
  uniformWord32 = applyIOGen genWord32
2✔
575
  {-# INLINE uniformWord32 #-}
576
  uniformWord64 = applyIOGen genWord64
2✔
577
  {-# INLINE uniformWord64 #-}
578

579
instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
580
  type MutableGen (IOGen g) m = IOGenM g
581
  freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
2✔
582
  modifyGen (IOGenM ref) f = liftIO $ do
2✔
583
    g <- readIORef ref
2✔
584
    let (a, IOGen g') = f (IOGen g)
2✔
585
    g' `seq` writeIORef ref g'
2✔
586
    pure a
2✔
587
  {-# INLINE modifyGen #-}
588
  overwriteGen (IOGenM ref) = liftIO . writeIORef ref . unIOGen
2✔
589
  {-# INLINE overwriteGen #-}
590

591
instance (RandomGen g, MonadIO m) => ThawedGen (IOGen g) m where
592
  thawGen (IOGen g) = newIOGenM g
2✔
593

594
-- | Applies a pure operation to the wrapped pseudo-random number generator.
595
--
596
-- ====__Examples__
597
--
598
-- >>> import System.Random.Stateful
599
-- >>> let pureGen = mkStdGen 137
600
-- >>> g <- newIOGenM pureGen
601
-- >>> applyIOGen random g :: IO Int
602
-- 7879794327570578227
603
--
604
-- @since 1.2.0
605
applyIOGen :: MonadIO m => (g -> (a, g)) -> IOGenM g -> m a
606
applyIOGen f (IOGenM ref) = liftIO $ do
2✔
607
  g <- readIORef ref
2✔
608
  case f g of
2✔
609
    (a, !g') -> a <$ writeIORef ref g'
2✔
610
{-# INLINE applyIOGen #-}
611

612
-- | Wraps an 'STRef' that holds a pure pseudo-random number generator.
613
--
614
-- *   'STGenM' is safe in the presence of exceptions, but not concurrency.
615
-- *   'STGenM' is slower than 'StateGenM' due to the extra pointer indirection.
616
--
617
-- @since 1.2.0
618
newtype STGenM g s = STGenM {unSTGenM :: STRef s g}
2✔
619

620
-- | Frozen version of mutable `STGenM` generator
621
--
622
-- @since 1.2.0
623
newtype STGen g = STGen {unSTGen :: g}
2✔
624
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
625

626
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
627
instance SeedGen g => SeedGen (STGen g) where
628
  type SeedSize (STGen g) = SeedSize g
UNCOV
629
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
630
  toSeed = coerce (toSeed :: g -> Seed g)
×
631

632
-- | Creates a new 'STGenM'.
633
--
634
-- @since 1.2.0
635
newSTGenM :: g -> ST s (STGenM g s)
636
newSTGenM = fmap STGenM . newSTRef
2✔
637

638
instance RandomGen g => StatefulGen (STGenM g s) (ST s) where
639
  uniformWord32R r = applySTGen (genWord32R r)
2✔
640
  {-# INLINE uniformWord32R #-}
641
  uniformWord64R r = applySTGen (genWord64R r)
2✔
642
  {-# INLINE uniformWord64R #-}
643
  uniformWord8 = applySTGen genWord8
2✔
644
  {-# INLINE uniformWord8 #-}
645
  uniformWord16 = applySTGen genWord16
2✔
646
  {-# INLINE uniformWord16 #-}
647
  uniformWord32 = applySTGen genWord32
2✔
648
  {-# INLINE uniformWord32 #-}
649
  uniformWord64 = applySTGen genWord64
2✔
650
  {-# INLINE uniformWord64 #-}
651

652
instance RandomGen g => FrozenGen (STGen g) (ST s) where
653
  type MutableGen (STGen g) (ST s) = STGenM g s
654
  freezeGen = fmap STGen . readSTRef . unSTGenM
2✔
655
  modifyGen (STGenM ref) f = do
2✔
656
    g <- readSTRef ref
2✔
657
    let (a, STGen g') = f (STGen g)
2✔
658
    g' `seq` writeSTRef ref g'
2✔
659
    pure a
2✔
660
  {-# INLINE modifyGen #-}
661
  overwriteGen (STGenM ref) = writeSTRef ref . unSTGen
2✔
662
  {-# INLINE overwriteGen #-}
663

664
instance RandomGen g => ThawedGen (STGen g) (ST s) where
665
  thawGen (STGen g) = newSTGenM g
2✔
666

667
-- | Applies a pure operation to the wrapped pseudo-random number generator.
668
--
669
-- ====__Examples__
670
--
671
-- >>> import System.Random.Stateful
672
-- >>> let pureGen = mkStdGen 137
673
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
674
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
675
--
676
-- @since 1.2.0
677
applySTGen :: (g -> (a, g)) -> STGenM g s -> ST s a
678
applySTGen f (STGenM ref) = do
2✔
679
  g <- readSTRef ref
2✔
680
  case f g of
2✔
681
    (a, !g') -> a <$ writeSTRef ref g'
2✔
682
{-# INLINE applySTGen #-}
683

684
-- | Runs a monadic generating action in the `ST` monad using a pure
685
-- pseudo-random number generator.
686
--
687
-- ====__Examples__
688
--
689
-- >>> import System.Random.Stateful
690
-- >>> let pureGen = mkStdGen 137
691
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
692
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
693
--
694
-- @since 1.2.0
695
runSTGen :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> (a, g)
696
runSTGen g action = unSTGen <$> runST (withMutableGen (STGen g) action)
1✔
697

698
-- | Runs a monadic generating action in the `ST` monad using a pure
699
-- pseudo-random number generator. Returns only the resulting pseudo-random
700
-- value.
701
--
702
-- ====__Examples__
703
--
704
-- >>> import System.Random.Stateful
705
-- >>> let pureGen = mkStdGen 137
706
-- >>> (runSTGen_ pureGen (\g -> applySTGen random g)) :: Int
707
-- 7879794327570578227
708
--
709
-- @since 1.2.0
710
runSTGen_ :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> a
711
runSTGen_ g action = fst $ runSTGen g action
2✔
712

713
-- | Wraps a 'TVar' that holds a pure pseudo-random number generator.
714
--
715
-- @since 1.2.1
716
newtype TGenM g = TGenM {unTGenM :: TVar g}
2✔
717

718
-- | Frozen version of mutable `TGenM` generator
719
--
720
-- @since 1.2.1
721
newtype TGen g = TGen {unTGen :: g}
2✔
722
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
723

724
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
725
instance SeedGen g => SeedGen (TGen g) where
726
  type SeedSize (TGen g) = SeedSize g
UNCOV
727
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
728
  toSeed = coerce (toSeed :: g -> Seed g)
×
729

730
-- | Creates a new 'TGenM' in `STM`.
731
--
732
-- @since 1.2.1
733
newTGenM :: g -> STM (TGenM g)
734
newTGenM = fmap TGenM . newTVar
2✔
735

736
-- | Creates a new 'TGenM' in `IO`.
737
--
738
-- @since 1.2.1
739
newTGenMIO :: MonadIO m => g -> m (TGenM g)
UNCOV
740
newTGenMIO g = liftIO (TGenM <$> newTVarIO g)
×
741

742
-- | @since 1.2.1
743
instance RandomGen g => StatefulGen (TGenM g) STM where
744
  uniformWord32R r = applyTGen (genWord32R r)
2✔
745
  {-# INLINE uniformWord32R #-}
746
  uniformWord64R r = applyTGen (genWord64R r)
2✔
747
  {-# INLINE uniformWord64R #-}
748
  uniformWord8 = applyTGen genWord8
2✔
749
  {-# INLINE uniformWord8 #-}
750
  uniformWord16 = applyTGen genWord16
2✔
751
  {-# INLINE uniformWord16 #-}
752
  uniformWord32 = applyTGen genWord32
2✔
753
  {-# INLINE uniformWord32 #-}
754
  uniformWord64 = applyTGen genWord64
2✔
755
  {-# INLINE uniformWord64 #-}
756

757
-- | @since 1.2.1
758
instance RandomGen g => FrozenGen (TGen g) STM where
759
  type MutableGen (TGen g) STM = TGenM g
760
  freezeGen = fmap TGen . readTVar . unTGenM
2✔
761
  modifyGen (TGenM ref) f = do
2✔
762
    g <- readTVar ref
2✔
763
    let (a, TGen g') = f (TGen g)
2✔
764
    g' `seq` writeTVar ref g'
2✔
765
    pure a
2✔
766
  {-# INLINE modifyGen #-}
767
  overwriteGen (TGenM ref) = writeTVar ref . unTGen
2✔
768
  {-# INLINE overwriteGen #-}
769

770
instance RandomGen g => ThawedGen (TGen g) STM where
771
  thawGen (TGen g) = newTGenM g
2✔
772

773
-- | Applies a pure operation to the wrapped pseudo-random number generator.
774
--
775
-- ====__Examples__
776
--
777
-- >>> import Control.Concurrent.STM
778
-- >>> import System.Random.Stateful
779
-- >>> import Data.Int (Int32)
780
-- >>> let pureGen = mkStdGen 137
781
-- >>> stmGen <- newTGenMIO pureGen
782
-- >>> atomically $ applyTGen uniform stmGen :: IO Int32
783
-- 637238067
784
--
785
-- @since 1.2.1
786
applyTGen :: (g -> (a, g)) -> TGenM g -> STM a
787
applyTGen f (TGenM tvar) = do
2✔
788
  g <- readTVar tvar
2✔
789
  case f g of
2✔
790
    (a, !g') -> a <$ writeTVar tvar g'
2✔
791
{-# INLINE applyTGen #-}
792

793
-- $uniform
794
--
795
-- This library provides two type classes to generate pseudo-random values:
796
--
797
-- *   'UniformRange' is used to generate a value of a type uniformly within a
798
--     range.
799
-- *   'Uniform' is used to generate a value of a type uniformly over all
800
--     possible values of that type.
801
--
802
-- Types may have instances for both or just one of 'UniformRange' and
803
-- 'Uniform'. A few examples illustrate this:
804
--
805
-- *   'Int', 'Data.Word.Word16' and 'Bool' are instances of both 'UniformRange' and
806
--     'Uniform'.
807
-- *   'Integer', 'Float' and 'Double' each have an instance for 'UniformRange'
808
--     but no 'Uniform' instance.
809
-- *   A hypothetical type @Radian@ representing angles by taking values in the
810
--     range @[0, 2π)@ has a trivial 'Uniform' instance, but no 'UniformRange'
811
--     instance: the problem is that two given @Radian@ values always span /two/
812
--     ranges, one clockwise and one anti-clockwise.
813
-- *   It is trivial to construct a @Uniform (a, b)@ instance given
814
--     @Uniform a@ and @Uniform b@ (and this library provides this tuple
815
--     instance).
816
-- *   On the other hand, there is no correct way to construct a
817
--     @UniformRange (a, b)@ instance based on just @UniformRange a@ and
818
--     @UniformRange b@.
819

820
-------------------------------------------------------------------------------
821
-- Notes
822
-------------------------------------------------------------------------------
823

824
-- $floating
825
--
826
-- Due to rounding errors, floating point operations are neither associative nor
827
-- distributive the way the corresponding operations on real numbers are. Additionally,
828
-- floating point numbers admit special values @NaN@ as well as negative and positive
829
-- infinity.
830
--
831
-- The 'UniformRange' instances for 'Float' and 'Double' use the following
832
-- procedure to generate a random value in a range for @uniformRM (l, h) g@:
833
--
834
-- * If @__l == h__@, return: @__l__@.
835
-- * If @__`isInfinite` l == True__@ or @__`isInfinite` h == True__@, return: @__l + h__@
836
-- * Otherwise:
837
--
838
--     1.  Generate an unsigned integral of matching width @__w__@ uniformly.
839
--
840
--     2.  Check whether @__h - l__@ overflows to infinity and, if it does, then convert
841
--         @__w__@ to a floating point number in @__[0.0, 1.0]__@ range through division
842
--         of @__w__@ by the highest possible value:
843
--
844
--         @
845
--         x = `fromIntegral` w / `fromIntegral` `maxBound`
846
--         @
847
--
848
--         Then we scale and clamp it before returning it:
849
--
850
--         @
851
--         `max` (`min` (x * l + (1 - x) * h) (`max` l h)) (`min` l h)
852
--         @
853
--
854
--         Clamping is necessary, because otherwise it would be possible to run into a
855
--         degenerate case when a scaled value is outside the specified range due to
856
--         rounding errors.
857
--
858
--     3.  Whenever @__h - l__@ does not overflow, we use this common formula for scaling:
859
--         @__ l + (h - l) * x__@.  However, instead of using @__[0.0, 1.0]__@ range we
860
--         use the top most bit of @__w__@ to decide whether we will treat the generated
861
--         floating point value as @__[0.0, 0.5]__@ range or @__[0.5, 1.0]__@ range and
862
--         use the left over bits to produce a floating point value in the half unit
863
--         range:
864
--
865
--         @
866
--         x = `fromIntegral` (`clearBit` w 31) / `fromIntegral` `maxBound`
867
--         @
868
--
869
--         Further scaling depends on the top most bit:
870
--
871
--         @
872
--         if `testBit` w 31
873
--            then l + (h - l) * x
874
--            else h + (l - h) * x
875
--         @
876
--
877
--         Because of this clever technique the result does not need clamping, since
878
--         scaled values are guaranteed to stay within the specified range. Another reason
879
--         why this tecnique is used for the common case instead of the one described in
880
--         @2.@ is because it avoids usage of @__1 - x__@, which consequently reduces loss
881
--         of randomness due to rounding.
882
--
883
--
884
-- What happens when @__NaN__@ or @__Infinity__@ are given to 'uniformRM'? We first
885
-- define them as constants:
886
--
887
-- >>> nan = read "NaN" :: Float
888
-- >>> inf = read "Infinity" :: Float
889
-- >>> g <- newIOGenM (mkStdGen 2024)
890
--
891
-- *   If at least one of \(l\) or \(h\) is @__NaN__@, the result is @__NaN__@.
892
--
893
--     >>> uniformRM (nan, 1) g
894
--     NaN
895
--     >>> uniformRM (-1, nan) g
896
--     NaN
897
--
898
-- *   If \(l\) and \(h\) are both @__Infinity__@ with opposing signs, then the result is @__NaN__@.
899
--
900
--     >>> uniformRM (-inf, inf) g
901
--     NaN
902
--     >>> uniformRM (inf, -inf) g
903
--     NaN
904
--
905
-- *   Otherwise, if \(l\) is @__Infinity__@ or @__-Infinity__@, the result is \(l\).
906
--
907
--     >>> uniformRM (inf, 1) g
908
--     Infinity
909
--     >>> uniformRM (-inf, 1) g
910
--     -Infinity
911
--
912
-- *   Otherwise, if \(h\) is @__Infinity__@ or @__-Infinity__@, the result is \(h\).
913
--
914
--     >>> uniformRM (1, inf) g
915
--     Infinity
916
--     >>> uniformRM (1, -inf) g
917
--     -Infinity
918
--
919
-- 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),
920
-- the [Java 10 standard library](https://docs.oracle.com/javase/10/docs/api/java/util/Random.html#doubles%28double,double%29)
921
-- and [CPython 3.8](https://github.com/python/cpython/blob/3.8/Lib/random.py#L417)
922
-- use a similar procedure to generate floating point values in a range.
923

924
-- $implemenstatefulegen
925
--
926
-- Typically, a monadic pseudo-random number generator has facilities to save
927
-- and restore its internal state in addition to generating pseudo-random numbers.
928
--
929
-- Here is an example instance for the monadic pseudo-random number generator
930
-- from the @mwc-random@ package:
931
--
932
-- > import qualified System.Random.MWC as MWC
933
-- > import qualified Data.Vector.Generic as G
934
--
935
-- > instance (s ~ PrimState m, PrimMonad m) => StatefulGen (MWC.Gen s) m where
936
-- >   uniformWord8 = MWC.uniform
937
-- >   uniformWord16 = MWC.uniform
938
-- >   uniformWord32 = MWC.uniform
939
-- >   uniformWord64 = MWC.uniform
940
-- >   uniformByteArrayM isPinned n g = stToPrim (fillByteArrayST isPinned n (MWC.uniform g))
941
--
942
-- > instance PrimMonad m => FrozenGen MWC.Seed m where
943
-- >   type MutableGen MWC.Seed m = MWC.Gen (PrimState m)
944
-- >   freezeGen = MWC.save
945
-- >   overwriteGen (Gen mv) (Seed v) = G.copy mv v
946
--
947
-- > instance PrimMonad m => ThawedGen MWC.Seed m where
948
-- >   thawGen = MWC.restore
949
--
950
-- === @FrozenGen@
951
--
952
-- `FrozenGen` gives us ability to use most of stateful pseudo-random number generator in
953
-- its immutable form, if one exists that is.  The biggest benefit that can be drawn from
954
-- a polymorphic access to a stateful pseudo-random number generator in a frozen form is
955
-- the ability to serialize, deserialize and possibly even use the stateful generator in a
956
-- pure setting without knowing the actual type of a generator ahead of time. For example
957
-- we can write a function that accepts a frozen state of some pseudo-random number
958
-- generator and produces a short list with random even integers.
959
--
960
-- >>> import Data.Int (Int8)
961
-- >>> import Control.Monad (replicateM)
962
-- >>> :{
963
-- myCustomRandomList :: ThawedGen f m => f -> m [Int8]
964
-- myCustomRandomList f =
965
--   withMutableGen_ f $ \gen -> do
966
--     len <- uniformRM (5, 10) gen
967
--     replicateM len $ do
968
--       x <- uniformM gen
969
--       pure $ if even x then x else x + 1
970
-- :}
971
--
972
-- and later we can apply it to a frozen version of a stateful generator, such as `STGen`:
973
--
974
-- >>> print $ runST $ myCustomRandomList (STGen (mkStdGen 217))
975
-- [-50,-2,4,-8,-58,-40,24,-32,-110,24]
976
--
977
-- Alternatively, instead of discarding the final state of the generator, as it happens
978
-- above, we could have used `withMutableGen`, which together with the result would give
979
-- us back its frozen form. This would allow us to store the end state of our generator
980
-- somewhere for the later reuse.
981

982
-- $references
983
--
984
-- 1. Guy L. Steele, Jr., Doug Lea, and Christine H. Flood. 2014. Fast
985
-- splittable pseudorandom number generators. In Proceedings of the 2014 ACM
986
-- International Conference on Object Oriented Programming Systems Languages &
987
-- Applications (OOPSLA '14). ACM, New York, NY, USA, 453-472. DOI:
988
-- <https://doi.org/10.1145/2660193.2660195>
989

990
-- $setup
991
-- >>> writeIORef theStdGen $ mkStdGen 2021
992
--
993
-- >>> :seti -XFlexibleContexts
994
-- >>> :seti -XFlexibleInstances
995
-- >>> :seti -XMultiParamTypeClasses
996
-- >>> :seti -XTypeFamilies
997
-- >>> :seti -XUndecidableInstances
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