Maintainer | Thomas.DuBuisson@gmail.com |
---|---|
Stability | beta |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Much like the MonadRandom package (Control.Monad.Random), this module provides plumbing for the CryptoRandomGen generators.
- class CRandom a where
- class CRandomR a where
- class (ContainsGenError e, MonadError e m) => MonadCRandom e m where
- class (ContainsGenError e, MonadError e m) => MonadCRandomR e m where
- class ContainsGenError e where
- newtype CRandT g e m a = CRandT {}
- type CRand g e = CRandT g e Identity
- runCRandT :: ContainsGenError e => CRandT g e m a -> g -> m (Either e (a, g))
- evalCRandT :: (ContainsGenError e, Monad m) => CRandT g e m a -> g -> m (Either e a)
- runCRand :: ContainsGenError e => CRand g e a -> g -> Either e (a, g)
- evalCRand :: CRand g GenError a -> g -> Either GenError a
- newGenCRand :: (CryptoRandomGen g, MonadCRandom GenError m, Functor m) => m g
- liftCRand :: (g -> Either e (a, g)) -> CRand g e a
- liftCRandT :: Monad m => (g -> Either e (a, g)) -> CRandT g e m a
- module Crypto.Random
Documentation
class CRandom a where Source #
CRandom a
is much like the Random
class from the System.Random module in the "random" package.
The main difference is CRandom builds on "crypto-api"'s CryptoRandomGen
, so it allows
explicit failure.
crandomR (low,high) g
as typically instantiated will generate a value between
[low, high] inclusively, swapping the pair if high < low.
Provided instances for crandom g
generates randoms between the bounds and between +/- 2^256
for Integer.
The crandomR
function has degraded (theoretically unbounded, probabilistically decent) performance
the closer your range size (high - low) is to 2^n (from the top).
crandom :: CryptoRandomGen g => g -> Either GenError (a, g) Source #
crandoms :: CryptoRandomGen g => g -> [a] Source #
class CRandomR a where Source #
crandomR :: CryptoRandomGen g => (a, a) -> g -> Either GenError (a, g) Source #
crandomRs :: CryptoRandomGen g => (a, a) -> g -> [a] Source #
class (ContainsGenError e, MonadError e m) => MonadCRandom e m where Source #
MonadCRandom m
represents a monad that can produce
random values (or fail with a GenError
). It is suggested
you use the CRandT
transformer in your monad stack.
getCRandom :: CRandom a => m a Source #
getBytes :: Int -> m ByteString Source #
getBytesWithEntropy :: Int -> ByteString -> m ByteString Source #
doReseed :: ByteString -> m () Source #
(Monoid w, MonadCRandom e m) => MonadCRandom e (WriterT w m) Source # | |
(Monoid w, MonadCRandom e m) => MonadCRandom e (WriterT w m) Source # | |
MonadCRandom e m => MonadCRandom e (StateT s m) Source # | |
MonadCRandom e m => MonadCRandom e (StateT s m) Source # | |
(ContainsGenError e, Monad m, CryptoRandomGen g) => MonadCRandom e (CRandT g e m) Source # | |
MonadCRandom e m => MonadCRandom e (ReaderT * r m) Source # | |
(Monoid w, MonadCRandom e m) => MonadCRandom e (RWST r w s m) Source # | |
(Monoid w, MonadCRandom e m) => MonadCRandom e (RWST r w s m) Source # | |
class (ContainsGenError e, MonadError e m) => MonadCRandomR e m where Source #
getCRandomR :: CRandomR a => (a, a) -> m a Source #
(MonadCRandomR e m, Monoid w) => MonadCRandomR e (WriterT w m) Source # | |
(MonadCRandomR e m, Monoid w) => MonadCRandomR e (WriterT w m) Source # | |
MonadCRandomR e m => MonadCRandomR e (StateT s m) Source # | |
MonadCRandomR e m => MonadCRandomR e (StateT s m) Source # | |
MonadCRandomR e m => MonadCRandomR e (ReaderT * r m) Source # | |
(ContainsGenError e, Monad m, CryptoRandomGen g) => MonadCRandomR e (CRandT g e m) Source # | |
(MonadCRandomR e m, Monoid w) => MonadCRandomR e (RWST r w s m) Source # | |
(MonadCRandomR e m, Monoid w) => MonadCRandomR e (RWST r w s m) Source # | |
class ContainsGenError e where Source #
toGenError :: e -> Maybe GenError Source #
fromGenError :: GenError -> e Source #
newtype CRandT g e m a Source #
CRandT is the transformer suggested for MonadCRandom.
MonadWriter w m => MonadWriter w (CRandT g e m) Source # | |
MonadState s m => MonadState s (CRandT g e m) Source # | |
MonadReader r m => MonadReader r (CRandT g e m) Source # | |
Monad m => MonadError e (CRandT g e m) Source # | |
(ContainsGenError e, Monad m, CryptoRandomGen g) => MonadCRandomR e (CRandT g e m) Source # | |
(ContainsGenError e, Monad m, CryptoRandomGen g) => MonadCRandom e (CRandT g e m) Source # | |
MonadTrans (CRandT g e) Source # | |
Monad m => Monad (CRandT g e m) Source # | |
Functor m => Functor (CRandT g e m) Source # | |
MonadFix m => MonadFix (CRandT g e m) Source # | |
Monad m => Applicative (CRandT g e m) Source # | |
MonadIO m => MonadIO (CRandT g e m) Source # | |
MonadThrow m => MonadThrow (CRandT g e m) Source # | Throws exceptions into the base monad. Since: 0.7.1 |
MonadCatch m => MonadCatch (CRandT g e m) Source # | Catches exceptions from the base monad. Since: 0.7.1 |
MonadCont m => MonadCont (CRandT g e m) Source # | |
type CRand g e = CRandT g e Identity Source #
Simple users of generators can use CRand for
quick and easy generation of randoms. See
below for a simple use of newGenIO
(from "crypto-api"),
getCRandom
, getBytes
, and runCRandom
.
getRandPair = do int <- getCRandom bytes <- getBytes 100 return (int, bytes) func = do g <- newGenIO case runCRand getRandPair g of Right ((int,bytes), g') -> useRandomVals (int,bytes) Left x -> handleGenError x
evalCRandT :: (ContainsGenError e, Monad m) => CRandT g e m a -> g -> m (Either e a) Source #
newGenCRand :: (CryptoRandomGen g, MonadCRandom GenError m, Functor m) => m g Source #
module Crypto.Random