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.SHA
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
- sha1LongMsg :: MsgFile
- sha224LongMsg :: MsgFile
- sha256LongMsg :: MsgFile
- sha384LongMsg :: MsgFile
- sha512LongMsg :: MsgFile
- sha512_224LongMsg :: MsgFile
- sha512_256LongMsg :: MsgFile
- sha1ShortMsg :: MsgFile
- sha224ShortMsg :: MsgFile
- sha256ShortMsg :: MsgFile
- sha384ShortMsg :: MsgFile
- sha512ShortMsg :: MsgFile
- sha512_224ShortMsg :: MsgFile
- sha512_256ShortMsg :: MsgFile
- data MonteFile = MonteFile {
- _monteDescription :: !Text
- _monteL :: !Natural
- _monteSeed :: !ByteString
- _monteVectors :: !(Vector MonteVector)
- data MonteVector = MonteVector {
- _monteCount :: !Natural
- _monteMd :: !ByteString
- sha1Monte :: MonteFile
- sha224Monte :: MonteFile
- sha256Monte :: MonteFile
- sha384Monte :: MonteFile
- sha512Monte :: MonteFile
- sha512_224Monte :: MonteFile
- sha512_256Monte :: 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 # | |
sha1LongMsg :: MsgFile Source #
SHA1LongMsg.rsp
sha224LongMsg :: MsgFile Source #
SHA224LongMsg.rsp
sha256LongMsg :: MsgFile Source #
SHA256LongMsg.rsp
sha384LongMsg :: MsgFile Source #
SHA384LongMsg.rsp
sha512LongMsg :: MsgFile Source #
SHA512LongMsg.rsp
sha512_224LongMsg :: MsgFile Source #
SHA512_224LongMsg.rsp
sha512_256LongMsg :: MsgFile Source #
SHA512_256LongMsg.rsp
Selected Short Messages Test for Byte-Oriented Implementations
sha1ShortMsg :: MsgFile Source #
SHA1ShortMsg.rsp
sha224ShortMsg :: MsgFile Source #
SHA224ShortMsg.rsp
sha256ShortMsg :: MsgFile Source #
SHA256ShortMsg.rsp
sha384ShortMsg :: MsgFile Source #
SHA384ShortMsg.rsp
sha512ShortMsg :: MsgFile Source #
SHA512ShortMsg.rsp
sha512_224ShortMsg :: MsgFile Source #
SHA512_224ShortMsg.rsp
sha512_256ShortMsg :: MsgFile Source #
SHA512_256ShortMsg.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 # |
sha224Monte :: MonteFile Source #
SHA224Monte.rsp
sha256Monte :: MonteFile Source #
SHA256Monte.rsp
sha384Monte :: MonteFile Source #
SHA384Monte.rsp
sha512Monte :: MonteFile Source #
SHA512Monte.rsp
sha512_224Monte :: MonteFile Source #
SHA512_224Monte.rsp
sha512_256Monte :: MonteFile Source #
SHA512_256Monte.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 SHA1 or SHA2 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 SHA1 or SHA2 implementation, assert the correct result for each
test vector in a MonteFile
.
The function to assert equality is usually provided by some testing framework.
NOTE that the test algorithms for SHA (SHA1 and SHA2) and SHA3 are different.
The test algorithm is describe in cf. https://csrc.nist.gov/csrc/media/projects/cryptographic-algorithm-validation-program/documents/shs/shavs.pdf. The pseudo code is as follows:
INPUT: Seed - A random seed n bits long { for (j=0; j<100; j++) { MD0 = MD1 = MD2 = Seed; for (i=3; i<1003; i++) { Mi = MDi-3 || MDi-2 || MDi-1; MDi = SHA(Mi); } MDj = Seed = MD1002; OUTPUT: MDj } }