1-- |
2-- Module      : Crypto.PubKey.MaskGenFunction
3-- License     : BSD-style
4-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
5-- Stability   : experimental
6-- Portability : Good
7--
8{-# LANGUAGE BangPatterns #-}
9module Crypto.PubKey.MaskGenFunction
10    ( MaskGenAlgorithm
11    , mgf1
12    ) where
13
14import           Crypto.Number.Serialize (i2ospOf_)
15import           Crypto.Hash
16import           Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes)
17import qualified Crypto.Internal.ByteArray as B
18
19-- | Represent a mask generation algorithm
20type MaskGenAlgorithm seed output =
21       seed   -- ^ seed
22    -> Int    -- ^ length to generate
23    -> output
24
25-- | Mask generation algorithm MGF1
26mgf1 :: (ByteArrayAccess seed, ByteArray output, HashAlgorithm hashAlg)
27     => hashAlg
28     -> seed
29     -> Int
30     -> output
31mgf1 hashAlg seed len =
32    let !seededCtx = hashUpdate (hashInitWith hashAlg) seed
33     in B.take len $ B.concat $ map (hashCounter seededCtx) [0..fromIntegral (maxCounter-1)]
34  where
35    digestLen     = hashDigestSize hashAlg
36    (chunks,left) = len `divMod` digestLen
37    maxCounter    = if left > 0 then chunks + 1 else chunks
38
39    hashCounter :: HashAlgorithm a => Context a -> Integer -> Digest a
40    hashCounter ctx counter = hashFinalize $ hashUpdate ctx (i2ospOf_ 4 counter :: Bytes)
41