multipass-0.1.0.2: Folding data with multiple named passes

Portabilitynon-portable (GADTs, Rank2Types)
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Data.Pass

Contents

Description

 

Synopsis

Evaluation

class Eval k whereSource

Methods

eval :: k a b -> Int -> [a] -> bSource

Run a calculation

Instances

Eval L 
Eval k => Eval (Fun k) 
Call k => Eval (Pass k) 
Call k => Eval (Calc k) 

(@@) :: (Eval k, Foldable f) => k a b -> f a -> bSource

class Naive k whereSource

Methods

naive :: k a b -> Int -> [a] -> bSource

Instances

Naive L 
Naive k => Naive (Fun k) 
Call k => Naive (Pass k) 
Call k => Naive (Calc k) 

(@@@) :: (Naive k, Foldable f) => k a b -> f a -> bSource

Single pass calculations

data Pass k a b whereSource

Constructors

Pass :: (Typeable m, Binary m, Monoid m) => (m -> o) -> Thrist k i m -> Pass k i o 
L :: (n -> o) -> L n n -> Thrist k i n -> Pass k i o 
Ap :: (b -> c) -> Pass k i (a -> b) -> Pass k i a -> Pass k i c 
Pure :: a -> Pass k i a 

Instances

Trans Pass 
Prep Pass 
Passable Pass 
Calculation Pass 
Step Pass 
Typeable2 k => Typeable2 (Pass k) 
By (Pass k) 
Call k => Naive (Pass k) 
Call k => Eval (Pass k) 
Robust (Pass k) 
Accelerant k => Accelerated (Pass k) 
Functor (Pass k a) 
Functor (Pass k a) => Applicative (Pass k a) 
(Fractional (Pass k a b), Floating b) => Floating (Pass k a b) 
(Num (Pass k a b), Fractional b) => Fractional (Pass k a b) 
Num b => Num (Pass k a b) 

class Passable t whereSource

Methods

pass :: (Eval k, Typeable b, Binary b, Monoid b) => t k a b -> Pass k a bSource

Embedding single pass calculations

class Prep t => Step t whereSource

Methods

step :: Pass k a b -> t k a bSource

Instances

Multipass calculations

data Calc k a b whereSource

Constructors

Stop :: b -> Calc k a b 
:& :: Pass k a b -> (b -> Calc k a c) -> Calc k a c 
Rank :: Ord b => Thrist k a b -> ([Int] -> Calc k a c) -> Calc k a c 

Instances

Trans Calc 
Prep Calc 
Calculation Calc 
Step Calc 
By (Calc k) 
Call k => Naive (Calc k) 
Call k => Eval (Calc k) 
Robust (Calc k) 
Accelerant k => Accelerated (Calc k) 
Monad (Calc k a) 
Functor (Calc k a) 
Functor (Calc k a) => Applicative (Calc k a) 
(Fractional (Calc k a b), Floating b) => Floating (Calc k a b) 
(Num (Calc k a b), Fractional b) => Fractional (Calc k a b) 
Num b => Num (Calc k a b) 

class Calculation t whereSource

Methods

calc :: (Eval k, Typeable b, Binary b, Monoid b) => t k a b -> Calc k a bSource

Input conditioning

class Prep t whereSource

Methods

prep :: k a b -> t k b c -> t k a cSource

Instances

L-Estimators

data L a b whereSource

An L-Estimator represents a linear combination of order statistics

Constructors

LTotal :: (Num a, Ord a) => L a a 
LMean :: (Fractional a, Ord a) => L a a 
LScale :: (Fractional a, Ord a) => L a a 
NthLargest :: (Num a, Ord a) => Int -> L a a 
NthSmallest :: (Num a, Ord a) => Int -> L a a 
QuantileBy :: (Fractional a, Ord a) => Estimator -> Rational -> L a a 
Winsorized :: (Fractional b, Ord b) => Rational -> L a b -> L a b 
Trimmed :: (Fractional b, Ord b) => Rational -> L a b -> L a b 
Jackknifed :: (Fractional b, Ord b) => L a b -> L a b 
:* :: Fractional b => Rational -> L a b -> L a b 
:+ :: Num b => L a b -> L a b -> L a b 

Instances

Typeable2 L 
By L 
Named L 
Naive L 
Eval L 
Robust L 
Accelerated L 
Eq (L a b) 
Show (L a b) 
Hashable (L a b) 

