histogram-fill-0.9.1.0: Library for histograms creation.

Safe HaskellNone
LanguageHaskell98

Data.Histogram.Bin.BinF

Contents

Synopsis

Generic and slow

data BinF f Source #

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 # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinInt -> BinF f Source #

RealFrac f => ConvertBin BinI (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinI -> BinF f Source #

Eq f => Eq (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

(==) :: BinF f -> BinF f -> Bool #

(/=) :: BinF f -> BinF f -> Bool #

Data f => Data (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

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 # 
Instance details

Defined in Data.Histogram.Bin.BinF

Show f => Show (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

showsPrec :: Int -> BinF f -> ShowS #

show :: BinF f -> String #

showList :: [BinF f] -> ShowS #

NFData f => NFData (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

rnf :: BinF f -> () #

RealFrac f => UniformBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binSize :: BinF f -> BinValue (BinF f) Source #

RealFrac f => VariableBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binSizeN :: BinF f -> Int -> BinValue (BinF f) Source #

RealFrac f => MergeableBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

RealFrac f => SliceableBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

unsafeSliceBin :: Int -> Int -> BinF f -> BinF f Source #

RealFrac f => Bin1D (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

RealFrac f => IntervalBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binInterval :: BinF f -> Int -> (BinValue (BinF f), BinValue (BinF f)) Source #

binsList :: Vector v (BinValue (BinF f), BinValue (BinF f)) => BinF f -> v (BinValue (BinF f), BinValue (BinF f)) Source #

RealFloat f => BinEq (BinF f) Source #

Equality is up to 2/3th of digits

Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binEq :: BinF f -> BinF f -> Bool Source #

RealFrac f => Bin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Associated Types

type BinValue (BinF f) :: * Source #

Methods

toIndex :: BinF f -> BinValue (BinF f) -> Int Source #

fromIndex :: BinF f -> Int -> BinValue (BinF f) Source #

nBins :: BinF f -> Int Source #

inRange :: BinF f -> BinValue (BinF f) -> Bool Source #

type BinValue (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

type BinValue (BinF f) = f

binF Source #

Arguments

:: RealFrac f 
=> f

Lower bound of range

-> Int

Number of bins

-> f

Upper bound of range

-> BinF f 

Create bins.

binFn Source #

Arguments

:: RealFrac f 
=> f

Begin of range

-> f

Size of step

-> f

Approximation of end of range

-> BinF f 

Create bins. Note that actual upper bound can differ from specified.

binFstep Source #

Arguments

:: RealFrac f 
=> f

Begin of range

-> f

Size of step

-> Int

Number of bins

-> BinF f 

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

data BinD Source #

Floating point bins of equal sizes. If you work with Doubles this data type should be used instead of BinF.

Instances
Eq BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

(==) :: BinD -> BinD -> Bool #

(/=) :: BinD -> BinD -> Bool #

Data BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

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 #

toConstr :: BinD -> Constr #

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 # 
Instance details

Defined in Data.Histogram.Bin.BinF

Show BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

showsPrec :: Int -> BinD -> ShowS #

show :: BinD -> String #

showList :: [BinD] -> ShowS #

NFData BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

rnf :: BinD -> () #

UniformBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

VariableBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

MergeableBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

SliceableBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

unsafeSliceBin :: Int -> Int -> BinD -> BinD Source #

Bin1D BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

IntervalBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

BinEq BinD Source #

Equality is up to 3e-11 (2/3th of digits)

Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binEq :: BinD -> BinD -> Bool Source #

Bin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Associated Types

type BinValue BinD :: * Source #

ConvertBin BinInt BinD Source # 
Instance details

Defined in Data.Histogram.Bin

ConvertBin BinI BinD Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinI -> BinD Source #

type BinValue BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

binD Source #

Arguments

:: Double

Lower bound of range

-> Int

Number of bins

-> Double

Upper bound of range

-> BinD 

Create bins.

binDn Source #

Arguments

:: Double

Begin of range

-> Double

Size of step

-> Double

Approximation of end of range

-> BinD 

Create bins. Note that actual upper bound can differ from specified.

binDstep Source #

Arguments

:: Double

Begin of range

-> Double

Size of step

-> Int

Number of bins

-> BinD 

Create bins

scaleBinD :: Double -> Double -> BinD -> BinD Source #

'scaleBinF a b' scales BinF using linear transform 'a+b*x'