{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TH2S.Implementation where import HROOT.TypeCast import HROOT.Class.TH2S.RawType import HROOT.Class.TH2S.FFI import HROOT.Class.TH2S.Interface import HROOT.Class.TH2S.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.TArrayS.RawType import HROOT.Class.TArrayS.Cast import HROOT.Class.TArrayS.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 ITH2S TH2S where instance ITH2 TH2S where fill2 = xform2 c_th2s_fill2 fill2w = xform3 c_th2s_fill2w fillN2 = xform5 c_th2s_filln2 fillRandom2 = xform2 c_th2s_fillrandom2 findFirstBinAbove2 = xform2 c_th2s_findfirstbinabove2 findLastBinAbove2 = xform2 c_th2s_findlastbinabove2 fitSlicesX = xform6 c_th2s_fitslicesx fitSlicesY = xform6 c_th2s_fitslicesy getCorrelationFactor2 = xform2 c_th2s_getcorrelationfactor2 getCovariance2 = xform2 c_th2s_getcovariance2 integral2 = xform5 c_th2s_integral2 rebinX2 = xform2 c_th2s_rebinx2 rebinY2 = xform2 c_th2s_rebiny2 rebin2D = xform3 c_th2s_rebin2d setShowProjectionX = xform1 c_th2s_setshowprojectionx setShowProjectionY = xform1 c_th2s_setshowprojectiony instance ITArrayS TH2S where instance ITH1 TH2S where add = xform2 c_th2s_add addBinContent = xform2 c_th2s_addbincontent chi2Test = xform3 c_th2s_chi2test computeIntegral = xform0 c_th2s_computeintegral directoryAutoAdd = xform1 c_th2s_directoryautoadd divide = xform5 c_th2s_divide drawCopyTH1 = xform1 c_th2s_drawcopyth1 drawNormalized = xform2 c_th2s_drawnormalized drawPanelTH1 = xform0 c_th2s_drawpanelth1 bufferEmpty = xform1 c_th2s_bufferempty evalF = xform2 c_th2s_evalf fFT = xform2 c_th2s_fft fill1 = xform1 c_th2s_fill1 fill1w = xform2 c_th2s_fill1w fillN1 = xform4 c_th2s_filln1 fillRandom = xform2 c_th2s_fillrandom findBin = xform3 c_th2s_findbin findFixBin = xform3 c_th2s_findfixbin findFirstBinAbove = xform2 c_th2s_findfirstbinabove findLastBinAbove = xform2 c_th2s_findlastbinabove fitPanelTH1 = xform0 c_th2s_fitpanelth1 getNdivisionA = xform1 c_th2s_getndivisiona getAxisColorA = xform1 c_th2s_getaxiscolora getLabelColorA = xform1 c_th2s_getlabelcolora getLabelFontA = xform1 c_th2s_getlabelfonta getLabelOffsetA = xform1 c_th2s_getlabeloffseta getLabelSizeA = xform1 c_th2s_getlabelsizea getTitleFontA = xform1 c_th2s_gettitlefonta getTitleOffsetA = xform1 c_th2s_gettitleoffseta getTitleSizeA = xform1 c_th2s_gettitlesizea getTickLengthA = xform1 c_th2s_getticklengtha getBarOffset = xform0 c_th2s_getbaroffset getBarWidth = xform0 c_th2s_getbarwidth getContour = xform1 c_th2s_getcontour getContourLevel = xform1 c_th2s_getcontourlevel getContourLevelPad = xform1 c_th2s_getcontourlevelpad getBin = xform3 c_th2s_getbin getBinCenter = xform1 c_th2s_getbincenter getBinContent1 = xform1 c_th2s_getbincontent1 getBinContent2 = xform2 c_th2s_getbincontent2 getBinContent3 = xform3 c_th2s_getbincontent3 getBinError1 = xform1 c_th2s_getbinerror1 getBinError2 = xform2 c_th2s_getbinerror2 getBinError3 = xform3 c_th2s_getbinerror3 getBinLowEdge = xform1 c_th2s_getbinlowedge getBinWidth = xform1 c_th2s_getbinwidth getCellContent = xform2 c_th2s_getcellcontent getCellError = xform2 c_th2s_getcellerror getEntries = xform0 c_th2s_getentries getEffectiveEntries = xform0 c_th2s_geteffectiveentries getFunction = xform1 c_th2s_getfunction getDimension = xform0 c_th2s_getdimension getKurtosis = xform1 c_th2s_getkurtosis getLowEdge = xform1 c_th2s_getlowedge getMaximumTH1 = xform1 c_th2s_getmaximumth1 getMaximumBin = xform0 c_th2s_getmaximumbin getMaximumStored = xform0 c_th2s_getmaximumstored getMinimumTH1 = xform1 c_th2s_getminimumth1 getMinimumBin = xform0 c_th2s_getminimumbin getMinimumStored = xform0 c_th2s_getminimumstored getMean = xform1 c_th2s_getmean getMeanError = xform1 c_th2s_getmeanerror getNbinsX = xform0 c_th2s_getnbinsx getNbinsY = xform0 c_th2s_getnbinsy getNbinsZ = xform0 c_th2s_getnbinsz getQuantilesTH1 = xform3 c_th2s_getquantilesth1 getRandom = xform0 c_th2s_getrandom getStats = xform1 c_th2s_getstats getSumOfWeights = xform0 c_th2s_getsumofweights getSumw2 = xform0 c_th2s_getsumw2 getSumw2N = xform0 c_th2s_getsumw2n getRMS = xform1 c_th2s_getrms getRMSError = xform1 c_th2s_getrmserror getSkewness = xform1 c_th2s_getskewness integral1 = xform3 c_th2s_integral1 interpolate1 = xform1 c_th2s_interpolate1 interpolate2 = xform2 c_th2s_interpolate2 interpolate3 = xform3 c_th2s_interpolate3 kolmogorovTest = xform2 c_th2s_kolmogorovtest labelsDeflate = xform1 c_th2s_labelsdeflate labelsInflate = xform1 c_th2s_labelsinflate labelsOption = xform2 c_th2s_labelsoption multiflyF = xform2 c_th2s_multiflyf multiply = xform5 c_th2s_multiply putStats = xform1 c_th2s_putstats rebin = xform3 c_th2s_rebin rebinAxis = xform2 c_th2s_rebinaxis rebuild = xform1 c_th2s_rebuild reset = xform1 c_th2s_reset resetStats = xform0 c_th2s_resetstats scale = xform2 c_th2s_scale setAxisColorA = xform2 c_th2s_setaxiscolora setAxisRange = xform3 c_th2s_setaxisrange setBarOffset = xform1 c_th2s_setbaroffset setBarWidth = xform1 c_th2s_setbarwidth setBinContent1 = xform2 c_th2s_setbincontent1 setBinContent2 = xform3 c_th2s_setbincontent2 setBinContent3 = xform4 c_th2s_setbincontent3 setBinError1 = xform2 c_th2s_setbinerror1 setBinError2 = xform3 c_th2s_setbinerror2 setBinError3 = xform4 c_th2s_setbinerror3 setBins1 = xform2 c_th2s_setbins1 setBins2 = xform4 c_th2s_setbins2 setBins3 = xform6 c_th2s_setbins3 setBinsLength = xform1 c_th2s_setbinslength setBuffer = xform2 c_th2s_setbuffer setCellContent = xform3 c_th2s_setcellcontent setContent = xform1 c_th2s_setcontent setContour = xform2 c_th2s_setcontour setContourLevel = xform2 c_th2s_setcontourlevel setDirectory = xform1 c_th2s_setdirectory setEntries = xform1 c_th2s_setentries setError = xform1 c_th2s_seterror setLabelColorA = xform2 c_th2s_setlabelcolora setLabelSizeA = xform2 c_th2s_setlabelsizea setLabelFontA = xform2 c_th2s_setlabelfonta setLabelOffsetA = xform2 c_th2s_setlabeloffseta setMaximum = xform1 c_th2s_setmaximum setMinimum = xform1 c_th2s_setminimum setNormFactor = xform1 c_th2s_setnormfactor setStats = xform1 c_th2s_setstats setOption = xform1 c_th2s_setoption setXTitle = xform1 c_th2s_setxtitle setYTitle = xform1 c_th2s_setytitle setZTitle = xform1 c_th2s_setztitle showBackground = xform2 c_th2s_showbackground showPeaks = xform3 c_th2s_showpeaks smooth = xform2 c_th2s_smooth sumw2 = xform0 c_th2s_sumw2 instance ITNamed TH2S where setName = xform1 c_th2s_setname setNameTitle = xform2 c_th2s_setnametitle setTitle = xform1 c_th2s_settitle instance ITAttLine TH2S where getLineColor = xform0 c_th2s_getlinecolor getLineStyle = xform0 c_th2s_getlinestyle getLineWidth = xform0 c_th2s_getlinewidth resetAttLine = xform1 c_th2s_resetattline setLineAttributes = xform0 c_th2s_setlineattributes setLineColor = xform1 c_th2s_setlinecolor setLineStyle = xform1 c_th2s_setlinestyle setLineWidth = xform1 c_th2s_setlinewidth instance ITAttFill TH2S where setFillColor = xform1 c_th2s_setfillcolor setFillStyle = xform1 c_th2s_setfillstyle instance ITAttMarker TH2S where getMarkerColor = xform0 c_th2s_getmarkercolor getMarkerStyle = xform0 c_th2s_getmarkerstyle getMarkerSize = xform0 c_th2s_getmarkersize resetAttMarker = xform1 c_th2s_resetattmarker setMarkerAttributes = xform0 c_th2s_setmarkerattributes setMarkerColor = xform1 c_th2s_setmarkercolor setMarkerStyle = xform1 c_th2s_setmarkerstyle setMarkerSize = xform1 c_th2s_setmarkersize instance ITObject TH2S where draw = xform1 c_th2s_draw findObject = xform1 c_th2s_findobject getName = xform0 c_th2s_getname isA = xform0 c_th2s_isa isFolder = xform0 c_th2s_isfolder isEqual = xform1 c_th2s_isequal isSortable = xform0 c_th2s_issortable paint = xform1 c_th2s_paint printObj = xform1 c_th2s_printobj recursiveRemove = xform1 c_th2s_recursiveremove saveAs = xform2 c_th2s_saveas useCurrentStyle = xform0 c_th2s_usecurrentstyle write = xform3 c_th2s_write instance IDeletable TH2S where delete = xform0 c_th2s_delete instance ITArray TH2S where instance ITH2S (Exist TH2S) where instance ITH2 (Exist TH2S) where fill2 (ETH2S x) = fill2 x fill2w (ETH2S x) = fill2w x fillN2 (ETH2S x) = fillN2 x fillRandom2 (ETH2S x) = fillRandom2 x findFirstBinAbove2 (ETH2S x) = findFirstBinAbove2 x findLastBinAbove2 (ETH2S x) = findLastBinAbove2 x fitSlicesX (ETH2S x) = fitSlicesX x fitSlicesY (ETH2S x) = fitSlicesY x getCorrelationFactor2 (ETH2S x) = getCorrelationFactor2 x getCovariance2 (ETH2S x) = getCovariance2 x integral2 (ETH2S x) = integral2 x rebinX2 (ETH2S x) = rebinX2 x rebinY2 (ETH2S x) = rebinY2 x rebin2D (ETH2S x) = rebin2D x setShowProjectionX (ETH2S x) = setShowProjectionX x setShowProjectionY (ETH2S x) = setShowProjectionY x instance ITArrayS (Exist TH2S) where instance ITH1 (Exist TH2S) where add (ETH2S x) = add x addBinContent (ETH2S x) = addBinContent x chi2Test (ETH2S x) = chi2Test x computeIntegral (ETH2S x) = computeIntegral x directoryAutoAdd (ETH2S x) = directoryAutoAdd x divide (ETH2S x) = divide x drawCopyTH1 (ETH2S x) a1 = return . ETH2S =<< drawCopyTH1 x a1 drawNormalized (ETH2S x) = drawNormalized x drawPanelTH1 (ETH2S x) = drawPanelTH1 x bufferEmpty (ETH2S x) = bufferEmpty x evalF (ETH2S x) = evalF x fFT (ETH2S x) = fFT x fill1 (ETH2S x) = fill1 x fill1w (ETH2S x) = fill1w x fillN1 (ETH2S x) = fillN1 x fillRandom (ETH2S x) = fillRandom x findBin (ETH2S x) = findBin x findFixBin (ETH2S x) = findFixBin x findFirstBinAbove (ETH2S x) = findFirstBinAbove x findLastBinAbove (ETH2S x) = findLastBinAbove x fitPanelTH1 (ETH2S x) = fitPanelTH1 x getNdivisionA (ETH2S x) = getNdivisionA x getAxisColorA (ETH2S x) = getAxisColorA x getLabelColorA (ETH2S x) = getLabelColorA x getLabelFontA (ETH2S x) = getLabelFontA x getLabelOffsetA (ETH2S x) = getLabelOffsetA x getLabelSizeA (ETH2S x) = getLabelSizeA x getTitleFontA (ETH2S x) = getTitleFontA x getTitleOffsetA (ETH2S x) = getTitleOffsetA x getTitleSizeA (ETH2S x) = getTitleSizeA x getTickLengthA (ETH2S x) = getTickLengthA x getBarOffset (ETH2S x) = getBarOffset x getBarWidth (ETH2S x) = getBarWidth x getContour (ETH2S x) = getContour x getContourLevel (ETH2S x) = getContourLevel x getContourLevelPad (ETH2S x) = getContourLevelPad x getBin (ETH2S x) = getBin x getBinCenter (ETH2S x) = getBinCenter x getBinContent1 (ETH2S x) = getBinContent1 x getBinContent2 (ETH2S x) = getBinContent2 x getBinContent3 (ETH2S x) = getBinContent3 x getBinError1 (ETH2S x) = getBinError1 x getBinError2 (ETH2S x) = getBinError2 x getBinError3 (ETH2S x) = getBinError3 x getBinLowEdge (ETH2S x) = getBinLowEdge x getBinWidth (ETH2S x) = getBinWidth x getCellContent (ETH2S x) = getCellContent x getCellError (ETH2S x) = getCellError x getEntries (ETH2S x) = getEntries x getEffectiveEntries (ETH2S x) = getEffectiveEntries x getFunction (ETH2S x) = getFunction x getDimension (ETH2S x) = getDimension x getKurtosis (ETH2S x) = getKurtosis x getLowEdge (ETH2S x) = getLowEdge x getMaximumTH1 (ETH2S x) = getMaximumTH1 x getMaximumBin (ETH2S x) = getMaximumBin x getMaximumStored (ETH2S x) = getMaximumStored x getMinimumTH1 (ETH2S x) = getMinimumTH1 x getMinimumBin (ETH2S x) = getMinimumBin x getMinimumStored (ETH2S x) = getMinimumStored x getMean (ETH2S x) = getMean x getMeanError (ETH2S x) = getMeanError x getNbinsX (ETH2S x) = getNbinsX x getNbinsY (ETH2S x) = getNbinsY x getNbinsZ (ETH2S x) = getNbinsZ x getQuantilesTH1 (ETH2S x) = getQuantilesTH1 x getRandom (ETH2S x) = getRandom x getStats (ETH2S x) = getStats x getSumOfWeights (ETH2S x) = getSumOfWeights x getSumw2 (ETH2S x) = getSumw2 x getSumw2N (ETH2S x) = getSumw2N x getRMS (ETH2S x) = getRMS x getRMSError (ETH2S x) = getRMSError x getSkewness (ETH2S x) = getSkewness x integral1 (ETH2S x) = integral1 x interpolate1 (ETH2S x) = interpolate1 x interpolate2 (ETH2S x) = interpolate2 x interpolate3 (ETH2S x) = interpolate3 x kolmogorovTest (ETH2S x) = kolmogorovTest x labelsDeflate (ETH2S x) = labelsDeflate x labelsInflate (ETH2S x) = labelsInflate x labelsOption (ETH2S x) = labelsOption x multiflyF (ETH2S x) = multiflyF x multiply (ETH2S x) = multiply x putStats (ETH2S x) = putStats x rebin (ETH2S x) = rebin x rebinAxis (ETH2S x) = rebinAxis x rebuild (ETH2S x) = rebuild x reset (ETH2S x) = reset x resetStats (ETH2S x) = resetStats x scale (ETH2S x) = scale x setAxisColorA (ETH2S x) = setAxisColorA x setAxisRange (ETH2S x) = setAxisRange x setBarOffset (ETH2S x) = setBarOffset x setBarWidth (ETH2S x) = setBarWidth x setBinContent1 (ETH2S x) = setBinContent1 x setBinContent2 (ETH2S x) = setBinContent2 x setBinContent3 (ETH2S x) = setBinContent3 x setBinError1 (ETH2S x) = setBinError1 x setBinError2 (ETH2S x) = setBinError2 x setBinError3 (ETH2S x) = setBinError3 x setBins1 (ETH2S x) = setBins1 x setBins2 (ETH2S x) = setBins2 x setBins3 (ETH2S x) = setBins3 x setBinsLength (ETH2S x) = setBinsLength x setBuffer (ETH2S x) = setBuffer x setCellContent (ETH2S x) = setCellContent x setContent (ETH2S x) = setContent x setContour (ETH2S x) = setContour x setContourLevel (ETH2S x) = setContourLevel x setDirectory (ETH2S x) = setDirectory x setEntries (ETH2S x) = setEntries x setError (ETH2S x) = setError x setLabelColorA (ETH2S x) = setLabelColorA x setLabelSizeA (ETH2S x) = setLabelSizeA x setLabelFontA (ETH2S x) = setLabelFontA x setLabelOffsetA (ETH2S x) = setLabelOffsetA x setMaximum (ETH2S x) = setMaximum x setMinimum (ETH2S x) = setMinimum x setNormFactor (ETH2S x) = setNormFactor x setStats (ETH2S x) = setStats x setOption (ETH2S x) = setOption x setXTitle (ETH2S x) = setXTitle x setYTitle (ETH2S x) = setYTitle x setZTitle (ETH2S x) = setZTitle x showBackground (ETH2S x) = showBackground x showPeaks (ETH2S x) = showPeaks x smooth (ETH2S x) = smooth x sumw2 (ETH2S x) = sumw2 x instance ITNamed (Exist TH2S) where setName (ETH2S x) = setName x setNameTitle (ETH2S x) = setNameTitle x setTitle (ETH2S x) = setTitle x instance ITAttLine (Exist TH2S) where getLineColor (ETH2S x) = getLineColor x getLineStyle (ETH2S x) = getLineStyle x getLineWidth (ETH2S x) = getLineWidth x resetAttLine (ETH2S x) = resetAttLine x setLineAttributes (ETH2S x) = setLineAttributes x setLineColor (ETH2S x) = setLineColor x setLineStyle (ETH2S x) = setLineStyle x setLineWidth (ETH2S x) = setLineWidth x instance ITAttFill (Exist TH2S) where setFillColor (ETH2S x) = setFillColor x setFillStyle (ETH2S x) = setFillStyle x instance ITAttMarker (Exist TH2S) where getMarkerColor (ETH2S x) = getMarkerColor x getMarkerStyle (ETH2S x) = getMarkerStyle x getMarkerSize (ETH2S x) = getMarkerSize x resetAttMarker (ETH2S x) = resetAttMarker x setMarkerAttributes (ETH2S x) = setMarkerAttributes x setMarkerColor (ETH2S x) = setMarkerColor x setMarkerStyle (ETH2S x) = setMarkerStyle x setMarkerSize (ETH2S x) = setMarkerSize x instance ITObject (Exist TH2S) where draw (ETH2S x) = draw x findObject (ETH2S x) = findObject x getName (ETH2S x) = getName x isA (ETH2S x) = isA x isFolder (ETH2S x) = isFolder x isEqual (ETH2S x) = isEqual x isSortable (ETH2S x) = isSortable x paint (ETH2S x) = paint x printObj (ETH2S x) = printObj x recursiveRemove (ETH2S x) = recursiveRemove x saveAs (ETH2S x) = saveAs x useCurrentStyle (ETH2S x) = useCurrentStyle x write (ETH2S x) = write x instance IDeletable (Exist TH2S) where delete (ETH2S x) = delete x instance ITArray (Exist TH2S) where instance FPtr (Exist TH2S) where type Raw (Exist TH2S) = RawTH2S get_fptr (ETH2S obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH2S (cast_fptr_to_obj (fptr :: ForeignPtr RawTH2S) :: TH2S)