HROOT-hist-0.10.0.3: Haskell binding to ROOT Hist modules
Safe HaskellSafe-Inferred
LanguageHaskell2010

HROOT.Hist.TH1

Documentation

newtype TH1 Source #

Constructors

TH1 (Ptr RawTH1) 

Instances

Instances details
ITAttFill TH1 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

setFillColor :: TH1 -> CInt -> IO ()

setFillStyle :: TH1 -> CInt -> IO ()

ITAttLine TH1 
Instance details

Defined in HROOT.Hist.TH1.Implementation

ITAttMarker TH1 
Instance details

Defined in HROOT.Hist.TH1.Implementation

ITNamed TH1 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

setName :: Castable c0 CString => TH1 -> c0 -> IO ()

setNameTitle :: (Castable c1 CString, Castable c0 CString) => TH1 -> c0 -> c1 -> IO ()

setTitle :: Castable c0 CString => TH1 -> c0 -> IO ()

ITObject TH1 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

clear :: Castable c0 CString => TH1 -> c0 -> IO ()

draw :: Castable c0 CString => TH1 -> c0 -> IO ()

findObject :: Castable c0 CString => TH1 -> c0 -> IO TObject

getName :: TH1 -> IO CString

isA :: TH1 -> IO TClass

paint :: Castable c0 CString => TH1 -> c0 -> IO ()

printObj :: Castable c0 CString => TH1 -> c0 -> IO ()

saveAs :: (Castable c1 CString, Castable c0 CString) => TH1 -> c0 -> c1 -> IO ()

write :: Castable c0 CString => TH1 -> c0 -> CInt -> CInt -> IO CInt

write_ :: TH1 -> IO CInt

ITH1 TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1 -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1 -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1 -> c0 -> IO TH1 Source #

drawNormalized :: Castable c0 CString => TH1 -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1 -> IO () Source #

bufferEmpty :: TH1 -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1 -> CDouble -> IO CInt Source #

fill1w :: TH1 -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CInt -> IO () Source #

findBin :: TH1 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1 -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1 -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1 -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1 -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1 -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getBarOffset :: TH1 -> IO CFloat Source #

getBarWidth :: TH1 -> IO CFloat Source #

getContour :: TH1 -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1 -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1 -> CInt -> IO CDouble Source #

getBin :: TH1 -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1 -> CInt -> IO CDouble Source #

getBinContent1 :: TH1 -> CInt -> IO CDouble Source #

getBinContent2 :: TH1 -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1 -> CInt -> IO CDouble Source #

getBinError2 :: TH1 -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1 -> CInt -> IO CDouble Source #

getBinWidth :: TH1 -> CInt -> IO CDouble Source #

getCellContent :: TH1 -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1 -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1 -> IO CDouble Source #

getEffectiveEntries :: TH1 -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1 -> c0 -> IO TF1 Source #

getDimension :: TH1 -> IO CInt Source #

getKurtosis :: TH1 -> CInt -> IO CDouble Source #

getLowEdge :: TH1 -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1 -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1 -> IO CInt Source #

getMaximumStored :: TH1 -> IO CDouble Source #

getMinimumTH1 :: TH1 -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1 -> IO CInt Source #

getMinimumStored :: TH1 -> IO CDouble Source #

getMean :: TH1 -> CInt -> IO CDouble Source #

getMeanError :: TH1 -> CInt -> IO CDouble Source #

getNbinsX :: TH1 -> IO CDouble Source #

getNbinsY :: TH1 -> IO CDouble Source #

getNbinsZ :: TH1 -> IO CDouble Source #

getQuantilesTH1 :: TH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1 -> IO CDouble Source #

getStats :: TH1 -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1 -> IO CDouble Source #

getSumw2 :: TH1 -> IO TArrayD Source #

getSumw2N :: TH1 -> IO CInt Source #

getRMS :: TH1 -> CInt -> IO CDouble Source #

getRMSError :: TH1 -> CInt -> IO CDouble Source #

getSkewness :: TH1 -> CInt -> IO CDouble Source #

interpolate3 :: TH1 -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1 -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1 -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1 -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1 -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1 -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1 -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1 -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1 -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1 -> c0 -> IO () Source #

resetStats :: TH1 -> IO () Source #

scale :: Castable c0 CString => TH1 -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1 -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1 -> CFloat -> IO () Source #

setBarWidth :: TH1 -> CFloat -> IO () Source #

setBinContent1 :: TH1 -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1 -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1 -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1 -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1 -> CInt -> c0 -> IO () Source #

setCellContent :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1 -> Ptr CDouble -> IO () Source #

setContour :: TH1 -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1 -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1 -> c0 -> IO () Source #

setEntries :: TH1 -> CDouble -> IO () Source #

setError :: TH1 -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1 -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1 -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1 -> CDouble -> IO () Source #

setMinimum :: TH1 -> CDouble -> IO () Source #

setNormFactor :: TH1 -> CDouble -> IO () Source #

setStats :: TH1 -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1 -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1 -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1 -> CInt -> c0 -> IO () Source #

sumw2 :: TH1 -> IO () Source #

Show TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.RawType

Methods

showsPrec :: Int -> TH1 -> ShowS #

show :: TH1 -> String #

showList :: [TH1] -> ShowS #

FPtr TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.RawType

Associated Types

type Raw TH1 #

Eq TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.RawType

Methods

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

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

Ord TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.RawType

Methods

compare :: TH1 -> TH1 -> Ordering #

(<) :: TH1 -> TH1 -> Bool #

(<=) :: TH1 -> TH1 -> Bool #

(>) :: TH1 -> TH1 -> Bool #

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

max :: TH1 -> TH1 -> TH1 #

min :: TH1 -> TH1 -> TH1 #

IDeletable TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

delete :: TH1 -> IO () #

Castable TH1 (Ptr RawTH1) Source # 
Instance details

Defined in HROOT.Hist.TH1.Cast

Methods

cast :: TH1 -> (Ptr RawTH1 -> IO r) -> IO r #

uncast :: Ptr RawTH1 -> (TH1 -> IO r) -> IO r #

type Raw TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.RawType

type Raw TH1 = RawTH1

class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITH1 a where Source #

Methods

add :: (ITH1 c0, FPtr c0) => a -> c0 -> CDouble -> IO () Source #

addBinContent :: a -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => a -> c0 -> IO a Source #

drawNormalized :: Castable c0 CString => a -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: a -> IO () Source #

bufferEmpty :: a -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> IO TH1 Source #

fill1 :: a -> CDouble -> IO CInt Source #

fill1w :: a -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: a -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => a -> c0 -> CInt -> IO () Source #

findBin :: a -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: a -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: a -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: a -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: a -> IO () Source #

getNdivisionA :: Castable c0 CString => a -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => a -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => a -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => a -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => a -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => a -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => a -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => a -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => a -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => a -> c0 -> IO CFloat Source #

getBarOffset :: a -> IO CFloat Source #

getBarWidth :: a -> IO CFloat Source #

getContour :: a -> Ptr CDouble -> IO CInt Source #

getContourLevel :: a -> CInt -> IO CDouble Source #

getContourLevelPad :: a -> CInt -> IO CDouble Source #

getBin :: a -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: a -> CInt -> IO CDouble Source #

getBinContent1 :: a -> CInt -> IO CDouble Source #

getBinContent2 :: a -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: a -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: a -> CInt -> IO CDouble Source #

getBinError2 :: a -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: a -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: a -> CInt -> IO CDouble Source #

getBinWidth :: a -> CInt -> IO CDouble Source #

getCellContent :: a -> CInt -> CInt -> IO CDouble Source #

getCellError :: a -> CInt -> CInt -> IO CDouble Source #

getEntries :: a -> IO CDouble Source #

getEffectiveEntries :: a -> IO CDouble Source #

getFunction :: Castable c0 CString => a -> c0 -> IO TF1 Source #

getDimension :: a -> IO CInt Source #

getKurtosis :: a -> CInt -> IO CDouble Source #

getLowEdge :: a -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: a -> CDouble -> IO CDouble Source #

getMaximumBin :: a -> IO CInt Source #

getMaximumStored :: a -> IO CDouble Source #

getMinimumTH1 :: a -> CDouble -> IO CDouble Source #

getMinimumBin :: a -> IO CInt Source #

getMinimumStored :: a -> IO CDouble Source #

getMean :: a -> CInt -> IO CDouble Source #

getMeanError :: a -> CInt -> IO CDouble Source #

getNbinsX :: a -> IO CDouble Source #

getNbinsY :: a -> IO CDouble Source #

getNbinsZ :: a -> IO CDouble Source #

getQuantilesTH1 :: a -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: a -> IO CDouble Source #

getStats :: a -> Ptr CDouble -> IO () Source #

getSumOfWeights :: a -> IO CDouble Source #

getSumw2 :: a -> IO TArrayD Source #

getSumw2N :: a -> IO CInt Source #

getRMS :: a -> CInt -> IO CDouble Source #

getRMSError :: a -> CInt -> IO CDouble Source #

getSkewness :: a -> CInt -> IO CDouble Source #

interpolate3 :: a -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => a -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => a -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => a -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => a -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: a -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => a -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => a -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => a -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => a -> c0 -> IO () Source #

reset :: Castable c0 CString => a -> c0 -> IO () Source #

resetStats :: a -> IO () Source #

scale :: Castable c0 CString => a -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => a -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => a -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: a -> CFloat -> IO () Source #

setBarWidth :: a -> CFloat -> IO () Source #

setBinContent1 :: a -> CInt -> CDouble -> IO () Source #

setBinContent2 :: a -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: a -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: a -> CInt -> CDouble -> IO () Source #

setBinError2 :: a -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: a -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: a -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: a -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: a -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: a -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => a -> CInt -> c0 -> IO () Source #

setCellContent :: a -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: a -> Ptr CDouble -> IO () Source #

setContour :: a -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: a -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO () Source #

setEntries :: a -> CDouble -> IO () Source #

setError :: a -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => a -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => a -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => a -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => a -> CFloat -> c0 -> IO () Source #

setMaximum :: a -> CDouble -> IO () Source #

setMinimum :: a -> CDouble -> IO () Source #

setNormFactor :: a -> CDouble -> IO () Source #

setStats :: a -> CBool -> IO () Source #

setOption :: Castable c0 CString => a -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => a -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => a -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => a -> c0 -> IO () Source #

showBackground :: Castable c0 CString => a -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => a -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => a -> CInt -> c0 -> IO () Source #

sumw2 :: a -> IO () Source #

Instances

Instances details
ITH1 TH1 Source # 
Instance details

Defined in HROOT.Hist.TH1.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1 -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1 -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1 -> c0 -> IO TH1 Source #

drawNormalized :: Castable c0 CString => TH1 -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1 -> IO () Source #

bufferEmpty :: TH1 -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1 -> CDouble -> IO CInt Source #

fill1w :: TH1 -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CInt -> IO () Source #

findBin :: TH1 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1 -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1 -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1 -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1 -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1 -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1 -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1 -> c0 -> IO CFloat Source #

getBarOffset :: TH1 -> IO CFloat Source #

getBarWidth :: TH1 -> IO CFloat Source #

getContour :: TH1 -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1 -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1 -> CInt -> IO CDouble Source #

getBin :: TH1 -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1 -> CInt -> IO CDouble Source #

getBinContent1 :: TH1 -> CInt -> IO CDouble Source #

getBinContent2 :: TH1 -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1 -> CInt -> IO CDouble Source #

getBinError2 :: TH1 -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1 -> CInt -> IO CDouble Source #

getBinWidth :: TH1 -> CInt -> IO CDouble Source #

getCellContent :: TH1 -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1 -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1 -> IO CDouble Source #

getEffectiveEntries :: TH1 -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1 -> c0 -> IO TF1 Source #

