HROOT-hist-0.8: Haskell binding to ROOT Hist modules

Safe HaskellNone

HROOT.Hist.TH1.Interface

Synopsis

Documentation

class (ITObject a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITH1 a whereSource

the TH1 class : the mother class of all histogram classes

 class TH1 : TNamed, TAttLine, TAttFill, TAttMarker

Methods

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

 void TH1::Add( TH1* h1, Double_t c1 ) 

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

 void TH1::AddBinContent( Int_t bin, Double_t w )

chi2Test :: (ITH1 c0, FPtr c0) => a -> c0 -> CString -> Ptr CDouble -> IO CDoubleSource

 Double_t TH1::Chi2Test( const TH1* h2, Option_t* option="UU", Double_t* res=0 ) const

computeIntegral :: a -> IO CDoubleSource

 Double_t TH1::ComputeIntegral ()

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

 void TH1::DirectoryAutoAdd(TDirectory* )

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

 void TH1::Divide(const TH1* h1, const TH1* h2, Double_t c1=1, Double_t c2=1, Option_t* option="")

drawCopyTH1 :: a -> CString -> IO aSource

drawNormalized :: a -> CString -> CDouble -> IO TH1Source

 TH1* TH1::DrawNormalized (Option_t* option="", Double_t norm=1) const

drawPanelTH1 :: a -> IO ()Source

bufferEmpty :: a -> CInt -> IO CIntSource

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

fFT :: (ITH1 c0, FPtr c0) => a -> c0 -> CString -> IO TH1Source

fill1 :: a -> CDouble -> IO CIntSource

fill1w :: a -> CDouble -> CDouble -> IO CIntSource

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 CIntSource

findFixBin :: a -> CDouble -> CDouble -> CDouble -> IO CIntSource

findFirstBinAbove :: a -> CDouble -> CInt -> IO CIntSource

findLastBinAbove :: a -> CDouble -> CInt -> IO CIntSource

fitPanelTH1 :: a -> IO ()Source

getNdivisionA :: a -> CString -> IO CIntSource

getAxisColorA :: a -> CString -> IO CIntSource

getLabelColorA :: a -> CString -> IO CIntSource

getLabelFontA :: a -> CString -> IO CIntSource

getLabelOffsetA :: a -> CString -> IO CDoubleSource

getLabelSizeA :: a -> CString -> IO CDoubleSource

getTitleFontA :: a -> CString -> IO CIntSource

getTitleOffsetA :: a -> CString -> IO CDoubleSource

getTitleSizeA :: a -> CString -> IO CDoubleSource

getTickLengthA :: a -> CString -> IO CDoubleSource

getBarOffset :: a -> IO CDoubleSource

getBarWidth :: a -> IO CDoubleSource

getContour :: a -> Ptr CDouble -> IO CIntSource

getContourLevel :: a -> CInt -> IO CDoubleSource

getContourLevelPad :: a -> CInt -> IO CDoubleSource

getBin :: a -> CInt -> CInt -> CInt -> IO CIntSource

getBinCenter :: a -> CInt -> IO CDoubleSource

getBinContent1 :: a -> CInt -> IO CDoubleSource

getBinContent2 :: a -> CInt -> CInt -> IO CDoubleSource

getBinContent3 :: a -> CInt -> CInt -> CInt -> IO CDoubleSource

getBinError1 :: a -> CInt -> IO CDoubleSource

getBinError2 :: a -> CInt -> CInt -> IO CDoubleSource

getBinError3 :: a -> CInt -> CInt -> CInt -> IO CDoubleSource

getBinLowEdge :: a -> CInt -> IO CDoubleSource

getBinWidth :: a -> CInt -> IO CDoubleSource

getCellContent :: a -> CInt -> CInt -> IO CDoubleSource

getCellError :: a -> CInt -> CInt -> IO CDoubleSource

getEntries :: a -> IO CDoubleSource

getEffectiveEntries :: a -> IO CDoubleSource

getFunction :: a -> CString -> IO TF1Source

getDimension :: a -> IO CIntSource

getKurtosis :: a -> CInt -> IO CDoubleSource

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

getMaximumTH1 :: a -> CDouble -> IO CDoubleSource

getMaximumBin :: a -> IO CIntSource

getMaximumStored :: a -> IO CDoubleSource

getMinimumTH1 :: a -> CDouble -> IO CDoubleSource

getMinimumBin :: a -> IO CIntSource

getMinimumStored :: a -> IO CDoubleSource

getMean :: a -> CInt -> IO CDoubleSource

getMeanError :: a -> CInt -> IO CDoubleSource

getNbinsX :: a -> IO CDoubleSource

getNbinsY :: a -> IO CDoubleSource

getNbinsZ :: a -> IO CDoubleSource

getQuantilesTH1 :: a -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CIntSource

getRandom :: a -> IO CDoubleSource

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

 void     GetStats(Double_t *stats) const;

getSumOfWeights :: a -> IO CDoubleSource

getSumw2 :: a -> IO TArrayDSource

getSumw2N :: a -> IO CIntSource

getRMS :: a -> CInt -> IO CDoubleSource

getRMSError :: a -> CInt -> IO CDoubleSource

getSkewness :: a -> CInt -> IO CDoubleSource

integral1 :: a -> CInt -> CInt -> CString -> IO CDoubleSource

interpolate1 :: a -> CDouble -> IO CDoubleSource

 Double_t Interpolate(Double_t x)

interpolate2 :: a -> CDouble -> CDouble -> IO CDoubleSource

 Double_t Interpolate(Double_t x, Double_t y)

interpolate3 :: a -> CDouble -> CDouble -> CDouble -> IO CDoubleSource

 Double_t Interpolate(Double_t x, Double_t y, Double_t z)

kolmogorovTest :: (ITH1 c0, FPtr c0) => a -> c0 -> CString -> IO CDoubleSource

 Double_t KolmogorovTest(const TH1 *h2, Option_t *option="") const

labelsDeflate :: a -> CString -> IO ()Source

 void     LabelsDeflate(Option_t *axis="X")

labelsInflate :: a -> CString -> IO ()Source

 void     LabelsInflate(Option_t *axis="X")

labelsOption :: a -> CString -> CString -> IO ()Source

 void     LabelsOption(Option_t *option="h", Option_t *axis="X")

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

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

 void     Multiply(const TH1 *h1, const TH1 *h2, Double_t c1=1, Double_t c2=1, Option_t *option=""); // *MENU*

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

 void     PutStats(Double_t *stats)

rebin :: a -> CInt -> CString -> Ptr CDouble -> IO TH1Source

 TH1     *Rebin(Int_t ngroup=2, const char*newname="", const Double_t *xbins=0);  // *MENU*

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

 void     RebinAxis(Double_t x, TAxis *axis)

rebuild :: a -> CString -> IO ()Source

 void     Rebuild(Option_t *option="")

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

 void     RecursiveRemove(TObject *obj)

reset :: a -> CString -> IO ()Source

 void     Reset(Option_t *option="")

resetStats :: a -> IO ()Source

 void     ResetStats()

scale :: a -> CDouble -> CString -> IO ()Source

 void     Scale(Double_t c1=1, Option_t *option="")

setAxisColorA :: a -> CInt -> CString -> IO ()Source

 void     SetAxisColor(Color_t color=1, Option_t *axis="X")

setAxisRange :: a -> CDouble -> CDouble -> CString -> IO ()Source

 void     SetAxisRange(Double_t xmin, Double_t xmax, Option_t *axis="X")

setBarOffset :: a -> CDouble -> IO ()Source

 void     SetBarOffset(Float_t offset=0.25)

setBarWidth :: a -> CDouble -> IO ()Source

 void     SetBarWidth(Float_t width=0.5) 

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

 void     SetBinContent(Int_t bin, Double_t content)

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

 void     SetBinContent(Int_t binx, Int_t biny, Double_t content)

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

 void     SetBinContent(Int_t binx, Int_t biny, Int_t binz, Double_t content)

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 :: a -> CInt -> CString -> 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 :: a -> CInt -> CString -> IO ()Source

setLabelSizeA :: a -> CDouble -> CString -> IO ()Source

setLabelFontA :: a -> CInt -> CString -> IO ()Source

setLabelOffsetA :: a -> CDouble -> CString -> IO ()Source

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

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

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

setStats :: a -> CInt -> IO ()Source

setOption :: a -> CString -> IO ()Source

setXTitle :: a -> CString -> IO ()Source

setYTitle :: a -> CString -> IO ()Source

setZTitle :: a -> CString -> IO ()Source

showBackground :: a -> CInt -> CString -> IO TH1Source

 TH1     *ShowBackground(Int_t niter=20, Option_t *option="same");

showPeaks :: a -> CDouble -> CString -> CDouble -> IO CIntSource

 Int_t    ShowPeaks(Double_t sigma=2, Option_t *option="", Double_t threshold=0.05); // *MENU*

smooth :: a -> CInt -> CString -> IO ()Source

 void     Smooth(Int_t ntimes=1, Option_t *option=""); // *MENU*

sumw2 :: a -> IO ()Source

upcastTH1 :: (FPtr a, ITH1 a) => a -> TH1Source

downcastTH1 :: (FPtr a, ITH1 a) => TH1 -> aSource