Portability | portable |
---|---|
Stability | beta |
Maintainer | Thomas.DuBuisson@gmail.com |
Safe Haskell | None |
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.
- class (Serialize d, Eq d, Ord d) => Hash ctx d | d -> ctx, ctx -> d where
- outputLength :: Tagged d BitLength
- blockLength :: Tagged d BitLength
- initialCtx :: ctx
- updateCtx :: ctx -> ByteString -> ctx
- finalize :: ctx -> ByteString -> d
- hash :: Hash ctx d => ByteString -> d
- hash' :: Hash ctx d => ByteString -> d
- hashFunc :: Hash c d => d -> ByteString -> d
- hashFunc' :: Hash c d => d -> ByteString -> d
- class Serialize k => BlockCipher k where
- blockSize :: Tagged k BitLength
- encryptBlock :: k -> ByteString -> ByteString
- decryptBlock :: k -> ByteString -> ByteString
- buildKey :: ByteString -> Maybe k
- keyLength :: Tagged k BitLength
- ecb :: k -> ByteString -> ByteString
- unEcb :: k -> ByteString -> ByteString
- cbc :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCbc :: k -> IV k -> ByteString -> (ByteString, IV k)
- ctr :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCtr :: k -> IV k -> ByteString -> (ByteString, IV k)
- cfb :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCfb :: k -> IV k -> ByteString -> (ByteString, IV k)
- ofb :: k -> IV k -> ByteString -> (ByteString, IV k)
- unOfb :: k -> IV k -> ByteString -> (ByteString, IV k)
- blockSizeBytes :: BlockCipher k => Tagged k ByteLength
- keyLengthBytes :: BlockCipher k => Tagged k ByteLength
- buildKeyIO :: BlockCipher k => IO k
- buildKeyGen :: (BlockCipher k, CryptoRandomGen g) => g -> Either GenError (k, g)
- class Serialize k => StreamCipher k iv | k -> iv where
- buildStreamKey :: ByteString -> Maybe k
- encryptStream :: k -> iv -> ByteString -> (ByteString, iv)
- decryptStream :: k -> iv -> ByteString -> (ByteString, iv)
- streamKeyLength :: Tagged k BitLength
- buildStreamKeyIO :: StreamCipher k iv => IO k
- buildStreamKeyGen :: (StreamCipher k iv, CryptoRandomGen g) => g -> Either GenError (k, g)
- class (Serialize p, Serialize v) => AsymCipher p v | p -> v, v -> p where
- buildKeyPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p, v), g)
- encryptAsym :: CryptoRandomGen g => g -> p -> ByteString -> Either GenError (ByteString, g)
- decryptAsym :: v -> ByteString -> Maybe ByteString
- publicKeyLength :: p -> BitLength
- privateKeyLength :: v -> BitLength
- buildKeyPairIO :: AsymCipher p v => BitLength -> IO (Either GenError (p, v))
- buildKeyPairGen :: (CryptoRandomGen g, AsymCipher p v) => BitLength -> g -> Either GenError ((p, v), g)
- class (Serialize p, Serialize v) => Signing p v | p -> v, v -> p where
- sign :: CryptoRandomGen g => g -> v -> ByteString -> Either GenError (ByteString, g)
- verify :: p -> ByteString -> ByteString -> Bool
- buildSigningPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p, v), g)
- signingKeyLength :: v -> BitLength
- verifyingKeyLength :: p -> BitLength
- buildSigningKeyPairIO :: Signing p v => BitLength -> IO (Either GenError (p, v))
- buildSigningKeyPairGen :: (Signing p v, CryptoRandomGen g) => BitLength -> g -> Either GenError ((p, v), g)
- encode :: Serialize a => a -> ByteString
- incIV :: BlockCipher k => IV k -> IV k
- module Crypto.Util
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
.
:: ctx | An initial context, provided with the first call to |
:: ctx | |
-> ByteString | |
-> ctx | Used to update a context, repeatedly called until all data is exhausted
must operate correctly for imputs of |
:: 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 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.
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.
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.
Using this generic interface higher level functions
such as cbc
, and other functions from Data.Crypto.Modes, provide a useful API
for comsumers of cipher implementations.
Instances must handle unaligned data
:: k | |
-> ByteString | |
-> ByteString | encrypt data of size |
:: k | |
-> ByteString | |
-> ByteString | decrypt data of size |
:: ByteString | |
-> Maybe k | smart constructor for keys from a bytestring. |
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)
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)
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.
buildStreamKey :: ByteString -> Maybe kSource
encryptStream :: k -> iv -> ByteString -> (ByteString, iv)Source
decryptStream :: k -> iv -> ByteString -> (ByteString, iv)Source
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 (Serialize p, Serialize v) => AsymCipher p v | p -> v, v -> p whereSource
Asymetric ciphers (common ones being RSA or EC based)
:: CryptoRandomGen g | |
=> g | |
-> BitLength | |
-> Either GenError ((p, v), g) | build a public/private key pair using the provided generator |
:: CryptoRandomGen g | |
=> g | |
-> p | |
-> ByteString | |
-> Either GenError (ByteString, g) | Asymetric encryption |
:: v | |
-> ByteString | |
-> Maybe ByteString | 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).
sign :: CryptoRandomGen g => g -> v -> ByteString -> Either GenError (ByteString, g)Source
verify :: p -> ByteString -> ByteString -> BoolSource
buildSigningPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p, v), g)Source
signingKeyLength :: v -> BitLengthSource
verifyingKeyLength :: p -> BitLengthSource
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.
incIV :: BlockCipher k => IV k -> IV kSource
Increase an IV
by one. This is way faster than decoding,
increasing, encoding
module Crypto.Util