Skip to content

Commit

Permalink
Random: make prgNewSeed return CryptoFailable
Browse files Browse the repository at this point in the history
  • Loading branch information
infinity0 committed Jun 22, 2020
1 parent 1686aee commit 9922075
Show file tree
Hide file tree
Showing 4 changed files with 19 additions and 9 deletions.
14 changes: 10 additions & 4 deletions Crypto/Cipher/ChaCha.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,13 +14,14 @@ module Crypto.Cipher.ChaCha
, State
-- * Simple interface for DRG purpose
, initializeSimple
, initializeSimpleErr
, generateSimple
, StateSimple
, toPortable
, fromPortable
) where

import Crypto.Error.Types (CryptoFailable (..), CryptoError (..))
import Crypto.Error.Types (CryptoFailable (..), CryptoError (..), throwCryptoError)
import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, ScrubbedBytes, unsafeMapWords)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Compat
Expand Down Expand Up @@ -79,9 +80,14 @@ initialize nbRounds key nonce
initializeSimple :: ByteArrayAccess seed
=> seed -- ^ a 40 bytes long seed
-> StateSimple
initializeSimple seed
| sLen < 40 = error "ChaCha Random: seed length should be 40 bytes"
| otherwise = unsafeDoIO $ do
initializeSimple = throwCryptoError . initializeSimpleErr

initializeSimpleErr :: ByteArrayAccess seed
=> seed -- ^ a 40 bytes long seed
-> CryptoFailable StateSimple
initializeSimpleErr seed
| sLen < 40 = CryptoFailed CryptoError_SeedTooSmall
| otherwise = CryptoPassed $ unsafeDoIO $ do
stPtr <- B.alloc 64 $ \stPtr ->
B.withByteArray seed $ \seedPtr ->
ccryptonite_chacha_init_core stPtr 32 seedPtr 8 (seedPtr `plusPtr` 32)
Expand Down
1 change: 1 addition & 0 deletions Crypto/Error/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@ data CryptoError =
| CryptoError_SaltTooSmall
| CryptoError_OutputLengthTooSmall
| CryptoError_OutputLengthTooBig
| CryptoError_SeedTooSmall
| CryptoError_StateSizeInvalid
deriving (Show,Eq,Enum,Data)

Expand Down
4 changes: 2 additions & 2 deletions Crypto/Random/ChaChaDRG.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ instance DRG ChaChaDRG where
randomBytesGenerate = generate

instance PRG ChaChaDRG where
prgNewSeed seed = ChaChaDRG $ C.initializeSimple seed
prgNewSeed seed = ChaChaDRG <$> C.initializeSimpleErr seed
prgSeedLength _ = 40

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

-- | 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
9 changes: 6 additions & 3 deletions Crypto/Random/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Crypto.Random.Types
, withDRG
) where

import Crypto.Error
import Crypto.Random.Entropy
import Crypto.Internal.ByteArray
import Data.Proxy
Expand All @@ -35,19 +36,21 @@ class DRG gen where
-- Like 'DRG' but also supports initialisation from some fixed seed.
class DRG gen => PRG gen where
-- | Initialize the DRG from some fixed seed.
prgNewSeed :: ByteArrayAccess seed => seed -> gen
--
-- The seed must be of length at least 'prgSeedLength'.
prgNewSeed :: ByteArrayAccess seed => seed -> CryptoFailable gen
-- | Length of seed in bytes
prgSeedLength :: proxy gen -> Int

-- | Initialize the PRG from some entropy supplier.
prgNewEntropy :: forall gen f. (PRG gen, Functor f)
=> (Int -> f ScrubbedBytes)
-> f gen
-> f (CryptoFailable gen)
prgNewEntropy myGetEntropy =
prgNewSeed <$> myGetEntropy (prgSeedLength (Proxy :: Proxy gen))

-- | Initialize the PRG from a 'MonadRandom'.
prgNew :: (PRG gen, MonadRandom f) => f gen
prgNew :: (PRG gen, MonadRandom f) => f (CryptoFailable gen)
prgNew = prgNewEntropy getRandomBytes

instance MonadRandom IO where
Expand Down

0 comments on commit 9922075

Please sign in to comment.