-- |
-- Module      : Crypto.Cipher.Types.GF
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : Stable
-- Portability : Excellent
--
-- Slow Galois Field arithmetic for generic XTS and GCM implementation
--
module Crypto.Cipher.Types.GF
    (
    -- * XTS support
      xtsGFMul
    ) where

import Control.Applicative
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import Data.Byteable
import Foreign.Storable
import Foreign.Ptr
import Data.Word
import Data.Bits

-- block size need to be 128 bits.
--
-- FIXME: add support for big endian.
xtsGFMul :: ByteString -> ByteString
xtsGFMul :: ByteString -> ByteString
xtsGFMul b :: ByteString
b
    | ByteString -> Int
B.length ByteString
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 16 = Int -> (Ptr Word8 -> IO ()) -> ByteString
B.unsafeCreate (ByteString -> Int
B.length ByteString
b) ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \dst :: Ptr Word8
dst ->
                         ByteString -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. Byteable a => a -> (Ptr Word8 -> IO b) -> IO b
withBytePtr ByteString
b ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \src :: Ptr Word8
src -> do
                         (hi :: Word64
hi,lo :: Word64
lo) <- Word64 -> Word64 -> (Word64, Word64)
gf (Word64 -> Word64 -> (Word64, Word64))
-> IO Word64 -> IO (Word64 -> (Word64, Word64))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Word8 -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
src) IO (Word64 -> (Word64, Word64)) -> IO Word64 -> IO (Word64, Word64)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr Word8 -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
src Ptr Any -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8)
                         Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8 -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
dst) Word64
lo
                         Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8 -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
dst Ptr Any -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) Word64
hi
    | Bool
otherwise        = [Char] -> ByteString
forall a. HasCallStack => [Char] -> a
error "unsupported block size in GF"
  where gf :: Word64 -> Word64 -> (Word64, Word64)
        gf :: Word64 -> Word64 -> (Word64, Word64)
gf srcLo :: Word64
srcLo srcHi :: Word64
srcHi =
            ((if Bool
carryLo then (Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. 1) else Word64 -> Word64
forall a. a -> a
id) (Word64
srcHi Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` 1)
            ,(if Bool
carryHi then Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
xor 0x87 else Word64 -> Word64
forall a. a -> a
id) (Word64 -> Word64) -> Word64 -> Word64
forall a b. (a -> b) -> a -> b
$ (Word64
srcLo Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` 1)
            )
          where carryHi :: Bool
carryHi = Word64
srcHi Word64 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` 63 
                carryLo :: Bool
carryLo = Word64
srcLo Word64 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` 63
{-
	const uint64_t gf_mask = cpu_to_le64(0x8000000000000000ULL);
	uint64_t r = ((a->q[1] & gf_mask) ? cpu_to_le64(0x87) : 0);
	a->q[1] = cpu_to_le64((le64_to_cpu(a->q[1]) << 1) | (a->q[0] & gf_mask ? 1 : 0));
	a->q[0] = cpu_to_le64(le64_to_cpu(a->q[0]) << 1) ^ r;
-}