Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exposes the low-level internal details of cryptographic hashes. Do not import this module unless you want to implement a new hash or give a new implementation of an existing hash.
- class (Primitive h, EndianStore h, Encodable h, Eq h, Implementation h ~ SomeHashI h) => Hash h where
- hash :: (Hash h, Recommendation h, PureByteSource src) => src -> h
- hashFile :: (Hash h, Recommendation h) => FilePath -> IO h
- hashSource :: (Hash h, Recommendation h, ByteSource src) => src -> IO h
- hash' :: (PureByteSource src, Hash h) => Implementation h -> src -> h
- hashFile' :: Hash h => Implementation h -> FilePath -> IO h
- hashSource' :: (Hash h, ByteSource src) => Implementation h -> src -> IO h
- data HashI h m = HashI {
- hashIName :: String
- hashIDescription :: String
- compress :: Pointer -> BLOCKS h -> MT m ()
- compressFinal :: Pointer -> BYTES Int -> MT m ()
- compressStartAlignment :: Alignment
- data SomeHashI h = HashM h m => SomeHashI (HashI h m)
- type HashM h m = (Initialisable m (), Extractable m h, Primitive h)
- truncatedI :: (BLOCKS htrunc -> BLOCKS h) -> (mtrunc -> m) -> HashI h m -> HashI htrunc mtrunc
- data HashMemory h = HashMemory {
- hashCell :: MemoryCell h
- messageLengthCell :: MemoryCell (BITS Word64)
- extractLength :: MT (HashMemory h) (BITS Word64)
- updateLength :: LengthUnit u => u -> MT (HashMemory h) ()
- completeHashing :: (Hash h, ByteSource src, HashM h m) => HashI h m -> src -> MT m h
Cryptographic hashes and their implementations.
Each cryptographic hash is a distinct type and are instances of a
the type class Hash
. The standard idiom that we follow for hash
implementations are the following:
HashI
:- This type captures implementations of a the hash. This type is parameterised over the memory element used by the implementation.
SomeHashI
:- This type is the existentially quantified version of
HashI
over its memory element. Thus it exposes only the interface and not the internals of the implementation. TheImplementation
associated type of a hash is the typeSomeHashI
To support a new hash, a developer needs to:
- Define a new type which captures the result of hashing. This
type should be an instance of the class
Hash
. - Define an implementation, i.e. a value of the type
SomeHashI
. - Define a recommended implementation, i.e. an instance of the
type class
Recommendation
class (Primitive h, EndianStore h, Encodable h, Eq h, Implementation h ~ SomeHashI h) => Hash h where Source #
Type class capturing a cryptographic hash.
additionalPadBlocks :: h -> BLOCKS h Source #
Cryptographic hashes can be computed for messages that are not a multiple of the block size. This combinator computes the maximum size of padding that can be attached to a message.
:: (Hash h, Recommendation h, PureByteSource src) | |
=> src | Message |
-> h |
Compute the hash of a pure byte source like, ByteString
.
:: (Hash h, Recommendation h) | |
=> FilePath | File to be hashed |
-> IO h |
Compute the hash of file.
:: (Hash h, Recommendation h, ByteSource src) | |
=> src | Message |
-> IO h |
Compute the hash of a generic byte source.
Computing hashes using non-standard implementations.
:: (PureByteSource src, Hash h) | |
=> Implementation h | Implementation |
-> src | the message as a byte source. |
-> h |
Similar to hash
but the user can specify the implementation to
use.
:: Hash h | |
=> Implementation h | Implementation |
-> FilePath | File to be hashed |
-> IO h |
Similar to hashFile' but the user can specify the implementation to use.
hashSource' :: (Hash h, ByteSource src) => Implementation h -> src -> IO h Source #
Similar to hashSource
but the user can specify the
implementation to use.
Hash implementations.
The Hash implementation. Implementations should ensure the following.
- The action
compress impl ptr blks
should only read till theblks
offset starting at ptr and never write any data. - The action
padFinal impl ptr byts
should touch at most⌈byts/blocksize⌉ + padBlocks
blocks starting at ptr. It should not write anything till thebyts
offset but may write stuff beyond that.
An easy to remember this rule is to remember that computing hash of a payload should not modify the payload.
HashI | |
|
Describable (HashI h m) Source # | |
BlockAlgorithm (HashI h m) Source # | |
Some implementation of a given hash. The existentially quantification allows us freedom to choose the best memory type suitable for each implementations.
Describable (SomeHashI h) Source # | |
BlockAlgorithm (SomeHashI h) Source # | |
type HashM h m = (Initialisable m (), Extractable m h, Primitive h) Source #
The constraints that a memory used by a hash implementation should satisfy.
Implementation of truncated hashes.
truncatedI :: (BLOCKS htrunc -> BLOCKS h) -> (mtrunc -> m) -> HashI h m -> HashI htrunc mtrunc Source #
Certain hashes are essentially bit-truncated versions of other hashes. For example, SHA224 is obtained from SHA256 by dropping the last 32-bits. This combinator can be used build an implementation of truncated hash from the implementation of its parent hash.
Memory used by most hashes.
data HashMemory h Source #
Computing cryptographic hashes usually involves chunking the message into blocks and compressing one block at a time. Usually this compression makes use of the hash of the previous block and the length of the message seen so far to compressing the current block. Most implementations therefore need to keep track of only hash and the length of the message seen so. This memory can be used in such situations.
HashMemory | |
|
Storable h => Memory (HashMemory h) Source # | |
Storable h => Extractable (HashMemory h) h Source # | |
Storable h => Initialisable (HashMemory h) h Source # | |
Initialisable (HashMemory SHA1) () Source # | |
Initialisable (HashMemory SHA256) () Source # | |
Initialisable (HashMemory SHA512) () Source # | |
extractLength :: MT (HashMemory h) (BITS Word64) Source #
Extract the length of the message hashed so far.
updateLength :: LengthUnit u => u -> MT (HashMemory h) () Source #
Update the message length by a given amount.
Some low level functions.
completeHashing :: (Hash h, ByteSource src, HashM h m) => HashI h m -> src -> MT m h Source #
Gives a memory action that completes the hashing procedure with the rest of the source. Useful to compute the hash of a source with some prefix (like in the HMAC procedure).