{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH3S.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH3S.RawType import HROOT.Hist.TH3S.FFI import HROOT.Hist.TH3S.Interface import HROOT.Hist.TH3S.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.TArrayS.RawType import HROOT.Core.TArrayS.Cast import HROOT.Core.TArrayS.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.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.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.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 import Data.Word import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITH3S TH3S where instance ITH3 TH3S where fill3 = xform3 c_th3s_fill3 fill3w = xform4 c_th3s_fill3w fitSlicesZ = xform7 c_th3s_fitslicesz getCorrelationFactor3 = xform2 c_th3s_getcorrelationfactor3 getCovariance3 = xform2 c_th3s_getcovariance3 rebinX3 = xform2 c_th3s_rebinx3 rebinY3 = xform2 c_th3s_rebiny3 rebinZ3 = xform2 c_th3s_rebinz3 rebin3D = xform4 c_th3s_rebin3d instance ITArrayS TH3S where instance ITH1 TH3S where add = xform2 c_th3s_add addBinContent = xform2 c_th3s_addbincontent chi2Test = xform3 c_th3s_chi2test computeIntegral = xform0 c_th3s_computeintegral directoryAutoAdd = xform1 c_th3s_directoryautoadd divide = xform5 c_th3s_divide drawCopyTH1 = xform1 c_th3s_drawcopyth1 drawNormalized = xform2 c_th3s_drawnormalized drawPanelTH1 = xform0 c_th3s_drawpanelth1 bufferEmpty = xform1 c_th3s_bufferempty evalF = xform2 c_th3s_evalf fFT = xform2 c_th3s_fft fill1 = xform1 c_th3s_fill1 fill1w = xform2 c_th3s_fill1w fillN1 = xform4 c_th3s_filln1 fillRandom = xform2 c_th3s_fillrandom findBin = xform3 c_th3s_findbin findFixBin = xform3 c_th3s_findfixbin findFirstBinAbove = xform2 c_th3s_findfirstbinabove findLastBinAbove = xform2 c_th3s_findlastbinabove fitPanelTH1 = xform0 c_th3s_fitpanelth1 getNdivisionA = xform1 c_th3s_getndivisiona getAxisColorA = xform1 c_th3s_getaxiscolora getLabelColorA = xform1 c_th3s_getlabelcolora getLabelFontA = xform1 c_th3s_getlabelfonta getLabelOffsetA = xform1 c_th3s_getlabeloffseta getLabelSizeA = xform1 c_th3s_getlabelsizea getTitleFontA = xform1 c_th3s_gettitlefonta getTitleOffsetA = xform1 c_th3s_gettitleoffseta getTitleSizeA = xform1 c_th3s_gettitlesizea getTickLengthA = xform1 c_th3s_getticklengtha getBarOffset = xform0 c_th3s_getbaroffset getBarWidth = xform0 c_th3s_getbarwidth getContour = xform1 c_th3s_getcontour getContourLevel = xform1 c_th3s_getcontourlevel getContourLevelPad = xform1 c_th3s_getcontourlevelpad getBin = xform3 c_th3s_getbin getBinCenter = xform1 c_th3s_getbincenter getBinContent1 = xform1 c_th3s_getbincontent1 getBinContent2 = xform2 c_th3s_getbincontent2 getBinContent3 = xform3 c_th3s_getbincontent3 getBinError1 = xform1 c_th3s_getbinerror1 getBinError2 = xform2 c_th3s_getbinerror2 getBinError3 = xform3 c_th3s_getbinerror3 getBinLowEdge = xform1 c_th3s_getbinlowedge getBinWidth = xform1 c_th3s_getbinwidth getCellContent = xform2 c_th3s_getcellcontent getCellError = xform2 c_th3s_getcellerror getEntries = xform0 c_th3s_getentries getEffectiveEntries = xform0 c_th3s_geteffectiveentries getFunction = xform1 c_th3s_getfunction getDimension = xform0 c_th3s_getdimension getKurtosis = xform1 c_th3s_getkurtosis getLowEdge = xform1 c_th3s_getlowedge getMaximumTH1 = xform1 c_th3s_getmaximumth1 getMaximumBin = xform0 c_th3s_getmaximumbin getMaximumStored = xform0 c_th3s_getmaximumstored getMinimumTH1 = xform1 c_th3s_getminimumth1 getMinimumBin = xform0 c_th3s_getminimumbin getMinimumStored = xform0 c_th3s_getminimumstored getMean = xform1 c_th3s_getmean getMeanError = xform1 c_th3s_getmeanerror getNbinsX = xform0 c_th3s_getnbinsx getNbinsY = xform0 c_th3s_getnbinsy getNbinsZ = xform0 c_th3s_getnbinsz getQuantilesTH1 = xform3 c_th3s_getquantilesth1 getRandom = xform0 c_th3s_getrandom getStats = xform1 c_th3s_getstats getSumOfWeights = xform0 c_th3s_getsumofweights getSumw2 = xform0 c_th3s_getsumw2 getSumw2N = xform0 c_th3s_getsumw2n getRMS = xform1 c_th3s_getrms getRMSError = xform1 c_th3s_getrmserror getSkewness = xform1 c_th3s_getskewness integral1 = xform3 c_th3s_integral1 interpolate1 = xform1 c_th3s_interpolate1 interpolate2 = xform2 c_th3s_interpolate2 interpolate3 = xform3 c_th3s_interpolate3 kolmogorovTest = xform2 c_th3s_kolmogorovtest labelsDeflate = xform1 c_th3s_labelsdeflate labelsInflate = xform1 c_th3s_labelsinflate labelsOption = xform2 c_th3s_labelsoption multiflyF = xform2 c_th3s_multiflyf multiply = xform5 c_th3s_multiply putStats = xform1 c_th3s_putstats rebin = xform3 c_th3s_rebin rebinAxis = xform2 c_th3s_rebinaxis rebuild = xform1 c_th3s_rebuild recursiveRemove = xform1 c_th3s_recursiveremove reset = xform1 c_th3s_reset resetStats = xform0 c_th3s_resetstats scale = xform2 c_th3s_scale setAxisColorA = xform2 c_th3s_setaxiscolora setAxisRange = xform3 c_th3s_setaxisrange setBarOffset = xform1 c_th3s_setbaroffset setBarWidth = xform1 c_th3s_setbarwidth setBinContent1 = xform2 c_th3s_setbincontent1 setBinContent2 = xform3 c_th3s_setbincontent2 setBinContent3 = xform4 c_th3s_setbincontent3 setBinError1 = xform2 c_th3s_setbinerror1 setBinError2 = xform3 c_th3s_setbinerror2 setBinError3 = xform4 c_th3s_setbinerror3 setBins1 = xform2 c_th3s_setbins1 setBins2 = xform4 c_th3s_setbins2 setBins3 = xform6 c_th3s_setbins3 setBinsLength = xform1 c_th3s_setbinslength setBuffer = xform2 c_th3s_setbuffer setCellContent = xform3 c_th3s_setcellcontent setContent = xform1 c_th3s_setcontent setContour = xform2 c_th3s_setcontour setContourLevel = xform2 c_th3s_setcontourlevel setDirectory = xform1 c_th3s_setdirectory setEntries = xform1 c_th3s_setentries setError = xform1 c_th3s_seterror setLabelColorA = xform2 c_th3s_setlabelcolora setLabelSizeA = xform2 c_th3s_setlabelsizea setLabelFontA = xform2 c_th3s_setlabelfonta setLabelOffsetA = xform2 c_th3s_setlabeloffseta setMaximum = xform1 c_th3s_setmaximum setMinimum = xform1 c_th3s_setminimum setNormFactor = xform1 c_th3s_setnormfactor setStats = xform1 c_th3s_setstats setOption = xform1 c_th3s_setoption setXTitle = xform1 c_th3s_setxtitle setYTitle = xform1 c_th3s_setytitle setZTitle = xform1 c_th3s_setztitle showBackground = xform2 c_th3s_showbackground showPeaks = xform3 c_th3s_showpeaks smooth = xform2 c_th3s_smooth sumw2 = xform0 c_th3s_sumw2 instance ITAtt3D TH3S where instance ITObject TH3S where draw = xform1 c_th3s_draw findObject = xform1 c_th3s_findobject getName = xform0 c_th3s_getname isA = xform0 c_th3s_isa paint = xform1 c_th3s_paint printObj = xform1 c_th3s_printobj saveAs = xform2 c_th3s_saveas write = xform3 c_th3s_write instance ITAttLine TH3S where getLineColor = xform0 c_th3s_getlinecolor getLineStyle = xform0 c_th3s_getlinestyle getLineWidth = xform0 c_th3s_getlinewidth resetAttLine = xform1 c_th3s_resetattline setLineAttributes = xform0 c_th3s_setlineattributes setLineColor = xform1 c_th3s_setlinecolor setLineStyle = xform1 c_th3s_setlinestyle setLineWidth = xform1 c_th3s_setlinewidth instance ITAttFill TH3S where setFillColor = xform1 c_th3s_setfillcolor setFillStyle = xform1 c_th3s_setfillstyle instance ITAttMarker TH3S where getMarkerColor = xform0 c_th3s_getmarkercolor getMarkerStyle = xform0 c_th3s_getmarkerstyle getMarkerSize = xform0 c_th3s_getmarkersize resetAttMarker = xform1 c_th3s_resetattmarker setMarkerAttributes = xform0 c_th3s_setmarkerattributes setMarkerColor = xform1 c_th3s_setmarkercolor setMarkerStyle = xform1 c_th3s_setmarkerstyle setMarkerSize = xform1 c_th3s_setmarkersize instance IDeletable TH3S where delete = xform0 c_th3s_delete instance ITArray TH3S where instance ITH3S (Exist TH3S) where instance ITH3 (Exist TH3S) where fill3 (ETH3S x) = fill3 x fill3w (ETH3S x) = fill3w x fitSlicesZ (ETH3S x) = fitSlicesZ x getCorrelationFactor3 (ETH3S x) = getCorrelationFactor3 x getCovariance3 (ETH3S x) = getCovariance3 x rebinX3 (ETH3S x) = rebinX3 x rebinY3 (ETH3S x) = rebinY3 x rebinZ3 (ETH3S x) = rebinZ3 x rebin3D (ETH3S x) = rebin3D x instance ITArrayS (Exist TH3S) where instance ITH1 (Exist TH3S) where add (ETH3S x) = add x addBinContent (ETH3S x) = addBinContent x chi2Test (ETH3S x) = chi2Test x computeIntegral (ETH3S x) = computeIntegral x directoryAutoAdd (ETH3S x) = directoryAutoAdd x divide (ETH3S x) = divide x drawCopyTH1 (ETH3S x) a1 = return . ETH3S =<< drawCopyTH1 x a1 drawNormalized (ETH3S x) = drawNormalized x drawPanelTH1 (ETH3S x) = drawPanelTH1 x bufferEmpty (ETH3S x) = bufferEmpty x evalF (ETH3S x) = evalF x fFT (ETH3S x) = fFT x fill1 (ETH3S x) = fill1 x fill1w (ETH3S x) = fill1w x fillN1 (ETH3S x) = fillN1 x fillRandom (ETH3S x) = fillRandom x findBin (ETH3S x) = findBin x findFixBin (ETH3S x) = findFixBin x findFirstBinAbove (ETH3S x) = findFirstBinAbove x findLastBinAbove (ETH3S x) = findLastBinAbove x fitPanelTH1 (ETH3S x) = fitPanelTH1 x getNdivisionA (ETH3S x) = getNdivisionA x getAxisColorA (ETH3S x) = getAxisColorA x getLabelColorA (ETH3S x) = getLabelColorA x getLabelFontA (ETH3S x) = getLabelFontA x getLabelOffsetA (ETH3S x) = getLabelOffsetA x getLabelSizeA (ETH3S x) = getLabelSizeA x getTitleFontA (ETH3S x) = getTitleFontA x getTitleOffsetA (ETH3S x) = getTitleOffsetA x getTitleSizeA (ETH3S x) = getTitleSizeA x getTickLengthA (ETH3S x) = getTickLengthA x getBarOffset (ETH3S x) = getBarOffset x getBarWidth (ETH3S x) = getBarWidth x getContour (ETH3S x) = getContour x getContourLevel (ETH3S x) = getContourLevel x getContourLevelPad (ETH3S x) = getContourLevelPad x getBin (ETH3S x) = getBin x getBinCenter (ETH3S x) = getBinCenter x getBinContent1 (ETH3S x) = getBinContent1 x getBinContent2 (ETH3S x) = getBinContent2 x getBinContent3 (ETH3S x) = getBinContent3 x getBinError1 (ETH3S x) = getBinError1 x getBinError2 (ETH3S x) = getBinError2 x getBinError3 (ETH3S x) = getBinError3 x getBinLowEdge (ETH3S x) = getBinLowEdge x getBinWidth (ETH3S x) = getBinWidth x getCellContent (ETH3S x) = getCellContent x getCellError (ETH3S x) = getCellError x getEntries (ETH3S x) = getEntries x getEffectiveEntries (ETH3S x) = getEffectiveEntries x getFunction (ETH3S x) = getFunction x getDimension (ETH3S x) = getDimension x getKurtosis (ETH3S x) = getKurtosis x getLowEdge (ETH3S x) = getLowEdge x getMaximumTH1 (ETH3S x) = getMaximumTH1 x getMaximumBin (ETH3S x) = getMaximumBin x getMaximumStored (ETH3S x) = getMaximumStored x getMinimumTH1 (ETH3S x) = getMinimumTH1 x getMinimumBin (ETH3S x) = getMinimumBin x getMinimumStored (ETH3S x) = getMinimumStored x getMean (ETH3S x) = getMean x getMeanError (ETH3S x) = getMeanError x getNbinsX (ETH3S x) = getNbinsX x getNbinsY (ETH3S x) = getNbinsY x getNbinsZ (ETH3S x) = getNbinsZ x getQuantilesTH1 (ETH3S x) = getQuantilesTH1 x getRandom (ETH3S x) = getRandom x getStats (ETH3S x) = getStats x getSumOfWeights (ETH3S x) = getSumOfWeights x getSumw2 (ETH3S x) = getSumw2 x getSumw2N (ETH3S x) = getSumw2N x getRMS (ETH3S x) = getRMS x getRMSError (ETH3S x) = getRMSError x getSkewness (ETH3S x) = getSkewness x integral1 (ETH3S x) = integral1 x interpolate1 (ETH3S x) = interpolate1 x interpolate2 (ETH3S x) = interpolate2 x interpolate3 (ETH3S x) = interpolate3 x kolmogorovTest (ETH3S x) = kolmogorovTest x labelsDeflate (ETH3S x) = labelsDeflate x labelsInflate (ETH3S x) = labelsInflate x labelsOption (ETH3S x) = labelsOption x multiflyF (ETH3S x) = multiflyF x multiply (ETH3S x) = multiply x putStats (ETH3S x) = putStats x rebin (ETH3S x) = rebin x rebinAxis (ETH3S x) = rebinAxis x rebuild (ETH3S x) = rebuild x recursiveRemove (ETH3S x) = recursiveRemove x reset (ETH3S x) = reset x resetStats (ETH3S x) = resetStats x scale (ETH3S x) = scale x setAxisColorA (ETH3S x) = setAxisColorA x setAxisRange (ETH3S x) = setAxisRange x setBarOffset (ETH3S x) = setBarOffset x setBarWidth (ETH3S x) = setBarWidth x setBinContent1 (ETH3S x) = setBinContent1 x setBinContent2 (ETH3S x) = setBinContent2 x setBinContent3 (ETH3S x) = setBinContent3 x setBinError1 (ETH3S x) = setBinError1 x setBinError2 (ETH3S x) = setBinError2 x setBinError3 (ETH3S x) = setBinError3 x setBins1 (ETH3S x) = setBins1 x setBins2 (ETH3S x) = setBins2 x setBins3 (ETH3S x) = setBins3 x setBinsLength (ETH3S x) = setBinsLength x setBuffer (ETH3S x) = setBuffer x setCellContent (ETH3S x) = setCellContent x setContent (ETH3S x) = setContent x setContour (ETH3S x) = setContour x setContourLevel (ETH3S x) = setContourLevel x setDirectory (ETH3S x) = setDirectory x setEntries (ETH3S x) = setEntries x setError (ETH3S x) = setError x setLabelColorA (ETH3S x) = setLabelColorA x setLabelSizeA (ETH3S x) = setLabelSizeA x setLabelFontA (ETH3S x) = setLabelFontA x setLabelOffsetA (ETH3S x) = setLabelOffsetA x setMaximum (ETH3S x) = setMaximum x setMinimum (ETH3S x) = setMinimum x setNormFactor (ETH3S x) = setNormFactor x setStats (ETH3S x) = setStats x setOption (ETH3S x) = setOption x setXTitle (ETH3S x) = setXTitle x setYTitle (ETH3S x) = setYTitle x setZTitle (ETH3S x) = setZTitle x showBackground (ETH3S x) = showBackground x showPeaks (ETH3S x) = showPeaks x smooth (ETH3S x) = smooth x sumw2 (ETH3S x) = sumw2 x instance ITAtt3D (Exist TH3S) where instance ITObject (Exist TH3S) where draw (ETH3S x) = draw x findObject (ETH3S x) = findObject x getName (ETH3S x) = getName x isA (ETH3S x) = isA x paint (ETH3S x) = paint x printObj (ETH3S x) = printObj x saveAs (ETH3S x) = saveAs x write (ETH3S x) = write x instance ITAttLine (Exist TH3S) where getLineColor (ETH3S x) = getLineColor x getLineStyle (ETH3S x) = getLineStyle x getLineWidth (ETH3S x) = getLineWidth x resetAttLine (ETH3S x) = resetAttLine x setLineAttributes (ETH3S x) = setLineAttributes x setLineColor (ETH3S x) = setLineColor x setLineStyle (ETH3S x) = setLineStyle x setLineWidth (ETH3S x) = setLineWidth x instance ITAttFill (Exist TH3S) where setFillColor (ETH3S x) = setFillColor x setFillStyle (ETH3S x) = setFillStyle x instance ITAttMarker (Exist TH3S) where getMarkerColor (ETH3S x) = getMarkerColor x getMarkerStyle (ETH3S x) = getMarkerStyle x getMarkerSize (ETH3S x) = getMarkerSize x resetAttMarker (ETH3S x) = resetAttMarker x setMarkerAttributes (ETH3S x) = setMarkerAttributes x setMarkerColor (ETH3S x) = setMarkerColor x setMarkerStyle (ETH3S x) = setMarkerStyle x setMarkerSize (ETH3S x) = setMarkerSize x instance IDeletable (Exist TH3S) where delete (ETH3S x) = delete x instance ITArray (Exist TH3S) where instance FPtr (Exist TH3S) where type Raw (Exist TH3S) = RawTH3S get_fptr (ETH3S obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH3S (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3S) :: TH3S)