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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH3C.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

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

foreign import ccall "HROOTHistTH3C.h TH3C_fill3" c_th3c_fill3 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_fill3w" c_th3c_fill3w 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_FitSlicesZ" c_th3c_fitslicesz 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_getCorrelationFactor3" c_th3c_getcorrelationfactor3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getCovariance3" c_th3c_getcovariance3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_rebinX3" c_th3c_rebinx3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3C.h TH3C_rebinY3" c_th3c_rebiny3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3C.h TH3C_rebinZ3" c_th3c_rebinz3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3C.h TH3C_Rebin3D" c_th3c_rebin3d 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3C.h TH3C_Add" c_th3c_add 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_AddBinContent" c_th3c_addbincontent 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Chi2Test" c_th3c_chi2test 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_ComputeIntegral" c_th3c_computeintegral 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_DirectoryAutoAdd" c_th3c_directoryautoadd 
  :: (Ptr RawTH3C) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Divide" c_th3c_divide 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_drawCopyTH1" c_th3c_drawcopyth1 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTH3C)

foreign import ccall "HROOTHistTH3C.h TH3C_DrawNormalized" c_th3c_drawnormalized 
  :: (Ptr RawTH3C) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3C.h TH3C_drawPanelTH1" c_th3c_drawpanelth1 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_BufferEmpty" c_th3c_bufferempty 
  :: (Ptr RawTH3C) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_evalF" c_th3c_evalf 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_FFT" c_th3c_fft 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3C.h TH3C_fill1" c_th3c_fill1 
  :: (Ptr RawTH3C) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_fill1w" c_th3c_fill1w 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_fillN1" c_th3c_filln1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_FillRandom" c_th3c_fillrandom 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_FindBin" c_th3c_findbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_FindFixBin" c_th3c_findfixbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_FindFirstBinAbove" c_th3c_findfirstbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_FindLastBinAbove" c_th3c_findlastbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_FitPanelTH1" c_th3c_fitpanelth1 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_getNdivisionA" c_th3c_getndivisiona 
  :: (Ptr RawTH3C) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_getAxisColorA" c_th3c_getaxiscolora 
  :: (Ptr RawTH3C) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_getLabelColorA" c_th3c_getlabelcolora 
  :: (Ptr RawTH3C) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_getLabelFontA" c_th3c_getlabelfonta 
  :: (Ptr RawTH3C) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_getLabelOffsetA" c_th3c_getlabeloffseta 
  :: (Ptr RawTH3C) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getLabelSizeA" c_th3c_getlabelsizea 
  :: (Ptr RawTH3C) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getTitleFontA" c_th3c_gettitlefonta 
  :: (Ptr RawTH3C) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_getTitleOffsetA" c_th3c_gettitleoffseta 
  :: (Ptr RawTH3C) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getTitleSizeA" c_th3c_gettitlesizea 
  :: (Ptr RawTH3C) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getTickLengthA" c_th3c_getticklengtha 
  :: (Ptr RawTH3C) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBarOffset" c_th3c_getbaroffset 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBarWidth" c_th3c_getbarwidth 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetContour" c_th3c_getcontour 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetContourLevel" c_th3c_getcontourlevel 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetContourLevelPad" c_th3c_getcontourlevelpad 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBin" c_th3c_getbin 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinCenter" c_th3c_getbincenter 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinContent1" c_th3c_getbincontent1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinContent2" c_th3c_getbincontent2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinContent3" c_th3c_getbincontent3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinError1" c_th3c_getbinerror1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinError2" c_th3c_getbinerror2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinError3" c_th3c_getbinerror3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinLowEdge" c_th3c_getbinlowedge 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetBinWidth" c_th3c_getbinwidth 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetCellContent" c_th3c_getcellcontent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetCellError" c_th3c_getcellerror 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetEntries" c_th3c_getentries 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetEffectiveEntries" c_th3c_geteffectiveentries 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetFunction" c_th3c_getfunction 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH3C.h TH3C_GetDimension" c_th3c_getdimension 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetKurtosis" c_th3c_getkurtosis 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetLowEdge" c_th3c_getlowedge 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_getMaximumTH1" c_th3c_getmaximumth1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetMaximumBin" c_th3c_getmaximumbin 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetMaximumStored" c_th3c_getmaximumstored 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getMinimumTH1" c_th3c_getminimumth1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetMinimumBin" c_th3c_getminimumbin 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetMinimumStored" c_th3c_getminimumstored 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetMean" c_th3c_getmean 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetMeanError" c_th3c_getmeanerror 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetNbinsX" c_th3c_getnbinsx 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetNbinsY" c_th3c_getnbinsy 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetNbinsZ" c_th3c_getnbinsz 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_getQuantilesTH1" c_th3c_getquantilesth1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetRandom" c_th3c_getrandom 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetStats" c_th3c_getstats 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_GetSumOfWeights" c_th3c_getsumofweights 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetSumw2" c_th3c_getsumw2 
  :: (Ptr RawTH3C) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH3C.h TH3C_GetSumw2N" c_th3c_getsumw2n 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetRMS" c_th3c_getrms 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetRMSError" c_th3c_getrmserror 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_GetSkewness" c_th3c_getskewness 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_integral1" c_th3c_integral1 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_interpolate1" c_th3c_interpolate1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_interpolate2" c_th3c_interpolate2 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_interpolate3" c_th3c_interpolate3 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_KolmogorovTest" c_th3c_kolmogorovtest 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_LabelsDeflate" c_th3c_labelsdeflate 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_LabelsInflate" c_th3c_labelsinflate 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_LabelsOption" c_th3c_labelsoption 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_multiflyF" c_th3c_multiflyf 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Multiply" c_th3c_multiply 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_PutStats" c_th3c_putstats 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Rebin" c_th3c_rebin 
  :: (Ptr RawTH3C) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3C.h TH3C_RebinAxis" c_th3c_rebinaxis 
  :: (Ptr RawTH3C) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Rebuild" c_th3c_rebuild 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_RecursiveRemove" c_th3c_recursiveremove 
  :: (Ptr RawTH3C) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Reset" c_th3c_reset 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_ResetStats" c_th3c_resetstats 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Scale" c_th3c_scale 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setAxisColorA" c_th3c_setaxiscolora 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetAxisRange" c_th3c_setaxisrange 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetBarOffset" c_th3c_setbaroffset 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetBarWidth" c_th3c_setbarwidth 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinContent1" c_th3c_setbincontent1 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinContent2" c_th3c_setbincontent2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinContent3" c_th3c_setbincontent3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinError1" c_th3c_setbinerror1 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinError2" c_th3c_setbinerror2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBinError3" c_th3c_setbinerror3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBins1" c_th3c_setbins1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBins2" c_th3c_setbins2 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setBins3" c_th3c_setbins3 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetBinsLength" c_th3c_setbinslength 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetBuffer" c_th3c_setbuffer 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetCellContent" c_th3c_setcellcontent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetContent" c_th3c_setcontent 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetContour" c_th3c_setcontour 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetContourLevel" c_th3c_setcontourlevel 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetDirectory" c_th3c_setdirectory 
  :: (Ptr RawTH3C) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetEntries" c_th3c_setentries 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetError" c_th3c_seterror 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setLabelColorA" c_th3c_setlabelcolora 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setLabelSizeA" c_th3c_setlabelsizea 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setLabelFontA" c_th3c_setlabelfonta 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_setLabelOffsetA" c_th3c_setlabeloffseta 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMaximum" c_th3c_setmaximum 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMinimum" c_th3c_setminimum 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetNormFactor" c_th3c_setnormfactor 
  :: (Ptr RawTH3C) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetStats" c_th3c_setstats 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetOption" c_th3c_setoption 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetXTitle" c_th3c_setxtitle 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetYTitle" c_th3c_setytitle 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetZTitle" c_th3c_setztitle 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_ShowBackground" c_th3c_showbackground 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3C.h TH3C_ShowPeaks" c_th3c_showpeaks 
  :: (Ptr RawTH3C) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_Smooth" c_th3c_smooth 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Sumw2" c_th3c_sumw2 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Draw" c_th3c_draw 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_FindObject" c_th3c_findobject 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH3C.h TH3C_GetName" c_th3c_getname 
  :: (Ptr RawTH3C) -> IO CString

