{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Random
(
ChaChaDRG
, SystemDRG
, Seed
, seedNew
, seedFromInteger
, seedToInteger
, seedFromBinary
, getSystemDRG
, drgNew
, drgNewSeed
, drgNewTest
, withDRG
, withRandomBytes
, DRG(..)
, MonadRandom(..)
, MonadPseudoRandom
) where
import Crypto.Error
import Crypto.Random.Types
import Crypto.Random.ChaChaDRG
import Crypto.Random.SystemDRG
import Data.ByteArray (ByteArray, ByteArrayAccess, ScrubbedBytes)
import qualified Data.ByteArray as B
import Crypto.Internal.Imports
import qualified Crypto.Number.Serialize as Serialize
newtype Seed = Seed ScrubbedBytes
deriving (Seed -> Int
forall p. Seed -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. Seed -> (Ptr p -> IO a) -> IO a
copyByteArrayToPtr :: forall p. Seed -> Ptr p -> IO ()
$ccopyByteArrayToPtr :: forall p. Seed -> Ptr p -> IO ()
withByteArray :: forall p a. Seed -> (Ptr p -> IO a) -> IO a
$cwithByteArray :: forall p a. Seed -> (Ptr p -> IO a) -> IO a
length :: Seed -> Int
$clength :: Seed -> Int
ByteArrayAccess)
seedLength :: Int
seedLength :: Int
seedLength = Int
40
seedNew :: MonadRandom randomly => randomly Seed
seedNew :: forall (randomly :: * -> *). MonadRandom randomly => randomly Seed
seedNew = ScrubbedBytes -> Seed
Seed forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
seedLength
seedToInteger :: Seed -> Integer
seedToInteger :: Seed -> Integer
seedToInteger (Seed ScrubbedBytes
b) = forall ba. ByteArrayAccess ba => ba -> Integer
Serialize.os2ip ScrubbedBytes
b
seedFromInteger :: Integer -> Seed
seedFromInteger :: Integer -> Seed
seedFromInteger Integer
i = ScrubbedBytes -> Seed
Seed forall a b. (a -> b) -> a -> b
$ forall ba. ByteArray ba => Int -> Integer -> ba
Serialize.i2ospOf_ Int
seedLength (Integer
i forall a. Integral a => a -> a -> a
`mod` Integer
2forall a b. (Num a, Integral b) => a -> b -> a
^(Int
seedLength forall a. Num a => a -> a -> a
* Int
8))
seedFromBinary :: ByteArrayAccess b => b -> CryptoFailable Seed
seedFromBinary :: forall b. ByteArrayAccess b => b -> CryptoFailable Seed
seedFromBinary b
b
| forall ba. ByteArrayAccess ba => ba -> Int
B.length b
b forall a. Eq a => a -> a -> Bool
/= Int
40 = forall a. CryptoError -> CryptoFailable a
CryptoFailed (CryptoError
CryptoError_SeedSizeInvalid)
| Bool
otherwise = forall a. a -> CryptoFailable a
CryptoPassed forall a b. (a -> b) -> a -> b
$ ScrubbedBytes -> Seed
Seed forall a b. (a -> b) -> a -> b
$ forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
B.convert b
b
drgNew :: MonadRandom randomly => randomly ChaChaDRG
drgNew :: forall (randomly :: * -> *).
MonadRandom randomly =>
randomly ChaChaDRG
drgNew = Seed -> ChaChaDRG
drgNewSeed forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (randomly :: * -> *). MonadRandom randomly => randomly Seed
seedNew
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed (Seed ScrubbedBytes
seed) = forall seed. ByteArrayAccess seed => seed -> ChaChaDRG
initialize ScrubbedBytes
seed
drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
drgNewTest = (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
initializeWords
withRandomBytes :: (ByteArray ba, DRG g) => g -> Int -> (ba -> a) -> (a, g)
withRandomBytes :: forall ba g a.
(ByteArray ba, DRG g) =>
g -> Int -> (ba -> a) -> (a, g)
withRandomBytes g
rng Int
len ba -> a
f = (ba -> a
f ba
bs, g
rng')
where (ba
bs, g
rng') = forall gen byteArray.
(DRG gen, ByteArray byteArray) =>
Int -> gen -> (byteArray, gen)
randomBytesGenerate Int
len g
rng