hkdf

Pure Haskell HMAC-based KDF (docs.ppad.tech/hkdf).
git clone git://git.ppad.tech/hkdf.git
Log | Files | Refs | README | LICENSE

HMAC.hs (3229B)


      1 {-# OPTIONS_HADDOCK prune #-}
      2 {-# LANGUAGE BangPatterns #-}
      3 {-# LANGUAGE ViewPatterns #-}
      4 
      5 -- |
      6 -- Module: Crypto.KDF.HMAC
      7 -- Copyright: (c) 2024 Jared Tobin
      8 -- License: MIT
      9 -- Maintainer: Jared Tobin <jared@ppad.tech>
     10 --
     11 -- A pure HKDF implementation, as specified by
     12 -- [RFC5869](https://datatracker.ietf.org/doc/html/rfc5869).
     13 
     14 module Crypto.KDF.HMAC (
     15     -- * HMAC synonym
     16     HMAC
     17 
     18     -- * HMAC-based KDF
     19   , derive
     20 
     21     -- internals
     22   , extract
     23   , expand
     24   , HMACEnv
     25   ) where
     26 
     27 import qualified Data.ByteString as BS
     28 import qualified Data.ByteString.Builder as BSB
     29 import qualified Data.ByteString.Internal as BI
     30 import Data.Word (Word64)
     31 
     32 fi :: (Integral a, Num b) => a -> b
     33 fi = fromIntegral
     34 {-# INLINE fi #-}
     35 
     36 -- NB following synonym really only exists to make haddocks more
     37 --    readable
     38 
     39 -- | A HMAC function, taking a key as the first argument and the input
     40 --   value as the second, producing a MAC digest.
     41 --
     42 --   >>> import qualified Crypto.Hash.SHA256 as SHA256
     43 --   >>> :t SHA256.hmac
     44 --   SHA256.hmac :: BS.ByteString -> BS.ByteString -> BS.ByteString
     45 --   >>> SHA256.hmac "my HMAC key" "my HMAC input"
     46 --   <256-bit MAC>
     47 type HMAC = BS.ByteString -> BS.ByteString -> BS.ByteString
     48 
     49 -- HMAC function and its associated outlength
     50 data HMACEnv = HMACEnv
     51                  !HMAC
     52   {-# UNPACK #-} !Int
     53 
     54 extract
     55   :: HMACEnv
     56   -> BS.ByteString  -- ^ salt
     57   -> BS.ByteString  -- ^ input keying material
     58   -> BS.ByteString  -- ^ pseudorandom key
     59 extract (HMACEnv hmac hashlen) salt@(BI.PS _ _ l) ikm
     60   | l == 0    = hmac (BS.replicate hashlen 0x00) ikm
     61   | otherwise = hmac salt ikm
     62 {-# INLINE extract #-}
     63 
     64 expand
     65   :: HMACEnv
     66   -> BS.ByteString  -- ^ optional context and application-specific info
     67   -> Word64         -- ^ bytelength of output keying material
     68   -> BS.ByteString  -- ^ pseudorandom key
     69   -> BS.ByteString  -- ^ output keying material
     70 expand (HMACEnv hmac hashlen) info (fi -> len) prk
     71     | len > 255 * hashlen = error "ppad-hkdf (expand): invalid outlength"
     72     | otherwise = BS.take len (go (1 :: Int) mempty mempty)
     73   where
     74     n = ceiling ((fi len :: Double) / (fi hashlen :: Double)) :: Int
     75     go !j t !tl
     76       | j > fi n = BS.toStrict (BSB.toLazyByteString t)
     77       | otherwise =
     78           let nt = hmac prk (tl <> info <> BS.singleton (fi j))
     79           in  go (succ j) (t <> BSB.byteString nt) nt
     80 {-# INLINE expand #-}
     81 
     82 -- | Derive a key from a secret, via a HMAC-based key derivation
     83 --   function.
     84 --
     85 --   The /salt/ and /info/ arguments are optional to the KDF, and may
     86 --   be simply passed as 'mempty'. An empty salt will be replaced by
     87 --   /hashlen/ zero bytes.
     88 --
     89 --   >>> import qualified Crypto.Hash.SHA256 as SHA256
     90 --   >>> derive SHA256.hmac "my public salt" mempty 64 "my secret input"
     91 --   <64-byte output keying material>
     92 derive
     93   :: HMAC          -- ^ HMAC function
     94   -> BS.ByteString -- ^ salt
     95   -> BS.ByteString -- ^ optional context and application-specific info
     96   -> Word64        -- ^ bytelength of output keying material (<= 255 * hashlen)
     97   -> BS.ByteString -- ^ input keying material
     98   -> BS.ByteString -- ^ output keying material
     99 derive hmac salt info len = expand env info len . extract env salt where
    100   env = HMACEnv hmac (fi (BS.length (hmac mempty mempty)))
    101