commit
093f1af8e4
@ -26,10 +26,10 @@ module Crypto.Hash.Algorithms
|
||||
, SHA512t_256(..)
|
||||
, RIPEMD160(..)
|
||||
, Tiger(..)
|
||||
, Kekkak_224(..)
|
||||
, Kekkak_256(..)
|
||||
, Kekkak_384(..)
|
||||
, Kekkak_512(..)
|
||||
, Keccak_224(..)
|
||||
, Keccak_256(..)
|
||||
, Keccak_384(..)
|
||||
, Keccak_512(..)
|
||||
, SHA3_224(..)
|
||||
, SHA3_256(..)
|
||||
, SHA3_384(..)
|
||||
@ -58,7 +58,7 @@ import Crypto.Hash.SHA384
|
||||
import Crypto.Hash.SHA512
|
||||
import Crypto.Hash.SHA512t
|
||||
import Crypto.Hash.SHA3
|
||||
import Crypto.Hash.Kekkak
|
||||
import Crypto.Hash.Keccak
|
||||
import Crypto.Hash.RIPEMD160
|
||||
import Crypto.Hash.Tiger
|
||||
import Crypto.Hash.Skein256
|
||||
|
||||
77
Crypto/Hash/Keccak.hs
Normal file
77
Crypto/Hash/Keccak.hs
Normal file
@ -0,0 +1,77 @@
|
||||
-- |
|
||||
-- Module : Crypto.Hash.Keccak
|
||||
-- License : BSD-style
|
||||
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
|
||||
-- Stability : experimental
|
||||
-- Portability : unknown
|
||||
--
|
||||
-- module containing the binding functions to work with the
|
||||
-- Keccak cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
module Crypto.Hash.Keccak
|
||||
( Keccak_224 (..), Keccak_256 (..), Keccak_384 (..), Keccak_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Keccak (224 bits) cryptographic hash algorithm
|
||||
data Keccak_224 = Keccak_224
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Keccak_224 where
|
||||
hashBlockSize _ = 144
|
||||
hashDigestSize _ = 28
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_keccak_init p 224
|
||||
hashInternalUpdate = c_keccak_update
|
||||
hashInternalFinalize = c_keccak_finalize
|
||||
|
||||
-- | Keccak (256 bits) cryptographic hash algorithm
|
||||
data Keccak_256 = Keccak_256
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Keccak_256 where
|
||||
hashBlockSize _ = 136
|
||||
hashDigestSize _ = 32
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_keccak_init p 256
|
||||
hashInternalUpdate = c_keccak_update
|
||||
hashInternalFinalize = c_keccak_finalize
|
||||
|
||||
-- | Keccak (384 bits) cryptographic hash algorithm
|
||||
data Keccak_384 = Keccak_384
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Keccak_384 where
|
||||
hashBlockSize _ = 104
|
||||
hashDigestSize _ = 48
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_keccak_init p 384
|
||||
hashInternalUpdate = c_keccak_update
|
||||
hashInternalFinalize = c_keccak_finalize
|
||||
|
||||
-- | Keccak (512 bits) cryptographic hash algorithm
|
||||
data Keccak_512 = Keccak_512
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Keccak_512 where
|
||||
hashBlockSize _ = 72
|
||||
hashDigestSize _ = 64
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_keccak_init p 512
|
||||
hashInternalUpdate = c_keccak_update
|
||||
hashInternalFinalize = c_keccak_finalize
|
||||
|
||||
|
||||
foreign import ccall unsafe "cryptonite_keccak_init"
|
||||
c_keccak_init :: Ptr (Context a) -> Word32 -> IO ()
|
||||
|
||||
foreign import ccall "cryptonite_keccak_update"
|
||||
c_keccak_update :: Ptr (Context a) -> Ptr Word8 -> Word32 -> IO ()
|
||||
|
||||
foreign import ccall unsafe "cryptonite_keccak_finalize"
|
||||
c_keccak_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()
|
||||
@ -1,77 +0,0 @@
|
||||
-- |
|
||||
-- Module : Crypto.Hash.Kekkak
|
||||
-- License : BSD-style
|
||||
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
|
||||
-- Stability : experimental
|
||||
-- Portability : unknown
|
||||
--
|
||||
-- module containing the binding functions to work with the
|
||||
-- Kekkak cryptographic hash.
|
||||
--
|
||||
{-# LANGUAGE ForeignFunctionInterface #-}
|
||||
module Crypto.Hash.Kekkak
|
||||
( Kekkak_224 (..), Kekkak_256 (..), Kekkak_384 (..), Kekkak_512 (..)
|
||||
) where
|
||||
|
||||
import Crypto.Hash.Types
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Data.Word (Word8, Word32)
|
||||
|
||||
|
||||
-- | Kekkak (224 bits) cryptographic hash algorithm
|
||||
data Kekkak_224 = Kekkak_224
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Kekkak_224 where
|
||||
hashBlockSize _ = 144
|
||||
hashDigestSize _ = 28
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_kekkak_init p 224
|
||||
hashInternalUpdate = c_kekkak_update
|
||||
hashInternalFinalize = c_kekkak_finalize
|
||||
|
||||
-- | Kekkak (256 bits) cryptographic hash algorithm
|
||||
data Kekkak_256 = Kekkak_256
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Kekkak_256 where
|
||||
hashBlockSize _ = 136
|
||||
hashDigestSize _ = 32
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_kekkak_init p 256
|
||||
hashInternalUpdate = c_kekkak_update
|
||||
hashInternalFinalize = c_kekkak_finalize
|
||||
|
||||
-- | Kekkak (384 bits) cryptographic hash algorithm
|
||||
data Kekkak_384 = Kekkak_384
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Kekkak_384 where
|
||||
hashBlockSize _ = 104
|
||||
hashDigestSize _ = 48
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_kekkak_init p 384
|
||||
hashInternalUpdate = c_kekkak_update
|
||||
hashInternalFinalize = c_kekkak_finalize
|
||||
|
||||
-- | Kekkak (512 bits) cryptographic hash algorithm
|
||||
data Kekkak_512 = Kekkak_512
|
||||
deriving (Show)
|
||||
|
||||
instance HashAlgorithm Kekkak_512 where
|
||||
hashBlockSize _ = 72
|
||||
hashDigestSize _ = 64
|
||||
hashInternalContextSize _ = 360
|
||||
hashInternalInit p = c_kekkak_init p 512
|
||||
hashInternalUpdate = c_kekkak_update
|
||||
hashInternalFinalize = c_kekkak_finalize
|
||||
|
||||
|
||||
foreign import ccall unsafe "cryptonite_kekkak_init"
|
||||
c_kekkak_init :: Ptr (Context a) -> Word32 -> IO ()
|
||||
|
||||
foreign import ccall "cryptonite_kekkak_update"
|
||||
c_kekkak_update :: Ptr (Context a) -> Ptr Word8 -> Word32 -> IO ()
|
||||
|
||||
foreign import ccall unsafe "cryptonite_kekkak_finalize"
|
||||
c_kekkak_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()
|
||||
@ -25,7 +25,7 @@
|
||||
#include <stdint.h>
|
||||
#include <string.h>
|
||||
#include "cryptonite_bitfn.h"
|
||||
#include "cryptonite_kekkak.h"
|
||||
#include "cryptonite_keccak.h"
|
||||
|
||||
#define KECCAK_NB_ROUNDS 24
|
||||
|
||||
@ -49,7 +49,7 @@ static const int keccak_rotc[24] =
|
||||
static const int keccak_piln[24] =
|
||||
{ 10,7,11,17,18,3,5,16,8,21,24,4,15,23,19,13,12,2,20,14,22,9,6,1 };
|
||||
|
||||
static inline void kekkak_do_chunk(uint64_t state[25], uint64_t buf[], int bufsz)
|
||||
static inline void keccak_do_chunk(uint64_t state[25], uint64_t buf[], int bufsz)
|
||||
{
|
||||
int i, j, r;
|
||||
uint64_t tmp, bc[5];
|
||||
@ -97,28 +97,28 @@ static inline void kekkak_do_chunk(uint64_t state[25], uint64_t buf[], int bufsz
|
||||
}
|
||||
}
|
||||
|
||||
void cryptonite_kekkak_init(struct kekkak_ctx *ctx, uint32_t hashlen)
|
||||
void cryptonite_keccak_init(struct keccak_ctx *ctx, uint32_t hashlen)
|
||||
{
|
||||
memset(ctx, 0, sizeof(*ctx));
|
||||
ctx->hashlen = hashlen / 8;
|
||||
ctx->bufsz = 200 - 2 * ctx->hashlen;
|
||||
}
|
||||
|
||||
void cryptonite_kekkak_update(struct kekkak_ctx *ctx, uint8_t *data, uint32_t len)
|
||||
void cryptonite_keccak_update(struct keccak_ctx *ctx, uint8_t *data, uint32_t len)
|
||||
{
|
||||
uint32_t to_fill;
|
||||
|
||||
to_fill = ctx->bufsz - ctx->bufindex;
|
||||
|
||||
if (ctx->bufindex == ctx->bufsz) {
|
||||
kekkak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
keccak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
ctx->bufindex = 0;
|
||||
}
|
||||
|
||||
/* process partial buffer if there's enough data to make a block */
|
||||
if (ctx->bufindex && len >= to_fill) {
|
||||
memcpy(ctx->buf + ctx->bufindex, data, to_fill);
|
||||
kekkak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
keccak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
len -= to_fill;
|
||||
data += to_fill;
|
||||
ctx->bufindex = 0;
|
||||
@ -126,7 +126,7 @@ void cryptonite_kekkak_update(struct kekkak_ctx *ctx, uint8_t *data, uint32_t le
|
||||
|
||||
/* process as much ctx->bufsz-block */
|
||||
for (; len >= ctx->bufsz; len -= ctx->bufsz, data += ctx->bufsz)
|
||||
kekkak_do_chunk(ctx->state, (uint64_t *) data, ctx->bufsz / 8);
|
||||
keccak_do_chunk(ctx->state, (uint64_t *) data, ctx->bufsz / 8);
|
||||
|
||||
/* append data into buf */
|
||||
if (len) {
|
||||
@ -135,13 +135,13 @@ void cryptonite_kekkak_update(struct kekkak_ctx *ctx, uint8_t *data, uint32_t le
|
||||
}
|
||||
}
|
||||
|
||||
void cryptonite_kekkak_finalize(struct kekkak_ctx *ctx, uint8_t *out)
|
||||
void cryptonite_keccak_finalize(struct keccak_ctx *ctx, uint8_t *out)
|
||||
{
|
||||
uint64_t w[25];
|
||||
|
||||
/* process full buffer if needed */
|
||||
if (ctx->bufindex == ctx->bufsz) {
|
||||
kekkak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
keccak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
ctx->bufindex = 0;
|
||||
}
|
||||
|
||||
@ -151,7 +151,7 @@ void cryptonite_kekkak_finalize(struct kekkak_ctx *ctx, uint8_t *out)
|
||||
ctx->buf[ctx->bufsz - 1] |= 0x80;
|
||||
|
||||
/* process */
|
||||
kekkak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
keccak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
||||
|
||||
/* output */
|
||||
cpu_to_le64_array(w, ctx->state, 25);
|
||||
@ -26,7 +26,7 @@
|
||||
|
||||
#include <stdint.h>
|
||||
|
||||
struct kekkak_ctx
|
||||
struct keccak_ctx
|
||||
{
|
||||
uint32_t hashlen; /* in bytes */
|
||||
uint32_t bufindex;
|
||||
@ -36,10 +36,10 @@ struct kekkak_ctx
|
||||
uint8_t buf[144]; /* minimum SHA3-224, otherwise buffer need increases */
|
||||
};
|
||||
|
||||
#define SHA3_CTX_SIZE sizeof(struct kekkak_ctx)
|
||||
#define SHA3_CTX_SIZE sizeof(struct keccak_ctx)
|
||||
|
||||
void cryptonite_kekkak_init(struct kekkak_ctx *ctx, uint32_t hashlen);
|
||||
void cryptonite_kekkak_update(struct kekkak_ctx *ctx, uint8_t *data, uint32_t len);
|
||||
void cryptonite_kekkak_finalize(struct kekkak_ctx *ctx, uint8_t *out);
|
||||
void cryptonite_keccak_init(struct keccak_ctx *ctx, uint32_t hashlen);
|
||||
void cryptonite_keccak_update(struct keccak_ctx *ctx, uint8_t *data, uint32_t len);
|
||||
void cryptonite_keccak_finalize(struct keccak_ctx *ctx, uint8_t *out);
|
||||
|
||||
#endif
|
||||
@ -6,7 +6,7 @@ Description:
|
||||
.
|
||||
* Symmetric ciphers: AES, DES, 3DES, Blowfish, Camellia, RC4, Salsa, ChaCha.
|
||||
.
|
||||
* Hash: SHA1, SHA2, SHA3, MD2, MD4, MD5, Kekkak, Skein, Ripemd, Tiger, Whirlpool
|
||||
* Hash: SHA1, SHA2, SHA3, MD2, MD4, MD5, Keccak, Skein, Ripemd, Tiger, Whirlpool
|
||||
.
|
||||
* MAC: HMAC, Poly1305
|
||||
.
|
||||
@ -145,7 +145,7 @@ Library
|
||||
Crypto.Hash.SHA512
|
||||
Crypto.Hash.SHA512t
|
||||
Crypto.Hash.SHA3
|
||||
Crypto.Hash.Kekkak
|
||||
Crypto.Hash.Keccak
|
||||
Crypto.Hash.MD2
|
||||
Crypto.Hash.MD4
|
||||
Crypto.Hash.MD5
|
||||
@ -195,7 +195,7 @@ Library
|
||||
, cbits/cryptonite_sha256.c
|
||||
, cbits/cryptonite_sha512.c
|
||||
, cbits/cryptonite_sha3.c
|
||||
, cbits/cryptonite_kekkak.c
|
||||
, cbits/cryptonite_keccak.c
|
||||
, cbits/cryptonite_md2.c
|
||||
, cbits/cryptonite_md4.c
|
||||
, cbits/cryptonite_md5.c
|
||||
|
||||
@ -34,7 +34,7 @@ hashModules =
|
||||
, GenHashModule "SHA384" "sha512.h" "sha384" 256 48 128 []
|
||||
, GenHashModule "SHA512" "sha512.h" "sha512" 256 64 128 []
|
||||
, GenHashModule "SHA512t" "sha512.h" "sha512t" 264 64 128 [(224,128),(256,128)]
|
||||
, GenHashModule "Kekkak" "kekkak.h" "kekkak" 360 64 64 [(224,144),(256,136),(384,104),(512,72)]
|
||||
, GenHashModule "Keccak" "keccak.h" "keccak" 360 64 64 [(224,144),(256,136),(384,104),(512,72)]
|
||||
, GenHashModule "SHA3" "sha3.h" "sha3" 360 64 64 [(224,144),(256,136),(384,104),(512,72)]
|
||||
, GenHashModule "RIPEMD160" "ripemd.h" "ripemd160" 128 20 64 []
|
||||
, GenHashModule "Skein256" "skein256.h" "skein256" 96 32 32 [(224,32),(256,32)]
|
||||
|
||||
@ -106,19 +106,19 @@ expected = [
|
||||
"19fa61d75522a4669b44e39c1d2e1726c530232130d407f89afee0964997f7a73e83be698b288febcf88e3e03c4f0757ea8964e59b63d93708b138cc42a66eb3",
|
||||
"b97de512e91e3828b40d2b0fdce9ceb3c4a71f9bea8d88e75c4fa854df36725fd2b52eb6544edcacd6f8beddfea403cb55ae31f03ad62a5ef54e42ee82c3fb35",
|
||||
"dce81fc695cfea3d7e1446509238daf89f24cc61896f2d265927daa70f2108f8902f0dfd68be085d5abb9fcd2e482c1dc24f2fabf81f40b73495cad44d7360d3"])
|
||||
, ("Kekkak-224", HashAlg Kekkak_224, [
|
||||
, ("Keccak-224", HashAlg Keccak_224, [
|
||||
"f71837502ba8e10837bdd8d365adb85591895602fc552b48b7390abd",
|
||||
"310aee6b30c47350576ac2873fa89fd190cdc488442f3ef654cf23fe",
|
||||
"0b27ff3b732133287f6831e2af47cf342b7ef1f3fcdee248811090cd" ])
|
||||
, ("Kekkak-256", HashAlg Kekkak_256, [
|
||||
, ("Keccak-256", HashAlg Keccak_256, [
|
||||
"c5d2460186f7233c927e7db2dcc703c0e500b653ca82273b7bfad8045d85a470",
|
||||
"4d741b6f1eb29cb2a9b9911c82f56fa8d73b04959d3d9d222895df6c0b28aa15",
|
||||
"ed6c07f044d7573cc53bf1276f8cba3dac497919597a45b4599c8f73e22aa334" ])
|
||||
, ("Kekkak-384", HashAlg Kekkak_384, [
|
||||
, ("Keccak-384", HashAlg Keccak_384, [
|
||||
"2c23146a63a29acf99e73b88f8c24eaa7dc60aa771780ccc006afbfa8fe2479b2dd2b21362337441ac12b515911957ff",
|
||||
"283990fa9d5fb731d786c5bbee94ea4db4910f18c62c03d173fc0a5e494422e8a0b3da7574dae7fa0baf005e504063b3",
|
||||
"1cc515e1812491058d8b8b226fd85045e746b4937a58b0111b6b7a39dd431b6295bd6b6d05e01e225586b4dab3cbb87a" ])
|
||||
, ("Kekkak-512", HashAlg Kekkak_512, [
|
||||
, ("Keccak-512", HashAlg Keccak_512, [
|
||||
"0eab42de4c3ceb9235fc91acffe746b29c29a8c366b7c60e4e67c466f36a4304c00fa9caf9d87976ba469bcbe06713b435f091ef2769fb160cdab33d3670680e",
|
||||
"d135bb84d0439dbac432247ee573a23ea7d3c9deb2a968eb31d47c4fb45f1ef4422d6c531b5b9bd6f449ebcc449ea94d0a8f05f62130fda612da53c79659f609",
|
||||
"10f8caabb5b179861da5e447d34b84d604e3eb81830880e1c2135ffc94580a47cb21f6243ec0053d58b1124d13af2090033659075ee718e0f111bb3f69fb24cf" ])
|
||||
|
||||
@ -3,7 +3,7 @@ module KAT_HMAC (tests) where
|
||||
|
||||
import qualified Crypto.MAC.HMAC as HMAC
|
||||
import Crypto.Hash (MD5(..), SHA1(..), SHA256(..)
|
||||
, Kekkak_224(..), Kekkak_256(..), Kekkak_384(..), Kekkak_512(..)
|
||||
, Keccak_224(..), Keccak_256(..), Keccak_384(..), Keccak_512(..)
|
||||
, SHA3_224(..), SHA3_256(..), SHA3_384(..), SHA3_512(..)
|
||||
, HashAlgorithm, digestFromByteString)
|
||||
import qualified Data.ByteString as B
|
||||
@ -43,27 +43,27 @@ sha256MACVectors =
|
||||
, MACVector "key" v1 $ digest "\xf7\xbc\x83\xf4\x30\x53\x84\x24\xb1\x32\x98\xe6\xaa\x6f\xb1\x43\xef\x4d\x59\xa1\x49\x46\x17\x59\x97\x47\x9d\xbc\x2d\x1a\x3c\xd8"
|
||||
]
|
||||
|
||||
kekkak_key1 = "\x4a\x65\x66\x65"
|
||||
kekkak_data1 = "\x77\x68\x61\x74\x20\x64\x6f\x20\x79\x61\x20\x77\x61\x6e\x74\x20\x66\x6f\x72\x20\x6e\x6f\x74\x68\x69\x6e\x67\x3f"
|
||||
keccak_key1 = "\x4a\x65\x66\x65"
|
||||
keccak_data1 = "\x77\x68\x61\x74\x20\x64\x6f\x20\x79\x61\x20\x77\x61\x6e\x74\x20\x66\x6f\x72\x20\x6e\x6f\x74\x68\x69\x6e\x67\x3f"
|
||||
|
||||
kekkak_224_MAC_Vectors :: [MACVector Kekkak_224]
|
||||
kekkak_224_MAC_Vectors =
|
||||
[ MACVector kekkak_key1 kekkak_data1 $ digest "\xe8\x24\xfe\xc9\x6c\x07\x4f\x22\xf9\x92\x35\xbb\x94\x2d\xa1\x98\x26\x64\xab\x69\x2c\xa8\x50\x10\x53\xcb\xd4\x14"
|
||||
keccak_224_MAC_Vectors :: [MACVector Keccak_224]
|
||||
keccak_224_MAC_Vectors =
|
||||
[ MACVector keccak_key1 keccak_data1 $ digest "\xe8\x24\xfe\xc9\x6c\x07\x4f\x22\xf9\x92\x35\xbb\x94\x2d\xa1\x98\x26\x64\xab\x69\x2c\xa8\x50\x10\x53\xcb\xd4\x14"
|
||||
]
|
||||
|
||||
kekkak_256_MAC_Vectors :: [MACVector Kekkak_256]
|
||||
kekkak_256_MAC_Vectors =
|
||||
[ MACVector kekkak_key1 kekkak_data1 $ digest "\xaa\x9a\xed\x44\x8c\x7a\xbc\x8b\x5e\x32\x6f\xfa\x6a\x01\xcd\xed\xf7\xb4\xb8\x31\x88\x14\x68\xc0\x44\xba\x8d\xd4\x56\x63\x69\xa1"
|
||||
keccak_256_MAC_Vectors :: [MACVector Keccak_256]
|
||||
keccak_256_MAC_Vectors =
|
||||
[ MACVector keccak_key1 keccak_data1 $ digest "\xaa\x9a\xed\x44\x8c\x7a\xbc\x8b\x5e\x32\x6f\xfa\x6a\x01\xcd\xed\xf7\xb4\xb8\x31\x88\x14\x68\xc0\x44\xba\x8d\xd4\x56\x63\x69\xa1"
|
||||
]
|
||||
|
||||
kekkak_384_MAC_Vectors :: [MACVector Kekkak_384]
|
||||
kekkak_384_MAC_Vectors =
|
||||
[ MACVector kekkak_key1 kekkak_data1 $ digest "\x5a\xf5\xc9\xa7\x7a\x23\xa6\xa9\x3d\x80\x64\x9e\x56\x2a\xb7\x7f\x4f\x35\x52\xe3\xc5\xca\xff\xd9\x3b\xdf\x8b\x3c\xfc\x69\x20\xe3\x02\x3f\xc2\x67\x75\xd9\xdf\x1f\x3c\x94\x61\x31\x46\xad\x2c\x9d"
|
||||
keccak_384_MAC_Vectors :: [MACVector Keccak_384]
|
||||
keccak_384_MAC_Vectors =
|
||||
[ MACVector keccak_key1 keccak_data1 $ digest "\x5a\xf5\xc9\xa7\x7a\x23\xa6\xa9\x3d\x80\x64\x9e\x56\x2a\xb7\x7f\x4f\x35\x52\xe3\xc5\xca\xff\xd9\x3b\xdf\x8b\x3c\xfc\x69\x20\xe3\x02\x3f\xc2\x67\x75\xd9\xdf\x1f\x3c\x94\x61\x31\x46\xad\x2c\x9d"
|
||||
]
|
||||
|
||||
kekkak_512_MAC_Vectors :: [MACVector Kekkak_512]
|
||||
kekkak_512_MAC_Vectors =
|
||||
[ MACVector kekkak_key1 kekkak_data1 $ digest "\xc2\x96\x2e\x5b\xbe\x12\x38\x00\x78\x52\xf7\x9d\x81\x4d\xbb\xec\xd4\x68\x2e\x6f\x09\x7d\x37\xa3\x63\x58\x7c\x03\xbf\xa2\xeb\x08\x59\xd8\xd9\xc7\x01\xe0\x4c\xec\xec\xfd\x3d\xd7\xbf\xd4\x38\xf2\x0b\x8b\x64\x8e\x01\xbf\x8c\x11\xd2\x68\x24\xb9\x6c\xeb\xbd\xcb"
|
||||
keccak_512_MAC_Vectors :: [MACVector Keccak_512]
|
||||
keccak_512_MAC_Vectors =
|
||||
[ MACVector keccak_key1 keccak_data1 $ digest "\xc2\x96\x2e\x5b\xbe\x12\x38\x00\x78\x52\xf7\x9d\x81\x4d\xbb\xec\xd4\x68\x2e\x6f\x09\x7d\x37\xa3\x63\x58\x7c\x03\xbf\xa2\xeb\x08\x59\xd8\xd9\xc7\x01\xe0\x4c\xec\xec\xfd\x3d\xd7\xbf\xd4\x38\xf2\x0b\x8b\x64\x8e\x01\xbf\x8c\x11\xd2\x68\x24\xb9\x6c\xeb\xbd\xcb"
|
||||
]
|
||||
|
||||
sha3_key1 = "\x4a\x65\x66\x65"
|
||||
@ -95,10 +95,10 @@ macTests =
|
||||
[ testGroup "md5" $ concatMap toMACTest $ zip is md5MACVectors
|
||||
, testGroup "sha1" $ concatMap toMACTest $ zip is sha1MACVectors
|
||||
, testGroup "sha256" $ concatMap toMACTest $ zip is sha256MACVectors
|
||||
, testGroup "kekkak-224" $ concatMap toMACTest $ zip is kekkak_224_MAC_Vectors
|
||||
, testGroup "kekkak-256" $ concatMap toMACTest $ zip is kekkak_256_MAC_Vectors
|
||||
, testGroup "kekkak-384" $ concatMap toMACTest $ zip is kekkak_384_MAC_Vectors
|
||||
, testGroup "kekkak-512" $ concatMap toMACTest $ zip is kekkak_512_MAC_Vectors
|
||||
, testGroup "keccak-224" $ concatMap toMACTest $ zip is keccak_224_MAC_Vectors
|
||||
, testGroup "keccak-256" $ concatMap toMACTest $ zip is keccak_256_MAC_Vectors
|
||||
, testGroup "keccak-384" $ concatMap toMACTest $ zip is keccak_384_MAC_Vectors
|
||||
, testGroup "keccak-512" $ concatMap toMACTest $ zip is keccak_512_MAC_Vectors
|
||||
, testGroup "sha3-224" $ concatMap toMACTest $ zip is sha3_224_MAC_Vectors
|
||||
, testGroup "sha3-256" $ concatMap toMACTest $ zip is sha3_256_MAC_Vectors
|
||||
, testGroup "sha3-384" $ concatMap toMACTest $ zip is sha3_384_MAC_Vectors
|
||||
|
||||
Loading…
Reference in New Issue
Block a user