{-# LINE 1 "src/HROOT/Hist/TH3S/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/HROOT/Hist/TH3S/FFI.hsc" #-}

-- module HROOT.Class.FFI where

module HROOT.Hist.TH3S.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TH3S.RawType
import HROOT.Hist.TH1D.RawType
import HROOT.Hist.TH1.RawType
import HROOT.Hist.TH3.RawType
import HROOT.Hist.TF1.RawType
import HROOT.Core.TDirectory.RawType
import HROOT.Core.TArrayD.RawType
import HROOT.Hist.TAxis.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 27 "src/HROOT/Hist/TH3S/FFI.hsc" #-}

foreign import ccall "HROOTHistTH3S.h TH3S_fill3" c_th3s_fill3 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_fill3w" c_th3s_fill3w 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_FitSlicesZ" c_th3s_fitslicesz 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_getCorrelationFactor3" c_th3s_getcorrelationfactor3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getCovariance3" c_th3s_getcovariance3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_rebinX3" c_th3s_rebinx3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3S.h TH3S_rebinY3" c_th3s_rebiny3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3S.h TH3S_rebinZ3" c_th3s_rebinz3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3S.h TH3S_Rebin3D" c_th3s_rebin3d 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3S.h TH3S_Add" c_th3s_add 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_AddBinContent" c_th3s_addbincontent 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Chi2Test" c_th3s_chi2test 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_ComputeIntegral" c_th3s_computeintegral 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_DirectoryAutoAdd" c_th3s_directoryautoadd 
  :: (Ptr RawTH3S) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Divide" c_th3s_divide 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_drawCopyTH1" c_th3s_drawcopyth1 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTH3S)

foreign import ccall "HROOTHistTH3S.h TH3S_DrawNormalized" c_th3s_drawnormalized 
  :: (Ptr RawTH3S) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3S.h TH3S_drawPanelTH1" c_th3s_drawpanelth1 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_BufferEmpty" c_th3s_bufferempty 
  :: (Ptr RawTH3S) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_evalF" c_th3s_evalf 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_FFT" c_th3s_fft 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3S.h TH3S_fill1" c_th3s_fill1 
  :: (Ptr RawTH3S) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_fill1w" c_th3s_fill1w 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_fillN1" c_th3s_filln1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_FillRandom" c_th3s_fillrandom 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_FindBin" c_th3s_findbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_FindFixBin" c_th3s_findfixbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_FindFirstBinAbove" c_th3s_findfirstbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_FindLastBinAbove" c_th3s_findlastbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_FitPanelTH1" c_th3s_fitpanelth1 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_getNdivisionA" c_th3s_getndivisiona 
  :: (Ptr RawTH3S) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_getAxisColorA" c_th3s_getaxiscolora 
  :: (Ptr RawTH3S) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_getLabelColorA" c_th3s_getlabelcolora 
  :: (Ptr RawTH3S) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_getLabelFontA" c_th3s_getlabelfonta 
  :: (Ptr RawTH3S) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_getLabelOffsetA" c_th3s_getlabeloffseta 
  :: (Ptr RawTH3S) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getLabelSizeA" c_th3s_getlabelsizea 
  :: (Ptr RawTH3S) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getTitleFontA" c_th3s_gettitlefonta 
  :: (Ptr RawTH3S) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_getTitleOffsetA" c_th3s_gettitleoffseta 
  :: (Ptr RawTH3S) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getTitleSizeA" c_th3s_gettitlesizea 
  :: (Ptr RawTH3S) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getTickLengthA" c_th3s_getticklengtha 
  :: (Ptr RawTH3S) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBarOffset" c_th3s_getbaroffset 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBarWidth" c_th3s_getbarwidth 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetContour" c_th3s_getcontour 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetContourLevel" c_th3s_getcontourlevel 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetContourLevelPad" c_th3s_getcontourlevelpad 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBin" c_th3s_getbin 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinCenter" c_th3s_getbincenter 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinContent1" c_th3s_getbincontent1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinContent2" c_th3s_getbincontent2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinContent3" c_th3s_getbincontent3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinError1" c_th3s_getbinerror1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinError2" c_th3s_getbinerror2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinError3" c_th3s_getbinerror3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinLowEdge" c_th3s_getbinlowedge 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetBinWidth" c_th3s_getbinwidth 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetCellContent" c_th3s_getcellcontent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetCellError" c_th3s_getcellerror 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetEntries" c_th3s_getentries 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetEffectiveEntries" c_th3s_geteffectiveentries 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetFunction" c_th3s_getfunction 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH3S.h TH3S_GetDimension" c_th3s_getdimension 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetKurtosis" c_th3s_getkurtosis 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetLowEdge" c_th3s_getlowedge 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_getMaximumTH1" c_th3s_getmaximumth1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetMaximumBin" c_th3s_getmaximumbin 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetMaximumStored" c_th3s_getmaximumstored 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getMinimumTH1" c_th3s_getminimumth1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetMinimumBin" c_th3s_getminimumbin 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetMinimumStored" c_th3s_getminimumstored 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetMean" c_th3s_getmean 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetMeanError" c_th3s_getmeanerror 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetNbinsX" c_th3s_getnbinsx 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetNbinsY" c_th3s_getnbinsy 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetNbinsZ" c_th3s_getnbinsz 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_getQuantilesTH1" c_th3s_getquantilesth1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetRandom" c_th3s_getrandom 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetStats" c_th3s_getstats 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_GetSumOfWeights" c_th3s_getsumofweights 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetSumw2" c_th3s_getsumw2 
  :: (Ptr RawTH3S) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH3S.h TH3S_GetSumw2N" c_th3s_getsumw2n 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetRMS" c_th3s_getrms 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetRMSError" c_th3s_getrmserror 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_GetSkewness" c_th3s_getskewness 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_integral1" c_th3s_integral1 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_interpolate1" c_th3s_interpolate1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_interpolate2" c_th3s_interpolate2 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_interpolate3" c_th3s_interpolate3 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_KolmogorovTest" c_th3s_kolmogorovtest 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_LabelsDeflate" c_th3s_labelsdeflate 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_LabelsInflate" c_th3s_labelsinflate 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_LabelsOption" c_th3s_labelsoption 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_multiflyF" c_th3s_multiflyf 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Multiply" c_th3s_multiply 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_PutStats" c_th3s_putstats 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Rebin" c_th3s_rebin 
  :: (Ptr RawTH3S) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3S.h TH3S_RebinAxis" c_th3s_rebinaxis 
  :: (Ptr RawTH3S) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Rebuild" c_th3s_rebuild 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_RecursiveRemove" c_th3s_recursiveremove 
  :: (Ptr RawTH3S) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Reset" c_th3s_reset 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_ResetStats" c_th3s_resetstats 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Scale" c_th3s_scale 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setAxisColorA" c_th3s_setaxiscolora 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetAxisRange" c_th3s_setaxisrange 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetBarOffset" c_th3s_setbaroffset 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetBarWidth" c_th3s_setbarwidth 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinContent1" c_th3s_setbincontent1 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinContent2" c_th3s_setbincontent2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinContent3" c_th3s_setbincontent3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinError1" c_th3s_setbinerror1 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinError2" c_th3s_setbinerror2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBinError3" c_th3s_setbinerror3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBins1" c_th3s_setbins1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBins2" c_th3s_setbins2 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setBins3" c_th3s_setbins3 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetBinsLength" c_th3s_setbinslength 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetBuffer" c_th3s_setbuffer 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetCellContent" c_th3s_setcellcontent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetContent" c_th3s_setcontent 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetContour" c_th3s_setcontour 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetContourLevel" c_th3s_setcontourlevel 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetDirectory" c_th3s_setdirectory 
  :: (Ptr RawTH3S) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetEntries" c_th3s_setentries 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetError" c_th3s_seterror 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setLabelColorA" c_th3s_setlabelcolora 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setLabelSizeA" c_th3s_setlabelsizea 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setLabelFontA" c_th3s_setlabelfonta 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_setLabelOffsetA" c_th3s_setlabeloffseta 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMaximum" c_th3s_setmaximum 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMinimum" c_th3s_setminimum 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetNormFactor" c_th3s_setnormfactor 
  :: (Ptr RawTH3S) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetStats" c_th3s_setstats 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetOption" c_th3s_setoption 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetXTitle" c_th3s_setxtitle 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetYTitle" c_th3s_setytitle 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetZTitle" c_th3s_setztitle 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_ShowBackground" c_th3s_showbackground 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3S.h TH3S_ShowPeaks" c_th3s_showpeaks 
  :: (Ptr RawTH3S) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_Smooth" c_th3s_smooth 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Sumw2" c_th3s_sumw2 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Draw" c_th3s_draw 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_FindObject" c_th3s_findobject 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH3S.h TH3S_GetName" c_th3s_getname 
  :: (Ptr RawTH3S) -> IO CString