getDimension :: TH1 -> IO CInt Source #

getKurtosis :: TH1 -> CInt -> IO CDouble Source #

getLowEdge :: TH1 -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1 -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1 -> IO CInt Source #

getMaximumStored :: TH1 -> IO CDouble Source #

getMinimumTH1 :: TH1 -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1 -> IO CInt Source #

getMinimumStored :: TH1 -> IO CDouble Source #

getMean :: TH1 -> CInt -> IO CDouble Source #

getMeanError :: TH1 -> CInt -> IO CDouble Source #

getNbinsX :: TH1 -> IO CDouble Source #

getNbinsY :: TH1 -> IO CDouble Source #

getNbinsZ :: TH1 -> IO CDouble Source #

getQuantilesTH1 :: TH1 -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1 -> IO CDouble Source #

getStats :: TH1 -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1 -> IO CDouble Source #

getSumw2 :: TH1 -> IO TArrayD Source #

getSumw2N :: TH1 -> IO CInt Source #

getRMS :: TH1 -> CInt -> IO CDouble Source #

getRMSError :: TH1 -> CInt -> IO CDouble Source #

getSkewness :: TH1 -> CInt -> IO CDouble Source #

interpolate3 :: TH1 -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1 -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1 -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1 -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1 -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1 -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1 -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1 -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1 -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1 -> c0 -> IO () Source #

resetStats :: TH1 -> IO () Source #

scale :: Castable c0 CString => TH1 -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1 -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1 -> CFloat -> IO () Source #

setBarWidth :: TH1 -> CFloat -> IO () Source #

setBinContent1 :: TH1 -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1 -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1 -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1 -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1 -> CInt -> c0 -> IO () Source #

setCellContent :: TH1 -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1 -> Ptr CDouble -> IO () Source #

setContour :: TH1 -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1 -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1 -> c0 -> IO () Source #

setEntries :: TH1 -> CDouble -> IO () Source #

setError :: TH1 -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1 -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1 -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1 -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1 -> CDouble -> IO () Source #

setMinimum :: TH1 -> CDouble -> IO () Source #

setNormFactor :: TH1 -> CDouble -> IO () Source #

setStats :: TH1 -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1 -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1 -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1 -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1 -> CInt -> c0 -> IO () Source #

sumw2 :: TH1 -> IO () Source #

ITH1 TH1C Source # 
Instance details

Defined in HROOT.Hist.TH1C.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1C -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1C -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1C -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1C -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1C -> c0 -> IO TH1C Source #

drawNormalized :: Castable c0 CString => TH1C -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1C -> IO () Source #

bufferEmpty :: TH1C -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1C -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1C -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1C -> CDouble -> IO CInt Source #

fill1w :: TH1C -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1C -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1C -> c0 -> CInt -> IO () Source #

findBin :: TH1C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1C -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1C -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1C -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1C -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1C -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1C -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1C -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1C -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1C -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1C -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1C -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1C -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1C -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1C -> c0 -> IO CFloat Source #

getBarOffset :: TH1C -> IO CFloat Source #

getBarWidth :: TH1C -> IO CFloat Source #

getContour :: TH1C -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1C -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1C -> CInt -> IO CDouble Source #

getBin :: TH1C -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1C -> CInt -> IO CDouble Source #

getBinContent1 :: TH1C -> CInt -> IO CDouble Source #

getBinContent2 :: TH1C -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1C -> CInt -> IO CDouble Source #

getBinError2 :: TH1C -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1C -> CInt -> IO CDouble Source #

getBinWidth :: TH1C -> CInt -> IO CDouble Source #

getCellContent :: TH1C -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1C -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1C -> IO CDouble Source #

getEffectiveEntries :: TH1C -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1C -> c0 -> IO TF1 Source #

getDimension :: TH1C -> IO CInt Source #

getKurtosis :: TH1C -> CInt -> IO CDouble Source #

getLowEdge :: TH1C -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1C -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1C -> IO CInt Source #

getMaximumStored :: TH1C -> IO CDouble Source #

getMinimumTH1 :: TH1C -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1C -> IO CInt Source #

getMinimumStored :: TH1C -> IO CDouble Source #

getMean :: TH1C -> CInt -> IO CDouble Source #

getMeanError :: TH1C -> CInt -> IO CDouble Source #

getNbinsX :: TH1C -> IO CDouble Source #

getNbinsY :: TH1C -> IO CDouble Source #

getNbinsZ :: TH1C -> IO CDouble Source #

getQuantilesTH1 :: TH1C -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1C -> IO CDouble Source #

getStats :: TH1C -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1C -> IO CDouble Source #

getSumw2 :: TH1C -> IO TArrayD Source #

getSumw2N :: TH1C -> IO CInt Source #

getRMS :: TH1C -> CInt -> IO CDouble Source #

getRMSError :: TH1C -> CInt -> IO CDouble Source #

getSkewness :: TH1C -> CInt -> IO CDouble Source #

interpolate3 :: TH1C -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1C -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1C -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1C -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1C -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1C -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1C -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1C -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1C -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1C -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1C -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1C -> c0 -> IO () Source #

resetStats :: TH1C -> IO () Source #

scale :: Castable c0 CString => TH1C -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1C -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1C -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1C -> CFloat -> IO () Source #

setBarWidth :: TH1C -> CFloat -> IO () Source #

setBinContent1 :: TH1C -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1C -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1C -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1C -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1C -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1C -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1C -> CInt -> c0 -> IO () Source #

setCellContent :: TH1C -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1C -> Ptr CDouble -> IO () Source #

setContour :: TH1C -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1C -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1C -> c0 -> IO () Source #

setEntries :: TH1C -> CDouble -> IO () Source #

setError :: TH1C -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1C -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1C -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1C -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1C -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1C -> CDouble -> IO () Source #

setMinimum :: TH1C -> CDouble -> IO () Source #

setNormFactor :: TH1C -> CDouble -> IO () Source #

setStats :: TH1C -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1C -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1C -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1C -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1C -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1C -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1C -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1C -> CInt -> c0 -> IO () Source #

sumw2 :: TH1C -> IO () Source #

ITH1 TH1D Source # 
Instance details

Defined in HROOT.Hist.TH1D.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1D -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1D -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1D -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1D -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1D -> c0 -> IO TH1D Source #

drawNormalized :: Castable c0 CString => TH1D -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1D -> IO () Source #

bufferEmpty :: TH1D -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1D -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1D -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1D -> CDouble -> IO CInt Source #

fill1w :: TH1D -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1D -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1D -> c0 -> CInt -> IO () Source #

findBin :: TH1D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1D -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1D -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1D -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1D -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1D -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1D -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1D -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1D -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1D -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1D -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1D -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1D -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1D -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1D -> c0 -> IO CFloat Source #

getBarOffset :: TH1D -> IO CFloat Source #

getBarWidth :: TH1D -> IO CFloat Source #

getContour :: TH1D -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1D -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1D -> CInt -> IO CDouble Source #

getBin :: TH1D -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1D -> CInt -> IO CDouble Source #

getBinContent1 :: TH1D -> CInt -> IO CDouble Source #

getBinContent2 :: TH1D -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1D -> CInt -> IO CDouble Source #

getBinError2 :: TH1D -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1D -> CInt -> IO CDouble Source #

getBinWidth :: TH1D -> CInt -> IO CDouble Source #

getCellContent :: TH1D -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1D -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1D -> IO CDouble Source #

getEffectiveEntries :: TH1D -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1D -> c0 -> IO TF1 Source #

getDimension :: TH1D -> IO CInt Source #

getKurtosis :: TH1D -> CInt -> IO CDouble Source #

getLowEdge :: TH1D -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1D -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1D -> IO CInt Source #

getMaximumStored :: TH1D -> IO CDouble Source #

getMinimumTH1 :: TH1D -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1D -> IO CInt Source #

getMinimumStored :: TH1D -> IO CDouble Source #

getMean :: TH1D -> CInt -> IO CDouble Source #

getMeanError :: TH1D -> CInt -> IO CDouble Source #

getNbinsX :: TH1D -> IO CDouble Source #

getNbinsY :: TH1D -> IO CDouble Source #

getNbinsZ :: TH1D -> IO CDouble Source #

getQuantilesTH1 :: TH1D -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1D -> IO CDouble Source #

getStats :: TH1D -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1D -> IO CDouble Source #

getSumw2 :: TH1D -> IO TArrayD Source #

getSumw2N :: TH1D -> IO CInt Source #

getRMS :: TH1D -> CInt -> IO CDouble Source #

getRMSError :: TH1D -> CInt -> IO CDouble Source #

getSkewness :: TH1D -> CInt -> IO CDouble Source #

interpolate3 :: TH1D -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1D -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1D -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1D -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1D -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1D -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1D -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1D -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1D -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1D -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1D -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1D -> c0 -> IO () Source #

resetStats :: TH1D -> IO () Source #

scale :: Castable c0 CString => TH1D -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1D -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1D -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1D -> CFloat -> IO () Source #

setBarWidth :: TH1D -> CFloat -> IO () Source #

setBinContent1 :: TH1D -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1D -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1D -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1D -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1D -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1D -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1D -> CInt -> c0 -> IO () Source #

setCellContent :: TH1D -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1D -> Ptr CDouble -> IO () Source #

setContour :: TH1D -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1D -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1D -> c0 -> IO () Source #

setEntries :: TH1D -> CDouble -> IO () Source #

setError :: TH1D -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1D -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1D -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1D -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1D -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1D -> CDouble -> IO () Source #

setMinimum :: TH1D -> CDouble -> IO () Source #

setNormFactor :: TH1D -> CDouble -> IO () Source #

setStats :: TH1D -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1D -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1D -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1D -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1D -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1D -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1D -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1D -> CInt -> c0 -> IO () Source #

sumw2 :: TH1D -> IO () Source #

ITH1 TH1F Source # 
Instance details

Defined in HROOT.Hist.TH1F.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1F -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1F -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1F -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1F -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1F -> c0 -> IO TH1F Source #

drawNormalized :: Castable c0 CString => TH1F -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1F -> IO () Source #

bufferEmpty :: TH1F -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1F -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1F -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1F -> CDouble -> IO CInt Source #

fill1w :: TH1F -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1F -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1F -> c0 -> CInt -> IO () Source #

findBin :: TH1F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1F -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1F -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1F -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1F -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1F -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1F -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1F -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1F -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1F -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1F -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1F -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1F -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1F -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1F -> c0 -> IO CFloat Source #

getBarOffset :: TH1F -> IO CFloat Source #

getBarWidth :: TH1F -> IO CFloat Source #

getContour :: TH1F -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1F -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1F -> CInt -> IO CDouble Source #

getBin :: TH1F -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1F -> CInt -> IO CDouble Source #

getBinContent1 :: TH1F -> CInt -> IO CDouble Source #

getBinContent2 :: TH1F -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1F -> CInt -> IO CDouble Source #

getBinError2 :: TH1F -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1F -> CInt -> IO CDouble Source #

getBinWidth :: TH1F -> CInt -> IO CDouble Source #

getCellContent :: TH1F -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1F -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1F -> IO CDouble Source #

getEffectiveEntries :: TH1F -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1F -> c0 -> IO TF1 Source #

getDimension :: TH1F -> IO CInt Source #

getKurtosis :: TH1F -> CInt -> IO CDouble Source #

getLowEdge :: TH1F -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1F -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1F -> IO CInt Source #

getMaximumStored :: TH1F -> IO CDouble Source #

getMinimumTH1 :: TH1F -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1F -> IO CInt Source #

getMinimumStored :: TH1F -> IO CDouble Source #

getMean :: TH1F -> CInt -> IO CDouble Source #

getMeanError :: TH1F -> CInt -> IO CDouble Source #

getNbinsX :: TH1F -> IO CDouble Source #

