-- |
-- /SplitMix/ is a splittable pseudorandom number generator (PRNG) that is quite fast.
--
-- This is 32bit variant (original one is 32 bit).
--
-- You __really don't want to use this one__.
--
--  Note: This module supports all GHCs since GHC-7.0.4,
--  but GHC-7.0 and GHC-7.2 have slow implementation, as there
--  are no native 'popCount'.
--
{-# LANGUAGE CPP         #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module System.Random.SplitMix32 (
    SMGen,
    nextWord32,
    nextWord64,
    nextTwoWord32,
    nextInt,
    nextDouble,
    nextFloat,
    nextInteger,
    splitSMGen,
    -- * Generation
    bitmaskWithRejection32,
    bitmaskWithRejection32',
    bitmaskWithRejection64,
    bitmaskWithRejection64',
    -- * Initialisation
    mkSMGen,
    initSMGen,
    newSMGen,
    seedSMGen,
    seedSMGen',
    unseedSMGen,
    ) where

import Data.Bits             (complement, shiftL, shiftR, xor, (.&.), (.|.))
import Data.Bits.Compat
       (countLeadingZeros, finiteBitSize, popCount, zeroBits)
import Data.IORef            (IORef, atomicModifyIORef, newIORef)
import Data.Word             (Word32, Word64)
import System.IO.Unsafe      (unsafePerformIO)

import System.Random.SplitMix.Init

#if defined(__HUGS__) || !MIN_VERSION_base(4,8,0)
import Data.Word (Word)
#endif

#ifndef __HUGS__
import Control.DeepSeq (NFData (..))
#endif

-- $setup
-- >>> import Text.Read (readMaybe)
-- >>> import Data.List (unfoldr)
-- >>> import Text.Printf (printf)

-------------------------------------------------------------------------------
-- Generator
-------------------------------------------------------------------------------

-- | SplitMix generator state.
data SMGen = SMGen {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32 -- seed and gamma; gamma is odd
  deriving Int -> SMGen -> ShowS
[SMGen] -> ShowS
SMGen -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SMGen] -> ShowS
$cshowList :: [SMGen] -> ShowS
show :: SMGen -> String
$cshow :: SMGen -> String
showsPrec :: Int -> SMGen -> ShowS
$cshowsPrec :: Int -> SMGen -> ShowS
Show

#ifndef __HUGS__
instance NFData SMGen where
    rnf :: SMGen -> ()
rnf (SMGen Word32
_ Word32
_) = ()
#endif

-- |
--
-- >>> readMaybe "SMGen 1 1" :: Maybe SMGen
-- Just (SMGen 1 1)
--
-- >>> readMaybe "SMGen 1 2" :: Maybe SMGen
-- Nothing
--
-- >>> readMaybe (show (mkSMGen 42)) :: Maybe SMGen
-- Just (SMGen 142593372 1604540297)
--
instance Read SMGen where
    readsPrec :: Int -> ReadS SMGen
readsPrec Int
d String
r =  forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10) (\String
r0 ->
        [ (Word32 -> Word32 -> SMGen
SMGen Word32
seed Word32
gamma, String
r3)
        | (String
"SMGen", String
r1) <- ReadS String
lex String
r0
        , (Word32
seed, String
r2) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
r1
        , (Word32
gamma, String
r3) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
r2
        , forall a. Integral a => a -> Bool
odd Word32
gamma
        ]) String
r

-------------------------------------------------------------------------------
-- Operations
-------------------------------------------------------------------------------

-- | Generate a 'Word32'.
--
-- >>> take 3 $ map (printf "%x") $ unfoldr (Just . nextWord32) (mkSMGen 1337) :: [String]
-- ["e0cfe722","a6ced0f0","c3a6d889"]
--
nextWord32 :: SMGen -> (Word32, SMGen)
nextWord32 :: SMGen -> (Word32, SMGen)
nextWord32 (SMGen Word32
seed Word32
gamma) = (Word32 -> Word32
mix32 Word32
seed', Word32 -> Word32 -> SMGen
SMGen Word32
seed' Word32
gamma)
  where
    seed' :: Word32
seed' = Word32
seed forall a. Num a => a -> a -> a
+ Word32
gamma