foreign import ccall "HROOTHistTH3S.h TH3S_IsA" c_th3s_isa 
  :: (Ptr RawTH3S) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH3S.h TH3S_Paint" c_th3s_paint 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_printObj" c_th3s_printobj 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SaveAs" c_th3s_saveas 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_Write" c_th3s_write 
  :: (Ptr RawTH3S) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetLineColor" c_th3s_getlinecolor 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetLineStyle" c_th3s_getlinestyle 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetLineWidth" c_th3s_getlinewidth 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_ResetAttLine" c_th3s_resetattline 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetLineAttributes" c_th3s_setlineattributes 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetLineColor" c_th3s_setlinecolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetLineStyle" c_th3s_setlinestyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetLineWidth" c_th3s_setlinewidth 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetFillColor" c_th3s_setfillcolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetFillStyle" c_th3s_setfillstyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_GetMarkerColor" c_th3s_getmarkercolor 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetMarkerStyle" c_th3s_getmarkerstyle 
  :: (Ptr RawTH3S) -> IO CInt

foreign import ccall "HROOTHistTH3S.h TH3S_GetMarkerSize" c_th3s_getmarkersize 
  :: (Ptr RawTH3S) -> IO CDouble

foreign import ccall "HROOTHistTH3S.h TH3S_ResetAttMarker" c_th3s_resetattmarker 
  :: (Ptr RawTH3S) -> CString -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMarkerAttributes" c_th3s_setmarkerattributes 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMarkerColor" c_th3s_setmarkercolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMarkerStyle" c_th3s_setmarkerstyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_SetMarkerSize" c_th3s_setmarkersize 
  :: (Ptr RawTH3S) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3S.h TH3S_delete" c_th3s_delete 
  :: (Ptr RawTH3S) -> IO ()