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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH3F.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TH3F.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/TH3F/FFI.hsc" #-}

foreign import ccall "HROOTHistTH3F.h TH3F_fill3" c_th3f_fill3 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_fill3w" c_th3f_fill3w 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_FitSlicesZ" c_th3f_fitslicesz 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_getCorrelationFactor3" c_th3f_getcorrelationfactor3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getCovariance3" c_th3f_getcovariance3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_rebinX3" c_th3f_rebinx3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3F.h TH3F_rebinY3" c_th3f_rebiny3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3F.h TH3F_rebinZ3" c_th3f_rebinz3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3F.h TH3F_Rebin3D" c_th3f_rebin3d 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3F.h TH3F_Add" c_th3f_add 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_AddBinContent" c_th3f_addbincontent 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Chi2Test" c_th3f_chi2test 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_ComputeIntegral" c_th3f_computeintegral 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_DirectoryAutoAdd" c_th3f_directoryautoadd 
  :: (Ptr RawTH3F) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Divide" c_th3f_divide 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_drawCopyTH1" c_th3f_drawcopyth1 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTH3F)

foreign import ccall "HROOTHistTH3F.h TH3F_DrawNormalized" c_th3f_drawnormalized 
  :: (Ptr RawTH3F) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3F.h TH3F_drawPanelTH1" c_th3f_drawpanelth1 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_BufferEmpty" c_th3f_bufferempty 
  :: (Ptr RawTH3F) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_evalF" c_th3f_evalf 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_FFT" c_th3f_fft 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3F.h TH3F_fill1" c_th3f_fill1 
  :: (Ptr RawTH3F) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_fill1w" c_th3f_fill1w 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_fillN1" c_th3f_filln1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_FillRandom" c_th3f_fillrandom 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_FindBin" c_th3f_findbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_FindFixBin" c_th3f_findfixbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_FindFirstBinAbove" c_th3f_findfirstbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_FindLastBinAbove" c_th3f_findlastbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_FitPanelTH1" c_th3f_fitpanelth1 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_getNdivisionA" c_th3f_getndivisiona 
  :: (Ptr RawTH3F) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_getAxisColorA" c_th3f_getaxiscolora 
  :: (Ptr RawTH3F) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_getLabelColorA" c_th3f_getlabelcolora 
  :: (Ptr RawTH3F) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_getLabelFontA" c_th3f_getlabelfonta 
  :: (Ptr RawTH3F) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_getLabelOffsetA" c_th3f_getlabeloffseta 
  :: (Ptr RawTH3F) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getLabelSizeA" c_th3f_getlabelsizea 
  :: (Ptr RawTH3F) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getTitleFontA" c_th3f_gettitlefonta 
  :: (Ptr RawTH3F) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_getTitleOffsetA" c_th3f_gettitleoffseta 
  :: (Ptr RawTH3F) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getTitleSizeA" c_th3f_gettitlesizea 
  :: (Ptr RawTH3F) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getTickLengthA" c_th3f_getticklengtha 
  :: (Ptr RawTH3F) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBarOffset" c_th3f_getbaroffset 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBarWidth" c_th3f_getbarwidth 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetContour" c_th3f_getcontour 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetContourLevel" c_th3f_getcontourlevel 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetContourLevelPad" c_th3f_getcontourlevelpad 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBin" c_th3f_getbin 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinCenter" c_th3f_getbincenter 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinContent1" c_th3f_getbincontent1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinContent2" c_th3f_getbincontent2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinContent3" c_th3f_getbincontent3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinError1" c_th3f_getbinerror1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinError2" c_th3f_getbinerror2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinError3" c_th3f_getbinerror3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinLowEdge" c_th3f_getbinlowedge 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetBinWidth" c_th3f_getbinwidth 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetCellContent" c_th3f_getcellcontent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetCellError" c_th3f_getcellerror 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetEntries" c_th3f_getentries 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetEffectiveEntries" c_th3f_geteffectiveentries 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetFunction" c_th3f_getfunction 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH3F.h TH3F_GetDimension" c_th3f_getdimension 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetKurtosis" c_th3f_getkurtosis 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetLowEdge" c_th3f_getlowedge 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_getMaximumTH1" c_th3f_getmaximumth1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetMaximumBin" c_th3f_getmaximumbin 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetMaximumStored" c_th3f_getmaximumstored 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getMinimumTH1" c_th3f_getminimumth1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetMinimumBin" c_th3f_getminimumbin 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetMinimumStored" c_th3f_getminimumstored 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetMean" c_th3f_getmean 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetMeanError" c_th3f_getmeanerror 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetNbinsX" c_th3f_getnbinsx 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetNbinsY" c_th3f_getnbinsy 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetNbinsZ" c_th3f_getnbinsz 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_getQuantilesTH1" c_th3f_getquantilesth1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetRandom" c_th3f_getrandom 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetStats" c_th3f_getstats 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_GetSumOfWeights" c_th3f_getsumofweights 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetSumw2" c_th3f_getsumw2 
  :: (Ptr RawTH3F) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH3F.h TH3F_GetSumw2N" c_th3f_getsumw2n 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetRMS" c_th3f_getrms 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetRMSError" c_th3f_getrmserror 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_GetSkewness" c_th3f_getskewness 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_integral1" c_th3f_integral1 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_interpolate1" c_th3f_interpolate1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_interpolate2" c_th3f_interpolate2 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_interpolate3" c_th3f_interpolate3 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_KolmogorovTest" c_th3f_kolmogorovtest 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_LabelsDeflate" c_th3f_labelsdeflate 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_LabelsInflate" c_th3f_labelsinflate 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_LabelsOption" c_th3f_labelsoption 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_multiflyF" c_th3f_multiflyf 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Multiply" c_th3f_multiply 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_PutStats" c_th3f_putstats 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Rebin" c_th3f_rebin 
  :: (Ptr RawTH3F) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3F.h TH3F_RebinAxis" c_th3f_rebinaxis 
  :: (Ptr RawTH3F) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Rebuild" c_th3f_rebuild 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_RecursiveRemove" c_th3f_recursiveremove 
  :: (Ptr RawTH3F) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Reset" c_th3f_reset 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_ResetStats" c_th3f_resetstats 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Scale" c_th3f_scale 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setAxisColorA" c_th3f_setaxiscolora 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetAxisRange" c_th3f_setaxisrange 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetBarOffset" c_th3f_setbaroffset 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetBarWidth" c_th3f_setbarwidth 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinContent1" c_th3f_setbincontent1 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinContent2" c_th3f_setbincontent2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinContent3" c_th3f_setbincontent3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinError1" c_th3f_setbinerror1 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinError2" c_th3f_setbinerror2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBinError3" c_th3f_setbinerror3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBins1" c_th3f_setbins1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBins2" c_th3f_setbins2 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setBins3" c_th3f_setbins3 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetBinsLength" c_th3f_setbinslength 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetBuffer" c_th3f_setbuffer 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetCellContent" c_th3f_setcellcontent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetContent" c_th3f_setcontent 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetContour" c_th3f_setcontour 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetContourLevel" c_th3f_setcontourlevel 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetDirectory" c_th3f_setdirectory 
  :: (Ptr RawTH3F) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetEntries" c_th3f_setentries 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetError" c_th3f_seterror 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setLabelColorA" c_th3f_setlabelcolora 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setLabelSizeA" c_th3f_setlabelsizea 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setLabelFontA" c_th3f_setlabelfonta 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_setLabelOffsetA" c_th3f_setlabeloffseta 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMaximum" c_th3f_setmaximum 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMinimum" c_th3f_setminimum 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetNormFactor" c_th3f_setnormfactor 
  :: (Ptr RawTH3F) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetStats" c_th3f_setstats 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetOption" c_th3f_setoption 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetXTitle" c_th3f_setxtitle 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetYTitle" c_th3f_setytitle 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetZTitle" c_th3f_setztitle 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_ShowBackground" c_th3f_showbackground 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3F.h TH3F_ShowPeaks" c_th3f_showpeaks 
  :: (Ptr RawTH3F) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_Smooth" c_th3f_smooth 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Sumw2" c_th3f_sumw2 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Draw" c_th3f_draw 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_FindObject" c_th3f_findobject 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH3F.h TH3F_GetName" c_th3f_getname 
  :: (Ptr RawTH3F) -> IO CString

