{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Data.Cuckoo.Internal
( w
, int
, fit
, intFit
, nextPowerOfTwo
, intNextPowerOfTwo
, set
, get
, sip
, fnv1a
, fnv1a_bytes
, sip_bytes
, sip2
) where
import Control.Monad.Primitive
import Data.Bits
import qualified Data.ByteArray as BA
import qualified Data.ByteArray.Hash as BA
import qualified Data.ByteArray.Pack as BA
import Data.Primitive.ByteArray
import Foreign
import GHC.Exts
import GHC.TypeLits
w :: forall (n :: Nat) . KnownNat n => Int
w = int $ natVal' @n proxy#
{-# INLINE w #-}
int :: Integral a => Num b => a -> b
int = fromIntegral
{-# INLINE int #-}
fit :: Real a => Real b => Integral c => a -> b -> c
fit a b = ceiling @Double $ realToFrac a / realToFrac b
{-# INLINE fit #-}
intFit :: Integral a => Integral b => a -> b -> a
intFit a b = 1 + (a - 1) `div` int b
{-# INLINE intFit #-}
nextPowerOfTwo :: Real a => Integral b => a -> b
nextPowerOfTwo x = 2 ^ ceiling @Double @Int (logBase 2 $ realToFrac x)
{-# INLINE nextPowerOfTwo #-}
intNextPowerOfTwo :: Int -> Int
intNextPowerOfTwo 0 = 1
intNextPowerOfTwo x = 1 `unsafeShiftL` (finiteBitSize x - countLeadingZeros (x - 1))
{-# INLINE intNextPowerOfTwo #-}
fnv1a
:: Storable a
=> Int
-> a
-> Word64
fnv1a s x = r
where
Right (BA.FnvHash64 r) = BA.fnv1a_64Hash
<$> BA.fill @BA.Bytes (8 + sizeOf x) (BA.putStorable s >> BA.putStorable x)
{-# INLINE fnv1a #-}
fnv1a_bytes
:: BA.ByteArrayAccess a
=> Int
-> a
-> Word64
fnv1a_bytes s x = r
where
Right (BA.FnvHash64 r) = BA.fnv1a_64Hash
<$> BA.fill @BA.Bytes (8 + BA.length x) (BA.putStorable s >> BA.putBytes x)
{-# INLINE fnv1a_bytes #-}
sip
:: Storable a
=> Int
-> a
-> Word64
sip s x = r
where
Right (BA.SipHash r) = BA.sipHash (BA.SipKey (int s) 914279)
<$> BA.fill @BA.Bytes (sizeOf x) (BA.putStorable x)
{-# INLINE sip #-}
sip_bytes
:: BA.ByteArrayAccess a
=> Int
-> a
-> Word64
sip_bytes s x = r
where
Right (BA.SipHash r) = BA.sipHash (BA.SipKey (int s) 1043639)
<$> BA.fill @BA.Bytes (BA.length x) (BA.putBytes x)
{-# INLINE sip_bytes #-}
sip2 :: Storable a => Int -> a -> Word64
sip2 s x = r
where
Right (BA.SipHash r) = BA.sipHash (BA.SipKey 994559 (int s * 713243))
<$> BA.fill @BA.Bytes (sizeOf x) (BA.putStorable x)
{-# INLINE sip2 #-}
set
:: PrimMonad m
=> MutableByteArray (PrimState m)
-> Int
-> Word64
-> m ()
set x i c = do
writeByteArray @Word32 x i (int c)
writeByteArray @Word32 x (succ i) (int $ c `unsafeShiftR` 32)
{-# INLINE set #-}
get
:: PrimMonad m
=> MutableByteArray (PrimState m)
-> Int
-> m Word64
get x i = do
a <- readByteArray @Word32 x i
b <- readByteArray @Word32 x (succ i)
return $! int a + (int b `unsafeShiftL` 32)
{-# INLINE get #-}