fix warnings

This commit is contained in:
Vincent Hanquez 2015-04-05 12:19:26 +01:00
parent ed4da5734b
commit 6eae9b0557
24 changed files with 83 additions and 119 deletions

View File

@ -20,7 +20,6 @@ module Crypto.Internal.ByteArray
import Data.SecureMem
import Crypto.Internal.Memory
import Crypto.Internal.Compat
import Crypto.Internal.Bytes
import Foreign.Ptr
import Foreign.ForeignPtr

View File

@ -21,14 +21,9 @@ module Crypto.Internal.Memory
, SecureBytes
) where
import Data.Word
import GHC.Types
import GHC.Prim
import GHC.Ptr
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Storable (pokeElemOff)
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils (copyBytes)
import Data.SecureMem (SecureMem)

View File

@ -46,9 +46,9 @@ generateBetween low high = (low +) <$> generateMax (high - low + 1)
-- the number of bits need to be multiple of 8. It will always returns
-- an integer that is close to 2^(1+bits/8) by setting the 2 highest bits to 1.
generateOfSize :: MonadRandom m => Int -> m Integer
generateOfSize bits = toInteger <$> getRandomBytes (bits `div` 8)
generateOfSize bits = unmarshall <$> getRandomBytes (bits `div` 8)
where
toInteger bs = os2ip $ snd $ B.mapAccumL (\acc w -> (0, w .|. acc)) 0xc0 bs
unmarshall bs = os2ip $ snd $ B.mapAccumL (\acc w -> (0, w .|. acc)) 0xc0 bs
-- | Generate a number with the specified number of bits
generateBits :: MonadRandom m => Int -> m Integer

View File

@ -23,7 +23,6 @@ module Crypto.PubKey.Curve25519
) where
import Control.Applicative
import Data.Bits
import Data.Byteable
import Data.ByteString (ByteString)
import Data.ByteString.Char8 ()
@ -31,7 +30,6 @@ import qualified Data.ByteString.Internal as B
import Data.SecureMem
import Data.Word
import Foreign.Ptr
import Foreign.Storable
import Crypto.Internal.Compat
@ -69,9 +67,9 @@ secretKey bs
-- e[31] &= 0x7f;
-- e[31] |= 40;
isValidPtr :: Ptr Word8 -> IO Bool
isValidPtr inp = do
b0 <- peekElemOff inp 0
b31 <- peekElemOff inp 31
isValidPtr _ = do
--b0 <- peekElemOff inp 0
--b31 <- peekElemOff inp 31
return True
{-
return $ and [ testBit b0 0 == False

View File

@ -20,6 +20,10 @@ module Crypto.PubKey.DSA
, signWith
-- * verification primitive
, verify
-- * Key pair
, KeyPair(..)
, toPublicKey
, toPrivateKey
) where
import Crypto.Random.Types

View File

@ -106,7 +106,7 @@ isPointValid (CurveFP (CurvePrime p cc)) (Point x y) =
b = ecc_b cc
eqModP z1 z2 = (z1 `mod` p) == (z2 `mod` p)
isValid e = e >= 0 && e < p
isPointValid curve@(CurveF2m (CurveBinary fx cc)) pt@(Point x y) =
isPointValid (CurveF2m (CurveBinary fx cc)) (Point x y) =
and [ isValid x
, isValid y
, ((((x `add` a) `mul` x `add` y) `mul` x) `add` b `add` (squareF2m fx y)) == 0

View File

@ -26,7 +26,6 @@ module Crypto.PubKey.ECC.Types
) where
import Data.Data
import Data.Tuple (swap)
-- | Define either a binary curve or a prime curve.
data Curve = CurveF2m CurveBinary -- ^ 𝔽(2^m)
@ -114,6 +113,7 @@ data CurveName =
| SEC_t571r1
deriving (Show,Read,Eq,Ord,Enum,Data,Typeable)
{-
curvesOIDs :: [ (CurveName, [Integer]) ]
curvesOIDs =
[ (SEC_p112r1, [1,3,132,0,6])
@ -150,6 +150,7 @@ curvesOIDs =
, (SEC_t571k1, [1,3,132,0,38])
, (SEC_t571r1, [1,3,132,0,39])
]
-}
-- | Get the curve definition associated with a recommended known curve name.
getCurveByName :: CurveName -> Curve

View File

@ -16,8 +16,6 @@ module Crypto.PubKey.RSA
, generateBlinder
) where
import Data.Bits
import Data.Word
import Control.Applicative
import Crypto.Random.Types
import Crypto.Number.ModArithmetic (inverse, inverseCoprimes)
@ -25,6 +23,7 @@ import Crypto.Number.Generate (generateMax)
import Crypto.Number.Prime (generatePrime)
import Crypto.PubKey.RSA.Types
{-
-- some bad implementation will not serialize ASN.1 integer properly, leading
-- to negative modulus.
-- TODO : Find a better place for this
@ -40,6 +39,7 @@ toPositive int
plusOne (x:xs) = if x == 0xff then 0 : plusOne xs else (x+1) : xs
bytesOfUInt x = reverse (list x)
where list i = if i <= 0xff then [fromIntegral i] else (fromIntegral i .&. 0xff) : list (i `shiftR` 8)
-}
-- | Generate a key pair given p and q.
--

