[HASH] re-enable SHA512t

This commit is contained in:
Vincent Hanquez 2015-05-06 07:53:51 +01:00
parent 6ba517e945
commit 81e335cfff
6 changed files with 68 additions and 47 deletions

View File

@ -18,6 +18,8 @@ module Crypto.Hash.Algorithms
, SHA256(..)
, SHA384(..)
, SHA512(..)
, SHA512t_224(..)
, SHA512t_256(..)
, RIPEMD160(..)
, Tiger(..)
, Kekkak_224(..)
@ -46,6 +48,7 @@ import Crypto.Hash.SHA224
import Crypto.Hash.SHA256
import Crypto.Hash.SHA384
import Crypto.Hash.SHA512
import Crypto.Hash.SHA512t
import Crypto.Hash.SHA3
import Crypto.Hash.Kekkak
import Crypto.Hash.RIPEMD160

View File

@ -5,55 +5,47 @@
-- Stability : experimental
-- Portability : unknown
--
-- A module containing SHA512/t
-- module containing the binding functions to work with the
-- SHA512t cryptographic hash.
--
{-# LANGUAGE ForeignFunctionInterface #-}
module Crypto.Hash.SHA512t
(-- Ctx(..)
-- * Incremental hashing Functions
init -- :: Ctx
, update -- :: Ctx -> ByteString -> Ctx
, finalize -- :: Ctx -> ByteString
-- * Single Pass hashing
--, hash -- :: ByteString -> ByteString
--, hashlazy -- :: ByteString -> ByteString
( SHA512t_224 (..), SHA512t_256 (..)
) where
import Prelude hiding (init, take)
import Data.List (foldl')
import qualified Data.ByteString.Lazy as L
import Crypto.Hash.Types
import Foreign.Ptr (Ptr)
import Data.Word (Word8, Word32)
import qualified Crypto.Hash.SHA512 as SHA512
import Crypto.Internal.Compat
import Crypto.Internal.ByteArray (ByteArray, ByteArrayAccess, take)
--import qualified Crypto.Hash.Internal.SHA512t as SHA512t
--import Crypto.Hash.Internal.SHA512 (withCtxNew)
init = undefined
update = undefined
finalize = undefined
{-
-- | SHA512 Context with variable size output
data Ctx = Ctx !Int !SHA512.Ctx
data SHA512t_224 = SHA512t_224
deriving (Show)
-- | init a context
init :: Int -> Ctx
init t = Ctx t $ unsafeDoIO $ withCtxNew $ \ptr -> SHA512t.internalInitAt t ptr
instance HashAlgorithm SHA512t_224 where
hashBlockSize _ = 128
hashDigestSize _ = 28
hashInternalContextSize _ = 264
hashInternalInit p = c_sha512t_init p 224
hashInternalUpdate = c_sha512t_update
hashInternalFinalize = c_sha512t_finalize
-- | update a context with a bytestring
update :: ByteArrayAccess ba => Ctx -> ba -> Ctx
update (Ctx t ctx) d = Ctx t (SHA512.update ctx d)
data SHA512t_256 = SHA512t_256
deriving (Show)
-- | finalize the context into a digest bytestring
finalize :: ByteArray digest => Ctx -> digest
finalize (Ctx sz ctx) = take (sz `div` 8) (SHA512.finalize ctx)
instance HashAlgorithm SHA512t_256 where
hashBlockSize _ = 128
hashDigestSize _ = 32
hashInternalContextSize _ = 264
hashInternalInit p = c_sha512t_init p 256
hashInternalUpdate = c_sha512t_update
hashInternalFinalize = c_sha512t_finalize
-- | hash a strict bytestring into a digest bytestring
hash :: (ByteArrayAccess ba, ByteArray digest) => Int -> ba -> digest
hash t = finalize . update (init t)
-- | hash a lazy bytestring into a digest bytestring
hashlazy :: ByteArray digest => Int -> L.ByteString -> digest
hashlazy t = finalize . foldl' update (init t) . L.toChunks
-}
foreign import ccall unsafe "cryptonite_sha512t_init"
c_sha512t_init :: Ptr (Context a) -> Word32 -> IO ()
foreign import ccall "cryptonite_sha512t_update"
c_sha512t_update :: Ptr (Context a) -> Ptr Word8 -> Word32 -> IO ()
foreign import ccall unsafe "cryptonite_sha512t_finalize"
c_sha512t_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

View File

@ -196,11 +196,13 @@ void cryptonite_sha512_finalize(struct sha512_ctx *ctx, uint8_t *out)
#include <stdio.h>
void cryptonite_sha512_init_t(struct sha512_ctx *ctx, int t)
void cryptonite_sha512t_init(struct sha512t_ctx *tctx, int t)
{
struct sha512_ctx *ctx = &tctx->ctx;
memset(ctx, 0, sizeof(*ctx));
if (t >= 512)
return;
tctx->t = t;
switch (t) {
case 224:
@ -243,3 +245,17 @@ void cryptonite_sha512_init_t(struct sha512_ctx *ctx, int t)
}
}
}
void cryptonite_sha512t_update(struct sha512t_ctx *ctx, const uint8_t *data, uint32_t len)
{
return cryptonite_sha512_update(&ctx->ctx, data, len);
}
void cryptonite_sha512t_finalize(struct sha512t_ctx *ctx, uint8_t *out)
{
uint8_t intermediate[SHA512_DIGEST_SIZE];
cryptonite_sha512_finalize(&ctx->ctx, intermediate);
memcpy(out, intermediate, ctx->t / 8);
}

View File

@ -33,6 +33,12 @@ struct sha512_ctx
uint64_t h[8];
};
struct sha512t_ctx
{
struct sha512_ctx ctx;
uint64_t t; /* the custom t (e.g. 224 for SHA512/224) */
};
#define sha384_ctx sha512_ctx
#define SHA384_DIGEST_SIZE 64
@ -41,6 +47,8 @@ struct sha512_ctx
#define SHA512_DIGEST_SIZE 64
#define SHA512_CTX_SIZE sizeof(struct sha512_ctx)
#define SHA512t_CTX_SIZE sizeof(struct sha512t_ctx)
void cryptonite_sha384_init(struct sha384_ctx *ctx);
void cryptonite_sha384_update(struct sha384_ctx *ctx, const uint8_t *data, uint32_t len);
void cryptonite_sha384_finalize(struct sha384_ctx *ctx, uint8_t *out);
@ -49,6 +57,9 @@ void cryptonite_sha512_init(struct sha512_ctx *ctx);
void cryptonite_sha512_update(struct sha512_ctx *ctx, const uint8_t *data, uint32_t len);
void cryptonite_sha512_finalize(struct sha512_ctx *ctx, uint8_t *out);
void cryptonite_sha512_init_t(struct sha512_ctx *ctx, int t);
/* only multiples of 8 are supported as valid t values */
void cryptonite_sha512t_init(struct sha512t_ctx *ctx, int t);
void cryptonite_sha512t_update(struct sha512t_ctx *ctx, const uint8_t *data, uint32_t len);
void cryptonite_sha512t_finalize(struct sha512t_ctx *ctx, uint8_t *out);
#endif

View File

@ -29,6 +29,7 @@ hashModules =
, GenHashModule "SHA256" "sha256.h" "sha256" 192 32 64 []
, 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 "SHA3" "sha3.h" "sha3" 360 64 64 [(224,144),(256,136),(384,104),(512,72)]
, GenHashModule "RIPEMD160" "ripemd.h" "ripemd160" 128 20 64 []

View File

@ -56,16 +56,14 @@ expected = [
"cf83e1357eefb8bdf1542850d66d8007d620e4050b5715dc83f4a921d36ce9ce47d0d13c5d85f2b0ff8318d2877eec2f63b931bd47417a81a538327af927da3e",
"07e547d9586f6a73f73fbac0435ed76951218fb7d0c8d788a309d785436bbb642e93a252a954f23912547d1e8a3b5ed6e1bfd7097821233fa0538f3db854fee6",
"3eeee1d0e11733ef152a6c29503b3ae20c4f1f3cda4cb26f1bc1a41f91c7fe4ab3bd86494049e201c4bd5155f31ecb7a3c8606843c4cc8dfcab7da11c8ae5045" ]),
{-
("SHA512/224", sha512_224Hash, [
("SHA512/224", HashAlg SHA512t_224, [
"6ed0dd02806fa89e25de060c19d3ac86cabb87d6a0ddd05c333b84f4",
"944cd2847fb54558d4775db0485a50003111c8e5daa63fe722c6aa37",
"2b9d6565a7e40f780ba8ab7c8dcf41e3ed3b77997f4c55aa987eede5" ]),
("SHA512/256", sha512_256Hash, [
("SHA512/256", HashAlg SHA512t_256, [
"c672b8d1ef56ed28ab87c3622c5114069bdd3ad7b8f9737498d0c01ecef0967a",
"dd9d67b371519c339ed8dbd25af90e976a1eeefd4ad3d889005e532fc5bef04d",
"cc8d255a7f2f38fd50388fd1f65ea7910835c5c1e73da46fba01ea50d5dd76fb" ]),
-}
("RIPEMD160", HashAlg RIPEMD160, [
"9c1185a5c5e9fc54612808977ee8f548b2258d31",
"37f332f68db77bd9d7edd4969571ad671cf9dd3b",