bins-0.1.2.0: Aggregate continuous values into discrete bins

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Bin

Contents

Description

Tools for aggregating numeric values into a set of discrete bins according to some binning specification.

See withBinner for main usage information, and Bin for the main binned data type, and binFreq for a common usage example.

Synopsis

Specifying the binning

data BinSpec (n :: Nat) a b Source #

Specification of binning.

A BinSpec n a b will bin values of type a into n bins, according to a scaling in type b.

Constructor is meant to be used with type application syntax to indicate n, like BinSpec 5 0 10 linView@

Constructors

BS 

Fields

linBS Source #

Arguments

:: a

Lower bound

-> a

Upper bound

-> BinSpec n a a 

Convenient constructor for a BinSpec for a linear scaling.

Meant to be used with type application syntax:

linBS @5 0 10

logBS Source #

Arguments

:: Floating a 
=> a

Lower bound

-> a

Upper bound

-> BinSpec n a a 

Convenient constructor for a BinSpec for a logarithmic scaling.

Meant to be used with type application syntax:

logBS @5 0 10

gaussBS Source #

Arguments

:: RealFrac a 
=> a

Standard Deviation

-> a

Lower bound

-> a

Upper bound

-> BinSpec n a Double 

Convenient constructor for a BinSpec for a gaussian scaling. Uses the midpoint as the inferred mean.

Meant to be used with type application syntax:

gaussBS @5 3 0 10

indicates that you want 5 bins.

BinView

type BinView a b = forall p. Profunctor p => p b b -> p a a Source #

A bidirectional "view" to transform the data type before binning.

See linView for a linear binning, and logView for a logarithmic binning. You can construct your own custom transformer using binView.

This type is essentially Iso from the lens library, and any Iso' from lens can be used here. However, it is important that all of these represent monotonic isomorphisms.

binView Source #

Arguments

:: (a -> b)

"to"

-> (b -> a)

"from"

-> BinView a b 

Construct a BinView based on "to" and "from" functions

It is important that the "to" and "from" functions be inverses of each other. Furthermore, both "to" and "from" should be monotonic.

linView :: BinView a a Source #

Linear binning

logView :: Floating a => BinView a a Source #

Logarithmic binning (smaller bins at lower levels, larger bins at higher levels).

gaussView Source #

Arguments

:: RealFrac a 
=> a

center / mean

-> a

standard deviation

-> BinView a Double 

Binning based on a Gaussian Distribution. Bins "by standard deviation"; there are more bins the closer to the mean you get, and less bins the farther away.

Inspecting BinSpec

binSpecIntervals :: forall n a b. (KnownNat n, Fractional b) => BinSpec n a b -> Vector (n + 1) a Source #

Generate a vector of the boundaries deriving the bins from a BinSpec. Can be useful for debugging.

Creating and manipulating bins

data Bin s n Source #

A Bin s n is a single bin index out of n partitions of the original data set, according to a BinSpec represented by s.

All Bins with the same s follow the same BinSpec, so you can safely use binRange withBinner.

It has useful Eq and Ord instances.

Actually has n + 2 partitions, since it also distinguishes values that are outside the BinSpec range.

Instances
Eq (Bin s n) Source # 
Instance details

Defined in Data.Bin

Methods

(==) :: Bin s n -> Bin s n -> Bool #

(/=) :: Bin s n -> Bin s n -> Bool #

Ord (Bin s n) Source # 
Instance details

Defined in Data.Bin

Methods

compare :: Bin s n -> Bin s n -> Ordering #

(<) :: Bin s n -> Bin s n -> Bool #

(<=) :: Bin s n -> Bin s n -> Bool #

(>) :: Bin s n -> Bin s n -> Bool #

(>=) :: Bin s n -> Bin s n -> Bool #

max :: Bin s n -> Bin s n -> Bin s n #

min :: Bin s n -> Bin s n -> Bin s n #

(KnownNat n, Show a, Fractional b, Reifies s (BinSpec n a b)) => Show (Bin s n) Source # 
Instance details

Defined in Data.Bin

Methods

showsPrec :: Int -> Bin s n -> ShowS #

show :: Bin s n -> String #

showList :: [Bin s n] -> ShowS #

