hkdf

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

Main.hs (2124B)


      1 {-# LANGUAGE OverloadedStrings #-}
      2 {-# LANGUAGE RecordWildCards #-}
      3 
      4 module Main where
      5 
      6 import Control.Exception
      7 import qualified Crypto.Hash.SHA256 as SHA256
      8 import qualified Crypto.Hash.SHA512 as SHA512
      9 import qualified Crypto.KDF.HMAC as KDF
     10 import qualified Data.ByteString as BS
     11 import qualified Data.Aeson as A
     12 import qualified Data.Text.IO as TIO
     13 import Test.Tasty
     14 import Test.Tasty.HUnit
     15 import qualified Wycheproof as W
     16 
     17 main :: IO ()
     18 main = do
     19   wycheproof_sha256 <- TIO.readFile "etc/hkdf_sha256_test.json"
     20   wycheproof_sha512 <- TIO.readFile "etc/hkdf_sha512_test.json"
     21   let wycheproofs = do
     22         a <- A.decodeStrictText wycheproof_sha256 :: Maybe W.Wycheproof
     23         b <- A.decodeStrictText wycheproof_sha512 :: Maybe W.Wycheproof
     24         pure (a, b)
     25   case wycheproofs of
     26     Nothing -> error "couldn't parse wycheproof vectors"
     27     Just (w256, w512) -> defaultMain $ testGroup "ppad-hkdf" [
     28         wycheproof_tests SHA256 w256
     29       , wycheproof_tests SHA512 w512
     30       ]
     31 
     32 data Hash = SHA256 | SHA512
     33   deriving Show
     34 
     35 wycheproof_tests :: Hash -> W.Wycheproof -> TestTree
     36 wycheproof_tests h W.Wycheproof {..} =
     37   testGroup ("wycheproof vectors (hkdf, " <> show h <> ")") $
     38     fmap (execute_group h) wp_testGroups
     39 
     40 execute_group :: Hash -> W.HkdfTestGroup -> TestTree
     41 execute_group h W.HkdfTestGroup {..} =
     42     testGroup msg (fmap (execute h) htg_tests)
     43   where
     44     msg = "keysize " <> show htg_keySize
     45 
     46 execute :: Hash -> W.HkdfTest -> TestTree
     47 execute h W.HkdfTest {..} = testCase t_msg $ do
     48     let ikm = ht_ikm
     49         sal = ht_salt
     50         inf = ht_info
     51         siz = ht_size
     52         pec = ht_okm
     53     if   ht_result == "invalid"
     54     then do
     55       out <- try (pure $! KDF.derive hmac sal inf siz ikm)
     56                :: IO (Either ErrorCall BS.ByteString)
     57       case out of
     58         Left _  -> assertBool "invalid" True
     59         Right o -> assertBool "invalid" (pec /= o)
     60     else do
     61       let out = KDF.derive hmac sal inf siz ikm
     62       assertEqual mempty pec out
     63   where
     64     hmac = case h of
     65       SHA256 -> SHA256.hmac
     66       SHA512 -> SHA512.hmac
     67     t_msg = "test " <> show ht_tcId -- XX embellish
     68