Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/master'
Browse files Browse the repository at this point in the history
  • Loading branch information
infinity0 committed Feb 17, 2021
2 parents 8f3d73d + 955f94b commit a0ca46f
Show file tree
Hide file tree
Showing 34 changed files with 587 additions and 30 deletions.
15 changes: 15 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,18 @@
## 0.28

* Add hash constant time capability
* Prevent possible overflow during hashing by hashing in 4GB chunks

## 0.27

* Optimise AES GCM and CCM
* Optimise P256R1 implementation
* Various AES-NI building improvements
* Add better ECDSA support
* Add XSalsa derive
* Implement square roots for ECC binary curve
* Various tests and benchmarks

## 0.26

* Add Rabin cryptosystem (and variants)
Expand Down
5 changes: 5 additions & 0 deletions Crypto/Cipher/RC4.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,11 @@ import Crypto.Internal.Compat
import Crypto.Internal.Imports

-- | The encryption state for RC4
--
-- This type is an instance of 'ByteArrayAccess' for debugging purpose. Internal
-- layout is architecture dependent, may contain uninitialized data fragments,
-- and change in future versions. The bytearray should not be used as input to
-- cryptographic algorithms.
newtype State = State ScrubbedBytes
deriving (ByteArrayAccess,NFData)

Expand Down
10 changes: 5 additions & 5 deletions Crypto/Cipher/Types/AEAD.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,24 +27,24 @@ data AEADModeImpl st = AEADModeImpl
-- | Authenticated Encryption with Associated Data algorithms
data AEAD cipher = forall st . AEAD
{ aeadModeImpl :: AEADModeImpl st
, aeadState :: st
, aeadState :: !st
}

-- | Append some header information to an AEAD context
aeadAppendHeader :: ByteArrayAccess aad => AEAD cipher -> aad -> AEAD cipher
aeadAppendHeader (AEAD impl st) aad = AEAD impl $ (aeadImplAppendHeader impl) st aad
aeadAppendHeader (AEAD impl st) aad = AEAD impl $ aeadImplAppendHeader impl st aad

-- | Encrypt some data and update the AEAD context
aeadEncrypt :: ByteArray ba => AEAD cipher -> ba -> (ba, AEAD cipher)
aeadEncrypt (AEAD impl st) ba = second (AEAD impl) $ (aeadImplEncrypt impl) st ba
aeadEncrypt (AEAD impl st) ba = second (AEAD impl) $ aeadImplEncrypt impl st ba

-- | Decrypt some data and update the AEAD context
aeadDecrypt :: ByteArray ba => AEAD cipher -> ba -> (ba, AEAD cipher)
aeadDecrypt (AEAD impl st) ba = second (AEAD impl) $ (aeadImplDecrypt impl) st ba
aeadDecrypt (AEAD impl st) ba = second (AEAD impl) $ aeadImplDecrypt impl st ba

-- | Finalize the AEAD context and return the authentication tag
aeadFinalize :: AEAD cipher -> Int -> AuthTag
aeadFinalize (AEAD impl st) n = (aeadImplFinalize impl) st n
aeadFinalize (AEAD impl st) = aeadImplFinalize impl st

-- | Simple AEAD encryption
aeadSimpleEncrypt :: (ByteArrayAccess aad, ByteArray ba)
Expand Down
43 changes: 40 additions & 3 deletions Crypto/Hash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,14 +28,17 @@ module Crypto.Hash
-- * Hash methods parametrized by algorithm
, hashInitWith
, hashWith
, hashPrefixWith
-- * Hash methods
, hashInit
, hashUpdates
, hashUpdate
, hashFinalize
, hashFinalizePrefix
, hashBlockSize
, hashDigestSize
, hash
, hashPrefix
, hashlazy
-- * Hash algorithms
, module Crypto.Hash.Algorithms
Expand All @@ -47,16 +50,20 @@ import Basement.Block.Mutable (copyFromPtr, new)
import Crypto.Internal.Compat (unsafeDoIO)
import Crypto.Hash.Types
import Crypto.Hash.Algorithms
import Foreign.Ptr (Ptr)
import Foreign.Ptr (Ptr, plusPtr)
import Crypto.Internal.ByteArray (ByteArrayAccess)
import qualified Crypto.Internal.ByteArray as B
import qualified Data.ByteString.Lazy as L
import Data.Word (Word8)
import Data.Word (Word8, Word32)

-- | Hash a strict bytestring into a digest.
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
hash bs = hashFinalize $ hashUpdate hashInit bs

