fix stuff
This commit is contained in:
parent
39ee0a4aa2
commit
279eebf2c6
@ -13,6 +13,7 @@ import Data.Word
|
||||
import Crypto.Error
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.DES.Primitive
|
||||
import Crypto.Cipher.DES.Serialization
|
||||
import Crypto.Internal.ByteArray
|
||||
|
||||
-- | DES Context
|
||||
@ -24,12 +25,10 @@ instance Cipher DES where
|
||||
cipherKeySize _ = KeySizeFixed 8
|
||||
cipherInit k = initDES k
|
||||
|
||||
{-
|
||||
instance BlockCipher DES where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES key) = unblockify . map (encrypt key) . blockify
|
||||
ecbDecrypt (DES key) = unblockify . map (decrypt key) . blockify
|
||||
-}
|
||||
|
||||
initDES :: ByteArray key => key -> CryptoFailable DES
|
||||
initDES k
|
||||
|
||||
@ -7,10 +7,8 @@
|
||||
--
|
||||
-- basic routine to convert between W64 and bytestring for DES.
|
||||
--
|
||||
{-# LANGUAGE CPP #-}
|
||||
module Crypto.Cipher.DES.Serialization
|
||||
( toW64
|
||||
, toBS
|
||||
( toBS
|
||||
, blockify
|
||||
, unblockify
|
||||
) where
|
||||
@ -18,17 +16,14 @@ module Crypto.Cipher.DES.Serialization
|
||||
import qualified Data.ByteString as B
|
||||
import Crypto.Cipher.DES.Primitive (Block(..))
|
||||
|
||||
#ifdef ARCH_IS_LITTLE_ENDIAN
|
||||
import Crypto.Internal.ByteArray
|
||||
import Crypto.Internal.Endian
|
||||
|
||||
import Data.Word (Word64)
|
||||
import Data.Byteable (withBytePtr)
|
||||
import qualified Data.ByteString.Internal as B (inlinePerformIO, unsafeCreate)
|
||||
import Foreign.Storable
|
||||
import Foreign.Ptr (castPtr, plusPtr, Ptr)
|
||||
import Data.Bits (shiftL, shiftR, (.|.), (.&.))
|
||||
#else
|
||||
import Data.Bits (shiftL, shiftR, (.|.))
|
||||
#endif
|
||||
|
||||
{-
|
||||
#ifdef ARCH_IS_LITTLE_ENDIAN
|
||||
-- | convert a 8 byte bytestring big endian to a host one
|
||||
toW64 :: B.ByteString -> Block
|
||||
@ -70,9 +65,30 @@ toBS (Block b) = B.pack $ map (shr b) [56,48,40,32,24,16,8,0]
|
||||
unblockify :: [Block] -> B.ByteString
|
||||
unblockify = B.concat . map toBS
|
||||
#endif
|
||||
-}
|
||||
|
||||
-- | create DES blocks from a strict bytestring
|
||||
blockify :: B.ByteString -> [Block]
|
||||
blockify :: ByteArrayAccess ba => ba -> [Block]
|
||||
blockify s
|
||||
| len `mod` 8 /= 0 = error "invalid block"
|
||||
| otherwise = loop 0
|
||||
where
|
||||
len = byteArrayLength s
|
||||
loop i
|
||||
| i == len = []
|
||||
| otherwise = Block (byteArrayToW64BE s i) : loop (i+8)
|
||||
|
||||
unblockify :: ByteArray ba => [Block] -> ba
|
||||
unblockify blocks = byteArrayAllocAndFreeze (nbBlocks * 8) $ \initPtr -> pokeTo (castPtr initPtr) blocks
|
||||
where nbBlocks = length blocks
|
||||
pokeTo :: Ptr Word64 -> [Block] -> IO ()
|
||||
pokeTo _ [] = return ()
|
||||
pokeTo ptr (Block x:xs) = poke ptr (toBE64 x) >> pokeTo (ptr `plusPtr` 8) xs
|
||||
|
||||
toBS :: Block -> B.ByteString
|
||||
toBS (Block w) = byteArrayAllocAndFreeze 8 $ \ptr -> poke (castPtr ptr) (toBE64 w)
|
||||
{-
|
||||
blockify s | B.null s = []
|
||||
| otherwise = let (s1,s2) = B.splitAt 8 s
|
||||
in toW64 s1:blockify s2
|
||||
-}
|
||||
|
||||
@ -12,12 +12,10 @@ module Crypto.Cipher.TripleDES
|
||||
) where
|
||||
|
||||
import Data.Word
|
||||
import Data.Byteable
|
||||
import qualified Data.ByteString as B
|
||||
|
||||
import Crypto.Error
|
||||
import Crypto.Internal.ByteArray
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.DES.Serialization
|
||||
import Crypto.Cipher.DES.Primitive
|
||||
|
||||
-- | 3DES with 3 different keys used all in the same direction
|
||||
@ -56,7 +54,6 @@ instance Cipher DES_EEE2 where
|
||||
cipherKeySize _ = KeySizeFixed 16
|
||||
cipherInit k = init2DES DES_EEE2 k
|
||||
|
||||
{-
|
||||
instance BlockCipher DES_EEE3 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EEE3 k1 k2 k3) = unblockify . map (encrypt k3 . encrypt k2 . encrypt k1) . blockify
|
||||
@ -76,7 +73,6 @@ instance BlockCipher DES_EDE2 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EDE2 k1 k2) = unblockify . map (encrypt k1 . decrypt k2 . encrypt k1) . blockify
|
||||
ecbDecrypt (DES_EDE2 k1 k2) = unblockify . map (decrypt k1 . encrypt k2 . decrypt k1) . blockify
|
||||
-}
|
||||
|
||||
init3DES :: ByteArray key => (Word64 -> Word64 -> Word64 -> a) -> key -> CryptoFailable a
|
||||
init3DES constr k
|
||||
|
||||
@ -37,7 +37,6 @@ import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Internal as B (unsafeCreate)
|
||||
import Data.Byteable
|
||||
import Data.Word
|
||||
import Data.Bits (shiftR)
|
||||
import Crypto.Cipher.Types.Base
|
||||
import Crypto.Cipher.Types.GF
|
||||
import Crypto.Cipher.Types.Utils
|
||||
@ -222,7 +221,7 @@ cfbEncryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -
|
||||
cfbEncryptGeneric cipher ivini input = byteArrayConcat $ doEnc ivini $ chunk (blockSize cipher) input
|
||||
where
|
||||
doEnc _ [] = []
|
||||
doEnc iv (i:is) =
|
||||
doEnc (IV iv) (i:is) =
|
||||
let o = byteArrayXor i $ ecbEncrypt cipher iv
|
||||
in o : doEnc (IV o) is
|
||||
|
||||
@ -230,15 +229,15 @@ cfbDecryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -
|
||||
cfbDecryptGeneric cipher ivini input = byteArrayConcat $ doDec ivini $ chunk (blockSize cipher) input
|
||||
where
|
||||
doDec _ [] = []
|
||||
doDec iv (i:is) =
|
||||
doDec (IV iv) (i:is) =
|
||||
let o = byteArrayXor i $ ecbEncrypt cipher iv
|
||||
in o : doDec (IV i) is
|
||||
|
||||
ctrCombineGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba
|
||||
ctrCombineGeneric cipher ivini input = byteArrayConcat $ doCnt ivini $ chunk (blockSize cipher) input
|
||||
where doCnt _ [] = []
|
||||
doCnt iv (i:is) =
|
||||
let ivEnc = ecbEncrypt cipher iv
|
||||
doCnt iv@(IV ivd) (i:is) =
|
||||
let ivEnc = ecbEncrypt cipher ivd
|
||||
in byteArrayXor i ivEnc : doCnt (ivAdd iv 1) is
|
||||
|
||||
{-
|
||||
|
||||
@ -29,6 +29,7 @@ import Data.Word
|
||||
import Data.SecureMem
|
||||
import Crypto.Internal.Memory
|
||||
import Crypto.Internal.Compat
|
||||
import Crypto.Internal.Endian
|
||||
import Crypto.Internal.Bytes (bufXor, bufCopy)
|
||||
import Foreign.Ptr
|
||||
import Foreign.Storable
|
||||
@ -124,9 +125,5 @@ byteArrayToBS bs = byteArrayCopyAndFreeze bs (\_ -> return ())
|
||||
byteArrayFromBS :: ByteArray bs => ByteString -> bs
|
||||
byteArrayFromBS bs = byteArrayCopyAndFreeze bs (\_ -> return ())
|
||||
|
||||
byteArrayToW64BE :: ByteArray bs => bs -> Int -> Word64
|
||||
byteArrayToW64BE :: ByteArrayAccess bs => bs -> Int -> Word64
|
||||
byteArrayToW64BE bs ofs = unsafeDoIO $ withByteArray bs $ \p -> fromBE64 <$> peek (p `plusPtr` ofs)
|
||||
|
||||
-- move me elsewhere. not working properly for big endian machine, as it should be id
|
||||
fromBE64 :: Word64 -> Word64
|
||||
fromBE64 = byteSwap64
|
||||
|
||||
@ -126,6 +126,7 @@ Library
|
||||
Crypto.Internal.Compat
|
||||
Crypto.Internal.Bytes
|
||||
Crypto.Internal.ByteArray
|
||||
Crypto.Internal.Endian
|
||||
Crypto.Internal.Memory
|
||||
Build-depends: base >= 4.3 && < 5
|
||||
, bytestring
|
||||
@ -160,6 +161,10 @@ Library
|
||||
, cbits/cryptonite_whirlpool.c
|
||||
, cbits/cryptonite_scrypt.c
|
||||
include-dirs: cbits
|
||||
|
||||
-- FIXME armel or mispel is also little endian.
|
||||
-- might be a good idea to also add a runtime autodetect mode.
|
||||
-- ARCH_ENDIAN_UNKNOWN
|
||||
if (arch(i386) || arch(x86_64))
|
||||
CPP-options: -DARCH_IS_LITTLE_ENDIAN
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user