Compare commits
38 Commits
cryptonite
...
uni2work
| Author | SHA1 | Date | |
|---|---|---|---|
|
|
f78fca2504 | ||
|
|
d163f69512 | ||
|
|
9401b4e3fd | ||
|
|
b96ec42d3e | ||
|
|
7dfaf914e6 | ||
|
|
aca61fa1b6 | ||
|
|
20b194fc97 | ||
|
|
cca5d72bf1 | ||
|
|
495eca0bb5 | ||
|
|
309abe378d | ||
|
|
f4f92b702c | ||
|
|
93f50b49b7 | ||
|
|
a8d1d401bc | ||
|
|
b3db979ca0 | ||
|
|
71a630edaf | ||
|
|
365c8978a2 | ||
|
|
8698c9fd94 | ||
|
|
e9c9c770d3 | ||
|
|
9961606e5b | ||
|
|
4b4a641970 | ||
|
|
a6fbe0ed4c | ||
|
|
b6981a4ea5 | ||
|
|
cf89276b5c | ||
|
|
f449a54eb2 | ||
|
|
95b247e5eb | ||
|
|
981b97a132 | ||
|
|
2e0a60f7f7 | ||
|
|
b01f610aa2 | ||
|
|
ef880291e3 | ||
|
|
977c72cac9 | ||
|
|
1cb2cd2f12 | ||
|
|
436b9abc13 | ||
|
|
6f932998ad | ||
|
|
bd84c75f3e | ||
|
|
6f70986cb1 | ||
|
|
633879f801 | ||
|
|
6075b698e1 | ||
|
|
f55636bd43 |
12
CHANGELOG.md
12
CHANGELOG.md
@ -1,3 +1,15 @@
|
|||||||
|
## 0.30
|
||||||
|
|
||||||
|
* Fix some C symbol blake2b prefix to be cryptonite_ prefix (fix mixing with other C library)
|
||||||
|
* add hmac-lazy
|
||||||
|
* Fix compilation with GHC 9.2
|
||||||
|
* Drop support for GHC8.0, GHC8.2, GHC8.4, GHC8.6
|
||||||
|
|
||||||
|
## 0.29
|
||||||
|
|
||||||
|
* advance compilation with gmp breakage due to change upstream
|
||||||
|
* Add native EdDSA support
|
||||||
|
|
||||||
## 0.28
|
## 0.28
|
||||||
|
|
||||||
* Add hash constant time capability
|
* Add hash constant time capability
|
||||||
|
|||||||
@ -283,45 +283,45 @@ pointsMulVarTime (Scalar s1) (Scalar s2) (Point p) =
|
|||||||
withByteArray p $ \pp ->
|
withByteArray p $ \pp ->
|
||||||
ed25519_base_double_scalarmul_vartime out ps1 pp ps2
|
ed25519_base_double_scalarmul_vartime out ps1 pp ps2
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_scalar_eq"
|
foreign import ccall unsafe "cryptonite_ed25519_scalar_eq"
|
||||||
ed25519_scalar_eq :: Ptr Scalar
|
ed25519_scalar_eq :: Ptr Scalar
|
||||||
-> Ptr Scalar
|
-> Ptr Scalar
|
||||||
-> IO CInt
|
-> IO CInt
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_scalar_encode"
|
foreign import ccall unsafe "cryptonite_ed25519_scalar_encode"
|
||||||
ed25519_scalar_encode :: Ptr Word8
|
ed25519_scalar_encode :: Ptr Word8
|
||||||
-> Ptr Scalar
|
-> Ptr Scalar
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_scalar_decode_long"
|
foreign import ccall unsafe "cryptonite_ed25519_scalar_decode_long"
|
||||||
ed25519_scalar_decode_long :: Ptr Scalar
|
ed25519_scalar_decode_long :: Ptr Scalar
|
||||||
-> Ptr Word8
|
-> Ptr Word8
|
||||||
-> CSize
|
-> CSize
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_scalar_add"
|
foreign import ccall unsafe "cryptonite_ed25519_scalar_add"
|
||||||
ed25519_scalar_add :: Ptr Scalar -- sum
|
ed25519_scalar_add :: Ptr Scalar -- sum
|
||||||
-> Ptr Scalar -- a
|
-> Ptr Scalar -- a
|
||||||
-> Ptr Scalar -- b
|
-> Ptr Scalar -- b
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_scalar_mul"
|
foreign import ccall unsafe "cryptonite_ed25519_scalar_mul"
|
||||||
ed25519_scalar_mul :: Ptr Scalar -- out
|
ed25519_scalar_mul :: Ptr Scalar -- out
|
||||||
-> Ptr Scalar -- a
|
-> Ptr Scalar -- a
|
||||||
-> Ptr Scalar -- b
|
-> Ptr Scalar -- b
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_encode"
|
foreign import ccall unsafe "cryptonite_ed25519_point_encode"
|
||||||
ed25519_point_encode :: Ptr Word8
|
ed25519_point_encode :: Ptr Word8
|
||||||
-> Ptr Point
|
-> Ptr Point
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_decode_vartime"
|
foreign import ccall unsafe "cryptonite_ed25519_point_decode_vartime"
|
||||||
ed25519_point_decode_vartime :: Ptr Point
|
ed25519_point_decode_vartime :: Ptr Point
|
||||||
-> Ptr Word8
|
-> Ptr Word8
|
||||||
-> IO CInt
|
-> IO CInt
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_eq"
|
foreign import ccall unsafe "cryptonite_ed25519_point_eq"
|
||||||
ed25519_point_eq :: Ptr Point
|
ed25519_point_eq :: Ptr Point
|
||||||
-> Ptr Point
|
-> Ptr Point
|
||||||
-> IO CInt
|
-> IO CInt
|
||||||
@ -330,23 +330,23 @@ foreign import ccall "cryptonite_ed25519_point_has_prime_order"
|
|||||||
ed25519_point_has_prime_order :: Ptr Point
|
ed25519_point_has_prime_order :: Ptr Point
|
||||||
-> IO CInt
|
-> IO CInt
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_negate"
|
foreign import ccall unsafe "cryptonite_ed25519_point_negate"
|
||||||
ed25519_point_negate :: Ptr Point -- minus_a
|
ed25519_point_negate :: Ptr Point -- minus_a
|
||||||
-> Ptr Point -- a
|
-> Ptr Point -- a
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_add"
|
foreign import ccall unsafe "cryptonite_ed25519_point_add"
|
||||||
ed25519_point_add :: Ptr Point -- sum
|
ed25519_point_add :: Ptr Point -- sum
|
||||||
-> Ptr Point -- a
|
-> Ptr Point -- a
|
||||||
-> Ptr Point -- b
|
-> Ptr Point -- b
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_double"
|
foreign import ccall unsafe "cryptonite_ed25519_point_double"
|
||||||
ed25519_point_double :: Ptr Point -- two_a
|
ed25519_point_double :: Ptr Point -- two_a
|
||||||
-> Ptr Point -- a
|
-> Ptr Point -- a
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
foreign import ccall "cryptonite_ed25519_point_mul_by_cofactor"
|
foreign import ccall unsafe "cryptonite_ed25519_point_mul_by_cofactor"
|
||||||
ed25519_point_mul_by_cofactor :: Ptr Point -- eight_a
|
ed25519_point_mul_by_cofactor :: Ptr Point -- eight_a
|
||||||
-> Ptr Point -- a
|
-> Ptr Point -- a
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|||||||
@ -40,6 +40,8 @@ module Crypto.Hash
|
|||||||
, hash
|
, hash
|
||||||
, hashPrefix
|
, hashPrefix
|
||||||
, hashlazy
|
, hashlazy
|
||||||
|
, hashPutContext
|
||||||
|
, hashGetContext
|
||||||
-- * Hash algorithms
|
-- * Hash algorithms
|
||||||
, module Crypto.Hash.Algorithms
|
, module Crypto.Hash.Algorithms
|
||||||
) where
|
) where
|
||||||
@ -51,10 +53,11 @@ import Crypto.Internal.Compat (unsafeDoIO)
|
|||||||
import Crypto.Hash.Types
|
import Crypto.Hash.Types
|
||||||
import Crypto.Hash.Algorithms
|
import Crypto.Hash.Algorithms
|
||||||
import Foreign.Ptr (Ptr, plusPtr)
|
import Foreign.Ptr (Ptr, plusPtr)
|
||||||
import Crypto.Internal.ByteArray (ByteArrayAccess)
|
import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray)
|
||||||
import qualified Crypto.Internal.ByteArray as B
|
import qualified Crypto.Internal.ByteArray as B
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
import Data.Word (Word8, Word32)
|
import Data.Word (Word8)
|
||||||
|
import Data.Int (Int32)
|
||||||
|
|
||||||
-- | Hash a strict bytestring into a digest.
|
-- | Hash a strict bytestring into a digest.
|
||||||
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
|
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
|
||||||
@ -91,14 +94,14 @@ hashUpdates c l
|
|||||||
mapM_ (\b -> B.withByteArray b (processBlocks ctx (B.length b))) ls
|
mapM_ (\b -> B.withByteArray b (processBlocks ctx (B.length b))) ls
|
||||||
where
|
where
|
||||||
ls = filter (not . B.null) l
|
ls = filter (not . B.null) l
|
||||||
-- process the data in 4GB chunks to fit in uint32_t
|
-- process the data in 2GB chunks to fit in uint32_t and Int on 32 bit systems
|
||||||
processBlocks ctx bytesLeft dataPtr
|
processBlocks ctx bytesLeft dataPtr
|
||||||
| bytesLeft == 0 = return ()
|
| bytesLeft == 0 = return ()
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
hashInternalUpdate ctx dataPtr (fromIntegral actuallyProcessed)
|
hashInternalUpdate ctx dataPtr (fromIntegral actuallyProcessed)
|
||||||
processBlocks ctx (bytesLeft - actuallyProcessed) (dataPtr `plusPtr` actuallyProcessed)
|
processBlocks ctx (bytesLeft - actuallyProcessed) (dataPtr `plusPtr` actuallyProcessed)
|
||||||
where
|
where
|
||||||
actuallyProcessed = min bytesLeft (fromIntegral (maxBound :: Word32))
|
actuallyProcessed = min bytesLeft (fromIntegral (maxBound :: Int32))
|
||||||
|
|
||||||
-- | Finalize a context and return a digest.
|
-- | Finalize a context and return a digest.
|
||||||
hashFinalize :: forall a . HashAlgorithm a
|
hashFinalize :: forall a . HashAlgorithm a
|
||||||
@ -158,3 +161,16 @@ digestFromByteString = from undefined
|
|||||||
unsafeFreeze muArray
|
unsafeFreeze muArray
|
||||||
where
|
where
|
||||||
count = CountOf (B.length ba)
|
count = CountOf (B.length ba)
|
||||||
|
|
||||||
|
hashPutContext :: forall a ba. (HashAlgorithmResumable a, ByteArray ba) => Context a -> ba
|
||||||
|
hashPutContext !c = B.allocAndFreeze (hashInternalContextSize (undefined :: a)) $ \(ptr :: Ptr Word8) ->
|
||||||
|
B.withByteArray c $ \(ctx :: Ptr (Context a)) -> hashInternalPutContextBE ctx ptr
|
||||||
|
|
||||||
|
hashGetContext :: forall a ba. (HashAlgorithmResumable a, ByteArrayAccess ba) => ba -> Maybe (Context a)
|
||||||
|
hashGetContext = from undefined
|
||||||
|
where
|
||||||
|
from :: a -> ba -> Maybe (Context a)
|
||||||
|
from alg bs
|
||||||
|
| B.length bs == (hashInternalContextSize alg) = Just $ Context $ B.allocAndFreeze (B.length bs) $ \(ctx :: Ptr (Context a)) ->
|
||||||
|
B.withByteArray bs $ \ptr -> hashInternalGetContextBE ptr ctx
|
||||||
|
| otherwise = Nothing
|
||||||
|
|||||||
@ -10,6 +10,7 @@
|
|||||||
module Crypto.Hash.Algorithms
|
module Crypto.Hash.Algorithms
|
||||||
( HashAlgorithm
|
( HashAlgorithm
|
||||||
, HashAlgorithmPrefix
|
, HashAlgorithmPrefix
|
||||||
|
, HashAlgorithmResumable
|
||||||
-- * Hash algorithms
|
-- * Hash algorithms
|
||||||
, Blake2s_160(..)
|
, Blake2s_160(..)
|
||||||
, Blake2s_224(..)
|
, Blake2s_224(..)
|
||||||
@ -55,7 +56,7 @@ module Crypto.Hash.Algorithms
|
|||||||
, Whirlpool(..)
|
, Whirlpool(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Crypto.Hash.Types (HashAlgorithm, HashAlgorithmPrefix)
|
import Crypto.Hash.Types (HashAlgorithm, HashAlgorithmPrefix, HashAlgorithmResumable)
|
||||||
import Crypto.Hash.Blake2s
|
import Crypto.Hash.Blake2s
|
||||||
import Crypto.Hash.Blake2sp
|
import Crypto.Hash.Blake2sp
|
||||||
import Crypto.Hash.Blake2b
|
import Crypto.Hash.Blake2b
|
||||||
|
|||||||
@ -37,6 +37,10 @@ instance HashAlgorithm Keccak_224 where
|
|||||||
hashInternalUpdate = c_keccak_update
|
hashInternalUpdate = c_keccak_update
|
||||||
hashInternalFinalize p = c_keccak_finalize p 224
|
hashInternalFinalize p = c_keccak_finalize p 224
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable Keccak_224 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | Keccak (256 bits) cryptographic hash algorithm
|
-- | Keccak (256 bits) cryptographic hash algorithm
|
||||||
data Keccak_256 = Keccak_256
|
data Keccak_256 = Keccak_256
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -52,6 +56,10 @@ instance HashAlgorithm Keccak_256 where
|
|||||||
hashInternalUpdate = c_keccak_update
|
hashInternalUpdate = c_keccak_update
|
||||||
hashInternalFinalize p = c_keccak_finalize p 256
|
hashInternalFinalize p = c_keccak_finalize p 256
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable Keccak_256 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | Keccak (384 bits) cryptographic hash algorithm
|
-- | Keccak (384 bits) cryptographic hash algorithm
|
||||||
data Keccak_384 = Keccak_384
|
data Keccak_384 = Keccak_384
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -67,6 +75,10 @@ instance HashAlgorithm Keccak_384 where
|
|||||||
hashInternalUpdate = c_keccak_update
|
hashInternalUpdate = c_keccak_update
|
||||||
hashInternalFinalize p = c_keccak_finalize p 384
|
hashInternalFinalize p = c_keccak_finalize p 384
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable Keccak_384 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | Keccak (512 bits) cryptographic hash algorithm
|
-- | Keccak (512 bits) cryptographic hash algorithm
|
||||||
data Keccak_512 = Keccak_512
|
data Keccak_512 = Keccak_512
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -82,6 +94,10 @@ instance HashAlgorithm Keccak_512 where
|
|||||||
hashInternalUpdate = c_keccak_update
|
hashInternalUpdate = c_keccak_update
|
||||||
hashInternalFinalize p = c_keccak_finalize p 512
|
hashInternalFinalize p = c_keccak_finalize p 512
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable Keccak_512 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
|
|
||||||
foreign import ccall unsafe "cryptonite_keccak_init"
|
foreign import ccall unsafe "cryptonite_keccak_init"
|
||||||
c_keccak_init :: Ptr (Context a) -> Word32 -> IO ()
|
c_keccak_init :: Ptr (Context a) -> Word32 -> IO ()
|
||||||
@ -91,3 +107,9 @@ foreign import ccall "cryptonite_keccak_update"
|
|||||||
|
|
||||||
foreign import ccall unsafe "cryptonite_keccak_finalize"
|
foreign import ccall unsafe "cryptonite_keccak_finalize"
|
||||||
c_keccak_finalize :: Ptr (Context a) -> Word32 -> Ptr (Digest a) -> IO ()
|
c_keccak_finalize :: Ptr (Context a) -> Word32 -> Ptr (Digest a) -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_ctx_to_be"
|
||||||
|
c_sha3_ctx_to_be :: Ptr (Context a) -> Ptr Word8 -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_be_to_ctx"
|
||||||
|
c_sha3_be_to_ctx :: Ptr Word8 -> Ptr (Context a) -> IO ()
|
||||||
|
|||||||
@ -37,6 +37,10 @@ instance HashAlgorithm SHA3_224 where
|
|||||||
hashInternalUpdate = c_sha3_update
|
hashInternalUpdate = c_sha3_update
|
||||||
hashInternalFinalize p = c_sha3_finalize p 224
|
hashInternalFinalize p = c_sha3_finalize p 224
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable SHA3_224 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | SHA3 (256 bits) cryptographic hash algorithm
|
-- | SHA3 (256 bits) cryptographic hash algorithm
|
||||||
data SHA3_256 = SHA3_256
|
data SHA3_256 = SHA3_256
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -52,6 +56,10 @@ instance HashAlgorithm SHA3_256 where
|
|||||||
hashInternalUpdate = c_sha3_update
|
hashInternalUpdate = c_sha3_update
|
||||||
hashInternalFinalize p = c_sha3_finalize p 256
|
hashInternalFinalize p = c_sha3_finalize p 256
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable SHA3_256 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | SHA3 (384 bits) cryptographic hash algorithm
|
-- | SHA3 (384 bits) cryptographic hash algorithm
|
||||||
data SHA3_384 = SHA3_384
|
data SHA3_384 = SHA3_384
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -67,6 +75,10 @@ instance HashAlgorithm SHA3_384 where
|
|||||||
hashInternalUpdate = c_sha3_update
|
hashInternalUpdate = c_sha3_update
|
||||||
hashInternalFinalize p = c_sha3_finalize p 384
|
hashInternalFinalize p = c_sha3_finalize p 384
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable SHA3_384 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | SHA3 (512 bits) cryptographic hash algorithm
|
-- | SHA3 (512 bits) cryptographic hash algorithm
|
||||||
data SHA3_512 = SHA3_512
|
data SHA3_512 = SHA3_512
|
||||||
deriving (Show,Data)
|
deriving (Show,Data)
|
||||||
@ -82,6 +94,10 @@ instance HashAlgorithm SHA3_512 where
|
|||||||
hashInternalUpdate = c_sha3_update
|
hashInternalUpdate = c_sha3_update
|
||||||
hashInternalFinalize p = c_sha3_finalize p 512
|
hashInternalFinalize p = c_sha3_finalize p 512
|
||||||
|
|
||||||
|
instance HashAlgorithmResumable SHA3_512 where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
|
|
||||||
foreign import ccall unsafe "cryptonite_sha3_init"
|
foreign import ccall unsafe "cryptonite_sha3_init"
|
||||||
c_sha3_init :: Ptr (Context a) -> Word32 -> IO ()
|
c_sha3_init :: Ptr (Context a) -> Word32 -> IO ()
|
||||||
@ -91,3 +107,9 @@ foreign import ccall "cryptonite_sha3_update"
|
|||||||
|
|
||||||
foreign import ccall unsafe "cryptonite_sha3_finalize"
|
foreign import ccall unsafe "cryptonite_sha3_finalize"
|
||||||
c_sha3_finalize :: Ptr (Context a) -> Word32 -> Ptr (Digest a) -> IO ()
|
c_sha3_finalize :: Ptr (Context a) -> Word32 -> Ptr (Digest a) -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_ctx_to_be"
|
||||||
|
c_sha3_ctx_to_be :: Ptr (Context a) -> Ptr Word8 -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_be_to_ctx"
|
||||||
|
c_sha3_be_to_ctx :: Ptr Word8 -> Ptr (Context a) -> IO ()
|
||||||
|
|||||||
@ -62,6 +62,10 @@ instance KnownNat bitlen => HashSHAKE (SHAKE128 bitlen) where
|
|||||||
cshakeInternalFinalize = cshakeFinalizeOutput (Proxy :: Proxy bitlen)
|
cshakeInternalFinalize = cshakeFinalizeOutput (Proxy :: Proxy bitlen)
|
||||||
cshakeOutputLength _ = integralNatVal (Proxy :: Proxy bitlen)
|
cshakeOutputLength _ = integralNatVal (Proxy :: Proxy bitlen)
|
||||||
|
|
||||||
|
instance KnownNat bitlen => HashAlgorithmResumable (SHAKE128 bitlen) where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
-- | SHAKE256 (256 bits) extendable output function. Supports an arbitrary
|
-- | SHAKE256 (256 bits) extendable output function. Supports an arbitrary
|
||||||
-- digest size, to be specified as a type parameter of kind 'Nat'.
|
-- digest size, to be specified as a type parameter of kind 'Nat'.
|
||||||
--
|
--
|
||||||
@ -86,6 +90,10 @@ instance KnownNat bitlen => HashSHAKE (SHAKE256 bitlen) where
|
|||||||
cshakeInternalFinalize = cshakeFinalizeOutput (Proxy :: Proxy bitlen)
|
cshakeInternalFinalize = cshakeFinalizeOutput (Proxy :: Proxy bitlen)
|
||||||
cshakeOutputLength _ = integralNatVal (Proxy :: Proxy bitlen)
|
cshakeOutputLength _ = integralNatVal (Proxy :: Proxy bitlen)
|
||||||
|
|
||||||
|
instance KnownNat bitlen => HashAlgorithmResumable (SHAKE256 bitlen) where
|
||||||
|
hashInternalPutContextBE = c_sha3_ctx_to_be
|
||||||
|
hashInternalGetContextBE = c_sha3_be_to_ctx
|
||||||
|
|
||||||
shakeFinalizeOutput :: KnownNat bitlen
|
shakeFinalizeOutput :: KnownNat bitlen
|
||||||
=> proxy bitlen
|
=> proxy bitlen
|
||||||
-> Ptr (Context a)
|
-> Ptr (Context a)
|
||||||
@ -129,3 +137,9 @@ foreign import ccall unsafe "cryptonite_sha3_finalize_cshake"
|
|||||||
|
|
||||||
foreign import ccall unsafe "cryptonite_sha3_output"
|
foreign import ccall unsafe "cryptonite_sha3_output"
|
||||||
c_sha3_output :: Ptr (Context a) -> Ptr (Digest a) -> Word32 -> IO ()
|
c_sha3_output :: Ptr (Context a) -> Ptr (Digest a) -> Word32 -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_ctx_to_be"
|
||||||
|
c_sha3_ctx_to_be :: Ptr (Context a) -> Ptr Word8 -> IO ()
|
||||||
|
|
||||||
|
foreign import ccall unsafe "cryptonite_sha3_be_to_ctx"
|
||||||
|
c_sha3_be_to_ctx :: Ptr Word8 -> Ptr (Context a) -> IO ()
|
||||||
|
|||||||
@ -15,6 +15,7 @@
|
|||||||
module Crypto.Hash.Types
|
module Crypto.Hash.Types
|
||||||
( HashAlgorithm(..)
|
( HashAlgorithm(..)
|
||||||
, HashAlgorithmPrefix(..)
|
, HashAlgorithmPrefix(..)
|
||||||
|
, HashAlgorithmResumable(..)
|
||||||
, Context(..)
|
, Context(..)
|
||||||
, Digest(..)
|
, Digest(..)
|
||||||
) where
|
) where
|
||||||
@ -70,6 +71,9 @@ class HashAlgorithm a => HashAlgorithmPrefix a where
|
|||||||
-> Word32
|
-> Word32
|
||||||
-> Ptr (Digest a)
|
-> Ptr (Digest a)
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
class HashAlgorithm a => HashAlgorithmResumable a where
|
||||||
|
hashInternalPutContextBE :: Ptr (Context a) -> Ptr Word8 -> IO ()
|
||||||
|
hashInternalGetContextBE :: Ptr Word8 -> Ptr (Context a) -> IO ()
|
||||||
|
|
||||||
{-
|
{-
|
||||||
hashContextGetAlgorithm :: HashAlgorithm a => Context a -> a
|
hashContextGetAlgorithm :: HashAlgorithm a => Context a -> a
|
||||||
|
|||||||
53
Crypto/Internal/Builder.hs
Normal file
53
Crypto/Internal/Builder.hs
Normal file
@ -0,0 +1,53 @@
|
|||||||
|
-- |
|
||||||
|
-- Module : Crypto.Internal.Builder
|
||||||
|
-- License : BSD-style
|
||||||
|
-- Maintainer : Olivier Chéron <olivier.cheron@gmail.com>
|
||||||
|
-- Stability : stable
|
||||||
|
-- Portability : Good
|
||||||
|
--
|
||||||
|
-- Delaying and merging ByteArray allocations. This is similar to module
|
||||||
|
-- "Data.ByteArray.Pack" except the total length is computed automatically based
|
||||||
|
-- on what is appended.
|
||||||
|
--
|
||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
module Crypto.Internal.Builder
|
||||||
|
( Builder
|
||||||
|
, buildAndFreeze
|
||||||
|
, builderLength
|
||||||
|
, byte
|
||||||
|
, bytes
|
||||||
|
, zero
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.ByteArray (ByteArray, ByteArrayAccess)
|
||||||
|
import qualified Data.ByteArray as B
|
||||||
|
import Data.Memory.PtrMethods (memSet)
|
||||||
|
|
||||||
|
import Foreign.Ptr (Ptr, plusPtr)
|
||||||
|
import Foreign.Storable (poke)
|
||||||
|
|
||||||
|
import Crypto.Internal.Imports hiding (empty)
|
||||||
|
|
||||||
|
data Builder = Builder !Int (Ptr Word8 -> IO ()) -- size and initializer
|
||||||
|
|
||||||
|
instance Semigroup Builder where
|
||||||
|
(Builder s1 f1) <> (Builder s2 f2) = Builder (s1 + s2) f
|
||||||
|
where f p = f1 p >> f2 (p `plusPtr` s1)
|
||||||
|
|
||||||
|
builderLength :: Builder -> Int
|
||||||
|
builderLength (Builder s _) = s
|
||||||
|
|
||||||
|
buildAndFreeze :: ByteArray ba => Builder -> ba
|
||||||
|
buildAndFreeze (Builder s f) = B.allocAndFreeze s f
|
||||||
|
|
||||||
|
byte :: Word8 -> Builder
|
||||||
|
byte !b = Builder 1 (`poke` b)
|
||||||
|
|
||||||
|
bytes :: ByteArrayAccess ba => ba -> Builder
|
||||||
|
bytes bs = Builder (B.length bs) (B.copyByteArrayToPtr bs)
|
||||||
|
|
||||||
|
zero :: Int -> Builder
|
||||||
|
zero s = if s > 0 then Builder s (\p -> memSet p 0 s) else empty
|
||||||
|
|
||||||
|
empty :: Builder
|
||||||
|
empty = Builder 0 (const $ return ())
|
||||||
@ -23,15 +23,21 @@ module Crypto.Internal.CompatPrim
|
|||||||
, convert4To32
|
, convert4To32
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GHC.Prim
|
|
||||||
#if !defined(ARCH_IS_LITTLE_ENDIAN) && !defined(ARCH_IS_BIG_ENDIAN)
|
#if !defined(ARCH_IS_LITTLE_ENDIAN) && !defined(ARCH_IS_BIG_ENDIAN)
|
||||||
import Data.Memory.Endian (getSystemEndianness, Endianness(..))
|
import Data.Memory.Endian (getSystemEndianness, Endianness(..))
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ >= 902
|
||||||
|
import GHC.Prim
|
||||||
|
#else
|
||||||
|
import GHC.Prim hiding (Word32#)
|
||||||
|
type Word32# = Word#
|
||||||
|
#endif
|
||||||
|
|
||||||
-- | Byteswap Word# to or from Big Endian
|
-- | Byteswap Word# to or from Big Endian
|
||||||
--
|
--
|
||||||
-- On a big endian machine, this function is a nop.
|
-- On a big endian machine, this function is a nop.
|
||||||
be32Prim :: Word# -> Word#
|
be32Prim :: Word32# -> Word32#
|
||||||
#ifdef ARCH_IS_LITTLE_ENDIAN
|
#ifdef ARCH_IS_LITTLE_ENDIAN
|
||||||
be32Prim = byteswap32Prim
|
be32Prim = byteswap32Prim
|
||||||
#elif defined(ARCH_IS_BIG_ENDIAN)
|
#elif defined(ARCH_IS_BIG_ENDIAN)
|
||||||
@ -43,7 +49,7 @@ be32Prim w = if getSystemEndianness == LittleEndian then byteswap32Prim w else w
|
|||||||
-- | Byteswap Word# to or from Little Endian
|
-- | Byteswap Word# to or from Little Endian
|
||||||
--
|
--
|
||||||
-- On a little endian machine, this function is a nop.
|
-- On a little endian machine, this function is a nop.
|
||||||
le32Prim :: Word# -> Word#
|
le32Prim :: Word32# -> Word32#
|
||||||
#ifdef ARCH_IS_LITTLE_ENDIAN
|
#ifdef ARCH_IS_LITTLE_ENDIAN
|
||||||
le32Prim w = w
|
le32Prim w = w
|
||||||
#elif defined(ARCH_IS_BIG_ENDIAN)
|
#elif defined(ARCH_IS_BIG_ENDIAN)
|
||||||
@ -54,16 +60,11 @@ le32Prim w = if getSystemEndianness == LittleEndian then w else byteswap32Prim w
|
|||||||
|
|
||||||
-- | Simple compatibility for byteswap the lower 32 bits of a Word#
|
-- | Simple compatibility for byteswap the lower 32 bits of a Word#
|
||||||
-- at the primitive level
|
-- at the primitive level
|
||||||
byteswap32Prim :: Word# -> Word#
|
byteswap32Prim :: Word32# -> Word32#
|
||||||
#if __GLASGOW_HASKELL__ >= 708
|
#if __GLASGOW_HASKELL__ >= 902
|
||||||
byteswap32Prim w = byteSwap32# w
|
byteswap32Prim w = wordToWord32# (byteSwap32# (word32ToWord# w))
|
||||||
#else
|
#else
|
||||||
byteswap32Prim w =
|
byteswap32Prim w = byteSwap32# w
|
||||||
let !a = uncheckedShiftL# w 24#
|
|
||||||
!b = and# (uncheckedShiftL# w 8#) 0x00ff0000##
|
|
||||||
!c = and# (uncheckedShiftRL# w 8#) 0x0000ff00##
|
|
||||||
!d = and# (uncheckedShiftRL# w 24#) 0x000000ff##
|
|
||||||
in or# a (or# b (or# c d))
|
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
-- | Combine 4 word8 [a,b,c,d] to a word32 representing [a,b,c,d]
|
-- | Combine 4 word8 [a,b,c,d] to a word32 representing [a,b,c,d]
|
||||||
|
|||||||
@ -5,11 +5,15 @@
|
|||||||
-- Stability : experimental
|
-- Stability : experimental
|
||||||
-- Portability : unknown
|
-- Portability : unknown
|
||||||
--
|
--
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
module Crypto.Internal.Imports
|
module Crypto.Internal.Imports
|
||||||
( module X
|
( module X
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Word as X
|
import Data.Word as X
|
||||||
|
#if !(MIN_VERSION_base(4,11,0))
|
||||||
|
import Data.Semigroup as X (Semigroup(..))
|
||||||
|
#endif
|
||||||
import Control.Applicative as X
|
import Control.Applicative as X
|
||||||
import Control.Monad as X (forM, forM_, void)
|
import Control.Monad as X (forM, forM_, void)
|
||||||
import Control.Arrow as X (first, second)
|
import Control.Arrow as X (first, second)
|
||||||
|
|||||||
@ -12,6 +12,7 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
module Crypto.MAC.HMAC
|
module Crypto.MAC.HMAC
|
||||||
( hmac
|
( hmac
|
||||||
|
, hmacLazy
|
||||||
, HMAC(..)
|
, HMAC(..)
|
||||||
-- * Incremental
|
-- * Incremental
|
||||||
, Context(..)
|
, Context(..)
|
||||||
@ -28,6 +29,7 @@ import Crypto.Internal.ByteArray (ScrubbedBytes, ByteArrayAccess)
|
|||||||
import qualified Crypto.Internal.ByteArray as B
|
import qualified Crypto.Internal.ByteArray as B
|
||||||
import Data.Memory.PtrMethods
|
import Data.Memory.PtrMethods
|
||||||
import Crypto.Internal.Compat
|
import Crypto.Internal.Compat
|
||||||
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
-- | Represent an HMAC that is a phantom type with the hash used to produce the mac.
|
-- | Represent an HMAC that is a phantom type with the hash used to produce the mac.
|
||||||
--
|
--
|
||||||
@ -39,13 +41,20 @@ newtype HMAC a = HMAC { hmacGetDigest :: Digest a }
|
|||||||
instance Eq (HMAC a) where
|
instance Eq (HMAC a) where
|
||||||
(HMAC b1) == (HMAC b2) = B.constEq b1 b2
|
(HMAC b1) == (HMAC b2) = B.constEq b1 b2
|
||||||
|
|
||||||
-- | compute a MAC using the supplied hashing function
|
-- | Compute a MAC using the supplied hashing function
|
||||||
hmac :: (ByteArrayAccess key, ByteArrayAccess message, HashAlgorithm a)
|
hmac :: (ByteArrayAccess key, ByteArrayAccess message, HashAlgorithm a)
|
||||||
=> key -- ^ Secret key
|
=> key -- ^ Secret key
|
||||||
-> message -- ^ Message to MAC
|
-> message -- ^ Message to MAC
|
||||||
-> HMAC a
|
-> HMAC a
|
||||||
hmac secret msg = finalize $ updates (initialize secret) [msg]
|
hmac secret msg = finalize $ updates (initialize secret) [msg]
|
||||||
|
|
||||||
|
-- | Compute a MAC using the supplied hashing function, for a lazy input
|
||||||
|
hmacLazy :: (ByteArrayAccess key, HashAlgorithm a)
|
||||||
|
=> key -- ^ Secret key
|
||||||
|
-> L.ByteString -- ^ Message to MAC
|
||||||
|
-> HMAC a
|
||||||
|
hmacLazy secret msg = finalize $ updates (initialize secret) (L.toChunks msg)
|
||||||
|
|
||||||
-- | Represent an ongoing HMAC state, that can be appended with 'update'
|
-- | Represent an ongoing HMAC state, that can be appended with 'update'
|
||||||
-- and finalize to an HMAC with 'hmacFinalize'
|
-- and finalize to an HMAC with 'hmacFinalize'
|
||||||
data Context hashalg = Context !(Hash.Context hashalg) !(Hash.Context hashalg)
|
data Context hashalg = Context !(Hash.Context hashalg) !(Hash.Context hashalg)
|
||||||
|
|||||||
@ -27,13 +27,12 @@ import qualified Crypto.Hash as H
|
|||||||
import Crypto.Hash.SHAKE (HashSHAKE(..))
|
import Crypto.Hash.SHAKE (HashSHAKE(..))
|
||||||
import Crypto.Hash.Types (HashAlgorithm(..), Digest(..))
|
import Crypto.Hash.Types (HashAlgorithm(..), Digest(..))
|
||||||
import qualified Crypto.Hash.Types as H
|
import qualified Crypto.Hash.Types as H
|
||||||
import Foreign.Ptr (Ptr, plusPtr)
|
import Crypto.Internal.Builder
|
||||||
import Foreign.Storable (poke)
|
import Crypto.Internal.Imports
|
||||||
|
import Foreign.Ptr (Ptr)
|
||||||
import Data.Bits (shiftR)
|
import Data.Bits (shiftR)
|
||||||
import Data.ByteArray (ByteArray, ByteArrayAccess)
|
import Data.ByteArray (ByteArrayAccess)
|
||||||
import qualified Data.ByteArray as B
|
import qualified Data.ByteArray as B
|
||||||
import Data.Word (Word8)
|
|
||||||
import Data.Memory.PtrMethods (memSet)
|
|
||||||
|
|
||||||
|
|
||||||
-- cSHAKE
|
-- cSHAKE
|
||||||
@ -47,8 +46,8 @@ cshakeInit n s p = H.Context $ B.allocAndFreeze c $ \(ptr :: Ptr (H.Context a))
|
|||||||
where
|
where
|
||||||
c = hashInternalContextSize (undefined :: a)
|
c = hashInternalContextSize (undefined :: a)
|
||||||
w = hashBlockSize (undefined :: a)
|
w = hashBlockSize (undefined :: a)
|
||||||
x = encodeString n <+> encodeString s
|
x = encodeString n <> encodeString s
|
||||||
b = builderAllocAndFreeze (bytepad x w) :: B.Bytes
|
b = buildAndFreeze (bytepad x w) :: B.Bytes
|
||||||
|
|
||||||
cshakeUpdate :: (HashSHAKE a, ByteArrayAccess ba)
|
cshakeUpdate :: (HashSHAKE a, ByteArrayAccess ba)
|
||||||
=> H.Context a -> ba -> H.Context a
|
=> H.Context a -> ba -> H.Context a
|
||||||
@ -77,7 +76,7 @@ cshakeFinalize !c s =
|
|||||||
-- The Eq instance is constant time. No Show instance is provided, to avoid
|
-- The Eq instance is constant time. No Show instance is provided, to avoid
|
||||||
-- printing by mistake.
|
-- printing by mistake.
|
||||||
newtype KMAC a = KMAC { kmacGetDigest :: Digest a }
|
newtype KMAC a = KMAC { kmacGetDigest :: Digest a }
|
||||||
deriving ByteArrayAccess
|
deriving (ByteArrayAccess,NFData)
|
||||||
|
|
||||||
instance Eq (KMAC a) where
|
instance Eq (KMAC a) where
|
||||||
(KMAC b1) == (KMAC b2) = B.constEq b1 b2
|
(KMAC b1) == (KMAC b2) = B.constEq b1 b2
|
||||||
@ -99,7 +98,7 @@ initialize str key = Context $ cshakeInit n str p
|
|||||||
where
|
where
|
||||||
n = B.pack [75,77,65,67] :: B.Bytes -- "KMAC"
|
n = B.pack [75,77,65,67] :: B.Bytes -- "KMAC"
|
||||||
w = hashBlockSize (undefined :: a)
|
w = hashBlockSize (undefined :: a)
|
||||||
p = builderAllocAndFreeze (bytepad (encodeString key) w) :: B.ScrubbedBytes
|
p = buildAndFreeze (bytepad (encodeString key) w) :: B.ScrubbedBytes
|
||||||
|
|
||||||
-- | Incrementally update a KMAC context.
|
-- | Incrementally update a KMAC context.
|
||||||
update :: (HashSHAKE a, ByteArrayAccess ba) => Context a -> ba -> Context a
|
update :: (HashSHAKE a, ByteArrayAccess ba) => Context a -> ba -> Context a
|
||||||
@ -114,56 +113,32 @@ finalize :: forall a . HashSHAKE a => Context a -> KMAC a
|
|||||||
finalize (Context ctx) = KMAC $ cshakeFinalize ctx suffix
|
finalize (Context ctx) = KMAC $ cshakeFinalize ctx suffix
|
||||||
where
|
where
|
||||||
l = cshakeOutputLength (undefined :: a)
|
l = cshakeOutputLength (undefined :: a)
|
||||||
suffix = builderAllocAndFreeze (rightEncode l) :: B.Bytes
|
suffix = buildAndFreeze (rightEncode l) :: B.Bytes
|
||||||
|
|
||||||
|
|
||||||
-- Utilities
|
-- Utilities
|
||||||
|
|
||||||
bytepad :: Builder -> Int -> Builder
|
bytepad :: Builder -> Int -> Builder
|
||||||
bytepad x w = prefix <+> x <+> zero padLen
|
bytepad x w = prefix <> x <> zero padLen
|
||||||
where
|
where
|
||||||
prefix = leftEncode w
|
prefix = leftEncode w
|
||||||
padLen = (w - builderLength prefix - builderLength x) `mod` w
|
padLen = (w - builderLength prefix - builderLength x) `mod` w
|
||||||
|
|
||||||
encodeString :: ByteArrayAccess bin => bin -> Builder
|
encodeString :: ByteArrayAccess bin => bin -> Builder
|
||||||
encodeString s = leftEncode (8 * B.length s) <+> bytes s
|
encodeString s = leftEncode (8 * B.length s) <> bytes s
|
||||||
|
|
||||||
leftEncode :: Int -> Builder
|
leftEncode :: Int -> Builder
|
||||||
leftEncode x = byte len <+> digits
|
leftEncode x = byte len <> digits
|
||||||
where
|
where
|
||||||
digits = i2osp x
|
digits = i2osp x
|
||||||
len = fromIntegral (builderLength digits)
|
len = fromIntegral (builderLength digits)
|
||||||
|
|
||||||
rightEncode :: Int -> Builder
|
rightEncode :: Int -> Builder
|
||||||
rightEncode x = digits <+> byte len
|
rightEncode x = digits <> byte len
|
||||||
where
|
where
|
||||||
digits = i2osp x
|
digits = i2osp x
|
||||||
len = fromIntegral (builderLength digits)
|
len = fromIntegral (builderLength digits)
|
||||||
|
|
||||||
i2osp :: Int -> Builder
|
i2osp :: Int -> Builder
|
||||||
i2osp i | i >= 256 = i2osp (shiftR i 8) <+> byte (fromIntegral i)
|
i2osp i | i >= 256 = i2osp (shiftR i 8) <> byte (fromIntegral i)
|
||||||
| otherwise = byte (fromIntegral i)
|
| otherwise = byte (fromIntegral i)
|
||||||
|
|
||||||
|
|
||||||
-- Delaying and merging ByteArray allocations
|
|
||||||
|
|
||||||
data Builder = Builder !Int (Ptr Word8 -> IO ()) -- size and initializer
|
|
||||||
|
|
||||||
(<+>) :: Builder -> Builder -> Builder
|
|
||||||
(Builder s1 f1) <+> (Builder s2 f2) = Builder (s1 + s2) f
|
|
||||||
where f p = f1 p >> f2 (p `plusPtr` s1)
|
|
||||||
|
|
||||||
builderLength :: Builder -> Int
|
|
||||||
builderLength (Builder s _) = s
|
|
||||||
|
|
||||||
builderAllocAndFreeze :: ByteArray ba => Builder -> ba
|
|
||||||
builderAllocAndFreeze (Builder s f) = B.allocAndFreeze s f
|
|
||||||
|
|
||||||
byte :: Word8 -> Builder
|
|
||||||
byte !b = Builder 1 (`poke` b)
|
|
||||||
|
|
||||||
bytes :: ByteArrayAccess ba => ba -> Builder
|
|
||||||
bytes bs = Builder (B.length bs) (B.copyByteArrayToPtr bs)
|
|
||||||
|
|
||||||
zero :: Int -> Builder
|
|
||||||
zero s = Builder s (\p -> memSet p 0 s)
|
|
||||||
|
|||||||
@ -72,7 +72,9 @@ gmpLog2 _ = GmpUnsupported
|
|||||||
-- | Compute the power modulus using extra security to remain constant
|
-- | Compute the power modulus using extra security to remain constant
|
||||||
-- time wise through GMP
|
-- time wise through GMP
|
||||||
gmpPowModSecInteger :: Integer -> Integer -> Integer -> GmpSupported Integer
|
gmpPowModSecInteger :: Integer -> Integer -> Integer -> GmpSupported Integer
|
||||||
#if MIN_VERSION_integer_gmp(1,0,2)
|
#if MIN_VERSION_integer_gmp(1,1,0)
|
||||||
|
gmpPowModSecInteger _ _ _ = GmpUnsupported
|
||||||
|
#elif MIN_VERSION_integer_gmp(1,0,2)
|
||||||
gmpPowModSecInteger b e m = GmpSupported (powModSecInteger b e m)
|
gmpPowModSecInteger b e m = GmpSupported (powModSecInteger b e m)
|
||||||
#elif MIN_VERSION_integer_gmp(1,0,0)
|
#elif MIN_VERSION_integer_gmp(1,0,0)
|
||||||
gmpPowModSecInteger _ _ _ = GmpUnsupported
|
gmpPowModSecInteger _ _ _ = GmpUnsupported
|
||||||
@ -103,7 +105,9 @@ gmpInverse _ _ = GmpUnsupported
|
|||||||
|
|
||||||
-- | Get the next prime from a specific value through GMP
|
-- | Get the next prime from a specific value through GMP
|
||||||
gmpNextPrime :: Integer -> GmpSupported Integer
|
gmpNextPrime :: Integer -> GmpSupported Integer
|
||||||
#if MIN_VERSION_integer_gmp(0,5,1)
|
#if MIN_VERSION_integer_gmp(1,1,0)
|
||||||
|
gmpNextPrime _ = GmpUnsupported
|
||||||
|
#elif MIN_VERSION_integer_gmp(0,5,1)
|
||||||
gmpNextPrime n = GmpSupported (nextPrimeInteger n)
|
gmpNextPrime n = GmpSupported (nextPrimeInteger n)
|
||||||
#else
|
#else
|
||||||
gmpNextPrime _ = GmpUnsupported
|
gmpNextPrime _ = GmpUnsupported
|
||||||
@ -111,7 +115,9 @@ gmpNextPrime _ = GmpUnsupported
|
|||||||
|
|
||||||
-- | Test if a number is prime using Miller Rabin
|
-- | Test if a number is prime using Miller Rabin
|
||||||
gmpTestPrimeMillerRabin :: Int -> Integer -> GmpSupported Bool
|
gmpTestPrimeMillerRabin :: Int -> Integer -> GmpSupported Bool
|
||||||
#if MIN_VERSION_integer_gmp(0,5,1)
|
#if MIN_VERSION_integer_gmp(1,1,0)
|
||||||
|
gmpTestPrimeMillerRabin _ _ = GmpUnsupported
|
||||||
|
#elif MIN_VERSION_integer_gmp(0,5,1)
|
||||||
gmpTestPrimeMillerRabin (I# tries) !n = GmpSupported $
|
gmpTestPrimeMillerRabin (I# tries) !n = GmpSupported $
|
||||||
case testPrimeInteger n tries of
|
case testPrimeInteger n tries of
|
||||||
0# -> False
|
0# -> False
|
||||||
|
|||||||
390
Crypto/PubKey/EdDSA.hs
Normal file
390
Crypto/PubKey/EdDSA.hs
Normal file
@ -0,0 +1,390 @@
|
|||||||
|
-- |
|
||||||
|
-- Module : Crypto.PubKey.EdDSA
|
||||||
|
-- License : BSD-style
|
||||||
|
-- Maintainer : Olivier Chéron <olivier.cheron@gmail.com>
|
||||||
|
-- Stability : experimental
|
||||||
|
-- Portability : unknown
|
||||||
|
--
|
||||||
|
-- EdDSA signature generation and verification, implemented in Haskell and
|
||||||
|
-- parameterized with elliptic curve and hash algorithm. Only edwards25519 is
|
||||||
|
-- supported at the moment.
|
||||||
|
--
|
||||||
|
-- The module provides \"context\" and \"prehash\" variants defined in
|
||||||
|
-- <https://tools.ietf.org/html/rfc8032 RFC 8032>.
|
||||||
|
--
|
||||||
|
-- This implementation is most useful when wanting to customize the hash
|
||||||
|
-- algorithm. See module "Crypto.PubKey.Ed25519" for faster Ed25519 with
|
||||||
|
-- SHA-512.
|
||||||
|
--
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE RankNTypes #-}
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
module Crypto.PubKey.EdDSA
|
||||||
|
( SecretKey
|
||||||
|
, PublicKey
|
||||||
|
, Signature
|
||||||
|
-- * Curves with EdDSA implementation
|
||||||
|
, EllipticCurveEdDSA(CurveDigestSize)
|
||||||
|
, publicKeySize
|
||||||
|
, secretKeySize
|
||||||
|
, signatureSize
|
||||||
|
-- * Smart constructors
|
||||||
|
, signature
|
||||||
|
, publicKey
|
||||||
|
, secretKey
|
||||||
|
-- * Methods
|
||||||
|
, toPublic
|
||||||
|
, sign
|
||||||
|
, signCtx
|
||||||
|
, signPh
|
||||||
|
, verify
|
||||||
|
, verifyCtx
|
||||||
|
, verifyPh
|
||||||
|
, generateSecretKey
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Bits
|
||||||
|
import Data.ByteArray (ByteArray, ByteArrayAccess, Bytes, ScrubbedBytes, View)
|
||||||
|
import qualified Data.ByteArray as B
|
||||||
|
import Data.ByteString (ByteString)
|
||||||
|
import Data.Proxy
|
||||||
|
|
||||||
|
import Crypto.ECC
|
||||||
|
import qualified Crypto.ECC.Edwards25519 as Edwards25519
|
||||||
|
import Crypto.Error
|
||||||
|
import Crypto.Hash (Digest)
|
||||||
|
import Crypto.Hash.IO
|
||||||
|
import Crypto.Random
|
||||||
|
|
||||||
|
import GHC.TypeLits (KnownNat, Nat)
|
||||||
|
|
||||||
|
import Crypto.Internal.Builder
|
||||||
|
import Crypto.Internal.Compat
|
||||||
|
import Crypto.Internal.Imports
|
||||||
|
import Crypto.Internal.Nat (integralNatVal)
|
||||||
|
|
||||||
|
import Foreign.Storable
|
||||||
|
|
||||||
|
|
||||||
|
-- API
|
||||||
|
|
||||||
|
-- | An EdDSA Secret key
|
||||||
|
newtype SecretKey curve = SecretKey ScrubbedBytes
|
||||||
|
deriving (Show,Eq,ByteArrayAccess,NFData)
|
||||||
|
|
||||||
|
-- | An EdDSA public key
|
||||||
|
newtype PublicKey curve hash = PublicKey Bytes
|
||||||
|
deriving (Show,Eq,ByteArrayAccess,NFData)
|
||||||
|
|
||||||
|
-- | An EdDSA signature
|
||||||
|
newtype Signature curve hash = Signature Bytes
|
||||||
|
deriving (Show,Eq,ByteArrayAccess,NFData)
|
||||||
|
|
||||||
|
-- | Elliptic curves with an implementation of EdDSA
|
||||||
|
class ( EllipticCurveBasepointArith curve
|
||||||
|
, KnownNat (CurveDigestSize curve)
|
||||||
|
) => EllipticCurveEdDSA curve where
|
||||||
|
|
||||||
|
-- | Size of the digest for this curve (in bytes)
|
||||||
|
type CurveDigestSize curve :: Nat
|
||||||
|
|
||||||
|
-- | Size of secret keys for this curve (in bytes)
|
||||||
|
secretKeySize :: proxy curve -> Int
|
||||||
|
|
||||||
|
-- hash with specified parameters
|
||||||
|
hashWithDom :: (HashAlgorithm hash, ByteArrayAccess ctx, ByteArrayAccess msg)
|
||||||
|
=> proxy curve -> hash -> Bool -> ctx -> Builder -> msg -> Bytes
|
||||||
|
|
||||||
|
-- conversion between scalar, point and public key
|
||||||
|
pointPublic :: proxy curve -> Point curve -> PublicKey curve hash
|
||||||
|
publicPoint :: proxy curve -> PublicKey curve hash -> CryptoFailable (Point curve)
|
||||||
|
encodeScalarLE :: ByteArray bs => proxy curve -> Scalar curve -> bs
|
||||||
|
decodeScalarLE :: ByteArrayAccess bs => proxy curve -> bs -> CryptoFailable (Scalar curve)
|
||||||
|
|
||||||
|
-- how to use bits in a secret key
|
||||||
|
scheduleSecret :: ( HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
)
|
||||||
|
=> proxy curve
|
||||||
|
-> hash
|
||||||
|
-> SecretKey curve
|
||||||
|
-> (Scalar curve, View Bytes)
|
||||||
|
|
||||||
|
-- | Size of public keys for this curve (in bytes)
|
||||||
|
publicKeySize :: EllipticCurveEdDSA curve => proxy curve -> Int
|
||||||
|
publicKeySize prx = signatureSize prx `div` 2
|
||||||
|
|
||||||
|
-- | Size of signatures for this curve (in bytes)
|
||||||
|
signatureSize :: forall proxy curve . EllipticCurveEdDSA curve
|
||||||
|
=> proxy curve -> Int
|
||||||
|
signatureSize _ = integralNatVal (Proxy :: Proxy (CurveDigestSize curve))
|
||||||
|
|
||||||
|
|
||||||
|
-- Constructors
|
||||||
|
|
||||||
|
-- | Try to build a public key from a bytearray
|
||||||
|
publicKey :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ba
|
||||||
|
)
|
||||||
|
=> proxy curve -> hash -> ba -> CryptoFailable (PublicKey curve hash)
|
||||||
|
publicKey prx _ bs
|
||||||
|
| B.length bs == publicKeySize prx =
|
||||||
|
CryptoPassed (PublicKey $ B.convert bs)
|
||||||
|
| otherwise =
|
||||||
|
CryptoFailed CryptoError_PublicKeySizeInvalid
|
||||||
|
|
||||||
|
-- | Try to build a secret key from a bytearray
|
||||||
|
secretKey :: (EllipticCurveEdDSA curve, ByteArrayAccess ba)
|
||||||
|
=> proxy curve -> ba -> CryptoFailable (SecretKey curve)
|
||||||
|
secretKey prx bs
|
||||||
|
| B.length bs == secretKeySize prx =
|
||||||
|
CryptoPassed (SecretKey $ B.convert bs)
|
||||||
|
| otherwise =
|
||||||
|
CryptoFailed CryptoError_SecretKeyStructureInvalid
|
||||||
|
|
||||||
|
-- | Try to build a signature from a bytearray
|
||||||
|
signature :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ba
|
||||||
|
)
|
||||||
|
=> proxy curve -> hash -> ba -> CryptoFailable (Signature curve hash)
|
||||||
|
signature prx _ bs
|
||||||
|
| B.length bs == signatureSize prx =
|
||||||
|
CryptoPassed (Signature $ B.convert bs)
|
||||||
|
| otherwise =
|
||||||
|
CryptoFailed CryptoError_SecretKeyStructureInvalid
|
||||||
|
|
||||||
|
|
||||||
|
-- Conversions
|
||||||
|
|
||||||
|
-- | Generate a secret key
|
||||||
|
generateSecretKey :: (EllipticCurveEdDSA curve, MonadRandom m)
|
||||||
|
=> proxy curve -> m (SecretKey curve)
|
||||||
|
generateSecretKey prx = SecretKey <$> getRandomBytes (secretKeySize prx)
|
||||||
|
|
||||||
|
-- | Create a public key from a secret key
|
||||||
|
toPublic :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
)
|
||||||
|
=> proxy curve -> hash -> SecretKey curve -> PublicKey curve hash
|
||||||
|
toPublic prx alg priv =
|
||||||
|
let p = pointBaseSmul prx (secretScalar prx alg priv)
|
||||||
|
in pointPublic prx p
|
||||||
|
|
||||||
|
secretScalar :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
)
|
||||||
|
=> proxy curve -> hash -> SecretKey curve -> Scalar curve
|
||||||
|
secretScalar prx alg priv = fst (scheduleSecret prx alg priv)
|
||||||
|
|
||||||
|
|
||||||
|
-- EdDSA signature generation & verification
|
||||||
|
|
||||||
|
-- | Sign a message using the key pair
|
||||||
|
sign :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash
|
||||||
|
sign prx = signCtx prx emptyCtx
|
||||||
|
|
||||||
|
-- | Verify a message
|
||||||
|
verify :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> PublicKey curve hash -> msg -> Signature curve hash -> Bool
|
||||||
|
verify prx = verifyCtx prx emptyCtx
|
||||||
|
|
||||||
|
-- | Sign a message using the key pair under context @ctx@
|
||||||
|
signCtx :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> ctx -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash
|
||||||
|
signCtx prx = signPhCtx prx False
|
||||||
|
|
||||||
|
-- | Verify a message under context @ctx@
|
||||||
|
verifyCtx :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> ctx -> PublicKey curve hash -> msg -> Signature curve hash -> Bool
|
||||||
|
verifyCtx prx = verifyPhCtx prx False
|
||||||
|
|
||||||
|
-- | Sign a prehashed message using the key pair under context @ctx@
|
||||||
|
signPh :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
)
|
||||||
|
=> proxy curve -> ctx -> SecretKey curve -> PublicKey curve hash -> Digest prehash -> Signature curve hash
|
||||||
|
signPh prx = signPhCtx prx True
|
||||||
|
|
||||||
|
-- | Verify a prehashed message under context @ctx@
|
||||||
|
verifyPh :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
)
|
||||||
|
=> proxy curve -> ctx -> PublicKey curve hash -> Digest prehash -> Signature curve hash -> Bool
|
||||||
|
verifyPh prx = verifyPhCtx prx True
|
||||||
|
|
||||||
|
signPhCtx :: forall proxy curve hash ctx msg .
|
||||||
|
( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> Bool -> ctx -> SecretKey curve -> PublicKey curve hash -> msg -> Signature curve hash
|
||||||
|
signPhCtx prx ph ctx priv pub msg =
|
||||||
|
let alg = undefined :: hash
|
||||||
|
(s, prefix) = scheduleSecret prx alg priv
|
||||||
|
digR = hashWithDom prx alg ph ctx (bytes prefix) msg
|
||||||
|
r = decodeScalarNoErr prx digR
|
||||||
|
pR = pointBaseSmul prx r
|
||||||
|
bsR = encodePoint prx pR
|
||||||
|
sK = getK prx ph ctx pub bsR msg
|
||||||
|
sS = scalarAdd prx r (scalarMul prx sK s)
|
||||||
|
in encodeSignature prx (bsR, pR, sS)
|
||||||
|
|
||||||
|
verifyPhCtx :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> Bool -> ctx -> PublicKey curve hash -> msg -> Signature curve hash -> Bool
|
||||||
|
verifyPhCtx prx ph ctx pub msg sig =
|
||||||
|
case doVerify of
|
||||||
|
CryptoPassed verified -> verified
|
||||||
|
CryptoFailed _ -> False
|
||||||
|
where
|
||||||
|
doVerify = do
|
||||||
|
(bsR, pR, sS) <- decodeSignature prx sig
|
||||||
|
nPub <- pointNegate prx `fmap` publicPoint prx pub
|
||||||
|
let sK = getK prx ph ctx pub bsR msg
|
||||||
|
pR' = pointsSmulVarTime prx sS sK nPub
|
||||||
|
return (pR == pR')
|
||||||
|
|
||||||
|
emptyCtx :: Bytes
|
||||||
|
emptyCtx = B.empty
|
||||||
|
|
||||||
|
getK :: forall proxy curve hash ctx msg .
|
||||||
|
( EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
, ByteArrayAccess ctx
|
||||||
|
, ByteArrayAccess msg
|
||||||
|
)
|
||||||
|
=> proxy curve -> Bool -> ctx -> PublicKey curve hash -> Bytes -> msg -> Scalar curve
|
||||||
|
getK prx ph ctx (PublicKey pub) bsR msg =
|
||||||
|
let alg = undefined :: hash
|
||||||
|
digK = hashWithDom prx alg ph ctx (bytes bsR <> bytes pub) msg
|
||||||
|
in decodeScalarNoErr prx digK
|
||||||
|
|
||||||
|
encodeSignature :: EllipticCurveEdDSA curve
|
||||||
|
=> proxy curve
|
||||||
|
-> (Bytes, Point curve, Scalar curve)
|
||||||
|
-> Signature curve hash
|
||||||
|
encodeSignature prx (bsR, _, sS) = Signature $ buildAndFreeze $
|
||||||
|
bytes bsR <> bytes bsS <> zero len0
|
||||||
|
where
|
||||||
|
bsS = encodeScalarLE prx sS :: Bytes
|
||||||
|
len0 = signatureSize prx - B.length bsR - B.length bsS
|
||||||
|
|
||||||
|
decodeSignature :: ( EllipticCurveEdDSA curve
|
||||||
|
, HashDigestSize hash ~ CurveDigestSize curve
|
||||||
|
)
|
||||||
|
=> proxy curve
|
||||||
|
-> Signature curve hash
|
||||||
|
-> CryptoFailable (Bytes, Point curve, Scalar curve)
|
||||||
|
decodeSignature prx (Signature bs) = do
|
||||||
|
let (bsR, bsS) = B.splitAt (publicKeySize prx) bs
|
||||||
|
pR <- decodePoint prx bsR
|
||||||
|
sS <- decodeScalarLE prx bsS
|
||||||
|
return (bsR, pR, sS)
|
||||||
|
|
||||||
|
-- implementations are supposed to decode any scalar up to the size of the digest
|
||||||
|
decodeScalarNoErr :: (EllipticCurveEdDSA curve, ByteArrayAccess bs)
|
||||||
|
=> proxy curve -> bs -> Scalar curve
|
||||||
|
decodeScalarNoErr prx = unwrap "decodeScalarNoErr" . decodeScalarLE prx
|
||||||
|
|
||||||
|
unwrap :: String -> CryptoFailable a -> a
|
||||||
|
unwrap name (CryptoFailed _) = error (name ++ ": assumption failed")
|
||||||
|
unwrap _ (CryptoPassed x) = x
|
||||||
|
|
||||||
|
|
||||||
|
-- Ed25519 implementation
|
||||||
|
|
||||||
|
instance EllipticCurveEdDSA Curve_Edwards25519 where
|
||||||
|
type CurveDigestSize Curve_Edwards25519 = 64
|
||||||
|
secretKeySize _ = 32
|
||||||
|
|
||||||
|
hashWithDom _ alg ph ctx bss
|
||||||
|
| not ph && B.null ctx = digestDomMsg alg bss
|
||||||
|
| otherwise = digestDomMsg alg (dom <> bss)
|
||||||
|
where dom = bytes ("SigEd25519 no Ed25519 collisions" :: ByteString) <>
|
||||||
|
byte (if ph then 1 else 0) <>
|
||||||
|
byte (fromIntegral $ B.length ctx) <>
|
||||||
|
bytes ctx
|
||||||
|
|
||||||
|
pointPublic _ = PublicKey . Edwards25519.pointEncode
|
||||||
|
publicPoint _ = Edwards25519.pointDecode
|
||||||
|
encodeScalarLE _ = Edwards25519.scalarEncode
|
||||||
|
decodeScalarLE _ = Edwards25519.scalarDecodeLong
|
||||||
|
|
||||||
|
scheduleSecret prx alg priv =
|
||||||
|
(decodeScalarNoErr prx clamped, B.dropView hashed 32)
|
||||||
|
where
|
||||||
|
hashed = digest alg $ \update -> update priv
|
||||||
|
|
||||||
|
clamped :: Bytes
|
||||||
|
clamped = B.copyAndFreeze (B.takeView hashed 32) $ \p -> do
|
||||||
|
b0 <- peekElemOff p 0 :: IO Word8
|
||||||
|
b31 <- peekElemOff p 31 :: IO Word8
|
||||||
|
pokeElemOff p 31 ((b31 .&. 0x7F) .|. 0x40)
|
||||||
|
pokeElemOff p 0 (b0 .&. 0xF8)
|
||||||
|
|
||||||
|
|
||||||
|
{-
|
||||||
|
Optimize hashing by limiting the number of roundtrips between Haskell and C.
|
||||||
|
Hash "update" functions do not use unsafe FFI call, so better concanetate
|
||||||
|
small fragments together and call the update function once.
|
||||||
|
|
||||||
|
Using the IO hash interface avoids context buffer copies.
|
||||||
|
|
||||||
|
Data type Digest is not used directly but converted to Bytes early. Any use of
|
||||||
|
withByteArray on the unpinned Digest backend would require copy through a
|
||||||
|
pinned trampoline.
|
||||||
|
-}
|
||||||
|
|
||||||
|
digestDomMsg :: (HashAlgorithm alg, ByteArrayAccess msg)
|
||||||
|
=> alg -> Builder -> msg -> Bytes
|
||||||
|
digestDomMsg alg bss bs = digest alg $ \update ->
|
||||||
|
update (buildAndFreeze bss :: Bytes) >> update bs
|
||||||
|
|
||||||
|
digest :: HashAlgorithm alg
|
||||||
|
=> alg
|
||||||
|
-> ((forall bs . ByteArrayAccess bs => bs -> IO ()) -> IO ())
|
||||||
|
-> Bytes
|
||||||
|
digest alg fn = B.convert $ unsafeDoIO $ do
|
||||||
|
mc <- hashMutableInitWith alg
|
||||||
|
fn (hashMutableUpdate mc)
|
||||||
|
hashMutableFinalize mc
|
||||||
@ -25,10 +25,9 @@ replenish :: Int -> [EntropyBackend] -> Ptr Word8 -> IO ()
|
|||||||
replenish _ [] _ = fail "cryptonite: random: cannot get any source of entropy on this system"
|
replenish _ [] _ = fail "cryptonite: random: cannot get any source of entropy on this system"
|
||||||
replenish poolSize backends ptr = loop 0 backends ptr poolSize
|
replenish poolSize backends ptr = loop 0 backends ptr poolSize
|
||||||
where loop :: Int -> [EntropyBackend] -> Ptr Word8 -> Int -> IO ()
|
where loop :: Int -> [EntropyBackend] -> Ptr Word8 -> Int -> IO ()
|
||||||
loop retry [] p n | n == 0 = return ()
|
loop _ _ _ 0 = return ()
|
||||||
| retry == 3 = error "cryptonite: random: cannot fully replenish"
|
loop retry [] p n | retry == 3 = error "cryptonite: random: cannot fully replenish"
|
||||||
| otherwise = loop (retry+1) backends p n
|
| otherwise = loop (retry+1) backends p n
|
||||||
loop _ (_:_) _ 0 = return ()
|
|
||||||
loop retry (b:bs) p n = do
|
loop retry (b:bs) p n = do
|
||||||
r <- gatherBackend b p n
|
r <- gatherBackend b p n
|
||||||
loop retry bs (p `plusPtr` r) (n - r)
|
loop retry bs (p `plusPtr` r) (n - r)
|
||||||
|
|||||||
@ -1,6 +1,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ExistentialQuantification #-}
|
{-# LANGUAGE ExistentialQuantification #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Gauge.Main
|
import Gauge.Main
|
||||||
@ -24,6 +25,8 @@ import qualified Crypto.PubKey.DH as DH
|
|||||||
import qualified Crypto.PubKey.ECC.Types as ECC
|
import qualified Crypto.PubKey.ECC.Types as ECC
|
||||||
import qualified Crypto.PubKey.ECC.Prim as ECC
|
import qualified Crypto.PubKey.ECC.Prim as ECC
|
||||||
import qualified Crypto.PubKey.ECDSA as ECDSA
|
import qualified Crypto.PubKey.ECDSA as ECDSA
|
||||||
|
import qualified Crypto.PubKey.Ed25519 as Ed25519
|
||||||
|
import qualified Crypto.PubKey.EdDSA as EdDSA
|
||||||
import Crypto.Random
|
import Crypto.Random
|
||||||
|
|
||||||
import Control.DeepSeq (NFData)
|
import Control.DeepSeq (NFData)
|
||||||
@ -325,6 +328,44 @@ benchECDSA = map doECDSABench curveHashes
|
|||||||
, ("secp521r1_sha512", CurveHashECDSA Curve_P521R1 SHA512)
|
, ("secp521r1_sha512", CurveHashECDSA Curve_P521R1 SHA512)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
benchEdDSA =
|
||||||
|
[ bgroup "EdDSA-Ed25519" benchGenEd25519
|
||||||
|
, bgroup "Ed25519" benchEd25519
|
||||||
|
]
|
||||||
|
where
|
||||||
|
benchGen prx alg =
|
||||||
|
[ bench "sign" $ perBatchEnv (genEnv prx alg) (run_gen_sign prx)
|
||||||
|
, bench "verify" $ perBatchEnv (genEnv prx alg) (run_gen_verify prx)
|
||||||
|
]
|
||||||
|
|
||||||
|
benchGenEd25519 = benchGen (Just Curve_Edwards25519) SHA512
|
||||||
|
benchEd25519 =
|
||||||
|
[ bench "sign" $ perBatchEnv ed25519Env run_ed25519_sign
|
||||||
|
, bench "verify" $ perBatchEnv ed25519Env run_ed25519_verify
|
||||||
|
]
|
||||||
|
|
||||||
|
msg = B.empty -- empty message = worst-case scenario showing API overhead
|
||||||
|
|
||||||
|
genEnv prx alg _ = do
|
||||||
|
sec <- EdDSA.generateSecretKey prx
|
||||||
|
let pub = EdDSA.toPublic prx alg sec
|
||||||
|
sig = EdDSA.sign prx sec pub msg
|
||||||
|
return (sec, pub, sig)
|
||||||
|
|
||||||
|
run_gen_sign prx (sec, pub, _) = return (EdDSA.sign prx sec pub msg)
|
||||||
|
|
||||||
|
run_gen_verify prx (_, pub, sig) = return (EdDSA.verify prx pub msg sig)
|
||||||
|
|
||||||
|
ed25519Env _ = do
|
||||||
|
sec <- Ed25519.generateSecretKey
|
||||||
|
let pub = Ed25519.toPublic sec
|
||||||
|
sig = Ed25519.sign sec pub msg
|
||||||
|
return (sec, pub, sig)
|
||||||
|
|
||||||
|
run_ed25519_sign (sec, pub, _) = return (Ed25519.sign sec pub msg)
|
||||||
|
|
||||||
|
run_ed25519_verify (_, pub, sig) = return (Ed25519.verify pub msg sig)
|
||||||
|
|
||||||
main = defaultMain
|
main = defaultMain
|
||||||
[ bgroup "hash" benchHash
|
[ bgroup "hash" benchHash
|
||||||
, bgroup "block-cipher" benchBlockCipher
|
, bgroup "block-cipher" benchBlockCipher
|
||||||
@ -338,5 +379,6 @@ main = defaultMain
|
|||||||
, bgroup "ECDH" benchECDH
|
, bgroup "ECDH" benchECDH
|
||||||
]
|
]
|
||||||
, bgroup "ECDSA" benchECDSA
|
, bgroup "ECDSA" benchECDSA
|
||||||
|
, bgroup "EdDSA" benchEdDSA
|
||||||
, bgroup "F2m" benchF2m
|
, bgroup "F2m" benchF2m
|
||||||
]
|
]
|
||||||
|
|||||||
@ -165,7 +165,7 @@ static __m128i gfmulx(__m128i v)
|
|||||||
TARGET_AESNI
|
TARGET_AESNI
|
||||||
static __m128i gfmul_generic(__m128i tag, const table_4bit htable)
|
static __m128i gfmul_generic(__m128i tag, const table_4bit htable)
|
||||||
{
|
{
|
||||||
aes_block _t;
|
aes_block _t ALIGNMENT(16);
|
||||||
_mm_store_si128((__m128i *) &_t, tag);
|
_mm_store_si128((__m128i *) &_t, tag);
|
||||||
cryptonite_aes_generic_gf_mul(&_t, htable);
|
cryptonite_aes_generic_gf_mul(&_t, htable);
|
||||||
tag = _mm_load_si128((__m128i *) &_t);
|
tag = _mm_load_si128((__m128i *) &_t);
|
||||||
|
|||||||
@ -83,25 +83,25 @@ static int blake2b_long(void *pout, size_t outlen, const void *in, size_t inlen)
|
|||||||
} while ((void)0, 0)
|
} while ((void)0, 0)
|
||||||
|
|
||||||
if (outlen <= BLAKE2B_OUTBYTES) {
|
if (outlen <= BLAKE2B_OUTBYTES) {
|
||||||
TRY(blake2b_init(&blake_state, outlen));
|
TRY(_cryptonite_blake2b_init(&blake_state, outlen));
|
||||||
TRY(blake2b_update(&blake_state, outlen_bytes, sizeof(outlen_bytes)));
|
TRY(_cryptonite_blake2b_update(&blake_state, outlen_bytes, sizeof(outlen_bytes)));
|
||||||
TRY(blake2b_update(&blake_state, in, inlen));
|
TRY(_cryptonite_blake2b_update(&blake_state, in, inlen));
|
||||||
TRY(blake2b_final(&blake_state, out, outlen));
|
TRY(_cryptonite_blake2b_final(&blake_state, out, outlen));
|
||||||
} else {
|
} else {
|
||||||
uint32_t toproduce;
|
uint32_t toproduce;
|
||||||
uint8_t out_buffer[BLAKE2B_OUTBYTES];
|
uint8_t out_buffer[BLAKE2B_OUTBYTES];
|
||||||
uint8_t in_buffer[BLAKE2B_OUTBYTES];
|
uint8_t in_buffer[BLAKE2B_OUTBYTES];
|
||||||
TRY(blake2b_init(&blake_state, BLAKE2B_OUTBYTES));
|
TRY(_cryptonite_blake2b_init(&blake_state, BLAKE2B_OUTBYTES));
|
||||||
TRY(blake2b_update(&blake_state, outlen_bytes, sizeof(outlen_bytes)));
|
TRY(_cryptonite_blake2b_update(&blake_state, outlen_bytes, sizeof(outlen_bytes)));
|
||||||
TRY(blake2b_update(&blake_state, in, inlen));
|
TRY(_cryptonite_blake2b_update(&blake_state, in, inlen));
|
||||||
TRY(blake2b_final(&blake_state, out_buffer, BLAKE2B_OUTBYTES));
|
TRY(_cryptonite_blake2b_final(&blake_state, out_buffer, BLAKE2B_OUTBYTES));
|
||||||
memcpy(out, out_buffer, BLAKE2B_OUTBYTES / 2);
|
memcpy(out, out_buffer, BLAKE2B_OUTBYTES / 2);
|
||||||
out += BLAKE2B_OUTBYTES / 2;
|
out += BLAKE2B_OUTBYTES / 2;
|
||||||
toproduce = (uint32_t)outlen - BLAKE2B_OUTBYTES / 2;
|
toproduce = (uint32_t)outlen - BLAKE2B_OUTBYTES / 2;
|
||||||
|
|
||||||
while (toproduce > BLAKE2B_OUTBYTES) {
|
while (toproduce > BLAKE2B_OUTBYTES) {
|
||||||
memcpy(in_buffer, out_buffer, BLAKE2B_OUTBYTES);
|
memcpy(in_buffer, out_buffer, BLAKE2B_OUTBYTES);
|
||||||
TRY(blake2b(out_buffer, BLAKE2B_OUTBYTES, in_buffer,
|
TRY(_cryptonite_blake2b(out_buffer, BLAKE2B_OUTBYTES, in_buffer,
|
||||||
BLAKE2B_OUTBYTES, NULL, 0));
|
BLAKE2B_OUTBYTES, NULL, 0));
|
||||||
memcpy(out, out_buffer, BLAKE2B_OUTBYTES / 2);
|
memcpy(out, out_buffer, BLAKE2B_OUTBYTES / 2);
|
||||||
out += BLAKE2B_OUTBYTES / 2;
|
out += BLAKE2B_OUTBYTES / 2;
|
||||||
@ -109,7 +109,7 @@ static int blake2b_long(void *pout, size_t outlen, const void *in, size_t inlen)
|
|||||||
}
|
}
|
||||||
|
|
||||||
memcpy(in_buffer, out_buffer, BLAKE2B_OUTBYTES);
|
memcpy(in_buffer, out_buffer, BLAKE2B_OUTBYTES);
|
||||||
TRY(blake2b(out_buffer, toproduce, in_buffer, BLAKE2B_OUTBYTES, NULL,
|
TRY(_cryptonite_blake2b(out_buffer, toproduce, in_buffer, BLAKE2B_OUTBYTES, NULL,
|
||||||
0));
|
0));
|
||||||
memcpy(out, out_buffer, toproduce);
|
memcpy(out, out_buffer, toproduce);
|
||||||
}
|
}
|
||||||
@ -597,31 +597,31 @@ void initial_hash(uint8_t *blockhash, argon2_context *context,
|
|||||||
return;
|
return;
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_init(&BlakeHash, ARGON2_PREHASH_DIGEST_LENGTH);
|
_cryptonite_blake2b_init(&BlakeHash, ARGON2_PREHASH_DIGEST_LENGTH);
|
||||||
|
|
||||||
store32(&value, context->lanes);
|
store32(&value, context->lanes);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, context->outlen);
|
store32(&value, context->outlen);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, context->m_cost);
|
store32(&value, context->m_cost);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, context->t_cost);
|
store32(&value, context->t_cost);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, context->version);
|
store32(&value, context->version);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, (uint32_t)type);
|
store32(&value, (uint32_t)type);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
store32(&value, context->pwdlen);
|
store32(&value, context->pwdlen);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
if (context->pwd != NULL) {
|
if (context->pwd != NULL) {
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)context->pwd,
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)context->pwd,
|
||||||
context->pwdlen);
|
context->pwdlen);
|
||||||
|
|
||||||
if (context->flags & ARGON2_FLAG_CLEAR_PASSWORD) {
|
if (context->flags & ARGON2_FLAG_CLEAR_PASSWORD) {
|
||||||
@ -631,18 +631,18 @@ void initial_hash(uint8_t *blockhash, argon2_context *context,
|
|||||||
}
|
}
|
||||||
|
|
||||||
store32(&value, context->saltlen);
|
store32(&value, context->saltlen);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
if (context->salt != NULL) {
|
if (context->salt != NULL) {
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)context->salt,
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)context->salt,
|
||||||
context->saltlen);
|
context->saltlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
store32(&value, context->secretlen);
|
store32(&value, context->secretlen);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
if (context->secret != NULL) {
|
if (context->secret != NULL) {
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)context->secret,
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)context->secret,
|
||||||
context->secretlen);
|
context->secretlen);
|
||||||
|
|
||||||
if (context->flags & ARGON2_FLAG_CLEAR_SECRET) {
|
if (context->flags & ARGON2_FLAG_CLEAR_SECRET) {
|
||||||
@ -652,14 +652,14 @@ void initial_hash(uint8_t *blockhash, argon2_context *context,
|
|||||||
}
|
}
|
||||||
|
|
||||||
store32(&value, context->adlen);
|
store32(&value, context->adlen);
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)&value, sizeof(value));
|
||||||
|
|
||||||
if (context->ad != NULL) {
|
if (context->ad != NULL) {
|
||||||
blake2b_update(&BlakeHash, (const uint8_t *)context->ad,
|
_cryptonite_blake2b_update(&BlakeHash, (const uint8_t *)context->ad,
|
||||||
context->adlen);
|
context->adlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_final(&BlakeHash, blockhash, ARGON2_PREHASH_DIGEST_LENGTH);
|
_cryptonite_blake2b_final(&BlakeHash, blockhash, ARGON2_PREHASH_DIGEST_LENGTH);
|
||||||
}
|
}
|
||||||
static
|
static
|
||||||
int initialize(argon2_instance_t *instance, argon2_context *context) {
|
int initialize(argon2_instance_t *instance, argon2_context *context) {
|
||||||
|
|||||||
@ -142,51 +142,51 @@ extern "C" {
|
|||||||
};
|
};
|
||||||
|
|
||||||
/* Streaming API */
|
/* Streaming API */
|
||||||
int blake2s_init( blake2s_state *S, size_t outlen );
|
int _cryptonite_blake2s_init( blake2s_state *S, size_t outlen );
|
||||||
int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2s_init_param( blake2s_state *S, const blake2s_param *P );
|
int _cryptonite_blake2s_init_param( blake2s_state *S, const blake2s_param *P );
|
||||||
int blake2s_update( blake2s_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2s_update( blake2s_state *S, const void *in, size_t inlen );
|
||||||
int blake2s_final( blake2s_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2s_final( blake2s_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2b_init( blake2b_state *S, size_t outlen );
|
int _cryptonite_blake2b_init( blake2b_state *S, size_t outlen );
|
||||||
int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2b_init_param( blake2b_state *S, const blake2b_param *P );
|
int _cryptonite_blake2b_init_param( blake2b_state *S, const blake2b_param *P );
|
||||||
int blake2b_update( blake2b_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2b_update( blake2b_state *S, const void *in, size_t inlen );
|
||||||
int blake2b_final( blake2b_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2b_final( blake2b_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2sp_init( blake2sp_state *S, size_t outlen );
|
int _cryptonite_blake2sp_init( blake2sp_state *S, size_t outlen );
|
||||||
int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2sp_update( blake2sp_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2sp_update( blake2sp_state *S, const void *in, size_t inlen );
|
||||||
int blake2sp_final( blake2sp_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2sp_final( blake2sp_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2bp_init( blake2bp_state *S, size_t outlen );
|
int _cryptonite_blake2bp_init( blake2bp_state *S, size_t outlen );
|
||||||
int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2bp_update( blake2bp_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2bp_update( blake2bp_state *S, const void *in, size_t inlen );
|
||||||
int blake2bp_final( blake2bp_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2bp_final( blake2bp_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
/* Variable output length API */
|
/* Variable output length API */
|
||||||
int blake2xs_init( blake2xs_state *S, const size_t outlen );
|
int _cryptonite_blake2xs_init( blake2xs_state *S, const size_t outlen );
|
||||||
int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2xs_update( blake2xs_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2xs_update( blake2xs_state *S, const void *in, size_t inlen );
|
||||||
int blake2xs_final(blake2xs_state *S, void *out, size_t outlen);
|
int _cryptonite_blake2xs_final(blake2xs_state *S, void *out, size_t outlen);
|
||||||
|
|
||||||
int blake2xb_init( blake2xb_state *S, const size_t outlen );
|
int _cryptonite_blake2xb_init( blake2xb_state *S, const size_t outlen );
|
||||||
int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2xb_update( blake2xb_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2xb_update( blake2xb_state *S, const void *in, size_t inlen );
|
||||||
int blake2xb_final(blake2xb_state *S, void *out, size_t outlen);
|
int _cryptonite_blake2xb_final(blake2xb_state *S, void *out, size_t outlen);
|
||||||
|
|
||||||
/* Simple API */
|
/* Simple API */
|
||||||
int blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
int blake2xs( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xs( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2xb( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xb( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
/* This is simply an alias for blake2b */
|
/* This is simply an alias for blake2b */
|
||||||
int blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
#if defined(__cplusplus)
|
#if defined(__cplusplus)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -78,7 +78,7 @@ static void blake2b_init0( blake2b_state *S )
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* init xors IV with input parameter block */
|
/* init xors IV with input parameter block */
|
||||||
int blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
int _cryptonite_blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
||||||
{
|
{
|
||||||
const uint8_t *p = ( const uint8_t * )( P );
|
const uint8_t *p = ( const uint8_t * )( P );
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -95,7 +95,7 @@ int blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
|||||||
|
|
||||||
|
|
||||||
|
|
||||||
int blake2b_init( blake2b_state *S, size_t outlen )
|
int _cryptonite_blake2b_init( blake2b_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
|
|
||||||
@ -113,11 +113,11 @@ int blake2b_init( blake2b_state *S, size_t outlen )
|
|||||||
memset( P->reserved, 0, sizeof( P->reserved ) );
|
memset( P->reserved, 0, sizeof( P->reserved ) );
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2b_init_param( S, P );
|
return _cryptonite_blake2b_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
|
|
||||||
@ -138,13 +138,13 @@ int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t k
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
if( blake2b_init_param( S, P ) < 0 ) return -1;
|
if( _cryptonite_blake2b_init_param( S, P ) < 0 ) return -1;
|
||||||
|
|
||||||
{
|
{
|
||||||
uint8_t block[BLAKE2B_BLOCKBYTES];
|
uint8_t block[BLAKE2B_BLOCKBYTES];
|
||||||
memset( block, 0, BLAKE2B_BLOCKBYTES );
|
memset( block, 0, BLAKE2B_BLOCKBYTES );
|
||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
blake2b_update( S, block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S, block, BLAKE2B_BLOCKBYTES );
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
@ -218,7 +218,7 @@ static void blake2b_compress( blake2b_state *S, const uint8_t block[BLAKE2B_BLOC
|
|||||||
#undef G
|
#undef G
|
||||||
#undef ROUND
|
#undef ROUND
|
||||||
|
|
||||||
int blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
if( inlen > 0 )
|
if( inlen > 0 )
|
||||||
@ -245,7 +245,7 @@ int blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t buffer[BLAKE2B_OUTBYTES] = {0};
|
uint8_t buffer[BLAKE2B_OUTBYTES] = {0};
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -270,7 +270,7 @@ int blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* inlen, at least, should be uint64_t. Others can be size_t. */
|
/* inlen, at least, should be uint64_t. Others can be size_t. */
|
||||||
int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2b_state S[1];
|
blake2b_state S[1];
|
||||||
|
|
||||||
@ -287,26 +287,26 @@ int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
if( keylen > 0 )
|
if( keylen > 0 )
|
||||||
{
|
{
|
||||||
if( blake2b_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
if( _cryptonite_blake2b_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
else
|
else
|
||||||
{
|
{
|
||||||
if( blake2b_init( S, outlen ) < 0 ) return -1;
|
if( _cryptonite_blake2b_init( S, outlen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_update( S, ( const uint8_t * )in, inlen );
|
_cryptonite_blake2b_update( S, ( const uint8_t * )in, inlen );
|
||||||
blake2b_final( S, out, outlen );
|
_cryptonite_blake2b_final( S, out, outlen );
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen ) {
|
int _cryptonite_blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen ) {
|
||||||
return blake2b(out, outlen, in, inlen, key, keylen);
|
return _cryptonite_blake2b(out, outlen, in, inlen, key, keylen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(SUPERCOP)
|
#if defined(SUPERCOP)
|
||||||
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
||||||
{
|
{
|
||||||
return blake2b( out, BLAKE2B_OUTBYTES, in, inlen, NULL, 0 );
|
return _cryptonite_blake2b( out, BLAKE2B_OUTBYTES, in, inlen, NULL, 0 );
|
||||||
}
|
}
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
@ -329,9 +329,9 @@ int main( void )
|
|||||||
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2B_OUTBYTES];
|
uint8_t hash[BLAKE2B_OUTBYTES];
|
||||||
blake2b( hash, BLAKE2B_OUTBYTES, buf, i, key, BLAKE2B_KEYBYTES );
|
_cryptonite_blake2b( hash, BLAKE2B_OUTBYTES, buf, i, key, BLAKE2B_KEYBYTES );
|
||||||
|
|
||||||
if( 0 != memcmp( hash, blake2b_keyed_kat[i], BLAKE2B_OUTBYTES ) )
|
if( 0 != memcmp( hash, _cryptonite_blake2b_keyed_kat[i], BLAKE2B_OUTBYTES ) )
|
||||||
{
|
{
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
@ -346,25 +346,25 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2b_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2b_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2b_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2b_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2b_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2b_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2b_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2b_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
if (0 != memcmp(hash, blake2b_keyed_kat[i], BLAKE2B_OUTBYTES)) {
|
if (0 != memcmp(hash, _cryptonite_blake2b_keyed_kat[i], BLAKE2B_OUTBYTES)) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|||||||
@ -36,7 +36,7 @@
|
|||||||
*/
|
*/
|
||||||
static int blake2bp_init_leaf_param( blake2b_state *S, const blake2b_param *P )
|
static int blake2bp_init_leaf_param( blake2b_state *S, const blake2b_param *P )
|
||||||
{
|
{
|
||||||
int err = blake2b_init_param(S, P);
|
int err = _cryptonite_blake2b_init_param(S, P);
|
||||||
S->outlen = P->inner_length;
|
S->outlen = P->inner_length;
|
||||||
return err;
|
return err;
|
||||||
}
|
}
|
||||||
@ -74,11 +74,11 @@ static int blake2bp_init_root( blake2b_state *S, size_t outlen, size_t keylen )
|
|||||||
memset( P->reserved, 0, sizeof( P->reserved ) );
|
memset( P->reserved, 0, sizeof( P->reserved ) );
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2b_init_param( S, P );
|
return _cryptonite_blake2b_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2bp_init( blake2bp_state *S, size_t outlen )
|
int _cryptonite_blake2bp_init( blake2bp_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -99,7 +99,7 @@ int blake2bp_init( blake2bp_state *S, size_t outlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -125,7 +125,7 @@ int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->S[i], block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], block, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -133,7 +133,7 @@ int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
size_t left = S->buflen;
|
size_t left = S->buflen;
|
||||||
@ -145,7 +145,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
memcpy( S->buf + left, in, fill );
|
memcpy( S->buf + left, in, fill );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
in += fill;
|
in += fill;
|
||||||
inlen -= fill;
|
inlen -= fill;
|
||||||
@ -168,7 +168,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2b_update( S->S[i], in__, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], in__, BLAKE2B_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -184,7 +184,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -201,19 +201,19 @@ int blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
|||||||
|
|
||||||
if( left > BLAKE2B_BLOCKBYTES ) left = BLAKE2B_BLOCKBYTES;
|
if( left > BLAKE2B_BLOCKBYTES ) left = BLAKE2B_BLOCKBYTES;
|
||||||
|
|
||||||
blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, left );
|
_cryptonite_blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, left );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_final( S->S[i], hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_final( S->S[i], hash[i], BLAKE2B_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->R, hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_update( S->R, hash[i], BLAKE2B_OUTBYTES );
|
||||||
|
|
||||||
return blake2b_final( S->R, out, S->outlen );
|
return _cryptonite_blake2b_final( S->R, out, S->outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
||||||
blake2b_state S[PARALLELISM_DEGREE][1];
|
blake2b_state S[PARALLELISM_DEGREE][1];
|
||||||
@ -243,7 +243,7 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S[i], block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S[i], block, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -264,7 +264,7 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2b_update( S[i], in__, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S[i], in__, BLAKE2B_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -273,10 +273,10 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
{
|
{
|
||||||
const size_t left = inlen__ - i * BLAKE2B_BLOCKBYTES;
|
const size_t left = inlen__ - i * BLAKE2B_BLOCKBYTES;
|
||||||
const size_t len = left <= BLAKE2B_BLOCKBYTES ? left : BLAKE2B_BLOCKBYTES;
|
const size_t len = left <= BLAKE2B_BLOCKBYTES ? left : BLAKE2B_BLOCKBYTES;
|
||||||
blake2b_update( S[i], in__, len );
|
_cryptonite_blake2b_update( S[i], in__, len );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_final( S[i], hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_final( S[i], hash[i], BLAKE2B_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
if( blake2bp_init_root( FS, outlen, keylen ) < 0 )
|
if( blake2bp_init_root( FS, outlen, keylen ) < 0 )
|
||||||
@ -285,9 +285,9 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
FS->last_node = 1; /* Mark as last node */
|
FS->last_node = 1; /* Mark as last node */
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( FS, hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_update( FS, hash[i], BLAKE2B_OUTBYTES );
|
||||||
|
|
||||||
return blake2b_final( FS, out, outlen );;
|
return _cryptonite_blake2b_final( FS, out, outlen );;
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2BP_SELFTEST)
|
#if defined(BLAKE2BP_SELFTEST)
|
||||||
@ -326,21 +326,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2bp_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2bp_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2bp_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2bp_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2bp_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2bp_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2bp_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2bp_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -73,7 +73,7 @@ static void blake2s_init0( blake2s_state *S )
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* init2 xors IV with input parameter block */
|
/* init2 xors IV with input parameter block */
|
||||||
int blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
int _cryptonite_blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
||||||
{
|
{
|
||||||
const unsigned char *p = ( const unsigned char * )( P );
|
const unsigned char *p = ( const unsigned char * )( P );
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -90,7 +90,7 @@ int blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
|||||||
|
|
||||||
|
|
||||||
/* Sequential blake2s initialization */
|
/* Sequential blake2s initialization */
|
||||||
int blake2s_init( blake2s_state *S, size_t outlen )
|
int _cryptonite_blake2s_init( blake2s_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
|
|
||||||
@ -109,10 +109,10 @@ int blake2s_init( blake2s_state *S, size_t outlen )
|
|||||||
/* memset(P->reserved, 0, sizeof(P->reserved) ); */
|
/* memset(P->reserved, 0, sizeof(P->reserved) ); */
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2s_init_param( S, P );
|
return _cryptonite_blake2s_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
|
|
||||||
@ -133,13 +133,13 @@ int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t k
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
if( blake2s_init_param( S, P ) < 0 ) return -1;
|
if( _cryptonite_blake2s_init_param( S, P ) < 0 ) return -1;
|
||||||
|
|
||||||
{
|
{
|
||||||
uint8_t block[BLAKE2S_BLOCKBYTES];
|
uint8_t block[BLAKE2S_BLOCKBYTES];
|
||||||
memset( block, 0, BLAKE2S_BLOCKBYTES );
|
memset( block, 0, BLAKE2S_BLOCKBYTES );
|
||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
blake2s_update( S, block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S, block, BLAKE2S_BLOCKBYTES );
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
@ -211,7 +211,7 @@ static void blake2s_compress( blake2s_state *S, const uint8_t in[BLAKE2S_BLOCKBY
|
|||||||
#undef G
|
#undef G
|
||||||
#undef ROUND
|
#undef ROUND
|
||||||
|
|
||||||
int blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
if( inlen > 0 )
|
if( inlen > 0 )
|
||||||
@ -238,7 +238,7 @@ int blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2s_final( blake2s_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2s_final( blake2s_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t buffer[BLAKE2S_OUTBYTES] = {0};
|
uint8_t buffer[BLAKE2S_OUTBYTES] = {0};
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -262,7 +262,7 @@ int blake2s_final( blake2s_state *S, void *out, size_t outlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2s_state S[1];
|
blake2s_state S[1];
|
||||||
|
|
||||||
@ -279,22 +279,22 @@ int blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
if( keylen > 0 )
|
if( keylen > 0 )
|
||||||
{
|
{
|
||||||
if( blake2s_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
if( _cryptonite_blake2s_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
else
|
else
|
||||||
{
|
{
|
||||||
if( blake2s_init( S, outlen ) < 0 ) return -1;
|
if( _cryptonite_blake2s_init( S, outlen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_update( S, ( const uint8_t * )in, inlen );
|
_cryptonite_blake2s_update( S, ( const uint8_t * )in, inlen );
|
||||||
blake2s_final( S, out, outlen );
|
_cryptonite_blake2s_final( S, out, outlen );
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(SUPERCOP)
|
#if defined(SUPERCOP)
|
||||||
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
||||||
{
|
{
|
||||||
return blake2s( out, BLAKE2S_OUTBYTES, in, inlen, NULL, 0 );
|
return _cryptonite_blake2s( out, BLAKE2S_OUTBYTES, in, inlen, NULL, 0 );
|
||||||
}
|
}
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
@ -317,7 +317,7 @@ int main( void )
|
|||||||
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2S_OUTBYTES];
|
uint8_t hash[BLAKE2S_OUTBYTES];
|
||||||
blake2s( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
_cryptonite_blake2s( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
||||||
|
|
||||||
if( 0 != memcmp( hash, blake2s_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
if( 0 != memcmp( hash, blake2s_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
||||||
{
|
{
|
||||||
@ -334,21 +334,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2s_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2s_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2s_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2s_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2s_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2s_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2s_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2s_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -35,7 +35,7 @@
|
|||||||
*/
|
*/
|
||||||
static int blake2sp_init_leaf_param( blake2s_state *S, const blake2s_param *P )
|
static int blake2sp_init_leaf_param( blake2s_state *S, const blake2s_param *P )
|
||||||
{
|
{
|
||||||
int err = blake2s_init_param(S, P);
|
int err = _cryptonite_blake2s_init_param(S, P);
|
||||||
S->outlen = P->inner_length;
|
S->outlen = P->inner_length;
|
||||||
return err;
|
return err;
|
||||||
}
|
}
|
||||||
@ -71,11 +71,11 @@ static int blake2sp_init_root( blake2s_state *S, size_t outlen, size_t keylen )
|
|||||||
P->inner_length = BLAKE2S_OUTBYTES;
|
P->inner_length = BLAKE2S_OUTBYTES;
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2s_init_param( S, P );
|
return _cryptonite_blake2s_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_init( blake2sp_state *S, size_t outlen )
|
int _cryptonite_blake2sp_init( blake2sp_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -96,7 +96,7 @@ int blake2sp_init( blake2sp_state *S, size_t outlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -122,7 +122,7 @@ int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->S[i], block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], block, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -130,7 +130,7 @@ int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
size_t left = S->buflen;
|
size_t left = S->buflen;
|
||||||
@ -142,7 +142,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
memcpy( S->buf + left, in, fill );
|
memcpy( S->buf + left, in, fill );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
in += fill;
|
in += fill;
|
||||||
inlen -= fill;
|
inlen -= fill;
|
||||||
@ -164,7 +164,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2s_update( S->S[i], in__, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], in__, BLAKE2S_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -181,7 +181,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -198,20 +198,20 @@ int blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
|||||||
|
|
||||||
if( left > BLAKE2S_BLOCKBYTES ) left = BLAKE2S_BLOCKBYTES;
|
if( left > BLAKE2S_BLOCKBYTES ) left = BLAKE2S_BLOCKBYTES;
|
||||||
|
|
||||||
blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, left );
|
_cryptonite_blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, left );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_final( S->S[i], hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_final( S->S[i], hash[i], BLAKE2S_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->R, hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_update( S->R, hash[i], BLAKE2S_OUTBYTES );
|
||||||
|
|
||||||
return blake2s_final( S->R, out, S->outlen );
|
return _cryptonite_blake2s_final( S->R, out, S->outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
||||||
blake2s_state S[PARALLELISM_DEGREE][1];
|
blake2s_state S[PARALLELISM_DEGREE][1];
|
||||||
@ -241,7 +241,7 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S[i], block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S[i], block, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -262,7 +262,7 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2s_update( S[i], in__, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S[i], in__, BLAKE2S_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -271,10 +271,10 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
{
|
{
|
||||||
const size_t left = inlen__ - i * BLAKE2S_BLOCKBYTES;
|
const size_t left = inlen__ - i * BLAKE2S_BLOCKBYTES;
|
||||||
const size_t len = left <= BLAKE2S_BLOCKBYTES ? left : BLAKE2S_BLOCKBYTES;
|
const size_t len = left <= BLAKE2S_BLOCKBYTES ? left : BLAKE2S_BLOCKBYTES;
|
||||||
blake2s_update( S[i], in__, len );
|
_cryptonite_blake2s_update( S[i], in__, len );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_final( S[i], hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_final( S[i], hash[i], BLAKE2S_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
if( blake2sp_init_root( FS, outlen, keylen ) < 0 )
|
if( blake2sp_init_root( FS, outlen, keylen ) < 0 )
|
||||||
@ -283,9 +283,9 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
FS->last_node = 1;
|
FS->last_node = 1;
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( FS, hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_update( FS, hash[i], BLAKE2S_OUTBYTES );
|
||||||
|
|
||||||
return blake2s_final( FS, out, outlen );
|
return _cryptonite_blake2s_final( FS, out, outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
@ -309,7 +309,7 @@ int main( void )
|
|||||||
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2S_OUTBYTES];
|
uint8_t hash[BLAKE2S_OUTBYTES];
|
||||||
blake2sp( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
_cryptonite_blake2sp( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
||||||
|
|
||||||
if( 0 != memcmp( hash, blake2sp_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
if( 0 != memcmp( hash, blake2sp_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
||||||
{
|
{
|
||||||
@ -326,21 +326,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2sp_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2sp_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2sp_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2sp_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2sp_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2sp_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2sp_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2sp_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -23,11 +23,11 @@
|
|||||||
#include "blake2.h"
|
#include "blake2.h"
|
||||||
#include "blake2-impl.h"
|
#include "blake2-impl.h"
|
||||||
|
|
||||||
int blake2xb_init( blake2xb_state *S, const size_t outlen ) {
|
int _cryptonite_blake2xb_init( blake2xb_state *S, const size_t outlen ) {
|
||||||
return blake2xb_init_key(S, outlen, NULL, 0);
|
return _cryptonite_blake2xb_init_key(S, outlen, NULL, 0);
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
if ( outlen == 0 || outlen > 0xFFFFFFFFUL ) {
|
if ( outlen == 0 || outlen > 0xFFFFFFFFUL ) {
|
||||||
return -1;
|
return -1;
|
||||||
@ -55,7 +55,7 @@ int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key,
|
|||||||
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
||||||
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
||||||
|
|
||||||
if( blake2b_init_param( S->S, S->P ) < 0 ) {
|
if( _cryptonite_blake2b_init_param( S->S, S->P ) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -63,17 +63,17 @@ int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key,
|
|||||||
uint8_t block[BLAKE2B_BLOCKBYTES];
|
uint8_t block[BLAKE2B_BLOCKBYTES];
|
||||||
memset(block, 0, BLAKE2B_BLOCKBYTES);
|
memset(block, 0, BLAKE2B_BLOCKBYTES);
|
||||||
memcpy(block, key, keylen);
|
memcpy(block, key, keylen);
|
||||||
blake2b_update(S->S, block, BLAKE2B_BLOCKBYTES);
|
_cryptonite_blake2b_update(S->S, block, BLAKE2B_BLOCKBYTES);
|
||||||
secure_zero_memory(block, BLAKE2B_BLOCKBYTES);
|
secure_zero_memory(block, BLAKE2B_BLOCKBYTES);
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_update( blake2xb_state *S, const void *in, size_t inlen ) {
|
int _cryptonite_blake2xb_update( blake2xb_state *S, const void *in, size_t inlen ) {
|
||||||
return blake2b_update( S->S, in, inlen );
|
return _cryptonite_blake2b_update( S->S, in, inlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
int _cryptonite_blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
||||||
|
|
||||||
blake2b_state C[1];
|
blake2b_state C[1];
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
@ -98,7 +98,7 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* Finalize the root hash */
|
/* Finalize the root hash */
|
||||||
if (blake2b_final(S->S, root, BLAKE2B_OUTBYTES) < 0) {
|
if (_cryptonite_blake2b_final(S->S, root, BLAKE2B_OUTBYTES) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -117,10 +117,10 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
/* Initialize state */
|
/* Initialize state */
|
||||||
P->digest_length = block_size;
|
P->digest_length = block_size;
|
||||||
store32(&P->node_offset, i);
|
store32(&P->node_offset, i);
|
||||||
blake2b_init_param(C, P);
|
_cryptonite_blake2b_init_param(C, P);
|
||||||
/* Process key if needed */
|
/* Process key if needed */
|
||||||
blake2b_update(C, root, BLAKE2B_OUTBYTES);
|
_cryptonite_blake2b_update(C, root, BLAKE2B_OUTBYTES);
|
||||||
if (blake2b_final(C, (uint8_t *)out + i * BLAKE2B_OUTBYTES, block_size) < 0 ) {
|
if (_cryptonite_blake2b_final(C, (uint8_t *)out + i * BLAKE2B_OUTBYTES, block_size) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
outlen -= block_size;
|
outlen -= block_size;
|
||||||
@ -133,7 +133,7 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
|
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
blake2xb_state S[1];
|
blake2xb_state S[1];
|
||||||
|
|
||||||
@ -154,15 +154,15 @@ int blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
return -1;
|
return -1;
|
||||||
|
|
||||||
/* Initialize the root block structure */
|
/* Initialize the root block structure */
|
||||||
if (blake2xb_init_key(S, outlen, key, keylen) < 0) {
|
if (_cryptonite_blake2xb_init_key(S, outlen, key, keylen) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* Absorb the input message */
|
/* Absorb the input message */
|
||||||
blake2xb_update(S, in, inlen);
|
_cryptonite_blake2xb_update(S, in, inlen);
|
||||||
|
|
||||||
/* Compute the root node of the tree and the final hash using the counter construction */
|
/* Compute the root node of the tree and the final hash using the counter construction */
|
||||||
return blake2xb_final(S, out, outlen);
|
return _cryptonite_blake2xb_final(S, out, outlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2XB_SELFTEST)
|
#if defined(BLAKE2XB_SELFTEST)
|
||||||
@ -189,7 +189,7 @@ int main( void )
|
|||||||
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
||||||
if( blake2xb( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2B_KEYBYTES ) < 0 ) {
|
if( _cryptonite_blake2xb( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2B_KEYBYTES ) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -208,21 +208,21 @@ int main( void )
|
|||||||
size_t mlen = BLAKE2_KAT_LENGTH;
|
size_t mlen = BLAKE2_KAT_LENGTH;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2xb_init_key(&S, outlen, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2xb_init_key(&S, outlen, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2xb_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2xb_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xb_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2xb_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xb_final(&S, hash, outlen)) < 0) {
|
if ( (err = _cryptonite_blake2xb_final(&S, hash, outlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -23,11 +23,11 @@
|
|||||||
#include "blake2.h"
|
#include "blake2.h"
|
||||||
#include "blake2-impl.h"
|
#include "blake2-impl.h"
|
||||||
|
|
||||||
int blake2xs_init( blake2xs_state *S, const size_t outlen ) {
|
int _cryptonite_blake2xs_init( blake2xs_state *S, const size_t outlen ) {
|
||||||
return blake2xs_init_key(S, outlen, NULL, 0);
|
return _cryptonite_blake2xs_init_key(S, outlen, NULL, 0);
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
if ( outlen == 0 || outlen > 0xFFFFUL ) {
|
if ( outlen == 0 || outlen > 0xFFFFUL ) {
|
||||||
return -1;
|
return -1;
|
||||||
@ -54,7 +54,7 @@ int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key,
|
|||||||
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
||||||
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
||||||
|
|
||||||
if( blake2s_init_param( S->S, S->P ) < 0 ) {
|
if( _cryptonite_blake2s_init_param( S->S, S->P ) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -62,17 +62,17 @@ int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key,
|
|||||||
uint8_t block[BLAKE2S_BLOCKBYTES];
|
uint8_t block[BLAKE2S_BLOCKBYTES];
|
||||||
memset(block, 0, BLAKE2S_BLOCKBYTES);
|
memset(block, 0, BLAKE2S_BLOCKBYTES);
|
||||||
memcpy(block, key, keylen);
|
memcpy(block, key, keylen);
|
||||||
blake2s_update(S->S, block, BLAKE2S_BLOCKBYTES);
|
_cryptonite_blake2s_update(S->S, block, BLAKE2S_BLOCKBYTES);
|
||||||
secure_zero_memory(block, BLAKE2S_BLOCKBYTES);
|
secure_zero_memory(block, BLAKE2S_BLOCKBYTES);
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_update( blake2xs_state *S, const void *in, size_t inlen ) {
|
int _cryptonite_blake2xs_update( blake2xs_state *S, const void *in, size_t inlen ) {
|
||||||
return blake2s_update( S->S, in, inlen );
|
return _cryptonite_blake2s_update( S->S, in, inlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
int _cryptonite_blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
||||||
|
|
||||||
blake2s_state C[1];
|
blake2s_state C[1];
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
@ -97,7 +97,7 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* Finalize the root hash */
|
/* Finalize the root hash */
|
||||||
if (blake2s_final(S->S, root, BLAKE2S_OUTBYTES) < 0) {
|
if (_cryptonite_blake2s_final(S->S, root, BLAKE2S_OUTBYTES) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -116,10 +116,10 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
/* Initialize state */
|
/* Initialize state */
|
||||||
P->digest_length = block_size;
|
P->digest_length = block_size;
|
||||||
store32(&P->node_offset, i);
|
store32(&P->node_offset, i);
|
||||||
blake2s_init_param(C, P);
|
_cryptonite_blake2s_init_param(C, P);
|
||||||
/* Process key if needed */
|
/* Process key if needed */
|
||||||
blake2s_update(C, root, BLAKE2S_OUTBYTES);
|
_cryptonite_blake2s_update(C, root, BLAKE2S_OUTBYTES);
|
||||||
if (blake2s_final(C, (uint8_t *)out + i * BLAKE2S_OUTBYTES, block_size) < 0) {
|
if (_cryptonite_blake2s_final(C, (uint8_t *)out + i * BLAKE2S_OUTBYTES, block_size) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
outlen -= block_size;
|
outlen -= block_size;
|
||||||
@ -131,7 +131,7 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
blake2xs_state S[1];
|
blake2xs_state S[1];
|
||||||
|
|
||||||
@ -152,15 +152,15 @@ int blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
return -1;
|
return -1;
|
||||||
|
|
||||||
/* Initialize the root block structure */
|
/* Initialize the root block structure */
|
||||||
if (blake2xs_init_key(S, outlen, key, keylen) < 0) {
|
if (_cryptonite_blake2xs_init_key(S, outlen, key, keylen) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* Absorb the input message */
|
/* Absorb the input message */
|
||||||
blake2xs_update(S, in, inlen);
|
_cryptonite_blake2xs_update(S, in, inlen);
|
||||||
|
|
||||||
/* Compute the root node of the tree and the final hash using the counter construction */
|
/* Compute the root node of the tree and the final hash using the counter construction */
|
||||||
return blake2xs_final(S, out, outlen);
|
return _cryptonite_blake2xs_final(S, out, outlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2XS_SELFTEST)
|
#if defined(BLAKE2XS_SELFTEST)
|
||||||
@ -187,7 +187,7 @@ int main( void )
|
|||||||
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
||||||
if( blake2xs( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2S_KEYBYTES ) < 0 ) {
|
if( _cryptonite_blake2xs( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2S_KEYBYTES ) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -206,21 +206,21 @@ int main( void )
|
|||||||
size_t mlen = BLAKE2_KAT_LENGTH;
|
size_t mlen = BLAKE2_KAT_LENGTH;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2xs_init_key(&S, outlen, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2xs_init_key(&S, outlen, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2xs_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2xs_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xs_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2xs_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xs_final(&S, hash, outlen)) < 0) {
|
if ( (err = _cryptonite_blake2xs_final(&S, hash, outlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -142,51 +142,51 @@ extern "C" {
|
|||||||
};
|
};
|
||||||
|
|
||||||
/* Streaming API */
|
/* Streaming API */
|
||||||
int blake2s_init( blake2s_state *S, size_t outlen );
|
int _cryptonite_blake2s_init( blake2s_state *S, size_t outlen );
|
||||||
int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2s_init_param( blake2s_state *S, const blake2s_param *P );
|
int _cryptonite_blake2s_init_param( blake2s_state *S, const blake2s_param *P );
|
||||||
int blake2s_update( blake2s_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2s_update( blake2s_state *S, const void *in, size_t inlen );
|
||||||
int blake2s_final( blake2s_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2s_final( blake2s_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2b_init( blake2b_state *S, size_t outlen );
|
int _cryptonite_blake2b_init( blake2b_state *S, size_t outlen );
|
||||||
int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2b_init_param( blake2b_state *S, const blake2b_param *P );
|
int _cryptonite_blake2b_init_param( blake2b_state *S, const blake2b_param *P );
|
||||||
int blake2b_update( blake2b_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2b_update( blake2b_state *S, const void *in, size_t inlen );
|
||||||
int blake2b_final( blake2b_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2b_final( blake2b_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2sp_init( blake2sp_state *S, size_t outlen );
|
int _cryptonite_blake2sp_init( blake2sp_state *S, size_t outlen );
|
||||||
int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2sp_update( blake2sp_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2sp_update( blake2sp_state *S, const void *in, size_t inlen );
|
||||||
int blake2sp_final( blake2sp_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2sp_final( blake2sp_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
int blake2bp_init( blake2bp_state *S, size_t outlen );
|
int _cryptonite_blake2bp_init( blake2bp_state *S, size_t outlen );
|
||||||
int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2bp_update( blake2bp_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2bp_update( blake2bp_state *S, const void *in, size_t inlen );
|
||||||
int blake2bp_final( blake2bp_state *S, void *out, size_t outlen );
|
int _cryptonite_blake2bp_final( blake2bp_state *S, void *out, size_t outlen );
|
||||||
|
|
||||||
/* Variable output length API */
|
/* Variable output length API */
|
||||||
int blake2xs_init( blake2xs_state *S, const size_t outlen );
|
int _cryptonite_blake2xs_init( blake2xs_state *S, const size_t outlen );
|
||||||
int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2xs_update( blake2xs_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2xs_update( blake2xs_state *S, const void *in, size_t inlen );
|
||||||
int blake2xs_final(blake2xs_state *S, void *out, size_t outlen);
|
int _cryptonite_blake2xs_final(blake2xs_state *S, void *out, size_t outlen);
|
||||||
|
|
||||||
int blake2xb_init( blake2xb_state *S, const size_t outlen );
|
int _cryptonite_blake2xb_init( blake2xb_state *S, const size_t outlen );
|
||||||
int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen );
|
||||||
int blake2xb_update( blake2xb_state *S, const void *in, size_t inlen );
|
int _cryptonite_blake2xb_update( blake2xb_state *S, const void *in, size_t inlen );
|
||||||
int blake2xb_final(blake2xb_state *S, void *out, size_t outlen);
|
int _cryptonite_blake2xb_final(blake2xb_state *S, void *out, size_t outlen);
|
||||||
|
|
||||||
/* Simple API */
|
/* Simple API */
|
||||||
int blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
int blake2xs( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xs( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
int blake2xb( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2xb( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
/* This is simply an alias for blake2b */
|
/* This is simply an alias for blake2b */
|
||||||
int blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
int _cryptonite_blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen );
|
||||||
|
|
||||||
#if defined(__cplusplus)
|
#if defined(__cplusplus)
|
||||||
}
|
}
|
||||||
|
|||||||
@ -74,7 +74,7 @@ static void blake2b_increment_counter( blake2b_state *S, const uint64_t inc )
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* init xors IV with input parameter block */
|
/* init xors IV with input parameter block */
|
||||||
int blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
int _cryptonite_blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
/*blake2b_init0( S ); */
|
/*blake2b_init0( S ); */
|
||||||
@ -92,7 +92,7 @@ int blake2b_init_param( blake2b_state *S, const blake2b_param *P )
|
|||||||
|
|
||||||
|
|
||||||
/* Some sort of default parameter block initialization, for sequential blake2b */
|
/* Some sort of default parameter block initialization, for sequential blake2b */
|
||||||
int blake2b_init( blake2b_state *S, size_t outlen )
|
int _cryptonite_blake2b_init( blake2b_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
|
|
||||||
@ -111,10 +111,10 @@ int blake2b_init( blake2b_state *S, size_t outlen )
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
return blake2b_init_param( S, P );
|
return _cryptonite_blake2b_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
|
|
||||||
@ -135,14 +135,14 @@ int blake2b_init_key( blake2b_state *S, size_t outlen, const void *key, size_t k
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
if( blake2b_init_param( S, P ) < 0 )
|
if( _cryptonite_blake2b_init_param( S, P ) < 0 )
|
||||||
return 0;
|
return 0;
|
||||||
|
|
||||||
{
|
{
|
||||||
uint8_t block[BLAKE2B_BLOCKBYTES];
|
uint8_t block[BLAKE2B_BLOCKBYTES];
|
||||||
memset( block, 0, BLAKE2B_BLOCKBYTES );
|
memset( block, 0, BLAKE2B_BLOCKBYTES );
|
||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
blake2b_update( S, block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S, block, BLAKE2B_BLOCKBYTES );
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
@ -218,7 +218,7 @@ static void blake2b_compress( blake2b_state *S, const uint8_t block[BLAKE2B_BLOC
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
if( inlen > 0 )
|
if( inlen > 0 )
|
||||||
@ -246,7 +246,7 @@ int blake2b_update( blake2b_state *S, const void *pin, size_t inlen )
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
if( out == NULL || outlen < S->outlen )
|
if( out == NULL || outlen < S->outlen )
|
||||||
return -1;
|
return -1;
|
||||||
@ -264,7 +264,7 @@ int blake2b_final( blake2b_state *S, void *out, size_t outlen )
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2b_state S[1];
|
blake2b_state S[1];
|
||||||
|
|
||||||
@ -281,26 +281,26 @@ int blake2b( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
if( keylen )
|
if( keylen )
|
||||||
{
|
{
|
||||||
if( blake2b_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
if( _cryptonite_blake2b_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
else
|
else
|
||||||
{
|
{
|
||||||
if( blake2b_init( S, outlen ) < 0 ) return -1;
|
if( _cryptonite_blake2b_init( S, outlen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_update( S, ( const uint8_t * )in, inlen );
|
_cryptonite_blake2b_update( S, ( const uint8_t * )in, inlen );
|
||||||
blake2b_final( S, out, outlen );
|
_cryptonite_blake2b_final( S, out, outlen );
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen ) {
|
int _cryptonite_blake2( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen ) {
|
||||||
return blake2b(out, outlen, in, inlen, key, keylen);
|
return _cryptonite_blake2b(out, outlen, in, inlen, key, keylen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(SUPERCOP)
|
#if defined(SUPERCOP)
|
||||||
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
int crypto_hash( unsigned char *out, unsigned char *in, unsigned long long inlen )
|
||||||
{
|
{
|
||||||
return blake2b( out, BLAKE2B_OUTBYTES, in, inlen, NULL, 0 );
|
return _cryptonite_blake2b( out, BLAKE2B_OUTBYTES, in, inlen, NULL, 0 );
|
||||||
}
|
}
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
@ -340,21 +340,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2b_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2b_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2b_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2b_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2b_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2b_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2b_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2b_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -36,7 +36,7 @@
|
|||||||
*/
|
*/
|
||||||
static int blake2bp_init_leaf_param( blake2b_state *S, const blake2b_param *P )
|
static int blake2bp_init_leaf_param( blake2b_state *S, const blake2b_param *P )
|
||||||
{
|
{
|
||||||
int err = blake2b_init_param(S, P);
|
int err = _cryptonite_blake2b_init_param(S, P);
|
||||||
S->outlen = P->inner_length;
|
S->outlen = P->inner_length;
|
||||||
return err;
|
return err;
|
||||||
}
|
}
|
||||||
@ -74,11 +74,11 @@ static int blake2bp_init_root( blake2b_state *S, size_t outlen, size_t keylen )
|
|||||||
memset( P->reserved, 0, sizeof( P->reserved ) );
|
memset( P->reserved, 0, sizeof( P->reserved ) );
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2b_init_param( S, P );
|
return _cryptonite_blake2b_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2bp_init( blake2bp_state *S, size_t outlen )
|
int _cryptonite_blake2bp_init( blake2bp_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
if( !outlen || outlen > BLAKE2B_OUTBYTES ) return -1;
|
if( !outlen || outlen > BLAKE2B_OUTBYTES ) return -1;
|
||||||
@ -98,7 +98,7 @@ int blake2bp_init( blake2bp_state *S, size_t outlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -124,7 +124,7 @@ int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->S[i], block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], block, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -132,7 +132,7 @@ int blake2bp_init_key( blake2bp_state *S, size_t outlen, const void *key, size_t
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
size_t left = S->buflen;
|
size_t left = S->buflen;
|
||||||
@ -144,7 +144,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
memcpy( S->buf + left, in, fill );
|
memcpy( S->buf + left, in, fill );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
in += fill;
|
in += fill;
|
||||||
inlen -= fill;
|
inlen -= fill;
|
||||||
@ -167,7 +167,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2b_update( S->S[i], in__, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S->S[i], in__, BLAKE2B_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -185,7 +185,7 @@ int blake2bp_update( blake2bp_state *S, const void *pin, size_t inlen )
|
|||||||
|
|
||||||
|
|
||||||
|
|
||||||
int blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -202,19 +202,19 @@ int blake2bp_final( blake2bp_state *S, void *out, size_t outlen )
|
|||||||
|
|
||||||
if( left > BLAKE2B_BLOCKBYTES ) left = BLAKE2B_BLOCKBYTES;
|
if( left > BLAKE2B_BLOCKBYTES ) left = BLAKE2B_BLOCKBYTES;
|
||||||
|
|
||||||
blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, left );
|
_cryptonite_blake2b_update( S->S[i], S->buf + i * BLAKE2B_BLOCKBYTES, left );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_final( S->S[i], hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_final( S->S[i], hash[i], BLAKE2B_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S->R, hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_update( S->R, hash[i], BLAKE2B_OUTBYTES );
|
||||||
|
|
||||||
return blake2b_final( S->R, out, S->outlen );
|
return _cryptonite_blake2b_final( S->R, out, S->outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2B_OUTBYTES];
|
||||||
blake2b_state S[PARALLELISM_DEGREE][1];
|
blake2b_state S[PARALLELISM_DEGREE][1];
|
||||||
@ -244,7 +244,7 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( S[i], block, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S[i], block, BLAKE2B_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2B_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -265,7 +265,7 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2b_update( S[i], in__, BLAKE2B_BLOCKBYTES );
|
_cryptonite_blake2b_update( S[i], in__, BLAKE2B_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2B_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -274,10 +274,10 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
{
|
{
|
||||||
const size_t left = inlen__ - i * BLAKE2B_BLOCKBYTES;
|
const size_t left = inlen__ - i * BLAKE2B_BLOCKBYTES;
|
||||||
const size_t len = left <= BLAKE2B_BLOCKBYTES ? left : BLAKE2B_BLOCKBYTES;
|
const size_t len = left <= BLAKE2B_BLOCKBYTES ? left : BLAKE2B_BLOCKBYTES;
|
||||||
blake2b_update( S[i], in__, len );
|
_cryptonite_blake2b_update( S[i], in__, len );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2b_final( S[i], hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_final( S[i], hash[i], BLAKE2B_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
if( blake2bp_init_root( FS, outlen, keylen ) < 0 )
|
if( blake2bp_init_root( FS, outlen, keylen ) < 0 )
|
||||||
@ -286,9 +286,9 @@ int blake2bp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
FS->last_node = 1; /* Mark as last node */
|
FS->last_node = 1; /* Mark as last node */
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2b_update( FS, hash[i], BLAKE2B_OUTBYTES );
|
_cryptonite_blake2b_update( FS, hash[i], BLAKE2B_OUTBYTES );
|
||||||
|
|
||||||
return blake2b_final( FS, out, outlen );
|
return _cryptonite_blake2b_final( FS, out, outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
@ -311,7 +311,7 @@ int main( void )
|
|||||||
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2B_OUTBYTES];
|
uint8_t hash[BLAKE2B_OUTBYTES];
|
||||||
blake2bp( hash, BLAKE2B_OUTBYTES, buf, i, key, BLAKE2B_KEYBYTES );
|
_cryptonite_blake2bp( hash, BLAKE2B_OUTBYTES, buf, i, key, BLAKE2B_KEYBYTES );
|
||||||
|
|
||||||
if( 0 != memcmp( hash, blake2bp_keyed_kat[i], BLAKE2B_OUTBYTES ) )
|
if( 0 != memcmp( hash, blake2bp_keyed_kat[i], BLAKE2B_OUTBYTES ) )
|
||||||
{
|
{
|
||||||
@ -328,21 +328,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2bp_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2bp_init_key(&S, BLAKE2B_OUTBYTES, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2bp_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2bp_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2bp_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2bp_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2bp_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2bp_final(&S, hash, BLAKE2B_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -72,7 +72,7 @@ static void blake2s_increment_counter( blake2s_state *S, const uint32_t inc )
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* init2 xors IV with input parameter block */
|
/* init2 xors IV with input parameter block */
|
||||||
int blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
int _cryptonite_blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
/*blake2s_init0( S ); */
|
/*blake2s_init0( S ); */
|
||||||
@ -90,7 +90,7 @@ int blake2s_init_param( blake2s_state *S, const blake2s_param *P )
|
|||||||
|
|
||||||
|
|
||||||
/* Some sort of default parameter block initialization, for sequential blake2s */
|
/* Some sort of default parameter block initialization, for sequential blake2s */
|
||||||
int blake2s_init( blake2s_state *S, size_t outlen )
|
int _cryptonite_blake2s_init( blake2s_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
|
|
||||||
@ -110,11 +110,11 @@ int blake2s_init( blake2s_state *S, size_t outlen )
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
return blake2s_init_param( S, P );
|
return _cryptonite_blake2s_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
|
|
||||||
@ -136,14 +136,14 @@ int blake2s_init_key( blake2s_state *S, size_t outlen, const void *key, size_t k
|
|||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
|
|
||||||
if( blake2s_init_param( S, P ) < 0 )
|
if( _cryptonite_blake2s_init_param( S, P ) < 0 )
|
||||||
return -1;
|
return -1;
|
||||||
|
|
||||||
{
|
{
|
||||||
uint8_t block[BLAKE2S_BLOCKBYTES];
|
uint8_t block[BLAKE2S_BLOCKBYTES];
|
||||||
memset( block, 0, BLAKE2S_BLOCKBYTES );
|
memset( block, 0, BLAKE2S_BLOCKBYTES );
|
||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
blake2s_update( S, block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S, block, BLAKE2S_BLOCKBYTES );
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
@ -206,7 +206,7 @@ static void blake2s_compress( blake2s_state *S, const uint8_t block[BLAKE2S_BLOC
|
|||||||
STOREU( &S->h[4], _mm_xor_si128( ff1, _mm_xor_si128( row2, row4 ) ) );
|
STOREU( &S->h[4], _mm_xor_si128( ff1, _mm_xor_si128( row2, row4 ) ) );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
if( inlen > 0 )
|
if( inlen > 0 )
|
||||||
@ -233,7 +233,7 @@ int blake2s_update( blake2s_state *S, const void *pin, size_t inlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2s_final( blake2s_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2s_final( blake2s_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t buffer[BLAKE2S_OUTBYTES] = {0};
|
uint8_t buffer[BLAKE2S_OUTBYTES] = {0};
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -275,15 +275,15 @@ int blake2s( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
if( keylen > 0 )
|
if( keylen > 0 )
|
||||||
{
|
{
|
||||||
if( blake2s_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
if( _cryptonite_blake2s_init_key( S, outlen, key, keylen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
else
|
else
|
||||||
{
|
{
|
||||||
if( blake2s_init( S, outlen ) < 0 ) return -1;
|
if( _cryptonite_blake2s_init( S, outlen ) < 0 ) return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_update( S, ( const uint8_t * )in, inlen );
|
_cryptonite_blake2s_update( S, ( const uint8_t * )in, inlen );
|
||||||
blake2s_final( S, out, outlen );
|
_cryptonite_blake2s_final( S, out, outlen );
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -330,21 +330,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2s_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2s_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2s_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2s_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2s_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2s_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2s_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2s_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -35,7 +35,7 @@
|
|||||||
*/
|
*/
|
||||||
static int blake2sp_init_leaf_param( blake2s_state *S, const blake2s_param *P )
|
static int blake2sp_init_leaf_param( blake2s_state *S, const blake2s_param *P )
|
||||||
{
|
{
|
||||||
int err = blake2s_init_param(S, P);
|
int err = _cryptonite_blake2s_init_param(S, P);
|
||||||
S->outlen = P->inner_length;
|
S->outlen = P->inner_length;
|
||||||
return err;
|
return err;
|
||||||
}
|
}
|
||||||
@ -71,11 +71,11 @@ static int blake2sp_init_root( blake2s_state *S, size_t outlen, size_t keylen )
|
|||||||
P->inner_length = BLAKE2S_OUTBYTES;
|
P->inner_length = BLAKE2S_OUTBYTES;
|
||||||
memset( P->salt, 0, sizeof( P->salt ) );
|
memset( P->salt, 0, sizeof( P->salt ) );
|
||||||
memset( P->personal, 0, sizeof( P->personal ) );
|
memset( P->personal, 0, sizeof( P->personal ) );
|
||||||
return blake2s_init_param( S, P );
|
return _cryptonite_blake2s_init_param( S, P );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_init( blake2sp_state *S, size_t outlen )
|
int _cryptonite_blake2sp_init( blake2sp_state *S, size_t outlen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -96,7 +96,7 @@ int blake2sp_init( blake2sp_state *S, size_t outlen )
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
size_t i;
|
size_t i;
|
||||||
|
|
||||||
@ -122,7 +122,7 @@ int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->S[i], block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], block, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -130,7 +130,7 @@ int blake2sp_init_key( blake2sp_state *S, size_t outlen, const void *key, size_t
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
int _cryptonite_blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
||||||
{
|
{
|
||||||
const unsigned char * in = (const unsigned char *)pin;
|
const unsigned char * in = (const unsigned char *)pin;
|
||||||
size_t left = S->buflen;
|
size_t left = S->buflen;
|
||||||
@ -142,7 +142,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
memcpy( S->buf + left, in, fill );
|
memcpy( S->buf + left, in, fill );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
in += fill;
|
in += fill;
|
||||||
inlen -= fill;
|
inlen -= fill;
|
||||||
@ -165,7 +165,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2s_update( S->S[i], in__, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S->S[i], in__, BLAKE2S_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -182,7 +182,7 @@ int blake2sp_update( blake2sp_state *S, const void *pin, size_t inlen )
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
int _cryptonite_blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
||||||
size_t i;
|
size_t i;
|
||||||
@ -199,20 +199,20 @@ int blake2sp_final( blake2sp_state *S, void *out, size_t outlen )
|
|||||||
|
|
||||||
if( left > BLAKE2S_BLOCKBYTES ) left = BLAKE2S_BLOCKBYTES;
|
if( left > BLAKE2S_BLOCKBYTES ) left = BLAKE2S_BLOCKBYTES;
|
||||||
|
|
||||||
blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, left );
|
_cryptonite_blake2s_update( S->S[i], S->buf + i * BLAKE2S_BLOCKBYTES, left );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_final( S->S[i], hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_final( S->S[i], hash[i], BLAKE2S_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S->R, hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_update( S->R, hash[i], BLAKE2S_OUTBYTES );
|
||||||
|
|
||||||
return blake2s_final( S->R, out, S->outlen );
|
return _cryptonite_blake2s_final( S->R, out, S->outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
int _cryptonite_blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
uint8_t hash[PARALLELISM_DEGREE][BLAKE2S_OUTBYTES];
|
||||||
blake2s_state S[PARALLELISM_DEGREE][1];
|
blake2s_state S[PARALLELISM_DEGREE][1];
|
||||||
@ -242,7 +242,7 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
memcpy( block, key, keylen );
|
memcpy( block, key, keylen );
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( S[i], block, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S[i], block, BLAKE2S_BLOCKBYTES );
|
||||||
|
|
||||||
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
secure_zero_memory( block, BLAKE2S_BLOCKBYTES ); /* Burn the key from stack */
|
||||||
}
|
}
|
||||||
@ -263,7 +263,7 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
|
|
||||||
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
while( inlen__ >= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES )
|
||||||
{
|
{
|
||||||
blake2s_update( S[i], in__, BLAKE2S_BLOCKBYTES );
|
_cryptonite_blake2s_update( S[i], in__, BLAKE2S_BLOCKBYTES );
|
||||||
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
in__ += PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
inlen__ -= PARALLELISM_DEGREE * BLAKE2S_BLOCKBYTES;
|
||||||
}
|
}
|
||||||
@ -272,10 +272,10 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
{
|
{
|
||||||
const size_t left = inlen__ - i * BLAKE2S_BLOCKBYTES;
|
const size_t left = inlen__ - i * BLAKE2S_BLOCKBYTES;
|
||||||
const size_t len = left <= BLAKE2S_BLOCKBYTES ? left : BLAKE2S_BLOCKBYTES;
|
const size_t len = left <= BLAKE2S_BLOCKBYTES ? left : BLAKE2S_BLOCKBYTES;
|
||||||
blake2s_update( S[i], in__, len );
|
_cryptonite_blake2s_update( S[i], in__, len );
|
||||||
}
|
}
|
||||||
|
|
||||||
blake2s_final( S[i], hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_final( S[i], hash[i], BLAKE2S_OUTBYTES );
|
||||||
}
|
}
|
||||||
|
|
||||||
if( blake2sp_init_root( FS, outlen, keylen ) < 0 )
|
if( blake2sp_init_root( FS, outlen, keylen ) < 0 )
|
||||||
@ -284,9 +284,9 @@ int blake2sp( void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
FS->last_node = 1;
|
FS->last_node = 1;
|
||||||
|
|
||||||
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
for( i = 0; i < PARALLELISM_DEGREE; ++i )
|
||||||
blake2s_update( FS, hash[i], BLAKE2S_OUTBYTES );
|
_cryptonite_blake2s_update( FS, hash[i], BLAKE2S_OUTBYTES );
|
||||||
|
|
||||||
return blake2s_final( FS, out, outlen );
|
return _cryptonite_blake2s_final( FS, out, outlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2SP_SELFTEST)
|
#if defined(BLAKE2SP_SELFTEST)
|
||||||
@ -308,7 +308,7 @@ int main( void )
|
|||||||
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
for( i = 0; i < BLAKE2_KAT_LENGTH; ++i )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2S_OUTBYTES];
|
uint8_t hash[BLAKE2S_OUTBYTES];
|
||||||
blake2sp( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
_cryptonite_blake2sp( hash, BLAKE2S_OUTBYTES, buf, i, key, BLAKE2S_KEYBYTES );
|
||||||
|
|
||||||
if( 0 != memcmp( hash, blake2sp_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
if( 0 != memcmp( hash, blake2sp_keyed_kat[i], BLAKE2S_OUTBYTES ) )
|
||||||
{
|
{
|
||||||
@ -325,21 +325,21 @@ int main( void )
|
|||||||
size_t mlen = i;
|
size_t mlen = i;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2sp_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2sp_init_key(&S, BLAKE2S_OUTBYTES, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2sp_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2sp_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2sp_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2sp_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2sp_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
if ( (err = _cryptonite_blake2sp_final(&S, hash, BLAKE2S_OUTBYTES)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -23,11 +23,11 @@
|
|||||||
#include "blake2.h"
|
#include "blake2.h"
|
||||||
#include "blake2-impl.h"
|
#include "blake2-impl.h"
|
||||||
|
|
||||||
int blake2xb_init( blake2xb_state *S, const size_t outlen ) {
|
int _cryptonite_blake2xb_init( blake2xb_state *S, const size_t outlen ) {
|
||||||
return blake2xb_init_key(S, outlen, NULL, 0);
|
return _cryptonite_blake2xb_init_key(S, outlen, NULL, 0);
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
if ( outlen == 0 || outlen > 0xFFFFFFFFUL ) {
|
if ( outlen == 0 || outlen > 0xFFFFFFFFUL ) {
|
||||||
return -1;
|
return -1;
|
||||||
@ -55,7 +55,7 @@ int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key,
|
|||||||
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
||||||
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
||||||
|
|
||||||
if( blake2b_init_param( S->S, S->P ) < 0 ) {
|
if( _cryptonite_blake2b_init_param( S->S, S->P ) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -63,17 +63,17 @@ int blake2xb_init_key( blake2xb_state *S, const size_t outlen, const void *key,
|
|||||||
uint8_t block[BLAKE2B_BLOCKBYTES];
|
uint8_t block[BLAKE2B_BLOCKBYTES];
|
||||||
memset(block, 0, BLAKE2B_BLOCKBYTES);
|
memset(block, 0, BLAKE2B_BLOCKBYTES);
|
||||||
memcpy(block, key, keylen);
|
memcpy(block, key, keylen);
|
||||||
blake2b_update(S->S, block, BLAKE2B_BLOCKBYTES);
|
_cryptonite_blake2b_update(S->S, block, BLAKE2B_BLOCKBYTES);
|
||||||
secure_zero_memory(block, BLAKE2B_BLOCKBYTES);
|
secure_zero_memory(block, BLAKE2B_BLOCKBYTES);
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_update( blake2xb_state *S, const void *in, size_t inlen ) {
|
int _cryptonite_blake2xb_update( blake2xb_state *S, const void *in, size_t inlen ) {
|
||||||
return blake2b_update( S->S, in, inlen );
|
return _cryptonite_blake2b_update( S->S, in, inlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
int _cryptonite_blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
||||||
|
|
||||||
blake2b_state C[1];
|
blake2b_state C[1];
|
||||||
blake2b_param P[1];
|
blake2b_param P[1];
|
||||||
@ -98,7 +98,7 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* Finalize the root hash */
|
/* Finalize the root hash */
|
||||||
if (blake2b_final(S->S, root, BLAKE2B_OUTBYTES) < 0) {
|
if (_cryptonite_blake2b_final(S->S, root, BLAKE2B_OUTBYTES) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -117,10 +117,10 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
/* Initialize state */
|
/* Initialize state */
|
||||||
P->digest_length = block_size;
|
P->digest_length = block_size;
|
||||||
store32(&P->node_offset, i);
|
store32(&P->node_offset, i);
|
||||||
blake2b_init_param(C, P);
|
_cryptonite_blake2b_init_param(C, P);
|
||||||
/* Process key if needed */
|
/* Process key if needed */
|
||||||
blake2b_update(C, root, BLAKE2B_OUTBYTES);
|
_cryptonite_blake2b_update(C, root, BLAKE2B_OUTBYTES);
|
||||||
if (blake2b_final(C, (uint8_t *)out + i * BLAKE2B_OUTBYTES, block_size) < 0 ) {
|
if (_cryptonite_blake2b_final(C, (uint8_t *)out + i * BLAKE2B_OUTBYTES, block_size) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
outlen -= block_size;
|
outlen -= block_size;
|
||||||
@ -133,7 +133,7 @@ int blake2xb_final( blake2xb_state *S, void *out, size_t outlen) {
|
|||||||
|
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
blake2xb_state S[1];
|
blake2xb_state S[1];
|
||||||
|
|
||||||
@ -154,15 +154,15 @@ int blake2xb(void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
return -1;
|
return -1;
|
||||||
|
|
||||||
/* Initialize the root block structure */
|
/* Initialize the root block structure */
|
||||||
if (blake2xb_init_key(S, outlen, key, keylen) < 0) {
|
if (_cryptonite_blake2xb_init_key(S, outlen, key, keylen) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* Absorb the input message */
|
/* Absorb the input message */
|
||||||
blake2xb_update(S, in, inlen);
|
_cryptonite_blake2xb_update(S, in, inlen);
|
||||||
|
|
||||||
/* Compute the root node of the tree and the final hash using the counter construction */
|
/* Compute the root node of the tree and the final hash using the counter construction */
|
||||||
return blake2xb_final(S, out, outlen);
|
return _cryptonite_blake2xb_final(S, out, outlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2XB_SELFTEST)
|
#if defined(BLAKE2XB_SELFTEST)
|
||||||
@ -189,7 +189,7 @@ int main( void )
|
|||||||
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
||||||
if( blake2xb( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2B_KEYBYTES ) < 0 ) {
|
if( _cryptonite_blake2xb( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2B_KEYBYTES ) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -208,21 +208,21 @@ int main( void )
|
|||||||
size_t mlen = BLAKE2_KAT_LENGTH;
|
size_t mlen = BLAKE2_KAT_LENGTH;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2xb_init_key(&S, outlen, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2xb_init_key(&S, outlen, key, BLAKE2B_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2xb_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2xb_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xb_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2xb_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xb_final(&S, hash, outlen)) < 0) {
|
if ( (err = _cryptonite_blake2xb_final(&S, hash, outlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -23,11 +23,11 @@
|
|||||||
#include "blake2.h"
|
#include "blake2.h"
|
||||||
#include "blake2-impl.h"
|
#include "blake2-impl.h"
|
||||||
|
|
||||||
int blake2xs_init( blake2xs_state *S, const size_t outlen ) {
|
int _cryptonite_blake2xs_init( blake2xs_state *S, const size_t outlen ) {
|
||||||
return blake2xs_init_key(S, outlen, NULL, 0);
|
return _cryptonite_blake2xs_init_key(S, outlen, NULL, 0);
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen )
|
int _cryptonite_blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key, size_t keylen )
|
||||||
{
|
{
|
||||||
if ( outlen == 0 || outlen > 0xFFFFUL ) {
|
if ( outlen == 0 || outlen > 0xFFFFUL ) {
|
||||||
return -1;
|
return -1;
|
||||||
@ -54,7 +54,7 @@ int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key,
|
|||||||
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
memset( S->P->salt, 0, sizeof( S->P->salt ) );
|
||||||
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
memset( S->P->personal, 0, sizeof( S->P->personal ) );
|
||||||
|
|
||||||
if( blake2s_init_param( S->S, S->P ) < 0 ) {
|
if( _cryptonite_blake2s_init_param( S->S, S->P ) < 0 ) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -62,17 +62,17 @@ int blake2xs_init_key( blake2xs_state *S, const size_t outlen, const void *key,
|
|||||||
uint8_t block[BLAKE2S_BLOCKBYTES];
|
uint8_t block[BLAKE2S_BLOCKBYTES];
|
||||||
memset(block, 0, BLAKE2S_BLOCKBYTES);
|
memset(block, 0, BLAKE2S_BLOCKBYTES);
|
||||||
memcpy(block, key, keylen);
|
memcpy(block, key, keylen);
|
||||||
blake2s_update(S->S, block, BLAKE2S_BLOCKBYTES);
|
_cryptonite_blake2s_update(S->S, block, BLAKE2S_BLOCKBYTES);
|
||||||
secure_zero_memory(block, BLAKE2S_BLOCKBYTES);
|
secure_zero_memory(block, BLAKE2S_BLOCKBYTES);
|
||||||
}
|
}
|
||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_update( blake2xs_state *S, const void *in, size_t inlen ) {
|
int _cryptonite_blake2xs_update( blake2xs_state *S, const void *in, size_t inlen ) {
|
||||||
return blake2s_update( S->S, in, inlen );
|
return _cryptonite_blake2s_update( S->S, in, inlen );
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
int _cryptonite_blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
||||||
|
|
||||||
blake2s_state C[1];
|
blake2s_state C[1];
|
||||||
blake2s_param P[1];
|
blake2s_param P[1];
|
||||||
@ -97,7 +97,7 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
/* Finalize the root hash */
|
/* Finalize the root hash */
|
||||||
if (blake2s_final(S->S, root, BLAKE2S_OUTBYTES) < 0) {
|
if (_cryptonite_blake2s_final(S->S, root, BLAKE2S_OUTBYTES) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -116,10 +116,10 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
/* Initialize state */
|
/* Initialize state */
|
||||||
P->digest_length = block_size;
|
P->digest_length = block_size;
|
||||||
store32(&P->node_offset, i);
|
store32(&P->node_offset, i);
|
||||||
blake2s_init_param(C, P);
|
_cryptonite_blake2s_init_param(C, P);
|
||||||
/* Process key if needed */
|
/* Process key if needed */
|
||||||
blake2s_update(C, root, BLAKE2S_OUTBYTES);
|
_cryptonite_blake2s_update(C, root, BLAKE2S_OUTBYTES);
|
||||||
if (blake2s_final(C, (uint8_t *)out + i * BLAKE2S_OUTBYTES, block_size) < 0) {
|
if (_cryptonite_blake2s_final(C, (uint8_t *)out + i * BLAKE2S_OUTBYTES, block_size) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
outlen -= block_size;
|
outlen -= block_size;
|
||||||
@ -131,7 +131,7 @@ int blake2xs_final(blake2xs_state *S, void *out, size_t outlen) {
|
|||||||
return 0;
|
return 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
int blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
int _cryptonite_blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void *key, size_t keylen)
|
||||||
{
|
{
|
||||||
blake2xs_state S[1];
|
blake2xs_state S[1];
|
||||||
|
|
||||||
@ -152,15 +152,15 @@ int blake2xs(void *out, size_t outlen, const void *in, size_t inlen, const void
|
|||||||
return -1;
|
return -1;
|
||||||
|
|
||||||
/* Initialize the root block structure */
|
/* Initialize the root block structure */
|
||||||
if (blake2xs_init_key(S, outlen, key, keylen) < 0) {
|
if (_cryptonite_blake2xs_init_key(S, outlen, key, keylen) < 0) {
|
||||||
return -1;
|
return -1;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* Absorb the input message */
|
/* Absorb the input message */
|
||||||
blake2xs_update(S, in, inlen);
|
_cryptonite_blake2xs_update(S, in, inlen);
|
||||||
|
|
||||||
/* Compute the root node of the tree and the final hash using the counter construction */
|
/* Compute the root node of the tree and the final hash using the counter construction */
|
||||||
return blake2xs_final(S, out, outlen);
|
return _cryptonite_blake2xs_final(S, out, outlen);
|
||||||
}
|
}
|
||||||
|
|
||||||
#if defined(BLAKE2XS_SELFTEST)
|
#if defined(BLAKE2XS_SELFTEST)
|
||||||
@ -187,7 +187,7 @@ int main( void )
|
|||||||
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
for( outlen = 1; outlen <= BLAKE2_KAT_LENGTH; ++outlen )
|
||||||
{
|
{
|
||||||
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
uint8_t hash[BLAKE2_KAT_LENGTH] = {0};
|
||||||
if( blake2xs( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2S_KEYBYTES ) < 0 ) {
|
if( _cryptonite_blake2xs( hash, outlen, buf, BLAKE2_KAT_LENGTH, key, BLAKE2S_KEYBYTES ) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -206,21 +206,21 @@ int main( void )
|
|||||||
size_t mlen = BLAKE2_KAT_LENGTH;
|
size_t mlen = BLAKE2_KAT_LENGTH;
|
||||||
int err = 0;
|
int err = 0;
|
||||||
|
|
||||||
if( (err = blake2xs_init_key(&S, outlen, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
if( (err = _cryptonite_blake2xs_init_key(&S, outlen, key, BLAKE2S_KEYBYTES)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
while (mlen >= step) {
|
while (mlen >= step) {
|
||||||
if ( (err = blake2xs_update(&S, p, step)) < 0 ) {
|
if ( (err = _cryptonite_blake2xs_update(&S, p, step)) < 0 ) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
mlen -= step;
|
mlen -= step;
|
||||||
p += step;
|
p += step;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xs_update(&S, p, mlen)) < 0) {
|
if ( (err = _cryptonite_blake2xs_update(&S, p, mlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
if ( (err = blake2xs_final(&S, hash, outlen)) < 0) {
|
if ( (err = _cryptonite_blake2xs_final(&S, hash, outlen)) < 0) {
|
||||||
goto fail;
|
goto fail;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|||||||
@ -2,15 +2,15 @@
|
|||||||
|
|
||||||
void cryptonite_blake2b_init(blake2b_ctx *ctx, uint32_t hashlen)
|
void cryptonite_blake2b_init(blake2b_ctx *ctx, uint32_t hashlen)
|
||||||
{
|
{
|
||||||
blake2b_init(ctx, hashlen / 8);
|
_cryptonite_blake2b_init(ctx, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2b_update(blake2b_ctx *ctx, const uint8_t *data, uint32_t len)
|
void cryptonite_blake2b_update(blake2b_ctx *ctx, const uint8_t *data, uint32_t len)
|
||||||
{
|
{
|
||||||
blake2b_update(ctx, data, len);
|
_cryptonite_blake2b_update(ctx, data, len);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2b_finalize(blake2b_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
void cryptonite_blake2b_finalize(blake2b_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
||||||
{
|
{
|
||||||
blake2b_final(ctx, out, hashlen / 8);
|
_cryptonite_blake2b_final(ctx, out, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|||||||
@ -2,15 +2,15 @@
|
|||||||
|
|
||||||
void cryptonite_blake2bp_init(blake2bp_ctx *ctx, uint32_t hashlen)
|
void cryptonite_blake2bp_init(blake2bp_ctx *ctx, uint32_t hashlen)
|
||||||
{
|
{
|
||||||
blake2bp_init(ctx, hashlen / 8);
|
_cryptonite_blake2bp_init(ctx, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2bp_update(blake2bp_ctx *ctx, const uint8_t *data, uint32_t len)
|
void cryptonite_blake2bp_update(blake2bp_ctx *ctx, const uint8_t *data, uint32_t len)
|
||||||
{
|
{
|
||||||
blake2bp_update(ctx, data, len);
|
_cryptonite_blake2bp_update(ctx, data, len);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2bp_finalize(blake2bp_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
void cryptonite_blake2bp_finalize(blake2bp_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
||||||
{
|
{
|
||||||
blake2bp_final(ctx, out, hashlen / 8);
|
_cryptonite_blake2bp_final(ctx, out, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|||||||
@ -2,15 +2,15 @@
|
|||||||
|
|
||||||
void cryptonite_blake2s_init(blake2s_ctx *ctx, uint32_t hashlen)
|
void cryptonite_blake2s_init(blake2s_ctx *ctx, uint32_t hashlen)
|
||||||
{
|
{
|
||||||
blake2s_init(ctx, hashlen / 8);
|
_cryptonite_blake2s_init(ctx, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2s_update(blake2s_ctx *ctx, const uint8_t *data, uint32_t len)
|
void cryptonite_blake2s_update(blake2s_ctx *ctx, const uint8_t *data, uint32_t len)
|
||||||
{
|
{
|
||||||
blake2s_update(ctx, data, len);
|
_cryptonite_blake2s_update(ctx, data, len);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2s_finalize(blake2s_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
void cryptonite_blake2s_finalize(blake2s_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
||||||
{
|
{
|
||||||
blake2s_final(ctx, out, hashlen / 8);
|
_cryptonite_blake2s_final(ctx, out, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|||||||
@ -2,15 +2,15 @@
|
|||||||
|
|
||||||
void cryptonite_blake2sp_init(blake2sp_ctx *ctx, uint32_t hashlen)
|
void cryptonite_blake2sp_init(blake2sp_ctx *ctx, uint32_t hashlen)
|
||||||
{
|
{
|
||||||
blake2sp_init(ctx, hashlen / 8);
|
_cryptonite_blake2sp_init(ctx, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2sp_update(blake2sp_ctx *ctx, const uint8_t *data, uint32_t len)
|
void cryptonite_blake2sp_update(blake2sp_ctx *ctx, const uint8_t *data, uint32_t len)
|
||||||
{
|
{
|
||||||
blake2sp_update(ctx, data, len);
|
_cryptonite_blake2sp_update(ctx, data, len);
|
||||||
}
|
}
|
||||||
|
|
||||||
void cryptonite_blake2sp_finalize(blake2sp_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
void cryptonite_blake2sp_finalize(blake2sp_ctx *ctx, uint32_t hashlen, uint8_t *out)
|
||||||
{
|
{
|
||||||
blake2sp_final(ctx, out, hashlen / 8);
|
_cryptonite_blake2sp_final(ctx, out, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|||||||
@ -121,14 +121,14 @@ void cryptonite_sha3_update(struct sha3_ctx *ctx, const uint8_t *data, uint32_t
|
|||||||
to_fill = ctx->bufsz - ctx->bufindex;
|
to_fill = ctx->bufsz - ctx->bufindex;
|
||||||
|
|
||||||
if (ctx->bufindex == ctx->bufsz) {
|
if (ctx->bufindex == ctx->bufsz) {
|
||||||
sha3_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
sha3_do_chunk(ctx->state, ctx->bufwords, ctx->bufsz / 8);
|
||||||
ctx->bufindex = 0;
|
ctx->bufindex = 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* process partial buffer if there's enough data to make a block */
|
/* process partial buffer if there's enough data to make a block */
|
||||||
if (ctx->bufindex && len >= to_fill) {
|
if (ctx->bufindex && len >= to_fill) {
|
||||||
memcpy(ctx->buf + ctx->bufindex, data, to_fill);
|
memcpy(ctx->buf + ctx->bufindex, data, to_fill);
|
||||||
sha3_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
sha3_do_chunk(ctx->state, ctx->bufwords, ctx->bufsz / 8);
|
||||||
len -= to_fill;
|
len -= to_fill;
|
||||||
data += to_fill;
|
data += to_fill;
|
||||||
ctx->bufindex = 0;
|
ctx->bufindex = 0;
|
||||||
@ -159,7 +159,7 @@ void cryptonite_sha3_finalize_with_pad_byte(struct sha3_ctx *ctx, uint8_t pad_by
|
|||||||
{
|
{
|
||||||
/* process full buffer if needed */
|
/* process full buffer if needed */
|
||||||
if (ctx->bufindex == ctx->bufsz) {
|
if (ctx->bufindex == ctx->bufsz) {
|
||||||
sha3_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
sha3_do_chunk(ctx->state, ctx->bufwords, ctx->bufsz / 8);
|
||||||
ctx->bufindex = 0;
|
ctx->bufindex = 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -169,7 +169,7 @@ void cryptonite_sha3_finalize_with_pad_byte(struct sha3_ctx *ctx, uint8_t pad_by
|
|||||||
ctx->buf[ctx->bufsz - 1] |= 0x80;
|
ctx->buf[ctx->bufsz - 1] |= 0x80;
|
||||||
|
|
||||||
/* process */
|
/* process */
|
||||||
sha3_do_chunk(ctx->state, (uint64_t *) ctx->buf, ctx->bufsz / 8);
|
sha3_do_chunk(ctx->state, ctx->bufwords, ctx->bufsz / 8);
|
||||||
ctx->bufindex = 0;
|
ctx->bufindex = 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -250,3 +250,31 @@ void cryptonite_keccak_finalize(struct sha3_ctx *ctx, uint32_t hashlen, uint8_t
|
|||||||
cryptonite_sha3_finalize_with_pad_byte(ctx, 1);
|
cryptonite_sha3_finalize_with_pad_byte(ctx, 1);
|
||||||
cryptonite_sha3_output(ctx, out, hashlen / 8);
|
cryptonite_sha3_output(ctx, out, hashlen / 8);
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
void cryptonite_sha3_ctx_to_be(struct sha3_ctx *ctx, uint8_t *out)
|
||||||
|
{
|
||||||
|
void *ptr = out;
|
||||||
|
const uint32_t bufindex_be = cpu_to_be32(ctx->bufindex);
|
||||||
|
memcpy(ptr, &bufindex_be, sizeof(uint32_t));
|
||||||
|
ptr += sizeof(uint32_t);
|
||||||
|
const uint32_t bufsz_be = cpu_to_be32(ctx->bufsz);
|
||||||
|
memcpy(ptr, &bufsz_be, sizeof(uint32_t));
|
||||||
|
ptr += sizeof(uint32_t);
|
||||||
|
cpu_to_be64_array((uint64_t *) ptr, ctx->state, 25);
|
||||||
|
ptr += 25 * sizeof(uint64_t);
|
||||||
|
cpu_to_be64_array((uint64_t *) ptr, ctx->bufwords, ctx->bufsz / sizeof(uint64_t));
|
||||||
|
}
|
||||||
|
|
||||||
|
void cryptonite_sha3_be_to_ctx(uint8_t *in, struct sha3_ctx *ctx)
|
||||||
|
{
|
||||||
|
const uint32_t bufindex_cpu = be32_to_cpu(* (uint32_t *) in);
|
||||||
|
memcpy(&ctx->bufindex, &bufindex_cpu, sizeof(uint32_t));
|
||||||
|
in += sizeof(uint32_t);
|
||||||
|
const uint32_t bufsz_cpu = be32_to_cpu(* (uint32_t *) in);
|
||||||
|
memcpy(&ctx->bufsz, &bufsz_cpu, sizeof(uint32_t));
|
||||||
|
in += sizeof(uint32_t);
|
||||||
|
be64_to_cpu_array(ctx->state, (uint64_t *) in, 25);
|
||||||
|
in += 25 * sizeof(uint64_t);
|
||||||
|
be64_to_cpu_array(ctx->bufwords, (uint64_t *) in, ctx->bufsz / sizeof(uint64_t));
|
||||||
|
}
|
||||||
|
|||||||
@ -29,9 +29,12 @@
|
|||||||
struct sha3_ctx
|
struct sha3_ctx
|
||||||
{
|
{
|
||||||
uint32_t bufindex;
|
uint32_t bufindex;
|
||||||
uint32_t bufsz;
|
uint32_t bufsz; /* size of buf, i.e. in bytes */
|
||||||
uint64_t state[25];
|
uint64_t state[25];
|
||||||
uint8_t buf[0]; /* maximum SHAKE128 is 168 bytes, otherwise buffer can be decreased */
|
union { /* maximum SHAKE128 is 168 bytes, otherwise buffer can be decreased */
|
||||||
|
uint8_t buf[0];
|
||||||
|
uint64_t bufwords[0];
|
||||||
|
};
|
||||||
};
|
};
|
||||||
|
|
||||||
#define SHA3_CTX_SIZE sizeof(struct sha3_ctx)
|
#define SHA3_CTX_SIZE sizeof(struct sha3_ctx)
|
||||||
@ -64,4 +67,7 @@ void cryptonite_keccak_init(struct sha3_ctx *ctx, uint32_t hashlen);
|
|||||||
void cryptonite_keccak_update(struct sha3_ctx *ctx, uint8_t *data, uint32_t len);
|
void cryptonite_keccak_update(struct sha3_ctx *ctx, uint8_t *data, uint32_t len);
|
||||||
void cryptonite_keccak_finalize(struct sha3_ctx *ctx, uint32_t hashlen, uint8_t *out);
|
void cryptonite_keccak_finalize(struct sha3_ctx *ctx, uint32_t hashlen, uint8_t *out);
|
||||||
|
|
||||||
|
void cryptonite_sha3_ctx_to_be(struct sha3_ctx *ctx, uint8_t *out);
|
||||||
|
void cryptonite_sha3_be_to_ctx(uint8_t *in, struct sha3_ctx *ctx);
|
||||||
|
|
||||||
#endif
|
#endif
|
||||||
|
|||||||
@ -1,5 +1,5 @@
|
|||||||
Name: cryptonite
|
Name: cryptonite
|
||||||
version: 0.28
|
version: 0.30
|
||||||
Synopsis: Cryptography Primitives sink
|
Synopsis: Cryptography Primitives sink
|
||||||
Description:
|
Description:
|
||||||
A repository of cryptographic primitives.
|
A repository of cryptographic primitives.
|
||||||
@ -36,7 +36,7 @@ Build-Type: Simple
|
|||||||
Homepage: https://github.com/haskell-crypto/cryptonite
|
Homepage: https://github.com/haskell-crypto/cryptonite
|
||||||
Bug-reports: https://github.com/haskell-crypto/cryptonite/issues
|
Bug-reports: https://github.com/haskell-crypto/cryptonite/issues
|
||||||
Cabal-Version: 1.18
|
Cabal-Version: 1.18
|
||||||
tested-with: GHC==8.8.2, GHC==8.6.5, GHC==8.4.4, GHC==8.2.2, GHC==8.0.2
|
tested-with: GHC==9.2.2, GHC==9.0.2, GHC==8.10.7, GHC==8.8.4
|
||||||
extra-doc-files: README.md CHANGELOG.md
|
extra-doc-files: README.md CHANGELOG.md
|
||||||
extra-source-files: cbits/*.h
|
extra-source-files: cbits/*.h
|
||||||
cbits/aes/*.h
|
cbits/aes/*.h
|
||||||
@ -170,6 +170,7 @@ Library
|
|||||||
Crypto.PubKey.ECIES
|
Crypto.PubKey.ECIES
|
||||||
Crypto.PubKey.Ed25519
|
Crypto.PubKey.Ed25519
|
||||||
Crypto.PubKey.Ed448
|
Crypto.PubKey.Ed448
|
||||||
|
Crypto.PubKey.EdDSA
|
||||||
Crypto.PubKey.RSA
|
Crypto.PubKey.RSA
|
||||||
Crypto.PubKey.RSA.PKCS15
|
Crypto.PubKey.RSA.PKCS15
|
||||||
Crypto.PubKey.RSA.Prim
|
Crypto.PubKey.RSA.Prim
|
||||||
@ -235,6 +236,7 @@ Library
|
|||||||
Crypto.PubKey.ElGamal
|
Crypto.PubKey.ElGamal
|
||||||
Crypto.ECC.Simple.Types
|
Crypto.ECC.Simple.Types
|
||||||
Crypto.ECC.Simple.Prim
|
Crypto.ECC.Simple.Prim
|
||||||
|
Crypto.Internal.Builder
|
||||||
Crypto.Internal.ByteArray
|
Crypto.Internal.ByteArray
|
||||||
Crypto.Internal.Compat
|
Crypto.Internal.Compat
|
||||||
Crypto.Internal.CompatPrim
|
Crypto.Internal.CompatPrim
|
||||||
@ -243,7 +245,7 @@ Library
|
|||||||
Crypto.Internal.Nat
|
Crypto.Internal.Nat
|
||||||
Crypto.Internal.Words
|
Crypto.Internal.Words
|
||||||
Crypto.Internal.WordArray
|
Crypto.Internal.WordArray
|
||||||
if impl(ghc < 8.0)
|
if impl(ghc < 8.8)
|
||||||
Buildable: False
|
Buildable: False
|
||||||
else
|
else
|
||||||
Build-depends: base
|
Build-depends: base
|
||||||
@ -410,6 +412,7 @@ Test-Suite test-cryptonite
|
|||||||
ECC.Edwards25519
|
ECC.Edwards25519
|
||||||
ECDSA
|
ECDSA
|
||||||
Hash
|
Hash
|
||||||
|
ResumableHash
|
||||||
Imports
|
Imports
|
||||||
KAT_AES.KATCBC
|
KAT_AES.KATCBC
|
||||||
KAT_AES.KATECB
|
KAT_AES.KATECB
|
||||||
@ -429,6 +432,7 @@ Test-Suite test-cryptonite
|
|||||||
KAT_DES
|
KAT_DES
|
||||||
KAT_Ed25519
|
KAT_Ed25519
|
||||||
KAT_Ed448
|
KAT_Ed448
|
||||||
|
KAT_EdDSA
|
||||||
KAT_CMAC
|
KAT_CMAC
|
||||||
KAT_HKDF
|
KAT_HKDF
|
||||||
KAT_HMAC
|
KAT_HMAC
|
||||||
|
|||||||
44
flake.lock
Normal file
44
flake.lock
Normal file
@ -0,0 +1,44 @@
|
|||||||
|
{
|
||||||
|
"nodes": {
|
||||||
|
"flake-utils": {
|
||||||
|
"locked": {
|
||||||
|
"lastModified": 1619345332,
|
||||||
|
"narHash": "sha256-qHnQkEp1uklKTpx3MvKtY6xzgcqXDsz5nLilbbuL+3A=",
|
||||||
|
"owner": "numtide",
|
||||||
|
"repo": "flake-utils",
|
||||||
|
"rev": "2ebf2558e5bf978c7fb8ea927dfaed8fefab2e28",
|
||||||
|
"type": "github"
|
||||||
|
},
|
||||||
|
"original": {
|
||||||
|
"owner": "numtide",
|
||||||
|
"ref": "master",
|
||||||
|
"repo": "flake-utils",
|
||||||
|
"type": "github"
|
||||||
|
}
|
||||||
|
},
|
||||||
|
"nixpkgs": {
|
||||||
|
"locked": {
|
||||||
|
"lastModified": 1620323686,
|
||||||
|
"narHash": "sha256-+gfcE3YTGl+Osc8HzOUXSFO8/0PAK4J8ZxCXZ4hjXHI=",
|
||||||
|
"owner": "NixOS",
|
||||||
|
"repo": "nixpkgs",
|
||||||
|
"rev": "dfacb8329b2236688b9a1e705116203a213b283a",
|
||||||
|
"type": "github"
|
||||||
|
},
|
||||||
|
"original": {
|
||||||
|
"owner": "NixOS",
|
||||||
|
"ref": "master",
|
||||||
|
"repo": "nixpkgs",
|
||||||
|
"type": "github"
|
||||||
|
}
|
||||||
|
},
|
||||||
|
"root": {
|
||||||
|
"inputs": {
|
||||||
|
"flake-utils": "flake-utils",
|
||||||
|
"nixpkgs": "nixpkgs"
|
||||||
|
}
|
||||||
|
}
|
||||||
|
},
|
||||||
|
"root": "root",
|
||||||
|
"version": 7
|
||||||
|
}
|
||||||
30
flake.nix
Normal file
30
flake.nix
Normal file
@ -0,0 +1,30 @@
|
|||||||
|
{
|
||||||
|
inputs = {
|
||||||
|
nixpkgs = {
|
||||||
|
type = "github";
|
||||||
|
owner = "NixOS";
|
||||||
|
repo = "nixpkgs";
|
||||||
|
ref = "master";
|
||||||
|
};
|
||||||
|
flake-utils = {
|
||||||
|
type = "github";
|
||||||
|
owner = "numtide";
|
||||||
|
repo = "flake-utils";
|
||||||
|
ref = "master";
|
||||||
|
};
|
||||||
|
};
|
||||||
|
|
||||||
|
outputs = { self, nixpkgs, flake-utils, ... }: flake-utils.lib.eachDefaultSystem
|
||||||
|
(system:
|
||||||
|
let pkgs = import nixpkgs {
|
||||||
|
inherit system;
|
||||||
|
config.allowUnfree = true;
|
||||||
|
};
|
||||||
|
in {
|
||||||
|
devShell = pkgs.mkShell {
|
||||||
|
name = "uni2work-cryptonite";
|
||||||
|
nativeBuildInputs = with pkgs.haskellPackages; [ stack ];
|
||||||
|
};
|
||||||
|
}
|
||||||
|
);
|
||||||
|
}
|
||||||
@ -1,3 +1,2 @@
|
|||||||
# ~*~ auto-generated by haskell-ci with config : 4fdddfa41dd039e198b8d125a70471f7dd140fa01001d99126af56fb31429ece ~*~
|
# ~*~ auto-generated by haskell-ci with config : 4fdddfa41dd039e198b8d125a70471f7dd140fa01001d99126af56fb31429ece ~*~
|
||||||
{ resolver: lts-14.27, packages: [ '.' ], extra-deps: [], flags: {} }
|
{ resolver: nightly-2022-03-12, packages: [ '.' ], extra-deps: [ memory-0.17.0 ], flags: {} }
|
||||||
|
|
||||||
|
|||||||
131
tests/KAT_EdDSA.hs
Normal file
131
tests/KAT_EdDSA.hs
Normal file
@ -0,0 +1,131 @@
|
|||||||
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
{-# LANGUAGE ExistentialQuantification #-}
|
||||||
|
{-# LANGUAGE GADTs #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
module KAT_EdDSA ( tests ) where
|
||||||
|
|
||||||
|
import Crypto.Error
|
||||||
|
import Crypto.ECC
|
||||||
|
import Crypto.Hash.Algorithms
|
||||||
|
import Crypto.Hash.IO
|
||||||
|
import qualified Crypto.PubKey.EdDSA as EdDSA
|
||||||
|
import Imports
|
||||||
|
|
||||||
|
data Vec = forall curve hash .
|
||||||
|
( EdDSA.EllipticCurveEdDSA curve
|
||||||
|
, HashAlgorithm hash
|
||||||
|
, HashDigestSize hash ~ EdDSA.CurveDigestSize curve
|
||||||
|
) => Vec
|
||||||
|
{ vecPrx :: Maybe curve
|
||||||
|
, vecAlg :: hash
|
||||||
|
, vecSec :: ByteString
|
||||||
|
, vecPub :: ByteString
|
||||||
|
, vecMsg :: ByteString
|
||||||
|
, vecSig :: ByteString
|
||||||
|
}
|
||||||
|
|
||||||
|
vectors =
|
||||||
|
[ Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = SHA512
|
||||||
|
, vecSec = "\x9d\x61\xb1\x9d\xef\xfd\x5a\x60\xba\x84\x4a\xf4\x92\xec\x2c\xc4\x44\x49\xc5\x69\x7b\x32\x69\x19\x70\x3b\xac\x03\x1c\xae\x7f\x60"
|
||||||
|
, vecPub = "\xd7\x5a\x98\x01\x82\xb1\x0a\xb7\xd5\x4b\xfe\xd3\xc9\x64\x07\x3a\x0e\xe1\x72\xf3\xda\xa6\x23\x25\xaf\x02\x1a\x68\xf7\x07\x51\x1a"
|
||||||
|
, vecMsg = ""
|
||||||
|
, vecSig = "\xe5\x56\x43\x00\xc3\x60\xac\x72\x90\x86\xe2\xcc\x80\x6e\x82\x8a\x84\x87\x7f\x1e\xb8\xe5\xd9\x74\xd8\x73\xe0\x65\x22\x49\x01\x55\x5f\xb8\x82\x15\x90\xa3\x3b\xac\xc6\x1e\x39\x70\x1c\xf9\xb4\x6b\xd2\x5b\xf5\xf0\x59\x5b\xbe\x24\x65\x51\x41\x43\x8e\x7a\x10\x0b"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = SHA512
|
||||||
|
, vecSec = "\x4c\xcd\x08\x9b\x28\xff\x96\xda\x9d\xb6\xc3\x46\xec\x11\x4e\x0f\x5b\x8a\x31\x9f\x35\xab\xa6\x24\xda\x8c\xf6\xed\x4f\xb8\xa6\xfb"
|
||||||
|
, vecPub = "\x3d\x40\x17\xc3\xe8\x43\x89\x5a\x92\xb7\x0a\xa7\x4d\x1b\x7e\xbc\x9c\x98\x2c\xcf\x2e\xc4\x96\x8c\xc0\xcd\x55\xf1\x2a\xf4\x66\x0c"
|
||||||
|
, vecMsg = "\x72"
|
||||||
|
, vecSig = "\x92\xa0\x09\xa9\xf0\xd4\xca\xb8\x72\x0e\x82\x0b\x5f\x64\x25\x40\xa2\xb2\x7b\x54\x16\x50\x3f\x8f\xb3\x76\x22\x23\xeb\xdb\x69\xda\x08\x5a\xc1\xe4\x3e\x15\x99\x6e\x45\x8f\x36\x13\xd0\xf1\x1d\x8c\x38\x7b\x2e\xae\xb4\x30\x2a\xee\xb0\x0d\x29\x16\x12\xbb\x0c\x00"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = SHA512
|
||||||
|
, vecSec = "\xc5\xaa\x8d\xf4\x3f\x9f\x83\x7b\xed\xb7\x44\x2f\x31\xdc\xb7\xb1\x66\xd3\x85\x35\x07\x6f\x09\x4b\x85\xce\x3a\x2e\x0b\x44\x58\xf7"
|
||||||
|
, vecPub = "\xfc\x51\xcd\x8e\x62\x18\xa1\xa3\x8d\xa4\x7e\xd0\x02\x30\xf0\x58\x08\x16\xed\x13\xba\x33\x03\xac\x5d\xeb\x91\x15\x48\x90\x80\x25"
|
||||||
|
, vecMsg = "\xaf\x82"
|
||||||
|
, vecSig = "\x62\x91\xd6\x57\xde\xec\x24\x02\x48\x27\xe6\x9c\x3a\xbe\x01\xa3\x0c\xe5\x48\xa2\x84\x74\x3a\x44\x5e\x36\x80\xd7\xdb\x5a\xc3\xac\x18\xff\x9b\x53\x8d\x16\xf2\x90\xae\x67\xf7\x60\x98\x4d\xc6\x59\x4a\x7c\x15\xe9\x71\x6e\xd2\x8d\xc0\x27\xbe\xce\xea\x1e\xc4\x0a"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = SHA512
|
||||||
|
, vecSec = "\xf5\xe5\x76\x7c\xf1\x53\x31\x95\x17\x63\x0f\x22\x68\x76\xb8\x6c\x81\x60\xcc\x58\x3b\xc0\x13\x74\x4c\x6b\xf2\x55\xf5\xcc\x0e\xe5"
|
||||||
|
, vecPub = "\x27\x81\x17\xfc\x14\x4c\x72\x34\x0f\x67\xd0\xf2\x31\x6e\x83\x86\xce\xff\xbf\x2b\x24\x28\xc9\xc5\x1f\xef\x7c\x59\x7f\x1d\x42\x6e"
|
||||||
|
, vecMsg = "\x08\xb8\xb2\xb7\x33\x42\x42\x43\x76\x0f\xe4\x26\xa4\xb5\x49\x08\x63\x21\x10\xa6\x6c\x2f\x65\x91\xea\xbd\x33\x45\xe3\xe4\xeb\x98\xfa\x6e\x26\x4b\xf0\x9e\xfe\x12\xee\x50\xf8\xf5\x4e\x9f\x77\xb1\xe3\x55\xf6\xc5\x05\x44\xe2\x3f\xb1\x43\x3d\xdf\x73\xbe\x84\xd8\x79\xde\x7c\x00\x46\xdc\x49\x96\xd9\xe7\x73\xf4\xbc\x9e\xfe\x57\x38\x82\x9a\xdb\x26\xc8\x1b\x37\xc9\x3a\x1b\x27\x0b\x20\x32\x9d\x65\x86\x75\xfc\x6e\xa5\x34\xe0\x81\x0a\x44\x32\x82\x6b\xf5\x8c\x94\x1e\xfb\x65\xd5\x7a\x33\x8b\xbd\x2e\x26\x64\x0f\x89\xff\xbc\x1a\x85\x8e\xfc\xb8\x55\x0e\xe3\xa5\xe1\x99\x8b\xd1\x77\xe9\x3a\x73\x63\xc3\x44\xfe\x6b\x19\x9e\xe5\xd0\x2e\x82\xd5\x22\xc4\xfe\xba\x15\x45\x2f\x80\x28\x8a\x82\x1a\x57\x91\x16\xec\x6d\xad\x2b\x3b\x31\x0d\xa9\x03\x40\x1a\xa6\x21\x00\xab\x5d\x1a\x36\x55\x3e\x06\x20\x3b\x33\x89\x0c\xc9\xb8\x32\xf7\x9e\xf8\x05\x60\xcc\xb9\xa3\x9c\xe7\x67\x96\x7e\xd6\x28\xc6\xad\x57\x3c\xb1\x16\xdb\xef\xef\xd7\x54\x99\xda\x96\xbd\x68\xa8\xa9\x7b\x92\x8a\x8b\xbc\x10\x3b\x66\x21\xfc\xde\x2b\xec\xa1\x23\x1d\x20\x6b\xe6\xcd\x9e\xc7\xaf\xf6\xf6\xc9\x4f\xcd\x72\x04\xed\x34\x55\xc6\x8c\x83\xf4\xa4\x1d\xa4\xaf\x2b\x74\xef\x5c\x53\xf1\xd8\xac\x70\xbd\xcb\x7e\xd1\x85\xce\x81\xbd\x84\x35\x9d\x44\x25\x4d\x95\x62\x9e\x98\x55\xa9\x4a\x7c\x19\x58\xd1\xf8\xad\xa5\xd0\x53\x2e\xd8\xa5\xaa\x3f\xb2\xd1\x7b\xa7\x0e\xb6\x24\x8e\x59\x4e\x1a\x22\x97\xac\xbb\xb3\x9d\x50\x2f\x1a\x8c\x6e\xb6\xf1\xce\x22\xb3\xde\x1a\x1f\x40\xcc\x24\x55\x41\x19\xa8\x31\xa9\xaa\xd6\x07\x9c\xad\x88\x42\x5d\xe6\xbd\xe1\xa9\x18\x7e\xbb\x60\x92\xcf\x67\xbf\x2b\x13\xfd\x65\xf2\x70\x88\xd7\x8b\x7e\x88\x3c\x87\x59\xd2\xc4\xf5\xc6\x5a\xdb\x75\x53\x87\x8a\xd5\x75\xf9\xfa\xd8\x78\xe8\x0a\x0c\x9b\xa6\x3b\xcb\xcc\x27\x32\xe6\x94\x85\xbb\xc9\xc9\x0b\xfb\xd6\x24\x81\xd9\x08\x9b\xec\xcf\x80\xcf\xe2\xdf\x16\xa2\xcf\x65\xbd\x92\xdd\x59\x7b\x07\x07\xe0\x91\x7a\xf4\x8b\xbb\x75\xfe\xd4\x13\xd2\x38\xf5\x55\x5a\x7a\x56\x9d\x80\xc3\x41\x4a\x8d\x08\x59\xdc\x65\xa4\x61\x28\xba\xb2\x7a\xf8\x7a\x71\x31\x4f\x31\x8c\x78\x2b\x23\xeb\xfe\x80\x8b\x82\xb0\xce\x26\x40\x1d\x2e\x22\xf0\x4d\x83\xd1\x25\x5d\xc5\x1a\xdd\xd3\xb7\x5a\x2b\x1a\xe0\x78\x45\x04\xdf\x54\x3a\xf8\x96\x9b\xe3\xea\x70\x82\xff\x7f\xc9\x88\x8c\x14\x4d\xa2\xaf\x58\x42\x9e\xc9\x60\x31\xdb\xca\xd3\xda\xd9\xaf\x0d\xcb\xaa\xaf\x26\x8c\xb8\xfc\xff\xea\xd9\x4f\x3c\x7c\xa4\x95\xe0\x56\xa9\xb4\x7a\xcd\xb7\x51\xfb\x73\xe6\x66\xc6\xc6\x55\xad\xe8\x29\x72\x97\xd0\x7a\xd1\xba\x5e\x43\xf1\xbc\xa3\x23\x01\x65\x13\x39\xe2\x29\x04\xcc\x8c\x42\xf5\x8c\x30\xc0\x4a\xaf\xdb\x03\x8d\xda\x08\x47\xdd\x98\x8d\xcd\xa6\xf3\xbf\xd1\x5c\x4b\x4c\x45\x25\x00\x4a\xa0\x6e\xef\xf8\xca\x61\x78\x3a\xac\xec\x57\xfb\x3d\x1f\x92\xb0\xfe\x2f\xd1\xa8\x5f\x67\x24\x51\x7b\x65\xe6\x14\xad\x68\x08\xd6\xf6\xee\x34\xdf\xf7\x31\x0f\xdc\x82\xae\xbf\xd9\x04\xb0\x1e\x1d\xc5\x4b\x29\x27\x09\x4b\x2d\xb6\x8d\x6f\x90\x3b\x68\x40\x1a\xde\xbf\x5a\x7e\x08\xd7\x8f\xf4\xef\x5d\x63\x65\x3a\x65\x04\x0c\xf9\xbf\xd4\xac\xa7\x98\x4a\x74\xd3\x71\x45\x98\x67\x80\xfc\x0b\x16\xac\x45\x16\x49\xde\x61\x88\xa7\xdb\xdf\x19\x1f\x64\xb5\xfc\x5e\x2a\xb4\x7b\x57\xf7\xf7\x27\x6c\xd4\x19\xc1\x7a\x3c\xa8\xe1\xb9\x39\xae\x49\xe4\x88\xac\xba\x6b\x96\x56\x10\xb5\x48\x01\x09\xc8\xb1\x7b\x80\xe1\xb7\xb7\x50\xdf\xc7\x59\x8d\x5d\x50\x11\xfd\x2d\xcc\x56\x00\xa3\x2e\xf5\xb5\x2a\x1e\xcc\x82\x0e\x30\x8a\xa3\x42\x72\x1a\xac\x09\x43\xbf\x66\x86\xb6\x4b\x25\x79\x37\x65\x04\xcc\xc4\x93\xd9\x7e\x6a\xed\x3f\xb0\xf9\xcd\x71\xa4\x3d\xd4\x97\xf0\x1f\x17\xc0\xe2\xcb\x37\x97\xaa\x2a\x2f\x25\x66\x56\x16\x8e\x6c\x49\x6a\xfc\x5f\xb9\x32\x46\xf6\xb1\x11\x63\x98\xa3\x46\xf1\xa6\x41\xf3\xb0\x41\xe9\x89\xf7\x91\x4f\x90\xcc\x2c\x7f\xff\x35\x78\x76\xe5\x06\xb5\x0d\x33\x4b\xa7\x7c\x22\x5b\xc3\x07\xba\x53\x71\x52\xf3\xf1\x61\x0e\x4e\xaf\xe5\x95\xf6\xd9\xd9\x0d\x11\xfa\xa9\x33\xa1\x5e\xf1\x36\x95\x46\x86\x8a\x7f\x3a\x45\xa9\x67\x68\xd4\x0f\xd9\xd0\x34\x12\xc0\x91\xc6\x31\x5c\xf4\xfd\xe7\xcb\x68\x60\x69\x37\x38\x0d\xb2\xea\xaa\x70\x7b\x4c\x41\x85\xc3\x2e\xdd\xcd\xd3\x06\x70\x5e\x4d\xc1\xff\xc8\x72\xee\xee\x47\x5a\x64\xdf\xac\x86\xab\xa4\x1c\x06\x18\x98\x3f\x87\x41\xc5\xef\x68\xd3\xa1\x01\xe8\xa3\xb8\xca\xc6\x0c\x90\x5c\x15\xfc\x91\x08\x40\xb9\x4c\x00\xa0\xb9\xd0"
|
||||||
|
, vecSig = "\x0a\xab\x4c\x90\x05\x01\xb3\xe2\x4d\x7c\xdf\x46\x63\x32\x6a\x3a\x87\xdf\x5e\x48\x43\xb2\xcb\xdb\x67\xcb\xf6\xe4\x60\xfe\xc3\x50\xaa\x53\x71\xb1\x50\x8f\x9f\x45\x28\xec\xea\x23\xc4\x36\xd9\x4b\x5e\x8f\xcd\x4f\x68\x1e\x30\xa6\xac\x00\xa9\x70\x4a\x18\x8a\x03"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = SHA512
|
||||||
|
, vecSec = "\x83\x3f\xe6\x24\x09\x23\x7b\x9d\x62\xec\x77\x58\x75\x20\x91\x1e\x9a\x75\x9c\xec\x1d\x19\x75\x5b\x7d\xa9\x01\xb9\x6d\xca\x3d\x42"
|
||||||
|
, vecPub = "\xec\x17\x2b\x93\xad\x5e\x56\x3b\xf4\x93\x2c\x70\xe1\x24\x50\x34\xc3\x54\x67\xef\x2e\xfd\x4d\x64\xeb\xf8\x19\x68\x34\x67\xe2\xbf"
|
||||||
|
, vecMsg = "\xdd\xaf\x35\xa1\x93\x61\x7a\xba\xcc\x41\x73\x49\xae\x20\x41\x31\x12\xe6\xfa\x4e\x89\xa9\x7e\xa2\x0a\x9e\xee\xe6\x4b\x55\xd3\x9a\x21\x92\x99\x2a\x27\x4f\xc1\xa8\x36\xba\x3c\x23\xa3\xfe\xeb\xbd\x45\x4d\x44\x23\x64\x3c\xe8\x0e\x2a\x9a\xc9\x4f\xa5\x4c\xa4\x9f"
|
||||||
|
, vecSig = "\xdc\x2a\x44\x59\xe7\x36\x96\x33\xa5\x2b\x1b\xf2\x77\x83\x9a\x00\x20\x10\x09\xa3\xef\xbf\x3e\xcb\x69\xbe\xa2\x18\x6c\x26\xb5\x89\x09\x35\x1f\xc9\xac\x90\xb3\xec\xfd\xfb\xc7\xc6\x64\x31\xe0\x30\x3d\xca\x17\x9c\x13\x8a\xc1\x7a\xd9\xbe\xf1\x17\x73\x31\xa7\x04"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = Blake2b_512
|
||||||
|
, vecSec = "\x9d\x61\xb1\x9d\xef\xfd\x5a\x60\xba\x84\x4a\xf4\x92\xec\x2c\xc4\x44\x49\xc5\x69\x7b\x32\x69\x19\x70\x3b\xac\x03\x1c\xae\x7f\x60"
|
||||||
|
, vecPub = "\x78\xe6\x5b\xf3\x0f\x89\x3d\x32\xfc\x57\xef\x05\x1c\x34\x1b\xde\xde\x24\x25\x44\xfc\x2a\x21\x12\xf0\xfa\x2c\x7a\xfd\xeb\xc0\x2f"
|
||||||
|
, vecMsg = ""
|
||||||
|
, vecSig = "\x99\xa5\x23\xbd\x46\x16\xc8\x16\x11\x44\xd6\xa9\x9d\x3c\x32\x40\x0c\xb4\xa3\x26\xf4\xd7\x9e\x30\x73\x40\xf6\xaf\xa1\x17\x50\xa0\x08\x5d\x7d\x84\x62\x6b\xc9\xe4\xb1\x53\xfc\x0e\x39\x6d\x15\xce\x44\xc3\x9b\xae\x45\x33\x80\x4d\xb1\xfe\x5b\x52\xf2\xb1\xb8\x05"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = Blake2b_512
|
||||||
|
, vecSec = "\x4c\xcd\x08\x9b\x28\xff\x96\xda\x9d\xb6\xc3\x46\xec\x11\x4e\x0f\x5b\x8a\x31\x9f\x35\xab\xa6\x24\xda\x8c\xf6\xed\x4f\xb8\xa6\xfb"
|
||||||
|
, vecPub = "\x5e\x71\x39\x2d\x91\xe6\xa5\x8f\xed\xeb\x08\x50\x36\x4f\x56\xcd\x15\x8a\x60\x44\x75\x57\xd7\x89\x03\x89\xc9\xb3\xd4\x57\x6d\x4d"
|
||||||
|
, vecMsg = "\x72"
|
||||||
|
, vecSig = "\x6d\xa7\x5e\x15\xb5\x70\x7f\x4d\xe5\xa1\x53\xc4\x8a\x5d\x83\x9f\xb8\x50\x74\xc3\x8a\xeb\x62\x85\x97\x7f\x03\xa1\x39\x77\x59\x7f\x97\x60\x69\xfd\xb9\x03\xf1\x83\x47\x4a\xaa\x5e\xd0\xcf\xe8\x78\xba\x8e\xf8\x68\xc5\xe4\x7c\xa3\xf9\x6c\xcf\xb3\xa8\x9b\x2a\x06"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = Blake2b_512
|
||||||
|
, vecSec = "\xc5\xaa\x8d\xf4\x3f\x9f\x83\x7b\xed\xb7\x44\x2f\x31\xdc\xb7\xb1\x66\xd3\x85\x35\x07\x6f\x09\x4b\x85\xce\x3a\x2e\x0b\x44\x58\xf7"
|
||||||
|
, vecPub = "\x8d\x53\xca\x70\xf0\xea\xb2\x3b\x91\x78\x34\x57\x85\xfc\xdb\x69\xed\x67\x23\xf8\x14\x8f\x7e\x33\x9e\x88\x65\x37\x00\xb7\x18\xda"
|
||||||
|
, vecMsg = "\xaf\x82"
|
||||||
|
, vecSig = "\x7c\xc3\xc1\x38\x52\xbd\x12\xab\xf3\xce\x4c\xa8\xca\x28\x36\xcb\xf8\x6d\xa9\x6c\x46\x34\xc5\x0d\xf3\xfb\x80\xdc\x80\x9e\x29\xdb\x0e\x10\x9c\x36\x13\x53\x40\x7c\x12\x36\xa9\x04\xf6\x36\x86\x8a\xa3\x39\x77\xa9\x9d\x3f\x84\x45\x98\xdb\x15\x38\xb4\x29\x52\x03"
|
||||||
|
}
|
||||||
|
, Vec
|
||||||
|
{ vecPrx = Just Curve_Edwards25519
|
||||||
|
, vecAlg = Blake2b_512
|
||||||
|
, vecSec = "\xf5\xe5\x76\x7c\xf1\x53\x31\x95\x17\x63\x0f\x22\x68\x76\xb8\x6c\x81\x60\xcc\x58\x3b\xc0\x13\x74\x4c\x6b\xf2\x55\xf5\xcc\x0e\xe5"
|
||||||
|
, vecPub = "\x9e\x3c\xa4\x9b\xb2\xd9\xe3\x6b\x8f\x0c\x94\x4a\x7b\x1c\x29\x26\x45\xda\x87\xce\x6f\xa6\xb4\x28\x86\xe5\xd7\xc8\x68\x33\xa7\x14"
|
||||||
|
, vecMsg = "\x08\xb8\xb2\xb7\x33\x42\x42\x43\x76\x0f\xe4\x26\xa4\xb5\x49\x08\x63\x21\x10\xa6\x6c\x2f\x65\x91\xea\xbd\x33\x45\xe3\xe4\xeb\x98\xfa\x6e\x26\x4b\xf0\x9e\xfe\x12\xee\x50\xf8\xf5\x4e\x9f\x77\xb1\xe3\x55\xf6\xc5\x05\x44\xe2\x3f\xb1\x43\x3d\xdf\x73\xbe\x84\xd8\x79\xde\x7c\x00\x46\xdc\x49\x96\xd9\xe7\x73\xf4\xbc\x9e\xfe\x57\x38\x82\x9a\xdb\x26\xc8\x1b\x37\xc9\x3a\x1b\x27\x0b\x20\x32\x9d\x65\x86\x75\xfc\x6e\xa5\x34\xe0\x81\x0a\x44\x32\x82\x6b\xf5\x8c\x94\x1e\xfb\x65\xd5\x7a\x33\x8b\xbd\x2e\x26\x64\x0f\x89\xff\xbc\x1a\x85\x8e\xfc\xb8\x55\x0e\xe3\xa5\xe1\x99\x8b\xd1\x77\xe9\x3a\x73\x63\xc3\x44\xfe\x6b\x19\x9e\xe5\xd0\x2e\x82\xd5\x22\xc4\xfe\xba\x15\x45\x2f\x80\x28\x8a\x82\x1a\x57\x91\x16\xec\x6d\xad\x2b\x3b\x31\x0d\xa9\x03\x40\x1a\xa6\x21\x00\xab\x5d\x1a\x36\x55\x3e\x06\x20\x3b\x33\x89\x0c\xc9\xb8\x32\xf7\x9e\xf8\x05\x60\xcc\xb9\xa3\x9c\xe7\x67\x96\x7e\xd6\x28\xc6\xad\x57\x3c\xb1\x16\xdb\xef\xef\xd7\x54\x99\xda\x96\xbd\x68\xa8\xa9\x7b\x92\x8a\x8b\xbc\x10\x3b\x66\x21\xfc\xde\x2b\xec\xa1\x23\x1d\x20\x6b\xe6\xcd\x9e\xc7\xaf\xf6\xf6\xc9\x4f\xcd\x72\x04\xed\x34\x55\xc6\x8c\x83\xf4\xa4\x1d\xa4\xaf\x2b\x74\xef\x5c\x53\xf1\xd8\xac\x70\xbd\xcb\x7e\xd1\x85\xce\x81\xbd\x84\x35\x9d\x44\x25\x4d\x95\x62\x9e\x98\x55\xa9\x4a\x7c\x19\x58\xd1\xf8\xad\xa5\xd0\x53\x2e\xd8\xa5\xaa\x3f\xb2\xd1\x7b\xa7\x0e\xb6\x24\x8e\x59\x4e\x1a\x22\x97\xac\xbb\xb3\x9d\x50\x2f\x1a\x8c\x6e\xb6\xf1\xce\x22\xb3\xde\x1a\x1f\x40\xcc\x24\x55\x41\x19\xa8\x31\xa9\xaa\xd6\x07\x9c\xad\x88\x42\x5d\xe6\xbd\xe1\xa9\x18\x7e\xbb\x60\x92\xcf\x67\xbf\x2b\x13\xfd\x65\xf2\x70\x88\xd7\x8b\x7e\x88\x3c\x87\x59\xd2\xc4\xf5\xc6\x5a\xdb\x75\x53\x87\x8a\xd5\x75\xf9\xfa\xd8\x78\xe8\x0a\x0c\x9b\xa6\x3b\xcb\xcc\x27\x32\xe6\x94\x85\xbb\xc9\xc9\x0b\xfb\xd6\x24\x81\xd9\x08\x9b\xec\xcf\x80\xcf\xe2\xdf\x16\xa2\xcf\x65\xbd\x92\xdd\x59\x7b\x07\x07\xe0\x91\x7a\xf4\x8b\xbb\x75\xfe\xd4\x13\xd2\x38\xf5\x55\x5a\x7a\x56\x9d\x80\xc3\x41\x4a\x8d\x08\x59\xdc\x65\xa4\x61\x28\xba\xb2\x7a\xf8\x7a\x71\x31\x4f\x31\x8c\x78\x2b\x23\xeb\xfe\x80\x8b\x82\xb0\xce\x26\x40\x1d\x2e\x22\xf0\x4d\x83\xd1\x25\x5d\xc5\x1a\xdd\xd3\xb7\x5a\x2b\x1a\xe0\x78\x45\x04\xdf\x54\x3a\xf8\x96\x9b\xe3\xea\x70\x82\xff\x7f\xc9\x88\x8c\x14\x4d\xa2\xaf\x58\x42\x9e\xc9\x60\x31\xdb\xca\xd3\xda\xd9\xaf\x0d\xcb\xaa\xaf\x26\x8c\xb8\xfc\xff\xea\xd9\x4f\x3c\x7c\xa4\x95\xe0\x56\xa9\xb4\x7a\xcd\xb7\x51\xfb\x73\xe6\x66\xc6\xc6\x55\xad\xe8\x29\x72\x97\xd0\x7a\xd1\xba\x5e\x43\xf1\xbc\xa3\x23\x01\x65\x13\x39\xe2\x29\x04\xcc\x8c\x42\xf5\x8c\x30\xc0\x4a\xaf\xdb\x03\x8d\xda\x08\x47\xdd\x98\x8d\xcd\xa6\xf3\xbf\xd1\x5c\x4b\x4c\x45\x25\x00\x4a\xa0\x6e\xef\xf8\xca\x61\x78\x3a\xac\xec\x57\xfb\x3d\x1f\x92\xb0\xfe\x2f\xd1\xa8\x5f\x67\x24\x51\x7b\x65\xe6\x14\xad\x68\x08\xd6\xf6\xee\x34\xdf\xf7\x31\x0f\xdc\x82\xae\xbf\xd9\x04\xb0\x1e\x1d\xc5\x4b\x29\x27\x09\x4b\x2d\xb6\x8d\x6f\x90\x3b\x68\x40\x1a\xde\xbf\x5a\x7e\x08\xd7\x8f\xf4\xef\x5d\x63\x65\x3a\x65\x04\x0c\xf9\xbf\xd4\xac\xa7\x98\x4a\x74\xd3\x71\x45\x98\x67\x80\xfc\x0b\x16\xac\x45\x16\x49\xde\x61\x88\xa7\xdb\xdf\x19\x1f\x64\xb5\xfc\x5e\x2a\xb4\x7b\x57\xf7\xf7\x27\x6c\xd4\x19\xc1\x7a\x3c\xa8\xe1\xb9\x39\xae\x49\xe4\x88\xac\xba\x6b\x96\x56\x10\xb5\x48\x01\x09\xc8\xb1\x7b\x80\xe1\xb7\xb7\x50\xdf\xc7\x59\x8d\x5d\x50\x11\xfd\x2d\xcc\x56\x00\xa3\x2e\xf5\xb5\x2a\x1e\xcc\x82\x0e\x30\x8a\xa3\x42\x72\x1a\xac\x09\x43\xbf\x66\x86\xb6\x4b\x25\x79\x37\x65\x04\xcc\xc4\x93\xd9\x7e\x6a\xed\x3f\xb0\xf9\xcd\x71\xa4\x3d\xd4\x97\xf0\x1f\x17\xc0\xe2\xcb\x37\x97\xaa\x2a\x2f\x25\x66\x56\x16\x8e\x6c\x49\x6a\xfc\x5f\xb9\x32\x46\xf6\xb1\x11\x63\x98\xa3\x46\xf1\xa6\x41\xf3\xb0\x41\xe9\x89\xf7\x91\x4f\x90\xcc\x2c\x7f\xff\x35\x78\x76\xe5\x06\xb5\x0d\x33\x4b\xa7\x7c\x22\x5b\xc3\x07\xba\x53\x71\x52\xf3\xf1\x61\x0e\x4e\xaf\xe5\x95\xf6\xd9\xd9\x0d\x11\xfa\xa9\x33\xa1\x5e\xf1\x36\x95\x46\x86\x8a\x7f\x3a\x45\xa9\x67\x68\xd4\x0f\xd9\xd0\x34\x12\xc0\x91\xc6\x31\x5c\xf4\xfd\xe7\xcb\x68\x60\x69\x37\x38\x0d\xb2\xea\xaa\x70\x7b\x4c\x41\x85\xc3\x2e\xdd\xcd\xd3\x06\x70\x5e\x4d\xc1\xff\xc8\x72\xee\xee\x47\x5a\x64\xdf\xac\x86\xab\xa4\x1c\x06\x18\x98\x3f\x87\x41\xc5\xef\x68\xd3\xa1\x01\xe8\xa3\xb8\xca\xc6\x0c\x90\x5c\x15\xfc\x91\x08\x40\xb9\x4c\x00\xa0\xb9\xd0"
|
||||||
|
, vecSig = "\xd0\x39\x65\xac\x31\x6a\x20\xf5\xa4\x7a\xb2\xd6\x18\x5e\xb3\xf0\xae\xea\x9c\x2e\xb8\xab\xe9\x22\xe9\x6d\x31\x7b\x3b\xd0\xef\x02\xe8\xd4\x7f\xd9\x23\x84\xe2\x86\x15\xeb\x33\x14\xad\xbc\x71\xc4\x67\x59\x96\x09\x9e\x48\x4c\xeb\x16\x28\x47\xc4\x0c\x32\x44\x0e"
|
||||||
|
}
|
||||||
|
]
|
||||||
|
|
||||||
|
|
||||||
|
doPublicKeyTest :: Int -> Vec -> TestTree
|
||||||
|
doPublicKeyTest i Vec{..} =
|
||||||
|
testCase (show i) (pub @=? EdDSA.toPublic vecPrx vecAlg sec)
|
||||||
|
where
|
||||||
|
!pub = throwCryptoError $ EdDSA.publicKey vecPrx vecAlg vecPub
|
||||||
|
!sec = throwCryptoError $ EdDSA.secretKey vecPrx vecSec
|
||||||
|
|
||||||
|
doSignatureTest :: Int -> Vec -> TestTree
|
||||||
|
doSignatureTest i Vec{..} =
|
||||||
|
testCase (show i) (sig @=? EdDSA.sign vecPrx sec pub vecMsg)
|
||||||
|
where
|
||||||
|
!sig = throwCryptoError $ EdDSA.signature vecPrx vecAlg vecSig
|
||||||
|
!pub = throwCryptoError $ EdDSA.publicKey vecPrx vecAlg vecPub
|
||||||
|
!sec = throwCryptoError $ EdDSA.secretKey vecPrx vecSec
|
||||||
|
|
||||||
|
doVerifyTest :: Int -> Vec -> TestTree
|
||||||
|
doVerifyTest i Vec{..} =
|
||||||
|
testCase (show i) (True @=? EdDSA.verify vecPrx pub vecMsg sig)
|
||||||
|
where
|
||||||
|
!sig = throwCryptoError $ EdDSA.signature vecPrx vecAlg vecSig
|
||||||
|
!pub = throwCryptoError $ EdDSA.publicKey vecPrx vecAlg vecPub
|
||||||
|
|
||||||
|
|
||||||
|
tests = testGroup "EdDSA"
|
||||||
|
[ testGroup "gen publickey" $ zipWith doPublicKeyTest [katZero..] vectors
|
||||||
|
, testGroup "gen signature" $ zipWith doSignatureTest [katZero..] vectors
|
||||||
|
, testGroup "verify sig" $ zipWith doVerifyTest [katZero..] vectors
|
||||||
|
]
|
||||||
65
tests/ResumableHash.hs
Normal file
65
tests/ResumableHash.hs
Normal file
@ -0,0 +1,65 @@
|
|||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
|
||||||
|
module ResumableHash (tests) where
|
||||||
|
|
||||||
|
import Crypto.Hash ( SHAKE128(..), SHAKE256(..), SHA3_224(..), SHA3_256(..), SHA3_384(..), SHA3_512(..), Keccak_224(..), Keccak_256(..), Keccak_384(..), Keccak_512(..)
|
||||||
|
, HashAlgorithm, HashAlgorithmResumable, Context, hashPutContext, hashGetContext)
|
||||||
|
import qualified Crypto.Hash as Hash
|
||||||
|
|
||||||
|
import qualified Data.ByteString as B
|
||||||
|
import qualified Data.ByteString.Lazy as LB
|
||||||
|
import qualified Data.ByteString.Builder as Builder
|
||||||
|
|
||||||
|
import Data.Maybe (fromMaybe)
|
||||||
|
|
||||||
|
import Imports
|
||||||
|
|
||||||
|
data HashResume a = HashResume [ByteString] [ByteString] (Hash.Digest a)
|
||||||
|
deriving (Show, Eq)
|
||||||
|
|
||||||
|
instance HashAlgorithm a => Arbitrary (HashResume a) where
|
||||||
|
arbitrary = do
|
||||||
|
(beforeChunks, afterChunks) <- oneof
|
||||||
|
[ ([], ) <$> (choose (1,20) >>= \n -> replicateM n (arbitraryBSof 1 99))
|
||||||
|
, (,) <$> (choose (1,20) >>= \n -> replicateM n (arbitraryBSof 1 99))
|
||||||
|
<*> (choose (1,20) >>= \n -> replicateM n (arbitraryBSof 1 99))
|
||||||
|
, (, []) <$> (choose (1,20) >>= \n -> replicateM n (arbitraryBSof 1 99))
|
||||||
|
, pure ([], [])
|
||||||
|
]
|
||||||
|
return $ HashResume beforeChunks afterChunks (Hash.hashlazy . LB.fromChunks $ beforeChunks ++ afterChunks)
|
||||||
|
|
||||||
|
resumeTests =
|
||||||
|
[ testResumeProperties "SHAKE128_256" (SHAKE128 :: SHAKE128 256)
|
||||||
|
, testResumeProperties "SHAKE256_256" (SHAKE256 :: SHAKE256 512)
|
||||||
|
, testResumeProperties "SHA3_224" SHA3_224
|
||||||
|
, testResumeProperties "SHA3_256" SHA3_256
|
||||||
|
, testResumeProperties "SHA3_384" SHA3_384
|
||||||
|
, testResumeProperties "SHA3_512" SHA3_512
|
||||||
|
, testResumeProperties "Keccak_224" Keccak_224
|
||||||
|
, testResumeProperties "Keccak_256" Keccak_256
|
||||||
|
, testResumeProperties "Keccak_384" Keccak_384
|
||||||
|
, testResumeProperties "Keccak_512" Keccak_512
|
||||||
|
, testCase "serializes big endian" $ test_is_be 168 (SHAKE128 :: SHAKE128 256)
|
||||||
|
]
|
||||||
|
where
|
||||||
|
testResumeProperties :: HashAlgorithmResumable a => TestName -> a -> TestTree
|
||||||
|
testResumeProperties name a = testGroup name
|
||||||
|
[ testProperty "resume" (prop_resume_start a)
|
||||||
|
]
|
||||||
|
|
||||||
|
prop_resume_start :: forall a. HashAlgorithmResumable a => a -> HashResume a -> Bool
|
||||||
|
prop_resume_start _ (HashResume beforeChunks afterChunks result) = fromMaybe False $ do
|
||||||
|
let beforeCtx = Hash.hashUpdates (Hash.hashInit :: Context a) beforeChunks
|
||||||
|
ctx <- hashGetContext (hashPutContext beforeCtx :: ByteString)
|
||||||
|
let afterCtx = Hash.hashUpdates ctx afterChunks
|
||||||
|
return $ result `assertEq` Hash.hashFinalize afterCtx
|
||||||
|
|
||||||
|
test_is_be :: forall a. HashAlgorithmResumable a => Word32 -> a -> Assertion
|
||||||
|
test_is_be size _ = slice @=? size_be
|
||||||
|
where size_be = LB.toStrict $ Builder.toLazyByteString $ Builder.word32BE size
|
||||||
|
serialized = hashPutContext (Hash.hashInit :: Context a) :: ByteString
|
||||||
|
slice = B.take 4 $ B.drop 4 serialized
|
||||||
|
|
||||||
|
tests = testGroup "ResumableHash" resumeTests
|
||||||
@ -13,6 +13,7 @@ import qualified ECC
|
|||||||
import qualified ECC.Edwards25519
|
import qualified ECC.Edwards25519
|
||||||
import qualified ECDSA
|
import qualified ECDSA
|
||||||
import qualified Hash
|
import qualified Hash
|
||||||
|
import qualified ResumableHash
|
||||||
import qualified Poly1305
|
import qualified Poly1305
|
||||||
import qualified Salsa
|
import qualified Salsa
|
||||||
import qualified XSalsa
|
import qualified XSalsa
|
||||||
@ -29,6 +30,7 @@ import qualified KAT_Curve25519
|
|||||||
import qualified KAT_Curve448
|
import qualified KAT_Curve448
|
||||||
import qualified KAT_Ed25519
|
import qualified KAT_Ed25519
|
||||||
import qualified KAT_Ed448
|
import qualified KAT_Ed448
|
||||||
|
import qualified KAT_EdDSA
|
||||||
import qualified KAT_OTP
|
import qualified KAT_OTP
|
||||||
import qualified KAT_PubKey
|
import qualified KAT_PubKey
|
||||||
import qualified KAT_Scrypt
|
import qualified KAT_Scrypt
|
||||||
@ -53,6 +55,7 @@ tests = testGroup "cryptonite"
|
|||||||
, Number.tests
|
, Number.tests
|
||||||
, Number.F2m.tests
|
, Number.F2m.tests
|
||||||
, Hash.tests
|
, Hash.tests
|
||||||
|
, ResumableHash.tests
|
||||||
, Padding.tests
|
, Padding.tests
|
||||||
, testGroup "ConstructHash"
|
, testGroup "ConstructHash"
|
||||||
[ KAT_MiyaguchiPreneel.tests
|
[ KAT_MiyaguchiPreneel.tests
|
||||||
@ -67,6 +70,7 @@ tests = testGroup "cryptonite"
|
|||||||
, KAT_Curve448.tests
|
, KAT_Curve448.tests
|
||||||
, KAT_Ed25519.tests
|
, KAT_Ed25519.tests
|
||||||
, KAT_Ed448.tests
|
, KAT_Ed448.tests
|
||||||
|
, KAT_EdDSA.tests
|
||||||
, KAT_PubKey.tests
|
, KAT_PubKey.tests
|
||||||
, KAT_OTP.tests
|
, KAT_OTP.tests
|
||||||
, testGroup "KDF"
|
, testGroup "KDF"
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user