Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- 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 BinInt (BinF f) Source # | |
Defined in Data.Histogram.Bin convertBin :: BinInt -> BinF f Source # | |
RealFrac f => ConvertBin BinI (BinF f) Source # | |
Defined in Data.Histogram.Bin convertBin :: BinI -> BinF f Source # | |
Eq f => Eq (BinF f) Source # | |
Data f => Data (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinF f -> c (BinF f) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BinF f) # toConstr :: BinF f -> Constr # dataTypeOf :: BinF f -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BinF f)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BinF f)) # gmapT :: (forall b. Data b => b -> b) -> BinF f -> BinF f # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinF f -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinF f -> r # gmapQ :: (forall d. Data d => d -> u) -> BinF f -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinF f -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinF f -> m (BinF f) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinF f -> m (BinF f) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinF f -> m (BinF f) # | |
Read f => Read (BinF f) Source # | |
Show f => Show (BinF f) Source # | |
NFData f => NFData (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF | |
RealFrac f => UniformBin (BinF f) Source # | |
RealFrac f => VariableBin (BinF f) Source # | |
RealFrac f => MergeableBin (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF unsafeMergeBins :: CutDirection -> Int -> BinF f -> BinF f Source # | |
RealFrac f => SliceableBin (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF | |
RealFrac f => Bin1D (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF | |
RealFrac f => IntervalBin (BinF f) Source # | |
RealFloat f => BinEq (BinF f) Source # | Equality is up to 2/3th of digits |
RealFrac f => Bin (BinF f) Source # | |
type BinValue (BinF f) Source # | |
Defined in Data.Histogram.Bin.BinF |
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
Eq BinD Source # | |
Data BinD Source # | |
Defined in Data.Histogram.Bin.BinF gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinD -> c BinD # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinD # dataTypeOf :: BinD -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinD) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinD) # gmapT :: (forall b. Data b => b -> b) -> BinD -> BinD # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinD -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinD -> r # gmapQ :: (forall d. Data d => d -> u) -> BinD -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinD -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinD -> m BinD # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinD -> m BinD # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinD -> m BinD # | |
Read BinD Source # | |
Show BinD Source # | |
NFData BinD Source # | |
Defined in Data.Histogram.Bin.BinF | |
UniformBin BinD Source # | |
VariableBin BinD Source # | |
MergeableBin BinD Source # | |
Defined in Data.Histogram.Bin.BinF unsafeMergeBins :: CutDirection -> Int -> BinD -> BinD Source # | |
SliceableBin BinD Source # | |
Defined in Data.Histogram.Bin.BinF | |
Bin1D BinD Source # | |
Defined in Data.Histogram.Bin.BinF | |
IntervalBin BinD Source # | |
BinEq BinD Source # | Equality is up to 3e-11 (2/3th of digits) |
Bin BinD Source # | |
ConvertBin BinInt BinD Source # | |
Defined in Data.Histogram.Bin convertBin :: BinInt -> BinD Source # | |
ConvertBin BinI BinD Source # | |
Defined in Data.Histogram.Bin convertBin :: BinI -> BinD Source # | |
type BinValue BinD Source # | |
Defined in Data.Histogram.Bin.BinF |
Create bins.
Create bins. Note that actual upper bound can differ from specified.
Create bins