-- |
-- Module      : Crypto.Random
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : stable
-- Portability : good
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Random
    (
    -- * Deterministic instances
      ChaChaDRG
    , SystemDRG
    , Seed
    -- * Seed
    , seedNew
    , seedFromInteger
    , seedToInteger
    , seedFromBinary
    -- * Deterministic Random class
    , getSystemDRG
    , drgNew
    , drgNewSeed
    , drgNewTest
    , withDRG
    , withRandomBytes
    , DRG(..)
    -- * Random abstraction
    , 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
Seed -> Ptr p -> IO ()
Seed -> (Ptr p -> IO a) -> IO a
(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
copyByteArrayToPtr :: Seed -> Ptr p -> IO ()
$ccopyByteArrayToPtr :: forall p. Seed -> Ptr p -> IO ()
withByteArray :: 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)

-- Length for ChaCha DRG seed
seedLength :: Int
seedLength :: Int
seedLength = Int
40

-- | Create a new Seed from system entropy
seedNew :: MonadRandom randomly => randomly Seed
seedNew :: randomly Seed
seedNew = ScrubbedBytes -> Seed
Seed (ScrubbedBytes -> Seed) -> randomly ScrubbedBytes -> randomly Seed
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Int -> randomly ScrubbedBytes
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
seedLength

-- | Convert a Seed to an integer
seedToInteger :: Seed -> Integer
seedToInteger :: Seed -> Integer
seedToInteger (Seed ScrubbedBytes
b) = ScrubbedBytes -> Integer
forall ba. ByteArrayAccess ba => ba -> Integer
Serialize.os2ip ScrubbedBytes
b

-- | Convert an integer to a Seed
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
2Integer -> 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))

-- | Convert a binary to a seed
seedFromBinary :: ByteArrayAccess b => b -> CryptoFailable Seed
seedFromBinary :: 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

-- | Create a new DRG from system entropy
drgNew :: MonadRandom randomly => randomly ChaChaDRG
drgNew :: randomly ChaChaDRG
drgNew = Seed -> ChaChaDRG
drgNewSeed (Seed -> ChaChaDRG) -> randomly Seed -> randomly ChaChaDRG
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` randomly Seed
forall (randomly :: * -> *). MonadRandom randomly => randomly Seed
seedNew

-- | Create a new DRG from a seed
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed :: Seed -> ChaChaDRG
drgNewSeed (Seed ScrubbedBytes
seed) = ScrubbedBytes -> ChaChaDRG
forall seed. ByteArrayAccess seed => seed -> ChaChaDRG
initialize ScrubbedBytes
seed

-- | Create a new DRG from 5 Word64.
--
-- This is a convenient interface to create deterministic interface
-- for quickcheck style testing.
--
-- It can also be used in other contexts provided the input
-- has been properly randomly generated.
--
-- Note that the @Arbitrary@ instance provided by QuickCheck for 'Word64' does
-- not have a uniform distribution.  It is often better to use instead
-- @arbitraryBoundedRandom@.
--
-- System endianness impacts how the tuple is interpreted and therefore changes
-- the resulting DRG.
drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
drgNewTest :: (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
drgNewTest = (Word64, Word64, Word64, Word64, Word64) -> ChaChaDRG
initializeWords

-- | Generate @len random bytes and mapped the bytes to the function @f.
--
-- This is equivalent to use Control.Arrow 'first' with 'randomBytesGenerate'
withRandomBytes :: (ByteArray ba, DRG g) => g -> Int -> (ba -> a) -> (a, g)
withRandomBytes :: 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 gen byteArray.
(DRG gen, ByteArray byteArray) =>
Int -> gen -> (byteArray, gen)
randomBytesGenerate Int
len g
rng