View File

@ -22,7 +22,6 @@ import Data.ByteString (ByteString)
import Data.Byteable
import qualified Data.ByteString as B
import Crypto.PubKey.RSA.Prim
import Crypto.PubKey.RSA.Types
import Crypto.PubKey.RSA (generateBlinder)
import Crypto.PubKey.HashDescr
import Crypto.PubKey.MaskGenFunction

View File

@ -12,13 +12,14 @@ module Crypto.PubKey.RSA.Types
, PublicKey(..)
, PrivateKey(..)
, KeyPair(..)
, toPublicKey
, toPrivateKey
, private_size
, private_n
, private_e
) where
import Data.Data
import Data.Typeable
-- | Blinder which is used to obfuscate the timing
-- of the decryption primitive (used by decryption and signing).
@ -62,13 +63,16 @@ data PrivateKey = PrivateKey
} deriving (Show,Read,Eq,Data,Typeable)
-- | get the size in bytes from a private key
private_size :: PrivateKey -> Int
private_size = public_size . private_pub
-- | get n from a private key
private_n = public_n . private_pub
private_n :: PrivateKey -> Integer
private_n = public_n . private_pub
-- | get e from a private key
private_e = public_e . private_pub
private_e :: PrivateKey -> Integer
private_e = public_e . private_pub
-- | Represent RSA KeyPair
--
@ -83,4 +87,3 @@ toPublicKey (KeyPair priv) = private_pub priv
-- | Private key of a RSA KeyPair
toPrivateKey :: KeyPair -> PrivateKey
toPrivateKey (KeyPair priv) = priv

View File

