{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH1D.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH1D.RawType import HROOT.Hist.TH1D.FFI import HROOT.Hist.TH1D.Interface import HROOT.Hist.TH1D.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.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.TArrayD.RawType import HROOT.Core.TArrayD.Cast import HROOT.Core.TArrayD.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 ITH1D TH1D where instance ITH1 TH1D where add = xform2 c_th1d_add addBinContent = xform2 c_th1d_addbincontent chi2Test = xform3 c_th1d_chi2test computeIntegral = xform0 c_th1d_computeintegral directoryAutoAdd = xform1 c_th1d_directoryautoadd divide = xform5 c_th1d_divide drawCopyTH1 = xform1 c_th1d_drawcopyth1 drawNormalized = xform2 c_th1d_drawnormalized drawPanelTH1 = xform0 c_th1d_drawpanelth1 bufferEmpty = xform1 c_th1d_bufferempty evalF = xform2 c_th1d_evalf fFT = xform2 c_th1d_fft fill1 = xform1 c_th1d_fill1 fill1w = xform2 c_th1d_fill1w fillN1 = xform4 c_th1d_filln1 fillRandom = xform2 c_th1d_fillrandom findBin = xform3 c_th1d_findbin findFixBin = xform3 c_th1d_findfixbin findFirstBinAbove = xform2 c_th1d_findfirstbinabove findLastBinAbove = xform2 c_th1d_findlastbinabove fitPanelTH1 = xform0 c_th1d_fitpanelth1 getNdivisionA = xform1 c_th1d_getndivisiona getAxisColorA = xform1 c_th1d_getaxiscolora getLabelColorA = xform1 c_th1d_getlabelcolora getLabelFontA = xform1 c_th1d_getlabelfonta getLabelOffsetA = xform1 c_th1d_getlabeloffseta getLabelSizeA = xform1 c_th1d_getlabelsizea getTitleFontA = xform1 c_th1d_gettitlefonta getTitleOffsetA = xform1 c_th1d_gettitleoffseta getTitleSizeA = xform1 c_th1d_gettitlesizea getTickLengthA = xform1 c_th1d_getticklengtha getBarOffset = xform0 c_th1d_getbaroffset getBarWidth = xform0 c_th1d_getbarwidth getContour = xform1 c_th1d_getcontour getContourLevel = xform1 c_th1d_getcontourlevel getContourLevelPad = xform1 c_th1d_getcontourlevelpad getBin = xform3 c_th1d_getbin getBinCenter = xform1 c_th1d_getbincenter getBinContent1 = xform1 c_th1d_getbincontent1 getBinContent2 = xform2 c_th1d_getbincontent2 getBinContent3 = xform3 c_th1d_getbincontent3 getBinError1 = xform1 c_th1d_getbinerror1 getBinError2 = xform2 c_th1d_getbinerror2 getBinError3 = xform3 c_th1d_getbinerror3 getBinLowEdge = xform1 c_th1d_getbinlowedge getBinWidth = xform1 c_th1d_getbinwidth getCellContent = xform2 c_th1d_getcellcontent getCellError = xform2 c_th1d_getcellerror getEntries = xform0 c_th1d_getentries getEffectiveEntries = xform0 c_th1d_geteffectiveentries getFunction = xform1 c_th1d_getfunction getDimension = xform0 c_th1d_getdimension getKurtosis = xform1 c_th1d_getkurtosis getLowEdge = xform1 c_th1d_getlowedge getMaximumTH1 = xform1 c_th1d_getmaximumth1 getMaximumBin = xform0 c_th1d_getmaximumbin getMaximumStored = xform0 c_th1d_getmaximumstored getMinimumTH1 = xform1 c_th1d_getminimumth1 getMinimumBin = xform0 c_th1d_getminimumbin getMinimumStored = xform0 c_th1d_getminimumstored getMean = xform1 c_th1d_getmean getMeanError = xform1 c_th1d_getmeanerror getNbinsX = xform0 c_th1d_getnbinsx getNbinsY = xform0 c_th1d_getnbinsy getNbinsZ = xform0 c_th1d_getnbinsz getQuantilesTH1 = xform3 c_th1d_getquantilesth1 getRandom = xform0 c_th1d_getrandom getStats = xform1 c_th1d_getstats getSumOfWeights = xform0 c_th1d_getsumofweights getSumw2 = xform0 c_th1d_getsumw2 getSumw2N = xform0 c_th1d_getsumw2n getRMS = xform1 c_th1d_getrms getRMSError = xform1 c_th1d_getrmserror getSkewness = xform1 c_th1d_getskewness integral1 = xform3 c_th1d_integral1 interpolate1 = xform1 c_th1d_interpolate1 interpolate2 = xform2 c_th1d_interpolate2 interpolate3 = xform3 c_th1d_interpolate3 kolmogorovTest = xform2 c_th1d_kolmogorovtest labelsDeflate = xform1 c_th1d_labelsdeflate labelsInflate = xform1 c_th1d_labelsinflate labelsOption = xform2 c_th1d_labelsoption multiflyF = xform2 c_th1d_multiflyf multiply = xform5 c_th1d_multiply putStats = xform1 c_th1d_putstats rebin = xform3 c_th1d_rebin rebinAxis = xform2 c_th1d_rebinaxis rebuild = xform1 c_th1d_rebuild recursiveRemove = xform1 c_th1d_recursiveremove reset = xform1 c_th1d_reset resetStats = xform0 c_th1d_resetstats scale = xform2 c_th1d_scale setAxisColorA = xform2 c_th1d_setaxiscolora setAxisRange = xform3 c_th1d_setaxisrange setBarOffset = xform1 c_th1d_setbaroffset setBarWidth = xform1 c_th1d_setbarwidth setBinContent1 = xform2 c_th1d_setbincontent1 setBinContent2 = xform3 c_th1d_setbincontent2 setBinContent3 = xform4 c_th1d_setbincontent3 setBinError1 = xform2 c_th1d_setbinerror1 setBinError2 = xform3 c_th1d_setbinerror2 setBinError3 = xform4 c_th1d_setbinerror3 setBins1 = xform2 c_th1d_setbins1 setBins2 = xform4 c_th1d_setbins2 setBins3 = xform6 c_th1d_setbins3 setBinsLength = xform1 c_th1d_setbinslength setBuffer = xform2 c_th1d_setbuffer setCellContent = xform3 c_th1d_setcellcontent setContent = xform1 c_th1d_setcontent setContour = xform2 c_th1d_setcontour setContourLevel = xform2 c_th1d_setcontourlevel setDirectory = xform1 c_th1d_setdirectory setEntries = xform1 c_th1d_setentries setError = xform1 c_th1d_seterror setLabelColorA = xform2 c_th1d_setlabelcolora setLabelSizeA = xform2 c_th1d_setlabelsizea setLabelFontA = xform2 c_th1d_setlabelfonta setLabelOffsetA = xform2 c_th1d_setlabeloffseta setMaximum = xform1 c_th1d_setmaximum setMinimum = xform1 c_th1d_setminimum setNormFactor = xform1 c_th1d_setnormfactor setStats = xform1 c_th1d_setstats setOption = xform1 c_th1d_setoption setXTitle = xform1 c_th1d_setxtitle setYTitle = xform1 c_th1d_setytitle setZTitle = xform1 c_th1d_setztitle showBackground = xform2 c_th1d_showbackground showPeaks = xform3 c_th1d_showpeaks smooth = xform2 c_th1d_smooth sumw2 = xform0 c_th1d_sumw2 instance ITArrayD TH1D where instance ITObject TH1D where draw = xform1 c_th1d_draw findObject = xform1 c_th1d_findobject getName = xform0 c_th1d_getname isA = xform0 c_th1d_isa paint = xform1 c_th1d_paint printObj = xform1 c_th1d_printobj saveAs = xform2 c_th1d_saveas write = xform3 c_th1d_write instance ITAttLine TH1D where getLineColor = xform0 c_th1d_getlinecolor getLineStyle = xform0 c_th1d_getlinestyle getLineWidth = xform0 c_th1d_getlinewidth resetAttLine = xform1 c_th1d_resetattline setLineAttributes = xform0 c_th1d_setlineattributes setLineColor = xform1 c_th1d_setlinecolor setLineStyle = xform1 c_th1d_setlinestyle setLineWidth = xform1 c_th1d_setlinewidth instance ITAttFill TH1D where setFillColor = xform1 c_th1d_setfillcolor setFillStyle = xform1 c_th1d_setfillstyle instance ITAttMarker TH1D where getMarkerColor = xform0 c_th1d_getmarkercolor getMarkerStyle = xform0 c_th1d_getmarkerstyle getMarkerSize = xform0 c_th1d_getmarkersize resetAttMarker = xform1 c_th1d_resetattmarker setMarkerAttributes = xform0 c_th1d_setmarkerattributes setMarkerColor = xform1 c_th1d_setmarkercolor setMarkerStyle = xform1 c_th1d_setmarkerstyle setMarkerSize = xform1 c_th1d_setmarkersize instance IDeletable TH1D where delete = xform0 c_th1d_delete instance ITArray TH1D where instance ITH1D (Exist TH1D) where instance ITH1 (Exist TH1D) where add (ETH1D x) = add x addBinContent (ETH1D x) = addBinContent x chi2Test (ETH1D x) = chi2Test x computeIntegral (ETH1D x) = computeIntegral x directoryAutoAdd (ETH1D x) = directoryAutoAdd x divide (ETH1D x) = divide x drawCopyTH1 (ETH1D x) a1 = return . ETH1D =<< drawCopyTH1 x a1 drawNormalized (ETH1D x) = drawNormalized x drawPanelTH1 (ETH1D x) = drawPanelTH1 x bufferEmpty (ETH1D x) = bufferEmpty x evalF (ETH1D x) = evalF x fFT (ETH1D x) = fFT x fill1 (ETH1D x) = fill1 x fill1w (ETH1D x) = fill1w x fillN1 (ETH1D x) = fillN1 x fillRandom (ETH1D x) = fillRandom x findBin (ETH1D x) = findBin x findFixBin (ETH1D x) = findFixBin x findFirstBinAbove (ETH1D x) = findFirstBinAbove x findLastBinAbove (ETH1D x) = findLastBinAbove x fitPanelTH1 (ETH1D x) = fitPanelTH1 x getNdivisionA (ETH1D x) = getNdivisionA x getAxisColorA (ETH1D x) = getAxisColorA x getLabelColorA (ETH1D x) = getLabelColorA x getLabelFontA (ETH1D x) = getLabelFontA x getLabelOffsetA (ETH1D x) = getLabelOffsetA x getLabelSizeA (ETH1D x) = getLabelSizeA x getTitleFontA (ETH1D x) = getTitleFontA x getTitleOffsetA (ETH1D x) = getTitleOffsetA x getTitleSizeA (ETH1D x) = getTitleSizeA x getTickLengthA (ETH1D x) = getTickLengthA x getBarOffset (ETH1D x) = getBarOffset x getBarWidth (ETH1D x) = getBarWidth x getContour (ETH1D x) = getContour x getContourLevel (ETH1D x) = getContourLevel x getContourLevelPad (ETH1D x) = getContourLevelPad x getBin (ETH1D x) = getBin x getBinCenter (ETH1D x) = getBinCenter x getBinContent1 (ETH1D x) = getBinContent1 x getBinContent2 (ETH1D x) = getBinContent2 x getBinContent3 (ETH1D x) = getBinContent3 x getBinError1 (ETH1D x) = getBinError1 x getBinError2 (ETH1D x) = getBinError2 x getBinError3 (ETH1D x) = getBinError3 x getBinLowEdge (ETH1D x) = getBinLowEdge x getBinWidth (ETH1D x) = getBinWidth x getCellContent (ETH1D x) = getCellContent x getCellError (ETH1D x) = getCellError x getEntries (ETH1D x) = getEntries x getEffectiveEntries (ETH1D x) = getEffectiveEntries x getFunction (ETH1D x) = getFunction x getDimension (ETH1D x) = getDimension x getKurtosis (ETH1D x) = getKurtosis x getLowEdge (ETH1D x) = getLowEdge x getMaximumTH1 (ETH1D x) = getMaximumTH1 x getMaximumBin (ETH1D x) = getMaximumBin x getMaximumStored (ETH1D x) = getMaximumStored x getMinimumTH1 (ETH1D x) = getMinimumTH1 x getMinimumBin (ETH1D x) = getMinimumBin x getMinimumStored (ETH1D x) = getMinimumStored x getMean (ETH1D x) = getMean x getMeanError (ETH1D x) = getMeanError x getNbinsX (ETH1D x) = getNbinsX x getNbinsY (ETH1D x) = getNbinsY x getNbinsZ (ETH1D x) = getNbinsZ x getQuantilesTH1 (ETH1D x) = getQuantilesTH1 x getRandom (ETH1D x) = getRandom x getStats (ETH1D x) = getStats x getSumOfWeights (ETH1D x) = getSumOfWeights x getSumw2 (ETH1D x) = getSumw2 x getSumw2N (ETH1D x) = getSumw2N x getRMS (ETH1D x) = getRMS x getRMSError (ETH1D x) = getRMSError x getSkewness (ETH1D x) = getSkewness x integral1 (ETH1D x) = integral1 x interpolate1 (ETH1D x) = interpolate1 x interpolate2 (ETH1D x) = interpolate2 x interpolate3 (ETH1D x) = interpolate3 x kolmogorovTest (ETH1D x) = kolmogorovTest x labelsDeflate (ETH1D x) = labelsDeflate x labelsInflate (ETH1D x) = labelsInflate x labelsOption (ETH1D x) = labelsOption x multiflyF (ETH1D x) = multiflyF x multiply (ETH1D x) = multiply x putStats (ETH1D x) = putStats x rebin (ETH1D x) = rebin x rebinAxis (ETH1D x) = rebinAxis x rebuild (ETH1D x) = rebuild x recursiveRemove (ETH1D x) = recursiveRemove x reset (ETH1D x) = reset x resetStats (ETH1D x) = resetStats x scale (ETH1D x) = scale x setAxisColorA (ETH1D x) = setAxisColorA x setAxisRange (ETH1D x) = setAxisRange x setBarOffset (ETH1D x) = setBarOffset x setBarWidth (ETH1D x) = setBarWidth x setBinContent1 (ETH1D x) = setBinContent1 x setBinContent2 (ETH1D x) = setBinContent2 x setBinContent3 (ETH1D x) = setBinContent3 x setBinError1 (ETH1D x) = setBinError1 x setBinError2 (ETH1D x) = setBinError2 x setBinError3 (ETH1D x) = setBinError3 x setBins1 (ETH1D x) = setBins1 x setBins2 (ETH1D x) = setBins2 x setBins3 (ETH1D x) = setBins3 x setBinsLength (ETH1D x) = setBinsLength x setBuffer (ETH1D x) = setBuffer x setCellContent (ETH1D x) = setCellContent x setContent (ETH1D x) = setContent x setContour (ETH1D x) = setContour x setContourLevel (ETH1D x) = setContourLevel x setDirectory (ETH1D x) = setDirectory x setEntries (ETH1D x) = setEntries x setError (ETH1D x) = setError x setLabelColorA (ETH1D x) = setLabelColorA x setLabelSizeA (ETH1D x) = setLabelSizeA x setLabelFontA (ETH1D x) = setLabelFontA x setLabelOffsetA (ETH1D x) = setLabelOffsetA x setMaximum (ETH1D x) = setMaximum x setMinimum (ETH1D x) = setMinimum x setNormFactor (ETH1D x) = setNormFactor x setStats (ETH1D x) = setStats x setOption (ETH1D x) = setOption x setXTitle (ETH1D x) = setXTitle x setYTitle (ETH1D x) = setYTitle x setZTitle (ETH1D x) = setZTitle x showBackground (ETH1D x) = showBackground x showPeaks (ETH1D x) = showPeaks x smooth (ETH1D x) = smooth x sumw2 (ETH1D x) = sumw2 x instance ITArrayD (Exist TH1D) where instance ITObject (Exist TH1D) where draw (ETH1D x) = draw x findObject (ETH1D x) = findObject x getName (ETH1D x) = getName x isA (ETH1D x) = isA x paint (ETH1D x) = paint x printObj (ETH1D x) = printObj x saveAs (ETH1D x) = saveAs x write (ETH1D x) = write x instance ITAttLine (Exist TH1D) where getLineColor (ETH1D x) = getLineColor x getLineStyle (ETH1D x) = getLineStyle x getLineWidth (ETH1D x) = getLineWidth x resetAttLine (ETH1D x) = resetAttLine x setLineAttributes (ETH1D x) = setLineAttributes x setLineColor (ETH1D x) = setLineColor x setLineStyle (ETH1D x) = setLineStyle x setLineWidth (ETH1D x) = setLineWidth x instance ITAttFill (Exist TH1D) where setFillColor (ETH1D x) = setFillColor x setFillStyle (ETH1D x) = setFillStyle x instance ITAttMarker (Exist TH1D) where getMarkerColor (ETH1D x) = getMarkerColor x getMarkerStyle (ETH1D x) = getMarkerStyle x getMarkerSize (ETH1D x) = getMarkerSize x resetAttMarker (ETH1D x) = resetAttMarker x setMarkerAttributes (ETH1D x) = setMarkerAttributes x setMarkerColor (ETH1D x) = setMarkerColor x setMarkerStyle (ETH1D x) = setMarkerStyle x setMarkerSize (ETH1D x) = setMarkerSize x instance IDeletable (Exist TH1D) where delete (ETH1D x) = delete x instance ITArray (Exist TH1D) where newTH1D :: CString -> CString -> CInt -> CDouble -> CDouble -> IO TH1D newTH1D = xform4 c_th1d_newth1d instance FPtr (Exist TH1D) where type Raw (Exist TH1D) = RawTH1D get_fptr (ETH1D obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH1D (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1D) :: TH1D)