module Crypto.Cipher.Types.GF
(
xtsGFMul
) where
import Crypto.Internal.Imports
import Crypto.Internal.ByteArray (ByteArray, withByteArray)
import qualified Crypto.Internal.ByteArray as B
import Foreign.Storable
import Foreign.Ptr
import Data.Bits
xtsGFMul :: ByteArray ba => ba -> ba
xtsGFMul b
| len == 16 =
B.allocAndFreeze len $ \dst ->
withByteArray b $ \src -> do
(hi,lo) <- gf <$> peek (castPtr src) <*> peek (castPtr src `plusPtr` 8)
poke (castPtr dst) lo
poke (castPtr dst `plusPtr` 8) hi
| otherwise = error "unsupported block size in GF"
where gf :: Word64 -> Word64 -> (Word64, Word64)
gf srcLo srcHi =
((if carryLo then (.|. 1) else id) (srcHi `shiftL` 1)
,(if carryHi then xor 0x87 else id) $ (srcLo `shiftL` 1)
)
where carryHi = srcHi `testBit` 63
carryLo = srcLo `testBit` 63
len = B.length b