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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH3.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

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


{-# LINE 26 "src/HROOT/Hist/TH3/FFI.hsc" #-}

foreign import ccall "HROOTHistTH3.h TH3_Add" c_th3_add 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_AddBinContent" c_th3_addbincontent 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Chi2Test" c_th3_chi2test 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_ComputeIntegral" c_th3_computeintegral 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_DirectoryAutoAdd" c_th3_directoryautoadd 
  :: (Ptr RawTH3) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Divide" c_th3_divide 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_drawCopyTH1" c_th3_drawcopyth1 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3.h TH3_DrawNormalized" c_th3_drawnormalized 
  :: (Ptr RawTH3) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3.h TH3_drawPanelTH1" c_th3_drawpanelth1 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_BufferEmpty" c_th3_bufferempty 
  :: (Ptr RawTH3) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_evalF" c_th3_evalf 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_FFT" c_th3_fft 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3.h TH3_fill1" c_th3_fill1 
  :: (Ptr RawTH3) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_fill1w" c_th3_fill1w 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_fillN1" c_th3_filln1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_FillRandom" c_th3_fillrandom 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_FindBin" c_th3_findbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_FindFixBin" c_th3_findfixbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_FindFirstBinAbove" c_th3_findfirstbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_FindLastBinAbove" c_th3_findlastbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_FitPanelTH1" c_th3_fitpanelth1 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_getNdivisionA" c_th3_getndivisiona 
  :: (Ptr RawTH3) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_getAxisColorA" c_th3_getaxiscolora 
  :: (Ptr RawTH3) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_getLabelColorA" c_th3_getlabelcolora 
  :: (Ptr RawTH3) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_getLabelFontA" c_th3_getlabelfonta 
  :: (Ptr RawTH3) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_getLabelOffsetA" c_th3_getlabeloffseta 
  :: (Ptr RawTH3) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getLabelSizeA" c_th3_getlabelsizea 
  :: (Ptr RawTH3) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getTitleFontA" c_th3_gettitlefonta 
  :: (Ptr RawTH3) -> CString -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_getTitleOffsetA" c_th3_gettitleoffseta 
  :: (Ptr RawTH3) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getTitleSizeA" c_th3_gettitlesizea 
  :: (Ptr RawTH3) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getTickLengthA" c_th3_getticklengtha 
  :: (Ptr RawTH3) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBarOffset" c_th3_getbaroffset 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBarWidth" c_th3_getbarwidth 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetContour" c_th3_getcontour 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetContourLevel" c_th3_getcontourlevel 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetContourLevelPad" c_th3_getcontourlevelpad 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBin" c_th3_getbin 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetBinCenter" c_th3_getbincenter 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinContent1" c_th3_getbincontent1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinContent2" c_th3_getbincontent2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinContent3" c_th3_getbincontent3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinError1" c_th3_getbinerror1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinError2" c_th3_getbinerror2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinError3" c_th3_getbinerror3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinLowEdge" c_th3_getbinlowedge 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetBinWidth" c_th3_getbinwidth 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetCellContent" c_th3_getcellcontent 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetCellError" c_th3_getcellerror 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetEntries" c_th3_getentries 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetEffectiveEntries" c_th3_geteffectiveentries 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetFunction" c_th3_getfunction 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH3.h TH3_GetDimension" c_th3_getdimension 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetKurtosis" c_th3_getkurtosis 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetLowEdge" c_th3_getlowedge 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_getMaximumTH1" c_th3_getmaximumth1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetMaximumBin" c_th3_getmaximumbin 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetMaximumStored" c_th3_getmaximumstored 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getMinimumTH1" c_th3_getminimumth1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetMinimumBin" c_th3_getminimumbin 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetMinimumStored" c_th3_getminimumstored 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetMean" c_th3_getmean 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetMeanError" c_th3_getmeanerror 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetNbinsX" c_th3_getnbinsx 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetNbinsY" c_th3_getnbinsy 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetNbinsZ" c_th3_getnbinsz 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getQuantilesTH1" c_th3_getquantilesth1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetRandom" c_th3_getrandom 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetStats" c_th3_getstats 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_GetSumOfWeights" c_th3_getsumofweights 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetSumw2" c_th3_getsumw2 
  :: (Ptr RawTH3) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH3.h TH3_GetSumw2N" c_th3_getsumw2n 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetRMS" c_th3_getrms 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetRMSError" c_th3_getrmserror 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_GetSkewness" c_th3_getskewness 
  :: (Ptr RawTH3) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_integral1" c_th3_integral1 
  :: (Ptr RawTH3) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_interpolate1" c_th3_interpolate1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_interpolate2" c_th3_interpolate2 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_interpolate3" c_th3_interpolate3 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_KolmogorovTest" c_th3_kolmogorovtest 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_LabelsDeflate" c_th3_labelsdeflate 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_LabelsInflate" c_th3_labelsinflate 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_LabelsOption" c_th3_labelsoption 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_multiflyF" c_th3_multiflyf 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Multiply" c_th3_multiply 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_PutStats" c_th3_putstats 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Rebin" c_th3_rebin 
  :: (Ptr RawTH3) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3.h TH3_RebinAxis" c_th3_rebinaxis 
  :: (Ptr RawTH3) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Rebuild" c_th3_rebuild 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_RecursiveRemove" c_th3_recursiveremove 
  :: (Ptr RawTH3) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Reset" c_th3_reset 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_ResetStats" c_th3_resetstats 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Scale" c_th3_scale 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setAxisColorA" c_th3_setaxiscolora 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetAxisRange" c_th3_setaxisrange 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetBarOffset" c_th3_setbaroffset 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetBarWidth" c_th3_setbarwidth 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinContent1" c_th3_setbincontent1 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinContent2" c_th3_setbincontent2 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinContent3" c_th3_setbincontent3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinError1" c_th3_setbinerror1 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinError2" c_th3_setbinerror2 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBinError3" c_th3_setbinerror3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBins1" c_th3_setbins1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBins2" c_th3_setbins2 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setBins3" c_th3_setbins3 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetBinsLength" c_th3_setbinslength 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetBuffer" c_th3_setbuffer 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetCellContent" c_th3_setcellcontent 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetContent" c_th3_setcontent 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetContour" c_th3_setcontour 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetContourLevel" c_th3_setcontourlevel 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetDirectory" c_th3_setdirectory 
  :: (Ptr RawTH3) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetEntries" c_th3_setentries 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetError" c_th3_seterror 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setLabelColorA" c_th3_setlabelcolora 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setLabelSizeA" c_th3_setlabelsizea 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setLabelFontA" c_th3_setlabelfonta 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_setLabelOffsetA" c_th3_setlabeloffseta 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMaximum" c_th3_setmaximum 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMinimum" c_th3_setminimum 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetNormFactor" c_th3_setnormfactor 
  :: (Ptr RawTH3) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetStats" c_th3_setstats 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetOption" c_th3_setoption 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetXTitle" c_th3_setxtitle 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetYTitle" c_th3_setytitle 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetZTitle" c_th3_setztitle 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_ShowBackground" c_th3_showbackground 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3.h TH3_ShowPeaks" c_th3_showpeaks 
  :: (Ptr RawTH3) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_Smooth" c_th3_smooth 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Sumw2" c_th3_sumw2 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Draw" c_th3_draw 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_FindObject" c_th3_findobject 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH3.h TH3_GetName" c_th3_getname 
  :: (Ptr RawTH3) -> IO CString

foreign import ccall "HROOTHistTH3.h TH3_IsA" c_th3_isa 
  :: (Ptr RawTH3) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH3.h TH3_Paint" c_th3_paint 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_printObj" c_th3_printobj 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SaveAs" c_th3_saveas 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_Write" c_th3_write 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetLineColor" c_th3_getlinecolor 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetLineStyle" c_th3_getlinestyle 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetLineWidth" c_th3_getlinewidth 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_ResetAttLine" c_th3_resetattline 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetLineAttributes" c_th3_setlineattributes 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetLineColor" c_th3_setlinecolor 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetLineStyle" c_th3_setlinestyle 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetLineWidth" c_th3_setlinewidth 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetFillColor" c_th3_setfillcolor 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetFillStyle" c_th3_setfillstyle 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_GetMarkerColor" c_th3_getmarkercolor 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetMarkerStyle" c_th3_getmarkerstyle 
  :: (Ptr RawTH3) -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_GetMarkerSize" c_th3_getmarkersize 
  :: (Ptr RawTH3) -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_ResetAttMarker" c_th3_resetattmarker 
  :: (Ptr RawTH3) -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMarkerAttributes" c_th3_setmarkerattributes 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMarkerColor" c_th3_setmarkercolor 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMarkerStyle" c_th3_setmarkerstyle 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_SetMarkerSize" c_th3_setmarkersize 
  :: (Ptr RawTH3) -> CInt -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_delete" c_th3_delete 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_fill3" c_th3_fill3 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_fill3w" c_th3_fill3w 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH3.h TH3_FitSlicesZ" c_th3_fitslicesz 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH3.h TH3_getCorrelationFactor3" c_th3_getcorrelationfactor3 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_getCovariance3" c_th3_getcovariance3 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH3.h TH3_tH3ProjectionX" c_th3_th3projectionx 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)

foreign import ccall "HROOTHistTH3.h TH3_tH3ProjectionY" c_th3_th3projectiony 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)

foreign import ccall "HROOTHistTH3.h TH3_tH3ProjectionZ" c_th3_th3projectionz 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)

foreign import ccall "HROOTHistTH3.h TH3_tH3Project3D" c_th3_th3project3d 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH3.h TH3_rebinX3" c_th3_rebinx3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3.h TH3_rebinY3" c_th3_rebiny3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3.h TH3_rebinZ3" c_th3_rebinz3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOTHistTH3.h TH3_Rebin3D" c_th3_rebin3d 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)