-- | Generate a 'Word64', by generating to 'Word32's.
nextWord64 :: SMGen -> (Word64, SMGen)
nextWord64 :: SMGen -> (Word64, SMGen)
nextWord64 SMGen
s0 = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w0 forall a. Bits a => a -> Int -> a
`shiftL` Int
32 forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w1,  SMGen
s2)
  where
    (Word32
w0, SMGen
s1) = SMGen -> (Word32, SMGen)
nextWord32 SMGen
s0
    (Word32
w1, SMGen
s2) = SMGen -> (Word32, SMGen)
nextWord32 SMGen
s1

-- | Generate two 'Word32'.
nextTwoWord32 :: SMGen -> (Word32, Word32, SMGen)
nextTwoWord32 :: SMGen -> (Word32, Word32, SMGen)
nextTwoWord32 SMGen
s0 = (Word32
w0, Word32
w1, SMGen
s2) where
    (Word32
w0, SMGen
s1) = SMGen -> (Word32, SMGen)
nextWord32 SMGen
s0
    (Word32
w1, SMGen
s2) = SMGen -> (Word32, SMGen)
nextWord32 SMGen
s1

-- | Generate an 'Int'.
nextInt :: SMGen -> (Int, SMGen)
nextInt :: SMGen -> (Int, SMGen)
nextInt SMGen
g | Bool
isBigInt  = (Int, SMGen)
int64
          | Bool
otherwise = (Int, SMGen)
int32
  where
    int32 :: (Int, SMGen)
