{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH1C.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH1C.RawType import HROOT.Hist.TH1C.FFI import HROOT.Hist.TH1C.Interface import HROOT.Hist.TH1C.Cast import HROOT.Core.TDirectory.RawType import HROOT.Core.TDirectory.Cast import HROOT.Core.TDirectory.Interface import HROOT.Hist.TF1.RawType import HROOT.Hist.TF1.Cast import HROOT.Hist.TF1.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.TH1.RawType import HROOT.Hist.TH1.Cast import HROOT.Hist.TH1.Interface import HROOT.Core.TArrayC.RawType import HROOT.Core.TArrayC.Cast import HROOT.Core.TArrayC.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 ITH1C TH1C where instance ITH1 TH1C where add = xform2 c_th1c_add addBinContent = xform2 c_th1c_addbincontent chi2Test = xform3 c_th1c_chi2test computeIntegral = xform0 c_th1c_computeintegral directoryAutoAdd = xform1 c_th1c_directoryautoadd divide = xform5 c_th1c_divide drawCopyTH1 = xform1 c_th1c_drawcopyth1 drawNormalized = xform2 c_th1c_drawnormalized drawPanelTH1 = xform0 c_th1c_drawpanelth1 bufferEmpty = xform1 c_th1c_bufferempty evalF = xform2 c_th1c_evalf fFT = xform2 c_th1c_fft fill1 = xform1 c_th1c_fill1 fill1w = xform2 c_th1c_fill1w fillN1 = xform4 c_th1c_filln1 fillRandom = xform2 c_th1c_fillrandom findBin = xform3 c_th1c_findbin findFixBin = xform3 c_th1c_findfixbin findFirstBinAbove = xform2 c_th1c_findfirstbinabove findLastBinAbove = xform2 c_th1c_findlastbinabove fitPanelTH1 = xform0 c_th1c_fitpanelth1 getNdivisionA = xform1 c_th1c_getndivisiona getAxisColorA = xform1 c_th1c_getaxiscolora getLabelColorA = xform1 c_th1c_getlabelcolora getLabelFontA = xform1 c_th1c_getlabelfonta getLabelOffsetA = xform1 c_th1c_getlabeloffseta getLabelSizeA = xform1 c_th1c_getlabelsizea getTitleFontA = xform1 c_th1c_gettitlefonta getTitleOffsetA = xform1 c_th1c_gettitleoffseta getTitleSizeA = xform1 c_th1c_gettitlesizea getTickLengthA = xform1 c_th1c_getticklengtha getBarOffset = xform0 c_th1c_getbaroffset getBarWidth = xform0 c_th1c_getbarwidth getContour = xform1 c_th1c_getcontour getContourLevel = xform1 c_th1c_getcontourlevel getContourLevelPad = xform1 c_th1c_getcontourlevelpad getBin = xform3 c_th1c_getbin getBinCenter = xform1 c_th1c_getbincenter getBinContent1 = xform1 c_th1c_getbincontent1 getBinContent2 = xform2 c_th1c_getbincontent2 getBinContent3 = xform3 c_th1c_getbincontent3 getBinError1 = xform1 c_th1c_getbinerror1 getBinError2 = xform2 c_th1c_getbinerror2 getBinError3 = xform3 c_th1c_getbinerror3 getBinLowEdge = xform1 c_th1c_getbinlowedge getBinWidth = xform1 c_th1c_getbinwidth getCellContent = xform2 c_th1c_getcellcontent getCellError = xform2 c_th1c_getcellerror getEntries = xform0 c_th1c_getentries getEffectiveEntries = xform0 c_th1c_geteffectiveentries getFunction = xform1 c_th1c_getfunction getDimension = xform0 c_th1c_getdimension getKurtosis = xform1 c_th1c_getkurtosis getLowEdge = xform1 c_th1c_getlowedge getMaximumTH1 = xform1 c_th1c_getmaximumth1 getMaximumBin = xform0 c_th1c_getmaximumbin getMaximumStored = xform0 c_th1c_getmaximumstored getMinimumTH1 = xform1 c_th1c_getminimumth1 getMinimumBin = xform0 c_th1c_getminimumbin getMinimumStored = xform0 c_th1c_getminimumstored getMean = xform1 c_th1c_getmean getMeanError = xform1 c_th1c_getmeanerror getNbinsX = xform0 c_th1c_getnbinsx getNbinsY = xform0 c_th1c_getnbinsy getNbinsZ = xform0 c_th1c_getnbinsz getQuantilesTH1 = xform3 c_th1c_getquantilesth1 getRandom = xform0 c_th1c_getrandom getStats = xform1 c_th1c_getstats getSumOfWeights = xform0 c_th1c_getsumofweights getSumw2 = xform0 c_th1c_getsumw2 getSumw2N = xform0 c_th1c_getsumw2n getRMS = xform1 c_th1c_getrms getRMSError = xform1 c_th1c_getrmserror getSkewness = xform1 c_th1c_getskewness integral1 = xform3 c_th1c_integral1 interpolate1 = xform1 c_th1c_interpolate1 interpolate2 = xform2 c_th1c_interpolate2 interpolate3 = xform3 c_th1c_interpolate3 kolmogorovTest = xform2 c_th1c_kolmogorovtest labelsDeflate = xform1 c_th1c_labelsdeflate labelsInflate = xform1 c_th1c_labelsinflate labelsOption = xform2 c_th1c_labelsoption multiflyF = xform2 c_th1c_multiflyf multiply = xform5 c_th1c_multiply putStats = xform1 c_th1c_putstats rebin = xform3 c_th1c_rebin rebinAxis = xform2 c_th1c_rebinaxis rebuild = xform1 c_th1c_rebuild recursiveRemove = xform1 c_th1c_recursiveremove reset = xform1 c_th1c_reset resetStats = xform0 c_th1c_resetstats scale = xform2 c_th1c_scale setAxisColorA = xform2 c_th1c_setaxiscolora setAxisRange = xform3 c_th1c_setaxisrange setBarOffset = xform1 c_th1c_setbaroffset setBarWidth = xform1 c_th1c_setbarwidth setBinContent1 = xform2 c_th1c_setbincontent1 setBinContent2 = xform3 c_th1c_setbincontent2 setBinContent3 = xform4 c_th1c_setbincontent3 setBinError1 = xform2 c_th1c_setbinerror1 setBinError2 = xform3 c_th1c_setbinerror2 setBinError3 = xform4 c_th1c_setbinerror3 setBins1 = xform2 c_th1c_setbins1 setBins2 = xform4 c_th1c_setbins2 setBins3 = xform6 c_th1c_setbins3 setBinsLength = xform1 c_th1c_setbinslength setBuffer = xform2 c_th1c_setbuffer setCellContent = xform3 c_th1c_setcellcontent setContent = xform1 c_th1c_setcontent setContour = xform2 c_th1c_setcontour setContourLevel = xform2 c_th1c_setcontourlevel setDirectory = xform1 c_th1c_setdirectory setEntries = xform1 c_th1c_setentries setError = xform1 c_th1c_seterror setLabelColorA = xform2 c_th1c_setlabelcolora setLabelSizeA = xform2 c_th1c_setlabelsizea setLabelFontA = xform2 c_th1c_setlabelfonta setLabelOffsetA = xform2 c_th1c_setlabeloffseta setMaximum = xform1 c_th1c_setmaximum setMinimum = xform1 c_th1c_setminimum setNormFactor = xform1 c_th1c_setnormfactor setStats = xform1 c_th1c_setstats setOption = xform1 c_th1c_setoption setXTitle = xform1 c_th1c_setxtitle setYTitle = xform1 c_th1c_setytitle setZTitle = xform1 c_th1c_setztitle showBackground = xform2 c_th1c_showbackground showPeaks = xform3 c_th1c_showpeaks smooth = xform2 c_th1c_smooth sumw2 = xform0 c_th1c_sumw2 instance ITArrayC TH1C where instance ITObject TH1C where draw = xform1 c_th1c_draw findObject = xform1 c_th1c_findobject getName = xform0 c_th1c_getname isA = xform0 c_th1c_isa paint = xform1 c_th1c_paint printObj = xform1 c_th1c_printobj saveAs = xform2 c_th1c_saveas write = xform3 c_th1c_write instance ITAttLine TH1C where getLineColor = xform0 c_th1c_getlinecolor getLineStyle = xform0 c_th1c_getlinestyle getLineWidth = xform0 c_th1c_getlinewidth resetAttLine = xform1 c_th1c_resetattline setLineAttributes = xform0 c_th1c_setlineattributes setLineColor = xform1 c_th1c_setlinecolor setLineStyle = xform1 c_th1c_setlinestyle setLineWidth = xform1 c_th1c_setlinewidth instance ITAttFill TH1C where setFillColor = xform1 c_th1c_setfillcolor setFillStyle = xform1 c_th1c_setfillstyle instance ITAttMarker TH1C where getMarkerColor = xform0 c_th1c_getmarkercolor getMarkerStyle = xform0 c_th1c_getmarkerstyle getMarkerSize = xform0 c_th1c_getmarkersize resetAttMarker = xform1 c_th1c_resetattmarker setMarkerAttributes = xform0 c_th1c_setmarkerattributes setMarkerColor = xform1 c_th1c_setmarkercolor setMarkerStyle = xform1 c_th1c_setmarkerstyle setMarkerSize = xform1 c_th1c_setmarkersize instance IDeletable TH1C where delete = xform0 c_th1c_delete instance ITArray TH1C where instance ITH1C (Exist TH1C) where instance ITH1 (Exist TH1C) where add (ETH1C x) = add x addBinContent (ETH1C x) = addBinContent x chi2Test (ETH1C x) = chi2Test x computeIntegral (ETH1C x) = computeIntegral x directoryAutoAdd (ETH1C x) = directoryAutoAdd x divide (ETH1C x) = divide x drawCopyTH1 (ETH1C x) a1 = return . ETH1C =<< drawCopyTH1 x a1 drawNormalized (ETH1C x) = drawNormalized x drawPanelTH1 (ETH1C x) = drawPanelTH1 x bufferEmpty (ETH1C x) = bufferEmpty x evalF (ETH1C x) = evalF x fFT (ETH1C x) = fFT x fill1 (ETH1C x) = fill1 x fill1w (ETH1C x) = fill1w x fillN1 (ETH1C x) = fillN1 x fillRandom (ETH1C x) = fillRandom x findBin (ETH1C x) = findBin x findFixBin (ETH1C x) = findFixBin x findFirstBinAbove (ETH1C x) = findFirstBinAbove x findLastBinAbove (ETH1C x) = findLastBinAbove x fitPanelTH1 (ETH1C x) = fitPanelTH1 x getNdivisionA (ETH1C x) = getNdivisionA x getAxisColorA (ETH1C x) = getAxisColorA x getLabelColorA (ETH1C x) = getLabelColorA x getLabelFontA (ETH1C x) = getLabelFontA x getLabelOffsetA (ETH1C x) = getLabelOffsetA x getLabelSizeA (ETH1C x) = getLabelSizeA x getTitleFontA (ETH1C x) = getTitleFontA x getTitleOffsetA (ETH1C x) = getTitleOffsetA x getTitleSizeA (ETH1C x) = getTitleSizeA x getTickLengthA (ETH1C x) = getTickLengthA x getBarOffset (ETH1C x) = getBarOffset x getBarWidth (ETH1C x) = getBarWidth x getContour (ETH1C x) = getContour x getContourLevel (ETH1C x) = getContourLevel x getContourLevelPad (ETH1C x) = getContourLevelPad x getBin (ETH1C x) = getBin x getBinCenter (ETH1C x) = getBinCenter x getBinContent1 (ETH1C x) = getBinContent1 x getBinContent2 (ETH1C x) = getBinContent2 x getBinContent3 (ETH1C x) = getBinContent3 x getBinError1 (ETH1C x) = getBinError1 x getBinError2 (ETH1C x) = getBinError2 x getBinError3 (ETH1C x) = getBinError3 x getBinLowEdge (ETH1C x) = getBinLowEdge x getBinWidth (ETH1C x) = getBinWidth x getCellContent (ETH1C x) = getCellContent x getCellError (ETH1C x) = getCellError x getEntries (ETH1C x) = getEntries x getEffectiveEntries (ETH1C x) = getEffectiveEntries x getFunction (ETH1C x) = getFunction x getDimension (ETH1C x) = getDimension x getKurtosis (ETH1C x) = getKurtosis x getLowEdge (ETH1C x) = getLowEdge x getMaximumTH1 (ETH1C x) = getMaximumTH1 x getMaximumBin (ETH1C x) = getMaximumBin x getMaximumStored (ETH1C x) = getMaximumStored x getMinimumTH1 (ETH1C x) = getMinimumTH1 x getMinimumBin (ETH1C x) = getMinimumBin x getMinimumStored (ETH1C x) = getMinimumStored x getMean (ETH1C x) = getMean x getMeanError (ETH1C x) = getMeanError x getNbinsX (ETH1C x) = getNbinsX x getNbinsY (ETH1C x) = getNbinsY x getNbinsZ (ETH1C x) = getNbinsZ x getQuantilesTH1 (ETH1C x) = getQuantilesTH1 x getRandom (ETH1C x) = getRandom x getStats (ETH1C x) = getStats x getSumOfWeights (ETH1C x) = getSumOfWeights x getSumw2 (ETH1C x) = getSumw2 x getSumw2N (ETH1C x) = getSumw2N x getRMS (ETH1C x) = getRMS x getRMSError (ETH1C x) = getRMSError x getSkewness (ETH1C x) = getSkewness x integral1 (ETH1C x) = integral1 x interpolate1 (ETH1C x) = interpolate1 x interpolate2 (ETH1C x) = interpolate2 x interpolate3 (ETH1C x) = interpolate3 x kolmogorovTest (ETH1C x) = kolmogorovTest x labelsDeflate (ETH1C x) = labelsDeflate x labelsInflate (ETH1C x) = labelsInflate x labelsOption (ETH1C x) = labelsOption x multiflyF (ETH1C x) = multiflyF x multiply (ETH1C x) = multiply x putStats (ETH1C x) = putStats x rebin (ETH1C x) = rebin x rebinAxis (ETH1C x) = rebinAxis x rebuild (ETH1C x) = rebuild x recursiveRemove (ETH1C x) = recursiveRemove x reset (ETH1C x) = reset x resetStats (ETH1C x) = resetStats x scale (ETH1C x) = scale x setAxisColorA (ETH1C x) = setAxisColorA x setAxisRange (ETH1C x) = setAxisRange x setBarOffset (ETH1C x) = setBarOffset x setBarWidth (ETH1C x) = setBarWidth x setBinContent1 (ETH1C x) = setBinContent1 x setBinContent2 (ETH1C x) = setBinContent2 x setBinContent3 (ETH1C x) = setBinContent3 x setBinError1 (ETH1C x) = setBinError1 x setBinError2 (ETH1C x) = setBinError2 x setBinError3 (ETH1C x) = setBinError3 x setBins1 (ETH1C x) = setBins1 x setBins2 (ETH1C x) = setBins2 x setBins3 (ETH1C x) = setBins3 x setBinsLength (ETH1C x) = setBinsLength x setBuffer (ETH1C x) = setBuffer x setCellContent (ETH1C x) = setCellContent x setContent (ETH1C x) = setContent x setContour (ETH1C x) = setContour x setContourLevel (ETH1C x) = setContourLevel x setDirectory (ETH1C x) = setDirectory x setEntries (ETH1C x) = setEntries x setError (ETH1C x) = setError x setLabelColorA (ETH1C x) = setLabelColorA x setLabelSizeA (ETH1C x) = setLabelSizeA x setLabelFontA (ETH1C x) = setLabelFontA x setLabelOffsetA (ETH1C x) = setLabelOffsetA x setMaximum (ETH1C x) = setMaximum x setMinimum (ETH1C x) = setMinimum x setNormFactor (ETH1C x) = setNormFactor x setStats (ETH1C x) = setStats x setOption (ETH1C x) = setOption x setXTitle (ETH1C x) = setXTitle x setYTitle (ETH1C x) = setYTitle x setZTitle (ETH1C x) = setZTitle x showBackground (ETH1C x) = showBackground x showPeaks (ETH1C x) = showPeaks x smooth (ETH1C x) = smooth x sumw2 (ETH1C x) = sumw2 x instance ITArrayC (Exist TH1C) where instance ITObject (Exist TH1C) where draw (ETH1C x) = draw x findObject (ETH1C x) = findObject x getName (ETH1C x) = getName x isA (ETH1C x) = isA x paint (ETH1C x) = paint x printObj (ETH1C x) = printObj x saveAs (ETH1C x) = saveAs x write (ETH1C x) = write x instance ITAttLine (Exist TH1C) where getLineColor (ETH1C x) = getLineColor x getLineStyle (ETH1C x) = getLineStyle x getLineWidth (ETH1C x) = getLineWidth x resetAttLine (ETH1C x) = resetAttLine x setLineAttributes (ETH1C x) = setLineAttributes x setLineColor (ETH1C x) = setLineColor x setLineStyle (ETH1C x) = setLineStyle x setLineWidth (ETH1C x) = setLineWidth x instance ITAttFill (Exist TH1C) where setFillColor (ETH1C x) = setFillColor x setFillStyle (ETH1C x) = setFillStyle x instance ITAttMarker (Exist TH1C) where getMarkerColor (ETH1C x) = getMarkerColor x getMarkerStyle (ETH1C x) = getMarkerStyle x getMarkerSize (ETH1C x) = getMarkerSize x resetAttMarker (ETH1C x) = resetAttMarker x setMarkerAttributes (ETH1C x) = setMarkerAttributes x setMarkerColor (ETH1C x) = setMarkerColor x setMarkerStyle (ETH1C x) = setMarkerStyle x setMarkerSize (ETH1C x) = setMarkerSize x instance IDeletable (Exist TH1C) where delete (ETH1C x) = delete x instance ITArray (Exist TH1C) where instance FPtr (Exist TH1C) where type Raw (Exist TH1C) = RawTH1C get_fptr (ETH1C obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH1C (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1C) :: TH1C)