{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH1.Implementation where import FFICXX.Runtime.Cast import Data.Word import Foreign.C import Foreign.Ptr import System.IO.Unsafe import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.FFI import HROOT.Hist.TH1.Interface import HROOT.Hist.TH1.Cast import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Core.TDirectory.RawType import HROOT.Core.TDirectory.Cast import HROOT.Core.TDirectory.Interface import HROOT.Hist.TF1.RawType import HROOT.Hist.TF1.Cast import HROOT.Hist.TF1.Interface import HROOT.Core.TArrayD.RawType import HROOT.Core.TArrayD.Cast import HROOT.Core.TArrayD.Interface import HROOT.Hist.TAxis.RawType import HROOT.Hist.TAxis.Cast import HROOT.Hist.TAxis.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.RawType import HROOT.Core.TAttLine.Cast import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.RawType import HROOT.Core.TAttFill.Cast import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.RawType import HROOT.Core.TAttMarker.Cast import HROOT.Core.TAttMarker.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import HROOT.Core.Deletable.RawType import HROOT.Core.Deletable.Cast import HROOT.Core.Deletable.Interface instance ITH1 TH1 where add = xform2 c_th1_add addBinContent = xform2 c_th1_addbincontent chi2Test = xform3 c_th1_chi2test computeIntegral = xform0 c_th1_computeintegral directoryAutoAdd = xform1 c_th1_directoryautoadd divide = xform5 c_th1_divide drawCopyTH1 = xform1 c_th1_drawcopyth1 drawNormalized = xform2 c_th1_drawnormalized drawPanelTH1 = xform0 c_th1_drawpanelth1 bufferEmpty = xform1 c_th1_bufferempty evalF = xform2 c_th1_evalf fFT = xform2 c_th1_fft fill1 = xform1 c_th1_fill1 fill1w = xform2 c_th1_fill1w fillN1 = xform4 c_th1_filln1 fillRandom = xform2 c_th1_fillrandom findBin = xform3 c_th1_findbin findFixBin = xform3 c_th1_findfixbin findFirstBinAbove = xform2 c_th1_findfirstbinabove findLastBinAbove = xform2 c_th1_findlastbinabove fit = xform5 c_th1_fit fitPanelTH1 = xform0 c_th1_fitpanelth1 getNdivisionA = xform1 c_th1_getndivisiona getAxisColorA = xform1 c_th1_getaxiscolora getLabelColorA = xform1 c_th1_getlabelcolora getLabelFontA = xform1 c_th1_getlabelfonta getLabelOffsetA = xform1 c_th1_getlabeloffseta getLabelSizeA = xform1 c_th1_getlabelsizea getTitleFontA = xform1 c_th1_gettitlefonta getTitleOffsetA = xform1 c_th1_gettitleoffseta getTitleSizeA = xform1 c_th1_gettitlesizea getTickLengthA = xform1 c_th1_getticklengtha getBarOffset = xform0 c_th1_getbaroffset getBarWidth = xform0 c_th1_getbarwidth getContour = xform1 c_th1_getcontour getContourLevel = xform1 c_th1_getcontourlevel getContourLevelPad = xform1 c_th1_getcontourlevelpad getBin = xform3 c_th1_getbin getBinCenter = xform1 c_th1_getbincenter getBinContent1 = xform1 c_th1_getbincontent1 getBinContent2 = xform2 c_th1_getbincontent2 getBinContent3 = xform3 c_th1_getbincontent3 getBinError1 = xform1 c_th1_getbinerror1 getBinError2 = xform2 c_th1_getbinerror2 getBinError3 = xform3 c_th1_getbinerror3 getBinLowEdge = xform1 c_th1_getbinlowedge getBinWidth = xform1 c_th1_getbinwidth getCellContent = xform2 c_th1_getcellcontent getCellError = xform2 c_th1_getcellerror getEntries = xform0 c_th1_getentries getEffectiveEntries = xform0 c_th1_geteffectiveentries getFunction = xform1 c_th1_getfunction getDimension = xform0 c_th1_getdimension getKurtosis = xform1 c_th1_getkurtosis getLowEdge = xform1 c_th1_getlowedge getMaximumTH1 = xform1 c_th1_getmaximumth1 getMaximumBin = xform0 c_th1_getmaximumbin getMaximumStored = xform0 c_th1_getmaximumstored getMinimumTH1 = xform1 c_th1_getminimumth1 getMinimumBin = xform0 c_th1_getminimumbin getMinimumStored = xform0 c_th1_getminimumstored getMean = xform1 c_th1_getmean getMeanError = xform1 c_th1_getmeanerror getNbinsX = xform0 c_th1_getnbinsx getNbinsY = xform0 c_th1_getnbinsy getNbinsZ = xform0 c_th1_getnbinsz getQuantilesTH1 = xform3 c_th1_getquantilesth1 getRandom = xform0 c_th1_getrandom getStats = xform1 c_th1_getstats getSumOfWeights = xform0 c_th1_getsumofweights getSumw2 = xform0 c_th1_getsumw2 getSumw2N = xform0 c_th1_getsumw2n getRMS = xform1 c_th1_getrms getRMSError = xform1 c_th1_getrmserror getSkewness = xform1 c_th1_getskewness integral1 = xform3 c_th1_integral1 interpolate1 = xform1 c_th1_interpolate1 interpolate2 = xform2 c_th1_interpolate2 interpolate3 = xform3 c_th1_interpolate3 kolmogorovTest = xform2 c_th1_kolmogorovtest labelsDeflate = xform1 c_th1_labelsdeflate labelsInflate = xform1 c_th1_labelsinflate labelsOption = xform2 c_th1_labelsoption multiflyF = xform2 c_th1_multiflyf multiply = xform5 c_th1_multiply putStats = xform1 c_th1_putstats rebin = xform3 c_th1_rebin rebinAxis = xform2 c_th1_rebinaxis rebuild = xform1 c_th1_rebuild recursiveRemove = xform1 c_th1_recursiveremove reset = xform1 c_th1_reset resetStats = xform0 c_th1_resetstats scale = xform2 c_th1_scale setAxisColorA = xform2 c_th1_setaxiscolora setAxisRange = xform3 c_th1_setaxisrange setBarOffset = xform1 c_th1_setbaroffset setBarWidth = xform1 c_th1_setbarwidth setBinContent1 = xform2 c_th1_setbincontent1 setBinContent2 = xform3 c_th1_setbincontent2 setBinContent3 = xform4 c_th1_setbincontent3 setBinError1 = xform2 c_th1_setbinerror1 setBinError2 = xform3 c_th1_setbinerror2 setBinError3 = xform4 c_th1_setbinerror3 setBins1 = xform2 c_th1_setbins1 setBins2 = xform4 c_th1_setbins2 setBins3 = xform6 c_th1_setbins3 setBinsLength = xform1 c_th1_setbinslength setBuffer = xform2 c_th1_setbuffer setCellContent = xform3 c_th1_setcellcontent setContent = xform1 c_th1_setcontent setContour = xform2 c_th1_setcontour setContourLevel = xform2 c_th1_setcontourlevel setDirectory = xform1 c_th1_setdirectory setEntries = xform1 c_th1_setentries setError = xform1 c_th1_seterror setLabelColorA = xform2 c_th1_setlabelcolora setLabelSizeA = xform2 c_th1_setlabelsizea setLabelFontA = xform2 c_th1_setlabelfonta setLabelOffsetA = xform2 c_th1_setlabeloffseta setMaximum = xform1 c_th1_setmaximum setMinimum = xform1 c_th1_setminimum setNormFactor = xform1 c_th1_setnormfactor setStats = xform1 c_th1_setstats setOption = xform1 c_th1_setoption setXTitle = xform1 c_th1_setxtitle setYTitle = xform1 c_th1_setytitle setZTitle = xform1 c_th1_setztitle showBackground = xform2 c_th1_showbackground showPeaks = xform3 c_th1_showpeaks smooth = xform2 c_th1_smooth sumw2 = xform0 c_th1_sumw2 instance ITNamed TH1 where setName = xform1 c_th1_setname setNameTitle = xform2 c_th1_setnametitle setTitle = xform1 c_th1_settitle instance ITAttLine TH1 where getLineColor = xform0 c_th1_getlinecolor getLineStyle = xform0 c_th1_getlinestyle getLineWidth = xform0 c_th1_getlinewidth resetAttLine = xform1 c_th1_resetattline setLineAttributes = xform0 c_th1_setlineattributes setLineColor = xform1 c_th1_setlinecolor setLineStyle = xform1 c_th1_setlinestyle setLineWidth = xform1 c_th1_setlinewidth instance ITAttFill TH1 where setFillColor = xform1 c_th1_setfillcolor setFillStyle = xform1 c_th1_setfillstyle instance ITAttMarker TH1 where getMarkerColor = xform0 c_th1_getmarkercolor getMarkerStyle = xform0 c_th1_getmarkerstyle getMarkerSize = xform0 c_th1_getmarkersize resetAttMarker = xform1 c_th1_resetattmarker setMarkerAttributes = xform0 c_th1_setmarkerattributes setMarkerColor = xform1 c_th1_setmarkercolor setMarkerStyle = xform1 c_th1_setmarkerstyle setMarkerSize = xform1 c_th1_setmarkersize instance ITObject TH1 where draw = xform1 c_th1_draw findObject = xform1 c_th1_findobject getName = xform0 c_th1_getname isA = xform0 c_th1_isa paint = xform1 c_th1_paint printObj = xform1 c_th1_printobj saveAs = xform2 c_th1_saveas write = xform3 c_th1_write instance IDeletable TH1 where delete = xform0 c_th1_delete tH1GetAsymmetry :: (ITH1 c0, FPtr c0) => TH1 -> c0 -> CDouble -> CDouble -> IO TH1 tH1GetAsymmetry = xform3 c_th1_th1getasymmetry tH1GetBufferLength :: TH1 -> IO CInt tH1GetBufferLength = xform0 c_th1_th1getbufferlength tH1GetBufferSize :: TH1 -> IO CInt tH1GetBufferSize = xform0 c_th1_th1getbuffersize tH1GetDirectory :: TH1 -> IO TDirectory tH1GetDirectory = xform0 c_th1_th1getdirectory tH1IsBinOverflow :: TH1 -> CInt -> IO CInt tH1IsBinOverflow = xform1 c_th1_th1isbinoverflow tH1IsBinUnderflow :: TH1 -> CInt -> IO CInt tH1IsBinUnderflow = xform1 c_th1_th1isbinunderflow tH1UseCurrentStyle :: TH1 -> IO () tH1UseCurrentStyle = xform0 c_th1_th1usecurrentstyle tH1GetDefaultBufferSize :: IO CInt tH1GetDefaultBufferSize = xformnull c_th1_th1getdefaultbuffersize tH1GetDefaultSumw2 :: IO CInt tH1GetDefaultSumw2 = xformnull c_th1_th1getdefaultsumw2 tH1SetDefaultBufferSize :: CInt -> IO () tH1SetDefaultBufferSize = xform0 c_th1_th1setdefaultbuffersize tH1SetDefaultSumw2 :: CInt -> IO () tH1SetDefaultSumw2 = xform0 c_th1_th1setdefaultsumw2 tH1SmoothArray :: CInt -> (Ptr CDouble) -> CInt -> IO () tH1SmoothArray = xform2 c_th1_th1smootharray tH1StatOverflows :: CInt -> IO () tH1StatOverflows = xform0 c_th1_th1statoverflows