Safe Haskell | None |
---|---|
Language | Haskell98 |
Data.Histogram.Bin.BinF
- data BinF f
- binF :: RealFrac f => f -> Int -> f -> BinF f
- binFn :: RealFrac f => f -> f -> f -> BinF f
- binFstep :: RealFrac f => f -> f -> Int -> BinF f
- scaleBinF :: (Show f, RealFrac f) => f -> f -> BinF f -> BinF f
- data BinD
- binD :: Double -> Int -> Double -> BinD
- binDn :: Double -> Double -> Double -> BinD
- binDstep :: Double -> Double -> Int -> BinD
- scaleBinD :: Double -> Double -> BinD -> BinD
Generic and slow
Floating point bins of equal size. Use following function for construction and inspection of value:
b = binFstep (lowerLimit b) (binSize b) (nBins b)
Performance note. Since BinF
is parametric in its value it
could not be unpacked and every access to data will require
pointer indirection. BinD
is binning specialized to Doubles
and it's always faster than BinF Double
.
Instances
RealFrac f => ConvertBin BinI (BinF f) | |
RealFrac f => ConvertBin BinInt (BinF f) | |
Eq f => Eq (BinF f) | |
Data f => Data (BinF f) | |
(Read f, RealFrac f) => Read (BinF f) | |
Show f => Show (BinF f) | |
NFData f => NFData (BinF f) | |
RealFrac f => UniformBin (BinF f) | |
RealFrac f => VariableBin (BinF f) | |
RealFrac f => MergeableBin (BinF f) | |
RealFrac f => SliceableBin (BinF f) | |
RealFrac f => Bin1D (BinF f) | |
RealFrac f => IntervalBin (BinF f) | |
RealFloat f => BinEq (BinF f) | Equality is up to 2/3th of digits |
RealFrac f => Bin (BinF f) | |
Typeable (* -> *) BinF | |
type BinValue (BinF f) = f |
Arguments
:: RealFrac f | |
=> f | Lower bound of range |
-> Int | Number of bins |
-> f | Upper bound of range |
-> BinF f |
Create bins.
Create bins. Note that actual upper bound can differ from specified.
Create bins
scaleBinF :: (Show f, RealFrac f) => f -> f -> BinF f -> BinF f Source
'scaleBinF a b' scales BinF using linear transform 'a+b*x'
Specialized for Double and fast
Floating point bins of equal sizes. If you work with Doubles this
data type should be used instead of BinF
.
Instances
Create bins.
Create bins. Note that actual upper bound can differ from specified.
Create bins