Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
A bloom filter for the Redis in-memory store.
Synopsis
- newtype HashCount = HashCount Int
- newtype Capacity = Capacity Int
- type Key = ByteString
- data Bloom a = Bloom {}
- createBF :: RedisCtx m (Either Reply) => Bloom a -> m (Either Reply Status)
- createIfNewBF :: RedisCtx m (Either Reply) => Bloom a -> m (Either Reply Bool)
- addBF :: RedisCtx m f => Bloom a -> a -> m ()
- queryBF :: (MonadRedis m, RedisCtx m (Either Reply)) => Bloom a -> a -> m Bool
Bloom filter configuration
Fundamental types
Number of hashes to use in a bloom filter.
Instances
Bounded HashCount Source # | |
Enum HashCount Source # | |
Defined in Data.RedisBloom.Internal succ :: HashCount -> HashCount # pred :: HashCount -> HashCount # fromEnum :: HashCount -> Int # enumFrom :: HashCount -> [HashCount] # enumFromThen :: HashCount -> HashCount -> [HashCount] # enumFromTo :: HashCount -> HashCount -> [HashCount] # enumFromThenTo :: HashCount -> HashCount -> HashCount -> [HashCount] # | |
Eq HashCount Source # | |
Integral HashCount Source # | |
Defined in Data.RedisBloom.Internal | |
Num HashCount Source # | |
Defined in Data.RedisBloom.Internal | |
Ord HashCount Source # | |
Defined in Data.RedisBloom.Internal | |
Real HashCount Source # | |
Defined in Data.RedisBloom.Internal toRational :: HashCount -> Rational # | |
Show HashCount Source # | |
Generic HashCount Source # | |
type Rep HashCount Source # | |
Defined in Data.RedisBloom.Internal |
Capacity of a bloom filter.
Instances
Enum Capacity Source # | |
Defined in Data.RedisBloom.Internal | |
Eq Capacity Source # | |
Integral Capacity Source # | |
Defined in Data.RedisBloom.Internal | |
Num Capacity Source # | |
Ord Capacity Source # | |
Defined in Data.RedisBloom.Internal | |
Real Capacity Source # | |
Defined in Data.RedisBloom.Internal toRational :: Capacity -> Rational # | |
Show Capacity Source # | |
Generic Capacity Source # | |
type Rep Capacity Source # | |
Defined in Data.RedisBloom.Internal |
type Key = ByteString Source #
Redis Key
Static bloom filter configuration
Bloom filter static configuration.
To use suggested values based on the desired
false-positive rate and capacity, use suggestCreate
.
Bloom | |
|
Bloom filter operations
createBF :: RedisCtx m (Either Reply) => Bloom a -> m (Either Reply Status) Source #
Create a new bloom filter with the specified configuration.