type Binner s n a = a -> Bin s n Source #

The type of a "binning function", given by withBinner. See withBinner for information on how to use.

withBinner :: (KnownNat n, RealFrac b) => BinSpec n a b -> (forall s. Reifies s (BinSpec n a b) => Binner s n a -> r) -> r Source #

With a BinSpec, give a "binning function" that you can use to create bins within a continuation.

withBinner myBinSpec $ toBin ->
    show (toBin 2.8523)

Uses a Rank-N continution to ensure that you can only compare Bins constructed from the same BinSpec/binning function.

fromFin :: Finite n -> Bin s n Source #

Construct a Bin if you know the bin number you want to specify. See fromIx if you want to specify bins that are over or under the maximum, as well.

Inspecting bins

binFin :: Bin s n -> Maybe (Finite n) Source #

Extract, potentially, the Bin index. Will return Nothing if the original value was outside the BinSpec range.

See binIx for a more specific version, which indicates if the original value was too high or too low. Also see binFinExt, which extends the range of the Finite to embed lower or higher values.

binRange :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> (Maybe a, Maybe a) Source #

Extract the minimum and maximum of the range indicabed by a given Bin.

A Nothing value indicates that we are outside of the normal range of the BinSpec, so is "unbounded" in that direction.

binMin :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a Source #

Extract the minimum of the range indicabed by a given Bin.

A Nothing value means that the original value was below the minimum limit of the BinSpec, so is "unbounded" in the lower direction.

binMax :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a Source #

Extract the maximum of the range indicabed by a given Bin.

A Nothing value means that the original value was above the maximum limit of the BinSpec, so is "unbounded" in the upper direction.

binFinExt :: KnownNat n => Bin s n -> Finite ((1 + n) + 1) Source #

Like binFin, but return the true "n + 2" slot number of a Bin, where minBound is "below minimum" and maxBound is "above maximum"

Since: 0.1.1.0

binFinComp :: KnownNat n => Bin s n -> Finite n Source #

Like binFin, but squishes or compresses "below minimum" to "above maximum" bins into the Finite, counting them in the same bin as the minimum and maximum bin, respectively.

Since: 0.1.1.0

Showing bins

displayBin Source #

Arguments

:: (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) 
=> (a -> String)

how to display a value

-> Bin s n 
-> String 

Display the interval maintained by a Bin.

displayBinDouble Source #

Arguments

:: (KnownNat n, Fractional b, Reifies s (BinSpec n Double b)) 
=> Int

number of decimal places to round

-> Bin s n 
-> String 

Display the interval maintained by a Bin, if the Bin contains a Double.

In-depth inspection

data Pointed a Source #

Data type extending a value with an extra "minimum" and "maximum" value.

Constructors

Bot 
PElem !a 
Top 
Instances
Functor Pointed Source # 
Instance details

Defined in Data.Bin

Methods

fmap :: (a -> b) -> Pointed a -> Pointed b #

(<$) :: a -> Pointed b -> Pointed a #

Eq a => Eq (Pointed a) Source # 
Instance details

Defined in Data.Bin

Methods

(==) :: Pointed a -> Pointed a -> Bool #

(/=) :: Pointed a -> Pointed a -> Bool #

Ord a => Ord (Pointed a) Source # 
Instance details

Defined in Data.Bin

Methods

compare :: Pointed a -> Pointed a -> Ordering #

(<) :: Pointed a -> Pointed a -> Bool #

(<=) :: Pointed a -> Pointed a -> Bool #

(>) :: Pointed a -> Pointed a -> Bool #

(>=) :: Pointed a -> Pointed a -> Bool #

max :: Pointed a -> Pointed a -> Pointed a #

min :: Pointed a -> Pointed a -> Pointed a #

Show a => Show (Pointed a) Source # 
Instance details

Defined in Data.Bin

Methods

showsPrec :: Int -> Pointed a -> ShowS #

show :: Pointed a -> String #

showList :: [Pointed a] -> ShowS #

pointed Source #

Arguments

:: b

return if Bot

-> (a -> b)

apply if PElem

-> b

return if Top

-> Pointed a 
-> b 

Church-style deconstructor for Pointed, analogous to maybe, either, and bool.

