Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generic cryptographic block primtives and their implementations. This module exposes low-level generic code used in the raaz system. Most likely, one would not need to stoop so low and it might be better to use a more high level interface.
Synopsis
- class BlockAlgorithm (Implementation p) => Primitive p where
- type Implementation p :: Type
- blockSize :: p -> BYTES Int
- class Describable a => BlockAlgorithm a where
- bufferStartAlignment :: a -> Alignment
- type family Key prim :: Type
- class Primitive p => Recommendation p where
- recommended :: p -> Implementation p
- data BLOCKS p
- blocksOf :: Int -> p -> BLOCKS p
- allocBufferFor :: Primitive prim => Implementation prim -> BLOCKS prim -> (Pointer -> IO b) -> IO b
Primtives and their implementations.
class BlockAlgorithm (Implementation p) => Primitive p where Source #
The type class that captures an abstract block cryptographic
primitive. Bulk cryptographic primitives like hashes, ciphers etc
often acts on blocks of data. The size of the block is captured by
the member blockSize
.
As a library, raaz believes in providing multiple implementations
for a given primitive. The associated type Implementation
captures implementations of the primitive.
For use in production code, the library recommends a particular
implementation using the Recommendation
class. By default this is
the implementation used when no explicit implementation is
specified.
type Implementation p :: Type Source #
Associated type that captures an implementation of this primitive.
Instances
Primitive ChaCha20 Source # | |
Primitive BLAKE2s Source # | |
Primitive BLAKE2b Source # | |
Primitive SHA1 Source # | |
Primitive SHA224 Source # | |
Primitive SHA256 Source # | |
Primitive SHA384 Source # | |
Primitive SHA512 Source # | |
Primitive (AES 128 'CBC) Source # | The 128-bit aes cipher in cbc mode. |
Primitive (AES 192 'CBC) Source # | The 192-bit aes cipher in cbc mode. |
Primitive (AES 256 'CBC) Source # | The 256-bit aes cipher in cbc mode. |
class Describable a => BlockAlgorithm a where Source #
Implementation of block primitives work on buffers. Often for optimal performance, and in some case for safety, we need restrictions on the size and alignment of the buffer pointer. This type class captures such restrictions.
bufferStartAlignment :: a -> Alignment Source #
The alignment expected for the buffer pointer.
Instances
BlockAlgorithm (SomeCipherI cipher) Source # | |
Defined in Raaz.Cipher.Internal bufferStartAlignment :: SomeCipherI cipher -> Alignment Source # | |
BlockAlgorithm (SomeHashI h) Source # | |
Defined in Raaz.Hash.Internal bufferStartAlignment :: SomeHashI h -> Alignment Source # | |
BlockAlgorithm (HashI h m) Source # | |
Defined in Raaz.Hash.Internal bufferStartAlignment :: HashI h m -> Alignment Source # | |
BlockAlgorithm (CipherI cipher encMem decMem) Source # | |
Defined in Raaz.Cipher.Internal bufferStartAlignment :: CipherI cipher encMem decMem -> Alignment Source # |
type family Key prim :: Type Source #
Some primitives like ciphers have an encryption/decryption key. This type family captures the key associated with a primitive if it has any.
class Primitive p => Recommendation p where Source #
Primitives that have a recommended implementations.
recommended :: p -> Implementation p Source #
The recommended implementation for the primitive.
Instances
Type safe message length in units of blocks of the primitive.
When dealing with buffer lengths for a primitive, it is often
better to use the type safe units BLOCKS
. Functions in the raaz
package that take lengths usually allow any type safe length as
long as they can be converted to bytes. This can avoid a lot of
tedious and error prone length calculations.
Instances
Enum (BLOCKS p) Source # | |
Eq (BLOCKS p) Source # | |
Ord (BLOCKS p) Source # | |
Defined in Raaz.Core.Primitives | |
Show (BLOCKS p) Source # | |
Semigroup (BLOCKS p) Source # | |
Monoid (BLOCKS p) Source # | |
Primitive p => LengthUnit (BLOCKS p) Source # | |
blocksOf :: Int -> p -> BLOCKS p Source #
The expression n
specifies the message lengths in
units of the block length of the primitive blocksOf
pp
. This expression is
sometimes required to make the type checker happy.
allocBufferFor :: Primitive prim => Implementation prim -> BLOCKS prim -> (Pointer -> IO b) -> IO b Source #
Allocate a buffer a particular implementation of a primitive prim.
algorithm algo
. It ensures that the memory passed is aligned
according to the demands of the implementation.