getNbinsY :: TH1F -> IO CDouble Source #

getNbinsZ :: TH1F -> IO CDouble Source #

getQuantilesTH1 :: TH1F -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1F -> IO CDouble Source #

getStats :: TH1F -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1F -> IO CDouble Source #

getSumw2 :: TH1F -> IO TArrayD Source #

getSumw2N :: TH1F -> IO CInt Source #

getRMS :: TH1F -> CInt -> IO CDouble Source #

getRMSError :: TH1F -> CInt -> IO CDouble Source #

getSkewness :: TH1F -> CInt -> IO CDouble Source #

interpolate3 :: TH1F -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1F -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1F -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1F -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1F -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1F -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1F -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1F -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1F -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1F -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1F -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1F -> c0 -> IO () Source #

resetStats :: TH1F -> IO () Source #

scale :: Castable c0 CString => TH1F -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1F -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1F -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1F -> CFloat -> IO () Source #

setBarWidth :: TH1F -> CFloat -> IO () Source #

setBinContent1 :: TH1F -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1F -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1F -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1F -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1F -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1F -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1F -> CInt -> c0 -> IO () Source #

setCellContent :: TH1F -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1F -> Ptr CDouble -> IO () Source #

setContour :: TH1F -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1F -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1F -> c0 -> IO () Source #

setEntries :: TH1F -> CDouble -> IO () Source #

setError :: TH1F -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1F -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1F -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1F -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1F -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1F -> CDouble -> IO () Source #

setMinimum :: TH1F -> CDouble -> IO () Source #

setNormFactor :: TH1F -> CDouble -> IO () Source #

setStats :: TH1F -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1F -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1F -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1F -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1F -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1F -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1F -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1F -> CInt -> c0 -> IO () Source #

sumw2 :: TH1F -> IO () Source #

ITH1 TH1I Source # 
Instance details

Defined in HROOT.Hist.TH1I.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1I -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1I -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1I -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1I -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1I -> c0 -> IO TH1I Source #

drawNormalized :: Castable c0 CString => TH1I -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1I -> IO () Source #

bufferEmpty :: TH1I -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1I -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1I -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1I -> CDouble -> IO CInt Source #

fill1w :: TH1I -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1I -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1I -> c0 -> CInt -> IO () Source #

findBin :: TH1I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1I -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1I -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1I -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1I -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1I -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1I -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1I -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1I -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1I -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1I -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1I -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1I -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1I -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1I -> c0 -> IO CFloat Source #

getBarOffset :: TH1I -> IO CFloat Source #

getBarWidth :: TH1I -> IO CFloat Source #

getContour :: TH1I -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1I -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1I -> CInt -> IO CDouble Source #

getBin :: TH1I -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1I -> CInt -> IO CDouble Source #

getBinContent1 :: TH1I -> CInt -> IO CDouble Source #

getBinContent2 :: TH1I -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1I -> CInt -> IO CDouble Source #

getBinError2 :: TH1I -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1I -> CInt -> IO CDouble Source #

getBinWidth :: TH1I -> CInt -> IO CDouble Source #

getCellContent :: TH1I -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1I -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1I -> IO CDouble Source #

getEffectiveEntries :: TH1I -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1I -> c0 -> IO TF1 Source #

getDimension :: TH1I -> IO CInt Source #

getKurtosis :: TH1I -> CInt -> IO CDouble Source #

getLowEdge :: TH1I -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1I -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1I -> IO CInt Source #

getMaximumStored :: TH1I -> IO CDouble Source #

getMinimumTH1 :: TH1I -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1I -> IO CInt Source #

getMinimumStored :: TH1I -> IO CDouble Source #

getMean :: TH1I -> CInt -> IO CDouble Source #

getMeanError :: TH1I -> CInt -> IO CDouble Source #

getNbinsX :: TH1I -> IO CDouble Source #

getNbinsY :: TH1I -> IO CDouble Source #

getNbinsZ :: TH1I -> IO CDouble Source #

getQuantilesTH1 :: TH1I -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1I -> IO CDouble Source #

getStats :: TH1I -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1I -> IO CDouble Source #

getSumw2 :: TH1I -> IO TArrayD Source #

getSumw2N :: TH1I -> IO CInt Source #

getRMS :: TH1I -> CInt -> IO CDouble Source #

getRMSError :: TH1I -> CInt -> IO CDouble Source #

getSkewness :: TH1I -> CInt -> IO CDouble Source #

interpolate3 :: TH1I -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1I -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1I -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1I -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1I -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1I -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1I -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1I -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1I -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1I -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1I -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1I -> c0 -> IO () Source #

resetStats :: TH1I -> IO () Source #

scale :: Castable c0 CString => TH1I -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1I -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1I -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1I -> CFloat -> IO () Source #

setBarWidth :: TH1I -> CFloat -> IO () Source #

setBinContent1 :: TH1I -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1I -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1I -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1I -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1I -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1I -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1I -> CInt -> c0 -> IO () Source #

setCellContent :: TH1I -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1I -> Ptr CDouble -> IO () Source #

setContour :: TH1I -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1I -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1I -> c0 -> IO () Source #

setEntries :: TH1I -> CDouble -> IO () Source #

setError :: TH1I -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1I -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1I -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1I -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1I -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1I -> CDouble -> IO () Source #

setMinimum :: TH1I -> CDouble -> IO () Source #

setNormFactor :: TH1I -> CDouble -> IO () Source #

setStats :: TH1I -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1I -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1I -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1I -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1I -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1I -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1I -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1I -> CInt -> c0 -> IO () Source #

sumw2 :: TH1I -> IO () Source #

ITH1 TH1K Source # 
Instance details

Defined in HROOT.Hist.TH1K.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1K -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1K -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1K -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1K -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1K -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1K -> c0 -> IO TH1K Source #

drawNormalized :: Castable c0 CString => TH1K -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1K -> IO () Source #

bufferEmpty :: TH1K -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1K -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1K -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1K -> CDouble -> IO CInt Source #

fill1w :: TH1K -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1K -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1K -> c0 -> CInt -> IO () Source #

findBin :: TH1K -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1K -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1K -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1K -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1K -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1K -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1K -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1K -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1K -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1K -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1K -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1K -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1K -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1K -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1K -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1K -> c0 -> IO CFloat Source #

getBarOffset :: TH1K -> IO CFloat Source #

getBarWidth :: TH1K -> IO CFloat Source #

getContour :: TH1K -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1K -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1K -> CInt -> IO CDouble Source #

getBin :: TH1K -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1K -> CInt -> IO CDouble Source #

getBinContent1 :: TH1K -> CInt -> IO CDouble Source #

getBinContent2 :: TH1K -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1K -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1K -> CInt -> IO CDouble Source #

getBinError2 :: TH1K -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1K -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1K -> CInt -> IO CDouble Source #

getBinWidth :: TH1K -> CInt -> IO CDouble Source #

getCellContent :: TH1K -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1K -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1K -> IO CDouble Source #

getEffectiveEntries :: TH1K -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1K -> c0 -> IO TF1 Source #

getDimension :: TH1K -> IO CInt Source #

getKurtosis :: TH1K -> CInt -> IO CDouble Source #

getLowEdge :: TH1K -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1K -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1K -> IO CInt Source #

getMaximumStored :: TH1K -> IO CDouble Source #

getMinimumTH1 :: TH1K -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1K -> IO CInt Source #

getMinimumStored :: TH1K -> IO CDouble Source #

getMean :: TH1K -> CInt -> IO CDouble Source #

getMeanError :: TH1K -> CInt -> IO CDouble Source #

getNbinsX :: TH1K -> IO CDouble Source #

getNbinsY :: TH1K -> IO CDouble Source #

getNbinsZ :: TH1K -> IO CDouble Source #

getQuantilesTH1 :: TH1K -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1K -> IO CDouble Source #

getStats :: TH1K -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1K -> IO CDouble Source #

getSumw2 :: TH1K -> IO TArrayD Source #

getSumw2N :: TH1K -> IO CInt Source #

getRMS :: TH1K -> CInt -> IO CDouble Source #

getRMSError :: TH1K -> CInt -> IO CDouble Source #

getSkewness :: TH1K -> CInt -> IO CDouble Source #

interpolate3 :: TH1K -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1K -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1K -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1K -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1K -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1K -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1K -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1K -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1K -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1K -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1K -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1K -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1K -> c0 -> IO () Source #

resetStats :: TH1K -> IO () Source #

scale :: Castable c0 CString => TH1K -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1K -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1K -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1K -> CFloat -> IO () Source #

setBarWidth :: TH1K -> CFloat -> IO () Source #

setBinContent1 :: TH1K -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1K -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1K -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1K -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1K -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1K -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1K -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1K -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1K -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1K -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1K -> CInt -> c0 -> IO () Source #

setCellContent :: TH1K -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1K -> Ptr CDouble -> IO () Source #

setContour :: TH1K -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1K -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1K -> c0 -> IO () Source #

setEntries :: TH1K -> CDouble -> IO () Source #

setError :: TH1K -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1K -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1K -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1K -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1K -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1K -> CDouble -> IO () Source #

setMinimum :: TH1K -> CDouble -> IO () Source #

setNormFactor :: TH1K -> CDouble -> IO () Source #

setStats :: TH1K -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1K -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1K -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1K -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1K -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1K -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1K -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1K -> CInt -> c0 -> IO () Source #

sumw2 :: TH1K -> IO () Source #

ITH1 TH1S Source # 
Instance details

Defined in HROOT.Hist.TH1S.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH1S -> c0 -> CDouble -> IO () Source #

addBinContent :: TH1S -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1S -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH1S -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH1S -> c0 -> IO TH1S Source #

drawNormalized :: Castable c0 CString => TH1S -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH1S -> IO () Source #

bufferEmpty :: TH1S -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH1S -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1S -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH1S -> CDouble -> IO CInt Source #

fill1w :: TH1S -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH1S -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH1S -> c0 -> CInt -> IO () Source #

findBin :: TH1S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH1S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH1S -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH1S -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH1S -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH1S -> IO () Source #

getNdivisionA :: Castable c0 CString => TH1S -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH1S -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH1S -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH1S -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH1S -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH1S -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH1S -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH1S -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH1S -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH1S -> c0 -> IO CFloat Source #

getBarOffset :: TH1S -> IO CFloat Source #

getBarWidth :: TH1S -> IO CFloat Source #

getContour :: TH1S -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH1S -> CInt -> IO CDouble Source #

getContourLevelPad :: TH1S -> CInt -> IO CDouble Source #

getBin :: TH1S -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH1S -> CInt -> IO CDouble Source #

getBinContent1 :: TH1S -> CInt -> IO CDouble Source #

getBinContent2 :: TH1S -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH1S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH1S -> CInt -> IO CDouble Source #

getBinError2 :: TH1S -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH1S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH1S -> CInt -> IO CDouble Source #

getBinWidth :: TH1S -> CInt -> IO CDouble Source #

getCellContent :: TH1S -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH1S -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH1S -> IO CDouble Source #

getEffectiveEntries :: TH1S -> IO CDouble Source #

getFunction :: Castable c0 CString => TH1S -> c0 -> IO TF1 Source #

getDimension :: TH1S -> IO CInt Source #

getKurtosis :: TH1S -> CInt -> IO CDouble Source #

getLowEdge :: TH1S -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH1S -> CDouble -> IO CDouble Source #

getMaximumBin :: TH1S -> IO CInt Source #

getMaximumStored :: TH1S -> IO CDouble Source #

getMinimumTH1 :: TH1S -> CDouble -> IO CDouble Source #

getMinimumBin :: TH1S -> IO CInt Source #

getMinimumStored :: TH1S -> IO CDouble Source #

getMean :: TH1S -> CInt -> IO CDouble Source #

getMeanError :: TH1S -> CInt -> IO CDouble Source #

