module Crypto.ConstructHash.MiyaguchiPreneel
( compute, compute'
, MiyaguchiPreneel
) where
import Data.List (foldl')
import Crypto.Data.Padding (pad, Format (ZERO))
import Crypto.Cipher.Types
import Crypto.Error (throwCryptoError)
import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes)
import qualified Crypto.Internal.ByteArray as B
newtype MiyaguchiPreneel a = MP Bytes
deriving (ByteArrayAccess)
instance Eq (MiyaguchiPreneel a) where
MP b1 == MP b2 = B.constEq b1 b2
compute' :: (ByteArrayAccess bin, BlockCipher cipher)
=> (Bytes -> cipher)
-> bin
-> MiyaguchiPreneel cipher
compute' g = MP . foldl' (step $ g) (B.replicate bsz 0) . chunks . pad (ZERO bsz) . B.convert
where
bsz = blockSize ( g B.empty )
chunks msg
| B.null msg = []
| otherwise = (hd :: Bytes) : chunks tl
where
(hd, tl) = B.splitAt bsz msg
compute :: (ByteArrayAccess bin, BlockCipher cipher)
=> bin
-> MiyaguchiPreneel cipher
compute = compute' $ throwCryptoError . cipherInit
step :: (ByteArray ba, BlockCipher k)
=> (ba -> k)
-> ba
-> ba
-> ba
step g iv msg =
ecbEncrypt k msg `bxor` iv `bxor` msg
where
k = g iv
bxor :: ByteArray ba => ba -> ba -> ba
bxor = B.xor