(@#) :: Num a => L a a -> Int -> [a]Source

f @# n Return a list of the coefficients that would be used by an L-Estimator for an input of length n

breakdown :: (Num b, Eq b) => L a b -> IntSource

A common measure of how robust an L estimator is in the presence of outliers.

iqm :: (Robust l, Fractional a, Ord a) => l a aSource

interquartile mean

idm :: (Robust l, Fractional a, Ord a) => l a aSource

Quantile estimators

data Estimator Source

Techniques used to smooth the nearest values when calculating quantile functions. R2 is used by default, and the numbering convention follows the use in the R programming language, as far as it goes.

Constructors

R1

Inverse of the empirical distribution function

R2

.. with averaging at discontinuities (default)

R3

The observation numbered closest to Np. NB: does not yield a proper median

R4

Linear interpolation of the empirical distribution function. NB: does not yield a proper median.

R5

.. with knots midway through the steps as used in hydrology. This is the simplest continuous estimator that yields a correct median

R6

Linear interpolation of the expectations of the order statistics for the uniform distribution on [0,1]

R7

Linear interpolation of the modes for the order statistics for the uniform distribution on [0,1]

R8

Linear interpolation of the approximate medans for order statistics.

R9

The resulting quantile estimates are approximately unbiased for the expected order statistics if x is normally distributed.

R10

When rounding h, this yields the order statistic with the least expected square deviation relative to p.

HD

The Harrell-Davis quantile estimator based on bootstrapped order statistics

class By k whereSource

Methods

by :: k a b -> Estimator -> k a bSource

Instances

By L 
By k => By (Thrist k) 
By k => By (Fun k) 
By (Pass k) 
By (Calc k) 

Robust statistics based on L-estimators

class Robust l whereSource

embedding for L-estimators

Methods

robust :: L a b -> l a bSource

winsorized :: (Fractional b, Ord b) => Rational -> L a b -> l a bSource

trimmed :: (Fractional b, Ord b) => Rational -> L a b -> l a bSource

jackknifed :: (Fractional b, Ord b) => L a b -> l a bSource

lscale :: (Fractional a, Ord a) => l a aSource

quantile :: (Fractional a, Ord a) => Rational -> l a aSource

midhinge :: (Fractional a, Ord a) => l a aSource

trimean :: (Fractional a, Ord a) => l a aSource

Tukey's trimean

iqr :: (Fractional a, Ord a) => l a aSource

interquartile range

idr :: (Fractional a, Ord a) => l a aSource

Instances

Robust L 
Robust l => Robust (Fun l) 
Robust (Pass k) 
Robust (Calc k) 

median :: (Robust l, Fractional a, Ord a) => l a aSource

tercile :: (Robust l, Fractional a, Ord a) => Rational -> l a aSource

t1 :: (Robust l, Fractional a, Ord a) => l a aSource

terciles 1 and 2

t2 :: (Robust l, Fractional a, Ord a) => l a aSource

terciles 1 and 2

quartile :: (Robust l, Fractional a, Ord a) => Rational -> l a aSource

q1 :: (Robust l, Fractional a, Ord a) => l a aSource

quantiles, with breakdown points 25%, 50%, and 25% respectively

q2 :: (Robust l, Fractional a, Ord a) => l a aSource

quantiles, with breakdown points 25%, 50%, and 25% respectively

q3 :: (Robust l, Fractional a, Ord a) => l a aSource

quantiles, with breakdown points 25%, 50%, and 25% respectively

quintile :: (Robust l, Fractional a, Ord a) => Rational -> l a aSource

qu1 :: (Robust l, Fractional a, Ord a) => l a aSource

quintiles 1 through 4

qu2 :: (Robust l, Fractional a, Ord a) => l a aSource

quintiles 1 through 4

qu3 :: (Robust l, Fractional a, Ord a) => l a aSource

quintiles 1 through 4

qu4 :: (Robust l, Fractional a, Ord a) => l a aSource

quintiles 1 through 4

percentile :: (Robust l, Fractional a, Ord a) => Rational -> l a aSource

permille :: (Robust l, Fractional a, Ord a) => Rational -> l a aSource

Acceleration for non-robust L-estimators

Implementation Details

data Thrist k a b whereSource

Constructors

Nil :: Thrist k a a 
:- :: k b c -> Thrist k a b -> Thrist k a c 

Instances

thrist :: k a b -> Thrist k a bSource

class Trans t whereSource

Methods

trans :: (Binary b, Monoid b, Typeable b) => k a b -> t k a bSource

Classes required for user-defined calculation types

class Named k => Call k whereSource

Methods

call :: k a b -> a -> bSource

Instances

(Named (Thrist k), Call k) => Call (Thrist k) 
(Named (Fun k), Call k) => Call (Fun k) 

class Typeable2 k => Named k whereSource

Methods

showsFun :: Int -> k a b -> String -> StringSource

putFun :: k a b -> PutSource

hashFunWithSalt :: Int -> k a b -> IntSource

equalFun :: k a b -> k c d -> BoolSource

Instances

Named L 
(Typeable2 (Thrist k), Named k) => Named (Thrist k) 
(Typeable2 (Fun k), Named k) => Named (Fun k)