commit 960823c7f28a24c6a954e8edbd4053ae60abd413
parent 011682c7c8ede1ce36e98b9b411b94cdcb7777fe
Author: Jared Tobin <jared@jtobin.io>
Date: Mon, 24 Feb 2025 10:08:48 +0400
test: skeleton
Diffstat:
M | test/Main.hs | | | 64 | +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++- |
M | test/Wycheproof.hs | | | 64 | +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++- |
2 files changed, 126 insertions(+), 2 deletions(-)
diff --git a/test/Main.hs b/test/Main.hs
@@ -1,4 +1,66 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
+
module Main where
+import Control.Exception
+import qualified Crypto.Hash.SHA256 as SHA256
+import qualified Crypto.Hash.SHA512 as SHA512
+import qualified Crypto.KDF.PBKDF as KDF
+import qualified Data.ByteString as BS
+import qualified Data.Aeson as A
+import qualified Data.Text.IO as TIO
+import Test.Tasty
+import Test.Tasty.HUnit
+import qualified Wycheproof as W
+
main :: IO ()
-main = pure ()
+main = do
+ wycheproof_hmacsha256 <- TIO.readFile "etc/pbkdf2_hmacsha256_test.json"
+ wycheproof_hmacsha512 <- TIO.readFile "etc/pbkdf2_hmacsha512_test.json"
+ let wycheproofs = do
+ a <- A.decodeStrictText wycheproof_hmacsha256 :: Maybe W.Wycheproof
+ b <- A.decodeStrictText wycheproof_hmacsha512 :: Maybe W.Wycheproof
+ pure (a, b)
+ case wycheproofs of
+ Nothing -> error "couldn't parse wycheproof vectors"
+ Just (w256, w512) -> defaultMain $ testGroup "ppad-pbkdf" [
+ wycheproof_tests SHA256 w256
+ , wycheproof_tests SHA512 w512
+ ]
+
+data Hash = SHA256 | SHA512
+ deriving Show
+
+wycheproof_tests :: Hash -> W.Wycheproof -> TestTree
+wycheproof_tests h W.Wycheproof {..} =
+ testGroup ("wycheproof vectors (pbkdf, " <> show h <> ")") $
+ fmap (execute_group h) wp_testGroups
+
+execute_group :: Hash -> W.PbkdfTestGroup -> TestTree
+execute_group h W.PbkdfTestGroup {..} =
+ testGroup mempty (fmap (execute h) ptg_tests)
+
+execute :: Hash -> W.PbkdfTest -> TestTree
+execute h W.PbkdfTest {..} = testCase t_msg $ do
+ let pas = pt_password
+ sal = pt_salt
+ cow = pt_iterationCount
+ siz = pt_dkLen
+ pec = pt_dk
+ if pt_result == "invalid"
+ then do
+ out <- try (pure $! KDF.derive hmac pas sal cow siz)
+ :: IO (Either ErrorCall BS.ByteString)
+ case out of
+ Left _ -> assertBool "invalid" True
+ Right o -> assertBool "invalid" (pec /= o)
+ else do
+ let out = KDF.derive hmac pas sal cow siz
+ assertEqual mempty pec out
+ where
+ hmac = case h of
+ SHA256 -> SHA256.hmac
+ SHA512 -> SHA512.hmac
+ t_msg = "test " <> show pt_tcId -- XX embellish
+
diff --git a/test/Wycheproof.hs b/test/Wycheproof.hs
@@ -1,2 +1,64 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Wycheproof (
+ Wycheproof(..)
+ , PbkdfTestGroup(..)
+ , PbkdfTest(..)
+ ) where
+
+import Data.Aeson ((.:))
+import qualified Data.Aeson as A
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Base16 as B16
+import qualified Data.Text as T
+import qualified Data.Text.Encoding as TE
+import Data.Word (Word32, Word64)
+
+data Wycheproof = Wycheproof {
+ wp_numberOfTests :: !Int
+ , wp_testGroups :: ![PbkdfTestGroup]
+ } deriving Show
+
+instance A.FromJSON Wycheproof where
+ parseJSON = A.withObject "Wycheproof" $ \m -> Wycheproof
+ <$> m .: "numberOfTests"
+ <*> m .: "testGroups"
+
+data PbkdfTestGroup = PbkdfTestGroup {
+ ptg_type :: !T.Text
+ , ptg_tests :: ![PbkdfTest]
+ } deriving Show
+
+instance A.FromJSON PbkdfTestGroup where
+ parseJSON = A.withObject "PbkdfTestGroup" $ \m -> PbkdfTestGroup
+ <$> m .: "type"
+ <*> m .: "tests"
+
+data PbkdfTest = PbkdfTest {
+ pt_tcId :: !Int
+ , pt_comment :: !T.Text
+ , pt_password :: !BS.ByteString
+ , pt_salt :: !BS.ByteString
+ , pt_iterationCount :: !Word64
+ , pt_dkLen :: !Word32
+ , pt_dk :: !BS.ByteString
+ , pt_result :: !T.Text
+ } deriving Show
+
+decodehex :: T.Text -> BS.ByteString
+decodehex t = case B16.decode (TE.encodeUtf8 t) of
+ Nothing -> error "bang"
+ Just bs -> bs
+
+instance A.FromJSON PbkdfTest where
+ parseJSON = A.withObject "PbkdfTest" $ \m -> PbkdfTest
+ <$> m .: "tcId"
+ <*> m .: "comment"
+ <*> fmap decodehex (m .: "password")
+ <*> fmap decodehex (m .: "salt")
+ <*> m .: "iterationCount"
+ <*> m .: "dkLen"
+ <*> fmap decodehex (m .: "dk")
+ <*> m .: "result"
+
-module Wycheproof where