add optional support for deepseq

This commit is contained in:
Vincent Hanquez 2015-05-22 18:35:46 +01:00
parent c78e9472b9
commit 8eaaa06e1e
18 changed files with 127 additions and 20 deletions

View File

@ -5,6 +5,7 @@
-- Stability : stable
-- Portability : good
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.AES
( AES128
, AES192
@ -15,15 +16,19 @@ import Crypto.Error
import Crypto.Cipher.Types
import Crypto.Cipher.Types.Block
import Crypto.Cipher.AES.Primitive
import Crypto.Internal.Imports
-- | AES with 128 bit key
newtype AES128 = AES128 AES
deriving (NFData)
-- | AES with 192 bit key
newtype AES192 = AES192 AES
deriving (NFData)
-- | AES with 256 bit key
newtype AES256 = AES256 AES
deriving (NFData)
instance Cipher AES128 where
cipherName _ = "AES128"

View File

@ -67,6 +67,7 @@ import Crypto.Error
import Crypto.Cipher.Types
import Crypto.Cipher.Types.Block (IV(..))
import Crypto.Internal.Compat
import Crypto.Internal.Imports
import Crypto.Internal.ByteArray (ByteArray, ByteArrayAccess, ScrubbedBytes, withByteArray)
import qualified Crypto.Internal.ByteArray as B
@ -110,12 +111,15 @@ ocbMode aes = AEADModeImpl
-- | AES Context (pre-processed key)
newtype AES = AES ScrubbedBytes
deriving (NFData)
-- | AESGCM State
newtype AESGCM = AESGCM ScrubbedBytes
deriving (NFData)
-- | AESOCB State
newtype AESOCB = AESOCB ScrubbedBytes
deriving (NFData)
sizeGCM :: Int
sizeGCM = 80

View File

@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
-- |
-- Module : Crypto.Cipher.Blowfish
-- License : BSD-style
@ -6,6 +5,8 @@
-- Stability : stable
-- Portability : good
--
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.Blowfish
( Blowfish
, Blowfish64
@ -14,23 +15,29 @@ module Crypto.Cipher.Blowfish
, Blowfish448
) where
import Crypto.Internal.Imports
import Crypto.Cipher.Types
import Crypto.Cipher.Blowfish.Primitive
-- | variable keyed blowfish state
newtype Blowfish = Blowfish Context
deriving (NFData)
-- | 64 bit keyed blowfish state
newtype Blowfish64 = Blowfish64 Context
deriving (NFData)
-- | 128 bit keyed blowfish state
newtype Blowfish128 = Blowfish128 Context
deriving (NFData)
-- | 256 bit keyed blowfish state
newtype Blowfish256 = Blowfish256 Context
deriving (NFData)
-- | 448 bit keyed blowfish state
newtype Blowfish448 = Blowfish448 Context
deriving (NFData)
instance Cipher Blowfish where
cipherName _ = "blowfish"

View File

@ -18,12 +18,13 @@ module Crypto.Cipher.Blowfish.Primitive
, decrypt
) where
import Control.Monad (forM_, when)
import Control.Monad (when)
import Data.Bits
import Data.Word
import Crypto.Error
import Crypto.Internal.Compat
import Crypto.Internal.Imports
import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Words
@ -37,6 +38,9 @@ data Context = BF (Int -> Word32) -- p
(Int -> Word32) -- sbox2
(Int -> Word32) -- sbox2
instance NFData Context where
rnf (BF p a b c d) = p `seq` a `seq` b `seq` c `seq` d `seq` ()
-- | Encrypt blocks
--
-- Input need to be a multiple of 8 bytes

View File

