{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, FlexibleContexts,
    FlexibleInstances, MultiParamTypeClasses, MagicHash, Rank2Types,
    ScopedTypeVariables, TypeFamilies, UnboxedTuples
    #-}
-- |
-- Module    : System.Random.MWC
-- Copyright : (c) 2009-2012 Bryan O'Sullivan
-- License   : BSD3
--
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : portable
--
-- Pseudo-random number generation using Marsaglia's MWC256, (also
-- known as MWC8222) multiply-with-carry generator, which has a period
-- of \(2^{8222}\) and fares well in tests of randomness.  It is also
-- extremely fast, between 2 and 3 times faster than the Mersenne
-- Twister. There're two representation of generator: 'Gen' which is
-- generator that uses in-place mutation and 'Seed' which is immutable
-- snapshot of generator's state.
--
--
-- == Initialization
--
-- Generator could be initialized in several ways. One is to obtain
-- randomness from operating system using 'createSystemRandom',
-- 'createSystemSeed' or 'withSystemRandomST' (All examples assume
-- that @System.Random.Stateful@ is imported)
--
-- >>> g <- createSystemRandom
-- >>> uniformM g :: IO Int
-- ...
--
-- >>> withSystemRandomST $ \g -> uniformM g :: IO Int
-- ...
--
-- Deterministically create generator from given seed using
-- 'initialize' function:
--
-- >>> import Data.Int
-- >>> import qualified Data.Vector.Unboxed as U
-- >>> import System.Random.Stateful
-- >>> g <- initialize $ U.fromList [1,2,3]
-- >>> uniformRM (1,200) g :: IO Int64
-- 101
--
-- Last way is to create generator with fixed seed which could be
-- useful in testing
--
-- >>> g <- create
-- >>> uniformM g :: IO Int
-- -8765701622605876598
--
--
-- == Generation of random numbers
--
-- Recommended way of generating random numbers in simple cases like
-- generating uniformly distributed random number in range or value
-- uniformly distributed in complete type domain is to use
-- 'UniformRange' and 'Uniform' type classes. Note that while small
-- self-contained examples usually require explicit annotations
-- usually result type could be inferred.
--
-- This example simulates 20 throws of fair 6-sided dice:
--
-- >>> g <- create
-- >>> replicateM 20 $ uniformRM (1, 6::Integer) g
-- [3,4,3,1,4,6,1,6,1,4,2,2,3,2,4,2,5,1,3,5]
--
-- For generating full range of possible values one could use
-- 'uniformM'. This example generates 10 random bytes, or equivalently
-- 10 throws of 256-sided dice:
--
-- >>> g <- create
-- >>> replicateM 10 $ uniformM g :: IO [Word8]
-- [209,138,126,150,165,15,69,203,155,146]
--
-- There're special functions for generation of @Doubles@ and @Float
-- in unit interval: 'Random.uniformDouble01M',
-- 'Random.uniformDoublePositive01M', 'Random.uniformFloat01M',
-- 'Random.uniformFloatPositive01M':
--
-- >>> uniformDouble01M =<< create
-- 0.5248103628705498
-- >>> uniformFloat01M =<< create
-- 0.5248104
--
-- For normal distribution and others see modules
-- "System.Random.MWC.Distributions" and
-- "System.Random.MWC.CondensedTable". Note that they could be used
-- with any other generator implementing 'Random.StatefulGen' API
--
-- There're special cases for generating random vectors and
-- bytestrings. For example in order to generate random 10-byte
-- sequences as unboxed vector or bytestring:
--
-- >>> g <- create
-- >>> uniformVector g 10 :: IO (U.Vector Word8)
-- [209,138,126,150,165,15,69,203,155,146]
--
-- >>> import qualified Data.ByteString as BS
-- >>> g <- create
-- >>> BS.unpack <$> uniformByteStringM 10 g
-- [138,242,130,33,209,248,89,134,150,180]
--
-- Note that 'Random.uniformByteStringM' produces different result
-- from 'uniformVector' since it uses PRNG's output more efficently.
--
--
-- == State handling
--
-- For repeatability, the state of the generator can be snapshotted
-- and replayed using the 'save' and 'restore' functions. Following
-- example shows how to save and restore generator:
--
-- >>> g <- create
-- >>> replicateM_ 10 (uniformM g :: IO Word64)
-- >>> s <- save g
-- >>> uniformM g :: IO Word32
-- 1771812561
-- >>> uniformM =<< restore s :: IO Word32
-- 1771812561
module System.Random.MWC
    (
    -- * Gen: Pseudo-Random Number Generators
      Gen
    , create
    , initialize
    , createSystemSeed
    , createSystemRandom
    , withSystemRandomST
    -- ** Type helpers
    -- $typehelp
    , GenIO
    , GenST
    , asGenIO
    , asGenST

    -- * Variates: uniformly distributed values
    , Random.Uniform(..)
    , Random.UniformRange(..)
    , Variate(..)
    , uniformVector

    -- * Seed: state management
    , Seed
    , fromSeed
    , toSeed
    , save
    , restore
    -- * Deprecated
    , withSystemRandom
    -- * References
    -- $references
    ) where

#if defined(__GLASGOW_HASKELL__) && !defined(__HADDOCK__)
#include "MachDeps.h"
#endif

import Control.Monad           (ap, liftM, unless)
import Control.Monad.Primitive (PrimMonad, PrimBase, PrimState, unsafePrimToIO, unsafeSTToPrim)
import Control.Monad.ST        (ST,runST)
import Data.Bits               ((.&.), (.|.), shiftL, shiftR, xor)
import Data.Int                (Int8, Int16, Int32, Int64)
import Data.IORef              (IORef, atomicModifyIORef, newIORef)
import Data.Typeable           (Typeable)
import Data.Vector.Generic     (Vector)
import Data.Word
import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Unboxed         as I
import qualified Data.Vector.Unboxed.Mutable as M
import System.IO        (hPutStrLn, stderr)
import System.IO.Unsafe (unsafePerformIO)
import qualified Control.Exception as E
import System.Random.MWC.SeedSource
import qualified System.Random.Stateful as Random

-- | NOTE: Consider use of more principled type classes
-- 'Random.Uniform' and 'Random.UniformRange' instead.
--
-- The class of types for which we can generate uniformly
-- distributed random variates.
--
-- The uniform PRNG uses Marsaglia's MWC256 (also known as MWC8222)
-- multiply-with-carry generator, which has a period of 2^8222 and
-- fares well in tests of randomness.  It is also extremely fast,
-- between 2 and 3 times faster than the Mersenne Twister.
--
-- /Note/: Marsaglia's PRNG is not known to be cryptographically
-- secure, so you should not use it for cryptographic operations.
class Variate a where
    -- | Generate a single uniformly distributed random variate.  The
    -- range of values produced varies by type:
    --
    -- * For fixed-width integral types, the type's entire range is
    --   used.
    --
    -- * For floating point numbers, the range (0,1] is used. Zero is
    --   explicitly excluded, to allow variates to be used in
    --   statistical calculations that require non-zero values
    --   (e.g. uses of the 'log' function).
    --
    -- To generate a 'Float' variate with a range of [0,1), subtract
    -- 2**(-33).  To do the same with 'Double' variates, subtract
    -- 2**(-53).
    uniform :: (PrimMonad m) => Gen (PrimState m) -> m a
    -- | Generate single uniformly distributed random variable in a
    -- given range.
    --
    -- * For integral types inclusive range is used.
    --
    -- * For floating point numbers range (a,b] is used if one ignores
    --   rounding errors.
    uniformR :: (PrimMonad m) => (a,a) -> Gen (PrimState m) -> m a

