module Foundation.Hashing.Hasher
    ( Hasher(..)
    ) where
import           Basement.Compat.Base
import           Basement.IntegralConv
import           Foundation.Array (UArray)
import qualified Basement.UArray as A
import           Data.Bits
class Hasher st where
    {-# MINIMAL hashNew, hashNewParam, hashMix8, hashEnd #-}
    
    type HashResult st
    
    type HashInitParam st
    
    hashNew :: st
    
    hashNewParam :: HashInitParam st -> st
    
    hashEnd :: st -> HashResult st
    
    hashMix8  :: Word8  -> st -> st
    
    hashMix16 :: Word16 -> st -> st
    hashMix16 Word16
w st
st = forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w2 forall a b. (a -> b) -> a -> b
$ forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w1 st
st
      where
        !w1 :: Word8
w1 = forall a b. IntegralDownsize a b => a -> b
integralDownsize (Word16
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
8)
        !w2 :: Word8
w2 = forall a b. IntegralDownsize a b => a -> b
integralDownsize Word16
w
    
    hashMix32 :: Word32 -> st -> st
    hashMix32 Word32
w st
st = forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w4 forall a b. (a -> b) -> a -> b
$ forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w3 forall a b. (a -> b) -> a -> b
$ forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w2 forall a b. (a -> b) -> a -> b
$ forall st. Hasher st => Word8 -> st -> st
hashMix8 Word8
w1 st
st
      where
        !w1 :: Word8
w1 = forall a b. IntegralDownsize a b => a -> b
integralDownsize (Word32
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
24)
        !w2 :: Word8
w2 = forall a b. IntegralDownsize a b => a -> b
integralDownsize (Word32
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
16)
        !w3 :: Word8
w3 = forall a b. IntegralDownsize a b => a -> b
integralDownsize (Word32
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
8)
        !w4 :: Word8
w4 = forall a b. IntegralDownsize a b => a -> b
integralDownsize Word32
w
    
    hashMix64 :: Word64 -> st -> st
    hashMix64 Word64
w st
st = forall st. Hasher st => Word32 -> st -> st
hashMix32 Word32
w2 forall a b. (a -> b) -> a -> b
$ forall st. Hasher st => Word32 -> st -> st
hashMix32 Word32
w1 st
st
      where
        !w1 :: Word32
w1 = forall a b. IntegralDownsize a b => a -> b
integralDownsize (Word64
w forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
32)
        !w2 :: Word32
w2 = forall a b. IntegralDownsize a b => a -> b
integralDownsize Word64
w
    
    hashMixBytes :: A.PrimType e => UArray e -> st -> st
    hashMixBytes UArray e
ba st
st = forall ty a. PrimType ty => (a -> ty -> a) -> a -> UArray ty -> a
A.foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall st. Hasher st => Word8 -> st -> st
hashMix8) st
st (forall a b. (PrimType a, PrimType b) => UArray a -> UArray b
A.unsafeRecast UArray e
ba)