@ -6,6 +6,7 @@
-- Portability : good
--
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.ChaCha
( initialize
, combine
@ -26,9 +27,11 @@ import Foreign.C.Types
-- | ChaCha context
newtype State = State ScrubbedBytes
deriving (NFData)
-- | ChaCha context for DRG purpose (see Crypto.Random.ChaChaDRG)
newtype StateSimple = StateSimple ScrubbedBytes -- just ChaCha's state
deriving (NFData)
-- | Initialize a new ChaCha context with the number of rounds,
-- the key and the nonce associated.

View File

@ -26,11 +26,12 @@ import Foreign.Ptr
import Crypto.Internal.ByteArray (ScrubbedBytes, ByteArray, ByteArrayAccess)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Compat
import Crypto.Internal.Compat
import Crypto.Internal.Imports
-- | The encryption state for RC4
newtype State = State ScrubbedBytes
deriving (ByteArrayAccess)
deriving (ByteArrayAccess,NFData)
-- | C Call for initializing the encryptor
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_init"

View File

@ -6,6 +6,7 @@
-- Portability : good
--
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.Salsa
( initialize
, combine
@ -22,6 +23,7 @@ import Foreign.C.Types
-- | Salsa context
newtype State = State ScrubbedBytes
deriving (NFData)
-- | Initialize a new Salsa context with the number of rounds,
-- the key and the nonce associated.

View File

@ -14,6 +14,7 @@ module Crypto.Hash.Types
, Digest(..)
) where
import Crypto.Internal.Imports
import Crypto.Internal.ByteArray (ByteArrayAccess, Bytes)
import qualified Crypto.Internal.ByteArray as B
import Data.Word
@ -47,11 +48,11 @@ hashContextGetAlgorithm = undefined
-- | Represent a context for a given hash algorithm.
newtype Context a = Context Bytes
deriving (ByteArrayAccess)
deriving (ByteArrayAccess,NFData)
-- | Represent a digest for a given hash algorithm.
newtype Digest a = Digest Bytes
deriving (Eq,ByteArrayAccess)
deriving (Eq,ByteArrayAccess,NFData)
instance Show (Digest a) where
show (Digest bs) = show (B.convertToBase B.Base16 bs :: Bytes)

View File

@ -0,0 +1,33 @@
-- |
-- Module : Crypto.Internal.DeepSeq
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : experimental
-- Portability : unknown
--
-- Simple abstraction module to allow compilation without deepseq
-- by defining our own NFData class if not compiling with deepseq
-- support.
--
{-# LANGUAGE CPP #-}
module Crypto.Internal.DeepSeq
( NFData(..)
) where
#ifdef WITH_DEEPSEQ_SUPPORT
import Control.DeepSeq
#else
import Data.Word
import Data.ByteArray
class NFData a where rnf :: a -> ()
instance NFData Word8 where rnf w = w `seq` ()
instance NFData Word16 where rnf w = w `seq` ()
instance NFData Word32 where rnf w = w `seq` ()
instance NFData Word64 where rnf w = w `seq` ()
instance NFData Bytes where rnf b = b `seq` ()
instance NFData ScrubbedBytes where rnf b = b `seq` ()
#endif

View File

@ -5,12 +5,12 @@
-- Stability : experimental
-- Portability : unknown
--
{-# LANGUAGE BangPatterns #-}
module Crypto.Internal.Imports
( module X
) where
import Data.Word as X
import Control.Applicative as X
import Control.Monad as X (forM, forM_, void)
import Control.Arrow as X (first, second)
import Data.Word as X
import Control.Applicative as X
import Control.Monad as X (forM, forM_, void)
import Control.Arrow as X (first, second)
import Crypto.Internal.DeepSeq as X

View File

@ -33,16 +33,16 @@ import qualified Crypto.Internal.ByteArray as B
-- | A Curve25519 Secret key
newtype SecretKey = SecretKey ScrubbedBytes
deriving (Show,Eq,ByteArrayAccess)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | A Curve25519 public key
newtype PublicKey = PublicKey Bytes
deriving (Show,Eq,ByteArrayAccess)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | A Curve25519 Diffie Hellman secret related to a
-- public key and a secret key.
newtype DhSecret = DhSecret ScrubbedBytes
deriving (Show,Eq,ByteArrayAccess)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | Try to build a public key from a bytearray
publicKey :: ByteArrayAccess bs => bs -> Either String PublicKey

View File

@ -35,6 +35,7 @@ import Crypto.Number.ModArithmetic (expFast, expSafe, inverse)
import Crypto.Number.Serialize
import Crypto.Number.Generate
import Crypto.Internal.ByteArray (ByteArrayAccess)
import Crypto.Internal.Imports
import Crypto.Hash
-- | DSA Public Number, usually embedded in DSA Public Key
@ -50,18 +51,27 @@ data Params = Params
, params_q :: Integer -- ^ DSA q
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData Params where
rnf (Params p g q) = p `seq` g `seq` q `seq` ()
-- | Represent a DSA signature namely R and S.
data Signature = Signature
{ sign_r :: Integer -- ^ DSA r
, sign_s :: Integer -- ^ DSA s
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData Signature where
rnf (Signature r s) = r `seq` s `seq` ()
-- | Represent a DSA public key.
data PublicKey = PublicKey
{ public_params :: Params -- ^ DSA parameters
, public_y :: PublicNumber -- ^ DSA public Y
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData PublicKey where
rnf (PublicKey params y) = y `seq` params `seq` ()
-- | Represent a DSA private key.
--
-- Only x need to be secret.
@ -71,10 +81,16 @@ data PrivateKey = PrivateKey
, private_x :: PrivateNumber -- ^ DSA private X
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData PrivateKey where
rnf (PrivateKey params x) = x `seq` params `seq` ()
-- | Represent a DSA key pair
data KeyPair = KeyPair Params PublicNumber PrivateNumber
deriving (Show,Read,Eq,Data,Typeable)
instance NFData KeyPair where
rnf (KeyPair params y x) = x `seq` y `seq` params `seq` ()
-- | Public key of a DSA Key pair
toPublicKey :: KeyPair -> PublicKey
toPublicKey (KeyPair params pub _) = PublicKey params pub

View File

@ -25,7 +25,8 @@ module Crypto.PubKey.ECC.Types
, getCurveByName
) where
import Data.Data
import Data.Data
import Crypto.Internal.Imports
-- | Define either a binary curve or a prime curve.
data Curve = CurveF2m CurveBinary -- ^ 𝔽(2^m)
@ -43,11 +44,18 @@ data Point = Point Integer Integer
| PointO -- ^ Point at Infinity
deriving (Show,Read,Eq,Data,Typeable)
instance NFData Point where
rnf (Point x y) = x `seq` y `seq` ()
rnf PointO = ()
-- | Define an elliptic curve in 𝔽(2^m).
-- The firt parameter is the Integer representatioin of the irreducible polynomial f(x).
data CurveBinary = CurveBinary Integer CurveCommon
deriving (Show,Read,Eq,Data,Typeable)
instance NFData CurveBinary where
rnf (CurveBinary i cc) = i `seq` cc `seq` ()
-- | Define an elliptic curve in 𝔽p.
-- The first parameter is the Prime Number.
data CurvePrime = CurvePrime Integer CurveCommon

View File

@ -35,15 +35,15 @@ import Crypto.Error
-- | An Ed25519 Secret key
newtype SecretKey = SecretKey ScrubbedBytes
deriving (Eq,ByteArrayAccess)
deriving (Eq,ByteArrayAccess,NFData)
-- | An Ed25519 public key
newtype PublicKey = PublicKey Bytes
deriving (Show,Eq,ByteArrayAccess)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | An Ed25519 signature
newtype Signature = Signature Bytes
deriving (Show,Eq,ByteArrayAccess)
deriving (Show,Eq,ByteArrayAccess,NFData)
-- | Try to build a public key from a bytearray
publicKey :: ByteArrayAccess ba => ba -> CryptoFailable PublicKey

View File

@ -11,6 +11,7 @@
-- TODO: provide a mapping between integer and ciphertext
-- generate numbers correctly
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.PubKey.ElGamal
( Params
, PublicNumber
@ -48,6 +49,7 @@ data Signature = Signature (Integer, Integer)
-- | ElGamal Ephemeral key. also called Temporary key.
newtype EphemeralKey = EphemeralKey Integer
deriving (NFData)
-- | generate a private number with no specific property
-- this number is usually called a and need to be between

View File

@ -6,6 +6,7 @@
-- Portability : Good
--
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.PubKey.RSA.Types
( Error(..)
, Blinder(..)
@ -20,6 +21,7 @@ module Crypto.PubKey.RSA.Types
) where
import Data.Data
import Crypto.Internal.Imports
-- | Blinder which is used to obfuscate the timing
-- of the decryption primitive (used by decryption and signing).
@ -42,6 +44,9 @@ data PublicKey = PublicKey
, public_e :: Integer -- ^ public exponant e
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData PublicKey where
rnf (PublicKey sz n e) = rnf n `seq` rnf e `seq` sz `seq` ()
-- | Represent a RSA private key.
--
-- Only the pub, d fields are mandatory to fill.
@ -62,6 +67,10 @@ data PrivateKey = PrivateKey
, private_qinv :: Integer -- ^ q^(-1) mod p
} deriving (Show,Read,Eq,Data,Typeable)
instance NFData PrivateKey where
rnf (PrivateKey pub d p q dp dq qinv) =
rnf pub `seq` rnf d `seq` rnf p `seq` rnf q `seq` rnf dp `seq` rnf dq `seq` qinv `seq` ()
-- | get the size in bytes from a private key
private_size :: PrivateKey -> Int
private_size = public_size . private_pub
@ -78,7 +87,7 @@ private_e = public_e . private_pub
--
-- note the RSA private key contains already an instance of public key for efficiency
newtype KeyPair = KeyPair PrivateKey
deriving (Show,Read,Eq,Data,Typeable)
deriving (Show,Read,Eq,Data,Typeable,NFData)
-- | Public key of a RSA KeyPair
toPublicKey :: KeyPair -> PublicKey

View File

@ -5,6 +5,7 @@
-- Stability : stable
-- Portability : good
--
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Random.ChaChaDRG
( ChaChaDRG
, initialize
@ -12,9 +13,9 @@ module Crypto.Random.ChaChaDRG
) where
import Crypto.Random.Types
import Crypto.Internal.Imports
import Crypto.Internal.ByteArray (ByteArray, ScrubbedBytes)
import qualified Crypto.Internal.ByteArray as B
import Data.Word
import Foreign.Storable (pokeElemOff)
import qualified Crypto.Cipher.ChaCha as C
@ -24,6 +25,7 @@ instance DRG ChaChaDRG where
-- | ChaCha Deterministic Random Generator
newtype ChaChaDRG = ChaChaDRG C.StateSimple
deriving (NFData)
-- | Initialize a new ChaCha context with the number of rounds,
-- the key and the nonce associated.

View File

@ -61,6 +61,11 @@ Flag integer-gmp
Default: True
Manual: True
Flag support_deepseq
Description: add deepseq instances for cryptographic types
Default: True
Manual: True
Library
Exposed-modules: Crypto.Cipher.AES
Crypto.Cipher.Blowfish
@ -147,6 +152,7 @@ Library
Crypto.Internal.ByteArray
Crypto.Internal.Compat
Crypto.Internal.CompatPrim
Crypto.Internal.DeepSeq
Crypto.Internal.Imports
Crypto.Internal.Words
Crypto.Internal.WordArray
@ -216,6 +222,10 @@ Library
if impl(ghc) && flag(integer-gmp)
Build-depends: integer-gmp
if flag(support_deepseq)
CPP-options: -DWITH_DEEPSEQ_SUPPORT
Build-depends: deepseq
Test-Suite test-cryptonite
type: exitcode-stdio-1.0
hs-source-dirs: tests