{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
module Raaz.Cipher.ChaCha20.Recommendation
( chacha20Random, RandomBuf, getBufferPointer, randomBufferSize
) where
import Control.Applicative
import Prelude
import Raaz.Core
import Raaz.Cipher.ChaCha20.Internal
#ifdef HAVE_VECTOR_256
import Raaz.Cipher.ChaCha20.Implementation.Vector256
#else
import Raaz.Cipher.ChaCha20.Implementation.CPortable
#endif
instance Recommendation ChaCha20 where
recommended :: ChaCha20 -> Implementation ChaCha20
recommended ChaCha20
_ = Implementation ChaCha20
SomeCipherI ChaCha20
implementation
newtype RandomBuf = RandomBuf { RandomBuf -> Pointer
unBuf :: Pointer }
instance Memory RandomBuf where
memoryAlloc :: Alloc RandomBuf
memoryAlloc = Pointer -> RandomBuf
RandomBuf (Pointer -> RandomBuf)
-> TwistRF AllocField (BYTES Int) Pointer -> Alloc RandomBuf
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ALIGN -> TwistRF AllocField (BYTES Int) Pointer
forall l.
LengthUnit l =>
l -> TwistRF AllocField (BYTES Int) Pointer
pointerAlloc ALIGN
sz
where sz :: ALIGN
sz = BLOCKS ChaCha20 -> Alignment -> ALIGN
forall l. LengthUnit l => l -> Alignment -> ALIGN
atLeastAligned BLOCKS ChaCha20
randomBufferSize Alignment
randomBufferAlignment
unsafeToPointer :: RandomBuf -> Pointer
unsafeToPointer = RandomBuf -> Pointer
unBuf
getBufferPointer :: MT RandomBuf Pointer
getBufferPointer :: MT RandomBuf Pointer
getBufferPointer = RandomBuf -> Pointer
actualPtr (RandomBuf -> Pointer)
-> MT RandomBuf RandomBuf -> MT RandomBuf Pointer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MT RandomBuf RandomBuf
forall (mT :: * -> * -> *) mem. MemoryThread mT => mT mem mem
getMemory
where actualPtr :: RandomBuf -> Pointer
actualPtr = (Pointer -> Alignment -> Pointer)
-> Alignment -> Pointer -> Pointer
forall a b c. (a -> b -> c) -> b -> a -> c
flip Pointer -> Alignment -> Pointer
forall a. Ptr a -> Alignment -> Ptr a
alignPtr Alignment
randomBufferAlignment (Pointer -> Pointer)
-> (RandomBuf -> Pointer) -> RandomBuf -> Pointer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RandomBuf -> Pointer
unBuf
randomBufferSize :: BLOCKS ChaCha20
randomBufferSize :: BLOCKS ChaCha20
randomBufferSize = Int
16 Int -> ChaCha20 -> BLOCKS ChaCha20
forall p. Int -> p -> BLOCKS p
`blocksOf` ChaCha20
ChaCha20
randomBufferAlignment :: Alignment
randomBufferAlignment :: Alignment
randomBufferAlignment = Alignment
32