foreign import ccall "HROOTHistTH3F.h TH3F_IsA" c_th3f_isa 
  :: (Ptr RawTH3F) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH3F.h TH3F_Paint" c_th3f_paint 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_printObj" c_th3f_printobj 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SaveAs" c_th3f_saveas 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_Write" c_th3f_write 
  :: (Ptr RawTH3F) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetLineColor" c_th3f_getlinecolor 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetLineStyle" c_th3f_getlinestyle 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetLineWidth" c_th3f_getlinewidth 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_ResetAttLine" c_th3f_resetattline 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetLineAttributes" c_th3f_setlineattributes 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetLineColor" c_th3f_setlinecolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetLineStyle" c_th3f_setlinestyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetLineWidth" c_th3f_setlinewidth 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetFillColor" c_th3f_setfillcolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetFillStyle" c_th3f_setfillstyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_GetMarkerColor" c_th3f_getmarkercolor 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetMarkerStyle" c_th3f_getmarkerstyle 
  :: (Ptr RawTH3F) -> IO CInt

foreign import ccall "HROOTHistTH3F.h TH3F_GetMarkerSize" c_th3f_getmarkersize 
  :: (Ptr RawTH3F) -> IO CDouble

foreign import ccall "HROOTHistTH3F.h TH3F_ResetAttMarker" c_th3f_resetattmarker 
  :: (Ptr RawTH3F) -> CString -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMarkerAttributes" c_th3f_setmarkerattributes 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMarkerColor" c_th3f_setmarkercolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMarkerStyle" c_th3f_setmarkerstyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_SetMarkerSize" c_th3f_setmarkersize 
  :: (Ptr RawTH3F) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3F.h TH3F_delete" c_th3f_delete 
  :: (Ptr RawTH3F) -> IO ()