{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TH2F.Implementation where import HROOT.TypeCast import HROOT.Class.TH2F.RawType import HROOT.Class.TH2F.FFI import HROOT.Class.TH2F.Interface import HROOT.Class.TH2F.Cast import HROOT.Class.TH1D.RawType import HROOT.Class.TH1D.Cast import HROOT.Class.TH1D.Interface import HROOT.Class.TF1.RawType import HROOT.Class.TF1.Cast import HROOT.Class.TF1.Interface import HROOT.Class.TObjArray.RawType import HROOT.Class.TObjArray.Cast import HROOT.Class.TObjArray.Interface import HROOT.Class.TDirectory.RawType import HROOT.Class.TDirectory.Cast import HROOT.Class.TDirectory.Interface import HROOT.Class.TArrayD.RawType import HROOT.Class.TArrayD.Cast import HROOT.Class.TArrayD.Interface import HROOT.Class.TAxis.RawType import HROOT.Class.TAxis.Cast import HROOT.Class.TAxis.Interface import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TH2.RawType import HROOT.Class.TH2.Cast import HROOT.Class.TH2.Interface import HROOT.Class.TArrayF.RawType import HROOT.Class.TArrayF.Cast import HROOT.Class.TArrayF.Interface import HROOT.Class.TH1.RawType import HROOT.Class.TH1.Cast import HROOT.Class.TH1.Interface import HROOT.Class.TNamed.RawType import HROOT.Class.TNamed.Cast import HROOT.Class.TNamed.Interface import HROOT.Class.TAttLine.RawType import HROOT.Class.TAttLine.Cast import HROOT.Class.TAttLine.Interface import HROOT.Class.TAttFill.RawType import HROOT.Class.TAttFill.Cast import HROOT.Class.TAttFill.Interface import HROOT.Class.TAttMarker.RawType import HROOT.Class.TAttMarker.Cast import HROOT.Class.TAttMarker.Interface import HROOT.Class.TObject.RawType import HROOT.Class.TObject.Cast import HROOT.Class.TObject.Interface import HROOT.Class.Deletable.RawType import HROOT.Class.Deletable.Cast import HROOT.Class.Deletable.Interface import HROOT.Class.TArray.RawType import HROOT.Class.TArray.Cast import HROOT.Class.TArray.Interface import Data.Word -- import Foreign.C -- import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITH2F TH2F where instance ITH2 TH2F where fill2 = xform2 c_th2f_fill2 fill2w = xform3 c_th2f_fill2w fillN2 = xform5 c_th2f_filln2 fillRandom2 = xform2 c_th2f_fillrandom2 findFirstBinAbove2 = xform2 c_th2f_findfirstbinabove2 findLastBinAbove2 = xform2 c_th2f_findlastbinabove2 fitSlicesX = xform6 c_th2f_fitslicesx fitSlicesY = xform6 c_th2f_fitslicesy getCorrelationFactor2 = xform2 c_th2f_getcorrelationfactor2 getCovariance2 = xform2 c_th2f_getcovariance2 integral2 = xform5 c_th2f_integral2 rebinX2 = xform2 c_th2f_rebinx2 rebinY2 = xform2 c_th2f_rebiny2 rebin2D = xform3 c_th2f_rebin2d setShowProjectionX = xform1 c_th2f_setshowprojectionx setShowProjectionY = xform1 c_th2f_setshowprojectiony instance ITArrayF TH2F where instance ITH1 TH2F where add = xform2 c_th2f_add addBinContent = xform2 c_th2f_addbincontent chi2Test = xform3 c_th2f_chi2test computeIntegral = xform0 c_th2f_computeintegral directoryAutoAdd = xform1 c_th2f_directoryautoadd divide = xform5 c_th2f_divide drawCopyTH1 = xform1 c_th2f_drawcopyth1 drawNormalized = xform2 c_th2f_drawnormalized drawPanelTH1 = xform0 c_th2f_drawpanelth1 bufferEmpty = xform1 c_th2f_bufferempty evalF = xform2 c_th2f_evalf fFT = xform2 c_th2f_fft fill1 = xform1 c_th2f_fill1 fill1w = xform2 c_th2f_fill1w fillN1 = xform4 c_th2f_filln1 fillRandom = xform2 c_th2f_fillrandom findBin = xform3 c_th2f_findbin findFixBin = xform3 c_th2f_findfixbin findFirstBinAbove = xform2 c_th2f_findfirstbinabove findLastBinAbove = xform2 c_th2f_findlastbinabove fitPanelTH1 = xform0 c_th2f_fitpanelth1 getNdivisionA = xform1 c_th2f_getndivisiona getAxisColorA = xform1 c_th2f_getaxiscolora getLabelColorA = xform1 c_th2f_getlabelcolora getLabelFontA = xform1 c_th2f_getlabelfonta getLabelOffsetA = xform1 c_th2f_getlabeloffseta getLabelSizeA = xform1 c_th2f_getlabelsizea getTitleFontA = xform1 c_th2f_gettitlefonta getTitleOffsetA = xform1 c_th2f_gettitleoffseta getTitleSizeA = xform1 c_th2f_gettitlesizea getTickLengthA = xform1 c_th2f_getticklengtha getBarOffset = xform0 c_th2f_getbaroffset getBarWidth = xform0 c_th2f_getbarwidth getContour = xform1 c_th2f_getcontour getContourLevel = xform1 c_th2f_getcontourlevel getContourLevelPad = xform1 c_th2f_getcontourlevelpad getBin = xform3 c_th2f_getbin getBinCenter = xform1 c_th2f_getbincenter getBinContent1 = xform1 c_th2f_getbincontent1 getBinContent2 = xform2 c_th2f_getbincontent2 getBinContent3 = xform3 c_th2f_getbincontent3 getBinError1 = xform1 c_th2f_getbinerror1 getBinError2 = xform2 c_th2f_getbinerror2 getBinError3 = xform3 c_th2f_getbinerror3 getBinLowEdge = xform1 c_th2f_getbinlowedge getBinWidth = xform1 c_th2f_getbinwidth getCellContent = xform2 c_th2f_getcellcontent getCellError = xform2 c_th2f_getcellerror getEntries = xform0 c_th2f_getentries getEffectiveEntries = xform0 c_th2f_geteffectiveentries getFunction = xform1 c_th2f_getfunction getDimension = xform0 c_th2f_getdimension getKurtosis = xform1 c_th2f_getkurtosis getLowEdge = xform1 c_th2f_getlowedge getMaximumTH1 = xform1 c_th2f_getmaximumth1 getMaximumBin = xform0 c_th2f_getmaximumbin getMaximumStored = xform0 c_th2f_getmaximumstored getMinimumTH1 = xform1 c_th2f_getminimumth1 getMinimumBin = xform0 c_th2f_getminimumbin getMinimumStored = xform0 c_th2f_getminimumstored getMean = xform1 c_th2f_getmean getMeanError = xform1 c_th2f_getmeanerror getNbinsX = xform0 c_th2f_getnbinsx getNbinsY = xform0 c_th2f_getnbinsy getNbinsZ = xform0 c_th2f_getnbinsz getQuantilesTH1 = xform3 c_th2f_getquantilesth1 getRandom = xform0 c_th2f_getrandom getStats = xform1 c_th2f_getstats getSumOfWeights = xform0 c_th2f_getsumofweights getSumw2 = xform0 c_th2f_getsumw2 getSumw2N = xform0 c_th2f_getsumw2n getRMS = xform1 c_th2f_getrms getRMSError = xform1 c_th2f_getrmserror getSkewness = xform1 c_th2f_getskewness integral1 = xform3 c_th2f_integral1 interpolate1 = xform1 c_th2f_interpolate1 interpolate2 = xform2 c_th2f_interpolate2 interpolate3 = xform3 c_th2f_interpolate3 kolmogorovTest = xform2 c_th2f_kolmogorovtest labelsDeflate = xform1 c_th2f_labelsdeflate labelsInflate = xform1 c_th2f_labelsinflate labelsOption = xform2 c_th2f_labelsoption multiflyF = xform2 c_th2f_multiflyf multiply = xform5 c_th2f_multiply putStats = xform1 c_th2f_putstats rebin = xform3 c_th2f_rebin rebinAxis = xform2 c_th2f_rebinaxis rebuild = xform1 c_th2f_rebuild reset = xform1 c_th2f_reset resetStats = xform0 c_th2f_resetstats scale = xform2 c_th2f_scale setAxisColorA = xform2 c_th2f_setaxiscolora setAxisRange = xform3 c_th2f_setaxisrange setBarOffset = xform1 c_th2f_setbaroffset setBarWidth = xform1 c_th2f_setbarwidth setBinContent1 = xform2 c_th2f_setbincontent1 setBinContent2 = xform3 c_th2f_setbincontent2 setBinContent3 = xform4 c_th2f_setbincontent3 setBinError1 = xform2 c_th2f_setbinerror1 setBinError2 = xform3 c_th2f_setbinerror2 setBinError3 = xform4 c_th2f_setbinerror3 setBins1 = xform2 c_th2f_setbins1 setBins2 = xform4 c_th2f_setbins2 setBins3 = xform6 c_th2f_setbins3 setBinsLength = xform1 c_th2f_setbinslength setBuffer = xform2 c_th2f_setbuffer setCellContent = xform3 c_th2f_setcellcontent setContent = xform1 c_th2f_setcontent setContour = xform2 c_th2f_setcontour setContourLevel = xform2 c_th2f_setcontourlevel setDirectory = xform1 c_th2f_setdirectory setEntries = xform1 c_th2f_setentries setError = xform1 c_th2f_seterror setLabelColorA = xform2 c_th2f_setlabelcolora setLabelSizeA = xform2 c_th2f_setlabelsizea setLabelFontA = xform2 c_th2f_setlabelfonta setLabelOffsetA = xform2 c_th2f_setlabeloffseta setMaximum = xform1 c_th2f_setmaximum setMinimum = xform1 c_th2f_setminimum setNormFactor = xform1 c_th2f_setnormfactor setStats = xform1 c_th2f_setstats setOption = xform1 c_th2f_setoption setXTitle = xform1 c_th2f_setxtitle setYTitle = xform1 c_th2f_setytitle setZTitle = xform1 c_th2f_setztitle showBackground = xform2 c_th2f_showbackground showPeaks = xform3 c_th2f_showpeaks smooth = xform2 c_th2f_smooth sumw2 = xform0 c_th2f_sumw2 instance ITNamed TH2F where setName = xform1 c_th2f_setname setNameTitle = xform2 c_th2f_setnametitle setTitle = xform1 c_th2f_settitle instance ITAttLine TH2F where getLineColor = xform0 c_th2f_getlinecolor getLineStyle = xform0 c_th2f_getlinestyle getLineWidth = xform0 c_th2f_getlinewidth resetAttLine = xform1 c_th2f_resetattline setLineAttributes = xform0 c_th2f_setlineattributes setLineColor = xform1 c_th2f_setlinecolor setLineStyle = xform1 c_th2f_setlinestyle setLineWidth = xform1 c_th2f_setlinewidth instance ITAttFill TH2F where setFillColor = xform1 c_th2f_setfillcolor setFillStyle = xform1 c_th2f_setfillstyle instance ITAttMarker TH2F where getMarkerColor = xform0 c_th2f_getmarkercolor getMarkerStyle = xform0 c_th2f_getmarkerstyle getMarkerSize = xform0 c_th2f_getmarkersize resetAttMarker = xform1 c_th2f_resetattmarker setMarkerAttributes = xform0 c_th2f_setmarkerattributes setMarkerColor = xform1 c_th2f_setmarkercolor setMarkerStyle = xform1 c_th2f_setmarkerstyle setMarkerSize = xform1 c_th2f_setmarkersize instance ITObject TH2F where draw = xform1 c_th2f_draw findObject = xform1 c_th2f_findobject getName = xform0 c_th2f_getname isA = xform0 c_th2f_isa isFolder = xform0 c_th2f_isfolder isEqual = xform1 c_th2f_isequal isSortable = xform0 c_th2f_issortable paint = xform1 c_th2f_paint printObj = xform1 c_th2f_printobj recursiveRemove = xform1 c_th2f_recursiveremove saveAs = xform2 c_th2f_saveas useCurrentStyle = xform0 c_th2f_usecurrentstyle write = xform3 c_th2f_write instance IDeletable TH2F where delete = xform0 c_th2f_delete instance ITArray TH2F where instance ITH2F (Exist TH2F) where instance ITH2 (Exist TH2F) where fill2 (ETH2F x) = fill2 x fill2w (ETH2F x) = fill2w x fillN2 (ETH2F x) = fillN2 x fillRandom2 (ETH2F x) = fillRandom2 x findFirstBinAbove2 (ETH2F x) = findFirstBinAbove2 x findLastBinAbove2 (ETH2F x) = findLastBinAbove2 x fitSlicesX (ETH2F x) = fitSlicesX x fitSlicesY (ETH2F x) = fitSlicesY x getCorrelationFactor2 (ETH2F x) = getCorrelationFactor2 x getCovariance2 (ETH2F x) = getCovariance2 x integral2 (ETH2F x) = integral2 x rebinX2 (ETH2F x) = rebinX2 x rebinY2 (ETH2F x) = rebinY2 x rebin2D (ETH2F x) = rebin2D x setShowProjectionX (ETH2F x) = setShowProjectionX x setShowProjectionY (ETH2F x) = setShowProjectionY x instance ITArrayF (Exist TH2F) where instance ITH1 (Exist TH2F) where add (ETH2F x) = add x addBinContent (ETH2F x) = addBinContent x chi2Test (ETH2F x) = chi2Test x computeIntegral (ETH2F x) = computeIntegral x directoryAutoAdd (ETH2F x) = directoryAutoAdd x divide (ETH2F x) = divide x drawCopyTH1 (ETH2F x) a1 = return . ETH2F =<< drawCopyTH1 x a1 drawNormalized (ETH2F x) = drawNormalized x drawPanelTH1 (ETH2F x) = drawPanelTH1 x bufferEmpty (ETH2F x) = bufferEmpty x evalF (ETH2F x) = evalF x fFT (ETH2F x) = fFT x fill1 (ETH2F x) = fill1 x fill1w (ETH2F x) = fill1w x fillN1 (ETH2F x) = fillN1 x fillRandom (ETH2F x) = fillRandom x findBin (ETH2F x) = findBin x findFixBin (ETH2F x) = findFixBin x findFirstBinAbove (ETH2F x) = findFirstBinAbove x findLastBinAbove (ETH2F x) = findLastBinAbove x fitPanelTH1 (ETH2F x) = fitPanelTH1 x getNdivisionA (ETH2F x) = getNdivisionA x getAxisColorA (ETH2F x) = getAxisColorA x getLabelColorA (ETH2F x) = getLabelColorA x getLabelFontA (ETH2F x) = getLabelFontA x getLabelOffsetA (ETH2F x) = getLabelOffsetA x getLabelSizeA (ETH2F x) = getLabelSizeA x getTitleFontA (ETH2F x) = getTitleFontA x getTitleOffsetA (ETH2F x) = getTitleOffsetA x getTitleSizeA (ETH2F x) = getTitleSizeA x getTickLengthA (ETH2F x) = getTickLengthA x getBarOffset (ETH2F x) = getBarOffset x getBarWidth (ETH2F x) = getBarWidth x getContour (ETH2F x) = getContour x getContourLevel (ETH2F x) = getContourLevel x getContourLevelPad (ETH2F x) = getContourLevelPad x getBin (ETH2F x) = getBin x getBinCenter (ETH2F x) = getBinCenter x getBinContent1 (ETH2F x) = getBinContent1 x getBinContent2 (ETH2F x) = getBinContent2 x getBinContent3 (ETH2F x) = getBinContent3 x getBinError1 (ETH2F x) = getBinError1 x getBinError2 (ETH2F x) = getBinError2 x getBinError3 (ETH2F x) = getBinError3 x getBinLowEdge (ETH2F x) = getBinLowEdge x getBinWidth (ETH2F x) = getBinWidth x getCellContent (ETH2F x) = getCellContent x getCellError (ETH2F x) = getCellError x getEntries (ETH2F x) = getEntries x getEffectiveEntries (ETH2F x) = getEffectiveEntries x getFunction (ETH2F x) = getFunction x getDimension (ETH2F x) = getDimension x getKurtosis (ETH2F x) = getKurtosis x getLowEdge (ETH2F x) = getLowEdge x getMaximumTH1 (ETH2F x) = getMaximumTH1 x getMaximumBin (ETH2F x) = getMaximumBin x getMaximumStored (ETH2F x) = getMaximumStored x getMinimumTH1 (ETH2F x) = getMinimumTH1 x getMinimumBin (ETH2F x) = getMinimumBin x getMinimumStored (ETH2F x) = getMinimumStored x getMean (ETH2F x) = getMean x getMeanError (ETH2F x) = getMeanError x getNbinsX (ETH2F x) = getNbinsX x getNbinsY (ETH2F x) = getNbinsY x getNbinsZ (ETH2F x) = getNbinsZ x getQuantilesTH1 (ETH2F x) = getQuantilesTH1 x getRandom (ETH2F x) = getRandom x getStats (ETH2F x) = getStats x getSumOfWeights (ETH2F x) = getSumOfWeights x getSumw2 (ETH2F x) = getSumw2 x getSumw2N (ETH2F x) = getSumw2N x getRMS (ETH2F x) = getRMS x getRMSError (ETH2F x) = getRMSError x getSkewness (ETH2F x) = getSkewness x integral1 (ETH2F x) = integral1 x interpolate1 (ETH2F x) = interpolate1 x interpolate2 (ETH2F x) = interpolate2 x interpolate3 (ETH2F x) = interpolate3 x kolmogorovTest (ETH2F x) = kolmogorovTest x labelsDeflate (ETH2F x) = labelsDeflate x labelsInflate (ETH2F x) = labelsInflate x labelsOption (ETH2F x) = labelsOption x multiflyF (ETH2F x) = multiflyF x multiply (ETH2F x) = multiply x putStats (ETH2F x) = putStats x rebin (ETH2F x) = rebin x rebinAxis (ETH2F x) = rebinAxis x rebuild (ETH2F x) = rebuild x reset (ETH2F x) = reset x resetStats (ETH2F x) = resetStats x scale (ETH2F x) = scale x setAxisColorA (ETH2F x) = setAxisColorA x setAxisRange (ETH2F x) = setAxisRange x setBarOffset (ETH2F x) = setBarOffset x setBarWidth (ETH2F x) = setBarWidth x setBinContent1 (ETH2F x) = setBinContent1 x setBinContent2 (ETH2F x) = setBinContent2 x setBinContent3 (ETH2F x) = setBinContent3 x setBinError1 (ETH2F x) = setBinError1 x setBinError2 (ETH2F x) = setBinError2 x setBinError3 (ETH2F x) = setBinError3 x setBins1 (ETH2F x) = setBins1 x setBins2 (ETH2F x) = setBins2 x setBins3 (ETH2F x) = setBins3 x setBinsLength (ETH2F x) = setBinsLength x setBuffer (ETH2F x) = setBuffer x setCellContent (ETH2F x) = setCellContent x setContent (ETH2F x) = setContent x setContour (ETH2F x) = setContour x setContourLevel (ETH2F x) = setContourLevel x setDirectory (ETH2F x) = setDirectory x setEntries (ETH2F x) = setEntries x setError (ETH2F x) = setError x setLabelColorA (ETH2F x) = setLabelColorA x setLabelSizeA (ETH2F x) = setLabelSizeA x setLabelFontA (ETH2F x) = setLabelFontA x setLabelOffsetA (ETH2F x) = setLabelOffsetA x setMaximum (ETH2F x) = setMaximum x setMinimum (ETH2F x) = setMinimum x setNormFactor (ETH2F x) = setNormFactor x setStats (ETH2F x) = setStats x setOption (ETH2F x) = setOption x setXTitle (ETH2F x) = setXTitle x setYTitle (ETH2F x) = setYTitle x setZTitle (ETH2F x) = setZTitle x showBackground (ETH2F x) = showBackground x showPeaks (ETH2F x) = showPeaks x smooth (ETH2F x) = smooth x sumw2 (ETH2F x) = sumw2 x instance ITNamed (Exist TH2F) where setName (ETH2F x) = setName x setNameTitle (ETH2F x) = setNameTitle x setTitle (ETH2F x) = setTitle x instance ITAttLine (Exist TH2F) where getLineColor (ETH2F x) = getLineColor x getLineStyle (ETH2F x) = getLineStyle x getLineWidth (ETH2F x) = getLineWidth x resetAttLine (ETH2F x) = resetAttLine x setLineAttributes (ETH2F x) = setLineAttributes x setLineColor (ETH2F x) = setLineColor x setLineStyle (ETH2F x) = setLineStyle x setLineWidth (ETH2F x) = setLineWidth x instance ITAttFill (Exist TH2F) where setFillColor (ETH2F x) = setFillColor x setFillStyle (ETH2F x) = setFillStyle x instance ITAttMarker (Exist TH2F) where getMarkerColor (ETH2F x) = getMarkerColor x getMarkerStyle (ETH2F x) = getMarkerStyle x getMarkerSize (ETH2F x) = getMarkerSize x resetAttMarker (ETH2F x) = resetAttMarker x setMarkerAttributes (ETH2F x) = setMarkerAttributes x setMarkerColor (ETH2F x) = setMarkerColor x setMarkerStyle (ETH2F x) = setMarkerStyle x setMarkerSize (ETH2F x) = setMarkerSize x instance ITObject (Exist TH2F) where draw (ETH2F x) = draw x findObject (ETH2F x) = findObject x getName (ETH2F x) = getName x isA (ETH2F x) = isA x isFolder (ETH2F x) = isFolder x isEqual (ETH2F x) = isEqual x isSortable (ETH2F x) = isSortable x paint (ETH2F x) = paint x printObj (ETH2F x) = printObj x recursiveRemove (ETH2F x) = recursiveRemove x saveAs (ETH2F x) = saveAs x useCurrentStyle (ETH2F x) = useCurrentStyle x write (ETH2F x) = write x instance IDeletable (Exist TH2F) where delete (ETH2F x) = delete x instance ITArray (Exist TH2F) where newTH2F :: String -> String -> Int -> Double -> Double -> Int -> Double -> Double -> IO TH2F newTH2F = xform7 c_th2f_newth2f instance FPtr (Exist TH2F) where type Raw (Exist TH2F) = RawTH2F get_fptr (ETH2F obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH2F (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2F) :: TH2F)