Skip to content
This repository has been archived by the owner on Sep 20, 2023. It is now read-only.

Commit

Permalink
Add PRG typeclass for use in pure code
Browse files Browse the repository at this point in the history
  • Loading branch information
infinity0 committed Jun 8, 2020
1 parent 7758559 commit ea9a0aa
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 1 deletion.
6 changes: 5 additions & 1 deletion Crypto/Random/ChaChaDRG.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,10 @@ import qualified Crypto.Cipher.ChaCha as C
instance DRG ChaChaDRG where
randomBytesGenerate = generate

instance PRG ChaChaDRG where
newPrgFromSeed seed = ChaChaDRG $ C.initializeSimple seed
prgSeedLength = 40

-- | ChaCha Deterministic Random Generator
newtype ChaChaDRG = ChaChaDRG C.StateSimple
deriving (NFData)
Expand All @@ -32,7 +36,7 @@ newtype ChaChaDRG = ChaChaDRG C.StateSimple
initialize :: ByteArrayAccess seed
=> seed -- ^ 40 bytes of seed
-> ChaChaDRG -- ^ the initial ChaCha state
initialize seed = ChaChaDRG $ C.initializeSimple seed
initialize = newPrgFromSeed

-- | Initialize a new ChaCha context from 5-tuple of words64.
-- This interface is useful when creating a RNG out of tests generators (e.g. QuickCheck).
Expand Down
26 changes: 26 additions & 0 deletions Crypto/Random/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,17 @@
-- Stability : experimental
-- Portability : Good
--
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Crypto.Random.Types
(
MonadRandom(..)
, MonadPseudoRandom
, DRG(..)
, PRG(..)
, newPrgFromEntropy
, newPrg
, withDRG
) where

Expand All @@ -25,6 +31,26 @@ class DRG gen where
-- | Generate N bytes of randomness from a DRG
randomBytesGenerate :: ByteArray byteArray => Int -> gen -> (byteArray, gen)

-- | A Psuedo Random Generator (PRG) class
--
-- Like 'DRG' but also supports initialisation from some fixed seed.
class DRG gen => PRG gen where
-- | Initialize the DRG from some fixed seed.
newPrgFromSeed :: ByteArrayAccess seed => seed -> gen
-- | Length of seed in bytes
prgSeedLength :: Int

-- | Initialize the PRG from some entropy supplier.
newPrgFromEntropy :: forall gen f. (PRG gen, Functor f)
=> (Int -> f ScrubbedBytes)
-> f gen
newPrgFromEntropy myGetEntropy =
newPrgFromSeed <$> myGetEntropy (prgSeedLength @gen)

-- | Initialize the PRG from a 'MonadRandom'.
newPrg :: (PRG gen, MonadRandom f) => f gen
newPrg = newPrgFromEntropy getRandomBytes

instance MonadRandom IO where
getRandomBytes = getEntropy

Expand Down

0 comments on commit ea9a0aa

Please sign in to comment.