{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH1.Interface where import Data.Word import Foreign.C import Foreign.Ptr import FFICXX.Runtime.Cast import HROOT.Hist.TH1.RawType import HROOT.Core.TDirectory.RawType import HROOT.Hist.TF1.RawType import HROOT.Core.TArrayD.RawType import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.Interface import HROOT.Core.TDirectory.Interface import HROOT.Core.TObject.Interface import {-# SOURCE #-} HROOT.Hist.TF1.Interface import {-# SOURCE #-} HROOT.Hist.TAxis.Interface class (ITNamed a, ITAttLine a, ITAttFill a, ITAttMarker a) => ITH1 a where add :: (ITH1 c0, FPtr c0) => a -> c0 -> CDouble -> IO () addBinContent :: a -> CInt -> CDouble -> IO () chi2Test :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> (Ptr CDouble) -> IO CDouble computeIntegral :: a -> IO CDouble directoryAutoAdd :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO () divide :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () drawCopyTH1 :: Castable c0 CString => a -> c0 -> IO a drawNormalized :: Castable c0 CString => a -> c0 -> CDouble -> IO TH1 drawPanelTH1 :: a -> IO () bufferEmpty :: a -> CInt -> IO CInt evalF :: (Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> c1 -> IO () fFT :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> IO TH1 fill1 :: a -> CDouble -> IO CInt fill1w :: a -> CDouble -> CDouble -> IO CInt fillN1 :: a -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () fillRandom :: (ITH1 c0, FPtr c0) => a -> c0 -> CInt -> IO () findBin :: a -> CDouble -> CDouble -> CDouble -> IO CInt findFixBin :: a -> CDouble -> CDouble -> CDouble -> IO CInt findFirstBinAbove :: a -> CDouble -> CInt -> IO CInt findLastBinAbove :: a -> CDouble -> CInt -> IO CInt fit :: (Castable c2 CString, Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> c1 -> c2 -> CDouble -> CDouble -> IO () fitPanelTH1 :: a -> IO () getNdivisionA :: Castable c0 CString => a -> c0 -> IO CInt getAxisColorA :: Castable c0 CString => a -> c0 -> IO CInt getLabelColorA :: Castable c0 CString => a -> c0 -> IO CInt getLabelFontA :: Castable c0 CString => a -> c0 -> IO CInt getLabelOffsetA :: Castable c0 CString => a -> c0 -> IO CDouble getLabelSizeA :: Castable c0 CString => a -> c0 -> IO CDouble getTitleFontA :: Castable c0 CString => a -> c0 -> IO CInt getTitleOffsetA :: Castable c0 CString => a -> c0 -> IO CDouble getTitleSizeA :: Castable c0 CString => a -> c0 -> IO CDouble getTickLengthA :: Castable c0 CString => a -> c0 -> IO CDouble getBarOffset :: a -> IO CDouble getBarWidth :: a -> IO CDouble getContour :: a -> (Ptr CDouble) -> IO CInt getContourLevel :: a -> CInt -> IO CDouble getContourLevelPad :: a -> CInt -> IO CDouble getBin :: a -> CInt -> CInt -> CInt -> IO CInt getBinCenter :: a -> CInt -> IO CDouble getBinContent1 :: a -> CInt -> IO CDouble getBinContent2 :: a -> CInt -> CInt -> IO CDouble getBinContent3 :: a -> CInt -> CInt -> CInt -> IO CDouble getBinError1 :: a -> CInt -> IO CDouble getBinError2 :: a -> CInt -> CInt -> IO CDouble getBinError3 :: a -> CInt -> CInt -> CInt -> IO CDouble getBinLowEdge :: a -> CInt -> IO CDouble getBinWidth :: a -> CInt -> IO CDouble getCellContent :: a -> CInt -> CInt -> IO CDouble getCellError :: a -> CInt -> CInt -> IO CDouble getEntries :: a -> IO CDouble getEffectiveEntries :: a -> IO CDouble getFunction :: Castable c0 CString => a -> c0 -> IO TF1 getDimension :: a -> IO CInt getKurtosis :: a -> CInt -> IO CDouble getLowEdge :: a -> (Ptr CDouble) -> IO () getMaximumTH1 :: a -> CDouble -> IO CDouble getMaximumBin :: a -> IO CInt getMaximumStored :: a -> IO CDouble getMinimumTH1 :: a -> CDouble -> IO CDouble getMinimumBin :: a -> IO CInt getMinimumStored :: a -> IO CDouble getMean :: a -> CInt -> IO CDouble getMeanError :: a -> CInt -> IO CDouble getNbinsX :: a -> IO CDouble getNbinsY :: a -> IO CDouble getNbinsZ :: a -> IO CDouble getQuantilesTH1 :: a -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt getRandom :: a -> IO CDouble getStats :: a -> (Ptr CDouble) -> IO () getSumOfWeights :: a -> IO CDouble getSumw2 :: a -> IO TArrayD getSumw2N :: a -> IO CInt getRMS :: a -> CInt -> IO CDouble getRMSError :: a -> CInt -> IO CDouble getSkewness :: a -> CInt -> IO CDouble integral1 :: Castable c0 CString => a -> CInt -> CInt -> c0 -> IO CDouble interpolate1 :: a -> CDouble -> IO CDouble interpolate2 :: a -> CDouble -> CDouble -> IO CDouble interpolate3 :: a -> CDouble -> CDouble -> CDouble -> IO CDouble kolmogorovTest :: (Castable c1 CString, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> IO CDouble labelsDeflate :: Castable c0 CString => a -> c0 -> IO () labelsInflate :: Castable c0 CString => a -> c0 -> IO () labelsOption :: (Castable c1 CString, Castable c0 CString) => a -> c0 -> c1 -> IO () multiflyF :: (ITF1 c0, FPtr c0) => a -> c0 -> CDouble -> IO () multiply :: (Castable c2 CString, ITH1 c1, FPtr c1, ITH1 c0, FPtr c0) => a -> c0 -> c1 -> CDouble -> CDouble -> c2 -> IO () putStats :: a -> (Ptr CDouble) -> IO () rebin :: Castable c0 CString => a -> CInt -> c0 -> (Ptr CDouble) -> IO TH1 rebinAxis :: (ITAxis c0, FPtr c0) => a -> CDouble -> c0 -> IO () rebuild :: Castable c0 CString => a -> c0 -> IO () recursiveRemove :: (ITObject c0, FPtr c0) => a -> c0 -> IO () reset :: Castable c0 CString => a -> c0 -> IO () resetStats :: a -> IO () scale :: Castable c0 CString => a -> CDouble -> c0 -> IO () setAxisColorA :: Castable c0 CString => a -> CInt -> c0 -> IO () setAxisRange :: Castable c0 CString => a -> CDouble -> CDouble -> c0 -> IO () setBarOffset :: a -> CDouble -> IO () setBarWidth :: a -> CDouble -> IO () setBinContent1 :: a -> CInt -> CDouble -> IO () setBinContent2 :: a -> CInt -> CInt -> CDouble -> IO () setBinContent3 :: a -> CInt -> CInt -> CInt -> CDouble -> IO () setBinError1 :: a -> CInt -> CDouble -> IO () setBinError2 :: a -> CInt -> CInt -> CDouble -> IO () setBinError3 :: a -> CInt -> CInt -> CInt -> CDouble -> IO () setBins1 :: a -> CInt -> (Ptr CDouble) -> IO () setBins2 :: a -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () setBins3 :: a -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO () setBinsLength :: a -> CInt -> IO () setBuffer :: Castable c0 CString => a -> CInt -> c0 -> IO () setCellContent :: a -> CInt -> CInt -> CDouble -> IO () setContent :: a -> (Ptr CDouble) -> IO () setContour :: a -> CInt -> (Ptr CDouble) -> IO () setContourLevel :: a -> CInt -> CDouble -> IO () setDirectory :: (ITDirectory c0, FPtr c0) => a -> c0 -> IO () setEntries :: a -> CDouble -> IO () setError :: a -> (Ptr CDouble) -> IO () setLabelColorA :: Castable c0 CString => a -> CInt -> c0 -> IO () setLabelSizeA :: Castable c0 CString => a -> CDouble -> c0 -> IO () setLabelFontA :: Castable c0 CString => a -> CInt -> c0 -> IO () setLabelOffsetA :: Castable c0 CString => a -> CDouble -> c0 -> IO () setMaximum :: a -> CDouble -> IO () setMinimum :: a -> CDouble -> IO () setNormFactor :: a -> CDouble -> IO () setStats :: a -> CInt -> IO () setOption :: Castable c0 CString => a -> c0 -> IO () setXTitle :: Castable c0 CString => a -> c0 -> IO () setYTitle :: Castable c0 CString => a -> c0 -> IO () setZTitle :: Castable c0 CString => a -> c0 -> IO () showBackground :: Castable c0 CString => a -> CInt -> c0 -> IO TH1 showPeaks :: Castable c0 CString => a -> CDouble -> c0 -> CDouble -> IO CInt smooth :: Castable c0 CString => a -> CInt -> c0 -> IO () sumw2 :: a -> IO () upcastTH1 :: forall a . (FPtr a, ITH1 a) => a -> TH1 upcastTH1 h = let fh = get_fptr h fh2 :: Ptr RawTH1 = castPtr fh in cast_fptr_to_obj fh2 downcastTH1 :: forall a . (FPtr a, ITH1 a) => TH1 -> a downcastTH1 h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2