-- | Hash the first N bytes of a bytestring, with code path independent from N.
hashPrefix :: (ByteArrayAccess ba, HashAlgorithmPrefix a) => ba -> Int -> Digest a
hashPrefix = hashFinalizePrefix hashInit

-- | Hash a lazy bytestring into a digest.
hashlazy :: HashAlgorithm a => L.ByteString -> Digest a
hashlazy lbs = hashFinalize $ hashUpdates hashInit (L.toChunks lbs)
Expand All @@ -81,9 +88,17 @@ hashUpdates :: forall a ba . (HashAlgorithm a, ByteArrayAccess ba)
hashUpdates c l
| null ls = c
| otherwise = Context $ B.copyAndFreeze c $ \(ctx :: Ptr (Context a)) ->
mapM_ (\b -> B.withByteArray b $ \d -> hashInternalUpdate ctx d (fromIntegral $ B.length b)) ls
mapM_ (\b -> B.withByteArray b (processBlocks ctx (B.length b))) ls
where
ls = filter (not . B.null) l
-- process the data in 4GB chunks to fit in uint32_t
processBlocks ctx bytesLeft dataPtr
| bytesLeft == 0 = return ()
| otherwise = do
hashInternalUpdate ctx dataPtr (fromIntegral actuallyProcessed)
processBlocks ctx (bytesLeft - actuallyProcessed) (dataPtr `plusPtr` actuallyProcessed)
where
actuallyProcessed = min bytesLeft (fromIntegral (maxBound :: Word32))

-- | Finalize a context and return a digest.
hashFinalize :: forall a . HashAlgorithm a
Expand All @@ -94,6 +109,24 @@ hashFinalize !c =
((!_) :: B.Bytes) <- B.copy c $ \(ctx :: Ptr (Context a)) -> hashInternalFinalize ctx dig
return ()

-- | Update the context with the first N bytes of a bytestring and return the
-- digest. The code path is independent from N but much slower than a normal
-- 'hashUpdate'. The function can be called for the last bytes of a message, in
-- order to exclude a variable padding, without leaking the padding length. The
-- begining of the message, never impacted by the padding, should preferably go
-- through 'hashUpdate' for better performance.
hashFinalizePrefix :: forall a ba . (HashAlgorithmPrefix a, ByteArrayAccess ba)
=> Context a
-> ba
-> Int
-> Digest a
hashFinalizePrefix !c b len =
Digest $ B.allocAndFreeze (hashDigestSize (undefined :: a)) $ \(dig :: Ptr (Digest a)) -> do
((!_) :: B.Bytes) <- B.copy c $ \(ctx :: Ptr (Context a)) ->
B.withByteArray b $ \d ->
hashInternalFinalizePrefix ctx d (fromIntegral $ B.length b) (fromIntegral len) dig
return ()

-- | Initialize a new context for a specified hash algorithm
hashInitWith :: HashAlgorithm alg => alg -> Context alg
hashInitWith _ = hashInit
Expand All @@ -102,6 +135,10 @@ hashInitWith _ = hashInit
hashWith :: (ByteArrayAccess ba, HashAlgorithm alg) => alg -> ba -> Digest alg
hashWith _ = hash

-- | Run the 'hashPrefix' function but takes an explicit hash algorithm parameter
hashPrefixWith :: (ByteArrayAccess ba, HashAlgorithmPrefix alg) => alg -> ba -> Int -> Digest alg
hashPrefixWith _ = hashPrefix

-- | Try to transform a bytearray into a Digest of specific algorithm.
--
-- If the digest is not the right size for the algorithm specified, then
Expand Down
3 changes: 2 additions & 1 deletion Crypto/Hash/Algorithms.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
--
module Crypto.Hash.Algorithms
( HashAlgorithm
, HashAlgorithmPrefix
-- * Hash algorithms
, Blake2s_160(..)
, Blake2s_224(..)
Expand Down Expand Up @@ -54,7 +55,7 @@ module Crypto.Hash.Algorithms
, Whirlpool(..)
) where

import Crypto.Hash.Types (HashAlgorithm)
import Crypto.Hash.Types (HashAlgorithm, HashAlgorithmPrefix)
import Crypto.Hash.Blake2s
import Crypto.Hash.Blake2sp
import Crypto.Hash.Blake2b
Expand Down
5 changes: 5 additions & 0 deletions Crypto/Hash/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,11 @@ import qualified Crypto.Internal.ByteArray as B
import Foreign.Ptr