getNbinsX :: TH1S -> IO CDouble Source #

getNbinsY :: TH1S -> IO CDouble Source #

getNbinsZ :: TH1S -> IO CDouble Source #

getQuantilesTH1 :: TH1S -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH1S -> IO CDouble Source #

getStats :: TH1S -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH1S -> IO CDouble Source #

getSumw2 :: TH1S -> IO TArrayD Source #

getSumw2N :: TH1S -> IO CInt Source #

getRMS :: TH1S -> CInt -> IO CDouble Source #

getRMSError :: TH1S -> CInt -> IO CDouble Source #

getSkewness :: TH1S -> CInt -> IO CDouble Source #

interpolate3 :: TH1S -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH1S -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH1S -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH1S -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH1S -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH1S -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH1S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH1S -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH1S -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH1S -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH1S -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH1S -> c0 -> IO () Source #

reset :: Castable c0 CString => TH1S -> c0 -> IO () Source #

resetStats :: TH1S -> IO () Source #

scale :: Castable c0 CString => TH1S -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH1S -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH1S -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH1S -> CFloat -> IO () Source #

setBarWidth :: TH1S -> CFloat -> IO () Source #

setBinContent1 :: TH1S -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH1S -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH1S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH1S -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH1S -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH1S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH1S -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH1S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH1S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH1S -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH1S -> CInt -> c0 -> IO () Source #

setCellContent :: TH1S -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH1S -> Ptr CDouble -> IO () Source #

setContour :: TH1S -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH1S -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH1S -> c0 -> IO () Source #

setEntries :: TH1S -> CDouble -> IO () Source #

setError :: TH1S -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH1S -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH1S -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH1S -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH1S -> CFloat -> c0 -> IO () Source #

setMaximum :: TH1S -> CDouble -> IO () Source #

setMinimum :: TH1S -> CDouble -> IO () Source #

setNormFactor :: TH1S -> CDouble -> IO () Source #

setStats :: TH1S -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH1S -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH1S -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH1S -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH1S -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH1S -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH1S -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH1S -> CInt -> c0 -> IO () Source #

sumw2 :: TH1S -> IO () Source #

ITH1 TH2 Source # 
Instance details

Defined in HROOT.Hist.TH2.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2 -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2 -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2 -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2 -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2 -> c0 -> IO TH2 Source #

drawNormalized :: Castable c0 CString => TH2 -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2 -> IO () Source #

bufferEmpty :: TH2 -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2 -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2 -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2 -> CDouble -> IO CInt Source #

fill1w :: TH2 -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2 -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2 -> c0 -> CInt -> IO () Source #

findBin :: TH2 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2 -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2 -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2 -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2 -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2 -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2 -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2 -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2 -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2 -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2 -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2 -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2 -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2 -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2 -> c0 -> IO CFloat Source #

getBarOffset :: TH2 -> IO CFloat Source #

getBarWidth :: TH2 -> IO CFloat Source #

getContour :: TH2 -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2 -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2 -> CInt -> IO CDouble Source #

getBin :: TH2 -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2 -> CInt -> IO CDouble Source #

getBinContent1 :: TH2 -> CInt -> IO CDouble Source #

getBinContent2 :: TH2 -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2 -> CInt -> IO CDouble Source #

getBinError2 :: TH2 -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2 -> CInt -> IO CDouble Source #

getBinWidth :: TH2 -> CInt -> IO CDouble Source #

getCellContent :: TH2 -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2 -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2 -> IO CDouble Source #

getEffectiveEntries :: TH2 -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2 -> c0 -> IO TF1 Source #

getDimension :: TH2 -> IO CInt Source #

getKurtosis :: TH2 -> CInt -> IO CDouble Source #

getLowEdge :: TH2 -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2 -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2 -> IO CInt Source #

getMaximumStored :: TH2 -> IO CDouble Source #

getMinimumTH1 :: TH2 -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2 -> IO CInt Source #

getMinimumStored :: TH2 -> IO CDouble Source #

getMean :: TH2 -> CInt -> IO CDouble Source #

getMeanError :: TH2 -> CInt -> IO CDouble Source #

getNbinsX :: TH2 -> IO CDouble Source #

getNbinsY :: TH2 -> IO CDouble Source #

getNbinsZ :: TH2 -> IO CDouble Source #

getQuantilesTH1 :: TH2 -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2 -> IO CDouble Source #

getStats :: TH2 -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2 -> IO CDouble Source #

getSumw2 :: TH2 -> IO TArrayD Source #

getSumw2N :: TH2 -> IO CInt Source #

getRMS :: TH2 -> CInt -> IO CDouble Source #

getRMSError :: TH2 -> CInt -> IO CDouble Source #

getSkewness :: TH2 -> CInt -> IO CDouble Source #

interpolate3 :: TH2 -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2 -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2 -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2 -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2 -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2 -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2 -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2 -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2 -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2 -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2 -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2 -> c0 -> IO () Source #

resetStats :: TH2 -> IO () Source #

scale :: Castable c0 CString => TH2 -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2 -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2 -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2 -> CFloat -> IO () Source #

setBarWidth :: TH2 -> CFloat -> IO () Source #

setBinContent1 :: TH2 -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2 -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2 -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2 -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2 -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2 -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2 -> CInt -> c0 -> IO () Source #

setCellContent :: TH2 -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2 -> Ptr CDouble -> IO () Source #

setContour :: TH2 -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2 -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2 -> c0 -> IO () Source #

setEntries :: TH2 -> CDouble -> IO () Source #

setError :: TH2 -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2 -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2 -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2 -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2 -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2 -> CDouble -> IO () Source #

setMinimum :: TH2 -> CDouble -> IO () Source #

setNormFactor :: TH2 -> CDouble -> IO () Source #

setStats :: TH2 -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2 -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2 -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2 -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2 -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2 -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2 -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2 -> CInt -> c0 -> IO () Source #

sumw2 :: TH2 -> IO () Source #

ITH1 TH2C Source # 
Instance details

Defined in HROOT.Hist.TH2C.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2C -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2C -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2C -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2C -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2C -> c0 -> IO TH2C Source #

drawNormalized :: Castable c0 CString => TH2C -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2C -> IO () Source #

bufferEmpty :: TH2C -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2C -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2C -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2C -> CDouble -> IO CInt Source #

fill1w :: TH2C -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2C -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2C -> c0 -> CInt -> IO () Source #

findBin :: TH2C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2C -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2C -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2C -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2C -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2C -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2C -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2C -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2C -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2C -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2C -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2C -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2C -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2C -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2C -> c0 -> IO CFloat Source #

getBarOffset :: TH2C -> IO CFloat Source #

getBarWidth :: TH2C -> IO CFloat Source #

getContour :: TH2C -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2C -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2C -> CInt -> IO CDouble Source #

getBin :: TH2C -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2C -> CInt -> IO CDouble Source #

getBinContent1 :: TH2C -> CInt -> IO CDouble Source #

getBinContent2 :: TH2C -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2C -> CInt -> IO CDouble Source #

getBinError2 :: TH2C -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2C -> CInt -> IO CDouble Source #

getBinWidth :: TH2C -> CInt -> IO CDouble Source #

getCellContent :: TH2C -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2C -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2C -> IO CDouble Source #

getEffectiveEntries :: TH2C -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2C -> c0 -> IO TF1 Source #

getDimension :: TH2C -> IO CInt Source #

getKurtosis :: TH2C -> CInt -> IO CDouble Source #

getLowEdge :: TH2C -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2C -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2C -> IO CInt Source #

getMaximumStored :: TH2C -> IO CDouble Source #

getMinimumTH1 :: TH2C -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2C -> IO CInt Source #

getMinimumStored :: TH2C -> IO CDouble Source #

getMean :: TH2C -> CInt -> IO CDouble Source #

getMeanError :: TH2C -> CInt -> IO CDouble Source #

getNbinsX :: TH2C -> IO CDouble Source #

getNbinsY :: TH2C -> IO CDouble Source #

getNbinsZ :: TH2C -> IO CDouble Source #

getQuantilesTH1 :: TH2C -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2C -> IO CDouble Source #

getStats :: TH2C -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2C -> IO CDouble Source #

getSumw2 :: TH2C -> IO TArrayD Source #

getSumw2N :: TH2C -> IO CInt Source #

getRMS :: TH2C -> CInt -> IO CDouble Source #

getRMSError :: TH2C -> CInt -> IO CDouble Source #

getSkewness :: TH2C -> CInt -> IO CDouble Source #

interpolate3 :: TH2C -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2C -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2C -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2C -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2C -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2C -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2C -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2C -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2C -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2C -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2C -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2C -> c0 -> IO () Source #

resetStats :: TH2C -> IO () Source #

scale :: Castable c0 CString => TH2C -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2C -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2C -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2C -> CFloat -> IO () Source #

setBarWidth :: TH2C -> CFloat -> IO () Source #

setBinContent1 :: TH2C -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2C -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2C -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2C -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2C -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2C -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2C -> CInt -> c0 -> IO () Source #

setCellContent :: TH2C -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2C -> Ptr CDouble -> IO () Source #

setContour :: TH2C -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2C -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2C -> c0 -> IO () Source #

setEntries :: TH2C -> CDouble -> IO () Source #

setError :: TH2C -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2C -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2C -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2C -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2C -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2C -> CDouble -> IO () Source #

setMinimum :: TH2C -> CDouble -> IO () Source #

setNormFactor :: TH2C -> CDouble -> IO () Source #

setStats :: TH2C -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2C -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2C -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2C -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2C -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2C -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2C -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2C -> CInt -> c0 -> IO () Source #

sumw2 :: TH2C -> IO () Source #

ITH1 TH2D Source # 
Instance details

Defined in HROOT.Hist.TH2D.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2D -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2D -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2D -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2D -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2D -> c0 -> IO TH2D Source #

drawNormalized :: Castable c0 CString => TH2D -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2D -> IO () Source #

bufferEmpty :: TH2D -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2D -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2D -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2D -> CDouble -> IO CInt Source #

fill1w :: TH2D -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2D -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2D -> c0 -> CInt -> IO () Source #

findBin :: TH2D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2D -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2D -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2D -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2D -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2D -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2D -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2D -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2D -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2D -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2D -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2D -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2D -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2D -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2D -> c0 -> IO CFloat Source #

getBarOffset :: TH2D -> IO CFloat Source #

getBarWidth :: TH2D -> IO CFloat Source #

getContour :: TH2D -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2D -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2D -> CInt -> IO CDouble Source #

getBin :: TH2D -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2D -> CInt -> IO CDouble Source #

getBinContent1 :: TH2D -> CInt -> IO CDouble Source #

getBinContent2 :: TH2D -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2D -> CInt -> IO CDouble Source #

getBinError2 :: TH2D -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2D -> CInt -> IO CDouble Source #

getBinWidth :: TH2D -> CInt -> IO CDouble Source #

getCellContent :: TH2D -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2D -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2D -> IO CDouble Source #

getEffectiveEntries :: TH2D -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2D -> c0 -> IO TF1 Source #

getDimension :: TH2D -> IO CInt Source #

getKurtosis :: TH2D -> CInt -> IO CDouble Source #

getLowEdge :: TH2D -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2D -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2D -> IO CInt Source #

getMaximumStored :: TH2D -> IO CDouble Source #

getMinimumTH1 :: TH2D -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2D -> IO CInt Source #

getMinimumStored :: TH2D -> IO CDouble Source #

getMean :: TH2D -> CInt -> IO CDouble Source #

getMeanError :: TH2D -> CInt -> IO CDouble Source #

getNbinsX :: TH2D -> IO CDouble Source #

getNbinsY :: TH2D -> IO CDouble Source #

getNbinsZ :: TH2D -> IO CDouble Source #

getQuantilesTH1 :: TH2D -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2D -> IO CDouble Source #

