cuckoo-filter-0.2.0.2: Pure and impure Cuckoo Filter

Copyright(c) Chris Coffey 2018
LicenseMIT
Maintainerchris@foldl.io
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.CuckooFilter.Internal

Contents

Description

This is the internal API and implemntation of CuckooFilter. It is subject to change at any time and should not be used. Instead, use the exports from CuckooFilter.

Synopsis

Constructing a Cuckoo Filter

newtype Size Source #

A non-zero natural number. Generally this is a power of two, although there's no hard requirement for that given the current implementation.

Constructors

Size Natural 
Instances
Eq Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Ord Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Associated Types

type Rep Size :: Type -> Type #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

ToJSON Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

FromJSON Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Serialize Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

put :: Putter Size #

get :: Get Size #

type Rep Size Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep Size = D1 (MetaData "Size" "Data.CuckooFilter.Internal" "cuckoo-filter-0.2.0.2-B7QL3ZxFbHGZXnXJGf4MU" True) (C1 (MetaCons "Size" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

makeSize :: Natural -> Maybe Size Source #

Safely make a Size or fail if a 0 is provided.

class Monad m => CuckooFilter filt m where Source #

A low-level interface for working with cuckoo filter storage.

Methods

initialize :: Size -> m (filt a) Source #

Create a new cuckoo filter of the specified size

bucketCount :: filt a -> m Natural Source #

Return the number of buckets contained in the filter. This is distinct from the total size of the filter (size /4)

writeBucket :: Int -> Bucket -> filt a -> m (filt a) Source #

Write the new contents of a bucket to the storage

readBucket :: Int -> filt a -> m Bucket Source #

Read the contents of a bucket from the storage

Fingerprints

newtype FingerPrint Source #

A FingerPrint is an 8 bit hash of a value

Constructors

FP Word8 
Instances
Eq FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Ord FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Show FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Generic FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Associated Types

type Rep FingerPrint :: Type -> Type #

Hashable FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

ToJSON FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

FromJSON FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Serialize FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep FingerPrint Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep FingerPrint = D1 (MetaData "FingerPrint" "Data.CuckooFilter.Internal" "cuckoo-filter-0.2.0.2-B7QL3ZxFbHGZXnXJGf4MU" True) (C1 (MetaCons "FP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)))

makeFingerprint :: Hashable a => a -> FingerPrint Source #

hash a % 255. Fingerprints are 8 bits each, and completely opaque to the lookup algorithm.

Working with indices

newtype Bucket Source #

A Bucket is a statically sized list of four FingerPrints.

Constructors

B Word32 
Instances
Eq Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

(==) :: Bucket -> Bucket -> Bool #

(/=) :: Bucket -> Bucket -> Bool #

Ord Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Show Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Generic Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Associated Types

type Rep Bucket :: Type -> Type #

Methods

from :: Bucket -> Rep Bucket x #

to :: Rep Bucket x -> Bucket #

ToJSON Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

FromJSON Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Serialize Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep Bucket Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep Bucket = D1 (MetaData "Bucket" "Data.CuckooFilter.Internal" "cuckoo-filter-0.2.0.2-B7QL3ZxFbHGZXnXJGf4MU" True) (C1 (MetaCons "B" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

class Index a where Source #

Methods

toIndex :: Natural -> a -> Int Source #

Instances
Index IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

toIndex :: Natural -> IndexB -> Int Source #

Index IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

toIndex :: Natural -> IndexA -> Int Source #

newtype IndexA Source #

An Index represents the keys into buckets

Constructors

IA Word32 
Instances
Eq IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

(==) :: IndexA -> IndexA -> Bool #

(/=) :: IndexA -> IndexA -> Bool #

Ord IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Show IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Generic IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Associated Types

type Rep IndexA :: Type -> Type #

Methods

from :: IndexA -> Rep IndexA x #

to :: Rep IndexA x -> IndexA #

Hashable IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

hashWithSalt :: Int -> IndexA -> Int #

hash :: IndexA -> Int #

ToJSON IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

FromJSON IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Serialize IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Index IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

toIndex :: Natural -> IndexA -> Int Source #

type Rep IndexA Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep IndexA = D1 (MetaData "IndexA" "Data.CuckooFilter.Internal" "cuckoo-filter-0.2.0.2-B7QL3ZxFbHGZXnXJGf4MU" True) (C1 (MetaCons "IA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

newtype IndexB Source #

Constructors

IB Word32 
Instances
Eq IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

(==) :: IndexB -> IndexB -> Bool #

(/=) :: IndexB -> IndexB -> Bool #

Ord IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Show IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Generic IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Associated Types

type Rep IndexB :: Type -> Type #

Methods

from :: IndexB -> Rep IndexB x #

to :: Rep IndexB x -> IndexB #

Hashable IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

hashWithSalt :: Int -> IndexB -> Int #

hash :: IndexB -> Int #

ToJSON IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

FromJSON IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Serialize IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Index IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

Methods

toIndex :: Natural -> IndexB -> Int Source #

type Rep IndexB Source # 
Instance details

Defined in Data.CuckooFilter.Internal

type Rep IndexB = D1 (MetaData "IndexB" "Data.CuckooFilter.Internal" "cuckoo-filter-0.2.0.2-B7QL3ZxFbHGZXnXJGf4MU" True) (C1 (MetaCons "IB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

replaceInBucket Source #

Arguments

:: FingerPrint 
-> (FingerPrint -> Bucket -> (Bool, Bool, Bool, Bool))

Bucket predicate

-> Bucket 
-> (FingerPrint, Bucket) 

primaryIndex :: Hashable a => a -> Natural -> IndexA Source #

(hash a) % numBuckets

secondaryIndex :: FingerPrint -> Natural -> IndexA -> IndexB Source #

(indexA xor hash fp) % numBuckets

Bucket Cells,