{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH3I.Implementation where import FFICXX.Runtime.Cast import Data.Word import Foreign.C import Foreign.Ptr import System.IO.Unsafe import HROOT.Hist.TH3I.RawType import HROOT.Hist.TH3I.FFI import HROOT.Hist.TH3I.Interface import HROOT.Hist.TH3I.Cast import HROOT.Hist.TH1D.RawType import HROOT.Hist.TH1D.Cast import HROOT.Hist.TH1D.Interface import HROOT.Hist.TF1.RawType import HROOT.Hist.TF1.Cast import HROOT.Hist.TF1.Interface import HROOT.Core.TDirectory.RawType import HROOT.Core.TDirectory.Cast import HROOT.Core.TDirectory.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.TH3.RawType import HROOT.Hist.TH3.Cast import HROOT.Hist.TH3.Interface import HROOT.Core.TArrayI.RawType import HROOT.Core.TArrayI.Cast import HROOT.Core.TArrayI.Interface import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.Cast import HROOT.Hist.TH1.Interface import HROOT.Core.TAtt3D.RawType import HROOT.Core.TAtt3D.Cast import HROOT.Core.TAtt3D.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 ITH3I TH3I instance ITH3 TH3I where fill3 = xform3 c_th3i_fill3 fill3w = xform4 c_th3i_fill3w fitSlicesZ = xform7 c_th3i_fitslicesz getCorrelationFactor3 = xform2 c_th3i_getcorrelationfactor3 getCovariance3 = xform2 c_th3i_getcovariance3 rebinX3 = xform2 c_th3i_rebinx3 rebinY3 = xform2 c_th3i_rebiny3 rebinZ3 = xform2 c_th3i_rebinz3 rebin3D = xform4 c_th3i_rebin3d instance ITArrayI TH3I instance ITH1 TH3I where add = xform2 c_th3i_add addBinContent = xform2 c_th3i_addbincontent chi2Test = xform3 c_th3i_chi2test computeIntegral = xform0 c_th3i_computeintegral directoryAutoAdd = xform1 c_th3i_directoryautoadd divide = xform5 c_th3i_divide drawCopyTH1 = xform1 c_th3i_drawcopyth1 drawNormalized = xform2 c_th3i_drawnormalized drawPanelTH1 = xform0 c_th3i_drawpanelth1 bufferEmpty = xform1 c_th3i_bufferempty evalF = xform2 c_th3i_evalf fFT = xform2 c_th3i_fft fill1 = xform1 c_th3i_fill1 fill1w = xform2 c_th3i_fill1w fillN1 = xform4 c_th3i_filln1 fillRandom = xform2 c_th3i_fillrandom findBin = xform3 c_th3i_findbin findFixBin = xform3 c_th3i_findfixbin findFirstBinAbove = xform2 c_th3i_findfirstbinabove findLastBinAbove = xform2 c_th3i_findlastbinabove fit = xform5 c_th3i_fit fitPanelTH1 = xform0 c_th3i_fitpanelth1 getNdivisionA = xform1 c_th3i_getndivisiona getAxisColorA = xform1 c_th3i_getaxiscolora getLabelColorA = xform1 c_th3i_getlabelcolora getLabelFontA = xform1 c_th3i_getlabelfonta getLabelOffsetA = xform1 c_th3i_getlabeloffseta getLabelSizeA = xform1 c_th3i_getlabelsizea getTitleFontA = xform1 c_th3i_gettitlefonta getTitleOffsetA = xform1 c_th3i_gettitleoffseta getTitleSizeA = xform1 c_th3i_gettitlesizea getTickLengthA = xform1 c_th3i_getticklengtha getBarOffset = xform0 c_th3i_getbaroffset getBarWidth = xform0 c_th3i_getbarwidth getContour = xform1 c_th3i_getcontour getContourLevel = xform1 c_th3i_getcontourlevel getContourLevelPad = xform1 c_th3i_getcontourlevelpad getBin = xform3 c_th3i_getbin getBinCenter = xform1 c_th3i_getbincenter getBinContent1 = xform1 c_th3i_getbincontent1 getBinContent2 = xform2 c_th3i_getbincontent2 getBinContent3 = xform3 c_th3i_getbincontent3 getBinError1 = xform1 c_th3i_getbinerror1 getBinError2 = xform2 c_th3i_getbinerror2 getBinError3 = xform3 c_th3i_getbinerror3 getBinLowEdge = xform1 c_th3i_getbinlowedge getBinWidth = xform1 c_th3i_getbinwidth getCellContent = xform2 c_th3i_getcellcontent getCellError = xform2 c_th3i_getcellerror getEntries = xform0 c_th3i_getentries getEffectiveEntries = xform0 c_th3i_geteffectiveentries getFunction = xform1 c_th3i_getfunction getDimension = xform0 c_th3i_getdimension getKurtosis = xform1 c_th3i_getkurtosis getLowEdge = xform1 c_th3i_getlowedge getMaximumTH1 = xform1 c_th3i_getmaximumth1 getMaximumBin = xform0 c_th3i_getmaximumbin getMaximumStored = xform0 c_th3i_getmaximumstored getMinimumTH1 = xform1 c_th3i_getminimumth1 getMinimumBin = xform0 c_th3i_getminimumbin getMinimumStored = xform0 c_th3i_getminimumstored getMean = xform1 c_th3i_getmean getMeanError = xform1 c_th3i_getmeanerror getNbinsX = xform0 c_th3i_getnbinsx getNbinsY = xform0 c_th3i_getnbinsy getNbinsZ = xform0 c_th3i_getnbinsz getQuantilesTH1 = xform3 c_th3i_getquantilesth1 getRandom = xform0 c_th3i_getrandom getStats = xform1 c_th3i_getstats getSumOfWeights = xform0 c_th3i_getsumofweights getSumw2 = xform0 c_th3i_getsumw2 getSumw2N = xform0 c_th3i_getsumw2n getRMS = xform1 c_th3i_getrms getRMSError = xform1 c_th3i_getrmserror getSkewness = xform1 c_th3i_getskewness integral1 = xform3 c_th3i_integral1 interpolate1 = xform1 c_th3i_interpolate1 interpolate2 = xform2 c_th3i_interpolate2 interpolate3 = xform3 c_th3i_interpolate3 kolmogorovTest = xform2 c_th3i_kolmogorovtest labelsDeflate = xform1 c_th3i_labelsdeflate labelsInflate = xform1 c_th3i_labelsinflate labelsOption = xform2 c_th3i_labelsoption multiflyF = xform2 c_th3i_multiflyf multiply = xform5 c_th3i_multiply putStats = xform1 c_th3i_putstats rebin = xform3 c_th3i_rebin rebinAxis = xform2 c_th3i_rebinaxis rebuild = xform1 c_th3i_rebuild recursiveRemove = xform1 c_th3i_recursiveremove reset = xform1 c_th3i_reset resetStats = xform0 c_th3i_resetstats scale = xform2 c_th3i_scale setAxisColorA = xform2 c_th3i_setaxiscolora setAxisRange = xform3 c_th3i_setaxisrange setBarOffset = xform1 c_th3i_setbaroffset setBarWidth = xform1 c_th3i_setbarwidth setBinContent1 = xform2 c_th3i_setbincontent1 setBinContent2 = xform3 c_th3i_setbincontent2 setBinContent3 = xform4 c_th3i_setbincontent3 setBinError1 = xform2 c_th3i_setbinerror1 setBinError2 = xform3 c_th3i_setbinerror2 setBinError3 = xform4 c_th3i_setbinerror3 setBins1 = xform2 c_th3i_setbins1 setBins2 = xform4 c_th3i_setbins2 setBins3 = xform6 c_th3i_setbins3 setBinsLength = xform1 c_th3i_setbinslength setBuffer = xform2 c_th3i_setbuffer setCellContent = xform3 c_th3i_setcellcontent setContent = xform1 c_th3i_setcontent setContour = xform2 c_th3i_setcontour setContourLevel = xform2 c_th3i_setcontourlevel setDirectory = xform1 c_th3i_setdirectory setEntries = xform1 c_th3i_setentries setError = xform1 c_th3i_seterror setLabelColorA = xform2 c_th3i_setlabelcolora setLabelSizeA = xform2 c_th3i_setlabelsizea setLabelFontA = xform2 c_th3i_setlabelfonta setLabelOffsetA = xform2 c_th3i_setlabeloffseta setMaximum = xform1 c_th3i_setmaximum setMinimum = xform1 c_th3i_setminimum setNormFactor = xform1 c_th3i_setnormfactor setStats = xform1 c_th3i_setstats setOption = xform1 c_th3i_setoption setXTitle = xform1 c_th3i_setxtitle setYTitle = xform1 c_th3i_setytitle setZTitle = xform1 c_th3i_setztitle showBackground = xform2 c_th3i_showbackground showPeaks = xform3 c_th3i_showpeaks smooth = xform2 c_th3i_smooth sumw2 = xform0 c_th3i_sumw2 instance ITAtt3D TH3I instance ITNamed TH3I where setName = xform1 c_th3i_setname setNameTitle = xform2 c_th3i_setnametitle setTitle = xform1 c_th3i_settitle instance ITAttLine TH3I where getLineColor = xform0 c_th3i_getlinecolor getLineStyle = xform0 c_th3i_getlinestyle getLineWidth = xform0 c_th3i_getlinewidth resetAttLine = xform1 c_th3i_resetattline setLineAttributes = xform0 c_th3i_setlineattributes setLineColor = xform1 c_th3i_setlinecolor setLineStyle = xform1 c_th3i_setlinestyle setLineWidth = xform1 c_th3i_setlinewidth instance ITAttFill TH3I where setFillColor = xform1 c_th3i_setfillcolor setFillStyle = xform1 c_th3i_setfillstyle instance ITAttMarker TH3I where getMarkerColor = xform0 c_th3i_getmarkercolor getMarkerStyle = xform0 c_th3i_getmarkerstyle getMarkerSize = xform0 c_th3i_getmarkersize resetAttMarker = xform1 c_th3i_resetattmarker setMarkerAttributes = xform0 c_th3i_setmarkerattributes setMarkerColor = xform1 c_th3i_setmarkercolor setMarkerStyle = xform1 c_th3i_setmarkerstyle setMarkerSize = xform1 c_th3i_setmarkersize instance ITObject TH3I where draw = xform1 c_th3i_draw findObject = xform1 c_th3i_findobject getName = xform0 c_th3i_getname isA = xform0 c_th3i_isa paint = xform1 c_th3i_paint printObj = xform1 c_th3i_printobj saveAs = xform2 c_th3i_saveas write = xform3 c_th3i_write instance IDeletable TH3I where delete = xform0 c_th3i_delete instance ITArray TH3I