Safe Haskell | None |
---|---|
Language | Haskell2010 |
A new data structure for accurate on-line accumulation of rank-based statistics such as quantiles and trimmed means. . See original paper: "Computing extremely accurate quantiles using t-digest" by Ted Dunning and Otmar Ertl for more details https://github.com/tdunning/t-digest/blob/master/docs/t-digest-paper/histo.pdf.
Examples
>>>
quantile 0.99 (tdigest [1..1000] :: TDigest 25)
Just 990.5
>>>
quantile 0.99 (tdigest [1..1000] :: TDigest 3)
Just 990.3...
t-Digest is more precise in tails, especially median is imprecise:
>>>
median (forceCompress $ tdigest [1..1000] :: TDigest 10)
Just 500.5
Semigroup
This operation isn't strictly associative, but statistical variables shouldn't be affected.
>>>
let td xs = tdigest xs :: TDigest 10
>>>
median (td [1..500] <> (td [501..1000] <> td [1001..1500]))
Just 750.5
>>>
median ((td [1..500] <> td [501..1000]) <> td [1001..1500])
Just 750.5
The linear is worst-case scenario:
>>>
let td' xs = tdigest (fairshuffle xs) :: TDigest 10
>>>
median (td' [1..500] <> (td' [501..1000] <> td' [1001..1500]))
Just 750.5
>>>
median ((td' [1..500] <> td' [501..1000]) <> td' [1001..1500])
Just 750.5
Synopsis
- data TDigest (compression :: Nat)
- tdigest :: (Foldable f, KnownNat comp) => f Double -> TDigest comp
- singleton :: Double -> TDigest comp
- insert :: KnownNat comp => Double -> TDigest comp -> TDigest comp
- insert' :: KnownNat comp => Double -> TDigest comp -> TDigest comp
- compress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp
- forceCompress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp
- minimumValue :: KnownNat comp => TDigest comp -> Mean
- maximumValue :: KnownNat comp => TDigest comp -> Mean
- median :: KnownNat comp => TDigest comp -> Maybe Double
- quantile :: KnownNat comp => Double -> TDigest comp -> Maybe Double
- mean :: KnownNat comp => TDigest comp -> Maybe Double
- variance :: KnownNat comp => TDigest comp -> Maybe Double
- stddev :: KnownNat comp => TDigest comp -> Maybe Double
- cdf :: KnownNat comp => Double -> TDigest comp -> Double
- icdf :: KnownNat comp => Double -> TDigest comp -> Maybe Double
- size :: TDigest comp -> Int
- valid :: TDigest comp -> Bool
- validate :: TDigest comp -> Either String (TDigest comp)
Construction
data TDigest (compression :: Nat) Source #
TDigest
is a vector of centroids plus not yet merged elements.
The size of structure is dictated by compression
, *𝛿*. And is *O(𝛿)*.
Instances
KnownNat comp => Reducer Double (TDigest comp) Source # | |
Show (TDigest compression) Source # | |
KnownNat comp => Semigroup (TDigest comp) Source # | |
KnownNat comp => Monoid (TDigest comp) Source # | |
NFData (TDigest comp) Source # | |
Defined in Data.TDigest.Vector.Internal | |
KnownNat comp => HasHistogram (TDigest comp) Maybe Source # | |
Population
Insert single value into TDigest
.
Compression
>>>
let digest = foldl' (flip insert') mempty [0..1000] :: TDigest 5
>>>
(size digest, size $ compress digest)
(1001,173)
>>>
(quantile 0.1 digest, quantile 0.1 $ compress digest)
(Just 99.6...,Just 99.6...)
Statistics
minimumValue :: KnownNat comp => TDigest comp -> Mean Source #
Center of left-most centroid. Note: may be different than min element inserted.
>>>
minimumValue (tdigest [1..100] :: TDigest 3)
1.0
maximumValue :: KnownNat comp => TDigest comp -> Mean Source #
Center of right-most centroid. Note: may be different than max element inserted.
>>>
maximumValue (tdigest [1..100] :: TDigest 3)
100.0
Percentile
quantile :: KnownNat comp => Double -> TDigest comp -> Maybe Double Source #
Calculate quantile of a specific value.
Mean & Variance
>>>
stddev (tdigest $ fairshuffle [0..100] :: TDigest 10)
Just 29.0...
mean :: KnownNat comp => TDigest comp -> Maybe Double Source #
Mean.
>>>
mean (tdigest [1..100] :: TDigest 10)
Just 50.5
Note: if you only need the mean, calculate it directly.
stddev :: KnownNat comp => TDigest comp -> Maybe Double Source #
Standard deviation, square root of variance.
CDF
cdf :: KnownNat comp => Double -> TDigest comp -> Double Source #
Cumulative distribution function.
Note: if this is the only thing you need, it's more efficient to count this directly.