getStats :: TH2D -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2D -> IO CDouble Source #

getSumw2 :: TH2D -> IO TArrayD Source #

getSumw2N :: TH2D -> IO CInt Source #

getRMS :: TH2D -> CInt -> IO CDouble Source #

getRMSError :: TH2D -> CInt -> IO CDouble Source #

getSkewness :: TH2D -> CInt -> IO CDouble Source #

interpolate3 :: TH2D -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2D -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2D -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2D -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2D -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2D -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2D -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2D -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2D -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2D -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2D -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2D -> c0 -> IO () Source #

resetStats :: TH2D -> IO () Source #

scale :: Castable c0 CString => TH2D -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2D -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2D -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2D -> CFloat -> IO () Source #

setBarWidth :: TH2D -> CFloat -> IO () Source #

setBinContent1 :: TH2D -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2D -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2D -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2D -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2D -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2D -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2D -> CInt -> c0 -> IO () Source #

setCellContent :: TH2D -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2D -> Ptr CDouble -> IO () Source #

setContour :: TH2D -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2D -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2D -> c0 -> IO () Source #

setEntries :: TH2D -> CDouble -> IO () Source #

setError :: TH2D -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2D -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2D -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2D -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2D -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2D -> CDouble -> IO () Source #

setMinimum :: TH2D -> CDouble -> IO () Source #

setNormFactor :: TH2D -> CDouble -> IO () Source #

setStats :: TH2D -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2D -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2D -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2D -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2D -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2D -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2D -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2D -> CInt -> c0 -> IO () Source #

sumw2 :: TH2D -> IO () Source #

ITH1 TH2F Source # 
Instance details

Defined in HROOT.Hist.TH2F.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2F -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2F -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2F -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2F -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2F -> c0 -> IO TH2F Source #

drawNormalized :: Castable c0 CString => TH2F -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2F -> IO () Source #

bufferEmpty :: TH2F -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2F -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2F -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2F -> CDouble -> IO CInt Source #

fill1w :: TH2F -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2F -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2F -> c0 -> CInt -> IO () Source #

findBin :: TH2F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2F -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2F -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2F -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2F -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2F -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2F -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2F -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2F -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2F -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2F -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2F -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2F -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2F -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2F -> c0 -> IO CFloat Source #

getBarOffset :: TH2F -> IO CFloat Source #

getBarWidth :: TH2F -> IO CFloat Source #

getContour :: TH2F -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2F -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2F -> CInt -> IO CDouble Source #

getBin :: TH2F -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2F -> CInt -> IO CDouble Source #

getBinContent1 :: TH2F -> CInt -> IO CDouble Source #

getBinContent2 :: TH2F -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2F -> CInt -> IO CDouble Source #

getBinError2 :: TH2F -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2F -> CInt -> IO CDouble Source #

getBinWidth :: TH2F -> CInt -> IO CDouble Source #

getCellContent :: TH2F -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2F -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2F -> IO CDouble Source #

getEffectiveEntries :: TH2F -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2F -> c0 -> IO TF1 Source #

getDimension :: TH2F -> IO CInt Source #

getKurtosis :: TH2F -> CInt -> IO CDouble Source #

getLowEdge :: TH2F -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2F -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2F -> IO CInt Source #

getMaximumStored :: TH2F -> IO CDouble Source #

getMinimumTH1 :: TH2F -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2F -> IO CInt Source #

getMinimumStored :: TH2F -> IO CDouble Source #

getMean :: TH2F -> CInt -> IO CDouble Source #

getMeanError :: TH2F -> CInt -> IO CDouble Source #

getNbinsX :: TH2F -> IO CDouble Source #

getNbinsY :: TH2F -> IO CDouble Source #

getNbinsZ :: TH2F -> IO CDouble Source #

getQuantilesTH1 :: TH2F -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2F -> IO CDouble Source #

getStats :: TH2F -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2F -> IO CDouble Source #

getSumw2 :: TH2F -> IO TArrayD Source #

getSumw2N :: TH2F -> IO CInt Source #

getRMS :: TH2F -> CInt -> IO CDouble Source #

getRMSError :: TH2F -> CInt -> IO CDouble Source #

getSkewness :: TH2F -> CInt -> IO CDouble Source #

interpolate3 :: TH2F -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2F -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2F -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2F -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2F -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2F -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2F -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2F -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2F -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2F -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2F -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2F -> c0 -> IO () Source #

resetStats :: TH2F -> IO () Source #

scale :: Castable c0 CString => TH2F -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2F -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2F -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2F -> CFloat -> IO () Source #

setBarWidth :: TH2F -> CFloat -> IO () Source #

setBinContent1 :: TH2F -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2F -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2F -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2F -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2F -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2F -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2F -> CInt -> c0 -> IO () Source #

setCellContent :: TH2F -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2F -> Ptr CDouble -> IO () Source #

setContour :: TH2F -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2F -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2F -> c0 -> IO () Source #

setEntries :: TH2F -> CDouble -> IO () Source #

setError :: TH2F -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2F -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2F -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2F -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2F -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2F -> CDouble -> IO () Source #

setMinimum :: TH2F -> CDouble -> IO () Source #

setNormFactor :: TH2F -> CDouble -> IO () Source #

setStats :: TH2F -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2F -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2F -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2F -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2F -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2F -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2F -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2F -> CInt -> c0 -> IO () Source #

sumw2 :: TH2F -> IO () Source #

ITH1 TH2I Source # 
Instance details

Defined in HROOT.Hist.TH2I.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2I -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2I -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2I -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2I -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2I -> c0 -> IO TH2I Source #

drawNormalized :: Castable c0 CString => TH2I -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2I -> IO () Source #

bufferEmpty :: TH2I -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2I -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2I -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2I -> CDouble -> IO CInt Source #

fill1w :: TH2I -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2I -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2I -> c0 -> CInt -> IO () Source #

findBin :: TH2I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2I -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2I -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2I -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2I -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2I -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2I -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2I -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2I -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2I -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2I -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2I -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2I -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2I -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2I -> c0 -> IO CFloat Source #

getBarOffset :: TH2I -> IO CFloat Source #

getBarWidth :: TH2I -> IO CFloat Source #

getContour :: TH2I -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2I -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2I -> CInt -> IO CDouble Source #

getBin :: TH2I -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2I -> CInt -> IO CDouble Source #

getBinContent1 :: TH2I -> CInt -> IO CDouble Source #

getBinContent2 :: TH2I -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2I -> CInt -> IO CDouble Source #

getBinError2 :: TH2I -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2I -> CInt -> IO CDouble Source #

getBinWidth :: TH2I -> CInt -> IO CDouble Source #

getCellContent :: TH2I -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2I -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2I -> IO CDouble Source #

getEffectiveEntries :: TH2I -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2I -> c0 -> IO TF1 Source #

getDimension :: TH2I -> IO CInt Source #

getKurtosis :: TH2I -> CInt -> IO CDouble Source #

getLowEdge :: TH2I -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2I -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2I -> IO CInt Source #

getMaximumStored :: TH2I -> IO CDouble Source #

getMinimumTH1 :: TH2I -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2I -> IO CInt Source #

getMinimumStored :: TH2I -> IO CDouble Source #

getMean :: TH2I -> CInt -> IO CDouble Source #

getMeanError :: TH2I -> CInt -> IO CDouble Source #

getNbinsX :: TH2I -> IO CDouble Source #

getNbinsY :: TH2I -> IO CDouble Source #

getNbinsZ :: TH2I -> IO CDouble Source #

getQuantilesTH1 :: TH2I -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2I -> IO CDouble Source #

getStats :: TH2I -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2I -> IO CDouble Source #

getSumw2 :: TH2I -> IO TArrayD Source #

getSumw2N :: TH2I -> IO CInt Source #

getRMS :: TH2I -> CInt -> IO CDouble Source #

getRMSError :: TH2I -> CInt -> IO CDouble Source #

getSkewness :: TH2I -> CInt -> IO CDouble Source #

interpolate3 :: TH2I -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2I -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2I -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2I -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2I -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2I -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2I -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2I -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2I -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2I -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2I -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2I -> c0 -> IO () Source #

resetStats :: TH2I -> IO () Source #

scale :: Castable c0 CString => TH2I -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2I -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2I -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2I -> CFloat -> IO () Source #

setBarWidth :: TH2I -> CFloat -> IO () Source #

setBinContent1 :: TH2I -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2I -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2I -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2I -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2I -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2I -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2I -> CInt -> c0 -> IO () Source #

setCellContent :: TH2I -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2I -> Ptr CDouble -> IO () Source #

setContour :: TH2I -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2I -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2I -> c0 -> IO () Source #

setEntries :: TH2I -> CDouble -> IO () Source #

setError :: TH2I -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2I -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2I -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2I -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2I -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2I -> CDouble -> IO () Source #

setMinimum :: TH2I -> CDouble -> IO () Source #

setNormFactor :: TH2I -> CDouble -> IO () Source #

setStats :: TH2I -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2I -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2I -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2I -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2I -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2I -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2I -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2I -> CInt -> c0 -> IO () Source #

sumw2 :: TH2I -> IO () Source #

ITH1 TH2Poly Source # 
Instance details

Defined in HROOT.Hist.TH2Poly.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2Poly -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2Poly -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2Poly -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2Poly -> c0 -> IO TH2Poly Source #

drawNormalized :: Castable c0 CString => TH2Poly -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2Poly -> IO () Source #

bufferEmpty :: TH2Poly -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2Poly -> CDouble -> IO CInt Source #

fill1w :: TH2Poly -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2Poly -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2Poly -> c0 -> CInt -> IO () Source #

findBin :: TH2Poly -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2Poly -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2Poly -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2Poly -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2Poly -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2Poly -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2Poly -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2Poly -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2Poly -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2Poly -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2Poly -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2Poly -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2Poly -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2Poly -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2Poly -> c0 -> IO CFloat Source #

getBarOffset :: TH2Poly -> IO CFloat Source #

getBarWidth :: TH2Poly -> IO CFloat Source #

getContour :: TH2Poly -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2Poly -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2Poly -> CInt -> IO CDouble Source #

getBin :: TH2Poly -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2Poly -> CInt -> IO CDouble Source #

getBinContent1 :: TH2Poly -> CInt -> IO CDouble Source #

getBinContent2 :: TH2Poly -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2Poly -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2Poly -> CInt -> IO CDouble Source #

getBinError2 :: TH2Poly -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2Poly -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2Poly -> CInt -> IO CDouble Source #

getBinWidth :: TH2Poly -> CInt -> IO CDouble Source #

getCellContent :: TH2Poly -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2Poly -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2Poly -> IO CDouble Source #

getEffectiveEntries :: TH2Poly -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2Poly -> c0 -> IO TF1 Source #

getDimension :: TH2Poly -> IO CInt Source #

getKurtosis :: TH2Poly -> CInt -> IO CDouble Source #

getLowEdge :: TH2Poly -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2Poly -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2Poly -> IO CInt Source #

getMaximumStored :: TH2Poly -> IO CDouble Source #

getMinimumTH1 :: TH2Poly -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2Poly -> IO CInt Source #

getMinimumStored :: TH2Poly -> IO CDouble Source #

getMean :: TH2Poly -> CInt -> IO CDouble Source #

getMeanError :: TH2Poly -> CInt -> IO CDouble Source #

getNbinsX :: TH2Poly -> IO CDouble Source #

getNbinsY :: TH2Poly -> IO CDouble Source #

getNbinsZ :: TH2Poly -> IO CDouble Source #

getQuantilesTH1 :: TH2Poly -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2Poly -> IO CDouble Source #

getStats :: TH2Poly -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2Poly -> IO CDouble Source #

getSumw2 :: TH2Poly -> IO TArrayD Source #

getSumw2N :: TH2Poly -> IO CInt Source #