foreign import ccall "HROOTHistTH3C.h TH3C_IsA" c_th3c_isa 
  :: (Ptr RawTH3C) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH3C.h TH3C_Paint" c_th3c_paint 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_printObj" c_th3c_printobj 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SaveAs" c_th3c_saveas 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_Write" c_th3c_write 
  :: (Ptr RawTH3C) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetLineColor" c_th3c_getlinecolor 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetLineStyle" c_th3c_getlinestyle 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetLineWidth" c_th3c_getlinewidth 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_ResetAttLine" c_th3c_resetattline 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetLineAttributes" c_th3c_setlineattributes 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetLineColor" c_th3c_setlinecolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetLineStyle" c_th3c_setlinestyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetLineWidth" c_th3c_setlinewidth 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetFillColor" c_th3c_setfillcolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetFillStyle" c_th3c_setfillstyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_GetMarkerColor" c_th3c_getmarkercolor 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetMarkerStyle" c_th3c_getmarkerstyle 
  :: (Ptr RawTH3C) -> IO CInt

foreign import ccall "HROOTHistTH3C.h TH3C_GetMarkerSize" c_th3c_getmarkersize 
  :: (Ptr RawTH3C) -> IO CDouble

foreign import ccall "HROOTHistTH3C.h TH3C_ResetAttMarker" c_th3c_resetattmarker 
  :: (Ptr RawTH3C) -> CString -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMarkerAttributes" c_th3c_setmarkerattributes 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMarkerColor" c_th3c_setmarkercolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMarkerStyle" c_th3c_setmarkerstyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_SetMarkerSize" c_th3c_setmarkersize 
  :: (Ptr RawTH3C) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3C.h TH3C_delete" c_th3c_delete 
  :: (Ptr RawTH3C) -> IO ()