Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internals of TDigest
.
Tree implementation is based on Adams’ Trees Revisited by Milan Straka http://fox.ucw.cz/papers/bbtree/bbtree.pdf
Synopsis
- data TDigest (compression :: Nat)
- getCentroids :: TDigest comp -> [Centroid]
- totalWeight :: TDigest comp -> Weight
- size :: TDigest comp -> Int
- minimumValue :: TDigest comp -> Mean
- maximumValue :: TDigest comp -> Mean
- emptyTDigest :: TDigest comp
- combineDigest :: KnownNat comp => TDigest comp -> TDigest comp -> TDigest comp
- insertCentroid :: forall comp. KnownNat comp => Centroid -> TDigest comp -> TDigest comp
- node :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp
- balanceR :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp
- balanceL :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp
- node' :: Int -> Mean -> Weight -> Weight -> TDigest comp -> TDigest comp -> TDigest comp
- singNode :: Mean -> Weight -> TDigest comp
- combinedCentroid :: Mean -> Weight -> Mean -> Weight -> Centroid
- threshold :: Double -> Double -> Double -> Double
- compress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp
- forceCompress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp
- toMVector :: forall comp s. KnownNat comp => TDigest comp -> ST s (MVector s (Centroid, Double))
- relMaxSize :: Int
- absMaxSize :: Int
- balOmega :: Int
- balAlpha :: Int
- debugPrint :: TDigest comp -> IO ()
- valid :: TDigest comp -> Bool
- validate :: TDigest comp -> Either String (TDigest comp)
- insert :: KnownNat comp => Double -> TDigest comp -> TDigest comp
- insert' :: KnownNat comp => Double -> TDigest comp -> TDigest comp
- singleton :: KnownNat comp => Double -> TDigest comp
- tdigest :: (Foldable f, KnownNat comp) => f Double -> TDigest comp
Documentation
data TDigest (compression :: Nat) Source #
TDigest
is a tree of centroids.
compression
is a 1/δ
. The greater the value of compression
the less
likely value merging will happen.
Node !Size !Mean !Weight !Weight !(TDigest compression) !(TDigest compression) | Tree node |
Nil | Empty tree |
Instances
KnownNat comp => Reducer Double (TDigest comp) Source # | |
Show (TDigest compression) Source # | |
KnownNat comp => Semigroup (TDigest comp) Source # | |
KnownNat comp => Monoid (TDigest comp) Source # | |
KnownNat comp => Binary (TDigest comp) Source # |
|
NFData (TDigest comp) Source # |
|
Defined in Data.TDigest.Tree.Internal | |
HasHistogram (TDigest comp) Maybe Source # | |
But*, the benefit vs. code explosion is not yet worth.
getCentroids :: TDigest comp -> [Centroid] Source #
totalWeight :: TDigest comp -> Weight Source #
Total count of samples.
>>>
totalWeight (tdigest [1..100] :: TDigest 5)
100.0
minimumValue :: 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 :: TDigest comp -> Mean Source #
Center of right-most centroid. Note: may be different than max element inserted.
>>>
maximumValue (tdigest [1..100] :: TDigest 3)
99.0
emptyTDigest :: TDigest comp Source #
node :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp Source #
Constructor which calculates size and total weight.
balanceR :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp Source #
Balance after right insertion.
balanceL :: Mean -> Weight -> TDigest comp -> TDigest comp -> TDigest comp Source #
Balance after left insertion.
node' :: Int -> Mean -> Weight -> Weight -> TDigest comp -> TDigest comp -> TDigest comp Source #
Alias to Node
combinedCentroid :: Mean -> Weight -> Mean -> Weight -> Centroid Source #
Add two weighted means together.
Calculate the threshold, i.e. maximum weight of centroid.
compress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp Source #
Compress TDigest
.
Reinsert the centroids in "better" order (in original paper: in random) so they have opportunity to merge.
Compression will happen only if size is both:
bigger than
and bigger than relMaxSize
* compabsMaxSize
.
forceCompress :: forall comp. KnownNat comp => TDigest comp -> TDigest comp Source #
Perform compression, even if current size says it's not necessary.
relMaxSize :: Int Source #
Relative size parameter. Hard-coded value: 25.
absMaxSize :: Int Source #
Absolute size parameter. Hard-coded value: 1000.
validate :: TDigest comp -> Either String (TDigest comp) Source #
Check various invariants in the TDigest
tree.
Insert single value into TDigest
.
>>>
:set -XDataKinds