module HROOT.Class.TH1.Implementation where
import HROOT.TypeCast
import HROOT.Class.TH1.RawType
import HROOT.Class.TH1.FFI
import HROOT.Class.TH1.Interface
import HROOT.Class.TH1.Cast
import HROOT.Class.TClass.RawType
import HROOT.Class.TClass.Cast
import HROOT.Class.TClass.Interface
import HROOT.Class.TDirectory.RawType
import HROOT.Class.TDirectory.Cast
import HROOT.Class.TDirectory.Interface
import HROOT.Class.TF1.RawType
import HROOT.Class.TF1.Cast
import HROOT.Class.TF1.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.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 Data.Word
import Foreign.ForeignPtr
import System.IO.Unsafe
instance ITH1 TH1 where
add = xform2 c_th1_add
addBinContent = xform2 c_th1_addbincontent
chi2Test = xform3 c_th1_chi2test
computeIntegral = xform0 c_th1_computeintegral
directoryAutoAdd = xform1 c_th1_directoryautoadd
divide = xform5 c_th1_divide
drawCopyTH1 = xform1 c_th1_drawcopyth1
drawNormalized = xform2 c_th1_drawnormalized
drawPanelTH1 = xform0 c_th1_drawpanelth1
bufferEmpty = xform1 c_th1_bufferempty
evalF = xform2 c_th1_evalf
fFT = xform2 c_th1_fft
fill1 = xform1 c_th1_fill1
fill1w = xform2 c_th1_fill1w
fillN1 = xform4 c_th1_filln1
fillRandom = xform2 c_th1_fillrandom
findBin = xform3 c_th1_findbin
findFixBin = xform3 c_th1_findfixbin
findFirstBinAbove = xform2 c_th1_findfirstbinabove
findLastBinAbove = xform2 c_th1_findlastbinabove
fitPanelTH1 = xform0 c_th1_fitpanelth1
getNdivisionA = xform1 c_th1_getndivisiona
getAxisColorA = xform1 c_th1_getaxiscolora
getLabelColorA = xform1 c_th1_getlabelcolora
getLabelFontA = xform1 c_th1_getlabelfonta
getLabelOffsetA = xform1 c_th1_getlabeloffseta
getLabelSizeA = xform1 c_th1_getlabelsizea
getTitleFontA = xform1 c_th1_gettitlefonta
getTitleOffsetA = xform1 c_th1_gettitleoffseta
getTitleSizeA = xform1 c_th1_gettitlesizea
getTickLengthA = xform1 c_th1_getticklengtha
getBarOffset = xform0 c_th1_getbaroffset
getBarWidth = xform0 c_th1_getbarwidth
getContour = xform1 c_th1_getcontour
getContourLevel = xform1 c_th1_getcontourlevel
getContourLevelPad = xform1 c_th1_getcontourlevelpad
getBin = xform3 c_th1_getbin
getBinCenter = xform1 c_th1_getbincenter
getBinContent1 = xform1 c_th1_getbincontent1
getBinContent2 = xform2 c_th1_getbincontent2
getBinContent3 = xform3 c_th1_getbincontent3
getBinError1 = xform1 c_th1_getbinerror1
getBinError2 = xform2 c_th1_getbinerror2
getBinError3 = xform3 c_th1_getbinerror3
getBinLowEdge = xform1 c_th1_getbinlowedge
getBinWidth = xform1 c_th1_getbinwidth
getCellContent = xform2 c_th1_getcellcontent
getCellError = xform2 c_th1_getcellerror
getEntries = xform0 c_th1_getentries
getEffectiveEntries = xform0 c_th1_geteffectiveentries
getFunction = xform1 c_th1_getfunction
getDimension = xform0 c_th1_getdimension
getKurtosis = xform1 c_th1_getkurtosis
getLowEdge = xform1 c_th1_getlowedge
getMaximumTH1 = xform1 c_th1_getmaximumth1
getMaximumBin = xform0 c_th1_getmaximumbin
getMaximumStored = xform0 c_th1_getmaximumstored
getMinimumTH1 = xform1 c_th1_getminimumth1
getMinimumBin = xform0 c_th1_getminimumbin
getMinimumStored = xform0 c_th1_getminimumstored
getMean = xform1 c_th1_getmean
getMeanError = xform1 c_th1_getmeanerror
getNbinsX = xform0 c_th1_getnbinsx
getNbinsY = xform0 c_th1_getnbinsy
getNbinsZ = xform0 c_th1_getnbinsz
getQuantilesTH1 = xform3 c_th1_getquantilesth1
getRandom = xform0 c_th1_getrandom
getStats = xform1 c_th1_getstats
getSumOfWeights = xform0 c_th1_getsumofweights
getSumw2 = xform0 c_th1_getsumw2
getSumw2N = xform0 c_th1_getsumw2n
getRMS = xform1 c_th1_getrms
getRMSError = xform1 c_th1_getrmserror
getSkewness = xform1 c_th1_getskewness
integral1 = xform3 c_th1_integral1
interpolate1 = xform1 c_th1_interpolate1
interpolate2 = xform2 c_th1_interpolate2
interpolate3 = xform3 c_th1_interpolate3
kolmogorovTest = xform2 c_th1_kolmogorovtest
labelsDeflate = xform1 c_th1_labelsdeflate
labelsInflate = xform1 c_th1_labelsinflate
labelsOption = xform2 c_th1_labelsoption
multiflyF = xform2 c_th1_multiflyf
multiply = xform5 c_th1_multiply
putStats = xform1 c_th1_putstats
rebin = xform3 c_th1_rebin
rebinAxis = xform2 c_th1_rebinaxis
rebuild = xform1 c_th1_rebuild
reset = xform1 c_th1_reset
resetStats = xform0 c_th1_resetstats
scale = xform2 c_th1_scale
setAxisColorA = xform2 c_th1_setaxiscolora
setAxisRange = xform3 c_th1_setaxisrange
setBarOffset = xform1 c_th1_setbaroffset
setBarWidth = xform1 c_th1_setbarwidth
setBinContent1 = xform2 c_th1_setbincontent1
setBinContent2 = xform3 c_th1_setbincontent2
setBinContent3 = xform4 c_th1_setbincontent3
setBinError1 = xform2 c_th1_setbinerror1
setBinError2 = xform3 c_th1_setbinerror2
setBinError3 = xform4 c_th1_setbinerror3
setBins1 = xform2 c_th1_setbins1
setBins2 = xform4 c_th1_setbins2
setBins3 = xform6 c_th1_setbins3
setBinsLength = xform1 c_th1_setbinslength
setBuffer = xform2 c_th1_setbuffer
setCellContent = xform3 c_th1_setcellcontent
setContent = xform1 c_th1_setcontent
setContour = xform2 c_th1_setcontour
setContourLevel = xform2 c_th1_setcontourlevel
setDirectory = xform1 c_th1_setdirectory
setEntries = xform1 c_th1_setentries
setError = xform1 c_th1_seterror
setLabelColorA = xform2 c_th1_setlabelcolora
setLabelSizeA = xform2 c_th1_setlabelsizea
setLabelFontA = xform2 c_th1_setlabelfonta
setLabelOffsetA = xform2 c_th1_setlabeloffseta
setMaximum = xform1 c_th1_setmaximum
setMinimum = xform1 c_th1_setminimum
setNormFactor = xform1 c_th1_setnormfactor
setStats = xform1 c_th1_setstats
setOption = xform1 c_th1_setoption
setXTitle = xform1 c_th1_setxtitle
setYTitle = xform1 c_th1_setytitle
setZTitle = xform1 c_th1_setztitle
showBackground = xform2 c_th1_showbackground
showPeaks = xform3 c_th1_showpeaks
smooth = xform2 c_th1_smooth
sumw2 = xform0 c_th1_sumw2
instance ITNamed TH1 where
setName = xform1 c_th1_setname
setNameTitle = xform2 c_th1_setnametitle
setTitle = xform1 c_th1_settitle
instance ITAttLine TH1 where
getLineColor = xform0 c_th1_getlinecolor
getLineStyle = xform0 c_th1_getlinestyle
getLineWidth = xform0 c_th1_getlinewidth
resetAttLine = xform1 c_th1_resetattline
setLineAttributes = xform0 c_th1_setlineattributes
setLineColor = xform1 c_th1_setlinecolor
setLineStyle = xform1 c_th1_setlinestyle
setLineWidth = xform1 c_th1_setlinewidth
instance ITAttFill TH1 where
setFillColor = xform1 c_th1_setfillcolor
setFillStyle = xform1 c_th1_setfillstyle
instance ITAttMarker TH1 where
getMarkerColor = xform0 c_th1_getmarkercolor
getMarkerStyle = xform0 c_th1_getmarkerstyle
getMarkerSize = xform0 c_th1_getmarkersize
resetAttMarker = xform1 c_th1_resetattmarker
setMarkerAttributes = xform0 c_th1_setmarkerattributes
setMarkerColor = xform1 c_th1_setmarkercolor
setMarkerStyle = xform1 c_th1_setmarkerstyle
setMarkerSize = xform1 c_th1_setmarkersize
instance ITObject TH1 where
draw = xform1 c_th1_draw
findObject = xform1 c_th1_findobject
getName = xform0 c_th1_getname
isA = xform0 c_th1_isa
isFolder = xform0 c_th1_isfolder
isEqual = xform1 c_th1_isequal
isSortable = xform0 c_th1_issortable
paint = xform1 c_th1_paint
printObj = xform1 c_th1_printobj
recursiveRemove = xform1 c_th1_recursiveremove
saveAs = xform2 c_th1_saveas
useCurrentStyle = xform0 c_th1_usecurrentstyle
write = xform3 c_th1_write
instance IDeletable TH1 where
delete = xform0 c_th1_delete
instance ITH1 (Exist TH1) where
add (ETH1 x) = add x
addBinContent (ETH1 x) = addBinContent x
chi2Test (ETH1 x) = chi2Test x
computeIntegral (ETH1 x) = computeIntegral x
directoryAutoAdd (ETH1 x) = directoryAutoAdd x
divide (ETH1 x) = divide x
drawCopyTH1 (ETH1 x) a1 = return . ETH1 =<< drawCopyTH1 x a1
drawNormalized (ETH1 x) = drawNormalized x
drawPanelTH1 (ETH1 x) = drawPanelTH1 x
bufferEmpty (ETH1 x) = bufferEmpty x
evalF (ETH1 x) = evalF x
fFT (ETH1 x) = fFT x
fill1 (ETH1 x) = fill1 x
fill1w (ETH1 x) = fill1w x
fillN1 (ETH1 x) = fillN1 x
fillRandom (ETH1 x) = fillRandom x
findBin (ETH1 x) = findBin x
findFixBin (ETH1 x) = findFixBin x
findFirstBinAbove (ETH1 x) = findFirstBinAbove x
findLastBinAbove (ETH1 x) = findLastBinAbove x
fitPanelTH1 (ETH1 x) = fitPanelTH1 x
getNdivisionA (ETH1 x) = getNdivisionA x
getAxisColorA (ETH1 x) = getAxisColorA x
getLabelColorA (ETH1 x) = getLabelColorA x
getLabelFontA (ETH1 x) = getLabelFontA x
getLabelOffsetA (ETH1 x) = getLabelOffsetA x
getLabelSizeA (ETH1 x) = getLabelSizeA x
getTitleFontA (ETH1 x) = getTitleFontA x
getTitleOffsetA (ETH1 x) = getTitleOffsetA x
getTitleSizeA (ETH1 x) = getTitleSizeA x
getTickLengthA (ETH1 x) = getTickLengthA x
getBarOffset (ETH1 x) = getBarOffset x
getBarWidth (ETH1 x) = getBarWidth x
getContour (ETH1 x) = getContour x
getContourLevel (ETH1 x) = getContourLevel x
getContourLevelPad (ETH1 x) = getContourLevelPad x
getBin (ETH1 x) = getBin x
getBinCenter (ETH1 x) = getBinCenter x
getBinContent1 (ETH1 x) = getBinContent1 x
getBinContent2 (ETH1 x) = getBinContent2 x
getBinContent3 (ETH1 x) = getBinContent3 x
getBinError1 (ETH1 x) = getBinError1 x
getBinError2 (ETH1 x) = getBinError2 x
getBinError3 (ETH1 x) = getBinError3 x
getBinLowEdge (ETH1 x) = getBinLowEdge x
getBinWidth (ETH1 x) = getBinWidth x
getCellContent (ETH1 x) = getCellContent x
getCellError (ETH1 x) = getCellError x
getEntries (ETH1 x) = getEntries x
getEffectiveEntries (ETH1 x) = getEffectiveEntries x
getFunction (ETH1 x) = getFunction x
getDimension (ETH1 x) = getDimension x
getKurtosis (ETH1 x) = getKurtosis x
getLowEdge (ETH1 x) = getLowEdge x
getMaximumTH1 (ETH1 x) = getMaximumTH1 x
getMaximumBin (ETH1 x) = getMaximumBin x
getMaximumStored (ETH1 x) = getMaximumStored x
getMinimumTH1 (ETH1 x) = getMinimumTH1 x
getMinimumBin (ETH1 x) = getMinimumBin x
getMinimumStored (ETH1 x) = getMinimumStored x
getMean (ETH1 x) = getMean x
getMeanError (ETH1 x) = getMeanError x
getNbinsX (ETH1 x) = getNbinsX x
getNbinsY (ETH1 x) = getNbinsY x
getNbinsZ (ETH1 x) = getNbinsZ x
getQuantilesTH1 (ETH1 x) = getQuantilesTH1 x
getRandom (ETH1 x) = getRandom x
getStats (ETH1 x) = getStats x
getSumOfWeights (ETH1 x) = getSumOfWeights x
getSumw2 (ETH1 x) = getSumw2 x
getSumw2N (ETH1 x) = getSumw2N x
getRMS (ETH1 x) = getRMS x
getRMSError (ETH1 x) = getRMSError x
getSkewness (ETH1 x) = getSkewness x
integral1 (ETH1 x) = integral1 x
interpolate1 (ETH1 x) = interpolate1 x
interpolate2 (ETH1 x) = interpolate2 x
interpolate3 (ETH1 x) = interpolate3 x
kolmogorovTest (ETH1 x) = kolmogorovTest x
labelsDeflate (ETH1 x) = labelsDeflate x
labelsInflate (ETH1 x) = labelsInflate x
labelsOption (ETH1 x) = labelsOption x
multiflyF (ETH1 x) = multiflyF x
multiply (ETH1 x) = multiply x
putStats (ETH1 x) = putStats x
rebin (ETH1 x) = rebin x
rebinAxis (ETH1 x) = rebinAxis x
rebuild (ETH1 x) = rebuild x
reset (ETH1 x) = reset x
resetStats (ETH1 x) = resetStats x
scale (ETH1 x) = scale x
setAxisColorA (ETH1 x) = setAxisColorA x
setAxisRange (ETH1 x) = setAxisRange x
setBarOffset (ETH1 x) = setBarOffset x
setBarWidth (ETH1 x) = setBarWidth x
setBinContent1 (ETH1 x) = setBinContent1 x
setBinContent2 (ETH1 x) = setBinContent2 x
setBinContent3 (ETH1 x) = setBinContent3 x
setBinError1 (ETH1 x) = setBinError1 x
setBinError2 (ETH1 x) = setBinError2 x
setBinError3 (ETH1 x) = setBinError3 x
setBins1 (ETH1 x) = setBins1 x
setBins2 (ETH1 x) = setBins2 x
setBins3 (ETH1 x) = setBins3 x
setBinsLength (ETH1 x) = setBinsLength x
setBuffer (ETH1 x) = setBuffer x
setCellContent (ETH1 x) = setCellContent x
setContent (ETH1 x) = setContent x
setContour (ETH1 x) = setContour x
setContourLevel (ETH1 x) = setContourLevel x
setDirectory (ETH1 x) = setDirectory x
setEntries (ETH1 x) = setEntries x
setError (ETH1 x) = setError x
setLabelColorA (ETH1 x) = setLabelColorA x
setLabelSizeA (ETH1 x) = setLabelSizeA x
setLabelFontA (ETH1 x) = setLabelFontA x
setLabelOffsetA (ETH1 x) = setLabelOffsetA x
setMaximum (ETH1 x) = setMaximum x
setMinimum (ETH1 x) = setMinimum x
setNormFactor (ETH1 x) = setNormFactor x
setStats (ETH1 x) = setStats x
setOption (ETH1 x) = setOption x
setXTitle (ETH1 x) = setXTitle x
setYTitle (ETH1 x) = setYTitle x
setZTitle (ETH1 x) = setZTitle x
showBackground (ETH1 x) = showBackground x
showPeaks (ETH1 x) = showPeaks x
smooth (ETH1 x) = smooth x
sumw2 (ETH1 x) = sumw2 x
instance ITNamed (Exist TH1) where
setName (ETH1 x) = setName x
setNameTitle (ETH1 x) = setNameTitle x
setTitle (ETH1 x) = setTitle x
instance ITAttLine (Exist TH1) where
getLineColor (ETH1 x) = getLineColor x
getLineStyle (ETH1 x) = getLineStyle x
getLineWidth (ETH1 x) = getLineWidth x
resetAttLine (ETH1 x) = resetAttLine x
setLineAttributes (ETH1 x) = setLineAttributes x
setLineColor (ETH1 x) = setLineColor x
setLineStyle (ETH1 x) = setLineStyle x
setLineWidth (ETH1 x) = setLineWidth x
instance ITAttFill (Exist TH1) where
setFillColor (ETH1 x) = setFillColor x
setFillStyle (ETH1 x) = setFillStyle x
instance ITAttMarker (Exist TH1) where
getMarkerColor (ETH1 x) = getMarkerColor x
getMarkerStyle (ETH1 x) = getMarkerStyle x
getMarkerSize (ETH1 x) = getMarkerSize x
resetAttMarker (ETH1 x) = resetAttMarker x
setMarkerAttributes (ETH1 x) = setMarkerAttributes x
setMarkerColor (ETH1 x) = setMarkerColor x
setMarkerStyle (ETH1 x) = setMarkerStyle x
setMarkerSize (ETH1 x) = setMarkerSize x
instance ITObject (Exist TH1) where
draw (ETH1 x) = draw x
findObject (ETH1 x) = findObject x
getName (ETH1 x) = getName x
isA (ETH1 x) = isA x
isFolder (ETH1 x) = isFolder x
isEqual (ETH1 x) = isEqual x
isSortable (ETH1 x) = isSortable x
paint (ETH1 x) = paint x
printObj (ETH1 x) = printObj x
recursiveRemove (ETH1 x) = recursiveRemove x
saveAs (ETH1 x) = saveAs x
useCurrentStyle (ETH1 x) = useCurrentStyle x
write (ETH1 x) = write x
instance IDeletable (Exist TH1) where
delete (ETH1 x) = delete x
tH1GetAsymmetry :: TH1 -> TH1 -> Double -> Double -> IO TH1
tH1GetAsymmetry = xform3 c_th1_th1getasymmetry
tH1GetBufferLength :: TH1 -> IO Int
tH1GetBufferLength = xform0 c_th1_th1getbufferlength
tH1GetBufferSize :: TH1 -> IO Int
tH1GetBufferSize = xform0 c_th1_th1getbuffersize
tH1GetDirectory :: TH1 -> IO TDirectory
tH1GetDirectory = xform0 c_th1_th1getdirectory
tH1GetXaxis :: TH1 -> IO TAxis
tH1GetXaxis = xform0 c_th1_th1getxaxis
tH1GetYaxis :: TH1 -> IO TAxis
tH1GetYaxis = xform0 c_th1_th1getyaxis
tH1GetZaxis :: TH1 -> IO TAxis
tH1GetZaxis = xform0 c_th1_th1getzaxis
tH1IsBinOverflow :: TH1 -> Int -> IO Int
tH1IsBinOverflow = xform1 c_th1_th1isbinoverflow
tH1IsBinUnderflow :: TH1 -> Int -> IO Int
tH1IsBinUnderflow = xform1 c_th1_th1isbinunderflow
tH1UseCurrentStyle :: TH1 -> IO ()
tH1UseCurrentStyle = xform0 c_th1_th1usecurrentstyle
instance FPtr (Exist TH1) where
type Raw (Exist TH1) = RawTH1
get_fptr (ETH1 obj) = castForeignPtr (get_fptr obj)
cast_fptr_to_obj fptr = ETH1 (cast_fptr_to_obj (fptr :: ForeignPtr RawTH1) :: TH1)