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

haskell / random / 416

06 Jan 2025 05:44PM UTC coverage: 68.696%. Remained the same
416

push

github

web-flow
Merge pull request #177 from Shimuuar/typo

Fix typo in haddocks

632 of 920 relevant lines covered (68.7%)

1.29 hits per line

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

76.94
/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 TypeOperators #-}
14
{-# LANGUAGE TypeFamilyDependencies #-}
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
  -- * Stateful
33
  , StatefulGen(..)
34
  , FrozenGen(..)
35
  , ThawedGen(..)
36
  , splitGenM
37
  , splitMutableGenM
38

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

45
  -- * Monadic adapters for pure pseudo-random number generators
46
  -- ** Pure adapter
47
  , StateGen(..)
48
  , StateGenM(..)
49
  , runStateGen
50
  , runStateGen_
51
  , runStateGenT
52
  , runStateGenT_
53
  , runStateGenST
54
  , runStateGenST_
55

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

73
  -- * Generators for sequences of pseudo-random bytes
74
  , uniformShortByteStringM
75
  , uniformByteArray
76
  , fillByteArrayST
77
  , genShortByteStringIO
78
  , genShortByteStringST
79
  , defaultUnsafeFillMutableByteArrayT
80
  , defaultUnsafeUniformFillMutableByteArray
81
  -- ** Helpers for dealing with MutableByteArray
82
  , newMutableByteArray
83
  , newPinnedMutableByteArray
84
  , freezeMutableByteArray
85
  , writeWord8
86
  , writeWord64LE
87
  , indexWord8
88
  , indexWord64LE
89
  , indexByteSliceWord64LE
90
  , sizeOfByteArray
91
  , shortByteStringToByteArray
92
  , byteArrayToShortByteString
93
  ) where
94

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

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

137

