add kekkak

This commit is contained in:
Vincent Hanquez 2014-08-01 05:06:55 -07:00
parent 2e5e428bb1
commit 903ff726a2
7 changed files with 412 additions and 1 deletions

View File

@ -43,6 +43,10 @@ module Crypto.Hash
, SHA512(..)
, RIPEMD160(..)
, Tiger(..)
, Kekkak_224(..)
, Kekkak_256(..)
, Kekkak_384(..)
, Kekkak_512(..)
, SHA3_224(..)
, SHA3_256(..)
, SHA3_384(..)
@ -72,6 +76,7 @@ import qualified Crypto.Hash.SHA256 as SHA256
import qualified Crypto.Hash.SHA384 as SHA384
import qualified Crypto.Hash.SHA512 as SHA512
import qualified Crypto.Hash.SHA3 as SHA3
import qualified Crypto.Hash.Kekkak as Kekkak
import qualified Crypto.Hash.RIPEMD160 as RIPEMD160
import qualified Crypto.Hash.Tiger as Tiger
import qualified Crypto.Hash.Skein256 as Skein256
@ -144,6 +149,15 @@ DEFINE_INSTANCE(Whirlpool, Whirlpool, 64)
-- | Tiger cryptographic hash
DEFINE_INSTANCE(Tiger, Tiger, 64)
-- | Kekkak (224 bits version) cryptographic hash
DEFINE_INSTANCE_LEN(Kekkak_224, Kekkak, 224, 144)
-- | Kekkak (256 bits version) cryptographic hash
DEFINE_INSTANCE_LEN(Kekkak_256, Kekkak, 256, 136)
-- | Kekkak (384 bits version) cryptographic hash
DEFINE_INSTANCE_LEN(Kekkak_384, Kekkak, 384, 104)
-- | Kekkak (512 bits version) cryptographic hash
DEFINE_INSTANCE_LEN(Kekkak_512, Kekkak, 512, 72)
-- | SHA3 (224 bits version) cryptographic hash
DEFINE_INSTANCE_LEN(SHA3_224, SHA3, 224, 144)
-- | SHA3 (256 bits version) cryptographic hash

144
Crypto/Hash/Kekkak.hs Normal file
View File

