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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH2.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TH2.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
import HROOT.Core.TObjArray.RawType


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

foreign import ccall "HROOTHistTH2.h TH2_Add" c_th2_add 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_AddBinContent" c_th2_addbincontent 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Chi2Test" c_th2_chi2test 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_ComputeIntegral" c_th2_computeintegral 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_DirectoryAutoAdd" c_th2_directoryautoadd 
  :: (Ptr RawTH2) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Divide" c_th2_divide 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_drawCopyTH1" c_th2_drawcopyth1 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2.h TH2_DrawNormalized" c_th2_drawnormalized 
  :: (Ptr RawTH2) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2.h TH2_drawPanelTH1" c_th2_drawpanelth1 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_BufferEmpty" c_th2_bufferempty 
  :: (Ptr RawTH2) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_evalF" c_th2_evalf 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_FFT" c_th2_fft 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2.h TH2_fill1" c_th2_fill1 
  :: (Ptr RawTH2) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_fill1w" c_th2_fill1w 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_fillN1" c_th2_filln1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_FillRandom" c_th2_fillrandom 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_FindBin" c_th2_findbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_FindFixBin" c_th2_findfixbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_FindFirstBinAbove" c_th2_findfirstbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_FindLastBinAbove" c_th2_findlastbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_FitPanelTH1" c_th2_fitpanelth1 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_getNdivisionA" c_th2_getndivisiona 
  :: (Ptr RawTH2) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_getAxisColorA" c_th2_getaxiscolora 
  :: (Ptr RawTH2) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_getLabelColorA" c_th2_getlabelcolora 
  :: (Ptr RawTH2) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_getLabelFontA" c_th2_getlabelfonta 
  :: (Ptr RawTH2) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_getLabelOffsetA" c_th2_getlabeloffseta 
  :: (Ptr RawTH2) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getLabelSizeA" c_th2_getlabelsizea 
  :: (Ptr RawTH2) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getTitleFontA" c_th2_gettitlefonta 
  :: (Ptr RawTH2) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_getTitleOffsetA" c_th2_gettitleoffseta 
  :: (Ptr RawTH2) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getTitleSizeA" c_th2_gettitlesizea 
  :: (Ptr RawTH2) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getTickLengthA" c_th2_getticklengtha 
  :: (Ptr RawTH2) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBarOffset" c_th2_getbaroffset 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBarWidth" c_th2_getbarwidth 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetContour" c_th2_getcontour 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetContourLevel" c_th2_getcontourlevel 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetContourLevelPad" c_th2_getcontourlevelpad 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBin" c_th2_getbin 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetBinCenter" c_th2_getbincenter 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinContent1" c_th2_getbincontent1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinContent2" c_th2_getbincontent2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinContent3" c_th2_getbincontent3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinError1" c_th2_getbinerror1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinError2" c_th2_getbinerror2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinError3" c_th2_getbinerror3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinLowEdge" c_th2_getbinlowedge 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetBinWidth" c_th2_getbinwidth 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetCellContent" c_th2_getcellcontent 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetCellError" c_th2_getcellerror 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetEntries" c_th2_getentries 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetEffectiveEntries" c_th2_geteffectiveentries 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetFunction" c_th2_getfunction 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH2.h TH2_GetDimension" c_th2_getdimension 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetKurtosis" c_th2_getkurtosis 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetLowEdge" c_th2_getlowedge 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_getMaximumTH1" c_th2_getmaximumth1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetMaximumBin" c_th2_getmaximumbin 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetMaximumStored" c_th2_getmaximumstored 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getMinimumTH1" c_th2_getminimumth1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetMinimumBin" c_th2_getminimumbin 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetMinimumStored" c_th2_getminimumstored 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetMean" c_th2_getmean 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetMeanError" c_th2_getmeanerror 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetNbinsX" c_th2_getnbinsx 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetNbinsY" c_th2_getnbinsy 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetNbinsZ" c_th2_getnbinsz 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getQuantilesTH1" c_th2_getquantilesth1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetRandom" c_th2_getrandom 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetStats" c_th2_getstats 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_GetSumOfWeights" c_th2_getsumofweights 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetSumw2" c_th2_getsumw2 
  :: (Ptr RawTH2) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH2.h TH2_GetSumw2N" c_th2_getsumw2n 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetRMS" c_th2_getrms 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetRMSError" c_th2_getrmserror 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_GetSkewness" c_th2_getskewness 
  :: (Ptr RawTH2) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_integral1" c_th2_integral1 
  :: (Ptr RawTH2) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_interpolate1" c_th2_interpolate1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_interpolate2" c_th2_interpolate2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_interpolate3" c_th2_interpolate3 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_KolmogorovTest" c_th2_kolmogorovtest 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_LabelsDeflate" c_th2_labelsdeflate 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_LabelsInflate" c_th2_labelsinflate 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_LabelsOption" c_th2_labelsoption 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_multiflyF" c_th2_multiflyf 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Multiply" c_th2_multiply 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_PutStats" c_th2_putstats 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Rebin" c_th2_rebin 
  :: (Ptr RawTH2) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2.h TH2_RebinAxis" c_th2_rebinaxis 
  :: (Ptr RawTH2) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Rebuild" c_th2_rebuild 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_RecursiveRemove" c_th2_recursiveremove 
  :: (Ptr RawTH2) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Reset" c_th2_reset 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_ResetStats" c_th2_resetstats 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Scale" c_th2_scale 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setAxisColorA" c_th2_setaxiscolora 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetAxisRange" c_th2_setaxisrange 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetBarOffset" c_th2_setbaroffset 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetBarWidth" c_th2_setbarwidth 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinContent1" c_th2_setbincontent1 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinContent2" c_th2_setbincontent2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinContent3" c_th2_setbincontent3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinError1" c_th2_setbinerror1 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinError2" c_th2_setbinerror2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBinError3" c_th2_setbinerror3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBins1" c_th2_setbins1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBins2" c_th2_setbins2 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setBins3" c_th2_setbins3 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetBinsLength" c_th2_setbinslength 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetBuffer" c_th2_setbuffer 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetCellContent" c_th2_setcellcontent 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetContent" c_th2_setcontent 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetContour" c_th2_setcontour 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetContourLevel" c_th2_setcontourlevel 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetDirectory" c_th2_setdirectory 
  :: (Ptr RawTH2) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetEntries" c_th2_setentries 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetError" c_th2_seterror 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setLabelColorA" c_th2_setlabelcolora 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setLabelSizeA" c_th2_setlabelsizea 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setLabelFontA" c_th2_setlabelfonta 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_setLabelOffsetA" c_th2_setlabeloffseta 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMaximum" c_th2_setmaximum 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMinimum" c_th2_setminimum 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetNormFactor" c_th2_setnormfactor 
  :: (Ptr RawTH2) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetStats" c_th2_setstats 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetOption" c_th2_setoption 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetXTitle" c_th2_setxtitle 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetYTitle" c_th2_setytitle 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetZTitle" c_th2_setztitle 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_ShowBackground" c_th2_showbackground 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2.h TH2_ShowPeaks" c_th2_showpeaks 
  :: (Ptr RawTH2) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_Smooth" c_th2_smooth 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Sumw2" c_th2_sumw2 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Draw" c_th2_draw 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_FindObject" c_th2_findobject 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH2.h TH2_GetName" c_th2_getname 
  :: (Ptr RawTH2) -> IO CString

