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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH2I.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TH2I.RawType
import HROOT.Hist.TH1D.RawType
import HROOT.Hist.TH2.RawType
import HROOT.Hist.TH1.RawType
import HROOT.Hist.TF1.RawType
import HROOT.Core.TObjArray.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 28 "src/HROOT/Hist/TH2I/FFI.hsc" #-}

foreign import ccall "HROOTHistTH2I.h TH2I_fill2" c_th2i_fill2 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_fill2w" c_th2i_fill2w 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_fillN2" c_th2i_filln2 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_fillRandom2" c_th2i_fillrandom2 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_findFirstBinAbove2" c_th2i_findfirstbinabove2 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_findLastBinAbove2" c_th2i_findlastbinabove2 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_FitSlicesX" c_th2i_fitslicesx 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_FitSlicesY" c_th2i_fitslicesy 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_getCorrelationFactor2" c_th2i_getcorrelationfactor2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getCovariance2" c_th2i_getcovariance2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_integral2" c_th2i_integral2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_rebinX2" c_th2i_rebinx2 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2I.h TH2I_rebinY2" c_th2i_rebiny2 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2I.h TH2I_Rebin2D" c_th2i_rebin2d 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2I.h TH2I_SetShowProjectionX" c_th2i_setshowprojectionx 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetShowProjectionY" c_th2i_setshowprojectiony 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Add" c_th2i_add 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_AddBinContent" c_th2i_addbincontent 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Chi2Test" c_th2i_chi2test 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_ComputeIntegral" c_th2i_computeintegral 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_DirectoryAutoAdd" c_th2i_directoryautoadd 
  :: (Ptr RawTH2I) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Divide" c_th2i_divide 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_drawCopyTH1" c_th2i_drawcopyth1 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTH2I)

foreign import ccall "HROOTHistTH2I.h TH2I_DrawNormalized" c_th2i_drawnormalized 
  :: (Ptr RawTH2I) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2I.h TH2I_drawPanelTH1" c_th2i_drawpanelth1 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_BufferEmpty" c_th2i_bufferempty 
  :: (Ptr RawTH2I) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_evalF" c_th2i_evalf 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_FFT" c_th2i_fft 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2I.h TH2I_fill1" c_th2i_fill1 
  :: (Ptr RawTH2I) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_fill1w" c_th2i_fill1w 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_fillN1" c_th2i_filln1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_FillRandom" c_th2i_fillrandom 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_FindBin" c_th2i_findbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_FindFixBin" c_th2i_findfixbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_FindFirstBinAbove" c_th2i_findfirstbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_FindLastBinAbove" c_th2i_findlastbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_FitPanelTH1" c_th2i_fitpanelth1 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_getNdivisionA" c_th2i_getndivisiona 
  :: (Ptr RawTH2I) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_getAxisColorA" c_th2i_getaxiscolora 
  :: (Ptr RawTH2I) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_getLabelColorA" c_th2i_getlabelcolora 
  :: (Ptr RawTH2I) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_getLabelFontA" c_th2i_getlabelfonta 
  :: (Ptr RawTH2I) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_getLabelOffsetA" c_th2i_getlabeloffseta 
  :: (Ptr RawTH2I) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getLabelSizeA" c_th2i_getlabelsizea 
  :: (Ptr RawTH2I) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getTitleFontA" c_th2i_gettitlefonta 
  :: (Ptr RawTH2I) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_getTitleOffsetA" c_th2i_gettitleoffseta 
  :: (Ptr RawTH2I) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getTitleSizeA" c_th2i_gettitlesizea 
  :: (Ptr RawTH2I) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getTickLengthA" c_th2i_getticklengtha 
  :: (Ptr RawTH2I) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBarOffset" c_th2i_getbaroffset 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBarWidth" c_th2i_getbarwidth 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetContour" c_th2i_getcontour 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetContourLevel" c_th2i_getcontourlevel 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetContourLevelPad" c_th2i_getcontourlevelpad 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBin" c_th2i_getbin 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinCenter" c_th2i_getbincenter 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinContent1" c_th2i_getbincontent1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinContent2" c_th2i_getbincontent2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinContent3" c_th2i_getbincontent3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinError1" c_th2i_getbinerror1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinError2" c_th2i_getbinerror2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinError3" c_th2i_getbinerror3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinLowEdge" c_th2i_getbinlowedge 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetBinWidth" c_th2i_getbinwidth 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetCellContent" c_th2i_getcellcontent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetCellError" c_th2i_getcellerror 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetEntries" c_th2i_getentries 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetEffectiveEntries" c_th2i_geteffectiveentries 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetFunction" c_th2i_getfunction 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH2I.h TH2I_GetDimension" c_th2i_getdimension 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetKurtosis" c_th2i_getkurtosis 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetLowEdge" c_th2i_getlowedge 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_getMaximumTH1" c_th2i_getmaximumth1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetMaximumBin" c_th2i_getmaximumbin 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetMaximumStored" c_th2i_getmaximumstored 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getMinimumTH1" c_th2i_getminimumth1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetMinimumBin" c_th2i_getminimumbin 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetMinimumStored" c_th2i_getminimumstored 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetMean" c_th2i_getmean 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetMeanError" c_th2i_getmeanerror 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetNbinsX" c_th2i_getnbinsx 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetNbinsY" c_th2i_getnbinsy 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetNbinsZ" c_th2i_getnbinsz 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_getQuantilesTH1" c_th2i_getquantilesth1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetRandom" c_th2i_getrandom 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetStats" c_th2i_getstats 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_GetSumOfWeights" c_th2i_getsumofweights 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetSumw2" c_th2i_getsumw2 
  :: (Ptr RawTH2I) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH2I.h TH2I_GetSumw2N" c_th2i_getsumw2n 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetRMS" c_th2i_getrms 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetRMSError" c_th2i_getrmserror 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_GetSkewness" c_th2i_getskewness 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_integral1" c_th2i_integral1 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_interpolate1" c_th2i_interpolate1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_interpolate2" c_th2i_interpolate2 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_interpolate3" c_th2i_interpolate3 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_KolmogorovTest" c_th2i_kolmogorovtest 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_LabelsDeflate" c_th2i_labelsdeflate 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_LabelsInflate" c_th2i_labelsinflate 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_LabelsOption" c_th2i_labelsoption 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_multiflyF" c_th2i_multiflyf 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Multiply" c_th2i_multiply 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_PutStats" c_th2i_putstats 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Rebin" c_th2i_rebin 
  :: (Ptr RawTH2I) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2I.h TH2I_RebinAxis" c_th2i_rebinaxis 
  :: (Ptr RawTH2I) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Rebuild" c_th2i_rebuild 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_RecursiveRemove" c_th2i_recursiveremove 
  :: (Ptr RawTH2I) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Reset" c_th2i_reset 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_ResetStats" c_th2i_resetstats 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Scale" c_th2i_scale 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setAxisColorA" c_th2i_setaxiscolora 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetAxisRange" c_th2i_setaxisrange 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetBarOffset" c_th2i_setbaroffset 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetBarWidth" c_th2i_setbarwidth 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinContent1" c_th2i_setbincontent1 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinContent2" c_th2i_setbincontent2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinContent3" c_th2i_setbincontent3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinError1" c_th2i_setbinerror1 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinError2" c_th2i_setbinerror2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBinError3" c_th2i_setbinerror3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBins1" c_th2i_setbins1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBins2" c_th2i_setbins2 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setBins3" c_th2i_setbins3 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetBinsLength" c_th2i_setbinslength 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetBuffer" c_th2i_setbuffer 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetCellContent" c_th2i_setcellcontent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetContent" c_th2i_setcontent 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetContour" c_th2i_setcontour 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetContourLevel" c_th2i_setcontourlevel 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetDirectory" c_th2i_setdirectory 
  :: (Ptr RawTH2I) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetEntries" c_th2i_setentries 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetError" c_th2i_seterror 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setLabelColorA" c_th2i_setlabelcolora 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setLabelSizeA" c_th2i_setlabelsizea 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setLabelFontA" c_th2i_setlabelfonta 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_setLabelOffsetA" c_th2i_setlabeloffseta 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMaximum" c_th2i_setmaximum 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMinimum" c_th2i_setminimum 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetNormFactor" c_th2i_setnormfactor 
  :: (Ptr RawTH2I) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetStats" c_th2i_setstats 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetOption" c_th2i_setoption 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetXTitle" c_th2i_setxtitle 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetYTitle" c_th2i_setytitle 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetZTitle" c_th2i_setztitle 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_ShowBackground" c_th2i_showbackground 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2I.h TH2I_ShowPeaks" c_th2i_showpeaks 
  :: (Ptr RawTH2I) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_Smooth" c_th2i_smooth 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Sumw2" c_th2i_sumw2 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Draw" c_th2i_draw 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_FindObject" c_th2i_findobject 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH2I.h TH2I_GetName" c_th2i_getname 
  :: (Ptr RawTH2I) -> IO CString