instance Variate Int8 where
    uniform :: Gen (PrimState m) -> m Int8
uniform  = (Word32 -> Int8) -> Gen (PrimState m) -> m Int8
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    uniformR :: (Int8, Int8) -> Gen (PrimState m) -> m Int8
uniformR (Int8, Int8)
a Gen (PrimState m)
b = (Int8, Int8) -> Gen (PrimState m) -> m Int8
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Int8, Int8)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Int16 where
    uniform :: Gen (PrimState m) -> m Int16
uniform  = (Word32 -> Int16) -> Gen (PrimState m) -> m Int16
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    uniformR :: (Int16, Int16) -> Gen (PrimState m) -> m Int16
uniformR (Int16, Int16)
a Gen (PrimState m)
b = (Int16, Int16) -> Gen (PrimState m) -> m Int16
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Int16, Int16)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Int32 where
    uniform :: Gen (PrimState m) -> m Int32
uniform  = (Word32 -> Int32) -> Gen (PrimState m) -> m Int32
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    uniformR :: (Int32, Int32) -> Gen (PrimState m) -> m Int32
uniformR (Int32, Int32)
a Gen (PrimState m)
b = (Int32, Int32) -> Gen (PrimState m) -> m Int32
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Int32, Int32)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Int64 where
    uniform :: Gen (PrimState m) -> m Int64
uniform  = (Word32 -> Word32 -> Int64) -> Gen (PrimState m) -> m Int64
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> Int64
forall a. Integral a => Word32 -> Word32 -> a
wordsTo64Bit
    uniformR :: (Int64, Int64) -> Gen (PrimState m) -> m Int64
uniformR (Int64, Int64)
a Gen (PrimState m)
b = (Int64, Int64) -> Gen (PrimState m) -> m Int64
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Int64, Int64)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Word8 where
    uniform :: Gen (PrimState m) -> m Word8
uniform  = (Word32 -> Word8) -> Gen (PrimState m) -> m Word8
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    uniformR :: (Word8, Word8) -> Gen (PrimState m) -> m Word8
uniformR (Word8, Word8)
a Gen (PrimState m)
b = (Word8, Word8) -> Gen (PrimState m) -> m Word8
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Word8, Word8)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Word16 where
    uniform :: Gen (PrimState m) -> m Word16
uniform  = (Word32 -> Word16) -> Gen (PrimState m) -> m Word16
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    uniformR :: (Word16, Word16) -> Gen (PrimState m) -> m Word16
uniformR (Word16, Word16)
a Gen (PrimState m)
b = (Word16, Word16) -> Gen (PrimState m) -> m Word16
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Word16, Word16)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Word32 where
    uniform :: Gen (PrimState m) -> m Word32
uniform  = (Word32 -> Word32) -> Gen (PrimState m) -> m Word32
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Word32
forall a. a -> a
id
    uniformR :: (Word32, Word32) -> Gen (PrimState m) -> m Word32
uniformR (Word32, Word32)
a Gen (PrimState m)
b = (Word32, Word32) -> Gen (PrimState m) -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Word32, Word32)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Word64 where
    uniform :: Gen (PrimState m) -> m Word64
uniform  = (Word32 -> Word32 -> Word64) -> Gen (PrimState m) -> m Word64
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> Word64
forall a. Integral a => Word32 -> Word32 -> a
wordsTo64Bit
    uniformR :: (Word64, Word64) -> Gen (PrimState m) -> m Word64
uniformR (Word64, Word64)
a Gen (PrimState m)
b = (Word64, Word64) -> Gen (PrimState m) -> m Word64
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Word64, Word64)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Bool where
    uniform :: Gen (PrimState m) -> m Bool
uniform = (Word32 -> Bool) -> Gen (PrimState m) -> m Bool
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Bool
wordToBool
    uniformR :: (Bool, Bool) -> Gen (PrimState m) -> m Bool
uniformR (Bool
False,Bool
True)  Gen (PrimState m)
g = Gen (PrimState m) -> m Bool
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
    uniformR (Bool
False,Bool
False) Gen (PrimState m)
_ = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
    uniformR (Bool
True,Bool
True)   Gen (PrimState m)
_ = Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
    uniformR (Bool
True,Bool
False)  Gen (PrimState m)
g = Gen (PrimState m) -> m Bool
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Float where
    uniform :: Gen (PrimState m) -> m Float
uniform          = (Word32 -> Float) -> Gen (PrimState m) -> m Float
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> Float
wordToFloat
    uniformR :: (Float, Float) -> Gen (PrimState m) -> m Float
uniformR (Float
x1,Float
x2) = (Word32 -> Float) -> Gen (PrimState m) -> m Float
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 (\Word32
w -> Float
x1 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ (Float
x2Float -> Float -> Float
forall a. Num a => a -> a -> a
-Float
x1) Float -> Float -> Float
forall a. Num a => a -> a -> a
* Word32 -> Float
wordToFloat Word32
w)
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Double where
    uniform :: Gen (PrimState m) -> m Double
uniform          = (Word32 -> Word32 -> Double) -> Gen (PrimState m) -> m Double
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> Double
wordsToDouble
    uniformR :: (Double, Double) -> Gen (PrimState m) -> m Double
uniformR (Double
x1,Double
x2) = (Word32 -> Word32 -> Double) -> Gen (PrimState m) -> m Double
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 (\Word32
w1 Word32
w2 -> Double
x1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
x2Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
x1) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Word32 -> Word32 -> Double
wordsToDouble Word32
w1 Word32
w2)
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Int where
#if WORD_SIZE_IN_BITS == 32
    uniform = uniform1 fromIntegral
#elif WORD_SIZE_IN_BITS == 64
    uniform :: Gen (PrimState m) -> m Int
uniform = (Word32 -> Word32 -> Int) -> Gen (PrimState m) -> m Int
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> Int
forall a. Integral a => Word32 -> Word32 -> a
wordsTo64Bit
#else
#error "Word size is not 32 nor 64"
#endif
    uniformR :: (Int, Int) -> Gen (PrimState m) -> m Int
uniformR (Int, Int)
a Gen (PrimState m)
b = (Int, Int) -> Gen (PrimState m) -> m Int
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Int, Int)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance Variate Word where
#if WORD_SIZE_IN_BITS == 32
    uniform = uniform1 fromIntegral
#elif WORD_SIZE_IN_BITS == 64
    uniform :: Gen (PrimState m) -> m Word