foreign import ccall "HROOTHistTH2.h TH2_IsA" c_th2_isa 
  :: (Ptr RawTH2) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH2.h TH2_Paint" c_th2_paint 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_printObj" c_th2_printobj 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SaveAs" c_th2_saveas 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_Write" c_th2_write 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetLineColor" c_th2_getlinecolor 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetLineStyle" c_th2_getlinestyle 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetLineWidth" c_th2_getlinewidth 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_ResetAttLine" c_th2_resetattline 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetLineAttributes" c_th2_setlineattributes 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetLineColor" c_th2_setlinecolor 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetLineStyle" c_th2_setlinestyle 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetLineWidth" c_th2_setlinewidth 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetFillColor" c_th2_setfillcolor 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetFillStyle" c_th2_setfillstyle 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_GetMarkerColor" c_th2_getmarkercolor 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetMarkerStyle" c_th2_getmarkerstyle 
  :: (Ptr RawTH2) -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_GetMarkerSize" c_th2_getmarkersize 
  :: (Ptr RawTH2) -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_ResetAttMarker" c_th2_resetattmarker 
  :: (Ptr RawTH2) -> CString -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMarkerAttributes" c_th2_setmarkerattributes 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMarkerColor" c_th2_setmarkercolor 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMarkerStyle" c_th2_setmarkerstyle 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetMarkerSize" c_th2_setmarkersize 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_delete" c_th2_delete 
  :: (Ptr RawTH2) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_fill2" c_th2_fill2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_fill2w" c_th2_fill2w 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_fillN2" c_th2_filln2 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_fillRandom2" c_th2_fillrandom2 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_findFirstBinAbove2" c_th2_findfirstbinabove2 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_findLastBinAbove2" c_th2_findlastbinabove2 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2.h TH2_FitSlicesX" c_th2_fitslicesx 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_FitSlicesY" c_th2_fitslicesy 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_getCorrelationFactor2" c_th2_getcorrelationfactor2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_getCovariance2" c_th2_getcovariance2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_integral2" c_th2_integral2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2.h TH2_tH2ProjectionX" c_th2_th2projectionx 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)

foreign import ccall "HROOTHistTH2.h TH2_tH2ProjectionY" c_th2_th2projectiony 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)

foreign import ccall "HROOTHistTH2.h TH2_rebinX2" c_th2_rebinx2 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2.h TH2_rebinY2" c_th2_rebiny2 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2.h TH2_Rebin2D" c_th2_rebin2d 
  :: (Ptr RawTH2) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2.h TH2_SetShowProjectionX" c_th2_setshowprojectionx 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2.h TH2_SetShowProjectionY" c_th2_setshowprojectiony 
  :: (Ptr RawTH2) -> CInt -> IO ()