crypto-api-0.13: A generic interface for cryptographic operations

Portabilityportable
Stabilitybeta
MaintainerThomas.DuBuisson@gmail.com
Safe HaskellNone

Crypto.Classes

Contents

Description

This is the heart of the crypto-api package. By making (or having) an instance of Hash, AsymCipher, BlockCipher or StreamCipher you provide (or obtain) access to any infrastructure built on these primitives include block cipher modes of operation, hashing, hmac, signing, etc. These classes allow users to build routines that are agnostic to the algorithm used so changing algorithms is as simple as changing a type signature.

Synopsis

Hash class and helper functions

class (Serialize d, Eq d, Ord d) => Hash ctx d | d -> ctx, ctx -> d whereSource

The Hash class is intended as the generic interface targeted by maintainers of Haskell digest implementations. Using this generic interface, higher level functions such as hash and hash' provide a useful API for comsumers of hash implementations.

Any instantiated implementation must handle unaligned data.

Minimum complete definition: outputLength, blockLength, initialCtx, updateCtx, and finalize.

Methods

outputLengthSource

Arguments

:: Tagged d BitLength

The size of the digest when encoded

blockLengthSource

Arguments

:: Tagged d BitLength

The amount of data operated on in each round of the digest computation

initialCtxSource

Arguments

:: ctx

An initial context, provided with the first call to updateCtx

updateCtxSource

Arguments

:: ctx 
-> ByteString 
-> ctx

Used to update a context, repeatedly called until all data is exhausted must operate correctly for imputs of n*blockLength bytes for n elem [0..]

finalizeSource

Arguments

:: ctx 
-> ByteString 
-> d

Finializing a context, plus any message data less than the block size, into a digest

hash :: Hash ctx d => ByteString -> dSource

Hash a lazy ByteString, creating a digest

hash' :: Hash ctx d => ByteString -> dSource

Hash a strict ByteString, creating a digest

hashFunc' :: Hash c d => d -> ByteString -> dSource

Obtain a strict hash function whose result is the same type as the given digest, which is discarded. If the type is already inferred then consider using the hash' function instead.

hashFunc :: Hash c d => d -> ByteString -> dSource

Obtain a lazy hash function whose result is the same type as the given digest, which is discarded. If the type is already inferred then consider using the hash function instead.

Cipher classes and helper functions

class Serialize k => BlockCipher k whereSource

The BlockCipher class is intended as the generic interface targeted by maintainers of Haskell cipher implementations.

Minimum complete definition: blockSize, encryptBlock, decryptBlock, buildKey, and keyLength.

Instances must handle unaligned data

Methods

blockSizeSource

Arguments

:: Tagged k BitLength

The size of a single block; the smallest unit on which the cipher operates.

encryptBlockSource

Arguments

:: k 
-> ByteString 
-> ByteString

encrypt data of size n*blockSize where n elem [0..] (ecb encryption)

decryptBlockSource

Arguments

:: k 
-> ByteString 
-> ByteString

decrypt data of size n*blockSize where n elem [0..] (ecb decryption)

buildKeySource

Arguments

:: ByteString 
-> Maybe k

smart constructor for keys from a bytestring.

keyLengthSource

Arguments

:: Tagged k BitLength

length of the cryptographic key

ecb :: k -> ByteString -> ByteStringSource

Electronic Cookbook (encryption)

unEcb :: k -> ByteString -> ByteStringSource

Electronic Cookbook (decryption)

cbc :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Cipherblock Chaining (encryption)

unCbc :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Cipherblock Chaining (decryption)

ctr :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Counter (encryption)

unCtr :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Counter (decryption)

ctrLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Counter (encryption)

unCtrLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Counter (decryption)

cfb :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Ciphertext feedback (encryption)

unCfb :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Ciphertext feedback (decryption)

ofb :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Output feedback (encryption)

unOfb :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Output feedback (decryption)

cbcLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Cipher block chaining encryption for lazy bytestrings

unCbcLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Cipher block chaining decryption for lazy bytestrings

sivLazy :: k -> k -> [ByteString] -> ByteString -> Maybe ByteStringSource

SIV (Synthetic IV) mode for lazy bytestrings. The third argument is the optional list of bytestrings to be authenticated but not encrypted As required by the specification this algorithm may return nothing when certain constraints aren't met.

unSivLazy :: k -> k -> [ByteString] -> ByteString -> Maybe ByteStringSource

SIV (Synthetic IV) for lazy bytestrings. The third argument is the optional list of bytestrings to be authenticated but not encrypted. As required by the specification this algorithm may return nothing when authentication fails.

