{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Hist.TH1F.Implementation where import FFICXX.Runtime.Cast import HROOT.Hist.TH1F.RawType import HROOT.Hist.TH1F.FFI import HROOT.Hist.TH1F.Interface import HROOT.Hist.TH1F.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 ITH1F TH1F where instance ITH1 TH1F where add = xform2 c_th1f_add addBinContent = xform2 c_th1f_addbincontent chi2Test = xform3 c_th1f_chi2test computeIntegral = xform0 c_th1f_computeintegral directoryAutoAdd = xform1 c_th1f_directoryautoadd divide = xform5 c_th1f_divide drawCopyTH1 = xform1 c_th1f_drawcopyth1 drawNormalized = xform2 c_th1f_drawnormalized drawPanelTH1 = xform0 c_th1f_drawpanelth1 bufferEmpty = xform1 c_th1f_bufferempty evalF = xform2 c_th1f_evalf fFT = xform2 c_th1f_fft fill1 = xform1 c_th1f_fill1 fill1w = xform2 c_th1f_fill1w fillN1 = xform4 c_th1f_filln1 fillRandom = xform2 c_th1f_fillrandom findBin = xform3 c_th1f_findbin findFixBin = xform3 c_th1f_findfixbin findFirstBinAbove = xform2 c_th1f_findfirstbinabove findLastBinAbove = xform2 c_th1f_findlastbinabove fitPanelTH1 = xform0 c_th1f_fitpanelth1 getNdivisionA = xform1 c_th1f_getndivisiona getAxisColorA = xform1 c_th1f_getaxiscolora getLabelColorA = xform1 c_th1f_getlabelcolora getLabelFontA = xform1 c_th1f_getlabelfonta getLabelOffsetA = xform1 c_th1f_getlabeloffseta getLabelSizeA = xform1 c_th1f_getlabelsizea getTitleFontA = xform1 c_th1f_gettitlefonta getTitleOffsetA = xform1 c_th1f_gettitleoffseta getTitleSizeA = xform1 c_th1f_gettitlesizea getTickLengthA = xform1 c_th1f_getticklengtha getBarOffset = xform0 c_th1f_getbaroffset getBarWidth = xform0 c_th1f_getbarwidth getContour = xform1 c_th1f_getcontour getContourLevel = xform1 c_th1f_getcontourlevel getContourLevelPad = xform1 c_th1f_getcontourlevelpad getBin = xform3 c_th1f_getbin getBinCenter = xform1 c_th1f_getbincenter getBinContent1 = xform1 c_th1f_getbincontent1 getBinContent2 = xform2 c_th1f_getbincontent2 getBinContent3 = xform3 c_th1f_getbincontent3 getBinError1 = xform1 c_th1f_getbinerror1 getBinError2 = xform2 c_th1f_getbinerror2 getBinError3 = xform3 c_th1f_getbinerror3 getBinLowEdge = xform1 c_th1f_getbinlowedge getBinWidth = xform1 c_th1f_getbinwidth getCellContent = xform2 c_th1f_getcellcontent getCellError = xform2 c_th1f_getcellerror getEntries = xform0 c_th1f_getentries getEffectiveEntries = xform0 c_th1f_geteffectiveentries getFunction = xform1 c_th1f_getfunction getDimension = xform0 c_th1f_getdimension getKurtosis = xform1 c_th1f_getkurtosis getLowEdge = xform1 c_th1f_getlowedge getMaximumTH1 = xform1 c_th1f_getmaximumth1 getMaximumBin = xform0 c_th1f_getmaximumbin getMaximumStored = xform0 c_th1f_getmaximumstored getMinimumTH1 = xform1 c_th1f_getminimumth1 getMinimumBin = xform0 c_th1f_getminimumbin getMinimumStored = xform0 c_th1f_getminimumstored getMean = xform1 c_th1f_getmean getMeanError = xform1 c_th1f_getmeanerror getNbinsX = xform0 c_th1f_getnbinsx getNbinsY = xform0 c_th1f_getnbinsy getNbinsZ = xform0 c_th1f_getnbinsz getQuantilesTH1 = xform3 c_th1f_getquantilesth1 getRandom = xform0 c_th1f_getrandom getStats = xform1 c_th1f_getstats getSumOfWeights = xform0 c_th1f_getsumofweights getSumw2 = xform0 c_th1f_getsumw2 getSumw2N = xform0 c_th1f_getsumw2n getRMS = xform1 c_th1f_getrms getRMSError = xform1 c_th1f_getrmserror getSkewness = xform1 c_th1f_getskewness integral1 = xform3 c_th1f_integral1 interpolate1 = xform1 c_th1f_interpolate1 interpolate2 = xform2 c_th1f_interpolate2 interpolate3 = xform3 c_th1f_interpolate3 kolmogorovTest = xform2 c_th1f_kolmogorovtest labelsDeflate = xform1 c_th1f_labelsdeflate labelsInflate = xform1 c_th1f_labelsinflate labelsOption = xform2 c_th1f_labelsoption multiflyF = xform2 c_th1f_multiflyf multiply = xform5 c_th1f_multiply putStats = xform1 c_th1f_putstats rebin = xform3 c_th1f_rebin rebinAxis = xform2 c_th1f_rebinaxis rebuild = xform1 c_th1f_rebuild recursiveRemove = xform1 c_th1f_recursiveremove reset = xform1 c_th1f_reset resetStats = xform0 c_th1f_resetstats scale = xform2 c_th1f_scale setAxisColorA = xform2 c_th1f_setaxiscolora setAxisRange = xform3 c_th1f_setaxisrange setBarOffset = xform1 c_th1f_setbaroffset setBarWidth = xform1 c_th1f_setbarwidth setBinContent1 = xform2 c_th1f_setbincontent1 setBinContent2 = xform3 c_th1f_setbincontent2 setBinContent3 = xform4 c_th1f_setbincontent3 setBinError1 = xform2 c_th1f_setbinerror1 setBinError2 = xform3 c_th1f_setbinerror2 setBinError3 = xform4 c_th1f_setbinerror3 setBins1 = xform2 c_th1f_setbins1 setBins2 = xform4 c_th1f_setbins2 setBins3 = xform6 c_th1f_setbins3 setBinsLength = xform1 c_th1f_setbinslength setBuffer = xform2 c_th1f_setbuffer setCellContent = xform3 c_th1f_setcellcontent setContent = xform1 c_th1f_setcontent setContour = xform2 c_th1f_setcontour setContourLevel = xform2 c_th1f_setcontourlevel setDirectory = xform1 c_th1f_setdirectory setEntries = xform1 c_th1f_setentries setError = xform1 c_th1f_seterror setLabelColorA = xform2 c_th1f_setlabelcolora setLabelSizeA = xform2 c_th1f_setlabelsizea setLabelFontA = xform2 c_th1f_setlabelfonta setLabelOffsetA = xform2 c_th1f_setlabeloffseta setMaximum = xform1 c_th1f_setmaximum setMinimum = xform1 c_th1f_setminimum setNormFactor = xform1 c_th1f_setnormfactor setStats = xform1 c_th1f_setstats setOption = xform1 c_th1f_setoption setXTitle = xform1 c_th1f_setxtitle setYTitle = xform1 c_th1f_setytitle setZTitle = xform1 c_th1f_setztitle showBackground = xform2 c_th1f_showbackground showPeaks = xform3 c_th1f_showpeaks smooth = xform2 c_th1f_smooth sumw2 = xform0 c_th1f_sumw2 instance ITArrayF TH1F where instance ITObject TH1F where draw = xform1 c_th1f_draw findObject = xform1 c_th1f_findobject getName = xform0 c_th1f_getname isA = xform0 c_th1f_isa paint = xform1 c_th1f_paint printObj = xform1 c_th1f_printobj saveAs = xform2 c_th1f_saveas write = xform3 c_th1f_write instance ITAttLine TH1F where getLineColor = xform0 c_th1f_getlinecolor getLineStyle = xform0 c_th1f_getlinestyle getLineWidth = xform0 c_th1f_getlinewidth resetAttLine = xform1 c_th1f_resetattline setLineAttributes = xform0 c_th1f_setlineattributes setLineColor = xform1 c_th1f_setlinecolor setLineStyle = xform1 c_th1f_setlinestyle setLineWidth = xform1 c_th1f_setlinewidth instance ITAttFill TH1F where setFillColor = xform1 c_th1f_setfillcolor setFillStyle = xform1 c_th1f_setfillstyle instance ITAttMarker TH1F where getMarkerColor = xform0 c_th1f_getmarkercolor getMarkerStyle = xform0 c_th1f_getmarkerstyle getMarkerSize = xform0 c_th1f_getmarkersize resetAttMarker = xform1 c_th1f_resetattmarker setMarkerAttributes = xform0 c_th1f_setmarkerattributes setMarkerColor = xform1 c_th1f_setmarkercolor setMarkerStyle = xform1 c_th1f_setmarkerstyle setMarkerSize = xform1 c_th1f_setmarkersize instance IDeletable TH1F where delete = xform0 c_th1f_delete instance ITArray TH1F where instance ITH1F (Exist TH1F) where instance ITH1 (Exist TH1F) where add (ETH1F x) = add x addBinContent (ETH1F x) = addBinContent x chi2Test (ETH1F x) = chi2Test x computeIntegral (ETH1F x) = computeIntegral x directoryAutoAdd (ETH1F x) = directoryAutoAdd x divide (ETH1F x) = divide x drawCopyTH1 (ETH1F x) a1 = return . ETH1F =<< drawCopyTH1 x a1 drawNormalized (ETH1F x) = drawNormalized x drawPanelTH1 (ETH1F x) = drawPanelTH1 x bufferEmpty (ETH1F x) = bufferEmpty x evalF (ETH1F x) = evalF x fFT (ETH1F x) = fFT x fill1 (ETH1F x) = fill1 x fill1w (ETH1F x) = fill1w x fillN1 (ETH1F x) = fillN1 x fillRandom (ETH1F x) = fillRandom x findBin (ETH1F x) = findBin x findFixBin (ETH1F x) = findFixBin x findFirstBinAbove (ETH1F x) = findFirstBinAbove x findLastBinAbove (ETH1F x) = findLastBinAbove x fitPanelTH1 (ETH1F x) = fitPanelTH1 x getNdivisionA (ETH1F x) = getNdivisionA x getAxisColorA (ETH1F x) = getAxisColorA x getLabelColorA (ETH1F x) = getLabelColorA x getLabelFontA (ETH1F x) = getLabelFontA x getLabelOffsetA (ETH1F x) = getLabelOffsetA x getLabelSizeA (ETH1F x) = getLabelSizeA x getTitleFontA (ETH1F x) = getTitleFontA x getTitleOffsetA (ETH1F x) = getTitleOffsetA x getTitleSizeA (ETH1F x) = getTitleSizeA x getTickLengthA (ETH1F x) = getTickLengthA x getBarOffset (ETH1F x) = getBarOffset x getBarWidth (ETH1F x) = getBarWidth x getContour (ETH1F x) = getContour x getContourLevel (ETH1F x) = getContourLevel x getContourLevelPad (ETH1F x) = getContourLevelPad x getBin (ETH1F x) = getBin x getBinCenter (ETH1F x) = getBinCenter x getBinContent1 (ETH1F x) = getBinContent1 x getBinContent2 (ETH1F x) = getBinContent2 x getBinContent3 (ETH1F x) = getBinContent3 x getBinError1 (ETH1F x) = getBinError1 x getBinError2 (ETH1F x) = getBinError2 x getBinError3 (ETH1F x) = getBinError3 x getBinLowEdge (ETH1F x) = getBinLowEdge x getBinWidth (ETH1F x) = getBinWidth x getCellContent (ETH1F x) = getCellContent x getCellError (ETH1F x) = getCellError x getEntries (ETH1F x) = getEntries x getEffectiveEntries (ETH1F x) = getEffectiveEntries x getFunction (ETH1F x) = getFunction x getDimension (ETH1F x) = getDimension x getKurtosis (ETH1F x) = getKurtosis x getLowEdge (ETH1F x) = getLowEdge x getMaximumTH1 (ETH1F x) = getMaximumTH1 x getMaximumBin (ETH1F x) = getMaximumBin x getMaximumStored (ETH1F x) = getMaximumStored x getMinimumTH1 (ETH1F x) = getMinimumTH1 x getMinimumBin (ETH1F x) = getMinimumBin x getMinimumStored (ETH1F x) = getMinimumStored x getMean (ETH1F x) = getMean x getMeanError (ETH1F x) = getMeanError x getNbinsX (ETH1F x) = getNbinsX x getNbinsY (ETH1F x) = getNbinsY x getNbinsZ (ETH1F x) = getNbinsZ x getQuantilesTH1 (ETH1F x) = getQuantilesTH1 x getRandom (ETH1F x) = getRandom x getStats (ETH1F x) = getStats x getSumOfWeights (ETH1F x) = getSumOfWeights x getSumw2 (ETH1F x) = getSumw2 x getSumw2N (ETH1F x) = getSumw2N x getRMS (ETH1F x) = getRMS x getRMSError (ETH1F x) = getRMSError x getSkewness (ETH1F x) = getSkewness x integral1 (ETH1F x) = integral1 x interpolate1 (ETH1F x) = interpolate1 x interpolate2 (ETH1F x) = interpolate2 x interpolate3 (ETH1F x) = interpolate3 x kolmogorovTest (ETH1F x) = kolmogorovTest x labelsDeflate (ETH1F x) = labelsDeflate x labelsInflate (ETH1F x) = labelsInflate x labelsOption (ETH1F x) = labelsOption x multiflyF (ETH1F x) = multiflyF x multiply (ETH1F x) = multiply x putStats (ETH1F x) = putStats x rebin (ETH1F x) = rebin x rebinAxis (ETH1F x) = rebinAxis x rebuild (ETH1F x) = rebuild x recursiveRemove (ETH1F x) = recursiveRemove x reset (ETH1F x) = reset x resetStats (ETH1F x) = resetStats x scale (ETH1F x) = scale x setAxisColorA (ETH1F x) = setAxisColorA x setAxisRange (ETH1F x) = setAxisRange x setBarOffset (ETH1F x) = setBarOffset x setBarWidth (ETH1F x) = setBarWidth x setBinContent1 (ETH1F x) = setBinContent1 x setBinContent2 (ETH1F x) = setBinContent2 x setBinContent3 (ETH1F x) = setBinContent3 x setBinError1 (ETH1F x) = setBinError1 x setBinError2 (ETH1F x) = setBinError2 x setBinError3 (ETH1F x) = setBinError3 x setBins1 (ETH1F x) = setBins1 x setBins2 (ETH1F x) = setBins2 x setBins3 (ETH1F x) = setBins3 x setBinsLength (ETH1F x) = setBinsLength x setBuffer (ETH1F x) = setBuffer x setCellContent (ETH1F x) = setCellContent x setContent (ETH1F x) = setContent x setContour (ETH1F x) = setContour x setContourLevel (ETH1F x) = setContourLevel x setDirectory (ETH1F x) = setDirectory x setEntries (ETH1F x) = setEntries x setError (ETH1F x) = setError x setLabelColorA (ETH1F x) = setLabelColorA x setLabelSizeA (ETH1F x) = setLabelSizeA x setLabelFontA (ETH1F x) = setLabelFontA x setLabelOffsetA (ETH1F x) = setLabelOffsetA x setMaximum (ETH1F x) = setMaximum x setMinimum (ETH1F x) = setMinimum x setNormFactor (ETH1F x) = setNormFactor x setStats (ETH1F x) = setStats x setOption (ETH1F x) = setOption x setXTitle (ETH1F x) = setXTitle x setYTitle (ETH1F x) = setYTitle x setZTitle (ETH1F x) = setZTitle x showBackground (ETH1F x) = showBackground x showPeaks (ETH1F x) = showPeaks x smooth (ETH1F x) = smooth x sumw2 (ETH1F x) = sumw2 x instance ITArrayF (Exist TH1F) where instance ITObject (Exist TH1F) where draw (ETH1F x) = draw x findObject (ETH1F x) = findObject x getName (ETH1F x) = getName x isA (ETH1F x) = isA x paint (ETH1F x) = paint x printObj (ETH1F x) = printObj x saveAs (ETH1F x) = saveAs x write (ETH1F x) = write x instance ITAttLine (Exist TH1F) where getLineColor (ETH1F x) = getLineColor x getLineStyle (ETH1F x) = getLineStyle x getLineWidth (ETH1F x) = getLineWidth x resetAttLine (ETH1F x) = resetAttLine x setLineAttributes (ETH1F x) = setLineAttributes x setLineColor (ETH1F x) = setLineColor x setLineStyle (ETH1F x) = setLineStyle x setLineWidth (ETH1F x) = setLineWidth x instance ITAttFill (Exist TH1F) where setFillColor (ETH1F x) = setFillColor x setFillStyle (ETH1F x) = setFillStyle x instance ITAttMarker (Exist TH1F) where getMarkerColor (ETH1F x) = getMarkerColor x getMarkerStyle (ETH1F x) = getMarkerStyle x getMarkerSize (ETH1F x) = getMarkerSize x resetAttMarker (ETH1F x) = resetAttMarker x setMarkerAttributes (ETH1F x) = setMarkerAttributes x setMarkerColor (ETH1F x) = setMarkerColor x setMarkerStyle (ETH1F x) = setMarkerStyle x setMarkerSize (ETH1F x) = setMarkerSize x instance IDeletable (Exist TH1F) where delete (ETH1F x) = delete x instance ITArray (Exist TH1F) where newTH1F :: CString -> CString -> CInt -> CDouble -> CDouble -> IO TH1F newTH1F = xform4 c_th1f_newth1f instance FPtr (Exist TH1F) where type Raw (Exist TH1F) = RawTH1F get_fptr (ETH1F obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETH1F (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1F) :: TH1F)