{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH3F.Implementation where import FFICXX.Runtime.Cast import Data.Word import Foreign.C import Foreign.Ptr import System.IO.Unsafe import HROOT.Hist.TH3F.RawType import HROOT.Hist.TH3F.FFI import HROOT.Hist.TH3F.Interface import HROOT.Hist.TH3F.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.TArrayF.RawType import HROOT.Core.TArrayF.Cast import HROOT.Core.TArrayF.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 ITH3F TH3F instance ITH3 TH3F where fill3 = xform3 c_th3f_fill3 fill3w = xform4 c_th3f_fill3w fitSlicesZ = xform7 c_th3f_fitslicesz getCorrelationFactor3 = xform2 c_th3f_getcorrelationfactor3 getCovariance3 = xform2 c_th3f_getcovariance3 rebinX3 = xform2 c_th3f_rebinx3 rebinY3 = xform2 c_th3f_rebiny3 rebinZ3 = xform2 c_th3f_rebinz3 rebin3D = xform4 c_th3f_rebin3d instance ITArrayF TH3F instance ITH1 TH3F where add = xform2 c_th3f_add addBinContent = xform2 c_th3f_addbincontent chi2Test = xform3 c_th3f_chi2test computeIntegral = xform0 c_th3f_computeintegral directoryAutoAdd = xform1 c_th3f_directoryautoadd divide = xform5 c_th3f_divide drawCopyTH1 = xform1 c_th3f_drawcopyth1 drawNormalized = xform2 c_th3f_drawnormalized drawPanelTH1 = xform0 c_th3f_drawpanelth1 bufferEmpty = xform1 c_th3f_bufferempty evalF = xform2 c_th3f_evalf fFT = xform2 c_th3f_fft fill1 = xform1 c_th3f_fill1 fill1w = xform2 c_th3f_fill1w fillN1 = xform4 c_th3f_filln1 fillRandom = xform2 c_th3f_fillrandom findBin = xform3 c_th3f_findbin findFixBin = xform3 c_th3f_findfixbin findFirstBinAbove = xform2 c_th3f_findfirstbinabove findLastBinAbove = xform2 c_th3f_findlastbinabove fit = xform5 c_th3f_fit fitPanelTH1 = xform0 c_th3f_fitpanelth1 getNdivisionA = xform1 c_th3f_getndivisiona getAxisColorA = xform1 c_th3f_getaxiscolora getLabelColorA = xform1 c_th3f_getlabelcolora getLabelFontA = xform1 c_th3f_getlabelfonta getLabelOffsetA = xform1 c_th3f_getlabeloffseta getLabelSizeA = xform1 c_th3f_getlabelsizea getTitleFontA = xform1 c_th3f_gettitlefonta getTitleOffsetA = xform1 c_th3f_gettitleoffseta getTitleSizeA = xform1 c_th3f_gettitlesizea getTickLengthA = xform1 c_th3f_getticklengtha getBarOffset = xform0 c_th3f_getbaroffset getBarWidth = xform0 c_th3f_getbarwidth getContour = xform1 c_th3f_getcontour getContourLevel = xform1 c_th3f_getcontourlevel getContourLevelPad = xform1 c_th3f_getcontourlevelpad getBin = xform3 c_th3f_getbin getBinCenter = xform1 c_th3f_getbincenter getBinContent1 = xform1 c_th3f_getbincontent1 getBinContent2 = xform2 c_th3f_getbincontent2 getBinContent3 = xform3 c_th3f_getbincontent3 getBinError1 = xform1 c_th3f_getbinerror1 getBinError2 = xform2 c_th3f_getbinerror2 getBinError3 = xform3 c_th3f_getbinerror3 getBinLowEdge = xform1 c_th3f_getbinlowedge getBinWidth = xform1 c_th3f_getbinwidth getCellContent = xform2 c_th3f_getcellcontent getCellError = xform2 c_th3f_getcellerror getEntries = xform0 c_th3f_getentries getEffectiveEntries = xform0 c_th3f_geteffectiveentries getFunction = xform1 c_th3f_getfunction getDimension = xform0 c_th3f_getdimension getKurtosis = xform1 c_th3f_getkurtosis getLowEdge = xform1 c_th3f_getlowedge getMaximumTH1 = xform1 c_th3f_getmaximumth1 getMaximumBin = xform0 c_th3f_getmaximumbin getMaximumStored = xform0 c_th3f_getmaximumstored getMinimumTH1 = xform1 c_th3f_getminimumth1 getMinimumBin = xform0 c_th3f_getminimumbin getMinimumStored = xform0 c_th3f_getminimumstored getMean = xform1 c_th3f_getmean getMeanError = xform1 c_th3f_getmeanerror getNbinsX = xform0 c_th3f_getnbinsx getNbinsY = xform0 c_th3f_getnbinsy getNbinsZ = xform0 c_th3f_getnbinsz getQuantilesTH1 = xform3 c_th3f_getquantilesth1 getRandom = xform0 c_th3f_getrandom getStats = xform1 c_th3f_getstats getSumOfWeights = xform0 c_th3f_getsumofweights getSumw2 = xform0 c_th3f_getsumw2 getSumw2N = xform0 c_th3f_getsumw2n getRMS = xform1 c_th3f_getrms getRMSError = xform1 c_th3f_getrmserror getSkewness = xform1 c_th3f_getskewness integral1 = xform3 c_th3f_integral1 interpolate1 = xform1 c_th3f_interpolate1 interpolate2 = xform2 c_th3f_interpolate2 interpolate3 = xform3 c_th3f_interpolate3 kolmogorovTest = xform2 c_th3f_kolmogorovtest labelsDeflate = xform1 c_th3f_labelsdeflate labelsInflate = xform1 c_th3f_labelsinflate labelsOption = xform2 c_th3f_labelsoption multiflyF = xform2 c_th3f_multiflyf multiply = xform5 c_th3f_multiply putStats = xform1 c_th3f_putstats rebin = xform3 c_th3f_rebin rebinAxis = xform2 c_th3f_rebinaxis rebuild = xform1 c_th3f_rebuild recursiveRemove = xform1 c_th3f_recursiveremove reset = xform1 c_th3f_reset resetStats = xform0 c_th3f_resetstats scale = xform2 c_th3f_scale setAxisColorA = xform2 c_th3f_setaxiscolora setAxisRange = xform3 c_th3f_setaxisrange setBarOffset = xform1 c_th3f_setbaroffset setBarWidth = xform1 c_th3f_setbarwidth setBinContent1 = xform2 c_th3f_setbincontent1 setBinContent2 = xform3 c_th3f_setbincontent2 setBinContent3 = xform4 c_th3f_setbincontent3 setBinError1 = xform2 c_th3f_setbinerror1 setBinError2 = xform3 c_th3f_setbinerror2 setBinError3 = xform4 c_th3f_setbinerror3 setBins1 = xform2 c_th3f_setbins1 setBins2 = xform4 c_th3f_setbins2 setBins3 = xform6 c_th3f_setbins3 setBinsLength = xform1 c_th3f_setbinslength setBuffer = xform2 c_th3f_setbuffer setCellContent = xform3 c_th3f_setcellcontent setContent = xform1 c_th3f_setcontent setContour = xform2 c_th3f_setcontour setContourLevel = xform2 c_th3f_setcontourlevel setDirectory = xform1 c_th3f_setdirectory setEntries = xform1 c_th3f_setentries setError = xform1 c_th3f_seterror setLabelColorA = xform2 c_th3f_setlabelcolora setLabelSizeA = xform2 c_th3f_setlabelsizea setLabelFontA = xform2 c_th3f_setlabelfonta setLabelOffsetA = xform2 c_th3f_setlabeloffseta setMaximum = xform1 c_th3f_setmaximum setMinimum = xform1 c_th3f_setminimum setNormFactor = xform1 c_th3f_setnormfactor setStats = xform1 c_th3f_setstats setOption = xform1 c_th3f_setoption setXTitle = xform1 c_th3f_setxtitle setYTitle = xform1 c_th3f_setytitle setZTitle = xform1 c_th3f_setztitle showBackground = xform2 c_th3f_showbackground showPeaks = xform3 c_th3f_showpeaks smooth = xform2 c_th3f_smooth sumw2 = xform0 c_th3f_sumw2 instance ITAtt3D TH3F instance ITNamed TH3F where setName = xform1 c_th3f_setname setNameTitle = xform2 c_th3f_setnametitle setTitle = xform1 c_th3f_settitle instance ITAttLine TH3F where getLineColor = xform0 c_th3f_getlinecolor getLineStyle = xform0 c_th3f_getlinestyle getLineWidth = xform0 c_th3f_getlinewidth resetAttLine = xform1 c_th3f_resetattline setLineAttributes = xform0 c_th3f_setlineattributes setLineColor = xform1 c_th3f_setlinecolor setLineStyle = xform1 c_th3f_setlinestyle setLineWidth = xform1 c_th3f_setlinewidth instance ITAttFill TH3F where setFillColor = xform1 c_th3f_setfillcolor setFillStyle = xform1 c_th3f_setfillstyle instance ITAttMarker TH3F where getMarkerColor = xform0 c_th3f_getmarkercolor getMarkerStyle = xform0 c_th3f_getmarkerstyle getMarkerSize = xform0 c_th3f_getmarkersize resetAttMarker = xform1 c_th3f_resetattmarker setMarkerAttributes = xform0 c_th3f_setmarkerattributes setMarkerColor = xform1 c_th3f_setmarkercolor setMarkerStyle = xform1 c_th3f_setmarkerstyle setMarkerSize = xform1 c_th3f_setmarkersize instance ITObject TH3F where draw = xform1 c_th3f_draw findObject = xform1 c_th3f_findobject getName = xform0 c_th3f_getname isA = xform0 c_th3f_isa paint = xform1 c_th3f_paint printObj = xform1 c_th3f_printobj saveAs = xform2 c_th3f_saveas write = xform3 c_th3f_write instance IDeletable TH3F where delete = xform0 c_th3f_delete instance ITArray TH3F