getRMS :: TH2Poly -> CInt -> IO CDouble Source #

getRMSError :: TH2Poly -> CInt -> IO CDouble Source #

getSkewness :: TH2Poly -> CInt -> IO CDouble Source #

interpolate3 :: TH2Poly -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2Poly -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2Poly -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2Poly -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2Poly -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2Poly -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2Poly -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2Poly -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

resetStats :: TH2Poly -> IO () Source #

scale :: Castable c0 CString => TH2Poly -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2Poly -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2Poly -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2Poly -> CFloat -> IO () Source #

setBarWidth :: TH2Poly -> CFloat -> IO () Source #

setBinContent1 :: TH2Poly -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2Poly -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2Poly -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2Poly -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2Poly -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2Poly -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2Poly -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2Poly -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2Poly -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2Poly -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2Poly -> CInt -> c0 -> IO () Source #

setCellContent :: TH2Poly -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2Poly -> Ptr CDouble -> IO () Source #

setContour :: TH2Poly -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2Poly -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2Poly -> c0 -> IO () Source #

setEntries :: TH2Poly -> CDouble -> IO () Source #

setError :: TH2Poly -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2Poly -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2Poly -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2Poly -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2Poly -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2Poly -> CDouble -> IO () Source #

setMinimum :: TH2Poly -> CDouble -> IO () Source #

setNormFactor :: TH2Poly -> CDouble -> IO () Source #

setStats :: TH2Poly -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2Poly -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2Poly -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2Poly -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2Poly -> CInt -> c0 -> IO () Source #

sumw2 :: TH2Poly -> IO () Source #

ITH1 TH2S Source # 
Instance details

Defined in HROOT.Hist.TH2S.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH2S -> c0 -> CDouble -> IO () Source #

addBinContent :: TH2S -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2S -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH2S -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH2S -> c0 -> IO TH2S Source #

drawNormalized :: Castable c0 CString => TH2S -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH2S -> IO () Source #

bufferEmpty :: TH2S -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH2S -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2S -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH2S -> CDouble -> IO CInt Source #

fill1w :: TH2S -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH2S -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH2S -> c0 -> CInt -> IO () Source #

findBin :: TH2S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH2S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH2S -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH2S -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH2S -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH2S -> IO () Source #

getNdivisionA :: Castable c0 CString => TH2S -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH2S -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH2S -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH2S -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH2S -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH2S -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH2S -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH2S -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH2S -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH2S -> c0 -> IO CFloat Source #

getBarOffset :: TH2S -> IO CFloat Source #

getBarWidth :: TH2S -> IO CFloat Source #

getContour :: TH2S -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH2S -> CInt -> IO CDouble Source #

getContourLevelPad :: TH2S -> CInt -> IO CDouble Source #

getBin :: TH2S -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH2S -> CInt -> IO CDouble Source #

getBinContent1 :: TH2S -> CInt -> IO CDouble Source #

getBinContent2 :: TH2S -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH2S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH2S -> CInt -> IO CDouble Source #

getBinError2 :: TH2S -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH2S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH2S -> CInt -> IO CDouble Source #

getBinWidth :: TH2S -> CInt -> IO CDouble Source #

getCellContent :: TH2S -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH2S -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH2S -> IO CDouble Source #

getEffectiveEntries :: TH2S -> IO CDouble Source #

getFunction :: Castable c0 CString => TH2S -> c0 -> IO TF1 Source #

getDimension :: TH2S -> IO CInt Source #

getKurtosis :: TH2S -> CInt -> IO CDouble Source #

getLowEdge :: TH2S -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH2S -> CDouble -> IO CDouble Source #

getMaximumBin :: TH2S -> IO CInt Source #

getMaximumStored :: TH2S -> IO CDouble Source #

getMinimumTH1 :: TH2S -> CDouble -> IO CDouble Source #

getMinimumBin :: TH2S -> IO CInt Source #

getMinimumStored :: TH2S -> IO CDouble Source #

getMean :: TH2S -> CInt -> IO CDouble Source #

getMeanError :: TH2S -> CInt -> IO CDouble Source #

getNbinsX :: TH2S -> IO CDouble Source #

getNbinsY :: TH2S -> IO CDouble Source #

getNbinsZ :: TH2S -> IO CDouble Source #

getQuantilesTH1 :: TH2S -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH2S -> IO CDouble Source #

getStats :: TH2S -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH2S -> IO CDouble Source #

getSumw2 :: TH2S -> IO TArrayD Source #

getSumw2N :: TH2S -> IO CInt Source #

getRMS :: TH2S -> CInt -> IO CDouble Source #

getRMSError :: TH2S -> CInt -> IO CDouble Source #

getSkewness :: TH2S -> CInt -> IO CDouble Source #

interpolate3 :: TH2S -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH2S -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH2S -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH2S -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH2S -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH2S -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH2S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH2S -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH2S -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH2S -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH2S -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH2S -> c0 -> IO () Source #

reset :: Castable c0 CString => TH2S -> c0 -> IO () Source #

resetStats :: TH2S -> IO () Source #

scale :: Castable c0 CString => TH2S -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH2S -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH2S -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH2S -> CFloat -> IO () Source #

setBarWidth :: TH2S -> CFloat -> IO () Source #

setBinContent1 :: TH2S -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH2S -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH2S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH2S -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH2S -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH2S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH2S -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH2S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH2S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH2S -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH2S -> CInt -> c0 -> IO () Source #

setCellContent :: TH2S -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH2S -> Ptr CDouble -> IO () Source #

setContour :: TH2S -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH2S -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH2S -> c0 -> IO () Source #

setEntries :: TH2S -> CDouble -> IO () Source #

setError :: TH2S -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH2S -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH2S -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH2S -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH2S -> CFloat -> c0 -> IO () Source #

setMaximum :: TH2S -> CDouble -> IO () Source #

setMinimum :: TH2S -> CDouble -> IO () Source #

setNormFactor :: TH2S -> CDouble -> IO () Source #

setStats :: TH2S -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH2S -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH2S -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH2S -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH2S -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH2S -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH2S -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH2S -> CInt -> c0 -> IO () Source #

sumw2 :: TH2S -> IO () Source #

ITH1 TH3 Source # 
Instance details

Defined in HROOT.Hist.TH3.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3 -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3 -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3 -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3 -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3 -> c0 -> IO TH3 Source #

drawNormalized :: Castable c0 CString => TH3 -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3 -> IO () Source #

bufferEmpty :: TH3 -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3 -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3 -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3 -> CDouble -> IO CInt Source #

fill1w :: TH3 -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3 -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3 -> c0 -> CInt -> IO () Source #

findBin :: TH3 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3 -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3 -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3 -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3 -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3 -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3 -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3 -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3 -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3 -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3 -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3 -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3 -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3 -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3 -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3 -> c0 -> IO CFloat Source #

getBarOffset :: TH3 -> IO CFloat Source #

getBarWidth :: TH3 -> IO CFloat Source #

getContour :: TH3 -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3 -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3 -> CInt -> IO CDouble Source #

getBin :: TH3 -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3 -> CInt -> IO CDouble Source #

getBinContent1 :: TH3 -> CInt -> IO CDouble Source #

getBinContent2 :: TH3 -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3 -> CInt -> IO CDouble Source #

getBinError2 :: TH3 -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3 -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3 -> CInt -> IO CDouble Source #

getBinWidth :: TH3 -> CInt -> IO CDouble Source #

getCellContent :: TH3 -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3 -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3 -> IO CDouble Source #

getEffectiveEntries :: TH3 -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3 -> c0 -> IO TF1 Source #

getDimension :: TH3 -> IO CInt Source #

getKurtosis :: TH3 -> CInt -> IO CDouble Source #

getLowEdge :: TH3 -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3 -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3 -> IO CInt Source #

getMaximumStored :: TH3 -> IO CDouble Source #

getMinimumTH1 :: TH3 -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3 -> IO CInt Source #

getMinimumStored :: TH3 -> IO CDouble Source #

getMean :: TH3 -> CInt -> IO CDouble Source #

getMeanError :: TH3 -> CInt -> IO CDouble Source #

getNbinsX :: TH3 -> IO CDouble Source #

getNbinsY :: TH3 -> IO CDouble Source #

getNbinsZ :: TH3 -> IO CDouble Source #

getQuantilesTH1 :: TH3 -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3 -> IO CDouble Source #

getStats :: TH3 -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3 -> IO CDouble Source #

getSumw2 :: TH3 -> IO TArrayD Source #

getSumw2N :: TH3 -> IO CInt Source #

getRMS :: TH3 -> CInt -> IO CDouble Source #

getRMSError :: TH3 -> CInt -> IO CDouble Source #

getSkewness :: TH3 -> CInt -> IO CDouble Source #

interpolate3 :: TH3 -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3 -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3 -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3 -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3 -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3 -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3 -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3 -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3 -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3 -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3 -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3 -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3 -> c0 -> IO () Source #

resetStats :: TH3 -> IO () Source #

scale :: Castable c0 CString => TH3 -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3 -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3 -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3 -> CFloat -> IO () Source #

setBarWidth :: TH3 -> CFloat -> IO () Source #

setBinContent1 :: TH3 -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3 -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3 -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3 -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3 -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3 -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3 -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3 -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3 -> CInt -> c0 -> IO () Source #

setCellContent :: TH3 -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3 -> Ptr CDouble -> IO () Source #

setContour :: TH3 -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3 -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3 -> c0 -> IO () Source #

setEntries :: TH3 -> CDouble -> IO () Source #

setError :: TH3 -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3 -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3 -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3 -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3 -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3 -> CDouble -> IO () Source #

setMinimum :: TH3 -> CDouble -> IO () Source #

setNormFactor :: TH3 -> CDouble -> IO () Source #

setStats :: TH3 -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3 -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3 -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3 -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3 -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3 -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3 -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3 -> CInt -> c0 -> IO () Source #

sumw2 :: TH3 -> IO () Source #

ITH1 TH3C Source # 
Instance details

Defined in HROOT.Hist.TH3C.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3C -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3C -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3C -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3C -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3C -> c0 -> IO TH3C Source #

drawNormalized :: Castable c0 CString => TH3C -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3C -> IO () Source #

bufferEmpty :: TH3C -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3C -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3C -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3C -> CDouble -> IO CInt Source #

fill1w :: TH3C -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3C -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3C -> c0 -> CInt -> IO () Source #

findBin :: TH3C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3C -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3C -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3C -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3C -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3C -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3C -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3C -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3C -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3C -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3C -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3C -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3C -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3C -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3C -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3C -> c0 -> IO CFloat Source #

getBarOffset :: TH3C -> IO CFloat Source #

getBarWidth :: TH3C -> IO CFloat Source #

getContour :: TH3C -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3C -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3C -> CInt -> IO CDouble Source #

getBin :: TH3C -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3C -> CInt -> IO CDouble Source #

getBinContent1 :: TH3C -> CInt -> IO CDouble Source #

getBinContent2 :: TH3C -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3C -> CInt -> IO CDouble Source #

getBinError2 :: TH3C -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3C -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3C -> CInt -> IO CDouble Source #

getBinWidth :: TH3C -> CInt -> IO CDouble Source #

getCellContent :: TH3C -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3C -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3C -> IO CDouble Source #

getEffectiveEntries :: TH3C -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3C -> c0 -> IO TF1 Source #

getDimension :: TH3C -> IO CInt Source #

getKurtosis :: TH3C -> CInt -> IO CDouble Source #

getLowEdge :: TH3C -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3C -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3C -> IO CInt Source #

getMaximumStored :: TH3C -> IO CDouble Source #

getMinimumTH1 :: TH3C -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3C -> IO CInt Source #

getMinimumStored :: TH3C -> IO CDouble Source #

getMean :: TH3C -> CInt -> IO CDouble Source #

getMeanError :: TH3C -> CInt -> IO CDouble Source #

