{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH1S.Implementation where import FFICXX.Runtime.Cast import Data.Word import Foreign.C import Foreign.Ptr import System.IO.Unsafe import HROOT.Hist.TH1S.RawType import HROOT.Hist.TH1S.FFI import HROOT.Hist.TH1S.Interface import HROOT.Hist.TH1S.Cast 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.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.Cast import HROOT.Hist.TH1.Interface import HROOT.Core.TArrayS.RawType import HROOT.Core.TArrayS.Cast import HROOT.Core.TArrayS.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 import HROOT.Core.TArray.RawType import HROOT.Core.TArray.Cast import HROOT.Core.TArray.Interface instance ITH1S TH1S instance ITH1 TH1S where add = xform2 c_th1s_add addBinContent = xform2 c_th1s_addbincontent chi2Test = xform3 c_th1s_chi2test computeIntegral = xform0 c_th1s_computeintegral directoryAutoAdd = xform1 c_th1s_directoryautoadd divide = xform5 c_th1s_divide drawCopyTH1 = xform1 c_th1s_drawcopyth1 drawNormalized = xform2 c_th1s_drawnormalized drawPanelTH1 = xform0 c_th1s_drawpanelth1 bufferEmpty = xform1 c_th1s_bufferempty evalF = xform2 c_th1s_evalf fFT = xform2 c_th1s_fft fill1 = xform1 c_th1s_fill1 fill1w = xform2 c_th1s_fill1w fillN1 = xform4 c_th1s_filln1 fillRandom = xform2 c_th1s_fillrandom findBin = xform3 c_th1s_findbin findFixBin = xform3 c_th1s_findfixbin findFirstBinAbove = xform2 c_th1s_findfirstbinabove findLastBinAbove = xform2 c_th1s_findlastbinabove fit = xform5 c_th1s_fit fitPanelTH1 = xform0 c_th1s_fitpanelth1 getNdivisionA = xform1 c_th1s_getndivisiona getAxisColorA = xform1 c_th1s_getaxiscolora getLabelColorA = xform1 c_th1s_getlabelcolora getLabelFontA = xform1 c_th1s_getlabelfonta getLabelOffsetA = xform1 c_th1s_getlabeloffseta getLabelSizeA = xform1 c_th1s_getlabelsizea getTitleFontA = xform1 c_th1s_gettitlefonta getTitleOffsetA = xform1 c_th1s_gettitleoffseta getTitleSizeA = xform1 c_th1s_gettitlesizea getTickLengthA = xform1 c_th1s_getticklengtha getBarOffset = xform0 c_th1s_getbaroffset getBarWidth = xform0 c_th1s_getbarwidth getContour = xform1 c_th1s_getcontour getContourLevel = xform1 c_th1s_getcontourlevel getContourLevelPad = xform1 c_th1s_getcontourlevelpad getBin = xform3 c_th1s_getbin getBinCenter = xform1 c_th1s_getbincenter getBinContent1 = xform1 c_th1s_getbincontent1 getBinContent2 = xform2 c_th1s_getbincontent2 getBinContent3 = xform3 c_th1s_getbincontent3 getBinError1 = xform1 c_th1s_getbinerror1 getBinError2 = xform2 c_th1s_getbinerror2 getBinError3 = xform3 c_th1s_getbinerror3 getBinLowEdge = xform1 c_th1s_getbinlowedge getBinWidth = xform1 c_th1s_getbinwidth getCellContent = xform2 c_th1s_getcellcontent getCellError = xform2 c_th1s_getcellerror getEntries = xform0 c_th1s_getentries getEffectiveEntries = xform0 c_th1s_geteffectiveentries getFunction = xform1 c_th1s_getfunction getDimension = xform0 c_th1s_getdimension getKurtosis = xform1 c_th1s_getkurtosis getLowEdge = xform1 c_th1s_getlowedge getMaximumTH1 = xform1 c_th1s_getmaximumth1 getMaximumBin = xform0 c_th1s_getmaximumbin getMaximumStored = xform0 c_th1s_getmaximumstored getMinimumTH1 = xform1 c_th1s_getminimumth1 getMinimumBin = xform0 c_th1s_getminimumbin getMinimumStored = xform0 c_th1s_getminimumstored getMean = xform1 c_th1s_getmean getMeanError = xform1 c_th1s_getmeanerror getNbinsX = xform0 c_th1s_getnbinsx getNbinsY = xform0 c_th1s_getnbinsy getNbinsZ = xform0 c_th1s_getnbinsz getQuantilesTH1 = xform3 c_th1s_getquantilesth1 getRandom = xform0 c_th1s_getrandom getStats = xform1 c_th1s_getstats getSumOfWeights = xform0 c_th1s_getsumofweights getSumw2 = xform0 c_th1s_getsumw2 getSumw2N = xform0 c_th1s_getsumw2n getRMS = xform1 c_th1s_getrms getRMSError = xform1 c_th1s_getrmserror getSkewness = xform1 c_th1s_getskewness integral1 = xform3 c_th1s_integral1 interpolate1 = xform1 c_th1s_interpolate1 interpolate2 = xform2 c_th1s_interpolate2 interpolate3 = xform3 c_th1s_interpolate3 kolmogorovTest = xform2 c_th1s_kolmogorovtest labelsDeflate = xform1 c_th1s_labelsdeflate labelsInflate = xform1 c_th1s_labelsinflate labelsOption = xform2 c_th1s_labelsoption multiflyF = xform2 c_th1s_multiflyf multiply = xform5 c_th1s_multiply putStats = xform1 c_th1s_putstats rebin = xform3 c_th1s_rebin rebinAxis = xform2 c_th1s_rebinaxis rebuild = xform1 c_th1s_rebuild recursiveRemove = xform1 c_th1s_recursiveremove reset = xform1 c_th1s_reset resetStats = xform0 c_th1s_resetstats scale = xform2 c_th1s_scale setAxisColorA = xform2 c_th1s_setaxiscolora setAxisRange = xform3 c_th1s_setaxisrange setBarOffset = xform1 c_th1s_setbaroffset setBarWidth = xform1 c_th1s_setbarwidth setBinContent1 = xform2 c_th1s_setbincontent1 setBinContent2 = xform3 c_th1s_setbincontent2 setBinContent3 = xform4 c_th1s_setbincontent3 setBinError1 = xform2 c_th1s_setbinerror1 setBinError2 = xform3 c_th1s_setbinerror2 setBinError3 = xform4 c_th1s_setbinerror3 setBins1 = xform2 c_th1s_setbins1 setBins2 = xform4 c_th1s_setbins2 setBins3 = xform6 c_th1s_setbins3 setBinsLength = xform1 c_th1s_setbinslength setBuffer = xform2 c_th1s_setbuffer setCellContent = xform3 c_th1s_setcellcontent setContent = xform1 c_th1s_setcontent setContour = xform2 c_th1s_setcontour setContourLevel = xform2 c_th1s_setcontourlevel setDirectory = xform1 c_th1s_setdirectory setEntries = xform1 c_th1s_setentries setError = xform1 c_th1s_seterror setLabelColorA = xform2 c_th1s_setlabelcolora setLabelSizeA = xform2 c_th1s_setlabelsizea setLabelFontA = xform2 c_th1s_setlabelfonta setLabelOffsetA = xform2 c_th1s_setlabeloffseta setMaximum = xform1 c_th1s_setmaximum setMinimum = xform1 c_th1s_setminimum setNormFactor = xform1 c_th1s_setnormfactor setStats = xform1 c_th1s_setstats setOption = xform1 c_th1s_setoption setXTitle = xform1 c_th1s_setxtitle setYTitle = xform1 c_th1s_setytitle setZTitle = xform1 c_th1s_setztitle showBackground = xform2 c_th1s_showbackground showPeaks = xform3 c_th1s_showpeaks smooth = xform2 c_th1s_smooth sumw2 = xform0 c_th1s_sumw2 instance ITArrayS TH1S instance ITNamed TH1S where setName = xform1 c_th1s_setname setNameTitle = xform2 c_th1s_setnametitle setTitle = xform1 c_th1s_settitle instance ITAttLine TH1S where getLineColor = xform0 c_th1s_getlinecolor getLineStyle = xform0 c_th1s_getlinestyle getLineWidth = xform0 c_th1s_getlinewidth resetAttLine = xform1 c_th1s_resetattline setLineAttributes = xform0 c_th1s_setlineattributes setLineColor = xform1 c_th1s_setlinecolor setLineStyle = xform1 c_th1s_setlinestyle setLineWidth = xform1 c_th1s_setlinewidth instance ITAttFill TH1S where setFillColor = xform1 c_th1s_setfillcolor setFillStyle = xform1 c_th1s_setfillstyle instance ITAttMarker TH1S where getMarkerColor = xform0 c_th1s_getmarkercolor getMarkerStyle = xform0 c_th1s_getmarkerstyle getMarkerSize = xform0 c_th1s_getmarkersize resetAttMarker = xform1 c_th1s_resetattmarker setMarkerAttributes = xform0 c_th1s_setmarkerattributes setMarkerColor = xform1 c_th1s_setmarkercolor setMarkerStyle = xform1 c_th1s_setmarkerstyle setMarkerSize = xform1 c_th1s_setmarkersize instance ITObject TH1S where draw = xform1 c_th1s_draw findObject = xform1 c_th1s_findobject getName = xform0 c_th1s_getname isA = xform0 c_th1s_isa paint = xform1 c_th1s_paint printObj = xform1 c_th1s_printobj saveAs = xform2 c_th1s_saveas write = xform3 c_th1s_write instance IDeletable TH1S where delete = xform0 c_th1s_delete instance ITArray TH1S