{-# 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.Hash (Digest, SHA512, hash)
import Crypto.Internal.Imports
import Crypto.Random.ChaChaDRG
import Crypto.Random.SystemDRG
import Crypto.Random.Types
import Data.ByteArray (ByteArray, ByteArrayAccess, ScrubbedBytes)
import qualified Data.ByteArray as B
import qualified Crypto.Number.Serialize as Serialize
newtype Seed = Seed ScrubbedBytes
    deriving (Seed -> Int
(Seed -> Int)
-> (forall p a. Seed -> (Ptr p -> IO a) -> IO a)
-> (forall p. Seed -> Ptr p -> IO ())
-> ByteArrayAccess Seed
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
$clength :: Seed -> Int
length :: Seed -> Int
$cwithByteArray :: forall p a. Seed -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. Seed -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. Seed -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. Seed -> Ptr p -> IO ()
ByteArrayAccess)
seedLength :: Int
seedLength :: Int
seedLength = Int
40
seedNew :: MonadRandom randomly => randomly Seed
seedNew :: forall (randomly :: * -> *). MonadRandom randomly => randomly Seed
seedNew =
    (ScrubbedBytes -> Seed
Seed (ScrubbedBytes -> Seed)
-> (ScrubbedBytes -> ScrubbedBytes) -> ScrubbedBytes -> Seed
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ScrubbedBytes -> ScrubbedBytes
forall bs. ByteArray bs => Int -> bs -> bs
B.take Int
seedLength (ScrubbedBytes -> ScrubbedBytes)
-> (ScrubbedBytes -> ScrubbedBytes)
-> ScrubbedBytes
-> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Digest SHA512 -> ScrubbedBytes
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
B.convert (Digest SHA512 -> ScrubbedBytes)
-> (ScrubbedBytes -> Digest SHA512)
-> ScrubbedBytes
-> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScrubbedBytes -> Digest SHA512
forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
hash :: ScrubbedBytes -> Digest SHA512))
        (ScrubbedBytes -> Seed) -> randomly ScrubbedBytes -> randomly Seed
forall a b. (a -> b) -> randomly a -> randomly b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Int -> randomly ScrubbedBytes
forall byteArray. ByteArray byteArray => Int -> randomly byteArray
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
64
seedToInteger :: Seed -> Integer
seedToInteger :: Seed -> Integer
seedToInteger (Seed ScrubbedBytes
b) = ScrubbedBytes -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
Serialize.os2ip ScrubbedBytes
b
seedFromInteger :: Integer -> Seed
seedFromInteger :: Integer -> Seed
seedFromInteger Integer
i = ScrubbedBytes -> Seed
Seed (ScrubbedBytes -> Seed) -> ScrubbedBytes -> Seed
forall a b. (a -> b) -> a -> b
$ Int -> Integer -> ScrubbedBytes
forall ba. ByteArray ba => Int -> Integer -> ba
Serialize.i2ospOf_ Int
seedLength (Integer
i Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
2 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
seedLength Int -> Int -> Int
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
    | b -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length b
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
40 = CryptoError -> CryptoFailable Seed
forall a. CryptoError -> CryptoFailable a
CryptoFailed (CryptoError
CryptoError_SeedSizeInvalid)
    | Bool
otherwise = Seed -> CryptoFailable Seed
forall a. a -> CryptoFailable a
CryptoPassed (Seed -> CryptoFailable Seed) -> Seed -> CryptoFailable Seed
forall a b. (a -> b) -> a -> b
$ ScrubbedBytes -> Seed
Seed (ScrubbedBytes -> Seed) -> ScrubbedBytes -> Seed
forall a b. (a -> b) -> a -> b
$ b -> ScrubbedBytes
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 (Seed -> ChaChaDRG) -> randomly Seed -> randomly ChaChaDRG
forall a b. (a -> b) -> randomly a -> randomly b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` randomly Seed
forall (randomly :: * -> *). MonadRandom randomly => randomly Seed
seedNew
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed (Seed ScrubbedBytes
seed) = ScrubbedBytes -> ChaChaDRG
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') = Int -> g -> (ba, g)
forall byteArray. ByteArray byteArray => Int -> g -> (byteArray, g)
forall gen byteArray.
(DRG gen, ByteArray byteArray) =>
Int -> gen -> (byteArray, gen)
randomBytesGenerate Int
len g
rng