sha256-0.1.0.2: A modern binding to SHA256, HMAC, HKDF, and PBKDF2
Copyright(c) 2024 Auth Global
LicenseApache2
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.Sha256.Hmac

Description

An implementation of HMAC-SHA256 that supports precomputed keys, streaming, backtracking, bitstring inputs, and (de)serialization of intermediate states.

Synopsis

Documentation

hmac :: HmacKeyPlain -> ByteString -> ByteString Source #

A simple interface to HMAC-SHA256. Note that this function was written to make partial application an efficient way to compute the hmac of multiple messages with exactly the same key:

    let myHash = hmac "my-key"
     in (myHash "message 1", myHash "message 2", myHash "message 3")
  

This typically saves two SHA-256 blocks per reused function application. Thus this example saves four block computations from the two reused calls to myHash in this example.

Initializing the myHash closure requires computing two SHA-256 blocks. Applying the closure requires two further SHA-256 blocks per message, as every message is less than 56 bytes long. Thus the total computation requires 8 SHA-256 blocks with reuse, or 12 SHA-256 blocks without reuse.

Key reuse can save four or more block computations per application if the reused key is longer than 64 bytes. I don't recommend using HMAC keys that are longer than 64 bytes, as all such keys can be trivially replaced with the SHA256 hash of the key, which is only 32 bytes long.

This high-level interface is implemented using hmacCtx_finalize, hmacKeyHashed_run, and hmacKeyHashed composed in a point-free style in order to help ensure key reuse works as expected.

data HmacKey Source #

A cached, precomputed hmac key. It comes in two flavors, one that remembers the plaintext key, and one that doesn't, remembering only the precomputed hmac key.

Computing an hmac key typically requires two SHA256 blocks, unless the key itself is more than 64 bytes, in which case precomputing the key will require at least four SHA256 blocks.

Instances

Instances details
Eq HmacKey Source # 
Instance details

Defined in Crypto.Sha256.Hmac.Implementation

Methods

(==) :: HmacKey -> HmacKey -> Bool #

(/=) :: HmacKey -> HmacKey -> Bool #

Ord HmacKey Source # 
Instance details

Defined in Crypto.Sha256.Hmac.Implementation

hmacKey_hashed :: HmacKeyPlain -> HmacKey Source #

Precompute an HmacKey without retaining the plaintext input, equivalent to 'hmacKey_forgetInput . hmacKey'

hmacKey_toPlain :: HmacKey -> Maybe HmacKeyPlain Source #

If the plaintext hmac key has been remembered by the precomputed key, return it. Otherwise return Nothing. Keys precomputed by hmacKey retain the plaintext, which can subsequently be forgotten by hmacKey_forgetPlain. Alternatively, keys precomputed by hmacKey_hashed never retains the plaintext key in the first place.

hmacKey_forgetPlain :: HmacKey -> HmacKey Source #

Forget any plaintext hmac keys being retained by a given precomputed key, meaning that for all x, hmacKey_toPlain (hmacKey_forgetPlain x) == Nothing.

This is potentially useful when implementing PBKDF2, as the plaintext password can immediately be replaced with a precomputed hmac key, even before key-stretching is complete. Note that the precomputed hmac key does provide a fast brute-force attack on the plaintext key, typically as little as 1 SHA256 block, so this cannot be relied upon for secrecy if the hmac key is potentially guessable, such as a weak password or a non-secret salt.

hmacKeyLike_byteCount :: HmacKeyLike -> Word64 Source #

how many bytes have been fed into the SHA256 state machine? This is always 64 more bytes than hmac's "message" input. If hmacKeyLike_toKey x == Just ..., then hmacKeyLike_byteCount x == 64. If hmacKeyLike_toKey x == Nothing, then this returns a multiple of 64 that is greater or equal to 128.

data HmacKeyHashed Source #

A precomputed HMAC key. This structure is 64 bytes long, and consists of two SHA256 hashes.

Computing an HMAC key typically costs two SHA256 blocks. No additional blocks are incurred for keys that are 64 bytes or less in length. Keys that are longer than 64 bytes long must be first hashed with SHA256 before the key can be derived, incurring extra block comptuations.

It is not uncommon that implementations of PBKDF2, HKDF, etc unnecessarily redo this computation even though a single HMAC key is used repeatedly.

Technically these "hashes" are unfinished SHA-256 states, as the standard end-of-message padding has yet to be applied. Thus you can't compute these hashes using the most common command-line tools like sha256sum.

The lack of end-of-message padding is also why precomputing HMAC keys on keys up to 64 bytes only requires one SHA-256 block computation for each of the two pads, whereas more typically the boundary for extra block computations happens between the 55th and 56th byte due to end-of-message padding.

data HmacKeyPrefixed Source #

Halfway between an HmacKeyHashed and an HmacCtx. It's both an HmacKeyHashed that's gained a counter, and a HmacCtx that's guaranteed to contain no unprocessed input data.

data HmacCtx Source #

Fixed-size context representing the state of a partial HMAC computation with a complete HMAC key and a partial message parameter. This maintains a buffer of up to 63 unprocessed bytes, so that you may feed it arbitrary bytestring without dealing with buffer boundaries.

Instances

Instances details
Eq HmacCtx Source # 
Instance details

Defined in Crypto.Sha256.Hmac.Implementation

Methods

(==) :: HmacCtx -> HmacCtx -> Bool #

(/=) :: HmacCtx -> HmacCtx -> Bool #

Ord HmacCtx Source # 
Instance details

Defined in Crypto.Sha256.Hmac.Implementation

hmacCtx_init :: HmacKey -> HmacCtx Source #

Initialize a new empty HMAC context from a precomputed HMAC key.

hmacCtx_update :: HmacCtx -> ByteString -> HmacCtx Source #

Append a bytestring onto the end of the message argument to HMAC.

hmacCtx_updates :: Foldable f => HmacCtx -> f ByteString -> HmacCtx Source #

Append zero or more bytestrings onto the end of the message argument to HMAC.

hmacCtx_finalize :: HmacCtx -> HashString Source #

Finish computing the final 32-byte hash for an HMAC context.

hmacCtx_finalizeBits :: ByteString -> Word64 -> HmacCtx -> HashString Source #

Append any arbitrary bitstring onto the end of an HMAC context, and finish computing the final 32-byte hash.

hmacCtx_finalizeBits_toByteString :: ByteString -> Word64 -> HmacCtx -> ByteString Source #

Append any arbitrary bitstring onto the end of an HMAC context, and finish computing the final 32-byte hash.