{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- |
-- Module: Data.Cuckoo.Internal.HashFunctions
-- Copyright: Copyright © 2021 Lars Kuhtz <lakuhtz@gmail.com>
-- License: BSD3
-- Maintainer: Lars Kuhtz <lakuhtz@gmail.com>
-- Stability: experimental
--
module Data.Cuckoo.Internal.HashFunctions
(
-- * Salted Hash Functions
  saltedFnv1aPtr
, saltedFnv1aStorable
, saltedFnv1aByteString

-- ** Salted Sip Hash
, saltedSipHashPtr
, saltedSipHashStorable
, saltedSipHashByteString

-- * Internal Use Only
, sipHashInternal
) where

import qualified Data.ByteString as B
import Data.Hash.FNV1.Salted
import Data.Hash.SipHash

import Foreign

import Data.Cuckoo.Internal

-- -------------------------------------------------------------------------- --
-- FNV1a

-- | Computes a 64 bit Fnv1a hash for a value that is an instance of
-- 'BA.ByteArrayAccess'.
--
-- The first argument is use as a salt.
--
saltedFnv1aPtr
    :: Int
        -- ^ Salt
    -> Ptr Word8
        -- ^ Bytes that are hashed
    -> Int
        -- ^ Number of bytes
    -> IO Word64
saltedFnv1aPtr :: Int -> Ptr Word8 -> Int -> IO Word64
saltedFnv1aPtr Int
s Ptr Word8
p Int
l = do
    Fnv1a64Hash !Word64
h <- Salt Fnv1a64Hash -> Ptr Word8 -> Int -> IO Fnv1a64Hash
forall a. Hash a => Salt a -> Ptr Word8 -> Int -> IO a
hashPtr (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) Ptr Word8
p Int
l
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
h
{-# INLINE saltedFnv1aPtr #-}

-- | Computes a 64 bit Fnv1a hash for a value that has an 'Storable' instance.
--
-- The first argument is use as a salt.
--
saltedFnv1aStorable
    :: Storable a
    => Int
        -- ^ Salt
    -> a
        -- ^ Value that is hashed
    -> Word64
saltedFnv1aStorable :: Int -> a -> Word64
saltedFnv1aStorable Int
s a
b =
    let Fnv1a64Hash !Word64
h = Salt Fnv1a64Hash -> a -> Fnv1a64Hash
forall a b. (Hash a, Storable b) => Salt a -> b -> a
hashStorable (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) a
b in Word64
h
{-# INLINE saltedFnv1aStorable #-}

saltedFnv1aByteString
    :: Int
        -- ^ Salt
    -> B.ByteString
        -- ^ Bytes that are hashed
    -> Word64
saltedFnv1aByteString :: Int -> ByteString -> Word64
saltedFnv1aByteString Int
s ByteString
b =
    let Fnv1a64Hash !Word64
h = Salt Fnv1a64Hash -> ByteString -> Fnv1a64Hash
forall a. Hash a => Salt a -> ByteString -> a
hashByteString (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s) ByteString
b in Word64
h
{-# INLINE saltedFnv1aByteString #-}

-- -------------------------------------------------------------------------- --
-- Sip Hash

-- | Computes a Sip hash for a value that is represented as byte pointer.
--
-- The first argument is a salt value that is used to derive the key for the
-- hash computation.
--
saltedSipHashPtr
    :: Int
        -- ^ Salt
    -> Ptr Word8
        -- ^ Bytes that is hashed
    -> Int
        -- ^ Number of bytes
    -> IO Word64
saltedSipHashPtr :: Int -> Ptr Word8 -> Int -> IO Word64
saltedSipHashPtr Int
s Ptr Word8
ptr Int
l = do
    SipHash !Word64
h <- Salt (SipHash 2 4) -> Ptr Word8 -> Int -> IO (SipHash 2 4)
forall a. Hash a => Salt a -> Ptr Word8 -> Int -> IO a
hashPtr @(SipHash 2 4) (Word64 -> Word64 -> SipHashKey
SipHashKey (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
int Int
s) Word64
1043639) Ptr Word8
ptr Int
l
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
h
{-# INLINE saltedSipHashPtr #-}

-- | Computes a Sip hash for a value that has an 'Storable' instance.
--
-- The first argument is a salt value that is used to derive the key for the
-- hash computation.
--
saltedSipHashStorable
    :: Storable a
    => Int
        -- ^ Salt
    -> a
        -- ^ Value that is hashed
    -> Word64
saltedSipHashStorable :: Int -> a -> Word64
saltedSipHashStorable Int
s a
b =
    let SipHash !Word64
h = Salt (SipHash 2 4) -> a -> SipHash 2 4
forall a b. (Hash a, Storable b) => Salt a -> b -> a
hashStorable @(SipHash 2 4) (Word64 -> Word64 -> SipHashKey
SipHashKey (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
int Int
s) Word64
914279) a
b
    in Word64
h
{-# INLINE saltedSipHashStorable #-}

-- | Computes a Sip hash for a value that has an 'Storable' instance.
--
-- The first argument is a salt value that is used to derive the key for the
-- hash computation.
--
saltedSipHashByteString
    :: Int
        -- ^ Salt
    -> B.ByteString
        -- ^ Value that is hashed
    -> Word64
saltedSipHashByteString :: Int -> ByteString -> Word64
saltedSipHashByteString Int
s ByteString
b =
    let SipHash !Word64
h = Salt (SipHash 2 4) -> ByteString -> SipHash 2 4
forall a. Hash a => Salt a -> ByteString -> a
hashByteString @(SipHash 2 4) (Word64 -> Word64 -> SipHashKey
SipHashKey (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
int Int
s) Word64
914279) ByteString
b
    in Word64
h
{-# INLINE saltedSipHashByteString #-}

-- -------------------------------------------------------------------------- --
-- Interal Use Only (Do Not Use)

-- | An version of a Sip hash that is used only internally. In order to avoid
-- dependencies between different hash computations, it shouldn't be used in the
-- implementation of instances of 'Data.Cuckoo.CuckooFilterHash'.
--
sipHashInternal :: Storable a => Int -> a -> Word64
sipHashInternal :: Int -> a -> Word64
sipHashInternal Int
s a
b =
    let SipHash !Word64
h = Salt (SipHash 2 4) -> a -> SipHash 2 4
forall a b. (Hash a, Storable b) => Salt a -> b -> a
hashStorable @(SipHash 2 4) (Word64 -> Word64 -> SipHashKey
SipHashKey Word64
994559 (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
int Int
s Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
713243)) a
b
    in Word64
h
{-# INLINE sipHashInternal #-}