Copyright | (c) 2024 Auth Global |
---|---|
License | Apache2 |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Crypto.PHKDF.Primitives
Description
Synopsis
- data HmacKey
- hmacKey :: HmacKeyPlain -> HmacKey
- data PhkdfCtx
- phkdfCtx :: ByteString -> PhkdfCtx
- phkdfCtx_init :: HmacKey -> PhkdfCtx
- phkdfCtx_initHashed :: HmacKeyHashed -> PhkdfCtx
- phkdfCtx_initPrefixed :: ByteString -> HmacKeyPrefixed -> PhkdfCtx
- phkdfCtx_initLike :: HmacKeyLike -> PhkdfCtx
- phkdfCtx_hmacKeyPlain :: PhkdfCtx -> Maybe HmacKeyPlain
- phkdfCtx_hmacKeyHashed :: PhkdfCtx -> Maybe HmacKeyHashed
- phkdfCtx_hmacKeyPrefixed :: PhkdfCtx -> HmacKeyPrefixed
- phkdfCtx_hmacKey :: PhkdfCtx -> Maybe HmacKey
- phkdfCtx_hmacKeyLike :: PhkdfCtx -> HmacKeyLike
- phkdfCtx_toResetHmacCtx :: PhkdfCtx -> HmacCtx
- phkdfCtx_reset :: PhkdfCtx -> PhkdfCtx
- phkdfCtx_feedArg :: ByteString -> PhkdfCtx -> PhkdfCtx
- phkdfCtx_feedArgs :: Foldable f => f ByteString -> PhkdfCtx -> PhkdfCtx
- phkdfCtx_feedArgsBy :: Foldable f => (a -> ByteString) -> f a -> PhkdfCtx -> PhkdfCtx
- phkdfCtx_feedArgConcat :: Foldable f => f ByteString -> PhkdfCtx -> PhkdfCtx
- phkdfCtx_finalize :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> ByteString
- phkdfCtx_finalizeHmac :: PhkdfCtx -> ByteString
- phkdfCtx_toHmacCtx :: PhkdfCtx -> HmacCtx
- phkdfCtx_toStream :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> Stream ByteString
- phkdfCtx_toGen :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> PhkdfGen
- data PhkdfSlowCtx
- phkdfSlowCtx_extract :: (Int -> ByteString) -> Word32 -> ByteString -> ByteString -> Word32 -> PhkdfCtx -> PhkdfSlowCtx
- phkdfSlowCtx_feedArg :: ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
- phkdfSlowCtx_feedArgs :: Foldable f => f ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx
- phkdfSlowCtx_finalize :: (Int -> ByteString) -> PhkdfSlowCtx -> ByteString
- phkdfSlowCtx_toStream :: (Int -> ByteString) -> PhkdfSlowCtx -> Stream ByteString
- data PhkdfGen
- phkdfGen :: ByteString -> ByteString -> Word32 -> ByteString -> PhkdfGen
- phkdfGen_init :: HmacKey -> ByteString -> Word32 -> ByteString -> PhkdfGen
- phkdfGen_initHashed :: HmacKeyHashed -> ByteString -> Word32 -> ByteString -> PhkdfGen
- phkdfGen_initPrefixed :: HmacKeyPrefixed -> ByteString -> Word32 -> ByteString -> PhkdfGen
- phkdfGen_initLike :: HmacKeyLike -> ByteString -> Word32 -> ByteString -> PhkdfGen
- phkdfGen_hmacKeyPlain :: PhkdfGen -> Maybe HmacKeyPlain
- phkdfGen_hmacKeyHashed :: PhkdfGen -> Maybe HmacKeyHashed
- phkdfGen_hmacKeyPrefixed :: PhkdfGen -> HmacKeyPrefixed
- phkdfGen_hmacKey :: PhkdfGen -> Maybe HmacKey
- phkdfGen_hmacKeyLike :: PhkdfGen -> HmacKeyLike
- phkdfGen_read :: PhkdfGen -> (ByteString, PhkdfGen)
- phkdfGen_peek :: PhkdfGen -> Maybe ByteString
- phkdfGen_toStream :: PhkdfGen -> Stream ByteString
Documentation
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
Eq HmacKey | |
Ord HmacKey | |
Defined in Crypto.Sha256.Hmac.Implementation |
hmacKey :: HmacKeyPlain -> HmacKey #
phkdfCtx :: ByteString -> PhkdfCtx Source #
initialize an empty phkdfStream
context from a plaintext HMAC key.
phkdfCtx_init :: HmacKey -> PhkdfCtx Source #
initialize an empty phkdfStream
context from a plaintext or precomputed HMAC key.
phkdfCtx_initHashed :: HmacKeyHashed -> PhkdfCtx Source #
initialize an empty phkdfStream
context from a precomputed HMAC key.
phkdfCtx_initPrefixed :: ByteString -> HmacKeyPrefixed -> PhkdfCtx Source #
initialize an empty phkdfStream
context from a buffer-prefixed HMAC key.
phkdfCtx_initLike :: HmacKeyLike -> PhkdfCtx Source #
initialize an empty phkdfStream
context from a plaintext, precomputed, or buffer-prefixed HMAC key.
phkdfCtx_toResetHmacCtx :: PhkdfCtx -> HmacCtx Source #
initialize a new empty HMAC context from the key originally supplied to the PHKDF context, discarding all arguments already added.
phkdfCtx_reset :: PhkdfCtx -> PhkdfCtx Source #
initialize a new empty phkdfStream
context from the HMAC key
originally supplied to the context, discarding all arguments already added.
phkdfCtx_feedArg :: ByteString -> PhkdfCtx -> PhkdfCtx Source #
append a single string onto the end of phkdfStream
's list of
arguments.
phkdfCtx_feedArgs :: Foldable f => f ByteString -> PhkdfCtx -> PhkdfCtx Source #
append zero or more strings onto the end of phkdfStream
's list of
arguments.
phkdfCtx_feedArgsBy :: Foldable f => (a -> ByteString) -> f a -> PhkdfCtx -> PhkdfCtx Source #
phkdfCtx_feedArgConcat :: Foldable f => f ByteString -> PhkdfCtx -> PhkdfCtx Source #
phkdfCtx_finalize :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> ByteString Source #
close out a phkdfStream
context using the first mode of operation,
examining only the first output block and discarding the rest of the
stream.
phkdfCtx_finalizeHmac :: PhkdfCtx -> ByteString Source #
"improperly" close out a PhkdfCtx
as if it were a call to hmac
instead
of phkdfStream
, though with a TupleHash message encoding.
phkdfCtx_toHmacCtx :: PhkdfCtx -> HmacCtx Source #
Turn a PhkdfCtx
into a incomplete call to hmac
, with the option of
adding additional data to the end of the message that need not be
TupleHash encoded.
phkdfCtx_toStream :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> Stream ByteString Source #
close out a phkdfStream
context with a given counter and tag
phkdfCtx_toGen :: (Int -> ByteString) -> Word32 -> ByteString -> PhkdfCtx -> PhkdfGen Source #
data PhkdfSlowCtx Source #
phkdfSlowCtx_extract :: (Int -> ByteString) -> Word32 -> ByteString -> ByteString -> Word32 -> PhkdfCtx -> PhkdfSlowCtx Source #
close out a phkdfStream
context with a call to phkdfSlowExtract
,
providing the counter, tag, fnName
, and number of rounds to compute.
Note that fnName
is truncated to a length of 25-29 bytes long,
depending upon the number of rounds specified. Thus the fnName
is
primarily intended to be a protocol constant.
phkdfSlowCtx_feedArg :: ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx Source #
Add a tweak to a call to phkdfSlowExtract
.
phkdfSlowCtx_feedArgs :: Foldable f => f ByteString -> PhkdfSlowCtx -> PhkdfSlowCtx Source #
Add zero or more tweaks to a call to phkdfSlowExtract
.
phkdfSlowCtx_finalize :: (Int -> ByteString) -> PhkdfSlowCtx -> ByteString Source #
finalize a call to phkdfSlowExtract
, discarding all but the first block
of the output stream
phkdfSlowCtx_toStream :: (Int -> ByteString) -> PhkdfSlowCtx -> Stream ByteString Source #
finalize a call to phkdfSlowExtract
phkdfGen :: ByteString -> ByteString -> Word32 -> ByteString -> PhkdfGen Source #
phkdfGen_init :: HmacKey -> ByteString -> Word32 -> ByteString -> PhkdfGen Source #
phkdfGen_initHashed :: HmacKeyHashed -> ByteString -> Word32 -> ByteString -> PhkdfGen Source #
phkdfGen_initPrefixed :: HmacKeyPrefixed -> ByteString -> Word32 -> ByteString -> PhkdfGen Source #
phkdfGen_initLike :: HmacKeyLike -> ByteString -> Word32 -> ByteString -> PhkdfGen Source #
phkdfGen_read :: PhkdfGen -> (ByteString, PhkdfGen) Source #
phkdfGen_peek :: PhkdfGen -> Maybe ByteString Source #