-- | A Mutable hash context
--
-- This type is an instance of 'B.ByteArrayAccess' for debugging purpose.
-- Internal layout is architecture dependent, may contain uninitialized data
-- fragments, and change in future versions. The bytearray should not be used
-- as input to cryptographic algorithms.
newtype MutableContext a = MutableContext B.Bytes
deriving (B.ByteArrayAccess)

Expand Down
6 changes: 6 additions & 0 deletions Crypto/Hash/MD5.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm MD5 where
hashInternalUpdate = c_md5_update
hashInternalFinalize = c_md5_finalize

instance HashAlgorithmPrefix MD5 where
hashInternalFinalizePrefix = c_md5_finalize_prefix

foreign import ccall unsafe "cryptonite_md5_init"
c_md5_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_md5_update"

foreign import ccall unsafe "cryptonite_md5_finalize"
c_md5_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_md5_finalize_prefix"
c_md5_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
6 changes: 6 additions & 0 deletions Crypto/Hash/SHA1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm SHA1 where
hashInternalUpdate = c_sha1_update
hashInternalFinalize = c_sha1_finalize

instance HashAlgorithmPrefix SHA1 where
hashInternalFinalizePrefix = c_sha1_finalize_prefix

foreign import ccall unsafe "cryptonite_sha1_init"
c_sha1_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_sha1_update"

foreign import ccall unsafe "cryptonite_sha1_finalize"
c_sha1_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_sha1_finalize_prefix"
c_sha1_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
6 changes: 6 additions & 0 deletions Crypto/Hash/SHA224.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm SHA224 where
hashInternalUpdate = c_sha224_update
hashInternalFinalize = c_sha224_finalize

instance HashAlgorithmPrefix SHA224 where
hashInternalFinalizePrefix = c_sha224_finalize_prefix

foreign import ccall unsafe "cryptonite_sha224_init"
c_sha224_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_sha224_update"

foreign import ccall unsafe "cryptonite_sha224_finalize"
c_sha224_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_sha224_finalize_prefix"
c_sha224_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
6 changes: 6 additions & 0 deletions Crypto/Hash/SHA256.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm SHA256 where
hashInternalUpdate = c_sha256_update
hashInternalFinalize = c_sha256_finalize

instance HashAlgorithmPrefix SHA256 where
hashInternalFinalizePrefix = c_sha256_finalize_prefix

foreign import ccall unsafe "cryptonite_sha256_init"
c_sha256_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_sha256_update"

foreign import ccall unsafe "cryptonite_sha256_finalize"
c_sha256_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_sha256_finalize_prefix"
c_sha256_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
6 changes: 6 additions & 0 deletions Crypto/Hash/SHA384.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm SHA384 where
hashInternalUpdate = c_sha384_update
hashInternalFinalize = c_sha384_finalize

instance HashAlgorithmPrefix SHA384 where
hashInternalFinalizePrefix = c_sha384_finalize_prefix

foreign import ccall unsafe "cryptonite_sha384_init"
c_sha384_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_sha384_update"

foreign import ccall unsafe "cryptonite_sha384_finalize"
c_sha384_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_sha384_finalize_prefix"
c_sha384_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
6 changes: 6 additions & 0 deletions Crypto/Hash/SHA512.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ instance HashAlgorithm SHA512 where
hashInternalUpdate = c_sha512_update
hashInternalFinalize = c_sha512_finalize

instance HashAlgorithmPrefix SHA512 where
hashInternalFinalizePrefix = c_sha512_finalize_prefix

foreign import ccall unsafe "cryptonite_sha512_init"
c_sha512_init :: Ptr (Context a)-> IO ()

Expand All @@ -42,3 +45,6 @@ foreign import ccall "cryptonite_sha512_update"

foreign import ccall unsafe "cryptonite_sha512_finalize"
c_sha512_finalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

