Maintainer | Thomas.DuBuisson@gmail.com |
---|---|
Stability | beta |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Control.Monad.CryptoRandom
Description
Much like the MonadRandom package (Control.Monad.Random), this module provides plumbing for the CryptoRandomGen generators.
Synopsis
- class CRandom a where
- crandom :: CryptoRandomGen g => g -> Either GenError (a, g)
- crandoms :: CryptoRandomGen g => g -> [a]
- class CRandomR a where
- crandomR :: CryptoRandomGen g => (a, a) -> g -> Either GenError (a, g)
- crandomRs :: CryptoRandomGen g => (a, a) -> g -> [a]
- class (ContainsGenError e, MonadError e m) => MonadCRandom e m where
- getCRandom :: CRandom a => m a
- getBytes :: Int -> m ByteString
- getBytesWithEntropy :: Int -> ByteString -> m ByteString
- doReseed :: ByteString -> m ()
- class (ContainsGenError e, MonadError e m) => MonadCRandomR e m where
- getCRandomR :: CRandomR a => (a, a) -> m a
- class ContainsGenError e where
- toGenError :: e -> Maybe GenError
- fromGenError :: GenError -> e
- 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
- data GenError
- class CryptoRandomGen g where
- newGen :: ByteString -> Either GenError g
- genSeedLength :: Tagged g ByteLength
- genBytes :: ByteLength -> g -> Either GenError (ByteString, g)
- reseedInfo :: g -> ReseedInfo
- reseedPeriod :: g -> ReseedInfo
- genBytesWithEntropy :: ByteLength -> ByteString -> g -> Either GenError (ByteString, g)
- reseed :: ByteString -> g -> Either GenError g
- newGenIO :: IO g
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).
Minimal complete definition
Methods
crandom :: CryptoRandomGen g => g -> Either GenError (a, g) Source #
crandoms :: CryptoRandomGen g => g -> [a] Source #
Instances
CRandom Bool Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Int Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Int8 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Int16 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Int32 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Int64 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Word8 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Word16 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Word32 Source # | |
Defined in Control.Monad.CryptoRandom | |
CRandom Word64 Source # | |
Defined in Control.Monad.CryptoRandom |
class CRandomR a where Source #
Minimal complete definition
Methods
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.
Methods
getCRandom :: CRandom a => m a Source #
getBytes :: Int -> m ByteString Source #
getBytesWithEntropy :: Int -> ByteString -> m ByteString Source #
doReseed :: ByteString -> m () Source #
Instances
class (ContainsGenError e, MonadError e m) => MonadCRandomR e m where Source #
Methods
getCRandomR :: CRandomR a => (a, a) -> m a Source #
Instances
class ContainsGenError e where Source #
Instances
ContainsGenError GenError Source # | |
Defined in Control.Monad.CryptoRandom |
newtype CRandT g e m a Source #
CRandT is the transformer suggested for MonadCRandom.
Instances
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 #
Generator failures should always return the appropriate GenError.
Note GenError
in an instance of exception but wether or not an
exception is thrown depends on if the selected generator (read:
if you don't want execptions from code that uses throw
then
pass in a generator that never has an error for the used functions)
Constructors
GenErrorOther String | Misc |
RequestedTooManyBytes | Requested more bytes than a single pass can generate (The maximum request is generator dependent) |
RangeInvalid | When using |
NeedReseed | Some generators cease operation after too high a count without a reseed (ex: NIST SP 800-90) |
NotEnoughEntropy | For instantiating new generators (or reseeding) |
NeedsInfiniteSeed | This generator can not be
instantiated or reseeded with a
finite seed (ex: |
Instances
Eq GenError | |
Data GenError | |
Defined in Crypto.Random Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenError -> c GenError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenError Source # toConstr :: GenError -> Constr Source # dataTypeOf :: GenError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenError) Source # gmapT :: (forall b. Data b => b -> b) -> GenError -> GenError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenError -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GenError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenError -> m GenError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenError -> m GenError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenError -> m GenError Source # | |
Ord GenError | |
Defined in Crypto.Random | |
Read GenError | |
Show GenError | |
Exception GenError | |
Defined in Crypto.Random Methods toException :: GenError -> SomeException Source # fromException :: SomeException -> Maybe GenError Source # displayException :: GenError -> String Source # | |
ContainsGenError GenError Source # | |
Defined in Control.Monad.CryptoRandom |
class CryptoRandomGen g where Source #
A class of random bit generators that allows for the possibility of failure, reseeding, providing entropy at the same time as requesting bytes
Minimum complete definition: newGen
, genSeedLength
, genBytes
,
reseed
, reseedInfo
, reseedPeriod
.
Minimal complete definition
newGen, genSeedLength, genBytes, reseedInfo, reseedPeriod, reseed
Methods
newGen :: ByteString -> Either GenError g Source #
Instantiate a new random bit generator. The provided
bytestring should be of length >= genSeedLength. If the
bytestring is shorter then the call may fail (suggested
error: NotEnoughEntropy
). If the bytestring is of
sufficent length the call should always succeed.
genSeedLength :: Tagged g ByteLength Source #
Length of input entropy necessary to instantiate or reseed a generator
genBytes :: ByteLength -> g -> Either GenError (ByteString, g) Source #
genBytes len g
generates a random ByteString of length
len
and new generator. The MonadCryptoRandom package
has routines useful for converting the ByteString to
commonly needed values (but "cereal" or other
deserialization libraries would also work).
This routine can fail if the generator has gone too long
without a reseed (usually this is in the ball-park of 2^48
requests). Suggested error in this cases is NeedReseed
reseedInfo :: g -> ReseedInfo Source #
Indicates how soon a reseed is needed
reseedPeriod :: g -> ReseedInfo Source #
Indicates the period between reseeds (constant for most generators).
genBytesWithEntropy :: ByteLength -> ByteString -> g -> Either GenError (ByteString, g) Source #
genBytesWithEntropy g i entropy
generates i
random
bytes and use the additional input entropy
in the
generation of the requested data to increase the confidence
our generated data is a secure random stream.
Some generators use entropy
to perturb the state of the
generator, meaning:
(_,g2') <- genBytesWithEntropy len g1 ent (_,g2 ) <- genBytes len g1 g2 /= g2'
But this is not required.
Default:
genBytesWithEntropy g bytes entropy = xor entropy (genBytes g bytes)
reseed :: ByteString -> g -> Either GenError g Source #
If the generator has produced too many random bytes on its
existing seed it will return NeedReseed
. In that case,
reseed the generator using this function and a new
high-entropy seed of length >= genSeedLength
. Using
bytestrings that are too short can result in an error
(NotEnoughEntropy
).
By default this uses System.Entropy to obtain
entropy for newGen
.
WARNING: The default implementation opens a file handle which will never be closed!
Instances
CryptoRandomGen SystemRandom | |
Defined in Crypto.Random Methods newGen :: ByteString -> Either GenError SystemRandom Source # genSeedLength :: Tagged SystemRandom ByteLength Source # genBytes :: ByteLength -> SystemRandom -> Either GenError (ByteString, SystemRandom) Source # reseedInfo :: SystemRandom -> ReseedInfo Source # reseedPeriod :: SystemRandom -> ReseedInfo Source # genBytesWithEntropy :: ByteLength -> ByteString -> SystemRandom -> Either GenError (ByteString, SystemRandom) Source # reseed :: ByteString -> SystemRandom -> Either GenError SystemRandom Source # |