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

haskell / random / 435

06 Jul 2025 08:50PM UTC coverage: 69.108% (+0.07%) from 69.035%
435

push

github

web-flow
Merge 4dba8f885 into ca8a869de

27 of 30 new or added lines in 3 files covered. (90.0%)

7 existing lines in 1 file now uncovered.

651 of 942 relevant lines covered (69.11%)

1.3 hits per line

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

84.04
/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

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

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

215
-------------------------------------------------------------------------------
216
-- Pseudo-random number generator interfaces
217
-------------------------------------------------------------------------------
218

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

231
-------------------------------------------------------------------------------
232
-- Monadic adapters
233
-------------------------------------------------------------------------------
234

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

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

265
{-# DEPRECATED applyRandomGenM "In favor of `modifyGen`" #-}
266

267
{-# DEPRECATED RandomGenM "In favor of `FrozenGen`" #-}
268

269
instance (RandomGen r, MonadIO m) => RandomGenM (IOGenM r) r m where
270
  applyRandomGenM = applyIOGen
×
271

272
instance (RandomGen r, MonadIO m) => RandomGenM (AtomicGenM r) r m where
273
  applyRandomGenM = applyAtomicGen
×
274

275
instance (RandomGen r, MonadState r m) => RandomGenM (StateGenM r) r m where
276
  applyRandomGenM f _ = state f
×
277

278
instance RandomGen r => RandomGenM (STGenM r s) r (ST s) where
279
  applyRandomGenM = applySTGen
×
280

281
instance RandomGen r => RandomGenM (TGenM r) r STM where
282
  applyRandomGenM = applyTGen
×
283

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

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

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

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

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

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

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

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

424
-- | Wraps an 'IORef' that holds a pure pseudo-random number generator.
425
--
426
-- *   'IOGenM' is safe in the presence of exceptions, but not concurrency.
427
-- *   'IOGenM' is slower than 'StateGenM' due to the extra pointer indirection.
428
-- *   'IOGenM' is faster than 'AtomicGenM' since the 'IORef' operations used by
429
--     'IOGenM' are not atomic.
430
--
431
-- An example use case is writing pseudo-random bytes into a file:
432
--
433
-- >>> import UnliftIO.Temporary (withSystemTempFile)
434
-- >>> import Data.ByteString (hPutStr)
435
-- >>> let ioGen g = withSystemTempFile "foo.bin" $ \_ h -> uniformRM (0, 100) g >>= flip uniformByteStringM g >>= hPutStr h
436
--
437
-- and then run it:
438
--
439
-- >>> newIOGenM (mkStdGen 1729) >>= ioGen
440
--
441
-- @since 1.2.0
442
newtype IOGenM g = IOGenM {unIOGenM :: IORef g}
2✔
443

444
-- | Frozen version of mutable `IOGenM` generator
445
--
446
-- @since 1.2.0
447
newtype IOGen g = IOGen {unIOGen :: g}
2✔
448
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
449

450
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
451
instance SeedGen g => SeedGen (IOGen g) where
452
  type SeedSize (IOGen g) = SeedSize g
UNCOV
453
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
454
  toSeed = coerce (toSeed :: g -> Seed g)
×
455

456
-- | Creates a new 'IOGenM'.
457
--
458
-- @since 1.2.0
459
newIOGenM :: MonadIO m => g -> m (IOGenM g)
460
newIOGenM = fmap IOGenM . liftIO . newIORef
2✔
461

462
instance (RandomGen g, MonadIO m) => StatefulGen (IOGenM g) m where
463
  uniformWord32R r = applyIOGen (genWord32R r)
2✔
464
  {-# INLINE uniformWord32R #-}
465
  uniformWord64R r = applyIOGen (genWord64R r)
2✔
466
  {-# INLINE uniformWord64R #-}
467
  uniformWord8 = applyIOGen genWord8
2✔
468
  {-# INLINE uniformWord8 #-}
469
  uniformWord16 = applyIOGen genWord16
2✔
470
  {-# INLINE uniformWord16 #-}
471
  uniformWord32 = applyIOGen genWord32
2✔
472
  {-# INLINE uniformWord32 #-}
473
  uniformWord64 = applyIOGen genWord64
2✔
474
  {-# INLINE uniformWord64 #-}
475

476
instance (RandomGen g, MonadIO m) => FrozenGen (IOGen g) m where
477
  type MutableGen (IOGen g) m = IOGenM g
478
  freezeGen = fmap IOGen . liftIO . readIORef . unIOGenM
2✔
479
  modifyGen (IOGenM ref) f = liftIO $ do
2✔
480
    g <- readIORef ref
2✔
481
    let (a, IOGen g') = f (IOGen g)
2✔
482
    g' `seq` writeIORef ref g'
2✔
483
    pure a
2✔
484
  {-# INLINE modifyGen #-}
485
  overwriteGen (IOGenM ref) = liftIO . writeIORef ref . unIOGen
2✔
486
  {-# INLINE overwriteGen #-}
487

488
instance (RandomGen g, MonadIO m) => ThawedGen (IOGen g) m where
489
  thawGen (IOGen g) = newIOGenM g
2✔
490

491
-- | Applies a pure operation to the wrapped pseudo-random number generator.
492
--
493
-- ====__Examples__
494
--
495
-- >>> import System.Random.Stateful
496
-- >>> let pureGen = mkStdGen 137
497
-- >>> g <- newIOGenM pureGen
498
-- >>> applyIOGen random g :: IO Int
499
-- 7879794327570578227
500
--
501
-- @since 1.2.0
502
applyIOGen :: MonadIO m => (g -> (a, g)) -> IOGenM g -> m a
503
applyIOGen f (IOGenM ref) = liftIO $ do
2✔
504
  g <- readIORef ref
2✔
505
  case f g of
2✔
506
    (a, !g') -> a <$ writeIORef ref g'
2✔
507
{-# INLINE applyIOGen #-}
508

509
-- | Wraps an 'STRef' that holds a pure pseudo-random number generator.
510
--
511
-- *   'STGenM' is safe in the presence of exceptions, but not concurrency.
512
-- *   'STGenM' is slower than 'StateGenM' due to the extra pointer indirection.
513
--
514
-- @since 1.2.0
515
newtype STGenM g s = STGenM {unSTGenM :: STRef s g}
2✔
516

517
-- | Frozen version of mutable `STGenM` generator
518
--
519
-- @since 1.2.0
520
newtype STGen g = STGen {unSTGen :: g}
2✔
521
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
522

523
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
524
instance SeedGen g => SeedGen (STGen g) where
525
  type SeedSize (STGen g) = SeedSize g
UNCOV
526
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
527
  toSeed = coerce (toSeed :: g -> Seed g)
×
528

529
-- | Creates a new 'STGenM'.
530
--
531
-- @since 1.2.0
532
newSTGenM :: g -> ST s (STGenM g s)
533
newSTGenM = fmap STGenM . newSTRef
2✔
534

535
instance RandomGen g => StatefulGen (STGenM g s) (ST s) where
536
  uniformWord32R r = applySTGen (genWord32R r)
2✔
537
  {-# INLINE uniformWord32R #-}
538
  uniformWord64R r = applySTGen (genWord64R r)
2✔
539
  {-# INLINE uniformWord64R #-}
540
  uniformWord8 = applySTGen genWord8
2✔
541
  {-# INLINE uniformWord8 #-}
542
  uniformWord16 = applySTGen genWord16
2✔
543
  {-# INLINE uniformWord16 #-}
544
  uniformWord32 = applySTGen genWord32
2✔
545
  {-# INLINE uniformWord32 #-}
546
  uniformWord64 = applySTGen genWord64
2✔
547
  {-# INLINE uniformWord64 #-}
548

549
instance RandomGen g => FrozenGen (STGen g) (ST s) where
550
  type MutableGen (STGen g) (ST s) = STGenM g s
551
  freezeGen = fmap STGen . readSTRef . unSTGenM
2✔
552
  modifyGen (STGenM ref) f = do
2✔
553
    g <- readSTRef ref
2✔
554
    let (a, STGen g') = f (STGen g)
2✔
555
    g' `seq` writeSTRef ref g'
2✔
556
    pure a
2✔
557
  {-# INLINE modifyGen #-}
558
  overwriteGen (STGenM ref) = writeSTRef ref . unSTGen
2✔
559
  {-# INLINE overwriteGen #-}
560

561
instance RandomGen g => ThawedGen (STGen g) (ST s) where
562
  thawGen (STGen g) = newSTGenM g
2✔
563

564
-- | Applies a pure operation to the wrapped pseudo-random number generator.
565
--
566
-- ====__Examples__
567
--
568
-- >>> import System.Random.Stateful
569
-- >>> let pureGen = mkStdGen 137
570
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
571
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
572
--
573
-- @since 1.2.0
574
applySTGen :: (g -> (a, g)) -> STGenM g s -> ST s a
575
applySTGen f (STGenM ref) = do
2✔
576
  g <- readSTRef ref
2✔
577
  case f g of
2✔
578
    (a, !g') -> a <$ writeSTRef ref g'
2✔
579
{-# INLINE applySTGen #-}
580

581
-- | Runs a monadic generating action in the `ST` monad using a pure
582
-- pseudo-random number generator.
583
--
584
-- ====__Examples__
585
--
586
-- >>> import System.Random.Stateful
587
-- >>> let pureGen = mkStdGen 137
588
-- >>> (runSTGen pureGen (\g -> applySTGen random g)) :: (Int, StdGen)
589
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
590
--
591
-- @since 1.2.0
592
runSTGen :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> (a, g)
593
runSTGen g action = unSTGen <$> runST (withMutableGen (STGen g) action)
1✔
594

595
-- | Runs a monadic generating action in the `ST` monad using a pure
596
-- pseudo-random number generator. Returns only the resulting pseudo-random
597
-- value.
598
--
599
-- ====__Examples__
600
--
601
-- >>> import System.Random.Stateful
602
-- >>> let pureGen = mkStdGen 137
603
-- >>> (runSTGen_ pureGen (\g -> applySTGen random g)) :: Int
604
-- 7879794327570578227
605
--
606
-- @since 1.2.0
607
runSTGen_ :: RandomGen g => g -> (forall s. STGenM g s -> ST s a) -> a
608
runSTGen_ g action = fst $ runSTGen g action
2✔
609

610
-- | Wraps a 'TVar' that holds a pure pseudo-random number generator.
611
--
612
-- @since 1.2.1
613
newtype TGenM g = TGenM {unTGenM :: TVar g}
2✔
614

615
-- | Frozen version of mutable `TGenM` generator
616
--
617
-- @since 1.2.1
618
newtype TGen g = TGen {unTGen :: g}
2✔
619
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
1✔
620

621
-- Standalone definition due to GHC-8.0 not supporting deriving with associated type families
622
instance SeedGen g => SeedGen (TGen g) where
623
  type SeedSize (TGen g) = SeedSize g
UNCOV
624
  fromSeed = coerce (fromSeed :: Seed g -> g)
×
UNCOV
625
  toSeed = coerce (toSeed :: g -> Seed g)
×
626

627
-- | Creates a new 'TGenM' in `STM`.
628
--
629
-- @since 1.2.1
630
newTGenM :: g -> STM (TGenM g)
631
newTGenM = fmap TGenM . newTVar
2✔
632

633
-- | Creates a new 'TGenM' in `IO`.
634
--
635
-- @since 1.2.1
636
newTGenMIO :: MonadIO m => g -> m (TGenM g)
UNCOV
637
newTGenMIO g = liftIO (TGenM <$> newTVarIO g)
×
638

639
-- | @since 1.2.1
640
instance RandomGen g => StatefulGen (TGenM g) STM where
641
  uniformWord32R r = applyTGen (genWord32R r)
2✔
642
  {-# INLINE uniformWord32R #-}
643
  uniformWord64R r = applyTGen (genWord64R r)
2✔
644
  {-# INLINE uniformWord64R #-}
645
  uniformWord8 = applyTGen genWord8
2✔
646
  {-# INLINE uniformWord8 #-}
647
  uniformWord16 = applyTGen genWord16
2✔
648
  {-# INLINE uniformWord16 #-}
649
  uniformWord32 = applyTGen genWord32
2✔
650
  {-# INLINE uniformWord32 #-}
651
  uniformWord64 = applyTGen genWord64
2✔
652
  {-# INLINE uniformWord64 #-}
653

654
-- | @since 1.2.1
655
instance RandomGen g => FrozenGen (TGen g) STM where
656
  type MutableGen (TGen g) STM = TGenM g
657
  freezeGen = fmap TGen . readTVar . unTGenM
2✔
658
  modifyGen (TGenM ref) f = do
2✔
659
    g <- readTVar ref
2✔
660
    let (a, TGen g') = f (TGen g)
2✔
661
    g' `seq` writeTVar ref g'
2✔
662
    pure a
2✔
663
  {-# INLINE modifyGen #-}
664
  overwriteGen (TGenM ref) = writeTVar ref . unTGen
2✔
665
  {-# INLINE overwriteGen #-}
666

667
instance RandomGen g => ThawedGen (TGen g) STM where
668
  thawGen (TGen g) = newTGenM g
2✔
669

670
-- | Applies a pure operation to the wrapped pseudo-random number generator.
671
--
672
-- ====__Examples__
673
--
674
-- >>> import Control.Concurrent.STM
675
-- >>> import System.Random.Stateful
676
-- >>> import Data.Int (Int32)
677
-- >>> let pureGen = mkStdGen 137
678
-- >>> stmGen <- newTGenMIO pureGen
679
-- >>> atomically $ applyTGen uniform stmGen :: IO Int32
680
-- 637238067
681
--
682
-- @since 1.2.1
683
applyTGen :: (g -> (a, g)) -> TGenM g -> STM a
684
applyTGen f (TGenM tvar) = do
2✔
685
  g <- readTVar tvar
2✔
686
  case f g of
2✔
687
    (a, !g') -> a <$ writeTVar tvar g'
2✔
688
{-# INLINE applyTGen #-}
689

690
-- $uniform
691
--
692
-- This library provides two type classes to generate pseudo-random values:
693
--
694
-- *   'UniformRange' is used to generate a value of a type uniformly within a
695
--     range.
696
-- *   'Uniform' is used to generate a value of a type uniformly over all
697
--     possible values of that type.
698
--
699
-- Types may have instances for both or just one of 'UniformRange' and
700
-- 'Uniform'. A few examples illustrate this:
701
--
702
-- *   'Int', 'Data.Word.Word16' and 'Bool' are instances of both 'UniformRange' and
703
--     'Uniform'.
704
-- *   'Integer', 'Float' and 'Double' each have an instance for 'UniformRange'
705
--     but no 'Uniform' instance.
706
-- *   A hypothetical type @Radian@ representing angles by taking values in the
707
--     range @[0, 2π)@ has a trivial 'Uniform' instance, but no 'UniformRange'
708
--     instance: the problem is that two given @Radian@ values always span /two/
709
--     ranges, one clockwise and one anti-clockwise.
710
-- *   It is trivial to construct a @Uniform (a, b)@ instance given
711
--     @Uniform a@ and @Uniform b@ (and this library provides this tuple
712
--     instance).
713
-- *   On the other hand, there is no correct way to construct a
714
--     @UniformRange (a, b)@ instance based on just @UniformRange a@ and
715
--     @UniformRange b@.
716

717
-------------------------------------------------------------------------------
718
-- Notes
719
-------------------------------------------------------------------------------
720

721
-- $floating
722
--
723
-- Due to rounding errors, floating point operations are neither associative nor
724
-- distributive the way the corresponding operations on real numbers are. Additionally,
725
-- floating point numbers admit special values @NaN@ as well as negative and positive
726
-- infinity.
727
--
728
-- The 'UniformRange' instances for 'Float' and 'Double' use the following
729
-- procedure to generate a random value in a range for @uniformRM (l, h) g@:
730
--
731
-- * If @__l == h__@, return: @__l__@.
732
-- * If @__`isInfinite` l == True__@ or @__`isInfinite` h == True__@, return: @__l + h__@
733
-- * Otherwise:
734
--
735
--     1.  Generate an unsigned integral of matching width @__w__@ uniformly.
736
--
737
--     2.  Check whether @__h - l__@ overflows to infinity and, if it does, then convert
738
--         @__w__@ to a floating point number in @__[0.0, 1.0]__@ range through division
739
--         of @__w__@ by the highest possible value:
740
--
741
--         @
742
--         x = `fromIntegral` w / `fromIntegral` `maxBound`
743
--         @
744
--
745
--         Then we scale and clamp it before returning it:
746
--
747
--         @
748
--         `max` (`min` (x * l + (1 - x) * h) (`max` l h)) (`min` l h)
749
--         @
750
--
751
--         Clamping is necessary, because otherwise it would be possible to run into a
752
--         degenerate case when a scaled value is outside the specified range due to
753
--         rounding errors.
754
--
755
--     3.  Whenever @__h - l__@ does not overflow, we use this common formula for scaling:
756
--         @__ l + (h - l) * x__@.  However, instead of using @__[0.0, 1.0]__@ range we
757
--         use the top most bit of @__w__@ to decide whether we will treat the generated
758
--         floating point value as @__[0.0, 0.5]__@ range or @__[0.5, 1.0]__@ range and
759
--         use the left over bits to produce a floating point value in the half unit
760
--         range:
761
--
762
--         @
763
--         x = `fromIntegral` (`clearBit` w 31) / `fromIntegral` `maxBound`
764
--         @
765
--
766
--         Further scaling depends on the top most bit:
767
--
768
--         @
769
--         if `testBit` w 31
770
--            then l + (h - l) * x
771
--            else h + (l - h) * x
772
--         @
773
--
774
--         Because of this clever technique the result does not need clamping, since
775
--         scaled values are guaranteed to stay within the specified range. Another reason
776
--         why this tecnique is used for the common case instead of the one described in
777
--         @2.@ is because it avoids usage of @__1 - x__@, which consequently reduces loss
778
--         of randomness due to rounding.
779
--
780
--
781
-- What happens when @__NaN__@ or @__Infinity__@ are given to 'uniformRM'? We first
782
-- define them as constants:
783
--
784
-- >>> nan = read "NaN" :: Float
785
-- >>> inf = read "Infinity" :: Float
786
-- >>> g <- newIOGenM (mkStdGen 2024)
787
--
788
-- *   If at least one of \(l\) or \(h\) is @__NaN__@, the result is @__NaN__@.
789
--
790
--     >>> uniformRM (nan, 1) g
791
--     NaN
792
--     >>> uniformRM (-1, nan) g
793
--     NaN
794
--
795
-- *   If \(l\) and \(h\) are both @__Infinity__@ with opposing signs, then the result is @__NaN__@.
796
--
797
--     >>> uniformRM (-inf, inf) g
798
--     NaN
799
--     >>> uniformRM (inf, -inf) g
800
--     NaN
801
--
802
-- *   Otherwise, if \(l\) is @__Infinity__@ or @__-Infinity__@, the result is \(l\).
803
--
804
--     >>> uniformRM (inf, 1) g
805
--     Infinity
806
--     >>> uniformRM (-inf, 1) g
807
--     -Infinity
808
--
809
-- *   Otherwise, if \(h\) is @__Infinity__@ or @__-Infinity__@, the result is \(h\).
810
--
811
--     >>> uniformRM (1, inf) g
812
--     Infinity
813
--     >>> uniformRM (1, -inf) g
814
--     -Infinity
815
--
816
-- 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),
817
-- the [Java 10 standard library](https://docs.oracle.com/javase/10/docs/api/java/util/Random.html#doubles%28double,double%29)
818
-- and [CPython 3.8](https://github.com/python/cpython/blob/3.8/Lib/random.py#L417)
819
-- use a similar procedure to generate floating point values in a range.
820

821
-- $implemenstatefulegen
822
--
823
-- Typically, a monadic pseudo-random number generator has facilities to save
824
-- and restore its internal state in addition to generating pseudo-random numbers.
825
--
826
-- Here is an example instance for the monadic pseudo-random number generator
827
-- from the @mwc-random@ package:
828
--
829
-- > import qualified System.Random.MWC as MWC
830
-- > import qualified Data.Vector.Generic as G
831
--
832
-- > instance (s ~ PrimState m, PrimMonad m) => StatefulGen (MWC.Gen s) m where
833
-- >   uniformWord8 = MWC.uniform
834
-- >   uniformWord16 = MWC.uniform
835
-- >   uniformWord32 = MWC.uniform
836
-- >   uniformWord64 = MWC.uniform
837
-- >   uniformByteArrayM isPinned n g = stToPrim (fillByteArrayST isPinned n (MWC.uniform g))
838
--
839
-- > instance PrimMonad m => FrozenGen MWC.Seed m where
840
-- >   type MutableGen MWC.Seed m = MWC.Gen (PrimState m)
841
-- >   freezeGen = MWC.save
842
-- >   overwriteGen (Gen mv) (Seed v) = G.copy mv v
843
--
844
-- > instance PrimMonad m => ThawedGen MWC.Seed m where
845
-- >   thawGen = MWC.restore
846
--
847
-- === @FrozenGen@
848
--
849
-- `FrozenGen` gives us ability to use most of stateful pseudo-random number generator in
850
-- its immutable form, if one exists that is.  The biggest benefit that can be drawn from
851
-- a polymorphic access to a stateful pseudo-random number generator in a frozen form is
852
-- the ability to serialize, deserialize and possibly even use the stateful generator in a
853
-- pure setting without knowing the actual type of a generator ahead of time. For example
854
-- we can write a function that accepts a frozen state of some pseudo-random number
855
-- generator and produces a short list with random even integers.
856
--
857
-- >>> import Data.Int (Int8)
858
-- >>> import Control.Monad (replicateM)
859
-- >>> :{
860
-- myCustomRandomList :: ThawedGen f m => f -> m [Int8]
861
-- myCustomRandomList f =
862
--   withMutableGen_ f $ \gen -> do
863
--     len <- uniformRM (5, 10) gen
864
--     replicateM len $ do
865
--       x <- uniformM gen
866
--       pure $ if even x then x else x + 1
867
-- :}
868
--
869
-- and later we can apply it to a frozen version of a stateful generator, such as `STGen`:
870
--
871
-- >>> print $ runST $ myCustomRandomList (STGen (mkStdGen 217))
872
-- [-50,-2,4,-8,-58,-40,24,-32,-110,24]
873
--
874
-- Alternatively, instead of discarding the final state of the generator, as it happens
875
-- above, we could have used `withMutableGen`, which together with the result would give
876
-- us back its frozen form. This would allow us to store the end state of our generator
877
-- somewhere for the later reuse.
878

879
-- $references
880
--
881
-- 1. Guy L. Steele, Jr., Doug Lea, and Christine H. Flood. 2014. Fast
882
-- splittable pseudorandom number generators. In Proceedings of the 2014 ACM
883
-- International Conference on Object Oriented Programming Systems Languages &
884
-- Applications (OOPSLA '14). ACM, New York, NY, USA, 453-472. DOI:
885
-- <https://doi.org/10.1145/2660193.2660195>
886

887
-- $setup
888
-- >>> writeIORef theStdGen $ mkStdGen 2021
889
--
890
-- >>> :seti -XFlexibleContexts
891
-- >>> :seti -XFlexibleInstances
892
-- >>> :seti -XMultiParamTypeClasses
893
-- >>> :seti -XTypeFamilies
894
-- >>> :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