{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnicodeSyntax #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-- -------------------------------------------------------------------------- --
-- |
-- Module: Data.ByteString.Random.PCG
-- Copyright: (c) Lars Kuhtz <lakuhtz@gmail.com> 2017
-- License: MIT
-- Maintainer: lakuhtz@gmail.com
-- Stability: experimental

module Data.ByteString.Random.PCG
( random
, randomGen
) where

import Data.ByteString (ByteString)

import Numeric.Natural (Natural)

import System.Random.PCG (uniform, GenIO, withSystemRandom)

-- internal imports

import Data.ByteString.Random.Internal

-- -------------------------------------------------------------------------- --

instance (g ~ GenIO)  RandomWords g where
    uniformW8 :: g -> IO Word8
uniformW8 = g -> IO Word8
forall a g (m :: * -> *). (Variate a, Generator g m) => g -> m a
uniform
    {-# INLINE uniformW8 #-}
    uniformW64 :: g -> IO Word64
uniformW64 = g -> IO Word64
forall a g (m :: * -> *). (Variate a, Generator g m) => g -> m a
uniform
    {-# INLINE uniformW64 #-}

{-# SPECIALIZE generate  GenIO  Natural  IO ByteString #-}

-- -------------------------------------------------------------------------- --

randomGen
     GenIO
        -- ^ PRNG
     Natural
        -- ^ Length of the result bytestring in bytes
     IO ByteString
randomGen :: GenIO -> Natural -> IO ByteString
randomGen = GenIO -> Natural -> IO ByteString
forall g. RandomWords g => g -> Natural -> IO ByteString
generate
{-# INLINE randomGen #-}

-- $setup
-- >>> import qualified Data.ByteString as B
-- >>> import Test.QuickCheck

-- | Generate a random bytestring of length n. The PRNG is seeded
-- from the system randomness source.
--
-- prop> ioProperty $ ((fromIntegral n ===) . B.length) <$> random n
-- prop> n > 4 ==> ioProperty $ (/=) <$> random n <*> random n
--
random
     Natural
        -- ^ Length of the result bytestring in bytes
     IO ByteString
random :: Natural -> IO ByteString
random Natural
n = (GenIO -> IO ByteString) -> IO ByteString
forall a. (GenIO -> IO a) -> IO a
withSystemRandom ((GenIO -> IO ByteString) -> IO ByteString)
-> (GenIO -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ (GenIO -> Natural -> IO ByteString)
-> Natural -> GenIO -> IO ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip GenIO -> Natural -> IO ByteString
randomGen Natural
n