Since: 0.1.1.0

pElem :: Pointed a -> Maybe a Source #

Extract the item from a Pointed if it is neither the extra minimum or maximum.

binIx :: Bin s n -> Pointed (Finite n) Source #

A more specific version of binFin that indicates whether or not the value was too high or too low for the BinSpec range.

fromIx :: Pointed (Finite n) -> Bin s n Source #

Construct a Bin if you know the bin number you want to specify, or if the bin is over or under the maximum.

expandFin :: KnownNat n => Pointed (Finite n) -> Finite ((1 + n) + 1) Source #

Expand a Pointed containing a Finite to a wider-ranged Finite. Used for binFinExt

Since: 0.1.2.0

unexpandFin :: KnownNat n => Finite ((1 + n) + 1) -> Pointed (Finite n) Source #

The inverse of expandFin: "re-pack" a Finite back into a Pointed containing a narrower-ranged Finite.

Since: 0.1.2.0

Untyped

data SomeBin a n Source #

A SomeBin a n is Bin s n, except with the BinSpec s hidden. It's useful for returning out of withBinner.

It has useful Eq and Ord instances.

To be able to "unify" two Bins inside a SomeBin, use sameBinSpec to verify that the two SomeBins were created with the same BinSpec.

Constructors

(Fractional b, Reifies s (BinSpec n a b)) => SomeBin 

Fields

Instances
(KnownNat n, Eq a) => Eq (SomeBin a n) Source #

Compares if the ranges match. Note that this is less performant than comparing the original Bins, or extracting and using sameBinSpec.

Instance details

Defined in Data.Bin

Methods

(==) :: SomeBin a n -> SomeBin a n -> Bool #

(/=) :: SomeBin a n -> SomeBin a n -> Bool #

(KnownNat n, Ord a) => Ord (SomeBin a n) Source #

Lexicographical ordering -- compares the lower bound, then the upper bounds. Note that this is less performant than comparing the original Bins, or extracting and using sameBinSpec

Instance details

Defined in Data.Bin

Methods

compare :: SomeBin a n -> SomeBin a n -> Ordering #

(<) :: SomeBin a n -> SomeBin a n -> Bool #

(<=) :: SomeBin a n -> SomeBin a n -> Bool #

(>) :: SomeBin a n -> SomeBin a n -> Bool #

(>=) :: SomeBin a n -> SomeBin a n -> Bool #

max :: SomeBin a n -> SomeBin a n -> SomeBin a n #

min :: SomeBin a n -> SomeBin a n -> SomeBin a n #

(KnownNat n, Show a) => Show (SomeBin a n) Source # 
Instance details

Defined in Data.Bin

Methods

showsPrec :: Int -> SomeBin a n -> ShowS #

show :: SomeBin a n -> String #

showList :: [SomeBin a n] -> ShowS #

sameBinSpec :: forall s t n a b p. (Reifies s (BinSpec n a b), Reifies t (BinSpec n a b), KnownNat n, Eq a, Fractional b) => p s -> p t -> Maybe (s :~: t) Source #

Verify that the two reified BinSpec types refer to the same one, allowing you to use functions like == and compare on Bins that you get out of a SomeBin.

Handy use patterns

binFreq :: forall n t a s. Foldable t => Binner s n a -> t a -> Map (Bin s n) Int Source #

Generate a histogram: given a container of as, generate a frequency map of how often values in a given discrete bin occurred.

xs :: [Double]
xs = [1..100]

main :: IO ()
main = withBinner (logBS @10 5 50) $ toBin ->
    mapM_ ((b, n) -> putStrLn (displayBinDouble 4 b ++ "t" ++ show n))
  . M.toList
  $ binFreq toBin xs
(-inf .. 5.0000)        4
[5.0000 .. 6.2946)      2
[6.2946 .. 7.9245)      1
[7.9245 .. 9.9763)      2
[9.9763 .. 12.5594)     3
[12.5594 .. 15.8114)    3
[15.8114 .. 19.9054)    4
[19.9054 .. 25.0594)    6
[25.0594 .. 31.5479)    6
[31.5479 .. 39.7164)    8
[39.7164 .. 50.0000)    10
[50.0000 .. +inf)       51