getNbinsX :: TH3C -> IO CDouble Source #

getNbinsY :: TH3C -> IO CDouble Source #

getNbinsZ :: TH3C -> IO CDouble Source #

getQuantilesTH1 :: TH3C -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3C -> IO CDouble Source #

getStats :: TH3C -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3C -> IO CDouble Source #

getSumw2 :: TH3C -> IO TArrayD Source #

getSumw2N :: TH3C -> IO CInt Source #

getRMS :: TH3C -> CInt -> IO CDouble Source #

getRMSError :: TH3C -> CInt -> IO CDouble Source #

getSkewness :: TH3C -> CInt -> IO CDouble Source #

interpolate3 :: TH3C -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3C -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3C -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3C -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3C -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3C -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3C -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3C -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3C -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3C -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3C -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3C -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3C -> c0 -> IO () Source #

resetStats :: TH3C -> IO () Source #

scale :: Castable c0 CString => TH3C -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3C -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3C -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3C -> CFloat -> IO () Source #

setBarWidth :: TH3C -> CFloat -> IO () Source #

setBinContent1 :: TH3C -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3C -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3C -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3C -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3C -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3C -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3C -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3C -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3C -> CInt -> c0 -> IO () Source #

setCellContent :: TH3C -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3C -> Ptr CDouble -> IO () Source #

setContour :: TH3C -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3C -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3C -> c0 -> IO () Source #

setEntries :: TH3C -> CDouble -> IO () Source #

setError :: TH3C -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3C -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3C -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3C -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3C -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3C -> CDouble -> IO () Source #

setMinimum :: TH3C -> CDouble -> IO () Source #

setNormFactor :: TH3C -> CDouble -> IO () Source #

setStats :: TH3C -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3C -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3C -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3C -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3C -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3C -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3C -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3C -> CInt -> c0 -> IO () Source #

sumw2 :: TH3C -> IO () Source #

ITH1 TH3D Source # 
Instance details

Defined in HROOT.Hist.TH3D.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3D -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3D -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3D -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3D -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3D -> c0 -> IO TH3D Source #

drawNormalized :: Castable c0 CString => TH3D -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3D -> IO () Source #

bufferEmpty :: TH3D -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3D -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3D -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3D -> CDouble -> IO CInt Source #

fill1w :: TH3D -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3D -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3D -> c0 -> CInt -> IO () Source #

findBin :: TH3D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3D -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3D -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3D -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3D -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3D -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3D -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3D -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3D -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3D -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3D -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3D -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3D -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3D -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3D -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3D -> c0 -> IO CFloat Source #

getBarOffset :: TH3D -> IO CFloat Source #

getBarWidth :: TH3D -> IO CFloat Source #

getContour :: TH3D -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3D -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3D -> CInt -> IO CDouble Source #

getBin :: TH3D -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3D -> CInt -> IO CDouble Source #

getBinContent1 :: TH3D -> CInt -> IO CDouble Source #

getBinContent2 :: TH3D -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3D -> CInt -> IO CDouble Source #

getBinError2 :: TH3D -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3D -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3D -> CInt -> IO CDouble Source #

getBinWidth :: TH3D -> CInt -> IO CDouble Source #

getCellContent :: TH3D -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3D -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3D -> IO CDouble Source #

getEffectiveEntries :: TH3D -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3D -> c0 -> IO TF1 Source #

getDimension :: TH3D -> IO CInt Source #

getKurtosis :: TH3D -> CInt -> IO CDouble Source #

getLowEdge :: TH3D -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3D -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3D -> IO CInt Source #

getMaximumStored :: TH3D -> IO CDouble Source #

getMinimumTH1 :: TH3D -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3D -> IO CInt Source #

getMinimumStored :: TH3D -> IO CDouble Source #

getMean :: TH3D -> CInt -> IO CDouble Source #

getMeanError :: TH3D -> CInt -> IO CDouble Source #

getNbinsX :: TH3D -> IO CDouble Source #

getNbinsY :: TH3D -> IO CDouble Source #

getNbinsZ :: TH3D -> IO CDouble Source #

getQuantilesTH1 :: TH3D -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3D -> IO CDouble Source #

getStats :: TH3D -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3D -> IO CDouble Source #

getSumw2 :: TH3D -> IO TArrayD Source #

getSumw2N :: TH3D -> IO CInt Source #

getRMS :: TH3D -> CInt -> IO CDouble Source #

getRMSError :: TH3D -> CInt -> IO CDouble Source #

getSkewness :: TH3D -> CInt -> IO CDouble Source #

interpolate3 :: TH3D -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3D -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3D -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3D -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3D -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3D -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3D -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3D -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3D -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3D -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3D -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3D -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3D -> c0 -> IO () Source #

resetStats :: TH3D -> IO () Source #

scale :: Castable c0 CString => TH3D -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3D -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3D -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3D -> CFloat -> IO () Source #

setBarWidth :: TH3D -> CFloat -> IO () Source #

setBinContent1 :: TH3D -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3D -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3D -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3D -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3D -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3D -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3D -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3D -> CInt -> c0 -> IO () Source #

setCellContent :: TH3D -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3D -> Ptr CDouble -> IO () Source #

setContour :: TH3D -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3D -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3D -> c0 -> IO () Source #

setEntries :: TH3D -> CDouble -> IO () Source #

setError :: TH3D -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3D -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3D -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3D -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3D -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3D -> CDouble -> IO () Source #

setMinimum :: TH3D -> CDouble -> IO () Source #

setNormFactor :: TH3D -> CDouble -> IO () Source #

setStats :: TH3D -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3D -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3D -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3D -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3D -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3D -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3D -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3D -> CInt -> c0 -> IO () Source #

sumw2 :: TH3D -> IO () Source #

ITH1 TH3F Source # 
Instance details

Defined in HROOT.Hist.TH3F.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3F -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3F -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3F -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3F -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3F -> c0 -> IO TH3F Source #

drawNormalized :: Castable c0 CString => TH3F -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3F -> IO () Source #

bufferEmpty :: TH3F -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3F -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3F -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3F -> CDouble -> IO CInt Source #

fill1w :: TH3F -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3F -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3F -> c0 -> CInt -> IO () Source #

findBin :: TH3F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3F -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3F -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3F -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3F -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3F -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3F -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3F -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3F -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3F -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3F -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3F -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3F -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3F -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3F -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3F -> c0 -> IO CFloat Source #

getBarOffset :: TH3F -> IO CFloat Source #

getBarWidth :: TH3F -> IO CFloat Source #

getContour :: TH3F -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3F -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3F -> CInt -> IO CDouble Source #

getBin :: TH3F -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3F -> CInt -> IO CDouble Source #

getBinContent1 :: TH3F -> CInt -> IO CDouble Source #

getBinContent2 :: TH3F -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3F -> CInt -> IO CDouble Source #

getBinError2 :: TH3F -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3F -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3F -> CInt -> IO CDouble Source #

getBinWidth :: TH3F -> CInt -> IO CDouble Source #

getCellContent :: TH3F -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3F -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3F -> IO CDouble Source #

getEffectiveEntries :: TH3F -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3F -> c0 -> IO TF1 Source #

getDimension :: TH3F -> IO CInt Source #

getKurtosis :: TH3F -> CInt -> IO CDouble Source #

getLowEdge :: TH3F -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3F -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3F -> IO CInt Source #

getMaximumStored :: TH3F -> IO CDouble Source #

getMinimumTH1 :: TH3F -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3F -> IO CInt Source #

getMinimumStored :: TH3F -> IO CDouble Source #

getMean :: TH3F -> CInt -> IO CDouble Source #

getMeanError :: TH3F -> CInt -> IO CDouble Source #

getNbinsX :: TH3F -> IO CDouble Source #

getNbinsY :: TH3F -> IO CDouble Source #

getNbinsZ :: TH3F -> IO CDouble Source #

getQuantilesTH1 :: TH3F -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3F -> IO CDouble Source #

getStats :: TH3F -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3F -> IO CDouble Source #

getSumw2 :: TH3F -> IO TArrayD Source #

getSumw2N :: TH3F -> IO CInt Source #

getRMS :: TH3F -> CInt -> IO CDouble Source #

getRMSError :: TH3F -> CInt -> IO CDouble Source #

getSkewness :: TH3F -> CInt -> IO CDouble Source #

interpolate3 :: TH3F -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3F -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3F -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3F -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3F -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3F -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3F -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3F -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3F -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3F -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3F -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3F -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3F -> c0 -> IO () Source #

resetStats :: TH3F -> IO () Source #

scale :: Castable c0 CString => TH3F -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3F -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3F -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3F -> CFloat -> IO () Source #

setBarWidth :: TH3F -> CFloat -> IO () Source #

setBinContent1 :: TH3F -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3F -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3F -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3F -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3F -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3F -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3F -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3F -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3F -> CInt -> c0 -> IO () Source #

setCellContent :: TH3F -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3F -> Ptr CDouble -> IO () Source #

setContour :: TH3F -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3F -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3F -> c0 -> IO () Source #

setEntries :: TH3F -> CDouble -> IO () Source #

setError :: TH3F -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3F -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3F -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3F -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3F -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3F -> CDouble -> IO () Source #

setMinimum :: TH3F -> CDouble -> IO () Source #

setNormFactor :: TH3F -> CDouble -> IO () Source #

setStats :: TH3F -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3F -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3F -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3F -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3F -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3F -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3F -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3F -> CInt -> c0 -> IO () Source #

sumw2 :: TH3F -> IO () Source #

ITH1 TH3I Source # 
Instance details

Defined in HROOT.Hist.TH3I.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3I -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3I -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3I -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3I -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3I -> c0 -> IO TH3I Source #

drawNormalized :: Castable c0 CString => TH3I -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3I -> IO () Source #

bufferEmpty :: TH3I -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3I -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3I -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3I -> CDouble -> IO CInt Source #

fill1w :: TH3I -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3I -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3I -> c0 -> CInt -> IO () Source #

findBin :: TH3I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3I -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3I -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3I -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3I -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3I -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3I -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3I -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3I -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3I -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3I -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3I -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3I -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3I -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3I -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3I -> c0 -> IO CFloat Source #

getBarOffset :: TH3I -> IO CFloat Source #

getBarWidth :: TH3I -> IO CFloat Source #

getContour :: TH3I -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3I -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3I -> CInt -> IO CDouble Source #

getBin :: TH3I -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3I -> CInt -> IO CDouble Source #

getBinContent1 :: TH3I -> CInt -> IO CDouble Source #

getBinContent2 :: TH3I -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3I -> CInt -> IO CDouble Source #

getBinError2 :: TH3I -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3I -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3I -> CInt -> IO CDouble Source #

getBinWidth :: TH3I -> CInt -> IO CDouble Source #

getCellContent :: TH3I -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3I -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3I -> IO CDouble Source #

getEffectiveEntries :: TH3I -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3I -> c0 -> IO TF1 Source #

getDimension :: TH3I -> IO CInt Source #

getKurtosis :: TH3I -> CInt -> IO CDouble Source #

getLowEdge :: TH3I -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3I -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3I -> IO CInt Source #

getMaximumStored :: TH3I -> IO CDouble Source #

getMinimumTH1 :: TH3I -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3I -> IO CInt Source #

getMinimumStored :: TH3I -> IO CDouble Source #

getMean :: TH3I -> CInt -> IO CDouble Source #

getMeanError :: TH3I -> CInt -> IO CDouble Source #

getNbinsX :: TH3I -> IO CDouble Source #

getNbinsY :: TH3I -> IO CDouble Source #

getNbinsZ :: TH3I -> IO CDouble Source #

getQuantilesTH1 :: TH3I -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3I -> IO CDouble Source #

getStats :: TH3I -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3I -> IO CDouble Source #

getSumw2 :: TH3I -> IO TArrayD Source #