138
-- | 'RandomGen' is an interface to pure pseudo-random number generators.
139
--
140
-- 'StdGen' is the standard 'RandomGen' instance provided by this library.
141
--
142
-- @since 1.0.0
143
{-# DEPRECATED next "No longer used" #-}
144
{-# DEPRECATED genRange "No longer used" #-}
145
class RandomGen g where
146
  {-# MINIMAL (genWord32|genWord64|(next,genRange)) #-}
147
  -- | Returns an 'Int' that is uniformly distributed over the range returned by
148
  -- 'genRange' (including both end points), and a new generator. Using 'next'
149
  -- is inefficient as all operations go via 'Integer'. See
150
  -- [here](https://alexey.kuleshevi.ch/blog/2019/12/21/random-benchmarks) for
151
  -- more details. It is thus deprecated.
152
  --
153
  -- @since 1.0.0
154
  next :: g -> (Int, g)
155
  next g = runStateGen g (uniformRM (genRange g))
×
156

157
  -- | Returns a 'Word8' that is uniformly distributed over the entire 'Word8'
158
  -- range.
159
  --
160
  -- @since 1.2.0
161
  genWord8 :: g -> (Word8, g)
162
  genWord8 = first fromIntegral . genWord32
2✔
163
  {-# INLINE genWord8 #-}
164

165
  -- | Returns a 'Word16' that is uniformly distributed over the entire 'Word16'
166
  -- range.
167
  --
168
  -- @since 1.2.0
169
  genWord16 :: g -> (Word16, g)
170
  genWord16 = first fromIntegral . genWord32
2✔
171
  {-# INLINE genWord16 #-}
172

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

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

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

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

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

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

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

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

275
{-# DEPRECATED genShortByteString "In favor of `System.Random.uniformShortByteString`" #-}
276
{-# DEPRECATED split "In favor of `splitGen`" #-}
277

278
-- | Pseudo-random generators that can be split into two separate and independent
279
-- psuedo-random generators should provide an instance for this type class.
280
--
281
-- Historically this functionality was included in the `RandomGen` type class in the
282
-- `split` function, however, few pseudo-random generators possess this property of
283
-- splittability. This lead the old `split` function being usually implemented in terms of
284
-- `error`.
285
--
286
-- @since 1.3.0
287
class RandomGen g => SplitGen g where
288

289
  -- | Returns two distinct pseudo-random number generators.
290
  --
291
  -- Implementations should take care to ensure that the resulting generators
292
  -- are not correlated.
293
  --
294
  -- @since 1.3.0
295
  splitGen :: g -> (g, g)
296

297
-- | 'StatefulGen' is an interface to monadic pseudo-random number generators.
298
--
299
-- @since 1.2.0
300
class Monad m => StatefulGen g m where
301
  {-# MINIMAL uniformWord32|uniformWord64 #-}
302
  -- | @uniformWord32R upperBound g@ generates a 'Word32' that is uniformly
303
  -- distributed over the range @[0, upperBound]@.
304
  --
305
  -- @since 1.2.0
306
  uniformWord32R :: Word32 -> g -> m Word32
307
  uniformWord32R = unsignedBitmaskWithRejectionM uniformWord32
×
308
  {-# INLINE uniformWord32R #-}
309

310
  -- | @uniformWord64R upperBound g@ generates a 'Word64' that is uniformly
311
  -- distributed over the range @[0, upperBound]@.
312
  --
313
  -- @since 1.2.0
314
  uniformWord64R :: Word64 -> g -> m Word64
315
  uniformWord64R = unsignedBitmaskWithRejectionM uniformWord64
×
316
  {-# INLINE uniformWord64R #-}
317

318
  -- | Generates a 'Word8' that is uniformly distributed over the entire 'Word8'
319
  -- range.
320
  --
321
  -- The default implementation extracts a 'Word8' from 'uniformWord32'.
322
  --
323
  -- @since 1.2.0
324
  uniformWord8 :: g -> m Word8
325
  uniformWord8 = fmap fromIntegral . uniformWord32
×
326
  {-# INLINE uniformWord8 #-}
327

328
  -- | Generates a 'Word16' that is uniformly distributed over the entire
329
  -- 'Word16' range.
330
  --
331
  -- The default implementation extracts a 'Word16' from 'uniformWord32'.
332
  --
333
  -- @since 1.2.0
334
  uniformWord16 :: g -> m Word16
335
  uniformWord16 = fmap fromIntegral . uniformWord32
×
336
  {-# INLINE uniformWord16 #-}
337

338
  -- | Generates a 'Word32' that is uniformly distributed over the entire
339
  -- 'Word32' range.
340
  --
341
  -- The default implementation extracts a 'Word32' from 'uniformWord64'.
342
  --
343
  -- @since 1.2.0
344
  uniformWord32 :: g -> m Word32
345
  uniformWord32 = fmap fromIntegral . uniformWord64
×
346
  {-# INLINE uniformWord32 #-}
347

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

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

376
  -- | @uniformShortByteString n g@ generates a 'ShortByteString' of length @n@
377
  -- filled with pseudo-random bytes.
378
  --
379
  -- @since 1.2.0
380
  uniformShortByteString :: Int -> g -> m ShortByteString
381
  uniformShortByteString = uniformShortByteStringM
×
382
  {-# INLINE uniformShortByteString #-}
383
{-# DEPRECATED uniformShortByteString "In favor of `uniformShortByteStringM`" #-}
384

385

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

421
  -- | Saves the state of the pseudo-random number generator as a frozen seed.
422
  --
423
  -- @since 1.2.0
424
  freezeGen :: MutableGen f m -> m f
425
  freezeGen mg = modifyGen mg (\fg -> (fg, fg))
×
426
  {-# INLINE freezeGen #-}
427

428
  -- | Apply a pure function to the frozen pseudo-random number generator.
429
  --
430
  -- @since 1.3.0
431
  modifyGen :: MutableGen f m -> (f -> (a, f)) -> m a
432
  modifyGen mg f = do
×
433
    fg <- freezeGen mg
×
434
    case f fg of
×
435
      (a, !fg') -> a <$ overwriteGen mg fg'
×
436
  {-# INLINE modifyGen #-}
437

438
  -- | Overwrite contents of the mutable pseudo-random number generator with the
439
  -- supplied frozen one
440
  --
441
  -- @since 1.3.0
442
  overwriteGen :: MutableGen f m -> f -> m ()
443
  overwriteGen mg fg = modifyGen mg (const ((), fg))
1✔
444
  {-# INLINE overwriteGen #-}
445

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

466
-- | Splits a pseudo-random number generator into two. Overwrites the mutable
467
-- pseudo-random number generator with one of the immutable pseudo-random number
468
-- generators produced by a `split` function and returns the other.
469
--
470
-- @since 1.3.0
471
splitGenM :: (SplitGen f, FrozenGen f m) => MutableGen f m -> m f
472
splitGenM = flip modifyGen splitGen
2✔
473

474
-- | Splits a pseudo-random number generator into two. Overwrites the mutable wrapper with
475
-- one of the resulting generators and returns the other as a new mutable generator.
476
--
477
-- @since 1.3.0
478
splitMutableGenM :: (SplitGen f, ThawedGen f m) => MutableGen f m -> m (MutableGen f m)
479
splitMutableGenM = splitGenM >=> thawGen
2✔
480

481
-- | Efficiently generates a sequence of pseudo-random bytes in a platform
482
-- independent manner.
483
--
484
-- @since 1.3.0
485
uniformByteArray ::
486
     RandomGen g
487
  => Bool -- ^ Should byte array be allocted in pinned or unpinned memory.
488
  -> Int -- ^ Number of bytes to generate
489
  -> g -- ^ Pure pseudo-random numer generator
490
  -> (ByteArray, g)
491
uniformByteArray isPinned n0 g =
2✔
492
  runST $ do
2✔
493
    let !n = max 0 n0
2✔
494
    mba <-
495
      if isPinned
2✔
496
        then newPinnedMutableByteArray n
2✔
497
        else newMutableByteArray n
2✔
498
    g' <- unsafeUniformFillMutableByteArray mba 0 n g
2✔
499
    ba <- freezeMutableByteArray mba
2✔
500
    pure (ba, g')
2✔
501
{-# INLINE uniformByteArray #-}
502

503
-- | Using an `ST` action that generates 8 bytes at a time fill in a new `ByteArray` in
504
-- architecture agnostic manner.
505
--
506
-- @since 1.3.0
507
fillByteArrayST :: Bool -> Int -> ST s Word64 -> ST s ByteArray
508
fillByteArrayST isPinned n0 action = do
×
509
  let !n = max 0 n0
×
510
  mba <- if isPinned
×
511
    then newPinnedMutableByteArray n
×
512
    else newMutableByteArray n
×
513
  runIdentityT $ defaultUnsafeFillMutableByteArrayT mba 0 n (lift action)
×
514
  freezeMutableByteArray mba
×
515
{-# INLINE fillByteArrayST #-}
516

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

558
-- | Efficiently generates a sequence of pseudo-random bytes in a platform
559
-- independent manner.
560
--
561
-- @since 1.2.0
562
defaultUnsafeUniformFillMutableByteArray ::
563
     RandomGen g
564
  => MutableByteArray s
565
  -> Int -- ^ Starting offset
566
  -> Int -- ^ Number of random bytes to write into the array
567
  -> g -- ^ ST action that can generate 8 random bytes at a time
568
  -> ST s g
569
defaultUnsafeUniformFillMutableByteArray mba i0 n g =
2✔
570
  flip execStateT g
2✔
571
    $ defaultUnsafeFillMutableByteArrayT mba i0 n (state genWord64)
2✔
572
{-# INLINE defaultUnsafeUniformFillMutableByteArray #-}
573

574

575
-- | Same as 'genShortByteStringIO', but runs in 'ST'.
576
--
577
-- @since 1.2.0
578
genShortByteStringST :: Int -> ST s Word64 -> ST s ShortByteString
579
genShortByteStringST n0 action = byteArrayToShortByteString <$> fillByteArrayST False n0 action
×
580
{-# INLINE genShortByteStringST #-}
581
{-# DEPRECATED genShortByteStringST "In favor of `fillByteArrayST`, since `uniformShortByteString`, which it was used for, was also deprecated" #-}
582

583
-- | Efficiently fills in a new `ShortByteString` in a platform independent manner.
584
--
585
-- @since 1.2.0
586
genShortByteStringIO ::
587
     Int -- ^ Number of bytes to generate
588
  -> IO Word64 -- ^ IO action that can generate 8 random bytes at a time
589
  -> IO ShortByteString
590
genShortByteStringIO n ioAction = stToIO $ genShortByteStringST n (ioToST ioAction)
×
591
{-# INLINE genShortByteStringIO #-}
592
{-# DEPRECATED genShortByteStringIO "In favor of `fillByteArrayST`" #-}
593

594
-- | @uniformShortByteString n g@ generates a 'ShortByteString' of length @n@
595
-- filled with pseudo-random bytes.
596
--
597
-- @since 1.3.0
598
uniformShortByteStringM :: StatefulGen g m => Int -> g -> m ShortByteString
599
uniformShortByteStringM n g = byteArrayToShortByteString <$> uniformByteArrayM False n g
2✔
600
{-# INLINE uniformShortByteStringM #-}
601

602
-- | Opaque data type that carries the type of a pure pseudo-random number
603
-- generator.
604
--
605
-- @since 1.2.0
606
data StateGenM g = StateGenM
607

608
-- | Wrapper for pure state gen, which acts as an immutable seed for the corresponding
609
-- stateful generator `StateGenM`
610
--
611
-- @since 1.2.0
612
newtype StateGen g = StateGen { unStateGen :: g }
2✔
613
  deriving (Eq, Ord, Show, RandomGen, Storable, NFData)
×
614

615
instance (RandomGen g, MonadState g m) => StatefulGen (StateGenM g) m where
616
  uniformWord32R r _ = state (genWord32R r)
2✔
617
  {-# INLINE uniformWord32R #-}
618
  uniformWord64R r _ = state (genWord64R r)
2✔
619
  {-# INLINE uniformWord64R #-}
620
  uniformWord8 _ = state genWord8
2✔
621
  {-# INLINE uniformWord8 #-}
622
  uniformWord16 _ = state genWord16
2✔
623
  {-# INLINE uniformWord16 #-}
624
  uniformWord32 _ = state genWord32
2✔
625
  {-# INLINE uniformWord32 #-}
626
  uniformWord64 _ = state genWord64
2✔
627
  {-# INLINE uniformWord64 #-}
628

629
instance (RandomGen g, MonadState g m) => FrozenGen (StateGen g) m where
630
  type MutableGen (StateGen g) m = StateGenM g
631
  freezeGen _ = fmap StateGen get
×
632
  modifyGen _ f = state (coerce f)
2✔
633
  {-# INLINE modifyGen #-}
634
  overwriteGen _ f = put (coerce f)
×
635
  {-# INLINE overwriteGen #-}
636

637
-- | Runs a monadic generating action in the `State` monad using a pure
638
-- pseudo-random number generator.
639
--
640
-- ====__Examples__
641
--
642
-- >>> import System.Random.Stateful
643
-- >>> let pureGen = mkStdGen 137
644
-- >>> runStateGen pureGen randomM :: (Int, StdGen)
645
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
646
--
647
-- @since 1.2.0
648
runStateGen :: RandomGen g => g -> (StateGenM g -> State g a) -> (a, g)
649
runStateGen g f = runState (f StateGenM) g
1✔
650
{-# INLINE runStateGen #-}
651

652
-- | Runs a monadic generating action in the `State` monad using a pure
653
-- pseudo-random number generator. Returns only the resulting pseudo-random
654
-- value.
655
--
656
-- ====__Examples__
657
--
658
-- >>> import System.Random.Stateful
659
-- >>> let pureGen = mkStdGen 137
660
-- >>> runStateGen_ pureGen randomM :: Int
661
-- 7879794327570578227
662
--
663
-- @since 1.2.0
664
runStateGen_ :: RandomGen g => g -> (StateGenM g -> State g a) -> a
665
runStateGen_ g = fst . runStateGen g
2✔
666
{-# INLINE runStateGen_ #-}
667

668
-- | Runs a monadic generating action in the `StateT` monad using a pure
669
-- pseudo-random number generator.
670
--
671
-- ====__Examples__
672
--
673
-- >>> import System.Random.Stateful
674
-- >>> let pureGen = mkStdGen 137
675
-- >>> runStateGenT pureGen randomM :: IO (Int, StdGen)
676
-- (7879794327570578227,StdGen {unStdGen = SMGen 11285859549637045894 7641485672361121627})
677
--
678
-- @since 1.2.0
679
runStateGenT :: RandomGen g => g -> (StateGenM g -> StateT g m a) -> m (a, g)
680
runStateGenT g f = runStateT (f StateGenM) g
1✔
681
{-# INLINE runStateGenT #-}
682

683
-- | Runs a monadic generating action in the `StateT` monad using a pure
684
-- pseudo-random number generator. Returns only the resulting pseudo-random
685
-- value.
686
--
687
-- ====__Examples__
688
--
689
-- >>> import System.Random.Stateful
690
-- >>> let pureGen = mkStdGen 137
691
-- >>> runStateGenT_ pureGen randomM :: IO Int
692
-- 7879794327570578227
693
--
694
-- @since 1.2.1
695
runStateGenT_ :: (RandomGen g, Functor f) => g -> (StateGenM g -> StateT g f a) -> f a
696
runStateGenT_ g = fmap fst . runStateGenT g
2✔
697
{-# INLINE runStateGenT_ #-}
698

699
-- | Runs a monadic generating action in the `ST` monad using a pure
700
-- pseudo-random number generator.
701
--
702
-- @since 1.2.0
703
runStateGenST :: RandomGen g => g -> (forall s . StateGenM g -> StateT g (ST s) a) -> (a, g)
704
runStateGenST g action = runST $ runStateGenT g action
2✔
705
{-# INLINE runStateGenST #-}
706

707
-- | Runs a monadic generating action in the `ST` monad using a pure
708
-- pseudo-random number generator. Same as `runStateGenST`, but discards the
709
-- resulting generator.
710
--
711
-- @since 1.2.1
712
runStateGenST_ :: RandomGen g => g -> (forall s . StateGenM g -> StateT g (ST s) a) -> a
713
runStateGenST_ g action = runST $ runStateGenT_ g action
×
714
{-# INLINE runStateGenST_ #-}
715

716

717
-- | Generates a list of pseudo-random values.
718
--
719
-- ====__Examples__
720
--
721
-- >>> import System.Random.Stateful
722
-- >>> let pureGen = mkStdGen 137
723
-- >>> g <- newIOGenM pureGen
724
-- >>> uniformListM 10 g :: IO [Bool]
725
-- [True,True,True,True,False,True,True,False,False,False]
726
--
727
-- @since 1.2.0
728
uniformListM :: (StatefulGen g m, Uniform a) => Int -> g -> m [a]
729
uniformListM n gen = replicateM n (uniformM gen)
2✔
730
{-# INLINE uniformListM #-}
731

732

733
-- | Generates a list of pseudo-random values in a specified range.
734
--
735
-- ====__Examples__
736
--
737
-- >>> import System.Random.Stateful
738
-- >>> let pureGen = mkStdGen 137
739
-- >>> g <- newIOGenM pureGen
740
-- >>> uniformListRM 10 (20, 30) g :: IO [Int]
741
-- [23,21,28,25,28,28,26,25,29,27]
742
--
743
-- @since 1.3.0
744
uniformListRM :: (StatefulGen g m, UniformRange a) => Int -> (a, a) -> g -> m [a]
745
uniformListRM n range gen = replicateM n (uniformRM range gen)
1✔
746
{-# INLINE uniformListRM #-}
747

748
-- | The standard pseudo-random number generator.
749
newtype StdGen = StdGen { unStdGen :: SM.SMGen }
×
750
  deriving (Show, RandomGen, SplitGen, NFData)
1✔
751

752
instance Eq StdGen where
753
  StdGen x1 == StdGen x2 = SM.unseedSMGen x1 == SM.unseedSMGen x2
2✔
754

755
instance RandomGen SM.SMGen where
756
  next = SM.nextInt
×
757
  {-# INLINE next #-}
758
  genWord32 = SM.nextWord32
2✔
759
  {-# INLINE genWord32 #-}
760
  genWord64 = SM.nextWord64
2✔
761
  {-# INLINE genWord64 #-}
762
  -- Despite that this is the same default implementation as in the type class definition,
763
  -- for some mysterious reason without this overwrite, performance of ByteArray generation
764
  -- slows down by a factor of x4:
765
  unsafeUniformFillMutableByteArray = defaultUnsafeUniformFillMutableByteArray
2✔
766
  {-# INLINE unsafeUniformFillMutableByteArray #-}
767

768
instance SplitGen SM.SMGen where
769
  splitGen = SM.splitSMGen
2✔
770
  {-# INLINE splitGen #-}
771

772
instance RandomGen SM32.SMGen where
773
  next = SM32.nextInt
×
774
  {-# INLINE next #-}
775
  genWord32 = SM32.nextWord32
×
776
  {-# INLINE genWord32 #-}
777
  genWord64 = SM32.nextWord64
×
778
  {-# INLINE genWord64 #-}
779

780
instance SplitGen SM32.SMGen where
781
  splitGen = SM32.splitSMGen
×
782
  {-# INLINE splitGen #-}
783

784
-- | Constructs a 'StdGen' deterministically from an `Int` seed. See `mkStdGen64` for a `Word64`
785
-- variant that is architecture agnostic.
786
mkStdGen :: Int -> StdGen
787
mkStdGen = mkStdGen64 . fromIntegral
2✔
788

789
-- | Constructs a 'StdGen' deterministically from a `Word64` seed.
790
--
791
-- The difference between `mkStdGen` is that `mkStdGen64` will work the same on 64-bit and
792
-- 32-bit architectures, while the former can only use 32-bit of information for
793
-- initializing the psuedo-random number generator on 32-bit operating systems
794
--
795
-- @since 1.3.0
796
mkStdGen64 :: Word64 -> StdGen
797
mkStdGen64 = StdGen . SM.mkSMGen
2✔
798

799
-- | Global mutable veriable with `StdGen`
800
theStdGen :: IORef StdGen
801
theStdGen = unsafePerformIO $ SM.initSMGen >>= newIORef . StdGen
2✔
802
{-# NOINLINE theStdGen #-}
803

804

805
-- | The class of types for which a uniformly distributed value can be drawn
806
-- from all possible values of the type.
807
--
808
-- @since 1.2.0
809
class Uniform a where
810
  -- | Generates a value uniformly distributed over all possible values of that
811
  -- type.
812
  --
813
  -- There is a default implementation via 'Generic':
814
  --
815
  -- >>> :seti -XDeriveGeneric -XDeriveAnyClass
816
  -- >>> import GHC.Generics (Generic)
817
  -- >>> import System.Random.Stateful
818
  -- >>> data MyBool = MyTrue | MyFalse deriving (Show, Generic, Finite, Uniform)
819
  -- >>> data Action = Code MyBool | Eat (Maybe Bool) | Sleep deriving (Show, Generic, Finite, Uniform)
820
  -- >>> gen <- newIOGenM (mkStdGen 42)
821
  -- >>> uniformListM 10 gen :: IO [Action]
822
  -- [Code MyTrue,Code MyTrue,Eat Nothing,Code MyFalse,Eat (Just False),Eat (Just True),Eat Nothing,Eat (Just False),Sleep,Code MyFalse]
823
  --
824
  -- @since 1.2.0
825
  uniformM :: StatefulGen g m => g -> m a
826

827
  default uniformM :: (StatefulGen g m, Generic a, GUniform (Rep a)) => g -> m a
828
  uniformM = fmap to . (`runContT` pure) . guniformM
×
829
  {-# INLINE uniformM #-}
830

831
-- | Default implementation of 'Uniform' type class for 'Generic' data.
832
-- It's important to use 'ContT', because without it 'fmap' and '>>=' remain
833
-- polymorphic too long and GHC fails to inline or specialize it, ending up
834
-- building full 'Rep' a structure in memory. 'ContT'
835
-- makes 'fmap' and '>>=' used in 'guniformM' monomorphic, so GHC is able to
836
-- specialize 'Generic' instance reasonably close to a handwritten one.
837
class GUniform f where
838
  guniformM :: StatefulGen g m => g -> ContT r m (f a)
839

840
instance GUniform f => GUniform (M1 i c f) where
841
  guniformM = fmap M1 . guniformM
×
842
  {-# INLINE guniformM #-}
843

844
instance Uniform a => GUniform (K1 i a) where
845
  guniformM = fmap K1 . lift . uniformM
×
846
  {-# INLINE guniformM #-}
847

848
instance GUniform U1 where
849
  guniformM = const $ return U1
×
850
  {-# INLINE guniformM #-}
851

852
instance (GUniform f, GUniform g) => GUniform (f :*: g) where
853
  guniformM g = (:*:) <$> guniformM g <*> guniformM g
×
854
  {-# INLINE guniformM #-}
855

856
instance (GFinite f, GFinite g) => GUniform (f :+: g) where
857
  guniformM = lift . finiteUniformM
×
858
  {-# INLINE guniformM #-}
859

860
finiteUniformM :: forall g m f a. (StatefulGen g m, GFinite f) => g -> m (f a)
861
finiteUniformM = fmap toGFinite . case gcardinality (proxy# :: Proxy# f) of
×
862
  Shift n
863
    | n <= 64 -> fmap toInteger . unsignedBitmaskWithRejectionM uniformWord64 (bit n - 1)
×
864
    | otherwise -> boundedByPowerOf2ExclusiveIntegralM n
×
865
  Card n
866
    | n <= bit 64 -> fmap toInteger . unsignedBitmaskWithRejectionM uniformWord64 (fromInteger n - 1)
×
867
    | otherwise -> boundedExclusiveIntegralM n
×
868
{-# INLINE finiteUniformM #-}
869

870
-- | A definition of 'Uniform' for 'System.Random.Finite' types.
871
-- If your data has several fields of sub-'Word' cardinality,
872
-- this instance may be more efficient than one, derived via 'Generic' and 'GUniform'.
873
--
874
-- >>> :seti -XDeriveGeneric -XDeriveAnyClass
875
-- >>> import GHC.Generics (Generic)
876
-- >>> import System.Random.Stateful
877
-- >>> data Triple = Triple Word8 Word8 Word8 deriving (Show, Generic, Finite)
878
-- >>> instance Uniform Triple where uniformM = uniformViaFiniteM
879
-- >>> gen <- newIOGenM (mkStdGen 42)
880
-- >>> uniformListM 5 gen :: IO [Triple]
881
-- [Triple 60 226 48,Triple 234 194 151,Triple 112 96 95,Triple 51 251 15,Triple 6 0 208]
882
--
883
uniformViaFiniteM :: (StatefulGen g m, Generic a, GFinite (Rep a)) => g -> m a
884
uniformViaFiniteM = fmap to . finiteUniformM
×
885
{-# INLINE uniformViaFiniteM #-}
886

887
-- | The class of types for which a uniformly distributed value can be drawn
888
-- from a range.
889
--
890
-- @since 1.2.0
891
class UniformRange a where
892
  -- | Generates a value uniformly distributed over the provided range, which
893
  -- is interpreted as inclusive in the lower and upper bound.
894
  --
895
  -- *   @uniformRM (1 :: Int, 4 :: Int)@ generates values uniformly from the
896
  --     set \(\{1,2,3,4\}\)
897
  --
898
  -- *   @uniformRM (1 :: Float, 4 :: Float)@ generates values uniformly from
899
  --     the set \(\{x\;|\;1 \le x \le 4\}\)
900
  --
901
  -- The following law should hold to make the function always defined:
902
  --
903
  -- > uniformRM (a, b) = uniformRM (b, a)
904
  --
905
  -- The range is understood as defined by means of 'isInRange', so
906
  --
907
  -- > isInRange (a, b) <$> uniformRM (a, b) gen == pure True
908
  --
909
  -- but beware of
910
  -- [floating point number caveats](System-Random-Stateful.html#fpcaveats).
911
  --
912
  -- There is a default implementation via 'Generic':
913
  --
914
  -- >>> :seti -XDeriveGeneric -XDeriveAnyClass
915
  -- >>> import GHC.Generics (Generic)
916
  -- >>> import Data.Word (Word8)
917
  -- >>> import Control.Monad (replicateM)
918
  -- >>> import System.Random.Stateful
919
  -- >>> gen <- newIOGenM (mkStdGen 42)
920
  -- >>> data Tuple = Tuple Bool Word8 deriving (Show, Generic, UniformRange)
921
  -- >>> replicateM 10 (uniformRM (Tuple False 100, Tuple True 150) gen)
922
  -- [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]
923
  --
924
  -- @since 1.2.0
925
  uniformRM :: StatefulGen g m => (a, a) -> g -> m a
926

927
  -- | A notion of (inclusive) ranges prescribed to @a@.
928
  --
929
  -- Ranges are symmetric:
930
  --
931
  -- > isInRange (lo, hi) x == isInRange (hi, lo) x
932
  --
933
  -- Ranges include their endpoints:
934
  --
935
  -- > isInRange (lo, hi) lo == True
936
  --
937
  -- When endpoints coincide, there is nothing else:
938
  --
939
  -- > isInRange (x, x) y == x == y
940
  --
941
  -- Endpoints are endpoints:
942
  --
943
  -- > isInRange (lo, hi) x ==>
944
  -- > isInRange (lo, x) hi == x == hi
945
  --
946
  -- Ranges are transitive relations:
947
  --
948
  -- > isInRange (lo, hi) lo' && isInRange (lo, hi) hi' && isInRange (lo', hi') x
949
  -- > ==> isInRange (lo, hi) x
950
  --
951
  -- There is a default implementation of 'isInRange' via 'Generic'. Other helper function
952
  -- that can be used for implementing this function are `isInRangeOrd` and
953
  -- `isInRangeEnum`
954
  --
955
  -- @since 1.3.0
956
  isInRange :: (a, a) -> a -> Bool
957

958
  default uniformRM :: (StatefulGen g m, Generic a, GUniformRange (Rep a)) => (a, a) -> g -> m a
959
  uniformRM (a, b) = fmap to . (`runContT` pure) . guniformRM (from a, from b)
2✔
960
  {-# INLINE uniformRM #-}
961

962
  default isInRange :: (Generic a, GUniformRange (Rep a)) => (a, a) -> a -> Bool
963
  isInRange (a, b) x = gisInRange (from a, from b) (from x)
2✔
964
  {-# INLINE isInRange #-}
965

966
class GUniformRange f where
967
  guniformRM :: StatefulGen g m => (f a, f a) -> g -> ContT r m (f a)
968
  gisInRange :: (f a, f a) -> f a -> Bool
969

970
instance GUniformRange f => GUniformRange (M1 i c f) where
971
  guniformRM (M1 a, M1 b) = fmap M1 . guniformRM (a, b)
2✔
972
  {-# INLINE guniformRM #-}
973
  gisInRange (M1 a, M1 b) (M1 x) = gisInRange (a, b) x
2✔
974

975
instance UniformRange a => GUniformRange (K1 i a) where
976
  guniformRM (K1 a, K1 b) = fmap K1 . lift . uniformRM (a, b)
2✔
977
  {-# INLINE guniformRM #-}
978
  gisInRange (K1 a, K1 b) (K1 x) = isInRange (a, b) x
2✔
979

980
instance GUniformRange U1 where
981
  guniformRM = const $ const $ return U1
×
982
  {-# INLINE guniformRM #-}
983
  gisInRange = const $ const True
2✔
984

985
instance (GUniformRange f, GUniformRange g) => GUniformRange (f :*: g) where
986
  guniformRM (x1 :*: y1, x2 :*: y2) g =
2✔
987
    (:*:) <$> guniformRM (x1, x2) g <*> guniformRM (y1, y2) g
1✔
988
  {-# INLINE guniformRM #-}
989
  gisInRange (x1 :*: y1, x2 :*: y2) (x3 :*: y3) =
2✔
990
    gisInRange (x1, x2) x3 && gisInRange (y1, y2) y3
2✔
991

992
-- | Utilize `Ord` instance to decide if a value is within the range. Designed to be used
993
-- for implementing `isInRange`
994
--
995
-- @since 1.3.0
996
isInRangeOrd :: Ord a => (a, a) -> a -> Bool
997
isInRangeOrd (a, b) x = min a b <= x && x <= max a b
2✔
998

999
-- | Utilize `Enum` instance to decide if a value is within the range. Designed to be used
1000
-- for implementing `isInRange`
1001
--
1002
-- @since 1.3.0
1003
isInRangeEnum :: Enum a => (a, a) -> a -> Bool
1004
isInRangeEnum (a, b) x = isInRangeOrd (fromEnum a, fromEnum b) (fromEnum x)
×
1005

1006
instance UniformRange Integer where
1007
  uniformRM = uniformIntegralM
2✔
1008
  {-# INLINE uniformRM #-}
1009
  isInRange = isInRangeOrd
2✔
1010

1011
instance UniformRange Natural where
1012
  uniformRM = uniformIntegralM
2✔
1013
  {-# INLINE uniformRM #-}
1014
  isInRange = isInRangeOrd
2✔
1015

1016
instance Uniform Int8 where
1017
  uniformM = fmap (fromIntegral :: Word8 -> Int8) . uniformWord8
2✔
1018
  {-# INLINE uniformM #-}
1019
instance UniformRange Int8 where
1020
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int8 -> Word8) fromIntegral
2✔
1021
  {-# INLINE uniformRM #-}
1022
  isInRange = isInRangeOrd
2✔
1023

1024
instance Uniform Int16 where
1025
  uniformM = fmap (fromIntegral :: Word16 -> Int16) . uniformWord16
2✔
1026
  {-# INLINE uniformM #-}
1027
instance UniformRange Int16 where
1028
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int16 -> Word16) fromIntegral
2✔
1029
  {-# INLINE uniformRM #-}
1030
  isInRange = isInRangeOrd
2✔
1031

1032
instance Uniform Int32 where
1033
  uniformM = fmap (fromIntegral :: Word32 -> Int32) . uniformWord32
2✔
1034
  {-# INLINE uniformM #-}
1035
instance UniformRange Int32 where
1036
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int32 -> Word32) fromIntegral
2✔
1037
  {-# INLINE uniformRM #-}
1038
  isInRange = isInRangeOrd
2✔
1039

1040
instance Uniform Int64 where
1041
  uniformM = fmap (fromIntegral :: Word64 -> Int64) . uniformWord64
2✔
1042
  {-# INLINE uniformM #-}
1043
instance UniformRange Int64 where
1044
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int64 -> Word64) fromIntegral
2✔
1045
  {-# INLINE uniformRM #-}
1046
  isInRange = isInRangeOrd
2✔
1047

1048
instance Uniform Int where
1049
  uniformM
2✔
1050
    | wordSizeInBits == 64 =
1✔
1051
      fmap (fromIntegral :: Word64 -> Int) . uniformWord64
2✔
1052
    | otherwise =
×
1053
      fmap (fromIntegral :: Word32 -> Int) . uniformWord32
×
1054
  {-# INLINE uniformM #-}
1055

1056
instance UniformRange Int where
1057
  uniformRM = signedBitmaskWithRejectionRM (fromIntegral :: Int -> Word) fromIntegral
2✔
1058
  {-# INLINE uniformRM #-}
1059
  isInRange = isInRangeOrd
2✔
1060

1061
instance Uniform Word where
1062
  uniformM
2✔
1063
    | wordSizeInBits == 64 =
1✔
1064
      fmap (fromIntegral :: Word64 -> Word) . uniformWord64
2✔
1065
    | otherwise =
×
1066
      fmap (fromIntegral :: Word32 -> Word) . uniformWord32
×
1067
  {-# INLINE uniformM #-}
1068

1069
instance UniformRange Word where
1070
  uniformRM = unsignedBitmaskWithRejectionRM
2✔
1071
  {-# INLINE uniformRM #-}
1072
  isInRange = isInRangeOrd
2✔
1073

1074
-- | Architecture specific `Word` generation in the specified lower range
1075
--
1076
-- @since 1.3.0
1077
uniformWordR ::
1078
    StatefulGen g m
1079
  => Word
1080
  -- ^ Maximum value to generate
1081
  -> g
1082
  -- ^ Stateful generator
1083
  -> m Word
1084
uniformWordR r
2✔
1085
  | wordSizeInBits == 64 =
1✔
1086
    fmap (fromIntegral :: Word64 -> Word) . uniformWord64R ((fromIntegral :: Word -> Word64) r)
2✔
1087
  | otherwise =
×
1088
    fmap (fromIntegral :: Word32 -> Word) . uniformWord32R ((fromIntegral :: Word -> Word32) r)
×
1089
{-# INLINE uniformWordR #-}
1090

1091
instance Uniform Word8 where
1092
  uniformM = uniformWord8
2✔
1093
  {-# INLINE uniformM #-}
1094
instance UniformRange Word8 where
1095
  uniformRM = unbiasedWordMult32RM
2✔
1096
  {-# INLINE uniformRM #-}
1097
  isInRange = isInRangeOrd
2✔
1098

1099
instance Uniform Word16 where
1100
  uniformM = uniformWord16
2✔
1101
  {-# INLINE uniformM #-}
1102
instance UniformRange Word16 where
1103
  uniformRM = unbiasedWordMult32RM
2✔
1104
  {-# INLINE uniformRM #-}
1105
  isInRange = isInRangeOrd
2✔
1106

1107
instance Uniform Word32 where
1108
  uniformM  = uniformWord32
2✔
1109
  {-# INLINE uniformM #-}
1110
instance UniformRange Word32 where
1111
  uniformRM = unbiasedWordMult32RM
2✔
1112
  {-# INLINE uniformRM #-}
1113
  isInRange = isInRangeOrd
2✔
1114

1115
instance Uniform Word64 where
1116
  uniformM  = uniformWord64
2✔
1117
  {-# INLINE uniformM #-}
1118
instance UniformRange Word64 where
1119
  uniformRM = unsignedBitmaskWithRejectionRM
2✔
1120
  {-# INLINE uniformRM #-}
1121
  isInRange = isInRangeOrd
2✔
1122

1123
#if __GLASGOW_HASKELL__ >= 802
1124
instance Uniform CBool where
1125
  uniformM = fmap CBool . uniformM
×
1126
  {-# INLINE uniformM #-}
1127
instance UniformRange CBool where
1128
  uniformRM (CBool b, CBool t) = fmap CBool . uniformRM (b, t)
2✔
1129
  {-# INLINE uniformRM #-}
1130
  isInRange = isInRangeOrd
2✔
1131
#endif
1132

1133
instance Uniform CChar where
1134
  uniformM = fmap CChar . uniformM
2✔
1135
  {-# INLINE uniformM #-}
1136
instance UniformRange CChar where
1137
  uniformRM (CChar b, CChar t) = fmap CChar . uniformRM (b, t)
2✔
1138
  {-# INLINE uniformRM #-}
1139
  isInRange = isInRangeOrd
2✔
1140

1141
instance Uniform CSChar where
1142
  uniformM = fmap CSChar . uniformM
2✔
1143
  {-# INLINE uniformM #-}
1144
instance UniformRange CSChar where
1145
  uniformRM (CSChar b, CSChar t) = fmap CSChar . uniformRM (b, t)
2✔
1146
  {-# INLINE uniformRM #-}
1147
  isInRange = isInRangeOrd
2✔
1148

1149
instance Uniform CUChar where
1150
  uniformM = fmap CUChar . uniformM
2✔
1151
  {-# INLINE uniformM #-}
1152
instance UniformRange CUChar where
1153
  uniformRM (CUChar b, CUChar t) = fmap CUChar . uniformRM (b, t)
2✔
1154
  {-# INLINE uniformRM #-}
1155
  isInRange = isInRangeOrd
2✔
1156

1157
instance Uniform CShort where
1158
  uniformM = fmap CShort . uniformM
2✔
1159
  {-# INLINE uniformM #-}
1160
instance UniformRange CShort where
1161
  uniformRM (CShort b, CShort t) = fmap CShort . uniformRM (b, t)
2✔
1162
  {-# INLINE uniformRM #-}
1163
  isInRange = isInRangeOrd
2✔
1164

1165
instance Uniform CUShort where
1166
  uniformM = fmap CUShort . uniformM
2✔
1167
  {-# INLINE uniformM #-}
1168
instance UniformRange CUShort where
1169
  uniformRM (CUShort b, CUShort t) = fmap CUShort . uniformRM (b, t)
2✔
1170
  {-# INLINE uniformRM #-}
1171
  isInRange = isInRangeOrd
2✔
1172

1173
instance Uniform CInt where
1174
  uniformM = fmap CInt . uniformM
2✔
1175
  {-# INLINE uniformM #-}
1176
instance UniformRange CInt where
1177
  uniformRM (CInt b, CInt t) = fmap CInt . uniformRM (b, t)
2✔
1178
  {-# INLINE uniformRM #-}
1179
  isInRange = isInRangeOrd
2✔
1180

1181
instance Uniform CUInt where
1182
  uniformM = fmap CUInt . uniformM
2✔
1183
  {-# INLINE uniformM #-}
1184
instance UniformRange CUInt where
1185
  uniformRM (CUInt b, CUInt t) = fmap CUInt . uniformRM (b, t)
2✔
1186
  {-# INLINE uniformRM #-}
1187
  isInRange = isInRangeOrd
2✔
1188

1189
instance Uniform CLong where
1190
  uniformM = fmap CLong . uniformM
2✔
1191
  {-# INLINE uniformM #-}
1192
instance UniformRange CLong where
1193
  uniformRM (CLong b, CLong t) = fmap CLong . uniformRM (b, t)
2✔
1194
  {-# INLINE uniformRM #-}
1195
  isInRange = isInRangeOrd
2✔
1196

1197
instance Uniform CULong where
1198
  uniformM = fmap CULong . uniformM
2✔
1199
  {-# INLINE uniformM #-}
1200
instance UniformRange CULong where
1201
  uniformRM (CULong b, CULong t) = fmap CULong . uniformRM (b, t)
2✔
1202
  {-# INLINE uniformRM #-}
1203
  isInRange = isInRangeOrd
2✔
1204

1205
instance Uniform CPtrdiff where
1206
  uniformM = fmap CPtrdiff . uniformM
2✔
1207
  {-# INLINE uniformM #-}
1208
instance UniformRange CPtrdiff where
1209
  uniformRM (CPtrdiff b, CPtrdiff t) = fmap CPtrdiff . uniformRM (b, t)
2✔
1210
  {-# INLINE uniformRM #-}
1211
  isInRange = isInRangeOrd
2✔
1212

1213
instance Uniform CSize where
1214
  uniformM = fmap CSize . uniformM
2✔
1215
  {-# INLINE uniformM #-}
1216
instance UniformRange CSize where
1217
  uniformRM (CSize b, CSize t) = fmap CSize . uniformRM (b, t)
2✔
1218
  {-# INLINE uniformRM #-}
1219
  isInRange = isInRangeOrd
2✔
1220

1221
instance Uniform CWchar where
1222
  uniformM = fmap CWchar . uniformM
2✔
1223
  {-# INLINE uniformM #-}
1224
instance UniformRange CWchar where
1225
  uniformRM (CWchar b, CWchar t) = fmap CWchar . uniformRM (b, t)
2✔
1226
  {-# INLINE uniformRM #-}
1227
  isInRange = isInRangeOrd
2✔
1228

1229
instance Uniform CSigAtomic where
1230
  uniformM = fmap CSigAtomic . uniformM
2✔
1231
  {-# INLINE uniformM #-}
1232
instance UniformRange CSigAtomic where
1233
  uniformRM (CSigAtomic b, CSigAtomic t) = fmap CSigAtomic . uniformRM (b, t)
2✔
1234
  {-# INLINE uniformRM #-}
1235
  isInRange = isInRangeOrd
2✔
1236

1237
instance Uniform CLLong where
1238
  uniformM = fmap CLLong . uniformM
2✔
1239
  {-# INLINE uniformM #-}
1240
instance UniformRange CLLong where
1241
  uniformRM (CLLong b, CLLong t) = fmap CLLong . uniformRM (b, t)
2✔
1242
  {-# INLINE uniformRM #-}
1243
  isInRange = isInRangeOrd
2✔
1244

1245
instance Uniform CULLong where
1246
  uniformM = fmap CULLong . uniformM
2✔
1247
  {-# INLINE uniformM #-}
1248
instance UniformRange CULLong where
1249
  uniformRM (CULLong b, CULLong t) = fmap CULLong . uniformRM (b, t)
2✔
1250
  {-# INLINE uniformRM #-}
1251
  isInRange = isInRangeOrd
2✔
1252

1253
instance Uniform CIntPtr where
1254
  uniformM = fmap CIntPtr . uniformM
2✔
1255
  {-# INLINE uniformM #-}
1256
instance UniformRange CIntPtr where
1257
  uniformRM (CIntPtr b, CIntPtr t) = fmap CIntPtr . uniformRM (b, t)
2✔
1258
  {-# INLINE uniformRM #-}
1259
  isInRange = isInRangeOrd
2✔
1260

1261
instance Uniform CUIntPtr where
1262
  uniformM = fmap CUIntPtr . uniformM
2✔
1263
  {-# INLINE uniformM #-}
1264
instance UniformRange CUIntPtr where
1265
  uniformRM (CUIntPtr b, CUIntPtr t) = fmap CUIntPtr . uniformRM (b, t)
2✔
1266
  {-# INLINE uniformRM #-}
1267
  isInRange = isInRangeOrd
2✔
1268

1269
instance Uniform CIntMax where
1270
  uniformM = fmap CIntMax . uniformM
2✔
1271
  {-# INLINE uniformM #-}
1272
instance UniformRange CIntMax where
1273
  uniformRM (CIntMax b, CIntMax t) = fmap CIntMax . uniformRM (b, t)
2✔
1274
  {-# INLINE uniformRM #-}
1275
  isInRange = isInRangeOrd
2✔
1276

1277
instance Uniform CUIntMax where
1278
  uniformM = fmap CUIntMax . uniformM
2✔
1279
  {-# INLINE uniformM #-}
1280
instance UniformRange CUIntMax where
1281
  uniformRM (CUIntMax b, CUIntMax t) = fmap CUIntMax . uniformRM (b, t)
2✔
1282
  {-# INLINE uniformRM #-}
1283
  isInRange = isInRangeOrd
2✔
1284

1285
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1286
instance UniformRange CFloat where
1287
  uniformRM (CFloat l, CFloat h) = fmap CFloat . uniformRM (l, h)
2✔
1288
  {-# INLINE uniformRM #-}
1289
  isInRange = isInRangeOrd
2✔
1290

1291
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1292
instance UniformRange CDouble where
1293
  uniformRM (CDouble l, CDouble h) = fmap CDouble . uniformRM (l, h)
2✔
1294
  {-# INLINE uniformRM #-}
1295
  isInRange = isInRangeOrd
2✔
1296

1297
-- The `chr#` and `ord#` are the prim functions that will be called, regardless of which
1298
-- way you gonna do the `Char` conversion, so it is better to call them directly and
1299
-- bypass all the hoops. Also because `intToChar` and `charToInt` are internal functions
1300
-- and are called on valid character ranges it is impossible to generate an invalid
1301
-- `Char`, therefore it is totally fine to omit all the unnecessary checks involved in
1302
-- other paths of conversion.
1303
word32ToChar :: Word32 -> Char
1304
#if __GLASGOW_HASKELL__ < 902
1305
word32ToChar (W32# w#) = C# (chr# (word2Int# w#))
2✔
1306
#else
1307
word32ToChar (W32# w#) = C# (chr# (word2Int# (word32ToWord# w#)))
1308
#endif
1309
{-# INLINE word32ToChar #-}
1310

1311
charToWord32 :: Char -> Word32
1312
#if __GLASGOW_HASKELL__ < 902
1313
charToWord32 (C# c#) = W32# (int2Word# (ord# c#))
2✔
1314
#else
1315
charToWord32 (C# c#) = W32# (wordToWord32# (int2Word# (ord# c#)))
1316
#endif
1317
{-# INLINE charToWord32 #-}
1318

1319
instance Uniform Char where
1320
  uniformM g = word32ToChar <$> unbiasedWordMult32 (charToWord32 maxBound) g
2✔
1321
  {-# INLINE uniformM #-}
1322
instance UniformRange Char where
1323
  uniformRM (l, h) g =
2✔
1324
    word32ToChar <$> unbiasedWordMult32RM (charToWord32 l, charToWord32 h) g
1✔
1325
  {-# INLINE uniformRM #-}
1326
  isInRange = isInRangeOrd
2✔
1327

1328
instance Uniform () where
1329
  uniformM = const $ pure ()
×
1330
  {-# INLINE uniformM #-}
1331
instance UniformRange () where
1332
  uniformRM = const $ const $ pure ()
2✔
1333
  {-# INLINE uniformRM #-}
1334

1335
instance Uniform Bool where
1336
  uniformM = fmap wordToBool . uniformWord8
2✔
1337
    where wordToBool w = (w .&. 1) /= 0
2✔
1338
          {-# INLINE wordToBool #-}
1339
  {-# INLINE uniformM #-}
1340
instance UniformRange Bool where
1341
  uniformRM (False, False) _g = return False
2✔
1342
  uniformRM (True, True)   _g = return True
2✔
1343
  uniformRM _               g = uniformM g
1✔
1344
  {-# INLINE uniformRM #-}
1345
  isInRange = isInRangeOrd
2✔
1346

1347
instance (Finite a, Uniform a) => Uniform (Maybe a)
1348

1349
instance (Finite a, Uniform a, Finite b, Uniform b) => Uniform (Either a b)
1350

1351
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1352
instance UniformRange Double where
1353
  uniformRM (l, h) g
2✔
1354
    | l == h = return l
2✔
1355
    | isInfinite l || isInfinite h =
2✔
1356
      -- Optimisation exploiting absorption:
1357
      --    (+Infinity) + (-Infinity) = NaN
1358
      --    (-Infinity) + (+Infinity) = NaN
1359
      --    (+Infinity) + _           = +Infinity
1360
      --    (-Infinity) + _           = -Infinity
1361
      --              _ + (+Infinity) = +Infinity
1362
      --              _ + (-Infinity) = -Infinity
1363
      return $! h + l
2✔
1364
    | otherwise = do
1✔
1365
      w64 <- uniformWord64 g
1✔
1366
      pure $! scaleFloating l h w64
2✔
1367
  {-# INLINE uniformRM #-}
1368
  isInRange = isInRangeOrd
2✔
1369

1370
-- | Generates uniformly distributed 'Double' in the range \([0, 1]\).
1371
--   Numbers are generated by generating uniform 'Word64' and dividing
1372
--   it by \(2^{64}\). It's used to implement 'UniformRange' instance for
1373
--   'Double'.
1374
--
1375
-- @since 1.2.0
1376
uniformDouble01M :: forall g m. StatefulGen g m => g -> m Double
1377
uniformDouble01M g = do
2✔
1378
  w64 <- uniformWord64 g
1✔
1379
  return $ fromIntegral w64 / m
2✔
1380
  where
1381
    m = fromIntegral (maxBound :: Word64) :: Double
2✔
1382
{-# INLINE uniformDouble01M #-}
1383

1384
-- | Generates uniformly distributed 'Double' in the range
1385
--   \((0, 1]\). Number is generated as \(2^{-64}/2+\operatorname{uniformDouble01M}\).
1386
--   Constant is 1\/2 of smallest nonzero value which could be generated
1387
--   by 'uniformDouble01M'.
1388
--
1389
-- @since 1.2.0
1390
uniformDoublePositive01M :: forall g m. StatefulGen g m => g -> m Double
1391
uniformDoublePositive01M g = (+ d) <$> uniformDouble01M g
1✔
1392
  where
1393
    -- We add small constant to shift generated value from zero. It's
1394
    -- selected as 1/2 of smallest possible nonzero value
1395
    d = 2.710505431213761e-20 -- 2**(-65)
2✔
1396
{-# INLINE uniformDoublePositive01M #-}
1397

1398
-- | See [Floating point number caveats](System-Random-Stateful.html#fpcaveats).
1399
instance UniformRange Float where
1400
  uniformRM (l, h) g
2✔
1401
    | l == h = return l
2✔
1402
    | isInfinite l || isInfinite h =
2✔
1403
      -- Optimisation exploiting absorption:
1404
      --    (+Infinity) + (-Infinity) = NaN
1405
      --    (-Infinity) + (+Infinity) = NaN
1406
      --    (+Infinity) + _           = +Infinity
1407
      --    (-Infinity) + _           = -Infinity
1408
      --              _ + (+Infinity) = +Infinity
1409
      --              _ + (-Infinity) = -Infinity
1410
      return $! h + l
2✔
1411
    | otherwise = do
1✔
1412
      w32 <- uniformWord32 g
1✔
1413
      pure $! scaleFloating l h w32
2✔
1414
  {-# INLINE uniformRM #-}
1415
  isInRange = isInRangeOrd
2✔
1416

1417
-- | This is the function that is used to scale a floating point value from random word range to
1418
-- the custom @[low, high]@ range.
1419
--
1420
-- @since 1.3.0
1421
scaleFloating ::
1422
     forall a w. (RealFloat a, Integral w, Bounded w, FiniteBits w)
1423
  => a
1424
  -- ^ Low
1425
  -> a
1426
  -- ^ High
1427
  -> w
1428
  -- ^ Uniformly distributed unsigned integral value that will be used for converting to a floating
1429
  -- point value and subsequent scaling to the specified range
1430
  -> a
1431
scaleFloating l h w =
2✔
1432
  if isInfinite diff
1✔
1433
    then let !x = fromIntegral w / m
×
1434
             !y = x * l + (1 - x) * h
×
1435
          in max (min y (max l h)) (min l h)
×
1436
    else let !topMostBit = finiteBitSize w - 1
1✔
1437
             !x = fromIntegral (clearBit w topMostBit) / m
2✔
1438
          in if testBit w topMostBit
2✔
1439
               then l + diff * x
2✔
1440
               else h + negate diff * x
2✔
1441
  where
1442
    !diff = h - l
2✔
1443
    !m = fromIntegral (maxBound :: w) :: a
2✔
1444
{-# INLINE scaleFloating #-}
1445

1446
-- | Generates uniformly distributed 'Float' in the range \([0, 1]\).
1447
--   Numbers are generated by generating uniform 'Word32' and dividing
1448
--   it by \(2^{32}\). It's used to implement 'UniformRange' instance for 'Float'.
1449
--
1450
-- @since 1.2.0
1451
uniformFloat01M :: forall g m. StatefulGen g m => g -> m Float
1452
uniformFloat01M g = do
2✔
1453
  w32 <- uniformWord32 g
1✔
1454
  return $ fromIntegral w32 / m
2✔
1455
  where
1456
    m = fromIntegral (maxBound :: Word32) :: Float
2✔
1457
{-# INLINE uniformFloat01M #-}
1458

1459
-- | Generates uniformly distributed 'Float' in the range
1460
--   \((0, 1]\). Number is generated as \(2^{-32}/2+\operatorname{uniformFloat01M}\).
1461
--   Constant is 1\/2 of smallest nonzero value which could be generated
1462
--   by 'uniformFloat01M'.
1463
--
1464
-- @since 1.2.0
1465
uniformFloatPositive01M :: forall g m. StatefulGen g m => g -> m Float
1466
uniformFloatPositive01M g = (+ d) <$> uniformFloat01M g
1✔
1467
  where
1468
    -- See uniformDoublePositive01M
1469
    d = 1.1641532182693481e-10 -- 2**(-33)
2✔
1470
{-# INLINE uniformFloatPositive01M #-}
1471

1472
-- | Generates uniformly distributed 'Enum'.
1473
-- One can use it to define a 'Uniform' instance:
1474
--
1475
-- > data Colors = Red | Green | Blue deriving (Enum, Bounded)
1476
-- > instance Uniform Colors where uniformM = uniformEnumM
1477
--
1478
-- @since 1.3.0
1479
uniformEnumM :: forall a g m. (Enum a, Bounded a, StatefulGen g m) => g -> m a
1480
uniformEnumM g = toEnum <$> uniformRM (fromEnum (minBound :: a), fromEnum (maxBound :: a)) g
×
1481
{-# INLINE uniformEnumM #-}
1482

1483
-- | Generates uniformly distributed 'Enum' in the given range.
1484
-- One can use it to define a 'UniformRange' instance:
1485
--
1486
-- > data Colors = Red | Green | Blue deriving (Enum)
1487
-- > instance UniformRange Colors where
1488
-- >   uniformRM = uniformEnumRM
1489
-- >   inInRange (lo, hi) x = isInRange (fromEnum lo, fromEnum hi) (fromEnum x)
1490
--
1491
-- @since 1.3.0
1492
uniformEnumRM :: forall a g m. (Enum a, StatefulGen g m) => (a, a) -> g -> m a
1493
uniformEnumRM (l, h) g = toEnum <$> uniformRM (fromEnum l, fromEnum h) g
1✔
1494
{-# INLINE uniformEnumRM #-}
1495

1496
-- The two integer functions below take an [inclusive,inclusive] range.
1497
randomIvalIntegral :: (RandomGen g, Integral a) => (a, a) -> g -> (a, g)
1498
randomIvalIntegral (l, h) = randomIvalInteger (toInteger l, toInteger h)
×
1499

1500
{-# SPECIALIZE randomIvalInteger :: (Num a) =>
1501
    (Integer, Integer) -> StdGen -> (a, StdGen) #-}
1502

1503
randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a, g)
1504
randomIvalInteger (l, h) rng
×
1505
 | l > h     = randomIvalInteger (h,l) rng
×
1506
 | otherwise = case f 1 0 rng of (v, rng') -> (fromInteger (l + v `mod` k), rng')
×
1507
     where
1508
       (genlo, genhi) = genRange rng
×
1509
       b = fromIntegral genhi - fromIntegral genlo + 1 :: Integer
×
1510

1511
       -- Probabilities of the most likely and least likely result
1512
       -- will differ at most by a factor of (1 +- 1/q). Assuming the RandomGen
1513
       -- is uniform, of course
1514

1515
       -- On average, log q / log b more pseudo-random values will be generated
1516
       -- than the minimum
1517
       q = 1000 :: Integer
×
1518
       k = h - l + 1
×
1519
       magtgt = k * q
×
1520

1521
       -- generate pseudo-random values until we exceed the target magnitude
1522
       f mag v g | mag >= magtgt = (v, g)
×
1523
                 | otherwise = v' `seq`f (mag*b) v' g' where
×
1524
                        (x,g') = next g
×
1525
                        v' = v * b + (fromIntegral x - fromIntegral genlo)
×
1526

1527
-- | Generate an integral in the range @[l, h]@ if @l <= h@ and @[h, l]@
1528
-- otherwise.
1529
uniformIntegralM :: forall a g m. (Bits a, Integral a, StatefulGen g m) => (a, a) -> g -> m a
1530
uniformIntegralM (l, h) gen = case l `compare` h of
2✔
1531
  LT -> do
2✔
1532
    let limit = h - l
2✔
1533
    bounded <- case toIntegralSized limit :: Maybe Word64 of
2✔
1534
      Just limitAsWord64 ->
1535
        -- Optimisation: if 'limit' fits into 'Word64', generate a bounded
1536
        -- 'Word64' and then convert to 'Integer'
1537
        fromIntegral <$> unsignedBitmaskWithRejectionM uniformWord64 limitAsWord64 gen
1✔
1538
      Nothing -> boundedExclusiveIntegralM (limit + 1) gen
1✔
1539
    return $ l + bounded
2✔
1540
  GT -> uniformIntegralM (h, l) gen
1✔
1541
  EQ -> pure l
2✔
1542
{-# INLINEABLE uniformIntegralM #-}
1543
{-# SPECIALIZE uniformIntegralM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer #-}
1544
{-# SPECIALIZE uniformIntegralM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural #-}
1545

1546
-- | Generate an integral in the range @[0, s)@ using a variant of Lemire's
1547
-- multiplication method.
1548
--
1549
-- Daniel Lemire. 2019. Fast Random Integer Generation in an Interval. In ACM
1550
-- Transactions on Modeling and Computer Simulation
1551
-- https://doi.org/10.1145/3230636
1552
--
1553
-- PRECONDITION (unchecked): s > 0
1554
boundedExclusiveIntegralM :: forall a g m . (Bits a, Integral a, StatefulGen g m) => a -> g -> m a
1555
boundedExclusiveIntegralM s gen = go
2✔
1556
  where
1557
    n = integralWordSize s
2✔
1558
    -- We renamed 'L' from the paper to 'k' here because 'L' is not a valid
1559
    -- variable name in Haskell and 'l' is already used in the algorithm.
1560
    k = wordSizeInBits * n
2✔
1561
    twoToK = (1 :: a) `shiftL` k
2✔
1562
    modTwoToKMask = twoToK - 1
2✔
1563

1564
    t = (twoToK - s) `rem` s -- `rem`, instead of `mod` because `twoToK >= s` is guaranteed
2✔
1565
    go :: (Bits a, Integral a, StatefulGen g m) => m a
1566
    go = do
2✔
1567
      x <- uniformIntegralWords n gen
1✔
1568
      let m = x * s
2✔
1569
      -- m .&. modTwoToKMask == m `mod` twoToK
1570
      let l = m .&. modTwoToKMask
2✔
1571
      if l < t
1✔
1572
        then go
×
1573
        -- m `shiftR` k == m `quot` twoToK
1574
        else return $ m `shiftR` k
2✔
1575
{-# INLINE boundedExclusiveIntegralM #-}
1576

1577
-- | boundedByPowerOf2ExclusiveIntegralM s ~ boundedExclusiveIntegralM (bit s)
1578
boundedByPowerOf2ExclusiveIntegralM ::
1579
  forall a g m. (Bits a, Integral a, StatefulGen g m) => Int -> g -> m a
1580
boundedByPowerOf2ExclusiveIntegralM s gen = do
×
1581
  let n = (s + wordSizeInBits - 1) `quot` wordSizeInBits
×
1582
  x <- uniformIntegralWords n gen
×
1583
  return $ x .&. (bit s - 1)
×
1584
{-# INLINE boundedByPowerOf2ExclusiveIntegralM #-}
1585

1586
-- | @integralWordSize i@ returns that least @w@ such that
1587
-- @i <= WORD_SIZE_IN_BITS^w@.
1588
integralWordSize :: (Bits a, Num a) => a -> Int
1589
integralWordSize = go 0
2✔
1590
  where
1591
    go !acc i
2✔
1592
      | i == 0 = acc
2✔
1593
      | otherwise = go (acc + 1) (i `shiftR` wordSizeInBits)
1✔
1594
{-# INLINE integralWordSize #-}
1595

1596
-- | @uniformIntegralWords n@ is a uniformly pseudo-random integral in the range
1597
-- @[0, WORD_SIZE_IN_BITS^n)@.
1598
uniformIntegralWords :: forall a g m. (Bits a, Integral a, StatefulGen g m) => Int -> g -> m a
1599
uniformIntegralWords n gen = go 0 n
2✔
1600
  where
1601
    go !acc i
2✔
1602
      | i == 0 = return acc
2✔
1603
      | otherwise = do
1✔
1604
        (w :: Word) <- uniformM gen
1✔
1605
        go ((acc `shiftL` wordSizeInBits) .|. fromIntegral w) (i - 1)
2✔
1606
{-# INLINE uniformIntegralWords #-}
1607

1608
-- | Uniformly generate an 'Integral' in an inclusive-inclusive range.
1609
--
1610
-- Only use for integrals size less than or equal to that of 'Word32'.
1611
unbiasedWordMult32RM :: forall a g m. (Integral a, StatefulGen g m) => (a, a) -> g -> m a
1612
unbiasedWordMult32RM (b, t) g
2✔
1613
  | b <= t    = (+b) . fromIntegral <$> unbiasedWordMult32 (fromIntegral (t - b)) g
1✔
1614
  | otherwise = (+t) . fromIntegral <$> unbiasedWordMult32 (fromIntegral (b - t)) g
1✔
1615
{-# INLINE unbiasedWordMult32RM #-}
1616

1617
-- | Uniformly generate Word32 in @[0, s]@.
1618
unbiasedWordMult32 :: forall g m. StatefulGen g m => Word32 -> g -> m Word32
1619
unbiasedWordMult32 s g
2✔
1620
  | s == maxBound = uniformWord32 g
1✔
1621
  | otherwise = unbiasedWordMult32Exclusive (s+1) g
1✔
1622
{-# INLINE unbiasedWordMult32 #-}
1623

1624
-- | See [Lemire's paper](https://arxiv.org/pdf/1805.10941.pdf),
1625
-- [O\'Neill's
1626
-- blogpost](https://www.pcg-random.org/posts/bounded-rands.html) and
1627
-- more directly [O\'Neill's github
1628
-- repo](https://github.com/imneme/bounded-rands/blob/3d71f53c975b1e5b29f2f3b05a74e26dab9c3d84/bounded32.cpp#L234).
1629
-- N.B. The range is [0,r) **not** [0,r].
1630
unbiasedWordMult32Exclusive :: forall g m . StatefulGen g m => Word32 -> g -> m Word32
1631
unbiasedWordMult32Exclusive r g = go
2✔
1632
  where
1633
    t :: Word32
1634
    t = (-r) `mod` r -- Calculates 2^32 `mod` r!!!
2✔
1635
    go :: StatefulGen g m => m Word32
1636
    go = do
2✔
1637
      x <- uniformWord32 g
2✔
1638
      let m :: Word64
1639
          m = fromIntegral x * fromIntegral r
2✔
1640
          l :: Word32
1641
          l = fromIntegral m
2✔
1642
      if l >= t then return (fromIntegral $ m `shiftR` 32) else go
2✔
1643
{-# INLINE unbiasedWordMult32Exclusive #-}
1644

1645
-- | This only works for unsigned integrals
1646
unsignedBitmaskWithRejectionRM ::
1647
     forall a g m . (FiniteBits a, Num a, Ord a, Uniform a, StatefulGen g m)
1648
  => (a, a)
1649
  -> g
1650
  -> m a
1651
unsignedBitmaskWithRejectionRM (bottom, top) gen
2✔
1652
  | bottom == top = pure top
2✔
1653
  | otherwise = (b +) <$> unsignedBitmaskWithRejectionM uniformM r gen
1✔
1654
  where
1655
    (b, r) = if bottom > top then (top, bottom - top) else (bottom, top - bottom)
2✔
1656
{-# INLINE unsignedBitmaskWithRejectionRM #-}
1657

1658
-- | This works for signed integrals by explicit conversion to unsigned and abusing
1659
-- overflow. It uses `unsignedBitmaskWithRejectionM`, therefore it requires functions that
1660
-- take the value to unsigned and back.
1661
signedBitmaskWithRejectionRM ::
1662
     forall a b g m. (Num a, Num b, Ord b, Ord a, FiniteBits a, StatefulGen g m, Uniform a)
1663
  => (b -> a) -- ^ Convert signed to unsigned. @a@ and @b@ must be of the same size.
1664
  -> (a -> b) -- ^ Convert unsigned to signed. @a@ and @b@ must be of the same size.
1665
  -> (b, b) -- ^ Range.
1666
  -> g -- ^ Generator.
1667
  -> m b
1668
signedBitmaskWithRejectionRM toUnsigned fromUnsigned (bottom, top) gen
2✔
1669
  | bottom == top = pure top
2✔
1670
  | otherwise =
×
1671
    (b +) . fromUnsigned <$> unsignedBitmaskWithRejectionM uniformM r gen
1✔
1672
    -- This works in all cases, see Appendix 1 at the end of the file.
1673
  where
1674
    (b, r) =
1675
      if bottom > top
2✔
1676
        then (top, toUnsigned bottom - toUnsigned top)
2✔
1677
        else (bottom, toUnsigned top - toUnsigned bottom)
2✔
1678
{-# INLINE signedBitmaskWithRejectionRM #-}
1679

1680

1681
-- | Detailed explanation about the algorithm employed here can be found in this post:
1682
-- http://web.archive.org/web/20200520071940/https://www.pcg-random.org/posts/bounded-rands.html
1683
unsignedBitmaskWithRejectionM ::
1684
  forall a g m. (Ord a, FiniteBits a, Num a, StatefulGen g m) => (g -> m a) -> a -> g -> m a
1685
unsignedBitmaskWithRejectionM genUniformM range gen = go
2✔
1686
  where
1687
    mask :: a
1688
    mask = complement zeroBits `shiftR` countLeadingZeros (range .|. 1)
2✔
1689
    go = do
2✔
1690
      x <- genUniformM gen
1✔
1691
      let x' = x .&. mask
2✔
1692
      if x' > range
2✔
1693
        then go
2✔
1694
        else pure x'
2✔
1695
{-# INLINE unsignedBitmaskWithRejectionM #-}
1696

1697
-------------------------------------------------------------------------------
1698
-- 'Uniform' instances for tuples
1699
-------------------------------------------------------------------------------
1700

1701
instance (Uniform a, Uniform b) => Uniform (a, b) where
1702
  uniformM g = (,) <$> uniformM g <*> uniformM g
1✔
1703
  {-# INLINE uniformM #-}
1704

1705
instance (Uniform a, Uniform b, Uniform c) => Uniform (a, b, c) where
1706
  uniformM g = (,,) <$> uniformM g <*> uniformM g <*> uniformM g
1✔
1707
  {-# INLINE uniformM #-}
1708

1709
instance (Uniform a, Uniform b, Uniform c, Uniform d) => Uniform (a, b, c, d) where
1710
  uniformM g = (,,,) <$> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g
1✔
1711
  {-# INLINE uniformM #-}
1712

1713
instance (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e) => Uniform (a, b, c, d, e) where
1714
  uniformM g = (,,,,) <$> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g <*> uniformM g
1✔
1715
  {-# INLINE uniformM #-}
1716

1717
instance (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f) =>
1718
  Uniform (a, b, c, d, e, f) where
1719
  uniformM g = (,,,,,)
2✔
1720
               <$> uniformM g
1✔
1721
               <*> uniformM g
1✔
1722
               <*> uniformM g
1✔
1723
               <*> uniformM g
1✔
1724
               <*> uniformM g
1✔
1725
               <*> uniformM g
1✔
1726
  {-# INLINE uniformM #-}
1727

1728
instance (Uniform a, Uniform b, Uniform c, Uniform d, Uniform e, Uniform f, Uniform g) =>
1729
  Uniform (a, b, c, d, e, f, g) where
1730
  uniformM g = (,,,,,,)
2✔
1731
               <$> uniformM g
1✔
1732
               <*> uniformM g
1✔
1733
               <*> uniformM g
1✔
1734
               <*> uniformM g
1✔
1735
               <*> uniformM g
1✔
1736
               <*> uniformM g
1✔
1737
               <*> uniformM g
1✔
1738
  {-# INLINE uniformM #-}
1739

1740
instance (UniformRange a, UniformRange b) => UniformRange (a, b)
1741
instance (UniformRange a, UniformRange b, UniformRange c) => UniformRange (a, b, c)
1742
instance (UniformRange a, UniformRange b, UniformRange c, UniformRange d) => UniformRange (a, b, c, d)
1743
instance (UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e) => UniformRange (a, b, c, d, e)
1744
instance (UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e, UniformRange f) => UniformRange (a, b, c, d, e, f)
1745
instance (UniformRange a, UniformRange b, UniformRange c, UniformRange d, UniformRange e, UniformRange f, UniformRange g) => UniformRange (a, b, c, d, e, f, g)
1746

1747
-- Appendix 1.
1748
--
1749
-- @top@ and @bottom@ are signed integers of bit width @n@. @toUnsigned@
1750
-- converts a signed integer to an unsigned number of the same bit width @n@.
1751
--
1752
--     range = toUnsigned top - toUnsigned bottom
1753
--
1754
-- This works out correctly thanks to modular arithmetic. Conceptually,
1755
--
1756
--     toUnsigned x | x >= 0 = x
1757
--     toUnsigned x | x <  0 = 2^n + x
1758
--
1759
-- The following combinations are possible:
1760
--
1761
-- 1. @bottom >= 0@ and @top >= 0@
1762
-- 2. @bottom < 0@ and @top >= 0@
1763
-- 3. @bottom < 0@ and @top < 0@
1764
--
1765
-- Note that @bottom >= 0@ and @top < 0@ is impossible because of the
1766
-- invariant @bottom < top@.
1767
--
1768
-- For any signed integer @i@ of width @n@, we have:
1769
--
1770
--     -2^(n-1) <= i <= 2^(n-1) - 1
1771
--
1772
-- Considering each combination in turn, we have
1773
--
1774
-- 1. @bottom >= 0@ and @top >= 0@
1775
--
1776
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1777
--                 --^ top    >= 0, so toUnsigned top    == top
1778
--                 --^ bottom >= 0, so toUnsigned bottom == bottom
1779
--           = (top - bottom) `mod` 2^n
1780
--                 --^ top <= 2^(n-1) - 1 and bottom >= 0
1781
--                 --^ top - bottom <= 2^(n-1) - 1
1782
--                 --^ 0 < top - bottom <= 2^(n-1) - 1
1783
--           = top - bottom
1784
--
1785
-- 2. @bottom < 0@ and @top >= 0@
1786
--
1787
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1788
--                 --^ top    >= 0, so toUnsigned top    == top
1789
--                 --^ bottom <  0, so toUnsigned bottom == 2^n + bottom
1790
--           = (top - (2^n + bottom)) `mod` 2^n
1791
--                 --^ summand -2^n cancels out in calculation modulo 2^n
1792
--           = (top - bottom) `mod` 2^n
1793
--                 --^ top <= 2^(n-1) - 1 and bottom >= -2^(n-1)
1794
--                 --^ top - bottom <= (2^(n-1) - 1) - (-2^(n-1)) = 2^n - 1
1795
--                 --^ 0 < top - bottom <= 2^n - 1
1796
--           = top - bottom
1797
--
1798
-- 3. @bottom < 0@ and @top < 0@
1799
--
1800
--     range = (toUnsigned top - toUnsigned bottom) `mod` 2^n
1801
--                 --^ top    < 0, so toUnsigned top    == 2^n + top
1802
--                 --^ bottom < 0, so toUnsigned bottom == 2^n + bottom
1803
--           = ((2^n + top) - (2^n + bottom)) `mod` 2^n
1804
--                 --^ summand 2^n cancels out in calculation modulo 2^n
1805
--           = (top - bottom) `mod` 2^n
1806
--                 --^ top <= -1
1807
--                 --^ bottom >= -2^(n-1)
1808
--                 --^ top - bottom <= -1 - (-2^(n-1)) = 2^(n-1) - 1
1809
--                 --^ 0 < top - bottom <= 2^(n-1) - 1
1810
--           = 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