foreign import ccall "HROOTHistTH2I.h TH2I_IsA" c_th2i_isa 
  :: (Ptr RawTH2I) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH2I.h TH2I_Paint" c_th2i_paint 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_printObj" c_th2i_printobj 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SaveAs" c_th2i_saveas 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_Write" c_th2i_write 
  :: (Ptr RawTH2I) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetLineColor" c_th2i_getlinecolor 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetLineStyle" c_th2i_getlinestyle 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetLineWidth" c_th2i_getlinewidth 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_ResetAttLine" c_th2i_resetattline 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetLineAttributes" c_th2i_setlineattributes 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetLineColor" c_th2i_setlinecolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetLineStyle" c_th2i_setlinestyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetLineWidth" c_th2i_setlinewidth 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetFillColor" c_th2i_setfillcolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetFillStyle" c_th2i_setfillstyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_GetMarkerColor" c_th2i_getmarkercolor 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetMarkerStyle" c_th2i_getmarkerstyle 
  :: (Ptr RawTH2I) -> IO CInt

foreign import ccall "HROOTHistTH2I.h TH2I_GetMarkerSize" c_th2i_getmarkersize 
  :: (Ptr RawTH2I) -> IO CDouble

foreign import ccall "HROOTHistTH2I.h TH2I_ResetAttMarker" c_th2i_resetattmarker 
  :: (Ptr RawTH2I) -> CString -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMarkerAttributes" c_th2i_setmarkerattributes 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMarkerColor" c_th2i_setmarkercolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMarkerStyle" c_th2i_setmarkerstyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_SetMarkerSize" c_th2i_setmarkersize 
  :: (Ptr RawTH2I) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2I.h TH2I_delete" c_th2i_delete 
  :: (Ptr RawTH2I) -> IO ()