| Copyright | (c) Justin Le 2018 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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
- data BinSpec (n :: Nat) a b = BS {}
- linBS :: forall n a. a -> a -> BinSpec n a a
- logBS :: forall n a. Floating a => a -> a -> BinSpec n a a
- gaussBS :: forall n a. RealFrac a => a -> a -> a -> BinSpec n a Double
- type BinView a b = forall p. Profunctor p => p b b -> p a a
- binView :: (a -> b) -> (b -> a) -> BinView a b
- linView :: BinView a a
- logView :: Floating a => BinView a a
- gaussView :: RealFrac a => a -> a -> BinView a Double
- binSpecIntervals :: forall n a b. (KnownNat n, Fractional b) => BinSpec n a b -> Vector (n + 1) a
- data Bin s n
- type Binner s n a = a -> Bin s n
- withBinner :: (KnownNat n, RealFrac b) => BinSpec n a b -> (forall s. Reifies s (BinSpec n a b) => Binner s n a -> r) -> r
- fromFin :: Finite n -> Bin s n
- binFin :: Bin s n -> Maybe (Finite n)
- binRange :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> (Maybe a, Maybe a)
- binMin :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a
- binMax :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a
- binFinExt :: KnownNat n => Bin s n -> Finite ((1 + n) + 1)
- binFinComp :: KnownNat n => Bin s n -> Finite n
- displayBin :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => (a -> String) -> Bin s n -> String
- displayBinDouble :: forall n b s. (KnownNat n, Fractional b, Reifies s (BinSpec n Double b)) => Int -> Bin s n -> String
- data Pointed a
- pointed :: b -> (a -> b) -> b -> Pointed a -> b
- pElem :: Pointed a -> Maybe a
- binIx :: Bin s n -> Pointed (Finite n)
- fromIx :: Pointed (Finite n) -> Bin s n
- expandFin :: KnownNat n => Pointed (Finite n) -> Finite ((1 + n) + 1)
- unexpandFin :: KnownNat n => Finite ((1 + n) + 1) -> Pointed (Finite n)
- data SomeBin a n = (Fractional b, Reifies s (BinSpec n a b)) => SomeBin {
- getSomeBin :: Bin s n
- 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)
- binFreq :: forall n t a s. Foldable t => Binner s n a -> t a -> Map (Bin s n) Int
Specifying the binning
Arguments
| :: a | Lower bound |
| -> a | Upper bound |
| -> BinSpec n a a |
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.
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.
logView :: Floating a => BinView a a Source #
Logarithmic binning (smaller bins at lower levels, larger bins at higher levels).
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
A is a single bin index out of Bin s nn 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.
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.
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 #
binMin :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a Source #
binMax :: forall n a b s. (KnownNat n, Fractional b, Reifies s (BinSpec n a b)) => Bin s n -> Maybe a Source #
Showing bins
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.
In-depth inspection
Data type extending a value with an extra "minimum" and "maximum" value.
Instances
| Functor Pointed Source # | |
| Eq a => Eq (Pointed a) Source # | |
| Ord a => Ord (Pointed a) Source # | |
| Show a => Show (Pointed a) Source # | |
pElem :: Pointed a -> Maybe a Source #
Extract the item from a Pointed if it is neither the extra minimum
or maximum.
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.
Untyped
A is SomeBin a n, except with the Bin s nBinSpec 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 |
| (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
|
Defined in Data.Bin | |
| (KnownNat n, Show a) => Show (SomeBin a n) Source # | |
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 #
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