uniform = (Word32 -> Word32 -> Word) -> Gen (PrimState m) -> m Word
forall (m :: * -> *) a.
PrimMonad m =>
(Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> Word
forall a. Integral a => Word32 -> Word32 -> a
wordsTo64Bit
#else
#error "Word size is not 32 nor 64"
#endif
    uniformR :: (Word, Word) -> Gen (PrimState m) -> m Word
uniformR (Word, Word)
a Gen (PrimState m)
b = (Word, Word) -> Gen (PrimState m) -> m Word
forall (m :: * -> *) a.
(PrimMonad m, Integral a, Bounded a, Variate a,
 Integral (Unsigned a), Bounded (Unsigned a),
 Variate (Unsigned a)) =>
(a, a) -> Gen (PrimState m) -> m a
uniformRange (Word, Word)
a Gen (PrimState m)
b
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance (Variate a, Variate b) => Variate (a,b) where
    uniform :: Gen (PrimState m) -> m (a, b)
uniform Gen (PrimState m)
g = (,) (a -> b -> (a, b)) -> m a -> m (b -> (a, b))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g m (b -> (a, b)) -> m b -> m (a, b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
    uniformR :: ((a, b), (a, b)) -> Gen (PrimState m) -> m (a, b)
uniformR ((a
x1,b
y1),(a
x2,b
y2)) Gen (PrimState m)
g = (,) (a -> b -> (a, b)) -> m a -> m (b -> (a, b))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` (a, a) -> Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (a
x1,a
x2) Gen (PrimState m)
g m (b -> (a, b)) -> m b -> m (a, b)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (b, b) -> Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (b
y1,b
y2) Gen (PrimState m)
g
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance (Variate a, Variate b, Variate c) => Variate (a,b,c) where
    uniform :: Gen (PrimState m) -> m (a, b, c)
uniform Gen (PrimState m)
g = (,,) (a -> b -> c -> (a, b, c)) -> m a -> m (b -> c -> (a, b, c))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g m (b -> c -> (a, b, c)) -> m b -> m (c -> (a, b, c))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g m (c -> (a, b, c)) -> m c -> m (a, b, c)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m c
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
    uniformR :: ((a, b, c), (a, b, c)) -> Gen (PrimState m) -> m (a, b, c)
uniformR ((a
x1,b
y1,c
z1),(a
x2,b
y2,c
z2)) Gen (PrimState m)
g =
      (,,) (a -> b -> c -> (a, b, c)) -> m a -> m (b -> c -> (a, b, c))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` (a, a) -> Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (a
x1,a
x2) Gen (PrimState m)
g m (b -> c -> (a, b, c)) -> m b -> m (c -> (a, b, c))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (b, b) -> Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (b
y1,b
y2) Gen (PrimState m)
g m (c -> (a, b, c)) -> m c -> m (a, b, c)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (c, c) -> Gen (PrimState m) -> m c
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (c
z1,c
z2) Gen (PrimState m)
g
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

instance (Variate a, Variate b, Variate c, Variate d) => Variate (a,b,c,d) where
    uniform :: Gen (PrimState m) -> m (a, b, c, d)
uniform Gen (PrimState m)
g = (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> m a -> m (b -> c -> d -> (a, b, c, d))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g m (b -> c -> d -> (a, b, c, d))
-> m b -> m (c -> d -> (a, b, c, d))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g m (c -> d -> (a, b, c, d)) -> m c -> m (d -> (a, b, c, d))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m c
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
                m (d -> (a, b, c, d)) -> m d -> m (a, b, c, d)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` Gen (PrimState m) -> m d
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
    uniformR :: ((a, b, c, d), (a, b, c, d)) -> Gen (PrimState m) -> m (a, b, c, d)
uniformR ((a
x1,b
y1,c
z1,d
t1),(a
x2,b
y2,c
z2,d
t2)) Gen (PrimState m)
g =
      (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> m a -> m (b -> c -> d -> (a, b, c, d))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` (a, a) -> Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (a
x1,a
x2) Gen (PrimState m)
g m (b -> c -> d -> (a, b, c, d))
-> m b -> m (c -> d -> (a, b, c, d))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (b, b) -> Gen (PrimState m) -> m b
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (b
y1,b
y2) Gen (PrimState m)
g m (c -> d -> (a, b, c, d)) -> m c -> m (d -> (a, b, c, d))
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap`
                    (c, c) -> Gen (PrimState m) -> m c
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (c
z1,c
z2) Gen (PrimState m)
g m (d -> (a, b, c, d)) -> m d -> m (a, b, c, d)
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
`ap` (d, d) -> Gen (PrimState m) -> m d
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (d
t1,d
t2) Gen (PrimState m)
g
    {-# INLINE uniform  #-}
    {-# INLINE uniformR #-}

wordsTo64Bit :: (Integral a) => Word32 -> Word32 -> a
wordsTo64Bit :: Word32 -> Word32 -> a
wordsTo64Bit Word32
x Word32
y =
    Word64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
32) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
y :: Word64)
{-# INLINE wordsTo64Bit #-}

wordToBool :: Word32 -> Bool
wordToBool :: Word32 -> Bool
wordToBool Word32
i = (Word32
i Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
1) Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
0
{-# INLINE wordToBool #-}

wordToFloat :: Word32 -> Float
wordToFloat :: Word32 -> Float
wordToFloat Word32
x      = (Int32 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
i Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
m_inv_32) Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
0.5 Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
m_inv_33
    where m_inv_33 :: Float
m_inv_33 = Float
1.16415321826934814453125e-10
          m_inv_32 :: Float
m_inv_32 = Float
2.3283064365386962890625e-10
          i :: Int32
i        = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x :: Int32
{-# INLINE wordToFloat #-}

wordsToDouble :: Word32 -> Word32 -> Double
wordsToDouble :: Word32 -> Word32 -> Double
wordsToDouble Word32
x Word32
y  = (Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
u Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
m_inv_32 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
0.5 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
m_inv_53) Double -> Double -> Double
forall a. Num a => a -> a -> a
+
                     Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32
v Int32 -> Int32 -> Int32
forall a. Bits a => a -> a -> a
.&. Int32
0xFFFFF) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
m_inv_52)
    where m_inv_52 :: Double
m_inv_52 = Double
2.220446049250313080847263336181640625e-16
          m_inv_53 :: Double
m_inv_53 = Double
1.1102230246251565404236316680908203125e-16
          m_inv_32 :: Double
m_inv_32 = Double
2.3283064365386962890625e-10
          u :: Int32
u        = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x :: Int32
          v :: Int32
v        = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
y :: Int32
{-# INLINE wordsToDouble #-}

-- | State of the pseudo-random number generator. It uses mutable
-- state so same generator shouldn't be used from the different
-- threads simultaneously.
newtype Gen s = Gen (M.MVector s Word32)

-- | A shorter name for PRNG state in the 'IO' monad.
type GenIO = Gen (PrimState IO)

-- | A shorter name for PRNG state in the 'ST' monad.
type GenST s = Gen (PrimState (ST s))

-- | Constrain the type of an action to run in the 'IO' monad.
asGenIO :: (GenIO -> IO a) -> (GenIO -> IO a)
asGenIO :: (GenIO -> IO a) -> GenIO -> IO a
asGenIO = (GenIO -> IO a) -> GenIO -> IO a
forall a. a -> a
id

-- | Constrain the type of an action to run in the 'ST' monad.
asGenST :: (GenST s -> ST s a) -> (GenST s -> ST s a)
asGenST :: (GenST s -> ST s a) -> GenST s -> ST s a
asGenST = (GenST s -> ST s a) -> GenST s -> ST s a
forall a. a -> a
id

ioff, coff :: Int
ioff :: Int
ioff = Int
256
coff :: Int
coff = Int
257

-- | Create a generator for variates using a fixed seed.
create :: PrimMonad m => m (Gen (PrimState m))
create :: m (Gen (PrimState m))
create = Vector Word32 -> m (Gen (PrimState m))
forall (m :: * -> *) (v :: * -> *).
(PrimMonad m, Vector v Word32) =>
v Word32 -> m (Gen (PrimState m))
initialize Vector Word32
defaultSeed
{-# INLINE create #-}

-- | Create a generator for variates using the given seed, of which up
-- to 256 elements will be used.  For arrays of less than 256
-- elements, part of the default seed will be used to finish
-- initializing the generator's state.
--
-- Examples:
--
-- > initialize (singleton 42)
--
-- > initialize (fromList [4, 8, 15, 16, 23, 42])
--
-- If a seed contains fewer than 256 elements, it is first used
-- verbatim, then its elements are 'xor'ed against elements of the
-- default seed until 256 elements are reached.
--
-- If a seed contains exactly 258 elements, then the last two elements
-- are used to set the generator's initial state. This allows for
-- complete generator reproducibility, so that e.g. @gen' == gen@ in
-- the following example:
--
-- @gen' <- 'initialize' . 'fromSeed' =<< 'save'@
--
-- In the MWC algorithm, the /carry/ value must be strictly smaller than the
-- multiplicator (see https://en.wikipedia.org/wiki/Multiply-with-carry).
-- Hence, if a seed contains exactly 258 elements, the /carry/ value, which is
-- the last of the 258 values, is moduloed by the multiplicator.
--
-- Note that if the /first/ carry value is strictly smaller than the multiplicator,
-- all subsequent carry values are also strictly smaller than the multiplicator
-- (a proof of this is in the comments of the code of 'uniformWord32'), hence
-- when restoring a saved state, we have the guarantee that moduloing the saved
-- carry won't modify its value.
initialize :: (PrimMonad m, Vector v Word32) =>
              v Word32 -> m (Gen (PrimState m))
initialize :: v Word32 -> m (Gen (PrimState m))
initialize v Word32
seed = do
    MVector (PrimState m) Word32
q <- Int -> m (MVector (PrimState m) Word32)
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
Int -> m (MVector (PrimState m) a)
M.unsafeNew Int
258
    MVector (PrimState m) Word32 -> m ()
fill MVector (PrimState m) Word32
q
    if Int
fini Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
258
      then do
        MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
ioff (Word32 -> m ()) -> Word32 -> m ()
forall a b. (a -> b) -> a -> b
$ v Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex v Word32
seed Int
ioff Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
255
        MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
coff (Word32 -> m ()) -> Word32 -> m ()
forall a b. (a -> b) -> a -> b
$ v Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex v Word32
seed Int
coff Word32 -> Word32 -> Word32
forall a. Integral a => a -> a -> a
`mod` Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
aa
      else do
        MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
ioff Word32
255
        MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
coff Word32
362436
    Gen (PrimState m) -> m (Gen (PrimState m))
forall (m :: * -> *) a. Monad m => a -> m a
return (MVector (PrimState m) Word32 -> Gen (PrimState m)
forall s. MVector s Word32 -> Gen s
Gen MVector (PrimState m) Word32
q)
  where fill :: MVector (PrimState m) Word32 -> m ()
fill MVector (PrimState m) Word32
q = Int -> m ()
go Int
0 where
          go :: Int -> m ()
go Int
i | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
256  = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
               | Bool
otherwise = MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
i Word32
s m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m ()
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
            where s :: Word32
s | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
fini = if Int
fini Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
                                  then Vector Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex Vector Word32
defaultSeed Int
i
                                  else Vector Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex Vector Word32
defaultSeed Int
i Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
`xor`
                                       v Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex v Word32
seed (Int
i Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
fini)
                    | Bool
otherwise = v Word32 -> Int -> Word32
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex v Word32
seed Int
i
        fini :: Int
fini = v Word32 -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.length v Word32
seed
{-# INLINE initialize #-}

-- | An immutable snapshot of the state of a 'Gen'.
newtype Seed = Seed (I.Vector Word32)
  deriving (Seed -> Seed -> Bool
(Seed -> Seed -> Bool) -> (Seed -> Seed -> Bool) -> Eq Seed
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seed -> Seed -> Bool
$c/= :: Seed -> Seed -> Bool
== :: Seed -> Seed -> Bool
$c== :: Seed -> Seed -> Bool
Eq, Int -> Seed -> ShowS
[Seed] -> ShowS
Seed -> String
(Int -> Seed -> ShowS)
-> (Seed -> String) -> ([Seed] -> ShowS) -> Show Seed
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seed] -> ShowS
$cshowList :: [Seed] -> ShowS
show :: Seed -> String
$cshow :: Seed -> String
showsPrec :: Int -> Seed -> ShowS
$cshowsPrec :: Int -> Seed -> ShowS
Show, Typeable)

-- | Convert seed into vector.
fromSeed :: Seed -> I.Vector Word32
fromSeed :: Seed -> Vector Word32
fromSeed (Seed Vector Word32
v) = Vector Word32
v

-- | @since 0.15.0.0
instance (s ~ PrimState m, PrimMonad m) => Random.StatefulGen (Gen s) m where
  uniformWord32R :: Word32 -> Gen s -> m Word32
uniformWord32R Word32
u = (Word32, Word32) -> Gen (PrimState m) -> m Word32
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (Word32
0, Word32
u)
  {-# INLINE uniformWord32R #-}
  uniformWord64R :: Word64 -> Gen s -> m Word64
uniformWord64R Word64
u = (Word64, Word64) -> Gen (PrimState m) -> m Word64
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
(a, a) -> Gen (PrimState m) -> m a
uniformR (Word64
0, Word64
u)
  {-# INLINE uniformWord64R #-}
  uniformWord8 :: Gen s -> m Word8
uniformWord8 = Gen s -> m Word8
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform
  {-# INLINE uniformWord8 #-}
  uniformWord16 :: Gen s -> m Word16
uniformWord16 = Gen s -> m Word16
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform
  {-# INLINE uniformWord16 #-}
  uniformWord32 :: Gen s -> m Word32
uniformWord32 = Gen s -> m Word32
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform
  {-# INLINE uniformWord32 #-}
  uniformWord64 :: Gen s -> m Word64
uniformWord64 = Gen s -> m Word64
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform
  {-# INLINE uniformWord64 #-}
  uniformShortByteString :: Int -> Gen s -> m ShortByteString
uniformShortByteString Int
n Gen s
g = ST s ShortByteString -> m ShortByteString
forall (m :: * -> *) s a. PrimMonad m => ST s a -> m a
unsafeSTToPrim (Int -> ST s Word64 -> ST s ShortByteString
forall s. Int -> ST s Word64 -> ST s ShortByteString
Random.genShortByteStringST Int
n (Gen (PrimState (ST s)) -> ST s Word64
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen s
Gen (PrimState (ST s))
g))
  {-# INLINE uniformShortByteString #-}

-- | @since 0.15.0.0
instance PrimMonad m => Random.FrozenGen Seed m where
  type MutableGen Seed m = Gen (PrimState m)
  thawGen :: Seed -> m (MutableGen Seed m)
thawGen = Seed -> m (MutableGen Seed m)
forall (m :: * -> *). PrimMonad m => Seed -> m (Gen (PrimState m))
restore
  freezeGen :: MutableGen Seed m -> m Seed
freezeGen = MutableGen Seed m -> m Seed
forall (m :: * -> *). PrimMonad m => Gen (PrimState m) -> m Seed
save

-- | Convert vector to 'Seed'. It acts similarily to 'initialize' and
-- will accept any vector. If you want to pass seed immediately to
-- restore you better call initialize directly since following law holds:
--
-- > restore (toSeed v) = initialize v
toSeed :: (Vector v Word32) => v Word32 -> Seed
toSeed :: v Word32 -> Seed
toSeed v Word32
v = Vector Word32 -> Seed
Seed (Vector Word32 -> Seed) -> Vector Word32 -> Seed
forall a b. (a -> b) -> a -> b
$ (forall s. ST s (MVector s Word32)) -> Vector Word32
forall a. Unbox a => (forall s. ST s (MVector s a)) -> Vector a
I.create ((forall s. ST s (MVector s Word32)) -> Vector Word32)
-> (forall s. ST s (MVector s Word32)) -> Vector Word32
forall a b. (a -> b) -> a -> b
$ do { Gen MVector s Word32
q <- v Word32 -> ST s (Gen (PrimState (ST s)))
forall (m :: * -> *) (v :: * -> *).
(PrimMonad m, Vector v Word32) =>
v Word32 -> m (Gen (PrimState m))
initialize v Word32
v; MVector s Word32 -> ST s (MVector s Word32)
forall (m :: * -> *) a. Monad m => a -> m a
return MVector s Word32
q }

-- | Save the state of a 'Gen', for later use by 'restore'.
save :: PrimMonad m => Gen (PrimState m) -> m Seed
save :: Gen (PrimState m) -> m Seed
save (Gen MVector (PrimState m) Word32
q) = Vector Word32 -> Seed
Seed (Vector Word32 -> Seed) -> m (Vector Word32) -> m Seed
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Mutable Vector (PrimState m) Word32 -> m (Vector Word32)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
G.freeze MVector (PrimState m) Word32
Mutable Vector (PrimState m) Word32
q
{-# INLINE save #-}

-- | Create a new 'Gen' that mirrors the state of a saved 'Seed'.
restore :: PrimMonad m => Seed -> m (Gen (PrimState m))
restore :: Seed -> m (Gen (PrimState m))
restore (Seed Vector Word32
s) = MVector (PrimState m) Word32 -> Gen (PrimState m)
forall s. MVector s Word32 -> Gen s
Gen (MVector (PrimState m) Word32 -> Gen (PrimState m))
-> m (MVector (PrimState m) Word32) -> m (Gen (PrimState m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Vector Word32 -> m (Mutable Vector (PrimState m) Word32)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
G.thaw Vector Word32
s
{-# INLINE restore #-}


-- $seeding
--
-- Library provides several functions allowing to intialize generator
-- using OS-provided randomness: \"@\/dev\/urandom@\" on Unix-like
-- systems or @RtlGenRandom@ on Windows. This is a somewhat expensive
-- function, and is intended to be called only occasionally (e.g. once
-- per thread).  You should use the `Gen` it creates to generate many
-- random numbers.

createSystemRandomList :: IO [Word32]
createSystemRandomList :: IO [Word32]
createSystemRandomList = do
  Int -> IO [Word32]
forall a. Storable a => Int -> IO [a]
acquireSeedSystem Int
256 IO [Word32] -> (IOException -> IO [Word32]) -> IO [Word32]
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \(IOException
_::E.IOException) -> do
    Bool
seen <- IORef Bool -> (Bool -> (Bool, Bool)) -> IO Bool
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef IORef Bool
seedCreatetionWarned ((,) Bool
True)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
seen (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ (IOException -> IO ()) -> IO () -> IO ()
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
E.handle (\(IOException
_::E.IOException) -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
      Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Warning: Couldn't use randomness source " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
randomSourceName
      Handle -> String -> IO ()
hPutStrLn Handle
stderr (String
"Warning: using system clock for seed instead " String -> ShowS
forall a. [a] -> [a] -> [a]
++
                        String
"(quality will be lower)")
    IO [Word32]
acquireSeedTime

seedCreatetionWarned :: IORef Bool
seedCreatetionWarned :: IORef Bool
seedCreatetionWarned = IO (IORef Bool) -> IORef Bool
forall a. IO a -> a
unsafePerformIO (IO (IORef Bool) -> IORef Bool) -> IO (IORef Bool) -> IORef Bool
forall a b. (a -> b) -> a -> b
$ Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False
{-# NOINLINE seedCreatetionWarned #-}



-- | Generate random seed for generator using system's fast source of
--   pseudo-random numbers.
--
-- @since 0.15.0.0
createSystemSeed :: IO Seed
createSystemSeed :: IO Seed
createSystemSeed = do
  [Word32]
seed <- IO [Word32]
createSystemRandomList
  Seed -> IO Seed
forall (m :: * -> *) a. Monad m => a -> m a
return (Seed -> IO Seed) -> Seed -> IO Seed
forall a b. (a -> b) -> a -> b
$! Vector Word32 -> Seed
forall (v :: * -> *). Vector v Word32 => v Word32 -> Seed
toSeed (Vector Word32 -> Seed) -> Vector Word32 -> Seed
forall a b. (a -> b) -> a -> b
$ [Word32] -> Vector Word32
forall a. Unbox a => [a] -> Vector a
I.fromList [Word32]
seed

-- | Seed a PRNG with data from the system's fast source of
--   pseudo-random numbers.
createSystemRandom :: IO GenIO
createSystemRandom :: IO GenIO
createSystemRandom = Vector Word32 -> IO (Gen RealWorld)
forall (m :: * -> *) (v :: * -> *).
(PrimMonad m, Vector v Word32) =>
v Word32 -> m (Gen (PrimState m))
initialize (Vector Word32 -> IO (Gen RealWorld))
-> ([Word32] -> Vector Word32) -> [Word32] -> IO (Gen RealWorld)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word32] -> Vector Word32
forall a. Unbox a => [a] -> Vector a
I.fromList ([Word32] -> IO (Gen RealWorld))
-> IO [Word32] -> IO (Gen RealWorld)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO [Word32]
createSystemRandomList


-- | Seed PRNG with data from the system's fast source of
--   pseudo-random numbers and execute computation in ST monad.
--
-- @since 0.15.0.0
withSystemRandomST :: (forall s. Gen s -> ST s a) -> IO a
withSystemRandomST :: (forall s. Gen s -> ST s a) -> IO a
withSystemRandomST forall s. Gen s -> ST s a
act = do
  Seed
seed <- IO Seed
createSystemSeed
  a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> IO a) -> a -> IO a
forall a b. (a -> b) -> a -> b
$! (forall s. ST s a) -> a
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s a) -> a) -> (forall s. ST s a) -> a
forall a b. (a -> b) -> a -> b
$ Gen s -> ST s a
forall s. Gen s -> ST s a
act (Gen s -> ST s a) -> ST s (Gen s) -> ST s a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Seed -> ST s (Gen (PrimState (ST s)))
forall (m :: * -> *). PrimMonad m => Seed -> m (Gen (PrimState m))
restore Seed
seed

-- | Seed a PRNG with data from the system's fast source of
--   pseudo-random numbers, then run the given action.
--
--   This function is unsafe and for example allows STRefs or any
--   other mutable data structure to escape scope:
--
--   >>> ref <- withSystemRandom $ \_ -> newSTRef 1
--   >>> withSystemRandom $ \_ -> modifySTRef ref succ >> readSTRef ref
--   2
--   >>> withSystemRandom $ \_ -> modifySTRef ref succ >> readSTRef ref
--   3
withSystemRandom :: PrimBase m
                 => (Gen (PrimState m) -> m a) -> IO a
withSystemRandom :: (Gen (PrimState m) -> m a) -> IO a
withSystemRandom Gen (PrimState m) -> m a
act = do
  Seed
seed <- IO Seed
createSystemSeed
  m a -> IO a
forall (m :: * -> *) a. PrimBase m => m a -> IO a
unsafePrimToIO (m a -> IO a) -> m a -> IO a
forall a b. (a -> b) -> a -> b
$ Gen (PrimState m) -> m a
act (Gen (PrimState m) -> m a) -> m (Gen (PrimState m)) -> m a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Seed -> m (Gen (PrimState m))
forall (m :: * -> *). PrimMonad m => Seed -> m (Gen (PrimState m))
restore Seed
seed
{-# DEPRECATED withSystemRandom "Use withSystemRandomST or createSystemSeed or createSystemRandom instead" #-}


-- | Compute the next index into the state pool.  This is simply
-- addition modulo 256.
nextIndex :: Integral a => a -> Int
nextIndex :: a -> Int
nextIndex a
i = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
j
    where j :: Word8
j = a -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a
ia -> a -> a
forall a. Num a => a -> a -> a
+a
1) :: Word8
{-# INLINE nextIndex #-}

-- The multiplicator : 0x5BCF5AB2
--
-- Eventhough it is a 'Word64', it is important for the correctness of the proof
-- on carry value that it is /not/ greater than maxBound 'Word32'.
aa :: Word64
aa :: Word64
aa = Word64
1540315826
{-# INLINE aa #-}

uniformWord32 :: PrimMonad m => Gen (PrimState m) -> m Word32
-- NOTE [Carry value]
uniformWord32 :: Gen (PrimState m) -> m Word32
uniformWord32 (Gen MVector (PrimState m) Word32
q) = do
  Int
i  <- Word32 -> Int
forall a. Integral a => a -> Int
nextIndex (Word32 -> Int) -> m Word32 -> m Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
ioff
  Word64
c  <- Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> m Word32 -> m Word64
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
coff
  Word64
qi <- Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> m Word32 -> m Word64
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
i
  let t :: Word64
t  = Word64
aa Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
qi Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
c
      c' :: Word32
c' = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
t Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32)
      x :: Word32
x  = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
t Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
c'
      (# Word32
x', Word32
c'' #)  | Word32
x Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
< Word32
c'    = (# Word32
x Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1, Word32
c' Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1 #)
                     | Bool
otherwise = (# Word32
x,     Word32
c' #)
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
i Word32
x'
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
ioff (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
coff Word32
c''
  Word32 -> m Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
x'
{-# INLINE uniformWord32 #-}

uniform1 :: PrimMonad m => (Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 :: (Word32 -> a) -> Gen (PrimState m) -> m a
uniform1 Word32 -> a
f Gen (PrimState m)
gen = do
  Word32
i <- Gen (PrimState m) -> m Word32
forall (m :: * -> *). PrimMonad m => Gen (PrimState m) -> m Word32
uniformWord32 Gen (PrimState m)
gen
  a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$! Word32 -> a
f Word32
i
{-# INLINE uniform1 #-}

uniform2 :: PrimMonad m => (Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 :: (Word32 -> Word32 -> a) -> Gen (PrimState m) -> m a
uniform2 Word32 -> Word32 -> a
f (Gen MVector (PrimState m) Word32
q) = do
  Int
i  <- Word32 -> Int
forall a. Integral a => a -> Int
nextIndex (Word32 -> Int) -> m Word32 -> m Int
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
ioff
  let j :: Int
j = Int -> Int
forall a. Integral a => a -> Int
nextIndex Int
i
  Word64
c  <- Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> m Word32 -> m Word64
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
coff
  Word64
qi <- Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> m Word32 -> m Word64
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
i
  Word64
qj <- Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> m Word32 -> m Word64
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) Word32 -> Int -> m Word32
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> m a
M.unsafeRead MVector (PrimState m) Word32
q Int
j
  let t :: Word64
t   = Word64
aa Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
qi Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
c
      c' :: Word32
c'  = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
t Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32)
      x :: Word32
x   = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
t Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
c'
      (# Word32
x', Word32
c'' #)  | Word32
x Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
< Word32
c'    = (# Word32
x Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1, Word32
c' Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1 #)
                     | Bool
otherwise = (# Word32
x,     Word32
c' #)
      u :: Word64
u   = Word64
aa Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
qj Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
c''
      d' :: Word32
d'  = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
u Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32)
      y :: Word32
y   = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
u Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
d'
      (# Word32
y', Word32
d'' #)  | Word32
y Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
< Word32
d'    = (# Word32
y Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1, Word32
d' Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
1 #)
                     | Bool
otherwise = (# Word32
y,     Word32
d' #)
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
i Word32
x'
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
j Word32
y'
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
ioff (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
j)
  MVector (PrimState m) Word32 -> Int -> Word32 -> m ()
forall (m :: * -> *) a.
(PrimMonad m, Unbox a) =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) Word32
q Int
coff Word32
d''
  a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$! Word32 -> Word32 -> a
f Word32
x' Word32
y'
{-# INLINE uniform2 #-}

-- Type family for fixed size integrals. For signed data types it's
-- its unsigned couterpart with same size and for unsigned data types
-- it's same type
type family Unsigned a :: *

type instance Unsigned Int8  = Word8
type instance Unsigned Int16 = Word16
type instance Unsigned Int32 = Word32
type instance Unsigned Int64 = Word64

type instance Unsigned Word8  = Word8
type instance Unsigned Word16 = Word16
type instance Unsigned Word32 = Word32
type instance Unsigned Word64 = Word64

type instance Unsigned Int   = Word
type instance Unsigned Word  = Word


-- Subtract two numbers under assumption that x>=y and store result in
-- unsigned data type of same size
sub :: (Integral a, Integral (Unsigned a)) => a -> a -> Unsigned a
sub :: a -> a -> Unsigned a
sub a
x a
y = a -> Unsigned a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x Unsigned a -> Unsigned a -> Unsigned a
forall a. Num a => a -> a -> a
- a -> Unsigned a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
y
{-# INLINE sub #-}

add :: (Integral a, Integral (Unsigned a)) => a -> Unsigned a -> a
add :: a -> Unsigned a -> a
add a
m Unsigned a
x = a
m a -> a -> a
forall a. Num a => a -> a -> a
+ Unsigned a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Unsigned a
x
{-# INLINE add #-}

-- Generate uniformly distributed value in inclusive range.
--
-- NOTE: This function must be fully applied. Otherwise it won't be
--       inlined, which will cause a severe performance loss.
--
-- > uniformR     = uniformRange      -- won't be inlined
-- > uniformR a b = uniformRange a b  -- will be inlined
uniformRange :: ( PrimMonad m
                , Integral a, Bounded a, Variate a
                , Integral (Unsigned a), Bounded (Unsigned a), Variate (Unsigned a))
             => (a,a) -> Gen (PrimState m) -> m a
uniformRange :: (a, a) -> Gen (PrimState m) -> m a
uniformRange (a
x1,a
x2) Gen (PrimState m)
g
  | Unsigned a
n Unsigned a -> Unsigned a -> Bool
forall a. Eq a => a -> a -> Bool
== Unsigned a
0    = Gen (PrimState m) -> m a
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g   -- Abuse overflow in unsigned types
  | Bool
otherwise = m a
loop
  where
    -- Allow ranges where x2<x1
    (# a
i, a
j #) | a
x1 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
x2   = (# a
x1, a
x2 #)
               | Bool
otherwise = (# a
x2, a
x1 #)
    n :: Unsigned a
n       = Unsigned a
1 Unsigned a -> Unsigned a -> Unsigned a
forall a. Num a => a -> a -> a
+ a -> a -> Unsigned a
forall a.
(Integral a, Integral (Unsigned a)) =>
a -> a -> Unsigned a
sub a
j a
i
    buckets :: Unsigned a
buckets = Unsigned a
forall a. Bounded a => a
maxBound Unsigned a -> Unsigned a -> Unsigned a
forall a. Integral a => a -> a -> a
`div` Unsigned a
n
    maxN :: Unsigned a
maxN    = Unsigned a
buckets Unsigned a -> Unsigned a -> Unsigned a
forall a. Num a => a -> a -> a
* Unsigned a
n
    loop :: m a
loop    = do Unsigned a
x <- Gen (PrimState m) -> m (Unsigned a)
forall a (m :: * -> *).
(Variate a, PrimMonad m) =>
Gen (PrimState m) -> m a
uniform Gen (PrimState m)
g
                 if Unsigned a
x Unsigned a -> Unsigned a -> Bool
forall a. Ord a => a -> a -> Bool
< Unsigned a
maxN then a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> m a) -> a -> m a
forall a b. (a -> b) -> a -> b
$! a -> Unsigned a -> a
forall a.
(Integral a, Integral (Unsigned a)) =>
a -> Unsigned a -> a
add a
i (Unsigned a
x Unsigned a -> Unsigned a -> Unsigned a
forall a. Integral a => a -> a -> a
`div` Unsigned a
buckets)
                             else m a
loop
{-# INLINE uniformRange #-}

-- | Generate a vector of pseudo-random variates.  This is not
-- necessarily faster than invoking 'uniform' repeatedly in a loop,
-- but it may be more convenient to use in some situations.
uniformVector
  :: (PrimMonad m, Random.StatefulGen g m, Random.Uniform a, Vector v a)
  => g -> Int -> m (v a)
-- NOTE: We use in-place mutation in order to generate vector instead
--       of generateM because latter will go though intermediate list until
--       we're working in IO/ST monad
--
-- See: https://github.com/haskell/vector/issues/208 for details
uniformVector :: g -> Int -> m (v a)
uniformVector g
gen Int
n = do
  Mutable v (PrimState m) a
mu <- Int -> m (Mutable v (PrimState m) a)
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
Int -> m (v (PrimState m) a)
GM.unsafeNew Int
n
  let go :: Int -> m (v a)
go !Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n     = g -> m a
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
Random.uniformM g
gen m a -> (a -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Mutable v (PrimState m) a -> Int -> a -> m ()
forall (m :: * -> *) (v :: * -> * -> *) a.
(PrimMonad m, MVector v a) =>
v (PrimState m) a -> Int -> a -> m ()
GM.unsafeWrite Mutable v (PrimState m) a
mu Int
i m () -> m (v a) -> m (v a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m (v a)
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
            | Bool
otherwise = Mutable v (PrimState m) a -> m (v a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
G.unsafeFreeze Mutable v (PrimState m) a
mu
  Int -> m (v a)
go Int
0
{-# INLINE uniformVector #-}


-- This is default seed for the generator and used when no seed is
-- specified or seed is only partial. It's not known how it was
-- generated but it looks random enough
defaultSeed :: I.Vector Word32
defaultSeed :: Vector Word32
defaultSeed = [Word32] -> Vector Word32
forall a. Unbox a => [a] -> Vector a
I.fromList [
  Word32
0x7042e8b3, Word32
0x06f7f4c5, Word32
0x789ea382, Word32
0x6fb15ad8, Word32
0x54f7a879, Word32
0x0474b184,
  Word32
0xb3f8f692, Word32
0x4114ea35, Word32
0xb6af0230, Word32
0xebb457d2, Word32
0x47693630, Word32
0x15bc0433,
  Word32
0x2e1e5b18, Word32
0xbe91129c, Word32
0xcc0815a0, Word32
0xb1260436, Word32
0xd6f605b1, Word32
0xeaadd777,
  Word32
0x8f59f791, Word32
0xe7149ed9, Word32
0x72d49dd5, Word32
0xd68d9ded, Word32
0xe2a13153, Word32
0x67648eab,
  Word32
0x48d6a1a1, Word32
0xa69ab6d7, Word32
0x236f34ec, Word32
0x4e717a21, Word32
0x9d07553d, Word32
0x6683a701,
  Word32
0x19004315, Word32
0x7b6429c5, Word32
0x84964f99, Word32
0x982eb292, Word32
0x3a8be83e, Word32
0xc1df1845,
  Word32
0x3cf7b527, Word32
0xb66a7d3f, Word32
0xf93f6838, Word32
0x736b1c85, Word32
0x5f0825c1, Word32
0x37e9904b,
  Word32
0x724cd7b3, Word32
0xfdcb7a46, Word32
0xfdd39f52, Word32
0x715506d5, Word32
0xbd1b6637, Word32
0xadabc0c0,
  Word32
0x219037fc, Word32
0x9d71b317, Word32
0x3bec717b, Word32
0xd4501d20, Word32
0xd95ea1c9, Word32
0xbe717202,
  Word32
0xa254bd61, Word32
0xd78a6c5b, Word32
0x043a5b16, Word32
0x0f447a25, Word32
0xf4862a00, Word32
0x48a48b75,
  Word32
0x1e580143, Word32
0xd5b6a11b, Word32
0x6fb5b0a4, Word32
0x5aaf27f9, Word32
0x668bcd0e, Word32
0x3fdf18fd,
  Word32
0x8fdcec4a, Word32
0x5255ce87, Word32
0xa1b24dbf, Word32
0x3ee4c2e1, Word32
0x9087eea2, Word32
0xa4131b26,
  Word32
0x694531a5, Word32
0xa143d867, Word32
0xd9f77c03, Word32
0xf0085918, Word32
0x1e85071c, Word32
0x164d1aba,
  Word32
0xe61abab5, Word32
0xb8b0c124, Word32
0x84899697, Word32
0xea022359, Word32
0x0cc7fa0c, Word32
0xd6499adf,
  Word32
0x746da638, Word32
0xd9e5d200, Word32
0xefb3360b, Word32
0x9426716a, Word32
0xabddf8c2, Word32
0xdd1ed9e4,
  Word32
0x17e1d567, Word32
0xa9a65000, Word32
0x2f37dbc5, Word32
0x9a4b8fd5, Word32
0xaeb22492, Word32
0x0ebe8845,
  Word32
0xd89dd090, Word32
0xcfbb88c6, Word32
0xb1325561, Word32
0x6d811d90, Word32
0x03aa86f4, Word32
0xbddba397,
  Word32
0x0986b9ed, Word32
0x6f4cfc69, Word32
0xc02b43bc, Word32
0xee916274, Word32
0xde7d9659, Word32
0x7d3afd93,
  Word32
0xf52a7095, Word32
0xf21a009c, Word32
0xfd3f795e, Word32
0x98cef25b, Word32
0x6cb3af61, Word32
0x6fa0e310,
  Word32
0x0196d036, Word32
0xbc198bca, Word32
0x15b0412d, Word32
0xde454349, Word32
0x5719472b, Word32
0x8244ebce,
  Word32
0xee61afc6, Word32
0xa60c9cb5, Word32
0x1f4d1fd0, Word32
0xe4fb3059, Word32
0xab9ec0f9, Word32
0x8d8b0255,
  Word32
0x4e7430bf, Word32
0x3a22aa6b, Word32
0x27de22d3, Word32
0x60c4b6e6, Word32
0x0cf61eb3, Word32
0x469a87df,
  Word32
0xa4da1388, Word32
0xf650f6aa, Word32
0x3db87d68, Word32
0xcdb6964c, Word32
0xb2649b6c, Word32
0x6a880fa9,
  Word32
0x1b0c845b, Word32
0xe0af2f28, Word32
0xfc1d5da9, Word32
0xf64878a6, Word32
0x667ca525, Word32
0x2114b1ce,
  Word32
0x2d119ae3, Word32
0x8d29d3bf, Word32
0x1a1b4922, Word32
0x3132980e, Word32
0xd59e4385, Word32
0x4dbd49b8,
  Word32
0x2de0bb05, Word32
0xd6c96598, Word32
0xb4c527c3, Word32
0xb5562afc, Word32
0x61eeb602, Word32
0x05aa192a,
  Word32
0x7d127e77, Word32
0xc719222d, Word32
0xde7cf8db, Word32
0x2de439b8, Word32
0x250b5f1a, Word32
0xd7b21053,
  Word32
0xef6c14a1, Word32
0x2041f80f, Word32
0xc287332e, Word32
0xbb1dbfd3, Word32
0x783bb979, Word32
0x9a2e6327,
  Word32
0x6eb03027, Word32
0x0225fa2f, Word32
0xa319bc89, Word32
0x864112d4, Word32
0xfe990445, Word32
0xe5e2e07c,
  Word32
0xf7c6acb8, Word32
0x1bc92142, Word32
0x12e9b40e, Word32
0x2979282d, Word32
0x05278e70, Word32
0xe160ba4c,
  Word32
0xc1de0909, Word32
0x458b9bf4, Word32
0xbfce9c94, Word32
0xa276f72a, Word32
0x8441597d, Word32
0x67adc2da,
  Word32
0x6162b854, Word32
0x7f9b2f4a, Word32
0x0d995b6b, Word32
0x193b643d, Word32
0x399362b3, Word32
0x8b653a4b,
  Word32
0x1028d2db, Word32
0x2b3df842, Word32
0x6eecafaf, Word32
0x261667e9, Word32
0x9c7e8cda, Word32
0x46063eab,
  Word32
0x7ce7a3a1, Word32
0xadc899c9, Word32
0x017291c4, Word32
0x528d1a93, Word32
0x9a1ee498, Word32
0xbb7d4d43,
  Word32
0x7837f0ed, Word32
0x34a230cc, Word32
0x614a628d, Word32
0xb03f93b8, Word32
0xd72e3b08, Word32
0x604c98db,
  Word32
0x3cfacb79, Word32
0x8b81646a, Word32
0xc0f082fa, Word32
0xd1f92388, Word32
0xe5a91e39, Word32
0xf95c756d,
  Word32
0x1177742f, Word32
0xf8819323, Word32
0x5c060b80, Word32
0x96c1cd8f, Word32
0x47d7b440, Word32
0xbbb84197,
  Word32
0x35f749cc, Word32
0x95b0e132, Word32
0x8d90ad54, Word32
0x5c3f9423, Word32
0x4994005b, Word32
0xb58f53b9,
  Word32
0x32df7348, Word32
0x60f61c29, Word32
0x9eae2f32, Word32
0x85a3d398, Word32
0x3b995dd4, Word32
0x94c5e460,
  Word32
0x8e54b9f3, Word32
0x87bc6e2a, Word32
0x90bbf1ea, Word32
0x55d44719, Word32
0x2cbbfe6e, Word32
0x439d82f0,
  Word32
0x4eb3782d, Word32
0xc3f1e669, Word32
0x61ff8d9e, Word32
0x0909238d, Word32
0xef406165, Word32
0x09c1d762,
  Word32
0x705d184f, Word32
0x188f2cc4, Word32
0x9c5aa12a, Word32
0xc7a5d70e, Word32
0xbc78cb1b, Word32
0x1d26ae62,
  Word32
0x23f96ae3, Word32
0xd456bf32, Word32
0xe4654f55, Word32
0x31462bd8 ]
{-# NOINLINE defaultSeed #-}

-- $references
--
-- * Marsaglia, G. (2003) Seeds for random number generators.
--   /Communications of the ACM/ 46(5):90&#8211;93.
--   <http://doi.acm.org/10.1145/769800.769827>
--
-- * Doornik, J.A. (2007) Conversion of high-period random numbers to
--   floating point.
--   /ACM Transactions on Modeling and Computer Simulation/ 17(1).
--   <http://www.doornik.com/research/randomdouble.pdf>


-- $typehelp
--
-- The functions in this package are deliberately written for
-- flexibility, and will run in both the 'IO' and 'ST' monads.
--
-- This can defeat the compiler's ability to infer a principal type in
-- simple (and common) cases.  For instance, we would like the
-- following to work cleanly:
--
-- > import System.Random.MWC
-- > import Data.Vector.Unboxed
-- >
-- > main = do
-- >   v <- withSystemRandom $ \gen -> uniformVector gen 20
-- >   print (v :: Vector Int)
--
-- Unfortunately, the compiler cannot tell what monad 'uniformVector'
-- should execute in.  The \"fix\" of adding explicit type annotations
-- is not pretty:
--
-- > {-# LANGUAGE ScopedTypeVariables #-}
-- >
-- > import Control.Monad.ST
-- >
-- > main = do
-- >   vs <- withSystemRandom $
-- >         \(gen::GenST s) -> uniformVector gen 20 :: ST s (Vector Int)
-- >   print vs
--
-- As a more readable alternative, this library provides 'asGenST' and
-- 'asGenIO' to constrain the types appropriately.  We can get rid of
-- the explicit type annotations as follows:
--
-- > main = do
-- >   vs <- withSystemRandom . asGenST $ \gen -> uniformVector gen 20
-- >   print (vs :: Vector Int)
--
-- This is almost as compact as the original code that the compiler
-- rejected.



-- $setup
--
-- >>> import Control.Monad
-- >>> import Data.Word
-- >>> import Data.STRef
-- >>> :set -Wno-deprecations


-- NOTE [Carry value]
-- ------------------
-- This is proof of statement:
--
-- > if the carry value is strictly smaller than the multiplicator,
-- > the next carry value is also strictly smaller than the multiplicator.
--
-- Eventhough the proof is written in terms of the actual value of the
-- multiplicator, it holds for any multiplicator value /not/ greater
-- than maxBound 'Word32'
--
--    (In the code, the multiplicator is aa, the carry value is c,
--     the next carry value is c''.)
--
-- So we'll assume that c < aa, and show that c'' < aa :
--
-- by definition, aa = 0x5BCF5AB2, qi <= 0xFFFFFFFF (because it is a 'Word32')
--
-- Then we get following:
--
--    aa*qi <= 0x5BCF5AB200000000 - 0x5BCF5AB2.
--    t     <  0x5BCF5AB200000000 (because t = aa * qi + c and c < 0x5BCF5AB2)
--    t     <= 0x5BCF5AB1FFFFFFFF
--    c'    <  0x5BCF5AB1
--    c''   <  0x5BCF5AB2,
--    c''   < aa, which is what we wanted to prove.