@ -11,13 +11,10 @@ module BlockCipher
, testKatCTR
, testKatXTS
, testKatAEAD
, CipherInfo
) where
import Data.ByteString (ByteString)
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.HUnit
import Imports
type BlockSize = Int
type KeySize = Int
@ -74,7 +71,7 @@ data KAT_AEAD = KAT_AEAD
, aeadTag :: ByteString -- ^ expected tag
} deriving (Show,Eq)
testECB (blockSize, keySize, cipherInit) ecbEncrypt ecbDecrypt kats =
testECB (_, _, cipherInit) ecbEncrypt ecbDecrypt kats =
testGroup "ECB" (concatMap katTest (zip is kats) {- ++ propTests-})
where katTest (i,d) =
[ testCase ("E" ++ show i) (ecbEncrypt ctx (ecbPlaintext d) @?= ecbCiphertext d)

22
tests/Imports.hs Normal file
View File

@ -0,0 +1,22 @@
module Imports
(
-- * Individual Types
Word16, Word32, Word64
, ByteString
-- * Modules
, module X
) where
import Data.Word (Word16, Word32, Word64)
import Data.ByteString (ByteString)
import Control.Applicative as X
import Control.Monad as X
import Data.Foldable as X (foldl')
import Data.Monoid as X
import Data.ByteString.Char8 as X ()
import Test.Tasty as X
import Test.Tasty.HUnit as X
import Test.Tasty.QuickCheck as X hiding (vector)
import Utils as X

View File

@ -4,10 +4,6 @@ module KATHash
( tests
) where
import Data.Char (ord)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC ()
import qualified Crypto.Hash.MD2 as MD2
import qualified Crypto.Hash.MD4 as MD4
@ -26,11 +22,8 @@ import qualified Crypto.Hash.Skein256 as Skein256
import qualified Crypto.Hash.Skein512 as Skein512
import qualified Crypto.Hash.Whirlpool as Whirlpool
import Utils
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.HUnit
import qualified Data.ByteString as B
import Imports
v0,v1,v2 :: ByteString
v0 = ""

View File

@ -9,7 +9,6 @@ import Crypto.Hash
import Crypto.Random
import qualified Crypto.Data.AFIS as AFIS
import Data.ByteString (ByteString)
import Data.ByteString.Char8 ()
import qualified Data.ByteString as B

View File

@ -2,11 +2,10 @@
module KAT_Blowfish where
--import Crypto.Cipher.Blowfish
import Data.ByteString.Char8 () -- orphan IsString for older bytestring versions
--import Data.ByteString.Char8 () -- orphan IsString for older bytestring versions
import Imports
import BlockCipher
import Test.Tasty
vectors_ecb = -- key plaintext cipher
[ KAT_ECB "\x00\x00\x00\x00\x00\x00\x00\x00" "\x00\x00\x00\x00\x00\x00\x00\x00" "\x4E\xF9\x97\x45\x61\x98\xDD\x78"
, KAT_ECB "\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF" "\xFF\xFF\xFF\xFF\xFF\xFF\xFF\xFF" "\x51\x86\x6F\xD5\xB8\x5E\xCB\x8A"

View File

@ -3,10 +3,7 @@ module KAT_Curve25519 ( tests ) where
import qualified Crypto.PubKey.Curve25519 as Curve25519
import Data.Byteable
import Data.ByteString (ByteString)
import Test.Tasty
import Test.Tasty.HUnit
import Imports
alicePrivate = either error id $ Curve25519.secretKey ("\x77\x07\x6d\x0a\x73\x18\xa5\x7d\x3c\x16\xc1\x72\x51\xb2\x66\x45\xdf\x4c\x2f\x87\xeb\xc0\x99\x2a\xb1\x77\xfb\xa5\x1d\xb9\x2c\x2a" :: ByteString)
alicePublic = either error id $ Curve25519.publicKey ("\x85\x20\xf0\x09\x89\x30\xa7\x54\x74\x8b\x7d\xdc\xb4\x3e\xf7\x5a\x0d\xbf\x3a\x0d\x26\x38\x1a\xf4\xeb\xa4\xa9\x8e\xaa\x9b\x4e\x6a" :: ByteString)

View File

@ -6,20 +6,10 @@ import Crypto.Hash (MD5(..), SHA1(..), SHA256(..)
, Kekkak_224(..), Kekkak_256(..), Kekkak_384(..), Kekkak_512(..)
, SHA3_224(..), SHA3_256(..), SHA3_384(..), SHA3_512(..)
, HashAlgorithm, digestFromByteString)
import Control.Applicative ((<$>))
import Control.Monad (replicateM)
import Data.Char
import Data.Bits
import Data.Word
import Data.ByteString (ByteString)
import Data.Byteable
import Data.Foldable (foldl')
import Data.Monoid (mconcat)
--import Data.Foldable (foldl')
import qualified Data.ByteString as B
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.HUnit
import Imports
data MACVector hash = MACVector
{ macKey :: ByteString
@ -33,11 +23,8 @@ instance Show (HMAC.HMAC a) where
digest :: HashAlgorithm hash => ByteString -> HMAC.HMAC hash
digest = maybe (error "cannot get digest") HMAC.HMAC . digestFromByteString
v0,v1,v2 :: ByteString
v0 = ""
v1 :: ByteString
v1 = "The quick brown fox jumps over the lazy dog"
v2 = "The quick brown fox jumps over the lazy cog"
vectors = [ v0, v1, v2 ]
md5MACVectors :: [MACVector MD5]
md5MACVectors =

View File

@ -1,15 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
module KAT_PubKey.DSA (dsaTests) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Crypto.PubKey.DSA as DSA
import qualified Crypto.Hash.SHA1 as SHA1
import Test.Tasty
import Test.Tasty.HUnit
import Imports
data VectorDSA = VectorDSA
{ pgq :: DSA.Params
@ -141,7 +136,7 @@ doVerifyTest (i, vector) = testCase (show i) (True @=? actual)
dsaTests = testGroup "DSA"
[ testGroup "SHA1"
[ testGroup "signature" $ map doSignatureTest (zip [0..] vectorsSHA1)
, testGroup "verify" $ map doVerifyTest (zip [0..] vectorsSHA1)
[ testGroup "signature" $ map doSignatureTest (zip [katZero..] vectorsSHA1)
, testGroup "verify" $ map doVerifyTest (zip [katZero..] vectorsSHA1)
]
]

View File

@ -2,9 +2,6 @@
module KAT_PubKey.ECC (eccTests, eccKatTests) where
import Control.Arrow (second)
import Control.Applicative
import Data.ByteString (ByteString)
import Crypto.Number.Serialize
import qualified Crypto.PubKey.ECC.Types as ECC
import qualified Crypto.PubKey.ECC.Prim as ECC
@ -12,9 +9,7 @@ import qualified Crypto.PubKey.ECC.Prim as ECC
import Test.Tasty.KAT
import Test.Tasty.KAT.FileLoader
import Test.Tasty
import Test.Tasty.HUnit
import Imports
data VectorPoint = VectorPoint
{ curve :: ECC.Curve
@ -107,13 +102,13 @@ vectorsPoint =
doPointValidTest (i, vector) = testCase (show i) (valid vector @=? ECC.isPointValid (curve vector) (ECC.Point (x vector) (y vector)))
eccTests = testGroup "ECC"
[ testGroup "valid-point" $ map doPointValidTest (zip [0..] vectorsPoint)
[ testGroup "valid-point" $ map doPointValidTest (zip [katZero..] vectorsPoint)
]
eccKatTests = do
res <- testKatLoad "KATs/ECC-PKV.txt" (map (second (map toVector)) . katLoaderSimple)
return $ testKatDetailed {-Grouped-} "ECC/valid-point" res (\g vect -> do
let c = ECC.getCurveByName <$> case g of
let mCurve = ECC.getCurveByName <$> case g of
"P-192" -> Just ECC.SEC_p192r1
"P-224" -> Just ECC.SEC_p224r1
"P-256" -> Just ECC.SEC_p256r1
@ -133,13 +128,14 @@ eccKatTests = do
"K-409" -> Just ECC.SEC_t409k1
"K-571" -> Just ECC.SEC_t571k1
-}
case c of
Nothing -> return True
Just curve -> do
return (ECC.isPointValid curve (ECC.Point (x vect) (y vect)) == valid vect)
case mCurve of
Nothing -> return True
Just c -> do
return (ECC.isPointValid c (ECC.Point (x vect) (y vect)) == valid vect)
)
where toVector kvs =
case sequence $ map (flip lookup kvs) [ "Qx", "Qy", "Result" ] of
Just [qx,qy,res] -> VectorPoint undefined (valueHexInteger qx) (valueHexInteger qy) (head res /= 'F')
Nothing -> error ("ERROR CRAP: " ++ show kvs) -- VectorPoint undefined 0 0 True
Just _ -> error ("ERROR: " ++ show kvs)
Nothing -> error ("ERROR: " ++ show kvs) -- VectorPoint undefined 0 0 True

View File

@ -2,16 +2,13 @@
{-# LANGUAGE OverloadedStrings #-}
module KAT_PubKey.ECDSA (ecdsaTests) where
import Data.ByteString (ByteString)
import Crypto.Number.Serialize
import qualified Crypto.PubKey.ECC.ECDSA as ECDSA
import qualified Crypto.PubKey.ECC.Types as ECC
import qualified Crypto.Hash.SHA1 as SHA1
import Test.Tasty.HUnit
import Test.Tasty
import Imports
data VectorECDSA = VectorECDSA
{ curve :: ECC.Curve
@ -89,7 +86,7 @@ doVerifyTest (i, vector) = testCase (show i) (True @=? actual)
ecdsaTests = testGroup "ECDSA"
[ testGroup "SHA1"
[ testGroup "signature" $ map doSignatureTest (zip [0..] vectorsSHA1)
, testGroup "verify" $ map doVerifyTest (zip [0..] vectorsSHA1)
[ testGroup "signature" $ map doSignatureTest (zip [katZero..] vectorsSHA1)
, testGroup "verify" $ map doVerifyTest (zip [katZero..] vectorsSHA1)
]
]

View File

@ -1,17 +1,11 @@
{-# LANGUAGE OverloadedStrings #-}
module KAT_PubKey.OAEP (oaepTests) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Crypto.PubKey.RSA
import Crypto.PubKey.MaskGenFunction
import qualified Crypto.PubKey.RSA.OAEP as OAEP
import qualified Crypto.Hash.SHA1 as SHA1
import Test.Tasty
import Test.Tasty.HUnit
import Imports
rsaKeyInt = PrivateKey
{ private_pub = PublicKey
@ -87,18 +81,17 @@ vectorsKey1 =
}
]
doEncryptionTest key (i, vec) = testCase (show i) (Right (cipherText vec) @=? actual)
where actual = OAEP.encryptWithSeed (seed vec) (OAEP.defaultOAEPParams SHA1.hash) key (message vec)
doEncryptionTest key (i, vector) = testCase (show i) (Right (cipherText vector) @=? actual)
where actual = OAEP.encryptWithSeed (seed vector) (OAEP.defaultOAEPParams SHA1.hash) key (message vector)
doDecryptionTest key (i, vector) = testCase (show i) (Right (message vector) @=? actual)
where actual = OAEP.decrypt Nothing (OAEP.defaultOAEPParams SHA1.hash) key (cipherText vector)
doDecryptionTest key (i, vec) = testCase (show i) (Right (message vec) @=? actual)
where actual = OAEP.decrypt Nothing (OAEP.defaultOAEPParams SHA1.hash) key (cipherText vec)
oaepTests = testGroup "RSA-OAEP"
[ testGroup "internal"
[ doEncryptionTest (private_pub rsaKeyInt) (0, vectorInt)
, doDecryptionTest rsaKeyInt (0, vectorInt)
[ doEncryptionTest (private_pub rsaKeyInt) (0 :: Int, vectorInt)
, doDecryptionTest rsaKeyInt (0 :: Int, vectorInt)
]
, testGroup "encryption key 1024 bits" $ map (doEncryptionTest $ private_pub rsaKey1) (zip [0..] vectorsKey1)
, testGroup "decryption key 1024 bits" $ map (doDecryptionTest rsaKey1) (zip [0..] vectorsKey1)
, testGroup "encryption key 1024 bits" $ map (doEncryptionTest $ private_pub rsaKey1) (zip [katZero..] vectorsKey1)
, testGroup "decryption key 1024 bits" $ map (doDecryptionTest rsaKey1) (zip [katZero..] vectorsKey1)
]

View File

@ -1,17 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
module KAT_PubKey.PSS (pssTests) where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Crypto.PubKey.RSA
import Crypto.PubKey.MaskGenFunction
import qualified Crypto.PubKey.RSA.PSS as PSS
import qualified Crypto.Hash.SHA1 as SHA1
import Test.Tasty
import Test.Tasty.HUnit
import Imports
data VectorPSS = VectorPSS { message :: ByteString
, salt :: ByteString
@ -472,9 +465,9 @@ doVerifyTest key (i, vector) = testCase (show i) (True @=? actual)
pssTests = testGroup "RSA-PSS"
[ testGroup "signature internal"
[ doSignTest rsaKeyInt (0, vectorInt) ]
[ doSignTest rsaKeyInt (katZero, vectorInt) ]
, testGroup "verify internal"
[ doVerifyTest rsaKeyInt (0, vectorInt) ]
, testGroup "signature key 1024" $ map (doSignTest rsaKey1) (zip [0..] vectorsKey1)
, testGroup "verify key 1024" $ map (doVerifyTest rsaKey1) (zip [0..] vectorsKey1)
[ doVerifyTest rsaKeyInt (katZero, vectorInt) ]
, testGroup "signature key 1024" $ map (doSignTest rsaKey1) (zip [katZero..] vectorsKey1)
, testGroup "verify key 1024" $ map (doVerifyTest rsaKey1) (zip [katZero..] vectorsKey1)
]

View File

@ -24,7 +24,6 @@ import qualified KAT_Scrypt
import qualified KAT_RC4
import qualified KAT_Blowfish
import qualified KAT_AFIS
import qualified BlockCipher
b8_128_k0_i0 = "\xe2\x8a\x5f\xa4\xa6\x7f\x8c\x5d\xef\xed\x3e\x6f\xb7\x30\x34\x86\xaa\x84\x27\xd3\x14\x19\xa7\x29\x57\x2d\x77\x79\x53\x49\x11\x20\xb6\x4a\xb8\xe7\x2b\x8d\xeb\x85\xcd\x6a\xea\x7c\xb6\x08\x9a\x10\x18\x24\xbe\xeb\x08\x81\x4a\x42\x8a\xab\x1f\xa2\xc8\x16\x08\x1b\x8a\x26\xaf\x44\x8a\x1b\xa9\x06\x36\x8f\xd8\xc8\x38\x31\xc1\x8c\xec\x8c\xed\x81\x1a\x02\x8e\x67\x5b\x8d\x2b\xe8\xfc\xe0\x81\x16\x5c\xea\xe9\xf1\xd1\xb7\xa9\x75\x49\x77\x49\x48\x05\x69\xce\xb8\x3d\xe6\xa0\xa5\x87\xd4\x98\x4f\x19\x92\x5f\x5d\x33\x8e\x43\x0d"

View File

@ -1,9 +1,7 @@
module Utils where
import Data.Char
import Data.Word
import Data.ByteString (ByteString)
import Data.Monoid (mconcat)
import qualified Data.ByteString as B
katZero :: Int