| Copyright | (c) Edward Kmett 2013-2015 |
|---|---|
| License | BSD3 |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell98 |
Data.HyperLogLog.Type
Contents
Description
This package provides an approximate streaming (constant space) unique object counter.
See the original paper for details: http://algo.inria.fr/flajolet/Publications/FlFuGaMe07.pdf
- newtype HyperLogLog p = HyperLogLog {}
- class HasHyperLogLog a p | a -> p where
- size :: Reifies p Integer => HyperLogLog p -> Approximate Int64
- insert :: (Reifies s Integer, Serial a) => a -> HyperLogLog s -> HyperLogLog s
- insertHash :: Reifies s Integer => Word32 -> HyperLogLog s -> HyperLogLog s
- intersectionSize :: Reifies p Integer => [HyperLogLog p] -> Approximate Int64
- cast :: forall p q. (Reifies p Integer, Reifies q Integer) => HyperLogLog p -> Maybe (HyperLogLog q)
- coerceConfig :: forall p q. (Reifies p Integer, Reifies q Integer) => Maybe (Coercion (HyperLogLog p) (HyperLogLog q))
HyperLogLog
newtype HyperLogLog p Source #
Initialize a new counter:
>>>runHyperLogLog (mempty :: HyperLogLog 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] :: HyperLogLog 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.
Constructors
| HyperLogLog | |
Fields | |
Instances
| HasHyperLogLog k (HyperLogLog k p) p Source # | |
| Eq (HyperLogLog k p) Source # | |
| Show (HyperLogLog k p) Source # | |
| Generic (HyperLogLog k p) Source # | |
| Semigroup (HyperLogLog k p) Source # | |
| Reifies k p Integer => Monoid (HyperLogLog k p) Source # | |
| Binary (HyperLogLog k p) Source # | |
| Serial (HyperLogLog k p) Source # | |
| Serialize (HyperLogLog k p) Source # | |
| NFData (HyperLogLog k p) Source # | |
| type Rep (HyperLogLog k p) Source # | |
class HasHyperLogLog a p | a -> p where Source #
Minimal complete definition
Methods
hyperLogLog :: Lens' a (HyperLogLog p) Source #
Instances
| HasHyperLogLog k (HyperLogLog k p) p Source # | |
size :: Reifies p Integer => HyperLogLog p -> Approximate Int64 Source #
Approximate size of our set
insert :: (Reifies s Integer, Serial a) => a -> HyperLogLog s -> HyperLogLog s Source #
insertHash :: Reifies s Integer => Word32 -> HyperLogLog s -> HyperLogLog s Source #
Insert a value that has already been hashed by whatever user defined hash function you want.
intersectionSize :: Reifies p Integer => [HyperLogLog p] -> Approximate Int64 Source #
cast :: forall p q. (Reifies p Integer, Reifies q Integer) => HyperLogLog p -> Maybe (HyperLogLog q) Source #
coerceConfig :: forall p q. (Reifies p Integer, Reifies q Integer) => Maybe (Coercion (HyperLogLog p) (HyperLogLog q)) Source #
If two types p and q reify the same configuration, then we can coerce
between and HyperLogLog p. We do this by building
a hole in the HyperLogLog qnominal role for the configuration parameter.