foreign import ccall "cryptonite_sha512_finalize_prefix"
c_sha512_finalize_prefix :: Ptr (Context a) -> Ptr Word8 -> Word32 -> Word32 -> Ptr (Digest a) -> IO ()
17 changes: 17 additions & 0 deletions Crypto/Hash/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
{-# LANGUAGE TypeFamilies #-}
module Crypto.Hash.Types
( HashAlgorithm(..)
, HashAlgorithmPrefix(..)
, Context(..)
, Digest(..)
) where
Expand Down Expand Up @@ -59,12 +60,28 @@ class HashAlgorithm a where
-- | Finalize the context and set the digest raw memory to the right value
hashInternalFinalize :: Ptr (Context a) -> Ptr (Digest a) -> IO ()

-- | Hashing algorithms with a constant-time implementation.
class HashAlgorithm a => HashAlgorithmPrefix a where
-- | Update the context with the first N bytes of a buffer and finalize this
-- context. The code path executed is independent from N and depends only
-- on the complete buffer length.
hashInternalFinalizePrefix :: Ptr (Context a)
-> Ptr Word8 -> Word32
-> Word32
-> Ptr (Digest a)
-> IO ()

{-
hashContextGetAlgorithm :: HashAlgorithm a => Context a -> a
hashContextGetAlgorithm = undefined
-}

-- | Represent a context for a given hash algorithm.
--
-- This type is an instance of 'ByteArrayAccess' for debugging purpose. Internal
-- layout is architecture dependent, may contain uninitialized data fragments,
-- and change in future versions. The bytearray should not be used as input to
-- cryptographic algorithms.
newtype Context a = Context Bytes
deriving (ByteArrayAccess,NFData)

Expand Down
5 changes: 5 additions & 0 deletions Crypto/MAC/Poly1305.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,11 @@ import Crypto.Internal.DeepSeq
import Crypto.Error

-- | Poly1305 State
--
-- This type is an instance of 'ByteArrayAccess' for debugging purpose. Internal
-- layout is architecture dependent, may contain uninitialized data fragments,
-- and change in future versions. The bytearray should not be used as input to
-- cryptographic algorithms.
newtype State = State ScrubbedBytes
deriving (ByteArrayAccess)

Expand Down
35 changes: 32 additions & 3 deletions Crypto/Number/F2m.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,9 @@ module Crypto.Number.F2m
, mulF2m
, squareF2m'
, squareF2m
, powF2m
, modF2m
, sqrtF2m
, invF2m
, divF2m
) where
Expand Down Expand Up @@ -66,8 +68,8 @@ mulF2m :: BinaryPolynomial -- ^ Modulus
mulF2m fx n1 n2
| fx < 0
|| n1 < 0
|| n2 < 0 = error "mulF2m: negative number represent no binary binary polynomial"
| fx == 0 = error "modF2m: cannot multiply modulo zero polynomial"
|| n2 < 0 = error "mulF2m: negative number represent no binary polynomial"
| fx == 0 = error "mulF2m: cannot multiply modulo zero polynomial"
| otherwise = modF2m fx $ go (if n2 `mod` 2 == 1 then n1 else 0) (log2 n2)
where
go n s | s == 0 = n
Expand Down Expand Up @@ -96,10 +98,37 @@ squareF2m fx = modF2m fx . squareF2m'
squareF2m' :: Integer
-> Integer
squareF2m' n
| n < 0 = error "mulF2m: negative number represent no binary binary polynomial"
| n < 0 = error "mulF2m: negative number represent no binary polynomial"
| otherwise = foldl' (\acc s -> if testBit n s then setBit acc (2 * s) else acc) 0 [0 .. log2 n]
{-# INLINE squareF2m' #-}

-- | Exponentiation in F₂m by computing @a^b mod fx@.
--
-- This implements an exponentiation by squaring based solution. It inherits the
-- same restrictions as 'squareF2m'. Negative exponents are disallowed.
powF2m :: BinaryPolynomial -- ^Modulus
-> Integer -- ^a
-> Integer -- ^b
-> Integer
powF2m fx a b
| b < 0 = error "powF2m: negative exponents disallowed"
| b == 0 = if fx > 1 then 1 else 0
| even b = squareF2m fx x
| otherwise = mulF2m fx a (squareF2m' x)
where x = powF2m fx a (b `div` 2)

-- | Square rooot in F₂m.
--
-- We exploit the fact that @a^(2^m) = a@, or in particular, @a^(2^m - 1) = 1@
-- from a classical result by Lagrange. Thus the square root is simply @a^(2^(m
-- - 1))@.
sqrtF2m :: BinaryPolynomial -- ^Modulus
-> Integer -- ^a
-> Integer
sqrtF2m fx a = go (log2 fx - 1) a
where go 0 x = x
go n x = go (n - 1) (squareF2m fx x)

-- | Extended GCD algorithm for polynomials. For @a@ and @b@ returns @(g, u, v)@ such that @a * u + b * v == g@.
--
-- Reference: https://en.wikipedia.org/wiki/Polynomial_greatest_common_divisor#B.C3.A9zout.27s_identity_and_extended_GCD_algorithm
Expand Down
Loading

0 comments on commit a0ca46f

Please sign in to comment.