getSumw2N :: TH3I -> IO CInt Source #

getRMS :: TH3I -> CInt -> IO CDouble Source #

getRMSError :: TH3I -> CInt -> IO CDouble Source #

getSkewness :: TH3I -> CInt -> IO CDouble Source #

interpolate3 :: TH3I -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3I -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3I -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3I -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3I -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3I -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3I -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3I -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3I -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3I -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3I -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3I -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3I -> c0 -> IO () Source #

resetStats :: TH3I -> IO () Source #

scale :: Castable c0 CString => TH3I -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3I -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3I -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3I -> CFloat -> IO () Source #

setBarWidth :: TH3I -> CFloat -> IO () Source #

setBinContent1 :: TH3I -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3I -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3I -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3I -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3I -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3I -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3I -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3I -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3I -> CInt -> c0 -> IO () Source #

setCellContent :: TH3I -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3I -> Ptr CDouble -> IO () Source #

setContour :: TH3I -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3I -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3I -> c0 -> IO () Source #

setEntries :: TH3I -> CDouble -> IO () Source #

setError :: TH3I -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3I -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3I -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3I -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3I -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3I -> CDouble -> IO () Source #

setMinimum :: TH3I -> CDouble -> IO () Source #

setNormFactor :: TH3I -> CDouble -> IO () Source #

setStats :: TH3I -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3I -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3I -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3I -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3I -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3I -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3I -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3I -> CInt -> c0 -> IO () Source #

sumw2 :: TH3I -> IO () Source #

ITH1 TH3S Source # 
Instance details

Defined in HROOT.Hist.TH3S.Implementation

Methods

add :: (ITH1 c0, FPtr c0) => TH3S -> c0 -> CDouble -> IO () Source #

addBinContent :: TH3S -> CInt -> CDouble -> IO () Source #

chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3S -> c0 -> c1 -> Ptr CDouble -> IO CDouble Source #

directoryAutoAdd :: (ITDirectory c0, FPtr c0) => TH3S -> c0 -> IO () Source #

divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

drawCopyTH1 :: Castable c0 CString => TH3S -> c0 -> IO TH3S Source #

drawNormalized :: Castable c0 CString => TH3S -> c0 -> CDouble -> IO TH1 Source #

drawPanelTH1 :: TH3S -> IO () Source #

bufferEmpty :: TH3S -> CInt -> IO CInt Source #

evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => TH3S -> c0 -> c1 -> IO () Source #

fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3S -> c0 -> c1 -> IO TH1 Source #

fill1 :: TH3S -> CDouble -> IO CInt Source #

fill1w :: TH3S -> CDouble -> CDouble -> IO CInt Source #

fillN1 :: TH3S -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO () Source #

fillRandom :: (ITH1 c0, FPtr c0) => TH3S -> c0 -> CInt -> IO () Source #

findBin :: TH3S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFixBin :: TH3S -> CDouble -> CDouble -> CDouble -> IO CInt Source #

findFirstBinAbove :: TH3S -> CDouble -> CInt -> IO CInt Source #

findLastBinAbove :: TH3S -> CDouble -> CInt -> IO CInt Source #

fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => TH3S -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () Source #

fitPanelTH1 :: TH3S -> IO () Source #

getNdivisionA :: Castable c0 CString => TH3S -> c0 -> IO CInt Source #

getAxisColorA :: Castable c0 CString => TH3S -> c0 -> IO CShort Source #

getLabelColorA :: Castable c0 CString => TH3S -> c0 -> IO CShort Source #

getLabelFontA :: Castable c0 CString => TH3S -> c0 -> IO CShort Source #

getLabelOffsetA :: Castable c0 CString => TH3S -> c0 -> IO CFloat Source #

getLabelSizeA :: Castable c0 CString => TH3S -> c0 -> IO CFloat Source #

getTitleFontA :: Castable c0 CString => TH3S -> c0 -> IO CShort Source #

getTitleOffsetA :: Castable c0 CString => TH3S -> c0 -> IO CFloat Source #

getTitleSizeA :: Castable c0 CString => TH3S -> c0 -> IO CFloat Source #

getTickLengthA :: Castable c0 CString => TH3S -> c0 -> IO CFloat Source #

getBarOffset :: TH3S -> IO CFloat Source #

getBarWidth :: TH3S -> IO CFloat Source #

getContour :: TH3S -> Ptr CDouble -> IO CInt Source #

getContourLevel :: TH3S -> CInt -> IO CDouble Source #

getContourLevelPad :: TH3S -> CInt -> IO CDouble Source #

getBin :: TH3S -> CInt -> CInt -> CInt -> IO CInt Source #

getBinCenter :: TH3S -> CInt -> IO CDouble Source #

getBinContent1 :: TH3S -> CInt -> IO CDouble Source #

getBinContent2 :: TH3S -> CInt -> CInt -> IO CDouble Source #

getBinContent3 :: TH3S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinError1 :: TH3S -> CInt -> IO CDouble Source #

getBinError2 :: TH3S -> CInt -> CInt -> IO CDouble Source #

getBinError3 :: TH3S -> CInt -> CInt -> CInt -> IO CDouble Source #

getBinLowEdge :: TH3S -> CInt -> IO CDouble Source #

getBinWidth :: TH3S -> CInt -> IO CDouble Source #

getCellContent :: TH3S -> CInt -> CInt -> IO CDouble Source #

getCellError :: TH3S -> CInt -> CInt -> IO CDouble Source #

getEntries :: TH3S -> IO CDouble Source #

getEffectiveEntries :: TH3S -> IO CDouble Source #

getFunction :: Castable c0 CString => TH3S -> c0 -> IO TF1 Source #

getDimension :: TH3S -> IO CInt Source #

getKurtosis :: TH3S -> CInt -> IO CDouble Source #

getLowEdge :: TH3S -> Ptr CDouble -> IO () Source #

getMaximumTH1 :: TH3S -> CDouble -> IO CDouble Source #

getMaximumBin :: TH3S -> IO CInt Source #

getMaximumStored :: TH3S -> IO CDouble Source #

getMinimumTH1 :: TH3S -> CDouble -> IO CDouble Source #

getMinimumBin :: TH3S -> IO CInt Source #

getMinimumStored :: TH3S -> IO CDouble Source #

getMean :: TH3S -> CInt -> IO CDouble Source #

getMeanError :: TH3S -> CInt -> IO CDouble Source #

getNbinsX :: TH3S -> IO CDouble Source #

getNbinsY :: TH3S -> IO CDouble Source #

getNbinsZ :: TH3S -> IO CDouble Source #

getQuantilesTH1 :: TH3S -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt Source #

getRandom :: TH3S -> IO CDouble Source #

getStats :: TH3S -> Ptr CDouble -> IO () Source #

getSumOfWeights :: TH3S -> IO CDouble Source #

getSumw2 :: TH3S -> IO TArrayD Source #

getSumw2N :: TH3S -> IO CInt Source #

getRMS :: TH3S -> CInt -> IO CDouble Source #

getRMSError :: TH3S -> CInt -> IO CDouble Source #

getSkewness :: TH3S -> CInt -> IO CDouble Source #

interpolate3 :: TH3S -> CDouble -> CDouble -> CDouble -> IO CDouble Source #

kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => TH3S -> c0 -> c1 -> IO CDouble Source #

labelsDeflate :: Castable c0 CString => TH3S -> c0 -> IO () Source #

labelsInflate :: Castable c0 CString => TH3S -> c0 -> IO () Source #

labelsOption :: (Castable c1 CString, Castable c0 CString) => TH3S -> c0 -> c1 -> IO () Source #

multiflyF :: (ITF1 c0, FPtr c0) => TH3S -> c0 -> CDouble -> IO () Source #

multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => TH3S -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () Source #

putStats :: TH3S -> Ptr CDouble -> IO () Source #

rebin :: Castable c0 CString => TH3S -> CInt -> c0 -> Ptr CDouble -> IO TH1 Source #

rebinAxis :: (ITAxis c0, FPtr c0) => TH3S -> CDouble -> c0 -> IO () Source #

rebuild :: Castable c0 CString => TH3S -> c0 -> IO () Source #

recursiveRemove :: (ITObject c0, FPtr c0) => TH3S -> c0 -> IO () Source #

reset :: Castable c0 CString => TH3S -> c0 -> IO () Source #

resetStats :: TH3S -> IO () Source #

scale :: Castable c0 CString => TH3S -> CDouble -> c0 -> IO () Source #

setAxisColorA :: Castable c0 CString => TH3S -> CShort -> c0 -> IO () Source #

setAxisRange :: Castable c0 CString => TH3S -> CDouble -> CDouble -> c0 -> IO () Source #

setBarOffset :: TH3S -> CFloat -> IO () Source #

setBarWidth :: TH3S -> CFloat -> IO () Source #

setBinContent1 :: TH3S -> CInt -> CDouble -> IO () Source #

setBinContent2 :: TH3S -> CInt -> CInt -> CDouble -> IO () Source #

setBinContent3 :: TH3S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBinError1 :: TH3S -> CInt -> CDouble -> IO () Source #

setBinError2 :: TH3S -> CInt -> CInt -> CDouble -> IO () Source #

setBinError3 :: TH3S -> CInt -> CInt -> CInt -> CDouble -> IO () Source #

setBins1 :: TH3S -> CInt -> Ptr CDouble -> IO () Source #

setBins2 :: TH3S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBins3 :: TH3S -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO () Source #

setBinsLength :: TH3S -> CInt -> IO () Source #

setBuffer :: Castable c0 CString => TH3S -> CInt -> c0 -> IO () Source #

setCellContent :: TH3S -> CInt -> CInt -> CDouble -> IO () Source #

setContent :: TH3S -> Ptr CDouble -> IO () Source #

setContour :: TH3S -> CInt -> Ptr CDouble -> IO () Source #

setContourLevel :: TH3S -> CInt -> CDouble -> IO () Source #

setDirectory :: (ITDirectory c0, FPtr c0) => TH3S -> c0 -> IO () Source #

setEntries :: TH3S -> CDouble -> IO () Source #

setError :: TH3S -> Ptr CDouble -> IO () Source #

setLabelColorA :: Castable c0 CString => TH3S -> CShort -> c0 -> IO () Source #

setLabelSizeA :: Castable c0 CString => TH3S -> CFloat -> c0 -> IO () Source #

setLabelFontA :: Castable c0 CString => TH3S -> CShort -> c0 -> IO () Source #

setLabelOffsetA :: Castable c0 CString => TH3S -> CFloat -> c0 -> IO () Source #

setMaximum :: TH3S -> CDouble -> IO () Source #

setMinimum :: TH3S -> CDouble -> IO () Source #

setNormFactor :: TH3S -> CDouble -> IO () Source #

setStats :: TH3S -> CBool -> IO () Source #

setOption :: Castable c0 CString => TH3S -> c0 -> IO () Source #

setXTitle :: Castable c0 CString => TH3S -> c0 -> IO () Source #

setYTitle :: Castable c0 CString => TH3S -> c0 -> IO () Source #

setZTitle :: Castable c0 CString => TH3S -> c0 -> IO () Source #

showBackground :: Castable c0 CString => TH3S -> CInt -> c0 -> IO TH1 Source #

showPeaks :: Castable c0 CString => TH3S -> CDouble -> c0 -> CDouble -> IO CInt Source #

smooth :: Castable c0 CString => TH3S -> CInt -> c0 -> IO () Source #

sumw2 :: TH3S -> IO () Source #

upcastTH1 :: forall a. (FPtr a, ITH1 a) => a -> TH1 Source #

downcastTH1 :: forall a. (FPtr a, ITH1 a) => TH1 -> a Source #

tH1_GetAsymmetry :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> CDouble -> IO TH1 Source #

tH1_GetDirectory :: TH1 -> IO TDirectory Source #