Maintainer | Thomas.DuBuisson@gmail.com |
---|---|
Stability | beta |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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)
- ctrLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCtrLazy :: 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)
- cbcLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCbcLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- sivLazy :: k -> k -> [ByteString] -> ByteString -> Maybe ByteString
- unSivLazy :: k -> k -> [ByteString] -> ByteString -> Maybe ByteString
- siv :: k -> k -> [ByteString] -> ByteString -> Maybe ByteString
- unSiv :: k -> k -> [ByteString] -> ByteString -> Maybe ByteString
- ecbLazy :: k -> ByteString -> ByteString
- unEcbLazy :: k -> ByteString -> ByteString
- cfbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- unCfbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- ofbLazy :: k -> IV k -> ByteString -> (ByteString, IV k)
- unOfbLazy :: 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 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 :: CryptoRandomGen g => g -> v -> ByteString -> Either GenError (ByteString, g)
- 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
- zeroIV :: BlockCipher k => IV k
- incIV :: BlockCipher k => IV k -> IV k
- getIV :: (BlockCipher k, CryptoRandomGen g) => g -> Either GenError (IV k, g)
- getIVIO :: BlockCipher k => IO (IV k)
- chunkFor :: BlockCipher k => k -> ByteString -> [ByteString]
- chunkFor' :: BlockCipher k => k -> ByteString -> [ByteString]
- module Crypto.Util
- module Crypto.Types
Hash class and helper functions
class (Serialize d, Eq d, Ord d) => Hash ctx d | d -> ctx, ctx -> d where Source
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 -> d Source
Hash a lazy ByteString, creating a digest
hash' :: Hash ctx d => ByteString -> d Source
Hash a strict ByteString, creating a digest
hashFunc' :: Hash c d => d -> ByteString -> d Source
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 -> d Source
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 where Source
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
:: 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 -> ByteString Source
Electronic Cookbook (encryption)
unEcb :: k -> ByteString -> ByteString Source
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 ByteString Source
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 ByteString Source
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 ByteString Source
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 ByteString Source
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 -> ByteString Source
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 -> ByteString Source
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 ByteLength Source
The number of bytes in a block cipher block
keyLengthBytes :: BlockCipher k => Tagged k ByteLength Source
The number of bytes in a block cipher key (assuming it is an even multiple of 8 bits)
buildKeyIO :: BlockCipher k => IO k Source
Build a symmetric key using the system entropy (see Entropy
)
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 where Source
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 k Source
encryptStream :: k -> iv -> ByteString -> (ByteString, iv) Source
decryptStream :: k -> iv -> ByteString -> (ByteString, iv) Source
buildStreamKeyIO :: StreamCipher k iv => IO k Source
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 where Source
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 |
:: CryptoRandomGen g | |
=> g | |
-> v | |
-> ByteString | |
-> Either GenError (ByteString, g) | Asymetric decryption |
publicKeyLength :: p -> BitLength Source
privateKeyLength :: v -> BitLength Source
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 where Source
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 -> Bool Source
buildSigningPair :: CryptoRandomGen g => g -> BitLength -> Either GenError ((p, v), g) Source
signingKeyLength :: v -> BitLength Source
verifyingKeyLength :: p -> BitLength Source
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 k Source
Obtain an IV
made only of zeroes
incIV :: BlockCipher k => IV k -> IV k Source
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.
chunkFor :: BlockCipher k => k -> ByteString -> [ByteString] Source
chunkFor' :: BlockCipher k => k -> ByteString -> [ByteString] Source
module Crypto.Util
module Crypto.Types