re-add ivAdd
This commit is contained in:
parent
6b70e270e1
commit
78d75b2ca2
@ -10,7 +10,6 @@
|
|||||||
{-# LANGUAGE ExistentialQuantification #-}
|
{-# LANGUAGE ExistentialQuantification #-}
|
||||||
module Crypto.Cipher.Types.Base
|
module Crypto.Cipher.Types.Base
|
||||||
( KeySizeSpecifier(..)
|
( KeySizeSpecifier(..)
|
||||||
, IV(..)
|
|
||||||
, Cipher(..)
|
, Cipher(..)
|
||||||
, AuthTag(..)
|
, AuthTag(..)
|
||||||
, AEADMode(..)
|
, AEADMode(..)
|
||||||
@ -35,11 +34,6 @@ data KeySizeSpecifier =
|
|||||||
-- | Offset inside an XTS data unit, measured in block size.
|
-- | Offset inside an XTS data unit, measured in block size.
|
||||||
type DataUnitOffset = Word32
|
type DataUnitOffset = Word32
|
||||||
|
|
||||||
-- | an IV parametrized by the cipher
|
|
||||||
data IV c = forall byteArray . ByteArray byteArray => IV byteArray
|
|
||||||
|
|
||||||
instance ByteArray (IV c) where
|
|
||||||
|
|
||||||
-- | Authentification Tag for AE cipher mode
|
-- | Authentification Tag for AE cipher mode
|
||||||
newtype AuthTag = AuthTag ByteString
|
newtype AuthTag = AuthTag ByteString
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|||||||
@ -15,7 +15,7 @@ module Crypto.Cipher.Types.Block
|
|||||||
-- * BlockCipher
|
-- * BlockCipher
|
||||||
BlockCipher(..)
|
BlockCipher(..)
|
||||||
-- * initialization vector (IV)
|
-- * initialization vector (IV)
|
||||||
, IV
|
, IV(..)
|
||||||
, makeIV
|
, makeIV
|
||||||
, nullIV
|
, nullIV
|
||||||
, ivAdd
|
, ivAdd
|
||||||
@ -45,6 +45,12 @@ import Crypto.Internal.ByteArray
|
|||||||
import Foreign.Ptr
|
import Foreign.Ptr
|
||||||
import Foreign.Storable
|
import Foreign.Storable
|
||||||
|
|
||||||
|
-- | an IV parametrized by the cipher
|
||||||
|
data IV c = forall byteArray . ByteArray byteArray => IV byteArray
|
||||||
|
|
||||||
|
instance BlockCipher c => ByteArray (IV c) where
|
||||||
|
|
||||||
|
|
||||||
type XTS cipher = (cipher, cipher)
|
type XTS cipher = (cipher, cipher)
|
||||||
-> IV cipher -- ^ Usually represent the Data Unit (e.g. disk sector)
|
-> IV cipher -- ^ Usually represent the Data Unit (e.g. disk sector)
|
||||||
-> DataUnitOffset -- ^ Offset in the data unit in number of blocks
|
-> DataUnitOffset -- ^ Offset in the data unit in number of blocks
|
||||||
@ -161,7 +167,26 @@ nullIV = toIV undefined
|
|||||||
--
|
--
|
||||||
-- Assume the IV is in Big Endian format.
|
-- Assume the IV is in Big Endian format.
|
||||||
ivAdd :: BlockCipher c => IV c -> Int -> IV c
|
ivAdd :: BlockCipher c => IV c -> Int -> IV c
|
||||||
ivAdd i _ = i
|
ivAdd (IV b) i = IV $ copy b
|
||||||
|
where copy :: ByteArray bs => bs -> bs
|
||||||
|
copy bs = byteArrayCopyAndFreeze bs $ \p -> do
|
||||||
|
let until0 accu = do
|
||||||
|
r <- loop accu (byteArrayLength bs - 1) p
|
||||||
|
case r of
|
||||||
|
0 -> return ()
|
||||||
|
_ -> until0 r
|
||||||
|
until0 i
|
||||||
|
|
||||||
|
loop :: Int -> Int -> Ptr Word8 -> IO Int
|
||||||
|
loop 0 _ _ = return 0
|
||||||
|
loop acc ofs p = do
|
||||||
|
v <- peek (p `plusPtr` ofs) :: IO Word8
|
||||||
|
let accv = acc + fromIntegral v
|
||||||
|
(hi,lo) = accv `divMod` 256
|
||||||
|
poke (p `plusPtr` ofs) (fromIntegral lo :: Word8)
|
||||||
|
if ofs == 0
|
||||||
|
then return hi
|
||||||
|
else loop hi (ofs - 1) p
|
||||||
{-
|
{-
|
||||||
ivAdd (IV b) i = IV $ snd $ B.mapAccumR addCarry i b
|
ivAdd (IV b) i = IV $ snd $ B.mapAccumR addCarry i b
|
||||||
where addCarry :: Int -> Word8 -> (Int, Word8)
|
where addCarry :: Int -> Word8 -> (Int, Word8)
|
||||||
|
|||||||
@ -14,6 +14,7 @@ module Crypto.Internal.ByteArray
|
|||||||
( ByteArray(..)
|
( ByteArray(..)
|
||||||
, byteArrayAllocAndFreeze
|
, byteArrayAllocAndFreeze
|
||||||
, empty
|
, empty
|
||||||
|
, byteArrayCopyAndFreeze
|
||||||
, byteArraySplit
|
, byteArraySplit
|
||||||
, byteArrayXor
|
, byteArrayXor
|
||||||
, byteArrayConcat
|
, byteArrayConcat
|
||||||
@ -99,3 +100,9 @@ byteArrayConcat allBs = byteArrayAllocAndFreeze total (loop allBs)
|
|||||||
let sz = byteArrayLength b
|
let sz = byteArrayLength b
|
||||||
withByteArray b $ \p -> bufCopy dst p sz
|
withByteArray b $ \p -> bufCopy dst p sz
|
||||||
loop bs (dst `plusPtr` sz)
|
loop bs (dst `plusPtr` sz)
|
||||||
|
|
||||||
|
byteArrayCopyAndFreeze :: ByteArray bs => bs -> (Ptr p -> IO ()) -> bs
|
||||||
|
byteArrayCopyAndFreeze bs f =
|
||||||
|
byteArrayAllocAndFreeze (byteArrayLength bs) $ \d -> do
|
||||||
|
withByteArray bs $ \s -> bufCopy d s (byteArrayLength bs)
|
||||||
|
f (castPtr d)
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user