-- |
-- 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           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

-- | Compute the gfmul with the XTS polynomial
--
-- block size need to be 128 bits.
--
-- FIXME: add support for big endian.
xtsGFMul :: ByteArray ba => ba -> ba
xtsGFMul :: ba -> ba
xtsGFMul ba
b
    | Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
16 =
        Int -> (Ptr Any -> IO ()) -> ba
forall a p. ByteArray a => Int -> (Ptr p -> IO ()) -> a
B.allocAndFreeze Int
len ((Ptr Any -> IO ()) -> ba) -> (Ptr Any -> IO ()) -> ba
forall a b. (a -> b) -> a -> b
$ \Ptr Any
dst ->
        ba -> (Ptr Any -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
withByteArray ba
b      ((Ptr Any -> IO ()) -> IO ()) -> (Ptr Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Any
src -> do
            (Word64
hi,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 Any -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
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 Any -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
src Ptr Any -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)
            Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Any -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
dst) Word64
lo
            Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Any -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
dst Ptr Any -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) Word64
hi
    | Bool
otherwise = [Char] -> ba
forall a. HasCallStack => [Char] -> a
error [Char]
"unsupported block size in GF"
  where gf :: Word64 -> Word64 -> (Word64, Word64)
        gf :: Word64 -> Word64 -> (Word64, Word64)
gf Word64
srcLo Word64
srcHi =
            ((if Bool
carryLo then (Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64
1) else Word64 -> Word64
forall a. a -> a
id) (Word64
srcHi Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
1)
            ,(if Bool
carryHi then Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
xor Word64
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` Int
1)
            )
          where carryHi :: Bool
carryHi = Word64
srcHi Word64 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
63 
                carryLo :: Bool
carryLo = Word64
srcLo Word64 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
63
        len :: Int
len = ba -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length ba
b
{-
	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;
-}