@ -0,0 +1,144 @@
{-# LANGUAGE ForeignFunctionInterface #-}
-- |
-- Module : Crypto.Hash.Kekkak
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- module containing the basic functions to work with the
-- Kekkak cryptographic hash.
--
module Crypto.Hash.Kekkak
( Ctx(..)
-- * Incremental hashing Functions
, init -- :: Int -> Ctx
, update -- :: Ctx -> ByteString -> Ctx
, updates -- :: Ctx -> [ByteString] -> Ctx
, finalize -- :: Ctx -> ByteString
-- * Single Pass hashing
, hash -- :: Int -> ByteString -> ByteString
, hashlazy -- :: Int -> ByteString -> ByteString
) where
import Prelude hiding (init)
import Foreign.Ptr
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Storable
import Foreign.Marshal.Alloc
import qualified Data.ByteString.Lazy as L
import Data.ByteString (ByteString)
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.ByteString.Internal (create, toForeignPtr)
import Data.Word
import Crypto.Hash.Internal (unsafeDoIO)
-- | Kekkak Context.
newtype Ctx = Ctx ByteString
{-# INLINE sizeCtx #-}
sizeCtx :: Int
sizeCtx = 360
{- return the number of bytes of output for the digest -}
peekHashlen :: Ptr Ctx -> IO Int
peekHashlen ptr = peek iptr >>= \v -> return $! fromIntegral v
where iptr :: Ptr Word32
iptr = castPtr ptr
{-# RULES "hash" forall b i. finalize (update (init i) b) = hash i b #-}
{-# RULES "hash.list1" forall b i. finalize (updates (init i) [b]) = hash i b #-}
{-# RULES "hashmany" forall b i. finalize (foldl update (init i) b) = hashlazy i (L.fromChunks b) #-}
{-# RULES "hashlazy" forall b i. finalize (foldl update (init i) $ L.toChunks b) = hashlazy i b #-}
{-# INLINE withByteStringPtr #-}
withByteStringPtr :: ByteString -> (Ptr Word8 -> IO a) -> IO a
withByteStringPtr b f =
withForeignPtr fptr $ \ptr -> f (ptr `plusPtr` off)
where (fptr, off, _) = toForeignPtr b
{-# INLINE memcopy64 #-}
memcopy64 :: Ptr Word64 -> Ptr Word64 -> IO ()
memcopy64 dst src = mapM_ peekAndPoke [0..(45-1)]
where peekAndPoke i = peekElemOff src i >>= pokeElemOff dst i
withCtxCopy :: Ctx -> (Ptr Ctx -> IO ()) -> IO Ctx
withCtxCopy (Ctx ctxB) f = Ctx `fmap` createCtx
where createCtx = create sizeCtx $ \dstPtr ->
withByteStringPtr ctxB $ \srcPtr -> do
memcopy64 (castPtr dstPtr) (castPtr srcPtr)
f (castPtr dstPtr)
withCtxThrow :: Ctx -> (Ptr Ctx -> IO a) -> IO a
withCtxThrow (Ctx ctxB) f =
allocaBytes sizeCtx $ \dstPtr ->
withByteStringPtr ctxB $ \srcPtr -> do
memcopy64 (castPtr dstPtr) (castPtr srcPtr)
f (castPtr dstPtr)
withCtxNew :: (Ptr Ctx -> IO ()) -> IO Ctx
withCtxNew f = Ctx `fmap` create sizeCtx (f . castPtr)
withCtxNewThrow :: (Ptr Ctx -> IO a) -> IO a
withCtxNewThrow f = allocaBytes sizeCtx (f . castPtr)
foreign import ccall unsafe "cryptonite_kekkak.h cryptonite_kekkak_init"
c_kekkak_init :: Ptr Ctx -> Word32 -> IO ()
foreign import ccall "cryptonite_kekkak.h cryptonite_kekkak_update"
c_kekkak_update :: Ptr Ctx -> Ptr Word8 -> Word32 -> IO ()
foreign import ccall unsafe "cryptonite_kekkak.h cryptonite_kekkak_finalize"
c_kekkak_finalize :: Ptr Ctx -> Ptr Word8 -> IO ()
updateInternalIO :: Ptr Ctx -> ByteString -> IO ()
updateInternalIO ptr d =
unsafeUseAsCStringLen d (\(cs, len) -> c_kekkak_update ptr (castPtr cs) (fromIntegral len))
finalizeInternalIO :: Ptr Ctx -> IO ByteString
finalizeInternalIO ptr =
peekHashlen ptr >>= \digestSize -> create digestSize (c_kekkak_finalize ptr)
{-# NOINLINE init #-}
-- | init a context where
init :: Int -- ^ algorithm hash size in bits
-> Ctx
init hashlen = unsafeDoIO $ withCtxNew $ \ptr -> c_kekkak_init ptr (fromIntegral hashlen)
{-# NOINLINE update #-}
-- | update a context with a bytestring returning the new updated context
update :: Ctx -- ^ the context to update
-> ByteString -- ^ the data to update with
-> Ctx -- ^ the updated context
update ctx d = unsafeDoIO $ withCtxCopy ctx $ \ptr -> updateInternalIO ptr d
{-# NOINLINE updates #-}
-- | updates a context with multiples bytestring returning the new updated context
updates :: Ctx -- ^ the context to update
-> [ByteString] -- ^ a list of data bytestring to update with
-> Ctx -- ^ the updated context
updates ctx d = unsafeDoIO $ withCtxCopy ctx $ \ptr -> mapM_ (updateInternalIO ptr) d
{-# NOINLINE finalize #-}
-- | finalize the context into a digest bytestring
finalize :: Ctx -> ByteString
finalize ctx = unsafeDoIO $ withCtxThrow ctx finalizeInternalIO
{-# NOINLINE hash #-}
-- | hash a strict bytestring into a digest bytestring
hash :: Int -- ^ algorithm hash size in bits
-> ByteString -- ^ the data to hash
-> ByteString -- ^ the digest output
hash hashlen d = unsafeDoIO $ withCtxNewThrow $ \ptr -> do
c_kekkak_init ptr (fromIntegral hashlen) >> updateInternalIO ptr d >> finalizeInternalIO ptr
{-# NOINLINE hashlazy #-}
-- | hash a lazy bytestring into a digest bytestring
hashlazy :: Int -- ^ algorithm hash size in bits
-> L.ByteString -- ^ the data to hash as a lazy bytestring
-> ByteString -- ^ the digest output
hashlazy hashlen l = unsafeDoIO $ withCtxNewThrow $ \ptr -> do
c_kekkak_init ptr (fromIntegral hashlen) >> mapM_ (updateInternalIO ptr) (L.toChunks l) >> finalizeInternalIO ptr

159
cbits/cryptonite_kekkak.c Normal file
View File

@ -0,0 +1,159 @@
/*
* Copyright (C) 2012 Vincent Hanquez <vincent@snarc.org>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#include <stdint.h>
#include <string.h>
#include "cryptonite_bitfn.h"
#include "cryptonite_kekkak.h"
#define KECCAK_NB_ROUNDS 24
/* rounds constants */
static const uint64_t keccak_rndc[24] =
{
0x0000000000000001ULL, 0x0000000000008082ULL, 0x800000000000808aULL,
0x8000000080008000ULL, 0x000000000000808bULL, 0x0000000080000001ULL,
0x8000000080008081ULL, 0x8000000000008009ULL, 0x000000000000008aULL,
0x0000000000000088ULL, 0x0000000080008009ULL, 0x000000008000000aULL,
0x000000008000808bULL, 0x800000000000008bULL, 0x8000000000008089ULL,
0x8000000000008003ULL, 0x8000000000008002ULL, 0x8000000000000080ULL,
0x000000000000800aULL, 0x800000008000000aULL, 0x8000000080008081ULL,
0x8000000000008080ULL, 0x0000000080000001ULL, 0x8000000080008008ULL,
};
/* triangular numbers constants */
static const int keccak_rotc[24] =
{ 1,3,6,10,15,21,28,36,45,55,2,14,27,41,56,8,25,43,62,18,39,61,20,44 };
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)
{
int i, j, r;
uint64_t tmp, bc[5];
/* merge buf with state */
for (i = 0; i < bufsz; i++)
state[i] ^= le64_to_cpu(buf[i]);
/* run keccak rounds */
for (r = 0; r < KECCAK_NB_ROUNDS; r++) {
/* compute the parity of each columns */
for (i = 0; i < 5; i++)
bc[i] = state[i] ^ state[i+5] ^ state[i+10] ^ state[i+15] ^ state[i+20];
for (i = 0; i < 5; i++) {
tmp = bc[(i + 4) % 5] ^ rol64(bc[(i + 1) % 5], 1);
for (j = 0; j < 25; j += 5)
state[j + i] ^= tmp;
}
/* rho pi */
tmp = state[1];
for (i = 0; i < 24; i++) {
j = keccak_piln[i];
bc[0] = state[j];
state[j] = rol64(tmp, keccak_rotc[i]);
tmp = bc[0];
}
/* bitwise combine along rows using a = a xor (not b and c) */
for (j = 0; j < 25; j += 5) {
for (i = 0; i < 5; i++)
bc[i] = state[j + i];
#define andn(b,c) (~(b) & (c))
state[j + 0] ^= andn(bc[1], bc[2]);
state[j + 1] ^= andn(bc[2], bc[3]);
state[j + 2] ^= andn(bc[3], bc[4]);
state[j + 3] ^= andn(bc[4], bc[0]);
state[j + 4] ^= andn(bc[0], bc[1]);
#undef andn
}
/* xor the round constant */
state[0] ^= keccak_rndc[r];
}
}
void cryptonite_kekkak_init(struct kekkak_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)
{
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);
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);
len -= to_fill;
data += to_fill;
ctx->bufindex = 0;
}
/* 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);
/* append data into buf */
if (len) {
memcpy(ctx->buf + ctx->bufindex, data, len);
ctx->bufindex += len;
}
}
void cryptonite_kekkak_finalize(struct kekkak_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);
ctx->bufindex = 0;
}
/* add the 10*1 padding */
ctx->buf[ctx->bufindex++] = 1;
memset(ctx->buf + ctx->bufindex, 0, ctx->bufsz - ctx->bufindex);
ctx->buf[ctx->bufsz - 1] |= 0x80;
/* process */
kekkak_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
/* output */
cpu_to_le64_array(w, ctx->state, 25);
memcpy(out, w, ctx->hashlen);
}

45
cbits/cryptonite_kekkak.h Normal file
View File

@ -0,0 +1,45 @@
/*
* Copyright (C) 2012 Vincent Hanquez <vincent@snarc.org>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef CRYPTOHASH_SHA3_H
#define CRYPTOHASH_SHA3_H
#include <stdint.h>
struct kekkak_ctx
{
uint32_t hashlen; /* in bytes */
uint32_t bufindex;
uint64_t state[25];
uint32_t bufsz;
uint32_t _padding;
uint8_t buf[144]; /* minimum SHA3-224, otherwise buffer need increases */
};
#define SHA3_CTX_SIZE sizeof(struct kekkak_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);
#endif

View File

@ -35,6 +35,7 @@ Library
Crypto.Hash.SHA512
Crypto.Hash.SHA512t
Crypto.Hash.SHA3
Crypto.Hash.Kekkak
Crypto.Hash.MD2
Crypto.Hash.MD4
Crypto.Hash.MD5
@ -65,6 +66,7 @@ Library
, cbits/cryptonite_sha256.c
, cbits/cryptonite_sha512.c
, cbits/cryptonite_sha3.c
, cbits/cryptonite_kekkak.c
, cbits/cryptonite_md2.c
, cbits/cryptonite_md4.c
, cbits/cryptonite_md5.c

View File

@ -19,6 +19,7 @@ import qualified Crypto.Hash.SHA384 as SHA384
import qualified Crypto.Hash.SHA512 as SHA512
import qualified Crypto.Hash.SHA512t as SHA512t
import qualified Crypto.Hash.SHA3 as SHA3
import qualified Crypto.Hash.Kekkak as Kekkak
import qualified Crypto.Hash.RIPEMD160 as RIPEMD160
import qualified Crypto.Hash.Tiger as Tiger
import qualified Crypto.Hash.Skein256 as Skein256
@ -59,6 +60,7 @@ sha512_224Hash = HashFct { fctHash = SHA512t.hash 224, fctInc = hashinc (SHA512t
sha512_256Hash = HashFct { fctHash = SHA512t.hash 256, fctInc = hashinc (SHA512t.init 256) SHA512t.update SHA512t.finalize }
sha3Hash i = HashFct { fctHash = SHA3.hash i, fctInc = hashinc (SHA3.init i) SHA3.update SHA3.finalize }
kekkakHash i = HashFct { fctHash = Kekkak.hash i, fctInc = hashinc (Kekkak.init i) Kekkak.update Kekkak.finalize }
ripemd160Hash = HashFct { fctHash = RIPEMD160.hash, fctInc = hashinc RIPEMD160.init RIPEMD160.update RIPEMD160.finalize }
tigerHash = HashFct { fctHash = Tiger.hash, fctInc = hashinc Tiger.init Tiger.update Tiger.finalize }
@ -147,6 +149,22 @@ expected = [
"19fa61d75522a4669b44e39c1d2e1726c530232130d407f89afee0964997f7a73e83be698b288febcf88e3e03c4f0757ea8964e59b63d93708b138cc42a66eb3",
"b97de512e91e3828b40d2b0fdce9ceb3c4a71f9bea8d88e75c4fa854df36725fd2b52eb6544edcacd6f8beddfea403cb55ae31f03ad62a5ef54e42ee82c3fb35",
"dce81fc695cfea3d7e1446509238daf89f24cc61896f2d265927daa70f2108f8902f0dfd68be085d5abb9fcd2e482c1dc24f2fabf81f40b73495cad44d7360d3"])
, ("Kekkak-224", kekkakHash 224, [
"f71837502ba8e10837bdd8d365adb85591895602fc552b48b7390abd",
"310aee6b30c47350576ac2873fa89fd190cdc488442f3ef654cf23fe",
"0b27ff3b732133287f6831e2af47cf342b7ef1f3fcdee248811090cd" ])
, ("Kekkak-256", kekkakHash 256, [
"c5d2460186f7233c927e7db2dcc703c0e500b653ca82273b7bfad8045d85a470",
"4d741b6f1eb29cb2a9b9911c82f56fa8d73b04959d3d9d222895df6c0b28aa15",
"ed6c07f044d7573cc53bf1276f8cba3dac497919597a45b4599c8f73e22aa334" ])
, ("Kekkak-384", kekkakHash 384, [
"2c23146a63a29acf99e73b88f8c24eaa7dc60aa771780ccc006afbfa8fe2479b2dd2b21362337441ac12b515911957ff",
"283990fa9d5fb731d786c5bbee94ea4db4910f18c62c03d173fc0a5e494422e8a0b3da7574dae7fa0baf005e504063b3",
"1cc515e1812491058d8b8b226fd85045e746b4937a58b0111b6b7a39dd431b6295bd6b6d05e01e225586b4dab3cbb87a" ])
, ("Kekkak-512", kekkakHash 512, [
"0eab42de4c3ceb9235fc91acffe746b29c29a8c366b7c60e4e67c466f36a4304c00fa9caf9d87976ba469bcbe06713b435f091ef2769fb160cdab33d3670680e",
"d135bb84d0439dbac432247ee573a23ea7d3c9deb2a968eb31d47c4fb45f1ef4422d6c531b5b9bd6f449ebcc449ea94d0a8f05f62130fda612da53c79659f609",
"10f8caabb5b179861da5e447d34b84d604e3eb81830880e1c2135ffc94580a47cb21f6243ec0053d58b1124d13af2090033659075ee718e0f111bb3f69fb24cf" ])
, ("SHA3-224", sha3Hash 224, [
"f71837502ba8e10837bdd8d365adb85591895602fc552b48b7390abd",
"310aee6b30c47350576ac2873fa89fd190cdc488442f3ef654cf23fe",

View File

@ -2,7 +2,9 @@
module KAT_HMAC (tests) where
import qualified Crypto.MAC.HMAC as HMAC
import Crypto.Hash (MD5(..), SHA1(..), SHA256(..), SHA3_224(..), SHA3_256(..), SHA3_384(..), SHA3_512(..)
import Crypto.Hash (MD5(..), SHA1(..), SHA256(..)
, Kekkak_224(..), Kekkak_256(..), Kekkak_384(..), Kekkak_512(..)
, SHA3_224(..), SHA3_256(..), SHA3_384(..), SHA3_512(..)
, HashAlgorithm, digestFromByteString)
import Control.Applicative ((<$>))
import Control.Monad (replicateM)
@ -55,6 +57,29 @@ 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"
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"
]
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"
]
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"
]
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"
]
sha3_key1 = "\x4a\x65\x66\x65"
sha3_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"
@ -84,6 +109,10 @@ macTests =
[ testGroup "hmac-md5" $ map toMACTest $ zip is md5MACVectors
, testGroup "hmac-sha1" $ map toMACTest $ zip is sha1MACVectors
, testGroup "hmac-sha256" $ map toMACTest $ zip is sha256MACVectors
, testGroup "hmac-kekkak-224" $ map toMACTest $ zip is kekkak_224_MAC_Vectors
, testGroup "hmac-kekkak-256" $ map toMACTest $ zip is kekkak_256_MAC_Vectors
, testGroup "hmac-kekkak-384" $ map toMACTest $ zip is kekkak_384_MAC_Vectors
, testGroup "hmac-kekkak-512" $ map toMACTest $ zip is kekkak_512_MAC_Vectors
, testGroup "hmac-sha3-224" $ map toMACTest $ zip is sha3_224_MAC_Vectors
, testGroup "hmac-sha3-256" $ map toMACTest $ zip is sha3_256_MAC_Vectors
, testGroup "hmac-sha3-384" $ map toMACTest $ zip is sha3_384_MAC_Vectors