bloomfilter-redis-0.1.0.4: Distributed bloom filters on Redis (using the Hedis client).

Safe HaskellTrustworthy
LanguageHaskell2010

Data.RedisBloom

Contents

Description

A bloom filter for the Redis in-memory store.

Synopsis

Bloom filter configuration

Fundamental types

newtype HashCount Source #

Number of hashes to use in a bloom filter.

Constructors

HashCount Int 
Instances
Bounded HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Enum HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Eq HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

(==) :: HashCount -> HashCount -> Bool

(/=) :: HashCount -> HashCount -> Bool

Integral HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Num HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Ord HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

compare :: HashCount -> HashCount -> Ordering

(<) :: HashCount -> HashCount -> Bool

(<=) :: HashCount -> HashCount -> Bool

(>) :: HashCount -> HashCount -> Bool

(>=) :: HashCount -> HashCount -> Bool

max :: HashCount -> HashCount -> HashCount

min :: HashCount -> HashCount -> HashCount

Real HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

toRational :: HashCount -> Rational

Show HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

showsPrec :: Int -> HashCount -> ShowS

show :: HashCount -> String

showList :: [HashCount] -> ShowS

Generic HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

Associated Types

type Rep HashCount :: Type -> Type

Methods

from :: HashCount -> Rep HashCount x

to :: Rep HashCount x -> HashCount

type Rep HashCount Source # 
Instance details

Defined in Data.RedisBloom.Internal

type Rep HashCount = D1 (MetaData "HashCount" "Data.RedisBloom.Internal" "bloomfilter-redis-0.1.0.4-inplace" True) (C1 (MetaCons "HashCount" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Capacity Source #

Capacity of a bloom filter.

Constructors

Capacity Int 
Instances
Enum Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Eq Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

(==) :: Capacity -> Capacity -> Bool

(/=) :: Capacity -> Capacity -> Bool

Integral Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Num Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Ord Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

compare :: Capacity -> Capacity -> Ordering

(<) :: Capacity -> Capacity -> Bool

(<=) :: Capacity -> Capacity -> Bool

(>) :: Capacity -> Capacity -> Bool

(>=) :: Capacity -> Capacity -> Bool

max :: Capacity -> Capacity -> Capacity

min :: Capacity -> Capacity -> Capacity

Real Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

toRational :: Capacity -> Rational

Show Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Methods

showsPrec :: Int -> Capacity -> ShowS

show :: Capacity -> String

showList :: [Capacity] -> ShowS

Generic Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

Associated Types

type Rep Capacity :: Type -> Type

Methods

from :: Capacity -> Rep Capacity x

to :: Rep Capacity x -> Capacity

type Rep Capacity Source # 
Instance details

Defined in Data.RedisBloom.Internal

type Rep Capacity = D1 (MetaData "Capacity" "Data.RedisBloom.Internal" "bloomfilter-redis-0.1.0.4-inplace" True) (C1 (MetaCons "Capacity" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

type Key = ByteString Source #

Redis Key

Static bloom filter configuration

data Bloom a Source #

Bloom filter static configuration. To use suggested values based on the desired false-positive rate and capacity, use suggestCreate.

Constructors

Bloom 

Fields

Bloom filter operations

createBF :: RedisCtx m (Either Reply) => Bloom a -> m (Either Reply Status) Source #

Create a new bloom filter with the specified configuration.

createIfNewBF :: RedisCtx m (Either Reply) => Bloom a -> m (Either Reply Bool) Source #

Create a new bloom filter with the specified configuration if the specified key does not yet exist.

addBF :: RedisCtx m f => Bloom a -> a -> m () Source #

Add an element to an existing bloom filter.

queryBF :: (MonadRedis m, RedisCtx m (Either Reply)) => Bloom a -> a -> m Bool Source #

Query whether an element exists in the bloom filter.

Gracefully fails upon failure by returning False.