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

haskell / random / 432

05 Jul 2025 07:13PM UTC coverage: 69.035% (+0.3%) from 68.696%
432

push

github

web-flow
Merge a02eb707e 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

76.67
/src/System/Random/Internal.hs
1
{-# LANGUAGE BangPatterns #-}
2
{-# LANGUAGE CPP #-}
3
{-# LANGUAGE DefaultSignatures #-}
4
{-# LANGUAGE FlexibleContexts #-}
5
{-# LANGUAGE FlexibleInstances #-}
6
{-# LANGUAGE GHCForeignImportPrim #-}
7
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
8
{-# LANGUAGE MagicHash #-}
9
{-# LANGUAGE MultiParamTypeClasses #-}
10
{-# LANGUAGE RankNTypes #-}
11
{-# LANGUAGE ScopedTypeVariables #-}
12
{-# LANGUAGE Trustworthy #-}
13
{-# LANGUAGE TypeFamilyDependencies #-}
14
{-# LANGUAGE TypeOperators #-}
15
{-# LANGUAGE UndecidableInstances #-}
16
{-# LANGUAGE UnliftedFFITypes #-}
17
{-# OPTIONS_HADDOCK hide, not-home #-}
18

19
-- |
20
-- Module      :  System.Random.Internal
21
-- Copyright   :  (c) The University of Glasgow 2001
22
-- License     :  BSD-style (see the file LICENSE in the 'random' repository)
23
-- Maintainer  :  libraries@haskell.org
24
-- Stability   :  stable
25
--
26
-- This library deals with the common task of pseudo-random number generation.
27
module System.Random.Internal (
28
  -- * Pure and monadic pseudo-random number generator interfaces
29
  RandomGen (..),
30
  SplitGen (..),
31
  Seed (..),
32

33
  -- * Stateful
34
  StatefulGen (..),
35
  FrozenGen (..),
36
  ThawedGen (..),
37
  splitGenM,
38
  splitMutableGenM,
39

40
  -- ** Standard pseudo-random number generator
41
  StdGen (..),
42
  mkStdGen,
43
  mkStdGen64,
44
  theStdGen,
45

46
  -- * Monadic adapters for pure pseudo-random number generators
47

48
  -- ** Pure adapter
49
  StateGen (..),
50
  StateGenM (..),
51
  runStateGen,
52
  runStateGen_,
53
  runStateGenT,
54
  runStateGenT_,
55
  runStateGenST,
56
  runStateGenST_,
57

58
  -- * Pseudo-random values of various types
59
  Uniform (..),
60
  uniformViaFiniteM,
61
  UniformRange (..),
62
  uniformWordR,
63
  uniformDouble01M,
64
  uniformDoublePositive01M,
65
  uniformFloat01M,
66
  uniformFloatPositive01M,
67
  uniformEnumM,
68
  uniformEnumRM,
69
  uniformListM,
70
  uniformListRM,
71
  isInRangeOrd,
72
  isInRangeEnum,
73
  scaleFloating,
74

75
  -- * Generators for sequences of pseudo-random bytes
76
  uniformShortByteStringM,
77
  uniformByteArray,
78
  fillByteArrayST,
79
  genShortByteStringIO,
80
  genShortByteStringST,
81
  defaultUnsafeFillMutableByteArrayT,
82
  defaultUnsafeUniformFillMutableByteArray,
83

84
  -- ** Helpers for dealing with MutableByteArray
85
  newMutableByteArray,
86
  newPinnedMutableByteArray,
87
  freezeMutableByteArray,
88
  writeWord8,
89
  writeWord64LE,
90
  indexWord8,
91
  indexWord64LE,
92
  indexByteSliceWord64LE,
93
  sizeOfByteArray,
94
  shortByteStringToByteArray,
95
  byteArrayToShortByteString,
96
) where
97

98
import Control.Arrow
99
import Control.DeepSeq (NFData)
100
import Control.Monad (replicateM, when, (>=>))
101
import Control.Monad.Cont (ContT, runContT)
102
import Control.Monad.ST
103
import Control.Monad.State.Strict (MonadState (..), State, StateT (..), execStateT, runState)
104
import Control.Monad.Trans (MonadTrans, lift)
105
import Control.Monad.Trans.Identity (IdentityT (runIdentityT))
106
import Data.Array.Byte (ByteArray (..), MutableByteArray (..))
107
import Data.Bits
108
import Data.ByteString.Short.Internal (ShortByteString (SBS))
109
import Data.IORef (IORef, newIORef)
110
import Data.Int
111
import Data.Kind
112
import Data.Word
113
import Foreign.C.Types
114
import Foreign.Storable (Storable)
115
import GHC.Exts
116
import GHC.Generics
117
import GHC.IO (IO (..))
118
import GHC.ST (ST (..))
119
import GHC.Word
120
import Numeric.Natural (Natural)
121
import System.IO.Unsafe (unsafePerformIO)
122
import System.Random.Array
123
import System.Random.GFinite (Cardinality (..), Finite, GFinite (..))
124
import qualified System.Random.SplitMix as SM
125
import qualified System.Random.SplitMix32 as SM32
126

127
-- | This is a binary form of pseudo-random number generator's state. It is designed to be
128
-- safe and easy to use for input/output operations like restoring from file, transmitting
129
-- over the network, etc.
130
--
131
-- Constructor is not exported, becasue it is important for implementation to enforce the
132
-- invariant of the underlying byte array being of the exact same length as the generator has
133
-- specified in `System.Random.Seed.SeedSize`. Use `System.Random.Seed.mkSeed` and
134
-- `System.Random.Seed.unSeed` to get access to the raw bytes in a safe manner.
135
--
136
-- @since 1.3.0
137
newtype Seed g = Seed ByteArray
138
  deriving (Eq, Ord, Show)
×
139

140
-- | 'RandomGen' is an interface to pure pseudo-random number generators.
141
--
142
-- 'StdGen' is the standard 'RandomGen' instance provided by this library.
143
--
144
-- @since 1.0.0
145
{-# DEPRECATED next "No longer used" #-}
146

147
{-# DEPRECATED genRange "No longer used" #-}
148

149
class RandomGen g where
150
  {-# MINIMAL (genWord32 | genWord64 | (next, genRange)) #-}
151

152
  -- | Returns an 'Int' that is uniformly distributed over the range returned by
153
  -- 'genRange' (including both end points), and a new generator. Using 'next'
154
  -- is inefficient as all operations go via 'Integer'. See
155
  -- [here](https://alexey.kuleshevi.ch/blog/2019/12/21/random-benchmarks) for
156
  -- more details. It is thus deprecated.
157
  --
158
  -- @since 1.0.0
159
  next :: g -> (Int, g)
160
  next g = runStateGen g (uniformRM (genRange g))
×
161

162
  -- | Returns a 'Word8' that is uniformly distributed over the entire 'Word8'
163
  -- range.
164
  --
165
  -- @since 1.2.0
166
  genWord8 :: g -> (Word8, g)
167
  genWord8 = first fromIntegral . genWord32
2✔
168
  {-# INLINE genWord8 #-}
169

170
  -- | Returns a 'Word16' that is uniformly distributed over the entire 'Word16'
171
  -- range.
172
  --
173
  -- @since 1.2.0
174
  genWord16 :: g -> (Word16, g)
175
  genWord16 = first fromIntegral . genWord32
2✔
176
  {-# INLINE genWord16 #-}
177

178
  -- | Returns a 'Word32' that is uniformly distributed over the entire 'Word32'
179
  -- range.
180
  --
181
  -- @since 1.2.0
182
  genWord32 :: g -> (Word32, g)
183
  genWord32 = randomIvalIntegral (minBound, maxBound)
×
184
  -- Once `next` is removed, this implementation should be used instead:
185
  -- first fromIntegral . genWord64
186
  {-# INLINE genWord32 #-}
187

188
  -- | Returns a 'Word64' that is uniformly distributed over the entire 'Word64'
189
  -- range.
190
  --
191
  -- @since 1.2.0
192
  genWord64 :: g -> (Word64, g)
193
  genWord64 g =
×
194
    case genWord32 g of
×
195
      (l32, g') ->
196
        case genWord32 g' of
×
197
          (h32, g'') ->
198
            ((fromIntegral h32 `shiftL` 32) .|. fromIntegral l32, g'')
×
199
  {-# INLINE genWord64 #-}
200

201
  -- | @genWord32R upperBound g@ returns a 'Word32' that is uniformly
202
  -- distributed over the range @[0, upperBound]@.
203
  --
204
  -- @since 1.2.0
205
  genWord32R :: Word32 -> g -> (Word32, g)
206
  genWord32R m g = runStateGen g (unbiasedWordMult32 m)
2✔
207
  {-# INLINE genWord32R #-}
208

209
  -- | @genWord64R upperBound g@ returns a 'Word64' that is uniformly
210
  -- distributed over the range @[0, upperBound]@.
211
  --
212
  -- @since 1.2.0
213
  genWord64R :: Word64 -> g -> (Word64, g)
214
  genWord64R m g = runStateGen g (unsignedBitmaskWithRejectionM uniformWord64 m)
2✔
215
  {-# INLINE genWord64R #-}
216

217
  -- | Same as @`uniformByteArray` `False`@, but for `ShortByteString`.
218
  --
219
  -- @genShortByteString n g@ returns a 'ShortByteString' of length @n@ filled with
220
  -- pseudo-random bytes.
221
  --
222
  -- /Note/ - This function will be removed from the type class in the next major release as
223
  -- it is no longer needed because of `unsafeUniformFillMutableByteArray`.
224
  --
225
  -- @since 1.2.0
226
  genShortByteString :: Int -> g -> (ShortByteString, g)
227
  genShortByteString n g =
×
228
    case uniformByteArray False n g of
×
229
      (ByteArray ba#, g') -> (SBS ba#, g')
×
230
  {-# INLINE genShortByteString #-}
231

232
  -- | Fill in the supplied `MutableByteArray` with uniformly generated random bytes. This function
233
  -- is unsafe because it is not required to do any bounds checking. For a safe variant use
234
  -- `System.Random.Sateful.uniformFillMutableByteArrayM` instead.
235
  --
236
  -- Default type class implementation uses `defaultUnsafeUniformFillMutableByteArray`.
237
  --
238
  -- @since 1.3.0
239
  unsafeUniformFillMutableByteArray ::
240
    -- | Mutable array to fill with random bytes
241
    MutableByteArray s ->
242
    -- | Offset into a mutable array from the beginning in number of bytes. Offset must
243
    -- be non-negative, but this will not be checked
244
    Int ->
245
    -- | Number of randomly generated bytes to write into the array. Number of bytes
246
    -- must be non-negative and less then the total size of the array, minus the
247
    -- offset. This also will be checked.
248
    Int ->
249
    g ->
250
    ST s g
UNCOV
251
  unsafeUniformFillMutableByteArray = defaultUnsafeUniformFillMutableByteArray
×
252
  {-# INLINE unsafeUniformFillMutableByteArray #-}
253

254
  -- | Yields the range of values returned by 'next'.
255
  --
256
  -- It is required that:
257
  --
258
  -- *   If @(a, b) = 'genRange' g@, then @a < b@.
259
  -- *   'genRange' must not examine its argument so the value it returns is
260
  --     determined only by the instance of 'RandomGen'.
261
  --
262
  -- The default definition spans the full range of 'Int'.
263
  --
264
  -- @since 1.0.0
265
  genRange :: g -> (Int, Int)
266
  genRange _ = (minBound, maxBound)
×
267

268
  -- | Returns two distinct pseudo-random number generators.
269
  --
270
  -- Implementations should take care to ensure that the resulting generators
271
  -- are not correlated. Some pseudo-random number generators are not
272
  -- splittable. In that case, the 'split' implementation should fail with a
273
  -- descriptive 'error' message.
274
  --
275
  -- @since 1.0.0
276
  split :: g -> (g, g)
277
  default split :: SplitGen g => g -> (g, g)
278
  split = splitGen
×
279

280
{-# DEPRECATED genShortByteString "In favor of `System.Random.uniformShortByteString`" #-}
281

282
{-# DEPRECATED split "In favor of `splitGen`" #-}
283

284
-- | Pseudo-random generators that can be split into two separate and independent
285
-- psuedo-random generators should provide an instance for this type class.
286
--
287
-- Historically this functionality was included in the `RandomGen` type class in the
288
-- `split` function, however, few pseudo-random generators possess this property of
289
-- splittability. This lead the old `split` function being usually implemented in terms of
290
-- `error`.
291
--
292
-- @since 1.3.0
293
class RandomGen g => SplitGen g where
294
  -- | Returns two distinct pseudo-random number generators.
295
  --
296
  -- Implementations should take care to ensure that the resulting generators
297
  -- are not correlated.
298
  --
299
  -- @since 1.3.0
300
  splitGen :: g -> (g, g)
301

302
-- | 'StatefulGen' is an interface to monadic pseudo-random number generators.
303
--
304
-- @since 1.2.0
305
class Monad m => StatefulGen g m where
306
  {-# MINIMAL uniformWord32 | uniformWord64 #-}
307

308
  -- | @uniformWord32R upperBound g@ generates a 'Word32' that is uniformly
309
  -- distributed over the range @[0, upperBound]@.
310
  --
311
  -- @since 1.2.0
312
  uniformWord32R :: Word32 -> g -> m Word32
313
  uniformWord32R = unsignedBitmaskWithRejectionM uniformWord32
×
314
  {-# INLINE uniformWord32R #-}
315

316
  -- | @uniformWord64R upperBound g@ generates a 'Word64' that is uniformly
317
  -- distributed over the range @[0, upperBound]@.
318
  --
319
  -- @since 1.2.0
320
  uniformWord64R :: Word64 -> g -> m Word64
321
  uniformWord64R = unsignedBitmaskWithRejectionM uniformWord64
×
322
  {-# INLINE uniformWord64R #-}
323

324
  -- | Generates a 'Word8' that is uniformly distributed over the entire 'Word8'
325
  -- range.
326
  --
327
  -- The default implementation extracts a 'Word8' from 'uniformWord32'.
328
  --
329
  -- @since 1.2.0
330
  uniformWord8 :: g -> m Word8
331
  uniformWord8 = fmap fromIntegral . uniformWord32
×
332
  {-# INLINE uniformWord8 #-}
333

334
  -- | Generates a 'Word16' that is uniformly distributed over the entire
335
  -- 'Word16' range.
336
  --
337
  -- The default implementation extracts a 'Word16' from 'uniformWord32'.
338
  --
339
  -- @since 1.2.0
340
  uniformWord16 :: g -> m Word16
341
  uniformWord16 = fmap fromIntegral . uniformWord32
×
342
  {-# INLINE uniformWord16 #-}
343

344
  -- | Generates a 'Word32' that is uniformly distributed over the entire
345
  -- 'Word32' range.
346
  --
347
  -- The default implementation extracts a 'Word32' from 'uniformWord64'.
348
  --
349
  -- @since 1.2.0
350
  uniformWord32 :: g -> m Word32
351
  uniformWord32 = fmap fromIntegral . uniformWord64
×
352
  {-# INLINE uniformWord32 #-}
353

354
  -- | Generates a 'Word64' that is uniformly distributed over the entire
355
  -- 'Word64' range.
356
  --
357
  -- The default implementation combines two 'Word32' from 'uniformWord32' into
358
  -- one 'Word64'.
359
  --
360
  -- @since 1.2.0
361
  uniformWord64 :: g -> m Word64
362
  uniformWord64 g = do
×
363
    l32 <- uniformWord32 g
×
364
    h32 <- uniformWord32 g
×
365
    pure (shiftL (fromIntegral h32) 32 .|. fromIntegral l32)
×
366
  {-# INLINE uniformWord64 #-}
367

368
  -- | @uniformByteArrayM n g@ generates a 'ByteArray' of length @n@
369
  -- filled with pseudo-random bytes.
370
  --
371
  -- @since 1.3.0
372
  uniformByteArrayM ::
373
    -- | Should `ByteArray` be allocated as pinned memory or not
374
    Bool ->
375
    -- | Size of the newly created `ByteArray` in number of bytes.
376
    Int ->
377
    -- | Generator to use for filling in the newly created `ByteArray`
378
    g ->
379
    m ByteArray
380
  default uniformByteArrayM ::
381
    (RandomGen f, FrozenGen f m, g ~ MutableGen f m) => Bool -> Int -> g -> m ByteArray
382
  uniformByteArrayM isPinned n g = modifyGen g (uniformByteArray isPinned n)
2✔
383
  {-# INLINE uniformByteArrayM #-}
384

385
  -- | @uniformShortByteString n g@ generates a 'ShortByteString' of length @n@
386
  -- filled with pseudo-random bytes.
387
  --
388
  -- @since 1.2.0
389
  uniformShortByteString :: Int -> g -> m ShortByteString
390
  uniformShortByteString = uniformShortByteStringM
×
391
  {-# INLINE uniformShortByteString #-}
392

393
{-# DEPRECATED uniformShortByteString "In favor of `uniformShortByteStringM`" #-}
394

395
-- | This class is designed for mutable pseudo-random number generators that have a frozen
396
-- imutable counterpart that can be manipulated in pure code.
397
--
398
-- It also works great with frozen generators that are based on pure generators that have
399
-- a `RandomGen` instance.
400
--
401
-- Here are a few laws, which are important for this type class:
402
--
403
-- * Roundtrip and complete destruction on overwrite:
404
--
405
-- @
406
-- overwriteGen mg fg >> freezeGen mg = pure fg
407
-- @
408
--
409
-- * Modification of a mutable generator:
410
--
411
-- @
412
-- overwriteGen mg fg = modifyGen mg (const ((), fg)
413
-- @
414
--
415
-- * Freezing of a mutable generator:
416
--
417
-- @
418
-- freezeGen mg = modifyGen mg (\fg -> (fg, fg))
419
-- @
420
--
421
-- @since 1.2.0
422
class StatefulGen (MutableGen f m) m => FrozenGen f m where
423
  {-# MINIMAL (modifyGen | (freezeGen, overwriteGen)) #-}
424

425
  -- | Represents the state of the pseudo-random number generator for use with
426
  -- 'thawGen' and 'freezeGen'.
427
  --
428
  -- @since 1.2.0
429
  type MutableGen f m = (g :: Type) | g -> f
430

431
  -- | Saves the state of the pseudo-random number generator as a frozen seed.
432
  --
433
  -- @since 1.2.0
434
  freezeGen :: MutableGen f m -> m f
435
  freezeGen mg = modifyGen mg (\fg -> (fg, fg))
×
436
  {-# INLINE freezeGen #-}
437

438
  -- | Apply a pure function to the frozen pseudo-random number generator.
439
  --
440
  -- @since 1.3.0
441
  modifyGen :: MutableGen f m -> (f -> (a, f)) -> m a
442
  modifyGen mg f = do
×
443
    fg <- freezeGen mg
×
444
    case f fg of
×
445
      (a, !fg') -> a <$ overwriteGen mg fg'
×
446
  {-# INLINE modifyGen #-}
447

448
  -- | Overwrite contents of the mutable pseudo-random number generator with the
449
  -- supplied frozen one
450
  --
451
  -- @since 1.3.0
452
  overwriteGen :: MutableGen f m -> f -> m ()
453
  overwriteGen mg fg = modifyGen mg (const ((), fg))
1✔
454
  {-# INLINE overwriteGen #-}
455

456
-- | Functionality for thawing frozen generators is not part of the `FrozenGen` class,
457
-- becase not all mutable generators support functionality of creating new mutable
458
-- generators, which is what thawing is in its essence. For this reason `StateGen` does
459
-- not have an instance for this type class, but it has one for `FrozenGen`.
460
--
461
-- Here is an important law that relates this type class to `FrozenGen`
462
--
463
-- * Roundtrip and independence of mutable generators:
464
--
465
-- @
466
-- traverse thawGen fgs >>= traverse freezeGen = pure fgs
467
-- @
468
--
469
-- @since 1.3.0
470
class FrozenGen f m => ThawedGen f m where
471
  -- | Create a new mutable pseudo-random number generator from its frozen state.
472
  --
473
  -- @since 1.2.0
474
  thawGen :: f -> m (MutableGen f m)
475

476
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
477
-- pseudo-random number generator with one of the immutable pseudo-random number
478
-- generators produced by a `split` function and returns the other.
479
--
480
-- @since 1.3.0
481
splitGenM :: (SplitGen f, FrozenGen f m) => MutableGen f m -> m f
482
splitGenM = flip modifyGen splitGen
2✔
483

484
-- | Splits a pseudo-random number generator into two. Overwrites the mutable wrapper with
485
-- one of the resulting generators and returns the other as a new mutable generator.
486
--
487
-- @since 1.3.0
488
splitMutableGenM :: (SplitGen f, ThawedGen f m) => MutableGen f m -> m (MutableGen f m)
489
splitMutableGenM = splitGenM >=> thawGen
2✔
490

491
-- | Efficiently generates a sequence of pseudo-random bytes in a platform
492
-- independent manner.
493
--
494
-- @since 1.3.0
495
uniformByteArray ::
496
  RandomGen g =>
497
  -- | Should byte array be allocated in pinned or unpinned memory.
498
  Bool ->
499
  -- | Number of bytes to generate
500
  Int ->
501
  -- | Pure pseudo-random numer generator
502
  g ->
503
  (ByteArray, g)
504
uniformByteArray isPinned n0 g =
2✔
505
  runST $ do
2✔
506
    let !n = max 0 n0
2✔
507
    mba <-
508
      if isPinned
2✔
509
        then newPinnedMutableByteArray n
2✔
510
        else newMutableByteArray n
2✔
511
    g' <- unsafeUniformFillMutableByteArray mba 0 n g
2✔
512
    ba <- freezeMutableByteArray mba
2✔
513
    pure (ba, g')
2✔
514
{-# INLINE uniformByteArray #-}
515

516
-- | Using an `ST` action that generates 8 bytes at a time fill in a new `ByteArray` in
517
-- architecture agnostic manner.
518
--
519
-- @since 1.3.0
520
fillByteArrayST :: Bool -> Int -> ST s Word64 -> ST s ByteArray
521
fillByteArrayST isPinned n0 action = do
×
522
  let !n = max 0 n0
×
523
  mba <-
NEW
524
    if isPinned
×
NEW
525
      then newPinnedMutableByteArray n
×
NEW
526
      else newMutableByteArray n
×
527
  runIdentityT $ defaultUnsafeFillMutableByteArrayT mba 0 n (lift action)
×
528
  freezeMutableByteArray mba
×
529
{-# INLINE fillByteArrayST #-}
530

531
defaultUnsafeFillMutableByteArrayT ::
532
  (Monad (t (ST s)), MonadTrans t) =>
533
  MutableByteArray s ->
534
  Int ->
535
  Int ->
536
  t (ST s) Word64 ->
537
  t (ST s) ()
538
defaultUnsafeFillMutableByteArrayT mba offset n gen64 = do
2✔
539
  let !n64 = n `quot` 8
2✔
540
      !endIx64 = offset + n64 * 8
2✔
541
      !nrem = n `rem` 8
2✔
542
  let go !i =
2✔
543
        when (i < endIx64) $ do
2✔
544
          w64 <- gen64
2✔
545
          -- Writing 8 bytes at a time in a Little-endian order gives us
546
          -- platform portability
547
          lift $ writeWord64LE mba i w64
2✔
548
          go (i + 8)
2✔
549
  go offset
2✔
550
  when (nrem > 0) $ do
2✔
551
    let !endIx = offset + n
2✔
552
    w64 <- gen64
2✔
553
    -- In order to not mess up the byte order we write 1 byte at a time in
554
    -- Little endian order. It is tempting to simply generate as many bytes as we
555
    -- still need using smaller generators (eg. uniformWord8), but that would
556
    -- result in inconsistent tail when total length is slightly varied.
557
    lift $ writeByteSliceWord64LE mba (endIx - nrem) endIx w64
2✔
558
{-# INLINEABLE defaultUnsafeFillMutableByteArrayT #-}
559
{-# SPECIALIZE defaultUnsafeFillMutableByteArrayT ::
560
  MutableByteArray s ->
561
  Int ->
562
  Int ->
563
  IdentityT (ST s) Word64 ->
564
  IdentityT (ST s) ()
565
  #-}
566
{-# SPECIALIZE defaultUnsafeFillMutableByteArrayT ::
567
  MutableByteArray s ->
568
  Int ->
569
  Int ->
570
  StateT g (ST s) Word64 ->
571
  StateT g (ST s) ()
572
  #-}
573

574
-- | Efficiently generates a sequence of pseudo-random bytes in a platform
575
-- independent manner.
576
--
577
-- @since 1.2.0
578
defaultUnsafeUniformFillMutableByteArray ::
579
  RandomGen g =>
580
  MutableByteArray s ->
581
  -- | Starting offset
582
  Int ->
583
  -- | Number of random bytes to write into the array
584
  Int ->
585
  -- | ST action that can generate 8 random bytes at a time
586
  g ->
587
  ST s g
588
defaultUnsafeUniformFillMutableByteArray mba i0 n g =
2✔
589
  flip execStateT g $
2✔
590
    defaultUnsafeFillMutableByteArrayT mba i0 n (state genWord64)
2✔
591
{-# INLINE defaultUnsafeUniformFillMutableByteArray #-}
592

593
-- | Same as 'genShortByteStringIO', but runs in 'ST'.
594
--
595
-- @since 1.2.0
596
genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString
597
genShortByteStringST n0 action = byteArrayToShortByteString <$> fillByteArrayST False n0 action
×
598
{-# INLINE genShortByteStringST #-}
599
{-# DEPRECATED
600
  genShortByteStringST
601
  "In favor of `fillByteArrayST`, since `uniformShortByteString`, which it was used for, was also deprecated"
602
  #-}
603

604
-- | Efficiently fills in a new `ShortByteString` in a platform independent manner.
605
--
606
-- @since 1.2.0
607
genShortByteStringIO ::
608
  -- | Number of bytes to generate
609
  Int ->
610
  -- | IO action that can generate 8 random bytes at a time
611
  IO Word64 ->
612
  IO ShortByteString
UNCOV
613
genShortByteStringIO n ioAction = stToIO $ genShortByteStringST n (ioToST ioAction)
×
614
{-# INLINE genShortByteStringIO #-}
615
{-# DEPRECATED genShortByteStringIO "In favor of `fillByteArrayST`" #-}
616

617
-- | @uniformShortByteString n g@ generates a 'ShortByteString' of length @n@
618
-- filled with pseudo-random bytes.
619
--
620
-- @since 1.3.0
621
uniformShortByteStringM :: StatefulGen g m => Int -> g -> m ShortByteString
622
uniformShortByteStringM n g = byteArrayToShortByteString <$> uniformByteArrayM False n g
2✔
623
{-# INLINE uniformShortByteStringM #-}
624

625
-- | Opaque data type that carries the type of a pure pseudo-random number
626
-- generator.
627
--
628
-- @since 1.2.0
629
data StateGenM g = StateGenM
630

631
-- | Wrapper for pure state gen, which acts as an immutable seed for the corresponding
632
-- stateful generator `StateGenM`
633
--
634
-- @since 1.2.0
635
newtype StateGen g = StateGen {unStateGen :: g}
2✔
636
  deriving (Eq, Ord, Show, RandomGen, SplitGen, Storable, NFData)
×
637

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

652
instance (RandomGen g, MonadState g m) => FrozenGen (StateGen g) m where
653
  type MutableGen (StateGen g) m = StateGenM g
654
  freezeGen _ = fmap StateGen get
×
655
  modifyGen _ f = state (coerce f)
2✔
656
  {-# INLINE modifyGen #-}
657
  overwriteGen _ f = put (coerce f)
×
658
  {-# INLINE overwriteGen #-}
659

660
-- | Runs a monadic generating action in the `State` monad using a pure
661
-- pseudo-random number generator.
662
--
663
-- ====__Examples__
664
--
665
-- >>> import System.Random.Stateful
666
-- >>> let pureGen = mkStdGen 137
667
-- >>> runStateGen pureGen randomM :: (Int, StdGen)
668
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
669
--
670
-- @since 1.2.0
671
runStateGen :: RandomGen g => g -> (StateGenM g -> State g a) -> (a, g)
672
runStateGen g f = runState (f StateGenM) g
1✔
673
{-# INLINE runStateGen #-}
674

675
-- | Runs a monadic generating action in the `State` monad using a pure
676
-- pseudo-random number generator. Returns only the resulting pseudo-random
677
-- value.
678
--
679
-- ====__Examples__
680
--
681
-- >>> import System.Random.Stateful
682
-- >>> let pureGen = mkStdGen 137
683
-- >>> runStateGen_ pureGen randomM :: Int
684
-- 7879794327570578227
685
--
686
-- @since 1.2.0
687
runStateGen_ :: RandomGen g => g -> (StateGenM g -> State g a) -> a
688
runStateGen_ g = fst . runStateGen g
2✔
689
{-# INLINE runStateGen_ #-}
690

691
-- | Runs a monadic generating action in the `StateT` monad using a pure
692
-- pseudo-random number generator.
693
--
694
-- ====__Examples__
695
--
696
-- >>> import System.Random.Stateful
697
-- >>> let pureGen = mkStdGen 137
698
-- >>> runStateGenT pureGen randomM :: IO (Int, StdGen)
699
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
700
--
701
-- @since 1.2.0
702
runStateGenT :: RandomGen g => g -> (StateGenM g -> StateT g m a) -> m (a, g)
703
runStateGenT g f = runStateT (f StateGenM) g
1✔
704
{-# INLINE runStateGenT #-}
705

706
-- | Runs a monadic generating action in the `StateT` monad using a pure
707
-- pseudo-random number generator. Returns only the resulting pseudo-random
708
-- value.
709
--
710
-- ====__Examples__
711
--
712
-- >>> import System.Random.Stateful
713
-- >>> let pureGen = mkStdGen 137
714
-- >>> runStateGenT_ pureGen randomM :: IO Int
715
-- 7879794327570578227
716
--
717
-- @since 1.2.1
718
runStateGenT_ :: (RandomGen g, Functor f) => g -> (StateGenM g -> StateT g f a) -> f a
719
runStateGenT_ g = fmap fst . runStateGenT g
2✔
720
{-# INLINE runStateGenT_ #-}
721

722
-- | Runs a monadic generating action in the `ST` monad using a pure
723
-- pseudo-random number generator.
724
--
725
-- @since 1.2.0
726
runStateGenST :: RandomGen g => g -> (forall s. StateGenM g -> StateT g (ST s) a) -> (a, g)
727
runStateGenST g action = runST $ runStateGenT g action
2✔
728
{-# INLINE runStateGenST #-}
729

730
-- | Runs a monadic generating action in the `ST` monad using a pure
731
-- pseudo-random number generator. Same as `runStateGenST`, but discards the
732
-- resulting generator.
733
--
734
-- @since 1.2.1
735
runStateGenST_ :: RandomGen g => g -> (forall s. StateGenM g -> StateT g (ST s) a) -> a
736
runStateGenST_ g action = runST $ runStateGenT_ g action
×
737
{-# INLINE runStateGenST_ #-}
738

739
-- | Generates a list of pseudo-random values.
740
--
741
-- ====__Examples__
742
--
743
-- >>> import System.Random.Stateful
744
-- >>> let pureGen = mkStdGen 137
745
-- >>> g <- newIOGenM pureGen
746
-- >>> uniformListM 10 g :: IO [Bool]
747
-- [True,True,True,True,False,True,True,False,False,False]
748
--
749
-- @since 1.2.0
750
uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a]
751
uniformListM n gen = replicateM n (uniformM gen)
2✔
752
{-# INLINE uniformListM #-}
753

754
-- | Generates a list of pseudo-random values in a specified range.
755
--
756
-- ====__Examples__
757
--
758
-- >>> import System.Random.Stateful
759
-- >>> let pureGen = mkStdGen 137
760
-- >>> g <- newIOGenM pureGen
761
-- >>> uniformListRM 10 (20, 30) g :: IO [Int]
762
-- [23,21,28,25,28,28,26,25,29,27]
763
--
764
-- @since 1.3.0
765
uniformListRM :: (StatefulGen g m, UniformRange a) => Int -> (a, a) -> g -> m [a]
766
uniformListRM n range gen = replicateM n (uniformRM range gen)
1✔
767
{-# INLINE uniformListRM #-}
768

769
-- | The standard pseudo-random number generator.
NEW
770
newtype StdGen = StdGen {unStdGen :: SM.SMGen}
×
771
  deriving (Show, RandomGen, SplitGen, NFData)
1✔
772

773
instance Eq StdGen where
774
  StdGen x1 == StdGen x2 = SM.unseedSMGen x1 == SM.unseedSMGen x2
2✔
775

776
instance RandomGen SM.SMGen where
777
  next = SM.nextInt
×
778
  {-# INLINE next #-}
779
  genWord32 = SM.nextWord32
2✔
780
  {-# INLINE genWord32 #-}
781
  genWord64 = SM.nextWord64
2✔
782
  {-# INLINE genWord64 #-}
783

784
  -- Despite that this is the same default implementation as in the type class definition,
785
  -- for some mysterious reason without this overwrite, performance of ByteArray generation
786
  -- slows down by a factor of x4:
787
  unsafeUniformFillMutableByteArray = defaultUnsafeUniformFillMutableByteArray
2✔
788
  {-# INLINE unsafeUniformFillMutableByteArray #-}
789

790
instance SplitGen SM.SMGen where
791
  splitGen = SM.splitSMGen
2✔
792
  {-# INLINE splitGen #-}
793

794
instance RandomGen SM32.SMGen where
795
  next = SM32.nextInt
×
796
  {-# INLINE next #-}
797
  genWord32 = SM32.nextWord32
×
798
  {-# INLINE genWord32 #-}
799
  genWord64 = SM32.nextWord64
×
800
  {-# INLINE genWord64 #-}
801

802
instance SplitGen SM32.SMGen where
803
  splitGen = SM32.splitSMGen
×
804
  {-# INLINE splitGen #-}
805

806
-- | Constructs a 'StdGen' deterministically from an `Int` seed. See `mkStdGen64` for a `Word64`
807
-- variant that is architecture agnostic.
808
mkStdGen :: Int -> StdGen
809
mkStdGen = mkStdGen64 . fromIntegral
2✔
810

811
-- | Constructs a 'StdGen' deterministically from a `Word64` seed.
812
--
813
-- The difference between `mkStdGen` is that `mkStdGen64` will work the same on 64-bit and
814
-- 32-bit architectures, while the former can only use 32-bit of information for
815
-- initializing the psuedo-random number generator on 32-bit operating systems
816
--
817
-- @since 1.3.0
818
mkStdGen64 :: Word64 -> StdGen
819
mkStdGen64 = StdGen . SM.mkSMGen
2✔
820

821
-- | Global mutable veriable with `StdGen`
822
theStdGen :: IORef StdGen
823
theStdGen = unsafePerformIO $ SM.initSMGen >>= newIORef . StdGen
2✔
824
{-# NOINLINE theStdGen #-}
825

826
-- | The class of types for which a uniformly distributed value can be drawn
827
-- from all possible values of the type.
828
--
829
-- @since 1.2.0
830
class Uniform a where
831
  -- | Generates a value uniformly distributed over all possible values of that
832
  -- type.
833
  --
834
  -- There is a default implementation via 'Generic':
835
  --
836
  -- >>> :seti -XDeriveGeneric -XDeriveAnyClass
837
  -- >>> import GHC.Generics (Generic)
838
  -- >>> import System.Random.Stateful
839
  -- >>> data MyBool = MyTrue | MyFalse deriving (Show, Generic, Finite, Uniform)
840
  -- >>> data Action = Code MyBool | Eat (Maybe Bool) | Sleep deriving (Show, Generic, Finite, Uniform)
841
  -- >>> gen <- newIOGenM (mkStdGen 42)
842
  -- >>> uniformListM 10 gen :: IO [Action]
843
  -- [Code MyTrue,Code MyTrue,Eat Nothing,Code MyFalse,Eat (Just False),Eat (Just True),Eat Nothing,Eat (Just False),Sleep,Code MyFalse]
844
  --
845
  -- @since 1.2.0
846
  uniformM :: StatefulGen g m => g -> m a
847
  default uniformM :: (StatefulGen g m, Generic a, GUniform (Rep a)) => g -> m a
UNCOV
848
  uniformM = fmap to . (`runContT` pure) . guniformM
×
849
  {-# INLINE uniformM #-}
850

851
-- | Default implementation of 'Uniform' type class for 'Generic' data.
852
-- It's important to use 'ContT', because without it 'fmap' and '>>=' remain
853
-- polymorphic too long and GHC fails to inline or specialize it, ending up
854
-- building full 'Rep' a structure in memory. 'ContT'
855
-- makes 'fmap' and '>>=' used in 'guniformM' monomorphic, so GHC is able to
856
-- specialize 'Generic' instance reasonably close to a handwritten one.
857
class GUniform f where
858
  guniformM :: StatefulGen g m => g -> ContT r m (f a)
859

860
instance GUniform f => GUniform (M1 i c f) where
861
  guniformM = fmap M1 . guniformM
×
862
  {-# INLINE guniformM #-}
863

864
instance Uniform a => GUniform (K1 i a) where
865
  guniformM = fmap K1 . lift . uniformM
×
866
  {-# INLINE guniformM #-}
867

868
instance GUniform U1 where
869
  guniformM = const $ return U1
×
870
  {-# INLINE guniformM #-}
871

872
instance (GUniform f, GUniform g) => GUniform (f :*: g) where
873
  guniformM g = (:*:) <$> guniformM g <*> guniformM g
×
874
  {-# INLINE guniformM #-}
875

876
instance (GFinite f, GFinite g) => GUniform (f :+: g) where
877
  guniformM = lift . finiteUniformM
×
878
  {-# INLINE guniformM #-}
879

880
finiteUniformM :: forall g m f a. (StatefulGen g m, GFinite f) => g -> m (f a)
NEW
881
finiteUniformM =
×
NEW
882
  fmap toGFinite . case gcardinality (proxy# :: Proxy# f) of
×
883
    Shift n
NEW
884
      | n <= 64 -> fmap toInteger . unsignedBitmaskWithRejectionM uniformWord64 (bit n - 1)
×
NEW
885
      | otherwise -> boundedByPowerOf2ExclusiveIntegralM n
×
886
    Card n
NEW
887
      | n <= bit 64 -> fmap toInteger . unsignedBitmaskWithRejectionM uniformWord64 (fromInteger n - 1)
×
NEW
888
      | otherwise -> boundedExclusiveIntegralM n
×
889
{-# INLINE finiteUniformM #-}
890

891
-- | A definition of 'Uniform' for 'System.Random.Finite' types.
892
-- If your data has several fields of sub-'Word' cardinality,
893
-- this instance may be more efficient than one, derived via 'Generic' and 'GUniform'.
894
--
895
-- >>> :seti -XDeriveGeneric -XDeriveAnyClass
896
-- >>> import GHC.Generics (Generic)
897
-- >>> import System.Random.Stateful
898
-- >>> data Triple = Triple Word8 Word8 Word8 deriving (Show, Generic, Finite)
899
-- >>> instance Uniform Triple where uniformM = uniformViaFiniteM
900
-- >>> gen <- newIOGenM (mkStdGen 42)
901
-- >>> uniformListM 5 gen :: IO [Triple]
902
-- [Triple 60 226 48,Triple 234 194 151,Triple 112 96 95,Triple 51 251 15,Triple 6 0 208]
903
uniformViaFiniteM :: (StatefulGen g m, Generic a, GFinite (Rep a)) => g -> m a
UNCOV
904
uniformViaFiniteM = fmap to . finiteUniformM
×
905
{-# INLINE uniformViaFiniteM #-}
906

907
-- | The class of types for which a uniformly distributed value can be drawn
908
-- from a range.
909
--
910
-- @since 1.2.0
911
class UniformRange a where
912
  -- | Generates a value uniformly distributed over the provided range, which
913
  -- is interpreted as inclusive in the lower and upper bound.
914
  --
915
  -- *   @uniformRM (1 :: Int, 4 :: Int)@ generates values uniformly from the
916
  --     set \(\{1,2,3,4\}\)
917
  --
918
  -- *   @uniformRM (1 :: Float, 4 :: Float)@ generates values uniformly from
919
  --     the set \(\{x\;|\;1 \le x \le 4\}\)
920
  --
921
  -- The following law should hold to make the function always defined:
922
  --
923
  -- > uniformRM (a, b) = uniformRM (b, a)
924
  --
925
  -- The range is understood as defined by means of 'isInRange', so
926
  --
927
  -- > isInRange (a, b) <$> uniformRM (a, b) gen == pure True
928
  --
929
  -- but beware of
930
  -- [floating point number caveats](System-Random-Stateful.html#fpcaveats).
931
  --
932
  -- There is a default implementation via 'Generic':
933
  --
934
  -- >>> :seti -XDeriveGeneric -XDeriveAnyClass
935
  -- >>> import GHC.Generics (Generic)
936
  -- >>> import Data.Word (Word8)
937
  -- >>> import Control.Monad (replicateM)
938
  -- >>> import System.Random.Stateful
939
  -- >>> gen <- newIOGenM (mkStdGen 42)
940
  -- >>> data Tuple = Tuple Bool Word8 deriving (Show, Generic, UniformRange)
941
  -- >>> replicateM 10 (uniformRM (Tuple False 100, Tuple True 150) gen)
942
  -- [Tuple False 102,Tuple True 118,Tuple False 115,Tuple True 113,Tuple True 126,Tuple False 127,Tuple True 130,Tuple False 113,Tuple False 150,Tuple False 125]
943
  --
944
  -- @since 1.2.0
945
  uniformRM :: StatefulGen g m => (a, a) -> g -> m a
946

947
  -- | A notion of (inclusive) ranges prescribed to @a@.
948
  --
949
  -- Ranges are symmetric:
950
  --
951
  -- > isInRange (lo, hi) x == isInRange (hi, lo) x
952
  --
953
  -- Ranges include their endpoints:
954
  --
955
  -- > isInRange (lo, hi) lo == True
956
  --
957
  -- When endpoints coincide, there is nothing else:
958
  --
959
  -- > isInRange (x, x) y == x == y
960
  --
961
  -- Endpoints are endpoints:
962
  --
963
  -- > isInRange (lo, hi) x ==>
964
  -- > isInRange (lo, x) hi == x == hi
965
  --
966
  -- Ranges are transitive relations:
967
  --
968
  -- > isInRange (lo, hi) lo' && isInRange (lo, hi) hi' && isInRange (lo', hi') x
969
  -- > ==> isInRange (lo, hi) x
970
  --
971
  -- There is a default implementation of 'isInRange' via 'Generic'. Other helper function
972
  -- that can be used for implementing this function are `isInRangeOrd` and
973
  -- `isInRangeEnum`.
974
  --
975
  -- Note that the @isRange@ method from @Data.Ix@ is /not/ a suitable default
976
  -- implementation of 'isInRange'. Unlike 'isInRange', @isRange@ is not
977
  -- required to be symmetric, and many @isRange@ implementations are not
978
  -- symmetric in practice.
979
  --
980
  -- @since 1.3.0
981
  isInRange :: (a, a) -> a -> Bool
982

983
  default uniformRM :: (StatefulGen g m, Generic a, GUniformRange (Rep a)) => (a, a) -> g -> m a
984
  uniformRM (a, b) = fmap to . (`runContT` pure) . guniformRM (from a, from b)
2✔
985
  {-# INLINE uniformRM #-}
986

987
  default isInRange :: (Generic a, GUniformRange (Rep a)) => (a, a) -> a -> Bool
988
  isInRange (a, b) x = gisInRange (from a, from b) (from x)
2✔
989
  {-# INLINE isInRange #-}
990

991
class GUniformRange f where
992
  guniformRM :: StatefulGen g m => (f a, f a) -> g -> ContT r m (f a)
993
  gisInRange :: (f a, f a) -> f a -> Bool
994

995
instance GUniformRange f => GUniformRange (M1 i c f) where
996
  guniformRM (M1 a, M1 b) = fmap M1 . guniformRM (a, b)
2✔
997
  {-# INLINE guniformRM #-}
998
  gisInRange (M1 a, M1 b) (M1 x) = gisInRange (a, b) x
2✔
999

1000
instance UniformRange a => GUniformRange (K1 i a) where
1001
  guniformRM (K1 a, K1 b) = fmap K1 . lift . uniformRM (a, b)
2✔
1002
  {-# INLINE guniformRM #-}
1003
  gisInRange (K1 a, K1 b) (K1 x) = isInRange (a, b) x
2✔
1004

1005
instance GUniformRange U1 where
UNCOV
1006
  guniformRM = const $ const $ return U1
×
1007
  {-# INLINE guniformRM #-}
1008
  gisInRange = const $ const True
2✔
1009

1010
instance (GUniformRange f, GUniformRange g) => GUniformRange (f :*: g) where
1011
  guniformRM (x1 :*: y1, x2 :*: y2) g =
2✔
1012
    (:*:) <$> guniformRM (x1, x2) g <*> guniformRM (y1, y2) g
1✔
1013
  {-# INLINE guniformRM #-}
1014
  gisInRange (x1 :*: y1, x2 :*: y2) (x3 :*: y3) =
2✔
1015
    gisInRange (x1, x2) x3 && gisInRange (y1, y2) y3
2✔
1016

1017
-- | Utilize `Ord` instance to decide if a value is within the range. Designed to be used
1018
-- for implementing `isInRange`
1019
--
1020
-- @since 1.3.0
1021
isInRangeOrd :: Ord a => (a, a) -> a -> Bool
1022
isInRangeOrd (a, b) x = min a b <= x && x <= max a b
2✔
1023

1024
-- | Utilize `Enum` instance to decide if a value is within the range. Designed to be used
1025
-- for implementing `isInRange`
1026
--
1027
-- @since 1.3.0
1028
isInRangeEnum :: Enum a => (a, a) -> a -> Bool
UNCOV
1029
isInRangeEnum (a, b) x = isInRangeOrd (fromEnum a, fromEnum b) (fromEnum x)
×
1030

1031
instance UniformRange Integer where
1032
  uniformRM = uniformIntegralM
2✔
1033
  {-# INLINE uniformRM #-}
1034
  isInRange = isInRangeOrd
2✔
1035

1036
instance UniformRange Natural where
1037
  uniformRM = uniformIntegralM
2✔
1038
  {-# INLINE uniformRM #-}
1039
  isInRange = isInRangeOrd
2✔
1040

1041
instance Uniform Int8 where
1042
  uniformM = fmap (fromIntegral :: Word8 -> Int8) . uniformWord8
2✔
1043
  {-# INLINE uniformM #-}
1044

1045
instance UniformRange Int8 where
1046
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int8 -> Word8) fromIntegral
2✔
1047
  {-# INLINE uniformRM #-}
1048
  isInRange = isInRangeOrd
2✔
1049

1050
instance Uniform Int16 where
1051
  uniformM = fmap (fromIntegral :: Word16 -> Int16) . uniformWord16
2✔
1052
  {-# INLINE uniformM #-}
1053

1054
instance UniformRange Int16 where
1055
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int16 -> Word16) fromIntegral
2✔
1056
  {-# INLINE uniformRM #-}
1057
  isInRange = isInRangeOrd
2✔
1058

1059
instance Uniform Int32 where
1060
  uniformM = fmap (fromIntegral :: Word32 -> Int32) . uniformWord32
2✔
1061
  {-# INLINE uniformM #-}
1062

1063
instance UniformRange Int32 where
1064
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int32 -> Word32) fromIntegral
2✔
1065
  {-# INLINE uniformRM #-}
1066
  isInRange = isInRangeOrd
2✔
1067

1068
instance Uniform Int64 where
1069
  uniformM = fmap (fromIntegral :: Word64 -> Int64) . uniformWord64
2✔
1070
  {-# INLINE uniformM #-}
1071

1072
instance UniformRange Int64 where
1073
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int64 -> Word64) fromIntegral
2✔
1074
  {-# INLINE uniformRM #-}
1075
  isInRange = isInRangeOrd
2✔
1076

1077
instance Uniform Int where
1078
  uniformM
2✔
1079
    | wordSizeInBits == 64 =
1✔
1080
        fmap (fromIntegral :: Word64 -> Int) . uniformWord64
2✔
UNCOV
1081
    | otherwise =
×
NEW
1082
        fmap (fromIntegral :: Word32 -> Int) . uniformWord32
×
1083
  {-# INLINE uniformM #-}
1084

1085
instance UniformRange Int where
1086
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int -> Word) fromIntegral
2✔
1087
  {-# INLINE uniformRM #-}
1088
  isInRange = isInRangeOrd
2✔
1089

1090
instance Uniform Word where
1091
  uniformM
2✔
1092
    | wordSizeInBits == 64 =
1✔
1093
        fmap (fromIntegral :: Word64 -> Word) . uniformWord64
2✔
UNCOV
1094
    | otherwise =
×
NEW
1095
        fmap (fromIntegral :: Word32 -> Word) . uniformWord32
×
1096
  {-# INLINE uniformM #-}
1097

1098
instance UniformRange Word where
1099
  uniformRM = unsignedBitmaskWithRejectionRM
2✔
1100
  {-# INLINE uniformRM #-}
1101
  isInRange = isInRangeOrd
2✔
1102

1103
-- | Architecture specific `Word` generation in the specified lower range
1104
--
1105
-- @since 1.3.0
1106
uniformWordR ::
1107
  StatefulGen g m =>
1108
  -- | Maximum value to generate
1109
  Word ->
1110
  -- | Stateful generator
1111
  g ->
1112
  m Word
1113
uniformWordR r
2✔
1114
  | wordSizeInBits == 64 =
1✔
1115
      fmap (fromIntegral :: Word64 -> Word) . uniformWord64R ((fromIntegral :: Word -> Word64) r)
2✔
UNCOV
1116
  | otherwise =
×
NEW
1117
      fmap (fromIntegral :: Word32 -> Word) . uniformWord32R ((fromIntegral :: Word -> Word32) r)
×
1118
{-# INLINE uniformWordR #-}
1119

1120
instance Uniform Word8 where
1121
  uniformM = uniformWord8
2✔
1122
  {-# INLINE uniformM #-}
1123

1124
instance UniformRange Word8 where
1125
  uniformRM = unbiasedWordMult32RM
2✔
1126
  {-# INLINE uniformRM #-}
1127
  isInRange = isInRangeOrd
2✔
1128

1129
instance Uniform Word16 where
1130
  uniformM = uniformWord16
2✔
1131
  {-# INLINE uniformM #-}
1132

1133
instance UniformRange Word16 where
1134
  uniformRM = unbiasedWordMult32RM
2✔
1135
  {-# INLINE uniformRM #-}
1136
  isInRange = isInRangeOrd
2✔
1137

1138
instance Uniform Word32 where
1139
  uniformM = uniformWord32
2✔
1140
  {-# INLINE uniformM #-}
1141

1142
instance UniformRange Word32 where
1143
  uniformRM = unbiasedWordMult32RM
2✔
1144
  {-# INLINE uniformRM #-}
1145
  isInRange = isInRangeOrd
2✔
1146

1147
instance Uniform Word64 where
1148
  uniformM = uniformWord64
2✔
1149
  {-# INLINE uniformM #-}
1150

1151
instance UniformRange Word64 where
1152
  uniformRM = unsignedBitmaskWithRejectionRM
2✔
1153
  {-# INLINE uniformRM #-}
1154
  isInRange = isInRangeOrd
2✔
1155

1156
#if __GLASGOW_HASKELL__ >= 802
1157
instance Uniform CBool where
UNCOV
1158
  uniformM = fmap CBool . uniformM
×
1159
  {-# INLINE uniformM #-}
1160
instance UniformRange CBool where
1161
  uniformRM (CBool b, CBool t) = fmap CBool . uniformRM (b, t)
2✔
1162
  {-# INLINE uniformRM #-}
1163
  isInRange = isInRangeOrd
2✔
1164
#endif
1165

1166
instance Uniform CChar where
1167
  uniformM = fmap CChar . uniformM
2✔
1168
  {-# INLINE uniformM #-}
1169

1170
instance UniformRange CChar where
1171
  uniformRM (CChar b, CChar t) = fmap CChar . uniformRM (b, t)
2✔
1172
  {-# INLINE uniformRM #-}
1173
  isInRange = isInRangeOrd
2✔
1174

1175
instance Uniform CSChar where
1176
  uniformM = fmap CSChar . uniformM
2✔
1177
  {-# INLINE uniformM #-}
1178

1179
instance UniformRange CSChar where
1180
  uniformRM (CSChar b, CSChar t) = fmap CSChar . uniformRM (b, t)
2✔
1181
  {-# INLINE uniformRM #-}
1182
  isInRange = isInRangeOrd
2✔
1183

1184
instance Uniform CUChar where
1185
  uniformM = fmap CUChar . uniformM
2✔
1186
  {-# INLINE uniformM #-}
1187

1188
instance UniformRange CUChar where
1189
  uniformRM (CUChar b, CUChar t) = fmap CUChar . uniformRM (b, t)
2✔
1190
  {-# INLINE uniformRM #-}
1191
  isInRange = isInRangeOrd
2✔
1192

1193
instance Uniform CShort where
1194
  uniformM = fmap CShort . uniformM
2✔
1195
  {-# INLINE uniformM #-}
1196

1197
instance UniformRange CShort where
1198
  uniformRM (CShort b, CShort t) = fmap CShort . uniformRM (b, t)
2✔
1199
  {-# INLINE uniformRM #-}
1200
  isInRange = isInRangeOrd
2✔
1201

1202
instance Uniform CUShort where
1203
  uniformM = fmap CUShort . uniformM
2✔
1204
  {-# INLINE uniformM #-}
1205

1206
instance UniformRange CUShort where
1207
  uniformRM (CUShort b, CUShort t) = fmap CUShort . uniformRM (b, t)
2✔
1208
  {-# INLINE uniformRM #-}
1209
  isInRange = isInRangeOrd
2✔
1210

1211
instance Uniform CInt where
1212
  uniformM = fmap CInt . uniformM
2✔
1213
  {-# INLINE uniformM #-}
1214

1215
instance UniformRange CInt where
1216
  uniformRM (CInt b, CInt t) = fmap CInt . uniformRM (b, t)
2✔
1217
  {-# INLINE uniformRM #-}
1218
  isInRange = isInRangeOrd
2✔
1219

1220
instance Uniform CUInt where
1221
  uniformM = fmap CUInt . uniformM
2✔
1222
  {-# INLINE uniformM #-}
1223

1224
instance UniformRange CUInt where
1225
  uniformRM (CUInt b, CUInt t) = fmap CUInt . uniformRM (b, t)
2✔
1226
  {-# INLINE uniformRM #-}
1227
  isInRange = isInRangeOrd
2✔
1228

1229
instance Uniform CLong where
1230
  uniformM = fmap CLong . uniformM
2✔
1231
  {-# INLINE uniformM #-}
1232

1233
instance UniformRange CLong where
1234
  uniformRM (CLong b, CLong t) = fmap CLong . uniformRM (b, t)
2✔
1235
  {-# INLINE uniformRM #-}
1236
  isInRange = isInRangeOrd
2✔
1237

1238
instance Uniform CULong where
1239
  uniformM = fmap CULong . uniformM
2✔
1240
  {-# INLINE uniformM #-}
1241

1242
instance UniformRange CULong where
1243
  uniformRM (CULong b, CULong t) = fmap CULong . uniformRM (b, t)
2✔
1244
  {-# INLINE uniformRM #-}
1245
  isInRange = isInRangeOrd
2✔
1246

1247
instance Uniform CPtrdiff where
1248
  uniformM = fmap CPtrdiff . uniformM
2✔
1249
  {-# INLINE uniformM #-}
1250

1251
instance UniformRange CPtrdiff where
1252
  uniformRM (CPtrdiff b, CPtrdiff t) = fmap CPtrdiff . uniformRM (b, t)
2✔
1253
  {-# INLINE uniformRM #-}
1254
  isInRange = isInRangeOrd
2✔
1255

1256
instance Uniform CSize where
1257
  uniformM = fmap CSize . uniformM
2✔
1258
  {-# INLINE uniformM #-}
1259

1260
instance UniformRange CSize where
1261
  uniformRM (CSize b, CSize t) = fmap CSize . uniformRM (b, t)
2✔
1262
  {-# INLINE uniformRM #-}
1263
  isInRange = isInRangeOrd
2✔
1264

1265
instance Uniform CWchar where
1266
  uniformM = fmap CWchar . uniformM
2✔
1267
  {-# INLINE uniformM #-}
1268

1269
instance UniformRange CWchar where
1270
  uniformRM (CWchar b, CWchar t) = fmap CWchar . uniformRM (b, t)
2✔
1271
  {-# INLINE uniformRM #-}
1272
  isInRange = isInRangeOrd
2✔
1273

1274
instance Uniform CSigAtomic where
1275
  uniformM = fmap CSigAtomic . uniformM
2✔
1276
  {-# INLINE uniformM #-}
1277

1278
instance UniformRange CSigAtomic where
1279
  uniformRM (CSigAtomic b, CSigAtomic t) = fmap CSigAtomic . uniformRM (b, t)
2✔
1280
  {-# INLINE uniformRM #-}
1281
  isInRange = isInRangeOrd
2✔
1282

1283
instance Uniform CLLong where
1284
  uniformM = fmap CLLong . uniformM
2✔
1285
  {-# INLINE uniformM #-}
1286

1287
instance UniformRange CLLong where
1288
  uniformRM (CLLong b, CLLong t) = fmap CLLong . uniformRM (b, t)
2✔
1289
  {-# INLINE uniformRM #-}
1290
  isInRange = isInRangeOrd
2✔
1291

1292
instance Uniform CULLong where
1293
  uniformM = fmap CULLong . uniformM
2✔
1294
  {-# INLINE uniformM #-}
1295

1296
instance UniformRange CULLong where
1297
  uniformRM (CULLong b, CULLong t) = fmap CULLong . uniformRM (b, t)
2✔
1298
  {-# INLINE uniformRM #-}
1299
  isInRange = isInRangeOrd
2✔
1300

1301
instance Uniform CIntPtr where
1302
  uniformM = fmap CIntPtr . uniformM
2✔
1303
  {-# INLINE uniformM #-}
1304

1305
instance UniformRange CIntPtr where
1306
  uniformRM (CIntPtr b, CIntPtr t) = fmap CIntPtr . uniformRM (b, t)
2✔
1307
  {-# INLINE uniformRM #-}
1308
  isInRange = isInRangeOrd
2✔
1309

1310
instance Uniform CUIntPtr where
1311
  uniformM = fmap CUIntPtr . uniformM
2✔
1312
  {-# INLINE uniformM #-}
1313

1314
instance UniformRange CUIntPtr where
1315
  uniformRM (CUIntPtr b, CUIntPtr t) = fmap CUIntPtr . uniformRM (b, t)
2✔
1316
  {-# INLINE uniformRM #-}
1317
  isInRange = isInRangeOrd
2✔
1318

1319
instance Uniform CIntMax where
1320
  uniformM = fmap CIntMax . uniformM
2✔
1321
  {-# INLINE uniformM #-}
1322

1323
instance UniformRange CIntMax where
1324
  uniformRM (CIntMax b, CIntMax t) = fmap CIntMax . uniformRM (b, t)
2✔
1325
  {-# INLINE uniformRM #-}
1326
  isInRange = isInRangeOrd
2✔
1327

1328
instance Uniform CUIntMax where
1329
  uniformM = fmap CUIntMax . uniformM
2✔
1330
  {-# INLINE uniformM #-}
1331

1332
instance UniformRange CUIntMax where
1333
  uniformRM (CUIntMax b, CUIntMax t) = fmap CUIntMax . uniformRM (b, t)
2✔
1334
  {-# INLINE uniformRM #-}
1335
  isInRange = isInRangeOrd
2✔
1336

1337
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1338
instance UniformRange CFloat where
1339
  uniformRM (CFloat l, CFloat h) = fmap CFloat . uniformRM (l, h)
2✔
1340
  {-# INLINE uniformRM #-}
1341
  isInRange = isInRangeOrd
2✔
1342

1343
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1344
instance UniformRange CDouble where
1345
  uniformRM (CDouble l, CDouble h) = fmap CDouble . uniformRM (l, h)
2✔
1346
  {-# INLINE uniformRM #-}
1347
  isInRange = isInRangeOrd
2✔
1348

1349
-- The `chr#` and `ord#` are the prim functions that will be called, regardless of which
1350
-- way you gonna do the `Char` conversion, so it is better to call them directly and
1351
-- bypass all the hoops. Also because `intToChar` and `charToInt` are internal functions
1352
-- and are called on valid character ranges it is impossible to generate an invalid
1353
-- `Char`, therefore it is totally fine to omit all the unnecessary checks involved in
1354
-- other paths of conversion.
1355
word32ToChar :: Word32 -> Char
1356
#if __GLASGOW_HASKELL__ < 902
1357
word32ToChar (W32# w#) = C# (chr# (word2Int# w#))
2✔
1358
#else
1359
word32ToChar (W32# w#) = C# (chr# (word2Int# (word32ToWord# w#)))
1360
#endif
1361
{-# INLINE word32ToChar #-}
1362

1363
charToWord32 :: Char -> Word32
1364
#if __GLASGOW_HASKELL__ < 902
1365
charToWord32 (C# c#) = W32# (int2Word# (ord# c#))
2✔
1366
#else
1367
charToWord32 (C# c#) = W32# (wordToWord32# (int2Word# (ord# c#)))
1368
#endif
1369
{-# INLINE charToWord32 #-}
1370

1371
instance Uniform Char where
1372
  uniformM g = word32ToChar <$> unbiasedWordMult32 (charToWord32 maxBound) g
2✔
1373
  {-# INLINE uniformM #-}
1374

1375
instance UniformRange Char where
1376
  uniformRM (l, h) g =
2✔
1377
    word32ToChar <$> unbiasedWordMult32RM (charToWord32 l, charToWord32 h) g
1✔
1378
  {-# INLINE uniformRM #-}
1379
  isInRange = isInRangeOrd
2✔
1380

1381
instance Uniform () where
UNCOV
1382
  uniformM = const $ pure ()
×
1383
  {-# INLINE uniformM #-}
1384

1385
instance UniformRange () where
1386
  uniformRM = const $ const $ pure ()
2✔
1387
  {-# INLINE uniformRM #-}
1388

1389
instance Uniform Bool where
1390
  uniformM = fmap wordToBool . uniformWord8
2✔
1391
    where
1392
      wordToBool w = (w .&. 1) /= 0
2✔
1393
      {-# INLINE wordToBool #-}
1394
  {-# INLINE uniformM #-}
1395

1396
instance UniformRange Bool where
1397
  uniformRM (False, False) _g = return False
2✔
1398
  uniformRM (True, True) _g = return True
2✔
1399
  uniformRM _ g = uniformM g
1✔
1400
  {-# INLINE uniformRM #-}
1401
  isInRange = isInRangeOrd
2✔
1402

1403
instance (Finite a, Uniform a) => Uniform (Maybe a)
1404

1405
instance (Finite a, Uniform a, Finite b, Uniform b) => Uniform (Either a b)
1406

1407
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1408
instance UniformRange Double where
1409
  uniformRM (l, h) g
2✔
1410
    | l == h = return l
2✔
1411
    | isInfinite l || isInfinite h =
2✔
1412
        -- Optimisation exploiting absorption:
1413
        --    (+Infinity) + (-Infinity) = NaN
1414
        --    (-Infinity) + (+Infinity) = NaN
1415
        --    (+Infinity) + _           = +Infinity
1416
        --    (-Infinity) + _           = -Infinity
1417
        --              _ + (+Infinity) = +Infinity
1418
        --              _ + (-Infinity) = -Infinity
1419
        return $! h + l
2✔
1420
    | otherwise = do
1✔
1421
        w64 <- uniformWord64 g
1✔
1422
        pure $! scaleFloating l h w64
2✔
1423
  {-# INLINE uniformRM #-}
1424
  isInRange = isInRangeOrd
2✔
1425

1426
-- | Generates uniformly distributed 'Double' in the range \([0, 1]\).
1427
--   Numbers are generated by generating uniform 'Word64' and dividing
1428
--   it by \(2^{64}\). It's used to implement 'UniformRange' instance for
1429
--   'Double'.
1430
--
1431
-- @since 1.2.0
1432
uniformDouble01M :: forall g m. StatefulGen g m => g -> m Double
1433
uniformDouble01M g = do
2✔
1434
  w64 <- uniformWord64 g
1✔
1435
  return $ fromIntegral w64 / m
2✔
1436
  where
1437
    m = fromIntegral (maxBound :: Word64) :: Double
2✔
1438
{-# INLINE uniformDouble01M #-}
1439

1440
-- | Generates uniformly distributed 'Double' in the range
1441
--   \((0, 1]\). Number is generated as \(2^{-64}/2+\operatorname{uniformDouble01M}\).
1442
--   Constant is 1\/2 of smallest nonzero value which could be generated
1443
--   by 'uniformDouble01M'.
1444
--
1445
-- @since 1.2.0
1446
uniformDoublePositive01M :: forall g m. StatefulGen g m => g -> m Double
1447
uniformDoublePositive01M g = (+ d) <$> uniformDouble01M g
1✔
1448
  where
1449
    -- We add small constant to shift generated value from zero. It's
1450
    -- selected as 1/2 of smallest possible nonzero value
1451
    d = 2.710505431213761e-20 -- 2**(-65)
2✔
1452
{-# INLINE uniformDoublePositive01M #-}
1453

1454
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1455
instance UniformRange Float where
1456
  uniformRM (l, h) g
2✔
1457
    | l == h = return l
2✔
1458
    | isInfinite l || isInfinite h =
2✔
1459
        -- Optimisation exploiting absorption:
1460
        --    (+Infinity) + (-Infinity) = NaN
1461
        --    (-Infinity) + (+Infinity) = NaN
1462
        --    (+Infinity) + _           = +Infinity
1463
        --    (-Infinity) + _           = -Infinity
1464
        --              _ + (+Infinity) = +Infinity
1465
        --              _ + (-Infinity) = -Infinity
1466
        return $! h + l
2✔
1467
    | otherwise = do
1✔
1468
        w32 <- uniformWord32 g
1✔
1469
        pure $! scaleFloating l h w32
2✔
1470
  {-# INLINE uniformRM #-}
1471
  isInRange = isInRangeOrd
2✔
1472

1473
-- | This is the function that is used to scale a floating point value from random word range to
1474
-- the custom @[low, high]@ range.
1475
--
1476
-- @since 1.3.0
1477
scaleFloating ::
1478
  forall a w.
1479
  (RealFloat a, Integral w, Bounded w, FiniteBits w) =>
1480
  -- | Low
1481
  a ->
1482
  -- | High
1483
  a ->
1484
  -- | Uniformly distributed unsigned integral value that will be used for converting to a floating
1485
  -- point value and subsequent scaling to the specified range
1486
  w ->
1487
  a
1488
scaleFloating l h w =
2✔
1489
  if isInfinite diff
1✔
1490
    then
NEW
1491
      let !x = fromIntegral w / m
×
NEW
1492
          !y = x * l + (1 - x) * h
×
NEW
1493
       in max (min y (max l h)) (min l h)
×
1494
    else
1495
      let !topMostBit = finiteBitSize w - 1
1✔
1496
          !x = fromIntegral (clearBit w topMostBit) / m
2✔
1497
       in if testBit w topMostBit
2✔
1498
            then l + diff * x
2✔
1499
            else h + negate diff * x
2✔
1500
  where
1501
    !diff = h - l
2✔
1502
    !m = fromIntegral (maxBound :: w) :: a
2✔
1503
{-# INLINE scaleFloating #-}
1504

1505
-- | Generates uniformly distributed 'Float' in the range \([0, 1]\).
1506
--   Numbers are generated by generating uniform 'Word32' and dividing
1507
--   it by \(2^{32}\). It's used to implement 'UniformRange' instance for 'Float'.
1508
--
1509
-- @since 1.2.0
1510
uniformFloat01M :: forall g m. StatefulGen g m => g -> m Float
1511
uniformFloat01M g = do
2✔
1512
  w32 <- uniformWord32 g
1✔
1513
  return $ fromIntegral w32 / m
2✔
1514
  where
1515
    m = fromIntegral (maxBound :: Word32) :: Float
2✔
1516
{-# INLINE uniformFloat01M #-}
1517

1518
-- | Generates uniformly distributed 'Float' in the range
1519
--   \((0, 1]\). Number is generated as \(2^{-32}/2+\operatorname{uniformFloat01M}\).
1520
--   Constant is 1\/2 of smallest nonzero value which could be generated
1521
--   by 'uniformFloat01M'.
1522
--
1523
-- @since 1.2.0
1524
uniformFloatPositive01M :: forall g m. StatefulGen g m => g -> m Float
1525
uniformFloatPositive01M g = (+ d) <$> uniformFloat01M g
1✔
1526
  where
1527
    -- See uniformDoublePositive01M
1528
    d = 1.1641532182693481e-10 -- 2**(-33)
2✔
1529
{-# INLINE uniformFloatPositive01M #-}
1530

1531
-- | Generates uniformly distributed 'Enum'.
1532
-- One can use it to define a 'Uniform' instance:
1533
--
1534
-- > data Colors = Red | Green | Blue deriving (Enum, Bounded)
1535
-- > instance Uniform Colors where uniformM = uniformEnumM
1536
--
1537
-- @since 1.3.0
1538
uniformEnumM :: forall a g m. (Enum a, Bounded a, StatefulGen g m) => g -> m a
UNCOV
1539
uniformEnumM g = toEnum <$> uniformRM (fromEnum (minBound :: a), fromEnum (maxBound :: a)) g
×
1540
{-# INLINE uniformEnumM #-}
1541

1542
-- | Generates uniformly distributed 'Enum' in the given range.
1543
-- One can use it to define a 'UniformRange' instance:
1544
--
1545
-- > data Colors = Red | Green | Blue deriving (Enum)
1546
-- > instance UniformRange Colors where
1547
-- >   uniformRM = uniformEnumRM
1548
-- >   inInRange (lo, hi) x = isInRange (fromEnum lo, fromEnum hi) (fromEnum x)
1549
--
1550
-- @since 1.3.0
1551
uniformEnumRM :: forall a g m. (Enum a, StatefulGen g m) => (a, a) -> g -> m a
1552
uniformEnumRM (l, h) g = toEnum <$> uniformRM (fromEnum l, fromEnum h) g
1✔
1553
{-# INLINE uniformEnumRM #-}
1554

1555
-- The two integer functions below take an [inclusive,inclusive] range.
1556
randomIvalIntegral :: (RandomGen g, Integral a) => (a, a) -> g -> (a, g)
UNCOV
1557
randomIvalIntegral (l, h) = randomIvalInteger (toInteger l, toInteger h)
×
1558

1559
{-# SPECIALIZE randomIvalInteger ::
1560
  Num a =>
1561
  (Integer, Integer) -> StdGen -> (a, StdGen)
1562
  #-}
1563
randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
UNCOV
1564
randomIvalInteger (l, h) rng
×
NEW
1565
  | l > h = randomIvalInteger (h, l) rng
×
NEW
1566
  | otherwise = case f 1 0 rng of (v, rng') -> (fromInteger (l + v `mod` k), rng')
×
1567
  where
NEW
1568
    (genlo, genhi) = genRange rng
×
NEW
1569
    b = fromIntegral genhi - fromIntegral genlo + 1 :: Integer
×
1570

1571
    -- Probabilities of the most likely and least likely result
1572
    -- will differ at most by a factor of (1 +- 1/q). Assuming the RandomGen
1573
    -- is uniform, of course
1574

1575
    -- On average, log q / log b more pseudo-random values will be generated
1576
    -- than the minimum
NEW
1577
    q = 1000 :: Integer
×
NEW
1578
    k = h - l + 1
×
NEW
1579
    magtgt = k * q
×
1580

1581
    -- generate pseudo-random values until we exceed the target magnitude
NEW
1582
    f mag v g
×
NEW
1583
      | mag >= magtgt = (v, g)
×
NEW
1584
      | otherwise = v' `seq` f (mag * b) v' g'
×
1585
      where
NEW
1586
        (x, g') = next g
×
NEW
1587
        v' = v * b + (fromIntegral x - fromIntegral genlo)
×
1588

1589
-- | Generate an integral in the range @[l, h]@ if @l <= h@ and @[h, l]@
1590
-- otherwise.
1591
uniformIntegralM :: forall a g m. (Bits a, Integral a, StatefulGen g m) => (a, a) -> g -> m a
1592
uniformIntegralM (l, h) gen = case l `compare` h of
2✔
1593
  LT -> do
2✔
1594
    let limit = h - l
2✔
1595
    bounded <- case toIntegralSized limit :: Maybe Word64 of
2✔
1596
      Just limitAsWord64 ->
1597
        -- Optimisation: if 'limit' fits into 'Word64', generate a bounded
1598
        -- 'Word64' and then convert to 'Integer'
1599
        fromIntegral <$> unsignedBitmaskWithRejectionM uniformWord64 limitAsWord64 gen
1✔
1600
      Nothing -> boundedExclusiveIntegralM (limit + 1) gen
1✔
1601
    return $ l + bounded
2✔
1602
  GT -> uniformIntegralM (h, l) gen
1✔
1603
  EQ -> pure l
2✔
1604
{-# INLINEABLE uniformIntegralM #-}
1605
{-# SPECIALIZE uniformIntegralM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer #-}
1606
{-# SPECIALIZE uniformIntegralM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural #-}
1607

1608
-- | Generate an integral in the range @[0, s)@ using a variant of Lemire's
1609
-- multiplication method.
1610
--
1611
-- Daniel Lemire. 2019. Fast Random Integer Generation in an Interval. In ACM
1612
-- Transactions on Modeling and Computer Simulation
1613
-- https://doi.org/10.1145/3230636
1614
--
1615
-- PRECONDITION (unchecked): s > 0
1616
boundedExclusiveIntegralM :: forall a g m. (Bits a, Integral a, StatefulGen g m) => a -> g -> m a
1617
boundedExclusiveIntegralM s gen = go
2✔
1618
  where
1619
    n = integralWordSize s
2✔
1620
    -- We renamed 'L' from the paper to 'k' here because 'L' is not a valid
1621
    -- variable name in Haskell and 'l' is already used in the algorithm.
1622
    k = wordSizeInBits * n
2✔
1623
    twoToK = (1 :: a) `shiftL` k
2✔
1624
    modTwoToKMask = twoToK - 1
2✔
1625

1626
    t = (twoToK - s) `rem` s -- `rem`, instead of `mod` because `twoToK >= s` is guaranteed
2✔
1627
    go :: (Bits a, Integral a, StatefulGen g m) => m a
1628
    go = do
2✔
1629
      x <- uniformIntegralWords n gen
1✔
1630
      let m = x * s
2✔
1631
      -- m .&. modTwoToKMask == m `mod` twoToK
1632
      let l = m .&. modTwoToKMask
2✔
1633
      if l < t
1✔
UNCOV
1634
        then go
×
1635
        -- m `shiftR` k == m `quot` twoToK
1636
        else return $ m `shiftR` k
2✔
1637
{-# INLINE boundedExclusiveIntegralM #-}
1638

1639
-- | boundedByPowerOf2ExclusiveIntegralM s ~ boundedExclusiveIntegralM (bit s)
1640
boundedByPowerOf2ExclusiveIntegralM ::
1641
  forall a g m. (Bits a, Integral a, StatefulGen g m) => Int -> g -> m a
UNCOV
1642
boundedByPowerOf2ExclusiveIntegralM s gen = do
×
1643
  let n = (s + wordSizeInBits - 1) `quot` wordSizeInBits
×
1644
  x <- uniformIntegralWords n gen
×
1645
  return $ x .&. (bit s - 1)
×
1646
{-# INLINE boundedByPowerOf2ExclusiveIntegralM #-}
1647

1648
-- | @integralWordSize i@ returns that least @w@ such that
1649
-- @i <= WORD_SIZE_IN_BITS^w@.
1650
integralWordSize :: (Bits a, Num a) => a -> Int
1651
integralWordSize = go 0
2✔
1652
  where
1653
    go !acc i
2✔
1654
      | i == 0 = acc
2✔
1655
      | otherwise = go (acc + 1) (i `shiftR` wordSizeInBits)
1✔
1656
{-# INLINE integralWordSize #-}
1657

1658
-- | @uniformIntegralWords n@ is a uniformly pseudo-random integral in the range
1659
-- @[0, WORD_SIZE_IN_BITS^n)@.
1660
uniformIntegralWords :: forall a g m. (Bits a, Integral a, StatefulGen g m) => Int -> g -> m a
1661
uniformIntegralWords n gen = go 0 n
2✔
1662
  where
1663
    go !acc i
2✔
1664
      | i == 0 = return acc
2✔
1665
      | otherwise = do
1✔
1666
          (w :: Word) <- uniformM gen
1✔
1667
          go ((acc `shiftL` wordSizeInBits) .|. fromIntegral w) (i - 1)
2✔
1668
{-# INLINE uniformIntegralWords #-}
1669

1670
-- | Uniformly generate an 'Integral' in an inclusive-inclusive range.
1671
--
1672
-- Only use for integrals size less than or equal to that of 'Word32'.
1673
unbiasedWordMult32RM :: forall a g m. (Integral a, StatefulGen g m) => (a, a) -> g -> m a
1674
unbiasedWordMult32RM (b, t) g
2✔
1675
  | b <= t = (+ b) . fromIntegral <$> unbiasedWordMult32 (fromIntegral (t - b)) g
1✔
1676
  | otherwise = (+ t) . fromIntegral <$> unbiasedWordMult32 (fromIntegral (b - t)) g
1✔
1677
{-# INLINE unbiasedWordMult32RM #-}
1678

1679
-- | Uniformly generate Word32 in @[0, s]@.
1680
unbiasedWordMult32 :: forall g m. StatefulGen g m => Word32 -> g -> m Word32
1681
unbiasedWordMult32 s g
2✔
1682
  | s == maxBound = uniformWord32 g
1✔
1683
  | otherwise = unbiasedWordMult32Exclusive (s + 1) g
1✔
1684
{-# INLINE unbiasedWordMult32 #-}
1685

1686
-- | See [Lemire's paper](https://arxiv.org/pdf/1805.10941.pdf),
1687
-- [O\'Neill's
1688
-- blogpost](https://www.pcg-random.org/posts/bounded-rands.html) and
1689
-- more directly [O\'Neill's github
1690
-- repo](https://github.com/imneme/bounded-rands/blob/3d71f53c975b1e5b29f2f3b05a74e26dab9c3d84/bounded32.cpp#L234).
1691
-- N.B. The range is [0,r) **not** [0,r].
1692
unbiasedWordMult32Exclusive :: forall g m. StatefulGen g m => Word32 -> g -> m Word32
1693
unbiasedWordMult32Exclusive r g = go
2✔
1694
  where
1695
    t :: Word32
1696
    t = (-r) `mod` r -- Calculates 2^32 `mod` r!!!
2✔
1697
    go :: StatefulGen g m => m Word32
1698
    go = do
2✔
1699
      x <- uniformWord32 g
2✔
1700
      let m :: Word64
1701
          m = fromIntegral x * fromIntegral r
2✔
1702
          l :: Word32
1703
          l = fromIntegral m
2✔
1704
      if l >= t then return (fromIntegral $ m `shiftR` 32) else go
2✔
1705
{-# INLINE unbiasedWordMult32Exclusive #-}
1706

1707
-- | This only works for unsigned integrals
1708
unsignedBitmaskWithRejectionRM ::
1709
  forall a g m.
1710
  (FiniteBits a, Num a, Ord a, Uniform a, StatefulGen g m) =>
1711
  (a, a) ->
1712
  g ->
1713
  m a
1714
unsignedBitmaskWithRejectionRM (bottom, top) gen
2✔
1715
  | bottom == top = pure top
2✔
1716
  | otherwise = (b +) <$> unsignedBitmaskWithRejectionM uniformM r gen
1✔
1717
  where
1718
    (b, r) = if bottom > top then (top, bottom - top) else (bottom, top - bottom)
2✔
1719
{-# INLINE unsignedBitmaskWithRejectionRM #-}
1720

1721
-- | This works for signed integrals by explicit conversion to unsigned and abusing
1722
-- overflow. It uses `unsignedBitmaskWithRejectionM`, therefore it requires functions that
1723
-- take the value to unsigned and back.
1724
signedBitmaskWithRejectionRM ::
1725
  forall a b g m.
1726
  (Num a, Num b, Ord b, Ord a, FiniteBits a, StatefulGen g m, Uniform a) =>
1727
  -- | Convert signed to unsigned. @a@ and @b@ must be of the same size.
1728
  (b -> a) ->
1729
  -- | Convert unsigned to signed. @a@ and @b@ must be of the same size.
1730
  (a -> b) ->
1731
  -- | Range.
1732
  (b, b) ->
1733
  -- | Generator.
1734
  g ->
1735
  m b
1736
signedBitmaskWithRejectionRM toUnsigned fromUnsigned (bottom, top) gen
2✔
1737
  | bottom == top = pure top
2✔
UNCOV
1738
  | otherwise =
×
1739
      (b +) . fromUnsigned <$> unsignedBitmaskWithRejectionM uniformM r gen
1✔
1740
  where
1741
    -- This works in all cases, see Appendix 1 at the end of the file.
1742

1743
    (b, r) =
1744
      if bottom > top
2✔
1745
        then (top, toUnsigned bottom - toUnsigned top)
2✔
1746
        else (bottom, toUnsigned top - toUnsigned bottom)
2✔
1747
{-# INLINE signedBitmaskWithRejectionRM #-}
1748

1749
-- | Detailed explanation about the algorithm employed here can be found in this post:
1750
-- http://web.archive.org/web/20200520071940/https://www.pcg-random.org/posts/bounded-rands.html
1751
unsignedBitmaskWithRejectionM ::
1752
  forall a g m. (Ord a, FiniteBits a, Num a, StatefulGen g m) => (g -> m a) -> a -> g -> m a
1753
unsignedBitmaskWithRejectionM genUniformM range gen = go
2✔
1754
  where
1755
    mask :: a
1756
    mask = complement zeroBits `shiftR` countLeadingZeros (range .|. 1)
2✔
1757
    go = do
2✔
1758
      x <- genUniformM gen
1✔
1759
      let x' = x .&. mask
2✔
1760
      if x' > range
2✔
1761
        then go
2✔
1762
        else pure x'
2✔
1763
{-# INLINE unsignedBitmaskWithRejectionM #-}
1764

1765
-------------------------------------------------------------------------------
1766
-- 'Uniform' instances for tuples
1767
-------------------------------------------------------------------------------
1768

1769
instance (Uniform a, Uniform b) => Uniform (a, b) where
1770
  uniformM g = (,) <$> uniformM g <*> uniformM g
1✔
1771
  {-# INLINE uniformM #-}
1772

1773
instance (Uniform a, Uniform b, Uniform c) => Uniform (a, b, c) where
1774
  uniformM g = (,,) <$> uniformM g <*> uniformM g <*> uniformM g
1✔
1775
  {-# INLINE uniformM #-}
1776

1777
instance (Uniform a, Uniform b, Uniform c, Uniform d) => Uniform (a, b, c, d) where
1778
  uniformM g = (,,,) <$> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g
1✔
1779
  {-# INLINE uniformM #-}
1780

1781
instance (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e) => Uniform (a, b, c, d, e) where
1782
  uniformM g = (,,,,) <$> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g
1✔
1783
  {-# INLINE uniformM #-}
1784

1785
instance
1786
  (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f) =>
1787
  Uniform (a, b, c, d, e, f)
1788
  where
1789
  uniformM g =
2✔
1790
    (,,,,,)
2✔
1791
      <$> uniformM g
1✔
1792
      <*> uniformM g
1✔
1793
      <*> uniformM g
1✔
1794
      <*> uniformM g
1✔
1795
      <*> uniformM g
1✔
1796
      <*> uniformM g
1✔
1797
  {-# INLINE uniformM #-}
1798

1799
instance
1800
  (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f, Uniform g) =>
1801
  Uniform (a, b, c, d, e, f, g)
1802
  where
1803
  uniformM g =
2✔
1804
    (,,,,,,)
2✔
1805
      <$> uniformM g
1✔
1806
      <*> uniformM g
1✔
1807
      <*> uniformM g
1✔
1808
      <*> uniformM g
1✔
1809
      <*> uniformM g
1✔
1810
      <*> uniformM g
1✔
1811
      <*> uniformM g
1✔
1812
  {-# INLINE uniformM #-}
1813

1814
instance (UniformRange a, UniformRange b) => UniformRange (a, b)
1815

1816
instance (UniformRange a, UniformRange b, UniformRange c) => UniformRange (a, b, c)
1817

1818
instance (UniformRange a, UniformRange b, UniformRange c, UniformRange d) => UniformRange (a, b, c, d)
1819

1820
instance
1821
  (UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e) =>
1822
  UniformRange (a, b, c, d, e)
1823

1824
instance
1825
  (UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e, UniformRange f) =>
1826
  UniformRange (a, b, c, d, e, f)
1827

1828
instance
1829
  ( UniformRange a
1830
  , UniformRange b
1831
  , UniformRange c
1832
  , UniformRange d
1833
  , UniformRange e
1834
  , UniformRange f
1835
  , UniformRange g
1836
  ) =>
1837
  UniformRange (a, b, c, d, e, f, g)
1838

1839
-- Appendix 1.
1840
--
1841
-- @top@ and @bottom@ are signed integers of bit width @n@. @toUnsigned@
1842
-- converts a signed integer to an unsigned number of the same bit width @n@.
1843
--
1844
--     range = toUnsigned top - toUnsigned bottom
1845
--
1846
-- This works out correctly thanks to modular arithmetic. Conceptually,
1847
--
1848
--     toUnsigned x | x >= 0 = x
1849
--     toUnsigned x | x <  0 = 2^n + x
1850
--
1851
-- The following combinations are possible:
1852
--
1853
-- 1. @bottom >= 0@ and @top >= 0@
1854
-- 2. @bottom < 0@ and @top >= 0@
1855
-- 3. @bottom < 0@ and @top < 0@
1856
--
1857
-- Note that @bottom >= 0@ and @top < 0@ is impossible because of the
1858
-- invariant @bottom < top@.
1859
--
1860
-- For any signed integer @i@ of width @n@, we have:
1861
--
1862
--     -2^(n-1) <= i <= 2^(n-1) - 1
1863
--
1864
-- Considering each combination in turn, we have
1865
--
1866
-- 1. @bottom >= 0@ and @top >= 0@
1867
--
1868
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1869
--                 --^ top    >= 0, so toUnsigned top    == top
1870
--                 --^ bottom >= 0, so toUnsigned bottom == bottom
1871
--           = (top - bottom) `mod` 2^n
1872
--                 --^ top <= 2^(n-1) - 1 and bottom >= 0
1873
--                 --^ top - bottom <= 2^(n-1) - 1
1874
--                 --^ 0 < top - bottom <= 2^(n-1) - 1
1875
--           = top - bottom
1876
--
1877
-- 2. @bottom < 0@ and @top >= 0@
1878
--
1879
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1880
--                 --^ top    >= 0, so toUnsigned top    == top
1881
--                 --^ bottom <  0, so toUnsigned bottom == 2^n + bottom
1882
--           = (top - (2^n + bottom)) `mod` 2^n
1883
--                 --^ summand -2^n cancels out in calculation modulo 2^n
1884
--           = (top - bottom) `mod` 2^n
1885
--                 --^ top <= 2^(n-1) - 1 and bottom >= -2^(n-1)
1886
--                 --^ top - bottom <= (2^(n-1) - 1) - (-2^(n-1)) = 2^n - 1
1887
--                 --^ 0 < top - bottom <= 2^n - 1
1888
--           = top - bottom
1889
--
1890
-- 3. @bottom < 0@ and @top < 0@
1891
--
1892
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1893
--                 --^ top    < 0, so toUnsigned top    == 2^n + top
1894
--                 --^ bottom < 0, so toUnsigned bottom == 2^n + bottom
1895
--           = ((2^n + top) - (2^n + bottom)) `mod` 2^n
1896
--                 --^ summand 2^n cancels out in calculation modulo 2^n
1897
--           = (top - bottom) `mod` 2^n
1898
--                 --^ top <= -1
1899
--                 --^ bottom >= -2^(n-1)
1900
--                 --^ top - bottom <= -1 - (-2^(n-1)) = 2^(n-1) - 1
1901
--                 --^ 0 < top - bottom <= 2^(n-1) - 1
1902
--           = top - bottom
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