{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Crypto.RNG
(
module Crypto.RNG.Class
, CryptoRNGT
, mapCryptoRNGT
, runCryptoRNGT
, withCryptoRNGState
, CryptoRNGState
, newCryptoRNGState
, newCryptoRNGStateSized
, randomBytesIO
) where
import Control.Applicative
import Control.Concurrent
import Control.Monad
import Control.Monad.Base
import Control.Monad.Catch
import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.Trans.Control
import Data.Bits
import Data.ByteString (ByteString)
import System.Entropy
import qualified Data.ByteString as BS
import qualified Data.ByteString.Short as SBS
import qualified System.Random.Stateful as R
import Crypto.RNG.Class
newtype CryptoRNGState = CryptoRNGState (MVar Buffer)
data Buffer = Buffer
{ Buffer -> Int
maxSize :: !Int
, Buffer -> ByteString
bytes :: !BS.ByteString
}
instance R.StatefulGen CryptoRNGState IO where
uniformWord8 :: CryptoRNGState -> IO Word8
uniformWord8 CryptoRNGState
st = ByteString -> Word8
forall a. (Bits a, Integral a) => ByteString -> a
mkWord (ByteString -> Word8) -> IO ByteString -> IO Word8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
1 CryptoRNGState
st
uniformWord16 :: CryptoRNGState -> IO Word16
uniformWord16 CryptoRNGState
st = ByteString -> Word16
forall a. (Bits a, Integral a) => ByteString -> a
mkWord (ByteString -> Word16) -> IO ByteString -> IO Word16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
2 CryptoRNGState
st
uniformWord32 :: CryptoRNGState -> IO Word32
uniformWord32 CryptoRNGState
st = ByteString -> Word32
forall a. (Bits a, Integral a) => ByteString -> a
mkWord (ByteString -> Word32) -> IO ByteString -> IO Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
4 CryptoRNGState
st
uniformWord64 :: CryptoRNGState -> IO Word64
uniformWord64 CryptoRNGState
st = ByteString -> Word64
forall a. (Bits a, Integral a) => ByteString -> a
mkWord (ByteString -> Word64) -> IO ByteString -> IO Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
8 CryptoRNGState
st
uniformShortByteString :: Int -> CryptoRNGState -> IO ShortByteString
uniformShortByteString Int
n CryptoRNGState
st = ByteString -> ShortByteString
SBS.toShort (ByteString -> ShortByteString)
-> IO ByteString -> IO ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
n CryptoRNGState
st
mkWord :: (Bits a, Integral a) => ByteString -> a
mkWord :: ByteString -> a
mkWord ByteString
bs = (a -> Word8 -> a) -> a -> ByteString -> a
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BS.foldl' (\a
acc Word8
w -> a -> Int -> a
forall a. Bits a => a -> Int -> a
shiftL a
acc Int
8 a -> a -> a
forall a. Bits a => a -> a -> a
.|. Word8 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w) a
0 ByteString
bs
newCryptoRNGState :: MonadIO m => m CryptoRNGState
newCryptoRNGState :: m CryptoRNGState
newCryptoRNGState = Int -> m CryptoRNGState
forall (m :: * -> *). MonadIO m => Int -> m CryptoRNGState
newCryptoRNGStateSized (Int -> m CryptoRNGState) -> Int -> m CryptoRNGState
forall a b. (a -> b) -> a -> b
$ Int
32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1024
newCryptoRNGStateSized
:: MonadIO m
=> Int
-> m CryptoRNGState
newCryptoRNGStateSized :: Int -> m CryptoRNGState
newCryptoRNGStateSized Int
bufferSize = IO CryptoRNGState -> m CryptoRNGState
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CryptoRNGState -> m CryptoRNGState)
-> IO CryptoRNGState -> m CryptoRNGState
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
bufferSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"Buffer size must be larger than 0"
MVar Buffer -> CryptoRNGState
CryptoRNGState (MVar Buffer -> CryptoRNGState)
-> IO (MVar Buffer) -> IO CryptoRNGState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Buffer -> IO (MVar Buffer)
forall a. a -> IO (MVar a)
newMVar (Int -> ByteString -> Buffer
Buffer Int
bufferSize ByteString
BS.empty)
randomBytesIO :: Int -> CryptoRNGState -> IO ByteString
randomBytesIO :: Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
n (CryptoRNGState MVar Buffer
rng) = MVar Buffer -> (Buffer -> IO (Buffer, ByteString)) -> IO ByteString
forall a b. MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar MVar Buffer
rng ((Buffer -> IO (Buffer, ByteString)) -> IO ByteString)
-> (Buffer -> IO (Buffer, ByteString)) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Buffer
buf -> do
([ByteString]
rs, Buffer
newBuf) <- Buffer -> Int -> [ByteString] -> IO ([ByteString], Buffer)
generateBytes Buffer
buf Int
n []
(Buffer, ByteString) -> IO (Buffer, ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Buffer
newBuf, [ByteString] -> ByteString
BS.concat [ByteString]
rs)
generateBytes
:: Buffer
-> Int
-> [BS.ByteString]
-> IO ([BS.ByteString], Buffer)
generateBytes :: Buffer -> Int -> [ByteString] -> IO ([ByteString], Buffer)
generateBytes Buffer
buf Int
n [ByteString]
acc = do
(ByteString
r, ByteString
newBytes) <- Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
n (ByteString -> (ByteString, ByteString))
-> IO ByteString -> IO (ByteString, ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> if ByteString -> Bool
BS.null (Buffer -> ByteString
bytes Buffer
buf)
then Int -> IO ByteString
getEntropy (Buffer -> Int
maxSize Buffer
buf)
else ByteString -> IO ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Buffer -> ByteString
bytes Buffer
buf)
let newBuf :: Buffer
newBuf = Buffer
buf { bytes :: ByteString
bytes = ByteString
newBytes }
k :: Int
k = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
BS.length ByteString
r
Buffer
newBuf Buffer -> IO ([ByteString], Buffer) -> IO ([ByteString], Buffer)
`seq` if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0
then ([ByteString], Buffer) -> IO ([ByteString], Buffer)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString
r ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
acc, Buffer
newBuf)
else Buffer -> Int -> [ByteString] -> IO ([ByteString], Buffer)
generateBytes Buffer
newBuf Int
k (ByteString
r ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
acc)
newtype CryptoRNGT m a = CryptoRNGT { CryptoRNGT m a -> ReaderT CryptoRNGState m a
unCryptoRNGT :: ReaderT CryptoRNGState m a }
deriving ( Applicative (CryptoRNGT m)
CryptoRNGT m a
Applicative (CryptoRNGT m)
-> (forall a. CryptoRNGT m a)
-> (forall a. CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a)
-> (forall a. CryptoRNGT m a -> CryptoRNGT m [a])
-> (forall a. CryptoRNGT m a -> CryptoRNGT m [a])
-> Alternative (CryptoRNGT m)
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
CryptoRNGT m a -> CryptoRNGT m [a]
CryptoRNGT m a -> CryptoRNGT m [a]
forall a. CryptoRNGT m a
forall a. CryptoRNGT m a -> CryptoRNGT m [a]
forall a. CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
forall (f :: * -> *).
Applicative f
-> (forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
forall (m :: * -> *). Alternative m => Applicative (CryptoRNGT m)
forall (m :: * -> *) a. Alternative m => CryptoRNGT m a
forall (m :: * -> *) a.
Alternative m =>
CryptoRNGT m a -> CryptoRNGT m [a]
forall (m :: * -> *) a.
Alternative m =>
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
many :: CryptoRNGT m a -> CryptoRNGT m [a]
$cmany :: forall (m :: * -> *) a.
Alternative m =>
CryptoRNGT m a -> CryptoRNGT m [a]
some :: CryptoRNGT m a -> CryptoRNGT m [a]
$csome :: forall (m :: * -> *) a.
Alternative m =>
CryptoRNGT m a -> CryptoRNGT m [a]
<|> :: CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
$c<|> :: forall (m :: * -> *) a.
Alternative m =>
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
empty :: CryptoRNGT m a
$cempty :: forall (m :: * -> *) a. Alternative m => CryptoRNGT m a
$cp1Alternative :: forall (m :: * -> *). Alternative m => Applicative (CryptoRNGT m)
Alternative, Functor (CryptoRNGT m)
a -> CryptoRNGT m a
Functor (CryptoRNGT m)
-> (forall a. a -> CryptoRNGT m a)
-> (forall a b.
CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b)
-> (forall a b c.
(a -> b -> c)
-> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c)
-> (forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b)
-> (forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a)
-> Applicative (CryptoRNGT m)
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a
CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
(a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c
forall a. a -> CryptoRNGT m a
forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a
forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
forall a b.
CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
forall a b c.
(a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *). Applicative m => Functor (CryptoRNGT m)
forall (m :: * -> *) a. Applicative m => a -> CryptoRNGT m a
forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a
forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c
<* :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m a
*> :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
liftA2 :: (a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m c
<*> :: CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
CryptoRNGT m (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
pure :: a -> CryptoRNGT m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> CryptoRNGT m a
$cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (CryptoRNGT m)
Applicative, a -> CryptoRNGT m b -> CryptoRNGT m a
(a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
(forall a b. (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b)
-> (forall a b. a -> CryptoRNGT m b -> CryptoRNGT m a)
-> Functor (CryptoRNGT m)
forall a b. a -> CryptoRNGT m b -> CryptoRNGT m a
forall a b. (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
forall (m :: * -> *) a b.
Functor m =>
a -> CryptoRNGT m b -> CryptoRNGT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CryptoRNGT m b -> CryptoRNGT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> CryptoRNGT m b -> CryptoRNGT m a
fmap :: (a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> CryptoRNGT m a -> CryptoRNGT m b
Functor, Applicative (CryptoRNGT m)
a -> CryptoRNGT m a
Applicative (CryptoRNGT m)
-> (forall a b.
CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b)
-> (forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b)
-> (forall a. a -> CryptoRNGT m a)
-> Monad (CryptoRNGT m)
CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
forall a. a -> CryptoRNGT m a
forall a b. CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
forall a b.
CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b
forall (m :: * -> *). Monad m => Applicative (CryptoRNGT m)
forall (m :: * -> *) a. Monad m => a -> CryptoRNGT m a
forall (m :: * -> *) a b.
Monad m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
forall (m :: * -> *) a b.
Monad m =>
CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> CryptoRNGT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> CryptoRNGT m a
>> :: CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
CryptoRNGT m a -> CryptoRNGT m b -> CryptoRNGT m b
>>= :: CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
CryptoRNGT m a -> (a -> CryptoRNGT m b) -> CryptoRNGT m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (CryptoRNGT m)
Monad, Monad (CryptoRNGT m)
Monad (CryptoRNGT m)
-> (forall a. [Char] -> CryptoRNGT m a) -> MonadFail (CryptoRNGT m)
[Char] -> CryptoRNGT m a
forall a. [Char] -> CryptoRNGT m a
forall (m :: * -> *).
Monad m -> (forall a. [Char] -> m a) -> MonadFail m
forall (m :: * -> *). MonadFail m => Monad (CryptoRNGT m)
forall (m :: * -> *) a. MonadFail m => [Char] -> CryptoRNGT m a
fail :: [Char] -> CryptoRNGT m a
$cfail :: forall (m :: * -> *) a. MonadFail m => [Char] -> CryptoRNGT m a
$cp1MonadFail :: forall (m :: * -> *). MonadFail m => Monad (CryptoRNGT m)
MonadFail, Monad (CryptoRNGT m)
Alternative (CryptoRNGT m)
CryptoRNGT m a
Alternative (CryptoRNGT m)
-> Monad (CryptoRNGT m)
-> (forall a. CryptoRNGT m a)
-> (forall a. CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a)
-> MonadPlus (CryptoRNGT m)
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
forall a. CryptoRNGT m a
forall a. CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
forall (m :: * -> *).
Alternative m
-> Monad m
-> (forall a. m a)
-> (forall a. m a -> m a -> m a)
-> MonadPlus m
forall (m :: * -> *). MonadPlus m => Monad (CryptoRNGT m)
forall (m :: * -> *). MonadPlus m => Alternative (CryptoRNGT m)
forall (m :: * -> *) a. MonadPlus m => CryptoRNGT m a
forall (m :: * -> *) a.
MonadPlus m =>
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
mplus :: CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
$cmplus :: forall (m :: * -> *) a.
MonadPlus m =>
CryptoRNGT m a -> CryptoRNGT m a -> CryptoRNGT m a
mzero :: CryptoRNGT m a
$cmzero :: forall (m :: * -> *) a. MonadPlus m => CryptoRNGT m a
$cp2MonadPlus :: forall (m :: * -> *). MonadPlus m => Monad (CryptoRNGT m)
$cp1MonadPlus :: forall (m :: * -> *). MonadPlus m => Alternative (CryptoRNGT m)
MonadPlus
, MonadError e, Monad (CryptoRNGT m)
Monad (CryptoRNGT m)
-> (forall a. IO a -> CryptoRNGT m a) -> MonadIO (CryptoRNGT m)
IO a -> CryptoRNGT m a
forall a. IO a -> CryptoRNGT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (CryptoRNGT m)
forall (m :: * -> *) a. MonadIO m => IO a -> CryptoRNGT m a
liftIO :: IO a -> CryptoRNGT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> CryptoRNGT m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (CryptoRNGT m)
MonadIO, MonadBase b, MonadBaseControl b
, Monad (CryptoRNGT m)
e -> CryptoRNGT m a
Monad (CryptoRNGT m)
-> (forall e a. Exception e => e -> CryptoRNGT m a)
-> MonadThrow (CryptoRNGT m)
forall e a. Exception e => e -> CryptoRNGT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (CryptoRNGT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> CryptoRNGT m a
throwM :: e -> CryptoRNGT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> CryptoRNGT m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (CryptoRNGT m)
MonadThrow, MonadThrow (CryptoRNGT m)
MonadThrow (CryptoRNGT m)
-> (forall e a.
Exception e =>
CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a)
-> MonadCatch (CryptoRNGT m)
CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a
forall e a.
Exception e =>
CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall (m :: * -> *). MonadCatch m => MonadThrow (CryptoRNGT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a
catch :: CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
CryptoRNGT m a -> (e -> CryptoRNGT m a) -> CryptoRNGT m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (CryptoRNGT m)
MonadCatch, MonadCatch (CryptoRNGT m)
MonadCatch (CryptoRNGT m)
-> (forall b.
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b)
-> (forall b.
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b)
-> (forall a b c.
CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c))
-> MonadMask (CryptoRNGT m)
CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c)
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
forall b.
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
forall a b c.
CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c)
forall (m :: * -> *).
MonadCatch m
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall b. ((forall a. m a -> m a) -> m b) -> m b)
-> (forall a b c.
m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c))
-> MonadMask m
forall (m :: * -> *). MonadMask m => MonadCatch (CryptoRNGT m)
forall (m :: * -> *) b.
MonadMask m =>
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
forall (m :: * -> *) a b c.
MonadMask m =>
CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c)
generalBracket :: CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c)
$cgeneralBracket :: forall (m :: * -> *) a b c.
MonadMask m =>
CryptoRNGT m a
-> (a -> ExitCase b -> CryptoRNGT m c)
-> (a -> CryptoRNGT m b)
-> CryptoRNGT m (b, c)
uninterruptibleMask :: ((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
$cuninterruptibleMask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
mask :: ((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
$cmask :: forall (m :: * -> *) b.
MonadMask m =>
((forall a. CryptoRNGT m a -> CryptoRNGT m a) -> CryptoRNGT m b)
-> CryptoRNGT m b
$cp1MonadMask :: forall (m :: * -> *). MonadMask m => MonadCatch (CryptoRNGT m)
MonadMask
, m a -> CryptoRNGT m a
(forall (m :: * -> *) a. Monad m => m a -> CryptoRNGT m a)
-> MonadTrans CryptoRNGT
forall (m :: * -> *) a. Monad m => m a -> CryptoRNGT m a
forall (t :: (* -> *) -> * -> *).
(forall (m :: * -> *) a. Monad m => m a -> t m a) -> MonadTrans t
lift :: m a -> CryptoRNGT m a
$clift :: forall (m :: * -> *) a. Monad m => m a -> CryptoRNGT m a
MonadTrans, MonadTrans CryptoRNGT
m (StT CryptoRNGT a) -> CryptoRNGT m a
MonadTrans CryptoRNGT
-> (forall (m :: * -> *) a.
Monad m =>
(Run CryptoRNGT -> m a) -> CryptoRNGT m a)
-> (forall (m :: * -> *) a.
Monad m =>
m (StT CryptoRNGT a) -> CryptoRNGT m a)
-> MonadTransControl CryptoRNGT
(Run CryptoRNGT -> m a) -> CryptoRNGT m a
forall (m :: * -> *) a.
Monad m =>
m (StT CryptoRNGT a) -> CryptoRNGT m a
forall (m :: * -> *) a.
Monad m =>
(Run CryptoRNGT -> m a) -> CryptoRNGT m a
forall (t :: (* -> *) -> * -> *).
MonadTrans t
-> (forall (m :: * -> *) a. Monad m => (Run t -> m a) -> t m a)
-> (forall (m :: * -> *) a. Monad m => m (StT t a) -> t m a)
-> MonadTransControl t
restoreT :: m (StT CryptoRNGT a) -> CryptoRNGT m a
$crestoreT :: forall (m :: * -> *) a.
Monad m =>
m (StT CryptoRNGT a) -> CryptoRNGT m a
liftWith :: (Run CryptoRNGT -> m a) -> CryptoRNGT m a
$cliftWith :: forall (m :: * -> *) a.
Monad m =>
(Run CryptoRNGT -> m a) -> CryptoRNGT m a
$cp1MonadTransControl :: MonadTrans CryptoRNGT
MonadTransControl
)
mapCryptoRNGT :: (m a -> n b) -> CryptoRNGT m a -> CryptoRNGT n b
mapCryptoRNGT :: (m a -> n b) -> CryptoRNGT m a -> CryptoRNGT n b
mapCryptoRNGT m a -> n b
f CryptoRNGT m a
m = (CryptoRNGState -> n b) -> CryptoRNGT n b
forall (m :: * -> *) a. (CryptoRNGState -> m a) -> CryptoRNGT m a
withCryptoRNGState ((CryptoRNGState -> n b) -> CryptoRNGT n b)
-> (CryptoRNGState -> n b) -> CryptoRNGT n b
forall a b. (a -> b) -> a -> b
$ \CryptoRNGState
rng -> m a -> n b
f (CryptoRNGState -> CryptoRNGT m a -> m a
forall (m :: * -> *) a. CryptoRNGState -> CryptoRNGT m a -> m a
runCryptoRNGT CryptoRNGState
rng CryptoRNGT m a
m)
runCryptoRNGT :: CryptoRNGState -> CryptoRNGT m a -> m a
runCryptoRNGT :: CryptoRNGState -> CryptoRNGT m a -> m a
runCryptoRNGT CryptoRNGState
rng CryptoRNGT m a
m = ReaderT CryptoRNGState m a -> CryptoRNGState -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (CryptoRNGT m a -> ReaderT CryptoRNGState m a
forall (m :: * -> *) a.
CryptoRNGT m a -> ReaderT CryptoRNGState m a
unCryptoRNGT CryptoRNGT m a
m) CryptoRNGState
rng
withCryptoRNGState :: (CryptoRNGState -> m a) -> CryptoRNGT m a
withCryptoRNGState :: (CryptoRNGState -> m a) -> CryptoRNGT m a
withCryptoRNGState = ReaderT CryptoRNGState m a -> CryptoRNGT m a
forall (m :: * -> *) a.
ReaderT CryptoRNGState m a -> CryptoRNGT m a
CryptoRNGT (ReaderT CryptoRNGState m a -> CryptoRNGT m a)
-> ((CryptoRNGState -> m a) -> ReaderT CryptoRNGState m a)
-> (CryptoRNGState -> m a)
-> CryptoRNGT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CryptoRNGState -> m a) -> ReaderT CryptoRNGState m a
forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT
instance MonadIO m => CryptoRNG (CryptoRNGT m) where
randomBytes :: Int -> CryptoRNGT m ByteString
randomBytes Int
n = ReaderT CryptoRNGState m CryptoRNGState
-> CryptoRNGT m CryptoRNGState
forall (m :: * -> *) a.
ReaderT CryptoRNGState m a -> CryptoRNGT m a
CryptoRNGT ReaderT CryptoRNGState m CryptoRNGState
forall r (m :: * -> *). MonadReader r m => m r
ask CryptoRNGT m CryptoRNGState
-> (CryptoRNGState -> CryptoRNGT m ByteString)
-> CryptoRNGT m ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO ByteString -> CryptoRNGT m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> CryptoRNGT m ByteString)
-> (CryptoRNGState -> IO ByteString)
-> CryptoRNGState
-> CryptoRNGT m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CryptoRNGState -> IO ByteString
randomBytesIO Int
n
random :: CryptoRNGT m a
random = ReaderT CryptoRNGState m CryptoRNGState
-> CryptoRNGT m CryptoRNGState
forall (m :: * -> *) a.
ReaderT CryptoRNGState m a -> CryptoRNGT m a
CryptoRNGT ReaderT CryptoRNGState m CryptoRNGState
forall r (m :: * -> *). MonadReader r m => m r
ask CryptoRNGT m CryptoRNGState
-> (CryptoRNGState -> CryptoRNGT m a) -> CryptoRNGT m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO a -> CryptoRNGT m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> CryptoRNGT m a)
-> (CryptoRNGState -> IO a) -> CryptoRNGState -> CryptoRNGT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CryptoRNGState -> IO a
forall a g (m :: * -> *). (Uniform a, StatefulGen g m) => g -> m a
R.uniformM
randomR :: (a, a) -> CryptoRNGT m a
randomR (a, a)
bounds = ReaderT CryptoRNGState m CryptoRNGState
-> CryptoRNGT m CryptoRNGState
forall (m :: * -> *) a.
ReaderT CryptoRNGState m a -> CryptoRNGT m a
CryptoRNGT ReaderT CryptoRNGState m CryptoRNGState
forall r (m :: * -> *). MonadReader r m => m r
ask CryptoRNGT m CryptoRNGState
-> (CryptoRNGState -> CryptoRNGT m a) -> CryptoRNGT m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO a -> CryptoRNGT m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> CryptoRNGT m a)
-> (CryptoRNGState -> IO a) -> CryptoRNGState -> CryptoRNGT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a, a) -> CryptoRNGState -> IO a
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
R.uniformRM (a, a)
bounds