raaz-0.0.1: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell98

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 Describable (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.

There is a reference implementation where the emphasis is on correctness rather than speed or security. They are used to verify the correctness of the other implementations for the same primitive. Apart from this, for production use, we have a recommended implementation.

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 SHA1 Source # 

Associated Types

type Implementation SHA1 :: * Source #

Primitive SHA224 Source # 

Associated Types

type Implementation SHA224 :: * Source #

Primitive SHA256 Source # 

Associated Types

type Implementation SHA256 :: * Source #

Primitive SHA384 Source # 

Associated Types

type Implementation SHA384 :: * Source #

Primitive SHA512 Source # 

Associated Types

type Implementation SHA512 :: * Source #

Hash h => Primitive (HMAC h) Source # 

Associated Types

type Implementation (HMAC h) :: * Source #

Methods

blockSize :: HMAC h -> BYTES Int 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 Primitive prim => Symmetric prim Source #

A symmetric primitive. An example would be primitives like Ciphers, HMACs etc.

Associated Types

type Key prim Source #

The key for the primitive.

Instances

Hash h => Symmetric (HMAC h) Source # 

Associated Types

type Key (HMAC h) :: * Source #

Symmetric (AES 128 CBC) Source #

Key is (KEY128,IV) pair.

Associated Types

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

Symmetric (AES 192 CBC) Source #

Key is (KEY192,IV) pair.

Associated Types

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

Symmetric (AES 256 CBC) Source #

Key is (KEY256,IV) pair.

Associated Types

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

class Asymmetric prim Source #

An asymmetric primitive.

Associated Types

type PublicKey prim Source #

The public key

type PrivateKey prim Source #

The private key

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 #

Integral (BLOCKS p) Source # 

Methods

quot :: BLOCKS p -> BLOCKS p -> BLOCKS p #

rem :: BLOCKS p -> BLOCKS p -> BLOCKS p #

div :: BLOCKS p -> BLOCKS p -> BLOCKS p #

mod :: BLOCKS p -> BLOCKS p -> BLOCKS p #

quotRem :: BLOCKS p -> BLOCKS p -> (BLOCKS p, BLOCKS p) #

divMod :: BLOCKS p -> BLOCKS p -> (BLOCKS p, BLOCKS p) #

toInteger :: BLOCKS p -> Integer #

Num (BLOCKS p) Source # 

Methods

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

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

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

negate :: BLOCKS p -> BLOCKS p #

abs :: BLOCKS p -> BLOCKS p #

signum :: BLOCKS p -> BLOCKS p #

fromInteger :: Integer -> BLOCKS p #

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 #

Real (BLOCKS p) Source # 

Methods

toRational :: BLOCKS p -> Rational #

Show (BLOCKS p) Source # 

Methods

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

show :: BLOCKS p -> String #

showList :: [BLOCKS p] -> ShowS #

Primitive p => LengthUnit (BLOCKS p) Source # 

Methods

inBytes :: BLOCKS p -> BYTES Int Source #

blocksOf :: Primitive p => 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.