hyperloglog-0.5: An approximate streaming (constant space) unique object counter
Copyright(c) Edward Kmett 2013-2015
LicenseBSD3
MaintainerEdward Kmett <[email protected]>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HyperLogLog

Contents

Description

Synopsis

HyperLogLog

data HyperLogLog s p Source #

Initialize a new counter:

>>> runHyperLogLog (mempty :: DefaultHyperLogLog 3) == V.fromList [0,0,0,0,0,0,0,0]
True

Please note how you specify a counter size with the n invocation. Sizes of up to 16 are valid, with 7 being a likely good minimum for decent accuracy.

Let's count a list of unique items and get the latest estimate:

>>> size (foldr insert mempty [1..10] :: DefaultHyperLogLog 4)
Approximate {_confidence = 0.9972, _lo = 2, _estimate = 9, _hi = 17}

Note how insert can be used to add new observations to the approximate counter.

The s type parameter configures the SipKey that is passed to the hash function when inserting a new value. Note that if cryptographic security is a primary consideration, it is recommended that you create HyperLogLog values using generateHyperLogLog so that the SipKey is randomly generated using system entropy. In contrast, the HyperLogLog data constructor and the mempty method allow constructing HyperLogLog values with fixed SipKeys, which can result in exponentially inaccurate estimates if exploited by an adversary. (See https://eprint.iacr.org/2021/1139.)

Instances

Instances details
HasHyperLogLog (HyperLogLog s p) (s :: k1) (p :: k2) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Reifies p Integer => Monoid (HyperLogLog s p) Source #

The Monoid instance "should" just work. Give me two estimators and I can give you an estimator for the union set of the two.

Note that using mempty permits the s type parameter to be a fixed SipKey, which can have cryptographic security implications. See the Haddocks for HyperLogLog for more details.

Instance details

Defined in Data.HyperLogLog.Type

Methods

mempty :: HyperLogLog s p #

mappend :: HyperLogLog s p -> HyperLogLog s p -> HyperLogLog s p #

mconcat :: [HyperLogLog s p] -> HyperLogLog s p #

Semigroup (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

(<>) :: HyperLogLog s p -> HyperLogLog s p -> HyperLogLog s p #

sconcat :: NonEmpty (HyperLogLog s p) -> HyperLogLog s p #

stimes :: Integral b => b -> HyperLogLog s p -> HyperLogLog s p #

Generic (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Associated Types

type Rep (HyperLogLog s p) :: Type -> Type #

Methods

from :: HyperLogLog s p -> Rep (HyperLogLog s p) x #

to :: Rep (HyperLogLog s p) x -> HyperLogLog s p #

Show (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

showsPrec :: Int -> HyperLogLog s p -> ShowS #

show :: HyperLogLog s p -> String #

showList :: [HyperLogLog s p] -> ShowS #

Binary (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

put :: HyperLogLog s p -> Put #

get :: Get (HyperLogLog s p) #

putList :: [HyperLogLog s p] -> Put #

Serial (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

serialize :: MonadPut m => HyperLogLog s p -> m () #

deserialize :: MonadGet m => m (HyperLogLog s p) #

Serialize (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

put :: Putter (HyperLogLog s p) #

get :: Get (HyperLogLog s p) #

NFData (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

rnf :: HyperLogLog s p -> () #

Eq (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

Methods

(==) :: HyperLogLog s p -> HyperLogLog s p -> Bool #

(/=) :: HyperLogLog s p -> HyperLogLog s p -> Bool #

type Rep (HyperLogLog s p) Source # 
Instance details

Defined in Data.HyperLogLog.Type

type Rep (HyperLogLog s p) = D1 ('MetaData "HyperLogLog" "Data.HyperLogLog.Type" "hyperloglog-0.5-GLIkAycmUmjIt8AcGSsiYs" 'True) (C1 ('MetaCons "HyperLogLog" 'PrefixI 'True) (S1 ('MetaSel ('Just "runHyperLogLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Rank))))

class HasHyperLogLog a s p | a -> s p where Source #

Instances

Instances details
HasHyperLogLog (HyperLogLog s p) (s :: k1) (p :: k2) Source # 
Instance details

Defined in Data.HyperLogLog.Type

size :: Reifies p Integer => HyperLogLog s p -> Approximate Int64 Source #

Approximate size of our set

insert :: forall s p a. (Reifies s SipKey, Reifies p Integer, Serial a) => a -> HyperLogLog s p -> HyperLogLog s p Source #

insertHash :: Reifies p Integer => Word32 -> HyperLogLog s p -> HyperLogLog s p Source #

Insert a value that has already been hashed by whatever user defined hash function you want.

cast :: forall p q s. (Reifies p Integer, Reifies q Integer) => HyperLogLog s p -> Maybe (HyperLogLog s q) Source #

coerceConfig :: forall p q r s. (Reifies p Integer, Reifies q Integer, Reifies r SipKey, Reifies s SipKey) => Maybe (Coercion (HyperLogLog r p) (HyperLogLog s q)) Source #

If the two types p and q reify the same configuration, and if the two types r and s reify the same SipKey, then we can coerce between HyperLogLog r p and HyperLogLog s q. We do this by building a hole in the nominal role for the configuration parameter.