siv :: k -> k -> [ByteString] -> ByteString -> Maybe ByteStringSource

SIV (Synthetic IV) mode for strict bytestrings. First argument is the optional list of bytestrings to be authenticated but not encrypted. As required by the specification this algorithm may return nothing when certain constraints aren't met.

unSiv :: k -> k -> [ByteString] -> ByteString -> Maybe ByteStringSource

SIV (Synthetic IV) for strict bytestrings First argument is the optional list of bytestrings to be authenticated but not encrypted As required by the specification this algorithm may return nothing when authentication fails.

ecbLazy :: k -> ByteString -> ByteStringSource

Cook book mode - not really a mode at all. If you don't know what you're doing, don't use this mode^H^H^H^H library.

unEcbLazy :: k -> ByteString -> ByteStringSource

ECB decrypt, complementary to ecb.

cfbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Ciphertext feed-back encryption mode for lazy bytestrings (with s == blockSize)

unCfbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Ciphertext feed-back decryption mode for lazy bytestrings (with s == blockSize)

ofbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Output feedback mode for lazy bytestrings

unOfbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)Source

Output feedback mode for lazy bytestrings

blockSizeBytes :: BlockCipher k => Tagged k ByteLengthSource

The number of bytes in a block cipher block

keyLengthBytes :: BlockCipher k => Tagged k ByteLengthSource

The number of bytes in a block cipher key (assuming it is an even multiple of 8 bits)

buildKeyIO :: BlockCipher k => IO kSource

Build a symmetric key using the system entropy (see Random)

buildKeyGen :: (BlockCipher k, CryptoRandomGen g) => g -> Either GenError (k, g)Source

Build a symmetric key using a given CryptoRandomGen

class Serialize k => StreamCipher k iv | k -> iv whereSource

A stream cipher class. Instance are expected to work on messages as small as one byte The length of the resulting cipher text should be equal to the length of the input message.

buildStreamKeyIO :: StreamCipher k iv => IO kSource

Build a stream key using the system random generator

buildStreamKeyGen :: (StreamCipher k iv, CryptoRandomGen g) => g -> Either GenError (k, g)Source

Build a stream key using the provided random generator

class AsymCipher p v | p -> v, v -> p whereSource

Asymetric ciphers (common ones being RSA or EC based)

Methods

buildKeyPairSource

Arguments

:: CryptoRandomGen g 
=> g 
-> BitLength 
-> Either GenError ((p, v), g)

build a public/private key pair using the provided generator

encryptAsymSource

Arguments

:: CryptoRandomGen g 
=> g 
-> p 
-> ByteString 
-> Either GenError (ByteString, g)

Asymetric encryption

decryptAsymSource

Arguments

:: CryptoRandomGen g 
=> g 
-> v 
-> ByteString 
-> Either GenError (ByteString, g)

Asymetric decryption

publicKeyLength :: p -> BitLengthSource

privateKeyLength :: v -> BitLengthSource

buildKeyPairIO :: AsymCipher p v => BitLength -> IO (Either GenError (p, v))Source

Build a pair of asymmetric keys using the system random generator.

buildKeyPairGen :: (CryptoRandomGen g, AsymCipher p v) => BitLength -> g -> Either GenError ((p, v), g)Source

Flipped buildKeyPair for ease of use with state monads.

class (Serialize p, Serialize v) => Signing p v | p -> v, v -> p whereSource

A class for signing operations which inherently can not be as generic as asymetric ciphers (ex: DSA).

buildSigningKeyPairIO :: Signing p v => BitLength -> IO (Either GenError (p, v))Source

Build a signing key using the system random generator

buildSigningKeyPairGen :: (Signing p v, CryptoRandomGen g) => BitLength -> g -> Either GenError ((p, v), g)Source

Flipped buildSigningPair for ease of use with state monads.

Misc helper functions

encode :: Serialize a => a -> ByteString

Encode a value using binary serialization to a strict ByteString.

zeroIV :: BlockCipher k => IV kSource

Obtain an IV made only of zeroes

incIV :: BlockCipher k => IV k -> IV kSource

Increase an IV by one. This is way faster than decoding, increasing, encoding

getIV :: (BlockCipher k, CryptoRandomGen g) => g -> Either GenError (IV k, g)Source

Obtain an IV using the provided CryptoRandomGenerator.

getIVIO :: BlockCipher k => IO (IV k)Source

Obtain an IV using the system entropy (see Random)