{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Safe #-}
module Data.RedisBloom.Suggestions
(
suggestCapacity, suggestHashCount,
suggestCreate
)
where
import Data.Hashable (Hashable)
import Data.RedisBloom
import Data.RedisBloom.Hash
suggestCapacity :: forall a b. (Integral a, RealFrac b, Floating b)
=> a
-> b
-> Capacity
suggestCapacity n p = ceiling g
where
n' = fromIntegral n
x = n' * log p
tw = 2 :: b
y = recip $ tw ** log tw
g = x / log y :: b
suggestHashCount :: forall a. (Integral a)
=> a
-> Capacity
-> HashCount
suggestHashCount n m = HashCount . round $ log tw * (fromIntegral m / fromIntegral n)
where
tw = 2 :: Double
suggestCreate :: (Integral a, RealFrac b, Floating b, Hashable d)
=> a
-> b
-> Key
-> Bloom d
suggestCreate n p k = Bloom k ca haff
where
ca = suggestCapacity n p
hc = suggestHashCount n ca
haff = hashFamilyFNV1a hc