Safe Haskell | None |
---|---|
Language | Haskell98 |
The module mirrors Crypto.Classes except that errors are thrown as
exceptions instead of having returning types of Either error result
or Maybe result
.
NB This module is experimental and might go away or be re-arranged.
- 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
- 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)
- getIVIO :: BlockCipher k => IO (IV k)
- blockSizeBytes :: BlockCipher k => Tagged k ByteLength
- keyLengthBytes :: BlockCipher k => Tagged k ByteLength
- buildKeyIO :: BlockCipher k => IO k
- class AsymCipher p v | p -> v, v -> p where
- publicKeyLength :: p -> BitLength
- privateKeyLength :: v -> BitLength
- buildKeyPairIO :: AsymCipher p v => BitLength -> IO (Either GenError (p, v))
- class (Serialize p, Serialize v) => Signing p v | p -> v, v -> p where
- verify :: p -> ByteString -> ByteString -> Bool
- signingKeyLength :: v -> BitLength
- verifyingKeyLength :: p -> BitLength
- incIV :: BlockCipher k => IV k -> IV k
- zeroIV :: BlockCipher k => IV k
- class CryptoRandomGen g where
- genSeedLength :: Tagged g ByteLength
- reseedInfo :: g -> ReseedInfo
- reseedPeriod :: g -> ReseedInfo
- newGenIO :: IO g
- data GenError
- data ReseedInfo
- data CipherError
- buildKey :: BlockCipher k => ByteString -> k
- getIV :: (BlockCipher k, CryptoRandomGen g) => g -> (IV k, g)
- buildKeyGen :: (CryptoRandomGen g, BlockCipher k) => g -> (k, g)
- buildKeyPair :: (CryptoRandomGen g, AsymCipher p v) => g -> BitLength -> ((p, v), g)
- encryptAsym :: (CryptoRandomGen g, AsymCipher p v) => g -> p -> ByteString -> (ByteString, g)
- decryptAsym :: (CryptoRandomGen g, AsymCipher p v) => g -> v -> ByteString -> (ByteString, g)
- newGen :: CryptoRandomGen g => ByteString -> g
- genBytes :: CryptoRandomGen g => ByteLength -> g -> (ByteString, g)
- genBytesWithEntropy :: CryptoRandomGen g => ByteLength -> ByteString -> g -> (ByteString, g)
- reseed :: CryptoRandomGen g => ByteString -> g -> g
- splitGen :: CryptoRandomGen g => g -> (g, g)
Documentation
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.
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 |
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
)
class AsymCipher p v | p -> v, v -> p where Source
Asymetric ciphers (common ones being RSA or EC based)
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.
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).
verify :: p -> ByteString -> ByteString -> Bool Source
signingKeyLength :: v -> BitLength Source
verifyingKeyLength :: p -> BitLength Source
incIV :: BlockCipher k => IV k -> IV k Source
Increase an IV
by one. This is way faster than decoding,
increasing, encoding
zeroIV :: BlockCipher k => IV k Source
Obtain an IV
made only of zeroes
class CryptoRandomGen g where Source
A class of random bit generators that allows for the possibility of failure, reseeding, providing entropy at the same time as requesting bytes
Minimum complete definition: newGen
, genSeedLength
, genBytes
,
reseed
, reseedInfo
, reseedPeriod
.
genSeedLength :: Tagged g ByteLength Source
Length of input entropy necessary to instantiate or reseed a generator
reseedInfo :: g -> ReseedInfo Source
Indicates how soon a reseed is needed
reseedPeriod :: g -> ReseedInfo Source
Indicates the period between reseeds (constant for most generators).
By default this uses System.Entropy to obtain
entropy for newGen
.
Generator failures should always return the appropriate GenError.
Note GenError
in an instance of exception but wether or not an
exception is thrown depends on if the selected generator (read:
if you don't want execptions from code that uses throw
then
pass in a generator that never has an error for the used functions)
GenErrorOther String | Misc |
RequestedTooManyBytes | Requested more bytes than a single pass can generate (The maximum request is generator dependent) |
RangeInvalid | When using |
NeedReseed | Some generators cease operation after too high a count without a reseed (ex: NIST SP 800-90) |
NotEnoughEntropy | For instantiating new generators (or reseeding) |
NeedsInfiniteSeed | This generator can not be
instantiated or reseeded with a
finite seed (ex: |
data ReseedInfo Source
data CipherError Source
buildKey :: BlockCipher k => ByteString -> k Source
Key construction from raw material (typically including key expansion)
This is a wrapper that can throw a CipherError
on exception.
getIV :: (BlockCipher k, CryptoRandomGen g) => g -> (IV k, g) Source
buildKeyGen :: (CryptoRandomGen g, BlockCipher k) => g -> (k, g) Source
Symmetric key generation
This is a wrapper that can throw a GenError
on exception.
buildKeyPair :: (CryptoRandomGen g, AsymCipher p v) => g -> BitLength -> ((p, v), g) Source
Asymetric key generation
This is a wrapper that can throw a GenError
on exception.
encryptAsym :: (CryptoRandomGen g, AsymCipher p v) => g -> p -> ByteString -> (ByteString, g) Source
Asymmetric encryption
This is a wrapper that can throw a GenError
on exception.
decryptAsym :: (CryptoRandomGen g, AsymCipher p v) => g -> v -> ByteString -> (ByteString, g) Source
Asymmetric decryption
This is a wrapper that can throw a GenError on exception.
newGen :: CryptoRandomGen g => ByteString -> g Source
Instantiate a new random bit generator. The provided
bytestring should be of length >= genSeedLength. If the
bytestring is shorter then the call may fail (suggested
error: NotEnoughEntropy
). If the bytestring is of
sufficent length the call should always succeed.
This is a wrapper that can throw GenError
types as exceptions.
genBytes :: CryptoRandomGen g => ByteLength -> g -> (ByteString, g) Source
genBytes len g
generates a random ByteString of length
len
and new generator. The MonadCryptoRandom
package
has routines useful for converting the ByteString to
commonly needed values (but cereal
or other
deserialization libraries would also work).
This is a wrapper that can throw GenError
types as exceptions.
genBytesWithEntropy :: CryptoRandomGen g => ByteLength -> ByteString -> g -> (ByteString, g) Source
genBytesWithEntropy g i entropy
generates i
random bytes and use
the additional input entropy
in the generation of the requested data
to increase the confidence our generated data is a secure random stream.
This is a wrapper that can throw GenError
types as exceptions.
reseed :: CryptoRandomGen g => ByteString -> g -> g Source
If the generator has produced too many random bytes on its existing
seed it will throw a NeedReseed
exception. In that case, reseed the
generator using this function and a new high-entropy seed of length >=
genSeedLength
. Using bytestrings that are too short can result in an
exception (NotEnoughEntropy
).
splitGen :: CryptoRandomGen g => g -> (g, g) Source
While the safety and wisdom of a splitting function depends on the
properties of the generator being split, several arguments from
informed people indicate such a function is safe for NIST SP 800-90
generators. (see libraries@haskell.org discussion around Sept, Oct
2010). You can find implementations of such generators in the DRBG
package.
This is a wrapper for splitGen
which throws errors as
exceptions.