raaz-0.2.0: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Primitives

Contents

Description

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

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.

Minimal complete definition

blockSize

Associated Types

type Implementation p :: * Source #

Associated type that captures an implementation of this primitive.

Methods

blockSize :: p -> BYTES Int Source #

The block size.

Instances

Primitive BLAKE2s Source # 

Associated Types

type Implementation BLAKE2s :: * Source #

Primitive BLAKE2b Source # 

Associated Types

type Implementation BLAKE2b :: * Source #

Primitive SHA1 Source # 

Associated Types

type Implementation SHA1 :: * Source #

Primitive SHA256 Source # 

Associated Types

type Implementation SHA256 :: * Source #

Primitive SHA224 Source # 

Associated Types

type Implementation SHA224 :: * Source #

Primitive SHA384 Source # 

Associated Types

type Implementation SHA384 :: * Source #

Primitive SHA512 Source # 

Associated Types

type Implementation SHA512 :: * Source #

Primitive ChaCha20 Source # 

Associated Types

type Implementation ChaCha20 :: * Source #

Primitive (AES 128 CBC) Source #

The 128-bit aes cipher in cbc mode.

Associated Types

type Implementation (AES 128 CBC) :: * Source #

Methods

blockSize :: AES 128 CBC -> BYTES Int Source #

Primitive (AES 192 CBC) Source #

The 192-bit aes cipher in cbc mode.

Associated Types

type Implementation (AES 192 CBC) :: * Source #

Methods

blockSize :: AES 192 CBC -> BYTES Int Source #

Primitive (AES 256 CBC) Source #

The 256-bit aes cipher in cbc mode.

Associated Types

type Implementation (AES 256 CBC) :: * Source #

Methods

blockSize :: AES 256 CBC -> BYTES Int Source #

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.

Minimal complete definition

bufferStartAlignment

Methods

bufferStartAlignment :: a -> Alignment Source #

The alignment expected for the buffer pointer.

type family Key prim :: * Source #

Some primitives like ciphers have an encryption/decryption key. This type family captures the key associated with a primitive if it has any.

Instances

type Key ChaCha20 Source # 
type Key (HMAC h) Source # 
type Key (HMAC h)
type Key (AES 128 CBC) Source # 
type Key (AES 128 CBC) = (KEY128, IV)
type Key (AES 192 CBC) Source # 
type Key (AES 192 CBC) = (KEY192, IV)
type Key (AES 256 CBC) Source # 
type Key (AES 256 CBC) = (KEY256, IV)

class Primitive p => Recommendation p where Source #

Primitives that have a recommended implementations.

Minimal complete definition

recommended

Methods

recommended :: p -> Implementation p Source #

The recommended implementation for the primitive.

data BLOCKS p Source #

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 # 

Methods

succ :: BLOCKS p -> BLOCKS p #

pred :: BLOCKS p -> BLOCKS p #

toEnum :: Int -> BLOCKS p #

fromEnum :: BLOCKS p -> Int #

enumFrom :: BLOCKS p -> [BLOCKS p] #

enumFromThen :: BLOCKS p -> BLOCKS p -> [BLOCKS p] #

enumFromTo :: BLOCKS p -> BLOCKS p -> [BLOCKS p] #

enumFromThenTo :: BLOCKS p -> BLOCKS p -> BLOCKS p -> [BLOCKS p] #

Eq (BLOCKS p) Source # 

Methods

(==) :: BLOCKS p -> BLOCKS p -> Bool #

(/=) :: BLOCKS p -> BLOCKS p -> Bool #

Ord (BLOCKS p) Source # 

Methods

compare :: BLOCKS p -> BLOCKS p -> Ordering #

(<) :: BLOCKS p -> BLOCKS p -> Bool #

(<=) :: BLOCKS p -> BLOCKS p -> Bool #

(>) :: BLOCKS p -> BLOCKS p -> Bool #

(>=) :: BLOCKS p -> BLOCKS p -> Bool #

max :: BLOCKS p -> BLOCKS p -> BLOCKS p #

min :: BLOCKS p -> BLOCKS p -> BLOCKS p #

Show (BLOCKS p) Source # 

Methods

showsPrec :: Int -> BLOCKS p -> ShowS #

show :: BLOCKS p -> String #

showList :: [BLOCKS p] -> ShowS #

Monoid (BLOCKS p) Source # 

Methods

mempty :: BLOCKS p #

mappend :: BLOCKS p -> BLOCKS p -> BLOCKS p #

mconcat :: [BLOCKS p] -> BLOCKS p #

Primitive p => LengthUnit (BLOCKS p) Source # 

Methods

inBytes :: BLOCKS p -> BYTES Int Source #

blocksOf :: Int -> p -> BLOCKS p Source #

The expression n blocksOf p specifies the message lengths in units of the block length of the primitive p. 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.