int32 = case SMGen -> (Word32, SMGen)
nextWord32 SMGen
g of
        (Word32
w, SMGen
g') -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w, SMGen
g')
    int64 :: (Int, SMGen)
int64 = case SMGen -> (Word64, SMGen)
nextWord64 SMGen
g of
        (Word64
w, SMGen
g') -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w, SMGen
g')

isBigInt :: Bool
isBigInt :: Bool
isBigInt = forall b. FiniteBits b => b -> Int
finiteBitSize (forall a. HasCallStack => a
undefined :: Int) forall a. Ord a => a -> a -> Bool
> Int
32

-- | Generate a 'Double' in @[0, 1)@ range.
--
-- >>> take 8 $ map (printf "%0.3f") $ unfoldr (Just . nextDouble) (mkSMGen 1337) :: [String]
-- ["0.878","0.764","0.063","0.845","0.262","0.490","0.176","0.544"]
--
nextDouble :: SMGen -> (Double, SMGen)
nextDouble :: SMGen -> (Double, SMGen)
nextDouble SMGen
g = case SMGen -> (Word64, SMGen)
nextWord64 SMGen
g of
    (Word64
w64, SMGen
g') -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
w64 forall a. Bits a => a -> Int -> a
`shiftR` Int
11) forall a. Num a => a -> a -> a
* Double
doubleUlp, SMGen
g')

-- | Generate a 'Float' in @[0, 1)@ range.
--
-- >>> take 8 $ map (printf "%0.3f") $ unfoldr (Just . nextFloat) (mkSMGen 1337) :: [String]
-- ["0.878","0.652","0.764","0.631","0.063","0.180","0.845","0.645"]
--
nextFloat :: SMGen -> (Float, SMGen)
nextFloat :: SMGen -> (Float, SMGen)
nextFloat SMGen
g = case SMGen -> (Word32, SMGen)
nextWord32 SMGen
g of
    (Word32
w32, SMGen
g') -> (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
w32 forall a. Bits a => a -> Int -> a
`shiftR` Int
8) forall a. Num a => a -> a -> a
* Float
floatUlp, SMGen
g')

-- | Generate an 'Integer' in closed @[x, y]@ range.
nextInteger :: Integer -> Integer -> SMGen -> (Integer, SMGen)
nextInteger :: Integer -> Integer -> SMGen -> (Integer, SMGen)
nextInteger Integer
lo Integer
hi SMGen
g = case forall a. Ord a => a -> a -> Ordering
compare Integer
lo Integer
hi of
    Ordering
LT -> let (Integer
i, SMGen
g') = Integer -> SMGen -> (Integer, SMGen)
nextInteger' (Integer
hi forall a. Num a => a -> a -> a
- Integer
lo) SMGen
g in (Integer
i forall a. Num a => a -> a -> a
+ Integer
lo, SMGen
g')
    Ordering
EQ -> (Integer
lo, SMGen
g)
    Ordering
GT -> let (Integer
i, SMGen
g') = Integer -> SMGen -> (Integer, SMGen)
nextInteger' (Integer
lo forall a. Num a => a -> a -> a
- Integer
hi) SMGen
g in (Integer
i forall a. Num a => a -> a -> a
+ Integer
hi, SMGen
g')

-- invariant: first argument is positive
-- Essentially bitmaskWithRejection but for Integers.
--
nextInteger' :: Integer -> SMGen -> (Integer, SMGen)
nextInteger' :: Integer -> SMGen -> (Integer, SMGen)
nextInteger' Integer
range = SMGen -> (Integer, SMGen)
loop
  where
    leadMask :: Word32
    restDigits :: Word
    (Word32
leadMask, Word
restDigits) = Word -> Integer -> (Word32, Word)
go Word
0 Integer
range where
        go :: Word -> Integer -> (Word32, Word)
        go :: Word -> Integer -> (Word32, Word)
go Word
n Integer
x | Integer
x forall a. Ord a => a -> a -> Bool
< Integer
two32 = (forall a. Bits a => a -> a
complement forall a. Bits a => a
zeroBits forall a. Bits a => a -> Int -> a
`shiftR` forall b. FiniteBits b => b -> Int
countLeadingZeros (forall a. Num a => Integer -> a
fromInteger Integer
x :: Word32), Word
n)
               | Bool
otherwise = Word -> Integer -> (Word32, Word)
go (Word
n forall a. Num a => a -> a -> a
+ Word
1) (Integer
x forall a. Bits a => a -> Int -> a
`shiftR` Int
32)

    generate :: SMGen -> (Integer, SMGen)
    generate :: SMGen -> (Integer, SMGen)
generate SMGen
g0 =
        let (Word32
x, SMGen
g') = SMGen -> (Word32, SMGen)
nextWord32 SMGen
g0
            x' :: Word32
x' = Word32
x forall a. Bits a => a -> a -> a
.&. Word32
leadMask
        in Integer -> Word -> SMGen -> (Integer, SMGen)
go (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x') Word
restDigits SMGen
g'
      where
        go :: Integer -> Word -> SMGen -> (Integer, SMGen)
        go :: Integer -> Word -> SMGen -> (Integer, SMGen)
go Integer
acc Word
0 SMGen
g = Integer
acc seq :: forall a b. a -> b -> b
`seq` (Integer
acc, SMGen
g)
        go Integer
acc Word
n SMGen
g =
            let (Word32
x, SMGen
g') = SMGen -> (Word32, SMGen)
nextWord32 SMGen
g
            in Integer -> Word -> SMGen -> (Integer, SMGen)
go (Integer
acc forall a. Num a => a -> a -> a
* Integer
two32 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
x) (Word
n forall a. Num a => a -> a -> a
- Word
1) SMGen
g'

    loop :: SMGen -> (Integer, SMGen)
loop SMGen
g = let (Integer
x, SMGen
g') = SMGen -> (Integer, SMGen)
generate SMGen
g
             in if Integer
x forall a. Ord a => a -> a -> Bool
> Integer
range
                then SMGen -> (Integer, SMGen)
loop SMGen
g'
                else (Integer
x, SMGen
g')

two32 :: Integer
two32 :: Integer
two32 = Integer
2 forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
32 :: Int)

-------------------------------------------------------------------------------
-- Splitting
-------------------------------------------------------------------------------

-- | Split a generator into a two uncorrelated generators.
splitSMGen :: SMGen -> (SMGen, SMGen)
splitSMGen :: SMGen -> (SMGen, SMGen)
splitSMGen (SMGen Word32
seed Word32
gamma) =
    (Word32 -> Word32 -> SMGen
SMGen Word32
seed'' Word32
gamma, Word32 -> Word32 -> SMGen
SMGen (Word32 -> Word32
mix32 Word32
seed') (Word32 -> Word32
mixGamma Word32
seed''))
  where
    seed' :: Word32
seed'  = Word32
seed forall a. Num a => a -> a -> a
+ Word32
gamma
    seed'' :: Word32
seed'' = Word32
seed' forall a. Num a => a -> a -> a
+ Word32
gamma

-------------------------------------------------------------------------------
-- Algorithm
-------------------------------------------------------------------------------

-- | (1 + sqrt 5) / 2 * (2 ^^ bits)
goldenGamma :: Word32
goldenGamma :: Word32
goldenGamma = Word32
0x9e3779b9

floatUlp :: Float
floatUlp :: Float
floatUlp =  Float
1.0 forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
1 forall a. Bits a => a -> Int -> a
`shiftL` Int
24 :: Word32)

doubleUlp :: Double
doubleUlp :: Double
doubleUlp =  Double
1.0 forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
1 forall a. Bits a => a -> Int -> a
`shiftL` Int
53 :: Word64)

#if defined(__GHCJS__) && defined(OPTIMISED_MIX32)
-- JavaScript Foreign Function Interface
-- https://github.com/ghcjs/ghcjs/blob/master/doc/foreign-function-interface.md

foreign import javascript unsafe
    "var x0 = $1 ^ $1 >>> 16; var x1 = x0 & 0xffff; var x2 = (((x0 >>> 16 & 0xffff) * 0x0000ca6b + x1 * 0x000085eb & 0xffff) << 16) + x1 * 0x0000ca6b; var x3 = x2 ^ x2 >>> 13; var x4 = x3 & 0xffff; var x5 = (((x3 >>> 16 & 0xffff) * 0x0000ae35 + x4 * 0x0000c2b2 & 0xffff) << 16) + x4 * 0x0000ae35; $r = (x5 ^ x5 >>> 16) | 0;"
    mix32 :: Word32 -> Word32

foreign import javascript unsafe
    "var x0 = $1 ^ $1 >>> 16; var x1 = x0 & 0xffff; var x2 = (((x0 >>> 16 & 0xffff) * 0x00006ccb + x1 * 0x000069ad & 0xffff) << 16) + x1 * 0x00006ccb; var x3 = x2 ^ x2 >>> 13; var x4 = x3 & 0xffff; var x5 = (((x3 >>> 16 & 0xffff) * 0x0000b5b3 + x4 * 0x0000cd9a & 0xffff) << 16) + x4 * 0x0000b5b3; $r = (x5 ^ x5 >>> 16) | 0;"
    mix32variant13 :: Word32 -> Word32

#else
mix32 :: Word32 -> Word32
mix32 :: Word32 -> Word32
mix32 Word32
z0 =
   -- MurmurHash3Mixer 32bit
    let z1 :: Word32
z1 = Int -> Word32 -> Word32 -> Word32
shiftXorMultiply Int
16 Word32
0x85ebca6b Word32
z0
        z2 :: Word32
z2 = Int -> Word32 -> Word32 -> Word32
shiftXorMultiply Int
13 Word32
0xc2b2ae35 Word32
z1
        z3 :: Word32
z3 = Int -> Word32 -> Word32
shiftXor Int
16 Word32
z2
    in Word32
z3

-- used only in mixGamma
mix32variant13 :: Word32 -> Word32
mix32variant13 :: Word32 -> Word32
mix32variant13 Word32
z0 =
   -- See avalanche "executable"
    let z1 :: Word32
z1 = Int -> Word32 -> Word32 -> Word32
shiftXorMultiply Int
16 Word32
0x69ad6ccb Word32
z0
        z2 :: Word32
z2 = Int -> Word32 -> Word32 -> Word32
shiftXorMultiply Int
13 Word32
0xcd9ab5b3 Word32
z1
        z3 :: Word32
z3 = Int -> Word32 -> Word32
shiftXor Int
16 Word32
z2
    in Word32
z3

shiftXor :: Int -> Word32 -> Word32
shiftXor :: Int -> Word32 -> Word32
shiftXor Int
n Word32
w = Word32
w forall a. Bits a => a -> a -> a
`xor` (Word32
w forall a. Bits a => a -> Int -> a
`shiftR` Int
n)

shiftXorMultiply :: Int -> Word32 -> Word32 -> Word32
shiftXorMultiply :: Int -> Word32 -> Word32 -> Word32
shiftXorMultiply Int
n Word32
k Word32
w = Int -> Word32 -> Word32
shiftXor Int
n Word32
w forall a. Num a => a -> a -> a
* Word32
k
#endif

mixGamma :: Word32 -> Word32
mixGamma :: Word32 -> Word32
mixGamma Word32
z0 =
    let z1 :: Word32
z1 = Word32 -> Word32
mix32variant13 Word32
z0 forall a. Bits a => a -> a -> a
.|. Word32
1             -- force to be odd
        n :: Int
n  = forall a. Bits a => a -> Int
popCount (Word32
z1 forall a. Bits a => a -> a -> a
`xor` (Word32
z1 forall a. Bits a => a -> Int -> a
`shiftR` Int
1))
    -- see: http://www.pcg-random.org/posts/bugs-in-splitmix.html
    -- let's trust the text of the paper, not the code.
    in if Int
n forall a. Ord a => a -> a -> Bool
>= Int
12
        then Word32
z1
        else Word32
z1 forall a. Bits a => a -> a -> a
`xor` Word32
0xaaaaaaaa

-------------------------------------------------------------------------------
-- Generation
-------------------------------------------------------------------------------

-- | /Bitmask with rejection/ method of generating subrange of 'Word32'.
--
-- @bitmaskWithRejection32 w32@ generates random numbers in closed-open
-- range of @[0, w32)@.
--
bitmaskWithRejection32 :: Word32 -> SMGen -> (Word32, SMGen)
bitmaskWithRejection32 :: Word32 -> SMGen -> (Word32, SMGen)
bitmaskWithRejection32 Word32
0 = forall a. HasCallStack => String -> a
error String
"bitmaskWithRejection32 0"
bitmaskWithRejection32 Word32
n = Word32 -> SMGen -> (Word32, SMGen)
bitmaskWithRejection32' (Word32
n forall a. Num a => a -> a -> a
- Word32
1)
{-# INLINEABLE bitmaskWithRejection32 #-}

-- | /Bitmask with rejection/ method of generating subrange of 'Word64'.
--
-- @bitmaskWithRejection64 w64@ generates random numbers in closed-open
-- range of @[0, w64)@.
--
-- >>> take 20 $ unfoldr (Just . bitmaskWithRejection64 5) (mkSMGen 1337)
-- [0,2,4,2,1,4,2,4,2,2,3,0,3,2,2,2,3,1,2,2]
--
bitmaskWithRejection64 :: Word64 -> SMGen -> (Word64, SMGen)
bitmaskWithRejection64 :: Word64 -> SMGen -> (Word64, SMGen)
bitmaskWithRejection64 Word64
0 = forall a. HasCallStack => String -> a
error String
"bitmaskWithRejection64 0"
bitmaskWithRejection64 Word64
n = Word64 -> SMGen -> (Word64, SMGen)
bitmaskWithRejection64' (Word64
n forall a. Num a => a -> a -> a
- Word64
1)
{-# INLINEABLE bitmaskWithRejection64 #-}

-- | /Bitmask with rejection/ method of generating subrange of 'Word32'.
--
-- @bitmaskWithRejection32' w32@ generates random numbers in closed-closed
-- range of @[0, w32]@.
--
-- @since 0.0.4
bitmaskWithRejection32' :: Word32 -> SMGen -> (Word32, SMGen)
bitmaskWithRejection32' :: Word32 -> SMGen -> (Word32, SMGen)
bitmaskWithRejection32' Word32
range = SMGen -> (Word32, SMGen)
go where
    mask :: Word32
mask = forall a. Bits a => a -> a
complement forall a. Bits a => a
zeroBits forall a. Bits a => a -> Int -> a
`shiftR` forall b. FiniteBits b => b -> Int
countLeadingZeros (Word32
range forall a. Bits a => a -> a -> a
.|. Word32
1)
    go :: SMGen -> (Word32, SMGen)
go SMGen
g = let (Word32
x, SMGen
g') = SMGen -> (Word32, SMGen)
nextWord32 SMGen
g
               x' :: Word32
x' = Word32
x forall a. Bits a => a -> a -> a
.&. Word32
mask
           in if Word32
x' forall a. Ord a => a -> a -> Bool
> Word32
range
              then SMGen -> (Word32, SMGen)
go SMGen
g'
              else (Word32
x', SMGen
g')
{-# INLINEABLE bitmaskWithRejection32' #-}

-- | /Bitmask with rejection/ method of generating subrange of 'Word64'.
--
-- @bitmaskWithRejection64' w64@ generates random numbers in closed-closed
-- range of @[0, w64]@.
--
-- >>> take 20 $ unfoldr (Just . bitmaskWithRejection64' 5) (mkSMGen 1337)
-- [0,2,4,2,1,4,2,4,5,5,2,2,5,3,5,0,3,2,2,2]
--
-- @since 0.0.4
bitmaskWithRejection64' :: Word64 -> SMGen -> (Word64, SMGen)
bitmaskWithRejection64' :: Word64 -> SMGen -> (Word64, SMGen)
bitmaskWithRejection64' Word64
range = SMGen -> (Word64, SMGen)
go where
    mask :: Word64
mask = forall a. Bits a => a -> a
complement forall a. Bits a => a
zeroBits forall a. Bits a => a -> Int -> a
`shiftR` forall b. FiniteBits b => b -> Int
countLeadingZeros (Word64
range forall a. Bits a => a -> a -> a
.|. Word64
1)
    go :: SMGen -> (Word64, SMGen)
go SMGen
g = let (Word64
x, SMGen
g') = SMGen -> (Word64, SMGen)
nextWord64 SMGen
g
               x' :: Word64
x' = Word64
x forall a. Bits a => a -> a -> a
.&. Word64
mask
           in if Word64
x' forall a. Ord a => a -> a -> Bool
> Word64
range
              then SMGen -> (Word64, SMGen)
go SMGen
g'
              else (Word64
x', SMGen
g')
{-# INLINEABLE bitmaskWithRejection64' #-}

-------------------------------------------------------------------------------
-- Initialisation
-------------------------------------------------------------------------------

-- | Create 'SMGen' using seed and gamma.
--
-- >>> seedSMGen 2 2
-- SMGen 2 3
--
seedSMGen
    :: Word32 -- ^ seed
    -> Word32 -- ^ gamma
    -> SMGen
seedSMGen :: Word32 -> Word32 -> SMGen
seedSMGen Word32
seed Word32
gamma = Word32 -> Word32 -> SMGen
SMGen Word32
seed (Word32
gamma forall a. Bits a => a -> a -> a
.|. Word32
1)

-- | Like 'seedSMGen' but takes a pair.
seedSMGen' :: (Word32, Word32) -> SMGen
seedSMGen' :: (Word32, Word32) -> SMGen
seedSMGen' = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Word32 -> Word32 -> SMGen
seedSMGen

-- | Extract current state of 'SMGen'.
unseedSMGen :: SMGen -> (Word32, Word32)
unseedSMGen :: SMGen -> (Word32, Word32)
unseedSMGen (SMGen Word32
seed Word32
gamma) = (Word32
seed, Word32
gamma)

-- | Preferred way to deterministically construct 'SMGen'.
--
-- >>> mkSMGen 42
-- SMGen 142593372 1604540297
--
mkSMGen :: Word32 -> SMGen
mkSMGen :: Word32 -> SMGen
mkSMGen Word32
s = Word32 -> Word32 -> SMGen
SMGen (Word32 -> Word32
mix32 Word32
s) (Word32 -> Word32
mixGamma (Word32
s forall a. Num a => a -> a -> a
+ Word32
goldenGamma))

-- | Initialize 'SMGen' using entropy available on the system (time, ...)
initSMGen :: IO SMGen
initSMGen :: IO SMGen
initSMGen = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> SMGen
mkSMGen IO Word32
initialSeed'

-- | Derive a new generator instance from the global 'SMGen' using 'splitSMGen'.
newSMGen :: IO SMGen
newSMGen :: IO SMGen
newSMGen = forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef IORef SMGen
theSMGen SMGen -> (SMGen, SMGen)
splitSMGen

theSMGen :: IORef SMGen
theSMGen :: IORef SMGen
theSMGen = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ IO SMGen
initSMGen forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. a -> IO (IORef a)
newIORef
{-# NOINLINE theSMGen #-}

initialSeed' :: IO Word32
initialSeed' :: IO Word32
initialSeed' = do
    Word64
w64 <- IO Word64
initialSeed
    forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bits a => a -> Int -> a
shiftR Word64
w64 Int
32) forall a. Bits a => a -> a -> a
`xor` forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w64)