{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH1K.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH1K.RawType import HROOT.Hist.TH1K.FFI import HROOT.Hist.TH1K.Interface import HROOT.Hist.TH1K.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.TArrayF.RawType import HROOT.Core.TArrayF.Cast import HROOT.Core.TArrayF.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 ITH1K TH1K where instance ITH1 TH1K where add = xform2 c_th1k_add addBinContent = xform2 c_th1k_addbincontent chi2Test = xform3 c_th1k_chi2test computeIntegral = xform0 c_th1k_computeintegral directoryAutoAdd = xform1 c_th1k_directoryautoadd divide = xform5 c_th1k_divide drawCopyTH1 = xform1 c_th1k_drawcopyth1 drawNormalized = xform2 c_th1k_drawnormalized drawPanelTH1 = xform0 c_th1k_drawpanelth1 bufferEmpty = xform1 c_th1k_bufferempty evalF = xform2 c_th1k_evalf fFT = xform2 c_th1k_fft fill1 = xform1 c_th1k_fill1 fill1w = xform2 c_th1k_fill1w fillN1 = xform4 c_th1k_filln1 fillRandom = xform2 c_th1k_fillrandom findBin = xform3 c_th1k_findbin findFixBin = xform3 c_th1k_findfixbin findFirstBinAbove = xform2 c_th1k_findfirstbinabove findLastBinAbove = xform2 c_th1k_findlastbinabove fitPanelTH1 = xform0 c_th1k_fitpanelth1 getNdivisionA = xform1 c_th1k_getndivisiona getAxisColorA = xform1 c_th1k_getaxiscolora getLabelColorA = xform1 c_th1k_getlabelcolora getLabelFontA = xform1 c_th1k_getlabelfonta getLabelOffsetA = xform1 c_th1k_getlabeloffseta getLabelSizeA = xform1 c_th1k_getlabelsizea getTitleFontA = xform1 c_th1k_gettitlefonta getTitleOffsetA = xform1 c_th1k_gettitleoffseta getTitleSizeA = xform1 c_th1k_gettitlesizea getTickLengthA = xform1 c_th1k_getticklengtha getBarOffset = xform0 c_th1k_getbaroffset getBarWidth = xform0 c_th1k_getbarwidth getContour = xform1 c_th1k_getcontour getContourLevel = xform1 c_th1k_getcontourlevel getContourLevelPad = xform1 c_th1k_getcontourlevelpad getBin = xform3 c_th1k_getbin getBinCenter = xform1 c_th1k_getbincenter getBinContent1 = xform1 c_th1k_getbincontent1 getBinContent2 = xform2 c_th1k_getbincontent2 getBinContent3 = xform3 c_th1k_getbincontent3 getBinError1 = xform1 c_th1k_getbinerror1 getBinError2 = xform2 c_th1k_getbinerror2 getBinError3 = xform3 c_th1k_getbinerror3 getBinLowEdge = xform1 c_th1k_getbinlowedge getBinWidth = xform1 c_th1k_getbinwidth getCellContent = xform2 c_th1k_getcellcontent getCellError = xform2 c_th1k_getcellerror getEntries = xform0 c_th1k_getentries getEffectiveEntries = xform0 c_th1k_geteffectiveentries getFunction = xform1 c_th1k_getfunction getDimension = xform0 c_th1k_getdimension getKurtosis = xform1 c_th1k_getkurtosis getLowEdge = xform1 c_th1k_getlowedge getMaximumTH1 = xform1 c_th1k_getmaximumth1 getMaximumBin = xform0 c_th1k_getmaximumbin getMaximumStored = xform0 c_th1k_getmaximumstored getMinimumTH1 = xform1 c_th1k_getminimumth1 getMinimumBin = xform0 c_th1k_getminimumbin getMinimumStored = xform0 c_th1k_getminimumstored getMean = xform1 c_th1k_getmean getMeanError = xform1 c_th1k_getmeanerror getNbinsX = xform0 c_th1k_getnbinsx getNbinsY = xform0 c_th1k_getnbinsy getNbinsZ = xform0 c_th1k_getnbinsz getQuantilesTH1 = xform3 c_th1k_getquantilesth1 getRandom = xform0 c_th1k_getrandom getStats = xform1 c_th1k_getstats getSumOfWeights = xform0 c_th1k_getsumofweights getSumw2 = xform0 c_th1k_getsumw2 getSumw2N = xform0 c_th1k_getsumw2n getRMS = xform1 c_th1k_getrms getRMSError = xform1 c_th1k_getrmserror getSkewness = xform1 c_th1k_getskewness integral1 = xform3 c_th1k_integral1 interpolate1 = xform1 c_th1k_interpolate1 interpolate2 = xform2 c_th1k_interpolate2 interpolate3 = xform3 c_th1k_interpolate3 kolmogorovTest = xform2 c_th1k_kolmogorovtest labelsDeflate = xform1 c_th1k_labelsdeflate labelsInflate = xform1 c_th1k_labelsinflate labelsOption = xform2 c_th1k_labelsoption multiflyF = xform2 c_th1k_multiflyf multiply = xform5 c_th1k_multiply putStats = xform1 c_th1k_putstats rebin = xform3 c_th1k_rebin rebinAxis = xform2 c_th1k_rebinaxis rebuild = xform1 c_th1k_rebuild recursiveRemove = xform1 c_th1k_recursiveremove reset = xform1 c_th1k_reset resetStats = xform0 c_th1k_resetstats scale = xform2 c_th1k_scale setAxisColorA = xform2 c_th1k_setaxiscolora setAxisRange = xform3 c_th1k_setaxisrange setBarOffset = xform1 c_th1k_setbaroffset setBarWidth = xform1 c_th1k_setbarwidth setBinContent1 = xform2 c_th1k_setbincontent1 setBinContent2 = xform3 c_th1k_setbincontent2 setBinContent3 = xform4 c_th1k_setbincontent3 setBinError1 = xform2 c_th1k_setbinerror1 setBinError2 = xform3 c_th1k_setbinerror2 setBinError3 = xform4 c_th1k_setbinerror3 setBins1 = xform2 c_th1k_setbins1 setBins2 = xform4 c_th1k_setbins2 setBins3 = xform6 c_th1k_setbins3 setBinsLength = xform1 c_th1k_setbinslength setBuffer = xform2 c_th1k_setbuffer setCellContent = xform3 c_th1k_setcellcontent setContent = xform1 c_th1k_setcontent setContour = xform2 c_th1k_setcontour setContourLevel = xform2 c_th1k_setcontourlevel setDirectory = xform1 c_th1k_setdirectory setEntries = xform1 c_th1k_setentries setError = xform1 c_th1k_seterror setLabelColorA = xform2 c_th1k_setlabelcolora setLabelSizeA = xform2 c_th1k_setlabelsizea setLabelFontA = xform2 c_th1k_setlabelfonta setLabelOffsetA = xform2 c_th1k_setlabeloffseta setMaximum = xform1 c_th1k_setmaximum setMinimum = xform1 c_th1k_setminimum setNormFactor = xform1 c_th1k_setnormfactor setStats = xform1 c_th1k_setstats setOption = xform1 c_th1k_setoption setXTitle = xform1 c_th1k_setxtitle setYTitle = xform1 c_th1k_setytitle setZTitle = xform1 c_th1k_setztitle showBackground = xform2 c_th1k_showbackground showPeaks = xform3 c_th1k_showpeaks smooth = xform2 c_th1k_smooth sumw2 = xform0 c_th1k_sumw2 instance ITArrayF TH1K where instance ITObject TH1K where draw = xform1 c_th1k_draw findObject = xform1 c_th1k_findobject getName = xform0 c_th1k_getname isA = xform0 c_th1k_isa paint = xform1 c_th1k_paint printObj = xform1 c_th1k_printobj saveAs = xform2 c_th1k_saveas write = xform3 c_th1k_write instance ITAttLine TH1K where getLineColor = xform0 c_th1k_getlinecolor getLineStyle = xform0 c_th1k_getlinestyle getLineWidth = xform0 c_th1k_getlinewidth resetAttLine = xform1 c_th1k_resetattline setLineAttributes = xform0 c_th1k_setlineattributes setLineColor = xform1 c_th1k_setlinecolor setLineStyle = xform1 c_th1k_setlinestyle setLineWidth = xform1 c_th1k_setlinewidth instance ITAttFill TH1K where setFillColor = xform1 c_th1k_setfillcolor setFillStyle = xform1 c_th1k_setfillstyle instance ITAttMarker TH1K where getMarkerColor = xform0 c_th1k_getmarkercolor getMarkerStyle = xform0 c_th1k_getmarkerstyle getMarkerSize = xform0 c_th1k_getmarkersize resetAttMarker = xform1 c_th1k_resetattmarker setMarkerAttributes = xform0 c_th1k_setmarkerattributes setMarkerColor = xform1 c_th1k_setmarkercolor setMarkerStyle = xform1 c_th1k_setmarkerstyle setMarkerSize = xform1 c_th1k_setmarkersize instance IDeletable TH1K where delete = xform0 c_th1k_delete instance ITArray TH1K where instance ITH1K (Exist TH1K) where instance ITH1 (Exist TH1K) where add (ETH1K x) = add x addBinContent (ETH1K x) = addBinContent x chi2Test (ETH1K x) = chi2Test x computeIntegral (ETH1K x) = computeIntegral x directoryAutoAdd (ETH1K x) = directoryAutoAdd x divide (ETH1K x) = divide x drawCopyTH1 (ETH1K x) a1 = return . ETH1K =<< drawCopyTH1 x a1 drawNormalized (ETH1K x) = drawNormalized x drawPanelTH1 (ETH1K x) = drawPanelTH1 x bufferEmpty (ETH1K x) = bufferEmpty x evalF (ETH1K x) = evalF x fFT (ETH1K x) = fFT x fill1 (ETH1K x) = fill1 x fill1w (ETH1K x) = fill1w x fillN1 (ETH1K x) = fillN1 x fillRandom (ETH1K x) = fillRandom x findBin (ETH1K x) = findBin x findFixBin (ETH1K x) = findFixBin x findFirstBinAbove (ETH1K x) = findFirstBinAbove x findLastBinAbove (ETH1K x) = findLastBinAbove x fitPanelTH1 (ETH1K x) = fitPanelTH1 x getNdivisionA (ETH1K x) = getNdivisionA x getAxisColorA (ETH1K x) = getAxisColorA x getLabelColorA (ETH1K x) = getLabelColorA x getLabelFontA (ETH1K x) = getLabelFontA x getLabelOffsetA (ETH1K x) = getLabelOffsetA x getLabelSizeA (ETH1K x) = getLabelSizeA x getTitleFontA (ETH1K x) = getTitleFontA x getTitleOffsetA (ETH1K x) = getTitleOffsetA x getTitleSizeA (ETH1K x) = getTitleSizeA x getTickLengthA (ETH1K x) = getTickLengthA x getBarOffset (ETH1K x) = getBarOffset x getBarWidth (ETH1K x) = getBarWidth x getContour (ETH1K x) = getContour x getContourLevel (ETH1K x) = getContourLevel x getContourLevelPad (ETH1K x) = getContourLevelPad x getBin (ETH1K x) = getBin x getBinCenter (ETH1K x) = getBinCenter x getBinContent1 (ETH1K x) = getBinContent1 x getBinContent2 (ETH1K x) = getBinContent2 x getBinContent3 (ETH1K x) = getBinContent3 x getBinError1 (ETH1K x) = getBinError1 x getBinError2 (ETH1K x) = getBinError2 x getBinError3 (ETH1K x) = getBinError3 x getBinLowEdge (ETH1K x) = getBinLowEdge x getBinWidth (ETH1K x) = getBinWidth x getCellContent (ETH1K x) = getCellContent x getCellError (ETH1K x) = getCellError x getEntries (ETH1K x) = getEntries x getEffectiveEntries (ETH1K x) = getEffectiveEntries x getFunction (ETH1K x) = getFunction x getDimension (ETH1K x) = getDimension x getKurtosis (ETH1K x) = getKurtosis x getLowEdge (ETH1K x) = getLowEdge x getMaximumTH1 (ETH1K x) = getMaximumTH1 x getMaximumBin (ETH1K x) = getMaximumBin x getMaximumStored (ETH1K x) = getMaximumStored x getMinimumTH1 (ETH1K x) = getMinimumTH1 x getMinimumBin (ETH1K x) = getMinimumBin x getMinimumStored (ETH1K x) = getMinimumStored x getMean (ETH1K x) = getMean x getMeanError (ETH1K x) = getMeanError x getNbinsX (ETH1K x) = getNbinsX x getNbinsY (ETH1K x) = getNbinsY x getNbinsZ (ETH1K x) = getNbinsZ x getQuantilesTH1 (ETH1K x) = getQuantilesTH1 x getRandom (ETH1K x) = getRandom x getStats (ETH1K x) = getStats x getSumOfWeights (ETH1K x) = getSumOfWeights x getSumw2 (ETH1K x) = getSumw2 x getSumw2N (ETH1K x) = getSumw2N x getRMS (ETH1K x) = getRMS x getRMSError (ETH1K x) = getRMSError x getSkewness (ETH1K x) = getSkewness x integral1 (ETH1K x) = integral1 x interpolate1 (ETH1K x) = interpolate1 x interpolate2 (ETH1K x) = interpolate2 x interpolate3 (ETH1K x) = interpolate3 x kolmogorovTest (ETH1K x) = kolmogorovTest x labelsDeflate (ETH1K x) = labelsDeflate x labelsInflate (ETH1K x) = labelsInflate x labelsOption (ETH1K x) = labelsOption x multiflyF (ETH1K x) = multiflyF x multiply (ETH1K x) = multiply x putStats (ETH1K x) = putStats x rebin (ETH1K x) = rebin x rebinAxis (ETH1K x) = rebinAxis x rebuild (ETH1K x) = rebuild x recursiveRemove (ETH1K x) = recursiveRemove x reset (ETH1K x) = reset x resetStats (ETH1K x) = resetStats x scale (ETH1K x) = scale x setAxisColorA (ETH1K x) = setAxisColorA x setAxisRange (ETH1K x) = setAxisRange x setBarOffset (ETH1K x) = setBarOffset x setBarWidth (ETH1K x) = setBarWidth x setBinContent1 (ETH1K x) = setBinContent1 x setBinContent2 (ETH1K x) = setBinContent2 x setBinContent3 (ETH1K x) = setBinContent3 x setBinError1 (ETH1K x) = setBinError1 x setBinError2 (ETH1K x) = setBinError2 x setBinError3 (ETH1K x) = setBinError3 x setBins1 (ETH1K x) = setBins1 x setBins2 (ETH1K x) = setBins2 x setBins3 (ETH1K x) = setBins3 x setBinsLength (ETH1K x) = setBinsLength x setBuffer (ETH1K x) = setBuffer x setCellContent (ETH1K x) = setCellContent x setContent (ETH1K x) = setContent x setContour (ETH1K x) = setContour x setContourLevel (ETH1K x) = setContourLevel x setDirectory (ETH1K x) = setDirectory x setEntries (ETH1K x) = setEntries x setError (ETH1K x) = setError x setLabelColorA (ETH1K x) = setLabelColorA x setLabelSizeA (ETH1K x) = setLabelSizeA x setLabelFontA (ETH1K x) = setLabelFontA x setLabelOffsetA (ETH1K x) = setLabelOffsetA x setMaximum (ETH1K x) = setMaximum x setMinimum (ETH1K x) = setMinimum x setNormFactor (ETH1K x) = setNormFactor x setStats (ETH1K x) = setStats x setOption (ETH1K x) = setOption x setXTitle (ETH1K x) = setXTitle x setYTitle (ETH1K x) = setYTitle x setZTitle (ETH1K x) = setZTitle x showBackground (ETH1K x) = showBackground x showPeaks (ETH1K x) = showPeaks x smooth (ETH1K x) = smooth x sumw2 (ETH1K x) = sumw2 x instance ITArrayF (Exist TH1K) where instance ITObject (Exist TH1K) where draw (ETH1K x) = draw x findObject (ETH1K x) = findObject x getName (ETH1K x) = getName x isA (ETH1K x) = isA x paint (ETH1K x) = paint x printObj (ETH1K x) = printObj x saveAs (ETH1K x) = saveAs x write (ETH1K x) = write x instance ITAttLine (Exist TH1K) where getLineColor (ETH1K x) = getLineColor x getLineStyle (ETH1K x) = getLineStyle x getLineWidth (ETH1K x) = getLineWidth x resetAttLine (ETH1K x) = resetAttLine x setLineAttributes (ETH1K x) = setLineAttributes x setLineColor (ETH1K x) = setLineColor x setLineStyle (ETH1K x) = setLineStyle x setLineWidth (ETH1K x) = setLineWidth x instance ITAttFill (Exist TH1K) where setFillColor (ETH1K x) = setFillColor x setFillStyle (ETH1K x) = setFillStyle x instance ITAttMarker (Exist TH1K) where getMarkerColor (ETH1K x) = getMarkerColor x getMarkerStyle (ETH1K x) = getMarkerStyle x getMarkerSize (ETH1K x) = getMarkerSize x resetAttMarker (ETH1K x) = resetAttMarker x setMarkerAttributes (ETH1K x) = setMarkerAttributes x setMarkerColor (ETH1K x) = setMarkerColor x setMarkerStyle (ETH1K x) = setMarkerStyle x setMarkerSize (ETH1K x) = setMarkerSize x instance IDeletable (Exist TH1K) where delete (ETH1K x) = delete x instance ITArray (Exist TH1K) where instance FPtr (Exist TH1K) where type Raw (Exist TH1K) = RawTH1K get_fptr (ETH1K obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH1K (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1K) :: TH1K)