Copyright | Copyright © 2022-2024 Lars Kuhtz <lakuhtz@gmail.com> |
---|---|
License | MIT |
Maintainer | Lars Kuhtz <lakuhtz@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Test.Hash.SHA3
Description
Details can be found here:
Response files are available here:
Synopsis
- data MsgFile = MsgFile {
- _msgDescription :: !Text
- _msgL :: !Natural
- _msgVectors :: !(Vector MsgVector)
- data MsgVector = MsgVector {
- _msgLen :: !Natural
- _msgMsg :: !ByteString
- _msgMd :: !ByteString
- sha3_224LongMsg :: MsgFile
- sha3_256LongMsg :: MsgFile
- sha3_384LongMsg :: MsgFile
- sha3_512LongMsg :: MsgFile
- sha3_224ShortMsg :: MsgFile
- sha3_256ShortMsg :: MsgFile
- sha3_384ShortMsg :: MsgFile
- sha3_512ShortMsg :: MsgFile
- data MonteFile = MonteFile {
- _monteDescription :: !Text
- _monteL :: !Natural
- _monteSeed :: !ByteString
- _monteVectors :: !(Vector MonteVector)
- data MonteVector = MonteVector {
- _monteCount :: !Natural
- _monteMd :: !ByteString
- sha3_224Monte :: MonteFile
- sha3_256Monte :: MonteFile
- sha3_384Monte :: MonteFile
- sha3_512Monte :: MonteFile
- msgTest :: (ByteString -> ByteString) -> MsgFile -> Bool
- msgAssert :: Monad m => (String -> ByteString -> ByteString -> m ()) -> (ByteString -> ByteString) -> MsgFile -> m ()
- monteTest :: (ByteString -> ByteString) -> MonteFile -> Bool
- monteAssert :: Monad m => (String -> ByteString -> ByteString -> m ()) -> (ByteString -> ByteString) -> MonteFile -> m ()
Selected Long Messages Test for Byte-Oriented Implementations
Constructors
MsgFile | |
Fields
|
Constructors
MsgVector | |
Fields
|
Instances
Show MsgVector Source # | |
Eq MsgVector Source # | |
Ord MsgVector Source # | |
Lift MsgVector Source # | |
sha3_224LongMsg :: MsgFile Source #
SHA3_224LongMsg.rsp
sha3_256LongMsg :: MsgFile Source #
SHA3_256LongMsg.rsp
sha3_384LongMsg :: MsgFile Source #
SHA3_384LongMsg.rsp
sha3_512LongMsg :: MsgFile Source #
SHA3_512LongMsg.rsp
Selected Short Messages Test for Byte-Oriented Implementations
sha3_224ShortMsg :: MsgFile Source #
SHA3_224ShortMsg.rsp
sha3_256ShortMsg :: MsgFile Source #
SHA3_256ShortMsg.rsp
sha3_384ShortMsg :: MsgFile Source #
SHA3_384ShortMsg.rsp
sha3_512ShortMsg :: MsgFile Source #
SHA3_512ShortMsg.rsp
The Pseudorandomly Generated Messages (Monte Carlo) Tests
Constructors
MonteFile | |
Fields
|
Instances
Show MonteFile Source # | |
Eq MonteFile Source # | |
Ord MonteFile Source # | |
Lift MonteFile Source # | |
data MonteVector Source #
Constructors
MonteVector | |
Fields
|
Instances
Show MonteVector Source # | |
Defined in Test.Hash.Internal Methods showsPrec :: Int -> MonteVector -> ShowS # show :: MonteVector -> String # showList :: [MonteVector] -> ShowS # | |
Eq MonteVector Source # | |
Defined in Test.Hash.Internal | |
Ord MonteVector Source # | |
Defined in Test.Hash.Internal Methods compare :: MonteVector -> MonteVector -> Ordering # (<) :: MonteVector -> MonteVector -> Bool # (<=) :: MonteVector -> MonteVector -> Bool # (>) :: MonteVector -> MonteVector -> Bool # (>=) :: MonteVector -> MonteVector -> Bool # max :: MonteVector -> MonteVector -> MonteVector # min :: MonteVector -> MonteVector -> MonteVector # | |
Lift MonteVector Source # | |
Defined in Test.Hash.Internal Methods lift :: Quote m => MonteVector -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => MonteVector -> Code m MonteVector # |
sha3_224Monte :: MonteFile Source #
Monte Carlo SHA-3 Hash Function Tests for Hashing Byte-Oriented Messages
SHA3_224Monte.rsp
sha3_256Monte :: MonteFile Source #
SHA3_256Monte.rsp
sha3_384Monte :: MonteFile Source #
SHA3_384Monte.rsp
sha3_512Monte :: MonteFile Source #
SHA3_512Monte.rsp
Test Utils
msgTest :: (ByteString -> ByteString) -> MsgFile -> Bool Source #
Check that all test vectors in a File are satisfied by a given hash implementation.
Arguments
:: Monad m | |
=> (String -> ByteString -> ByteString -> m ()) | Function to assertion Equality. The first argument is a test label, the second argument is the actual value, and the thrid value is the expected value. |
-> (ByteString -> ByteString) | Hash function |
-> MsgFile | |
-> m () |
For a given hash implementation, assert the correct result for each test
vector in a MsgFile
.
The function to assert equality is usually provided by some testing framework.
monteTest :: (ByteString -> ByteString) -> MonteFile -> Bool Source #
Test a given SHA3 implementation for the test vectors in a monte file. See
monteAssert
for details.
Arguments
:: Monad m | |
=> (String -> ByteString -> ByteString -> m ()) | Function to assertion Equality. The first argument is a test label, the second argument is the actual value, and the thrid value is the expected value. |
-> (ByteString -> ByteString) | Hash function |
-> MonteFile | |
-> m () |
For a given SHA3 implementation, assert the correct result for each test
vector in a MonteFile
.
The function to assert equality is usually provided by some testing framework.
The test algorithm is describe in cf. https://csrc.nist.gov/CSRC/media/Projects/Cryptographic-Algorithm-Validation-Program/documents/sha3/sha3vs.pdf The pseudo code is as follows:
INPUT: A random Seed n bits long { MD0 = Seed; for (j=0; j<100; j++) { for (i=1; i<1001; i++) { Msgi = MDi-1; MDi = SHA3(Msgi); } MD0 = MD1000; OUTPUT: MD0 } }
NOTE that the test algorithms for SHA (SHA1 and SHA2) and SHA3 are different.