{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH2D.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH2D.RawType import HROOT.Hist.TH2D.FFI import HROOT.Hist.TH2D.Interface import HROOT.Hist.TH2D.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.TObjArray.RawType import HROOT.Core.TObjArray.Cast import HROOT.Core.TObjArray.Interface import HROOT.Core.TDirectory.RawType import HROOT.Core.TDirectory.Cast import HROOT.Core.TDirectory.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.TH2.RawType import HROOT.Hist.TH2.Cast import HROOT.Hist.TH2.Interface import HROOT.Core.TArrayD.RawType import HROOT.Core.TArrayD.Cast import HROOT.Core.TArrayD.Interface import HROOT.Hist.TH1.RawType import HROOT.Hist.TH1.Cast import HROOT.Hist.TH1.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 ITH2D TH2D where instance ITH2 TH2D where fill2 = xform2 c_th2d_fill2 fill2w = xform3 c_th2d_fill2w fillN2 = xform5 c_th2d_filln2 fillRandom2 = xform2 c_th2d_fillrandom2 findFirstBinAbove2 = xform2 c_th2d_findfirstbinabove2 findLastBinAbove2 = xform2 c_th2d_findlastbinabove2 fitSlicesX = xform6 c_th2d_fitslicesx fitSlicesY = xform6 c_th2d_fitslicesy getCorrelationFactor2 = xform2 c_th2d_getcorrelationfactor2 getCovariance2 = xform2 c_th2d_getcovariance2 integral2 = xform5 c_th2d_integral2 rebinX2 = xform2 c_th2d_rebinx2 rebinY2 = xform2 c_th2d_rebiny2 rebin2D = xform3 c_th2d_rebin2d setShowProjectionX = xform1 c_th2d_setshowprojectionx setShowProjectionY = xform1 c_th2d_setshowprojectiony instance ITArrayD TH2D where instance ITH1 TH2D where add = xform2 c_th2d_add addBinContent = xform2 c_th2d_addbincontent chi2Test = xform3 c_th2d_chi2test computeIntegral = xform0 c_th2d_computeintegral directoryAutoAdd = xform1 c_th2d_directoryautoadd divide = xform5 c_th2d_divide drawCopyTH1 = xform1 c_th2d_drawcopyth1 drawNormalized = xform2 c_th2d_drawnormalized drawPanelTH1 = xform0 c_th2d_drawpanelth1 bufferEmpty = xform1 c_th2d_bufferempty evalF = xform2 c_th2d_evalf fFT = xform2 c_th2d_fft fill1 = xform1 c_th2d_fill1 fill1w = xform2 c_th2d_fill1w fillN1 = xform4 c_th2d_filln1 fillRandom = xform2 c_th2d_fillrandom findBin = xform3 c_th2d_findbin findFixBin = xform3 c_th2d_findfixbin findFirstBinAbove = xform2 c_th2d_findfirstbinabove findLastBinAbove = xform2 c_th2d_findlastbinabove fitPanelTH1 = xform0 c_th2d_fitpanelth1 getNdivisionA = xform1 c_th2d_getndivisiona getAxisColorA = xform1 c_th2d_getaxiscolora getLabelColorA = xform1 c_th2d_getlabelcolora getLabelFontA = xform1 c_th2d_getlabelfonta getLabelOffsetA = xform1 c_th2d_getlabeloffseta getLabelSizeA = xform1 c_th2d_getlabelsizea getTitleFontA = xform1 c_th2d_gettitlefonta getTitleOffsetA = xform1 c_th2d_gettitleoffseta getTitleSizeA = xform1 c_th2d_gettitlesizea getTickLengthA = xform1 c_th2d_getticklengtha getBarOffset = xform0 c_th2d_getbaroffset getBarWidth = xform0 c_th2d_getbarwidth getContour = xform1 c_th2d_getcontour getContourLevel = xform1 c_th2d_getcontourlevel getContourLevelPad = xform1 c_th2d_getcontourlevelpad getBin = xform3 c_th2d_getbin getBinCenter = xform1 c_th2d_getbincenter getBinContent1 = xform1 c_th2d_getbincontent1 getBinContent2 = xform2 c_th2d_getbincontent2 getBinContent3 = xform3 c_th2d_getbincontent3 getBinError1 = xform1 c_th2d_getbinerror1 getBinError2 = xform2 c_th2d_getbinerror2 getBinError3 = xform3 c_th2d_getbinerror3 getBinLowEdge = xform1 c_th2d_getbinlowedge getBinWidth = xform1 c_th2d_getbinwidth getCellContent = xform2 c_th2d_getcellcontent getCellError = xform2 c_th2d_getcellerror getEntries = xform0 c_th2d_getentries getEffectiveEntries = xform0 c_th2d_geteffectiveentries getFunction = xform1 c_th2d_getfunction getDimension = xform0 c_th2d_getdimension getKurtosis = xform1 c_th2d_getkurtosis getLowEdge = xform1 c_th2d_getlowedge getMaximumTH1 = xform1 c_th2d_getmaximumth1 getMaximumBin = xform0 c_th2d_getmaximumbin getMaximumStored = xform0 c_th2d_getmaximumstored getMinimumTH1 = xform1 c_th2d_getminimumth1 getMinimumBin = xform0 c_th2d_getminimumbin getMinimumStored = xform0 c_th2d_getminimumstored getMean = xform1 c_th2d_getmean getMeanError = xform1 c_th2d_getmeanerror getNbinsX = xform0 c_th2d_getnbinsx getNbinsY = xform0 c_th2d_getnbinsy getNbinsZ = xform0 c_th2d_getnbinsz getQuantilesTH1 = xform3 c_th2d_getquantilesth1 getRandom = xform0 c_th2d_getrandom getStats = xform1 c_th2d_getstats getSumOfWeights = xform0 c_th2d_getsumofweights getSumw2 = xform0 c_th2d_getsumw2 getSumw2N = xform0 c_th2d_getsumw2n getRMS = xform1 c_th2d_getrms getRMSError = xform1 c_th2d_getrmserror getSkewness = xform1 c_th2d_getskewness integral1 = xform3 c_th2d_integral1 interpolate1 = xform1 c_th2d_interpolate1 interpolate2 = xform2 c_th2d_interpolate2 interpolate3 = xform3 c_th2d_interpolate3 kolmogorovTest = xform2 c_th2d_kolmogorovtest labelsDeflate = xform1 c_th2d_labelsdeflate labelsInflate = xform1 c_th2d_labelsinflate labelsOption = xform2 c_th2d_labelsoption multiflyF = xform2 c_th2d_multiflyf multiply = xform5 c_th2d_multiply putStats = xform1 c_th2d_putstats rebin = xform3 c_th2d_rebin rebinAxis = xform2 c_th2d_rebinaxis rebuild = xform1 c_th2d_rebuild recursiveRemove = xform1 c_th2d_recursiveremove reset = xform1 c_th2d_reset resetStats = xform0 c_th2d_resetstats scale = xform2 c_th2d_scale setAxisColorA = xform2 c_th2d_setaxiscolora setAxisRange = xform3 c_th2d_setaxisrange setBarOffset = xform1 c_th2d_setbaroffset setBarWidth = xform1 c_th2d_setbarwidth setBinContent1 = xform2 c_th2d_setbincontent1 setBinContent2 = xform3 c_th2d_setbincontent2 setBinContent3 = xform4 c_th2d_setbincontent3 setBinError1 = xform2 c_th2d_setbinerror1 setBinError2 = xform3 c_th2d_setbinerror2 setBinError3 = xform4 c_th2d_setbinerror3 setBins1 = xform2 c_th2d_setbins1 setBins2 = xform4 c_th2d_setbins2 setBins3 = xform6 c_th2d_setbins3 setBinsLength = xform1 c_th2d_setbinslength setBuffer = xform2 c_th2d_setbuffer setCellContent = xform3 c_th2d_setcellcontent setContent = xform1 c_th2d_setcontent setContour = xform2 c_th2d_setcontour setContourLevel = xform2 c_th2d_setcontourlevel setDirectory = xform1 c_th2d_setdirectory setEntries = xform1 c_th2d_setentries setError = xform1 c_th2d_seterror setLabelColorA = xform2 c_th2d_setlabelcolora setLabelSizeA = xform2 c_th2d_setlabelsizea setLabelFontA = xform2 c_th2d_setlabelfonta setLabelOffsetA = xform2 c_th2d_setlabeloffseta setMaximum = xform1 c_th2d_setmaximum setMinimum = xform1 c_th2d_setminimum setNormFactor = xform1 c_th2d_setnormfactor setStats = xform1 c_th2d_setstats setOption = xform1 c_th2d_setoption setXTitle = xform1 c_th2d_setxtitle setYTitle = xform1 c_th2d_setytitle setZTitle = xform1 c_th2d_setztitle showBackground = xform2 c_th2d_showbackground showPeaks = xform3 c_th2d_showpeaks smooth = xform2 c_th2d_smooth sumw2 = xform0 c_th2d_sumw2 instance ITObject TH2D where draw = xform1 c_th2d_draw findObject = xform1 c_th2d_findobject getName = xform0 c_th2d_getname isA = xform0 c_th2d_isa paint = xform1 c_th2d_paint printObj = xform1 c_th2d_printobj saveAs = xform2 c_th2d_saveas write = xform3 c_th2d_write instance ITAttLine TH2D where getLineColor = xform0 c_th2d_getlinecolor getLineStyle = xform0 c_th2d_getlinestyle getLineWidth = xform0 c_th2d_getlinewidth resetAttLine = xform1 c_th2d_resetattline setLineAttributes = xform0 c_th2d_setlineattributes setLineColor = xform1 c_th2d_setlinecolor setLineStyle = xform1 c_th2d_setlinestyle setLineWidth = xform1 c_th2d_setlinewidth instance ITAttFill TH2D where setFillColor = xform1 c_th2d_setfillcolor setFillStyle = xform1 c_th2d_setfillstyle instance ITAttMarker TH2D where getMarkerColor = xform0 c_th2d_getmarkercolor getMarkerStyle = xform0 c_th2d_getmarkerstyle getMarkerSize = xform0 c_th2d_getmarkersize resetAttMarker = xform1 c_th2d_resetattmarker setMarkerAttributes = xform0 c_th2d_setmarkerattributes setMarkerColor = xform1 c_th2d_setmarkercolor setMarkerStyle = xform1 c_th2d_setmarkerstyle setMarkerSize = xform1 c_th2d_setmarkersize instance IDeletable TH2D where delete = xform0 c_th2d_delete instance ITArray TH2D where instance ITH2D (Exist TH2D) where instance ITH2 (Exist TH2D) where fill2 (ETH2D x) = fill2 x fill2w (ETH2D x) = fill2w x fillN2 (ETH2D x) = fillN2 x fillRandom2 (ETH2D x) = fillRandom2 x findFirstBinAbove2 (ETH2D x) = findFirstBinAbove2 x findLastBinAbove2 (ETH2D x) = findLastBinAbove2 x fitSlicesX (ETH2D x) = fitSlicesX x fitSlicesY (ETH2D x) = fitSlicesY x getCorrelationFactor2 (ETH2D x) = getCorrelationFactor2 x getCovariance2 (ETH2D x) = getCovariance2 x integral2 (ETH2D x) = integral2 x rebinX2 (ETH2D x) = rebinX2 x rebinY2 (ETH2D x) = rebinY2 x rebin2D (ETH2D x) = rebin2D x setShowProjectionX (ETH2D x) = setShowProjectionX x setShowProjectionY (ETH2D x) = setShowProjectionY x instance ITArrayD (Exist TH2D) where instance ITH1 (Exist TH2D) where add (ETH2D x) = add x addBinContent (ETH2D x) = addBinContent x chi2Test (ETH2D x) = chi2Test x computeIntegral (ETH2D x) = computeIntegral x directoryAutoAdd (ETH2D x) = directoryAutoAdd x divide (ETH2D x) = divide x drawCopyTH1 (ETH2D x) a1 = return . ETH2D =<< drawCopyTH1 x a1 drawNormalized (ETH2D x) = drawNormalized x drawPanelTH1 (ETH2D x) = drawPanelTH1 x bufferEmpty (ETH2D x) = bufferEmpty x evalF (ETH2D x) = evalF x fFT (ETH2D x) = fFT x fill1 (ETH2D x) = fill1 x fill1w (ETH2D x) = fill1w x fillN1 (ETH2D x) = fillN1 x fillRandom (ETH2D x) = fillRandom x findBin (ETH2D x) = findBin x findFixBin (ETH2D x) = findFixBin x findFirstBinAbove (ETH2D x) = findFirstBinAbove x findLastBinAbove (ETH2D x) = findLastBinAbove x fitPanelTH1 (ETH2D x) = fitPanelTH1 x getNdivisionA (ETH2D x) = getNdivisionA x getAxisColorA (ETH2D x) = getAxisColorA x getLabelColorA (ETH2D x) = getLabelColorA x getLabelFontA (ETH2D x) = getLabelFontA x getLabelOffsetA (ETH2D x) = getLabelOffsetA x getLabelSizeA (ETH2D x) = getLabelSizeA x getTitleFontA (ETH2D x) = getTitleFontA x getTitleOffsetA (ETH2D x) = getTitleOffsetA x getTitleSizeA (ETH2D x) = getTitleSizeA x getTickLengthA (ETH2D x) = getTickLengthA x getBarOffset (ETH2D x) = getBarOffset x getBarWidth (ETH2D x) = getBarWidth x getContour (ETH2D x) = getContour x getContourLevel (ETH2D x) = getContourLevel x getContourLevelPad (ETH2D x) = getContourLevelPad x getBin (ETH2D x) = getBin x getBinCenter (ETH2D x) = getBinCenter x getBinContent1 (ETH2D x) = getBinContent1 x getBinContent2 (ETH2D x) = getBinContent2 x getBinContent3 (ETH2D x) = getBinContent3 x getBinError1 (ETH2D x) = getBinError1 x getBinError2 (ETH2D x) = getBinError2 x getBinError3 (ETH2D x) = getBinError3 x getBinLowEdge (ETH2D x) = getBinLowEdge x getBinWidth (ETH2D x) = getBinWidth x getCellContent (ETH2D x) = getCellContent x getCellError (ETH2D x) = getCellError x getEntries (ETH2D x) = getEntries x getEffectiveEntries (ETH2D x) = getEffectiveEntries x getFunction (ETH2D x) = getFunction x getDimension (ETH2D x) = getDimension x getKurtosis (ETH2D x) = getKurtosis x getLowEdge (ETH2D x) = getLowEdge x getMaximumTH1 (ETH2D x) = getMaximumTH1 x getMaximumBin (ETH2D x) = getMaximumBin x getMaximumStored (ETH2D x) = getMaximumStored x getMinimumTH1 (ETH2D x) = getMinimumTH1 x getMinimumBin (ETH2D x) = getMinimumBin x getMinimumStored (ETH2D x) = getMinimumStored x getMean (ETH2D x) = getMean x getMeanError (ETH2D x) = getMeanError x getNbinsX (ETH2D x) = getNbinsX x getNbinsY (ETH2D x) = getNbinsY x getNbinsZ (ETH2D x) = getNbinsZ x getQuantilesTH1 (ETH2D x) = getQuantilesTH1 x getRandom (ETH2D x) = getRandom x getStats (ETH2D x) = getStats x getSumOfWeights (ETH2D x) = getSumOfWeights x getSumw2 (ETH2D x) = getSumw2 x getSumw2N (ETH2D x) = getSumw2N x getRMS (ETH2D x) = getRMS x getRMSError (ETH2D x) = getRMSError x getSkewness (ETH2D x) = getSkewness x integral1 (ETH2D x) = integral1 x interpolate1 (ETH2D x) = interpolate1 x interpolate2 (ETH2D x) = interpolate2 x interpolate3 (ETH2D x) = interpolate3 x kolmogorovTest (ETH2D x) = kolmogorovTest x labelsDeflate (ETH2D x) = labelsDeflate x labelsInflate (ETH2D x) = labelsInflate x labelsOption (ETH2D x) = labelsOption x multiflyF (ETH2D x) = multiflyF x multiply (ETH2D x) = multiply x putStats (ETH2D x) = putStats x rebin (ETH2D x) = rebin x rebinAxis (ETH2D x) = rebinAxis x rebuild (ETH2D x) = rebuild x recursiveRemove (ETH2D x) = recursiveRemove x reset (ETH2D x) = reset x resetStats (ETH2D x) = resetStats x scale (ETH2D x) = scale x setAxisColorA (ETH2D x) = setAxisColorA x setAxisRange (ETH2D x) = setAxisRange x setBarOffset (ETH2D x) = setBarOffset x setBarWidth (ETH2D x) = setBarWidth x setBinContent1 (ETH2D x) = setBinContent1 x setBinContent2 (ETH2D x) = setBinContent2 x setBinContent3 (ETH2D x) = setBinContent3 x setBinError1 (ETH2D x) = setBinError1 x setBinError2 (ETH2D x) = setBinError2 x setBinError3 (ETH2D x) = setBinError3 x setBins1 (ETH2D x) = setBins1 x setBins2 (ETH2D x) = setBins2 x setBins3 (ETH2D x) = setBins3 x setBinsLength (ETH2D x) = setBinsLength x setBuffer (ETH2D x) = setBuffer x setCellContent (ETH2D x) = setCellContent x setContent (ETH2D x) = setContent x setContour (ETH2D x) = setContour x setContourLevel (ETH2D x) = setContourLevel x setDirectory (ETH2D x) = setDirectory x setEntries (ETH2D x) = setEntries x setError (ETH2D x) = setError x setLabelColorA (ETH2D x) = setLabelColorA x setLabelSizeA (ETH2D x) = setLabelSizeA x setLabelFontA (ETH2D x) = setLabelFontA x setLabelOffsetA (ETH2D x) = setLabelOffsetA x setMaximum (ETH2D x) = setMaximum x setMinimum (ETH2D x) = setMinimum x setNormFactor (ETH2D x) = setNormFactor x setStats (ETH2D x) = setStats x setOption (ETH2D x) = setOption x setXTitle (ETH2D x) = setXTitle x setYTitle (ETH2D x) = setYTitle x setZTitle (ETH2D x) = setZTitle x showBackground (ETH2D x) = showBackground x showPeaks (ETH2D x) = showPeaks x smooth (ETH2D x) = smooth x sumw2 (ETH2D x) = sumw2 x instance ITObject (Exist TH2D) where draw (ETH2D x) = draw x findObject (ETH2D x) = findObject x getName (ETH2D x) = getName x isA (ETH2D x) = isA x paint (ETH2D x) = paint x printObj (ETH2D x) = printObj x saveAs (ETH2D x) = saveAs x write (ETH2D x) = write x instance ITAttLine (Exist TH2D) where getLineColor (ETH2D x) = getLineColor x getLineStyle (ETH2D x) = getLineStyle x getLineWidth (ETH2D x) = getLineWidth x resetAttLine (ETH2D x) = resetAttLine x setLineAttributes (ETH2D x) = setLineAttributes x setLineColor (ETH2D x) = setLineColor x setLineStyle (ETH2D x) = setLineStyle x setLineWidth (ETH2D x) = setLineWidth x instance ITAttFill (Exist TH2D) where setFillColor (ETH2D x) = setFillColor x setFillStyle (ETH2D x) = setFillStyle x instance ITAttMarker (Exist TH2D) where getMarkerColor (ETH2D x) = getMarkerColor x getMarkerStyle (ETH2D x) = getMarkerStyle x getMarkerSize (ETH2D x) = getMarkerSize x resetAttMarker (ETH2D x) = resetAttMarker x setMarkerAttributes (ETH2D x) = setMarkerAttributes x setMarkerColor (ETH2D x) = setMarkerColor x setMarkerStyle (ETH2D x) = setMarkerStyle x setMarkerSize (ETH2D x) = setMarkerSize x instance IDeletable (Exist TH2D) where delete (ETH2D x) = delete x instance ITArray (Exist TH2D) where newTH2D :: CString -> CString -> CInt -> CDouble -> CDouble -> CInt -> CDouble -> CDouble -> IO TH2D newTH2D = xform7 c_th2d_newth2d instance FPtr (Exist TH2D) where type Raw (Exist TH2D) = RawTH2D get_fptr (ETH2D obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH2D (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2D) :: TH2D)