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

-- module HROOT.Class.FFI where

module HROOT.Hist.TH2Poly.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

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

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fill2" c_th2poly_fill2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fill2w" c_th2poly_fill2w 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fillN2" c_th2poly_filln2 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fillRandom2" c_th2poly_fillrandom2 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_findFirstBinAbove2" c_th2poly_findfirstbinabove2 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_findLastBinAbove2" c_th2poly_findlastbinabove2 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FitSlicesX" c_th2poly_fitslicesx 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FitSlicesY" c_th2poly_fitslicesy 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getCorrelationFactor2" c_th2poly_getcorrelationfactor2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getCovariance2" c_th2poly_getcovariance2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_integral2" c_th2poly_integral2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_rebinX2" c_th2poly_rebinx2 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_rebinY2" c_th2poly_rebiny2 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Rebin2D" c_th2poly_rebin2d 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetShowProjectionX" c_th2poly_setshowprojectionx 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetShowProjectionY" c_th2poly_setshowprojectiony 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Add" c_th2poly_add 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_AddBinContent" c_th2poly_addbincontent 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Chi2Test" c_th2poly_chi2test 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ComputeIntegral" c_th2poly_computeintegral 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_DirectoryAutoAdd" c_th2poly_directoryautoadd 
  :: (Ptr RawTH2Poly) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Divide" c_th2poly_divide 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_drawCopyTH1" c_th2poly_drawcopyth1 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTH2Poly)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_DrawNormalized" c_th2poly_drawnormalized 
  :: (Ptr RawTH2Poly) -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_drawPanelTH1" c_th2poly_drawpanelth1 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_BufferEmpty" c_th2poly_bufferempty 
  :: (Ptr RawTH2Poly) -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_evalF" c_th2poly_evalf 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FFT" c_th2poly_fft 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fill1" c_th2poly_fill1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fill1w" c_th2poly_fill1w 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_fillN1" c_th2poly_filln1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FillRandom" c_th2poly_fillrandom 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FindBin" c_th2poly_findbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FindFixBin" c_th2poly_findfixbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FindFirstBinAbove" c_th2poly_findfirstbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FindLastBinAbove" c_th2poly_findlastbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FitPanelTH1" c_th2poly_fitpanelth1 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getNdivisionA" c_th2poly_getndivisiona 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getAxisColorA" c_th2poly_getaxiscolora 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getLabelColorA" c_th2poly_getlabelcolora 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getLabelFontA" c_th2poly_getlabelfonta 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getLabelOffsetA" c_th2poly_getlabeloffseta 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getLabelSizeA" c_th2poly_getlabelsizea 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getTitleFontA" c_th2poly_gettitlefonta 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getTitleOffsetA" c_th2poly_gettitleoffseta 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getTitleSizeA" c_th2poly_gettitlesizea 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getTickLengthA" c_th2poly_getticklengtha 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBarOffset" c_th2poly_getbaroffset 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBarWidth" c_th2poly_getbarwidth 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetContour" c_th2poly_getcontour 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetContourLevel" c_th2poly_getcontourlevel 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetContourLevelPad" c_th2poly_getcontourlevelpad 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBin" c_th2poly_getbin 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinCenter" c_th2poly_getbincenter 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinContent1" c_th2poly_getbincontent1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinContent2" c_th2poly_getbincontent2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinContent3" c_th2poly_getbincontent3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinError1" c_th2poly_getbinerror1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinError2" c_th2poly_getbinerror2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinError3" c_th2poly_getbinerror3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinLowEdge" c_th2poly_getbinlowedge 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetBinWidth" c_th2poly_getbinwidth 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetCellContent" c_th2poly_getcellcontent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetCellError" c_th2poly_getcellerror 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetEntries" c_th2poly_getentries 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetEffectiveEntries" c_th2poly_geteffectiveentries 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetFunction" c_th2poly_getfunction 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetDimension" c_th2poly_getdimension 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetKurtosis" c_th2poly_getkurtosis 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetLowEdge" c_th2poly_getlowedge 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getMaximumTH1" c_th2poly_getmaximumth1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMaximumBin" c_th2poly_getmaximumbin 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMaximumStored" c_th2poly_getmaximumstored 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getMinimumTH1" c_th2poly_getminimumth1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMinimumBin" c_th2poly_getminimumbin 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMinimumStored" c_th2poly_getminimumstored 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMean" c_th2poly_getmean 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMeanError" c_th2poly_getmeanerror 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetNbinsX" c_th2poly_getnbinsx 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetNbinsY" c_th2poly_getnbinsy 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetNbinsZ" c_th2poly_getnbinsz 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_getQuantilesTH1" c_th2poly_getquantilesth1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetRandom" c_th2poly_getrandom 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetStats" c_th2poly_getstats 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetSumOfWeights" c_th2poly_getsumofweights 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetSumw2" c_th2poly_getsumw2 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTArrayD)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetSumw2N" c_th2poly_getsumw2n 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetRMS" c_th2poly_getrms 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetRMSError" c_th2poly_getrmserror 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetSkewness" c_th2poly_getskewness 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_integral1" c_th2poly_integral1 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_interpolate1" c_th2poly_interpolate1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_interpolate2" c_th2poly_interpolate2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_interpolate3" c_th2poly_interpolate3 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_KolmogorovTest" c_th2poly_kolmogorovtest 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_LabelsDeflate" c_th2poly_labelsdeflate 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_LabelsInflate" c_th2poly_labelsinflate 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_LabelsOption" c_th2poly_labelsoption 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_multiflyF" c_th2poly_multiflyf 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Multiply" c_th2poly_multiply 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_PutStats" c_th2poly_putstats 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Rebin" c_th2poly_rebin 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_RebinAxis" c_th2poly_rebinaxis 
  :: (Ptr RawTH2Poly) -> CDouble -> (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Rebuild" c_th2poly_rebuild 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_RecursiveRemove" c_th2poly_recursiveremove 
  :: (Ptr RawTH2Poly) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Reset" c_th2poly_reset 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ResetStats" c_th2poly_resetstats 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Scale" c_th2poly_scale 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setAxisColorA" c_th2poly_setaxiscolora 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetAxisRange" c_th2poly_setaxisrange 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetBarOffset" c_th2poly_setbaroffset 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetBarWidth" c_th2poly_setbarwidth 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinContent1" c_th2poly_setbincontent1 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinContent2" c_th2poly_setbincontent2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinContent3" c_th2poly_setbincontent3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinError1" c_th2poly_setbinerror1 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinError2" c_th2poly_setbinerror2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBinError3" c_th2poly_setbinerror3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBins1" c_th2poly_setbins1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBins2" c_th2poly_setbins2 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setBins3" c_th2poly_setbins3 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetBinsLength" c_th2poly_setbinslength 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetBuffer" c_th2poly_setbuffer 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetCellContent" c_th2poly_setcellcontent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetContent" c_th2poly_setcontent 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetContour" c_th2poly_setcontour 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetContourLevel" c_th2poly_setcontourlevel 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetDirectory" c_th2poly_setdirectory 
  :: (Ptr RawTH2Poly) -> (Ptr RawTDirectory) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetEntries" c_th2poly_setentries 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetError" c_th2poly_seterror 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setLabelColorA" c_th2poly_setlabelcolora 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setLabelSizeA" c_th2poly_setlabelsizea 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setLabelFontA" c_th2poly_setlabelfonta 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_setLabelOffsetA" c_th2poly_setlabeloffseta 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMaximum" c_th2poly_setmaximum 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMinimum" c_th2poly_setminimum 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetNormFactor" c_th2poly_setnormfactor 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetStats" c_th2poly_setstats 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetOption" c_th2poly_setoption 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetXTitle" c_th2poly_setxtitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetYTitle" c_th2poly_setytitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetZTitle" c_th2poly_setztitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ShowBackground" c_th2poly_showbackground 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ShowPeaks" c_th2poly_showpeaks 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Smooth" c_th2poly_smooth 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Sumw2" c_th2poly_sumw2 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Draw" c_th2poly_draw 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_FindObject" c_th2poly_findobject 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetName" c_th2poly_getname 
  :: (Ptr RawTH2Poly) -> IO CString

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_IsA" c_th2poly_isa 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Paint" c_th2poly_paint 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_printObj" c_th2poly_printobj 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SaveAs" c_th2poly_saveas 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_Write" c_th2poly_write 
  :: (Ptr RawTH2Poly) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetLineColor" c_th2poly_getlinecolor 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetLineStyle" c_th2poly_getlinestyle 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetLineWidth" c_th2poly_getlinewidth 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ResetAttLine" c_th2poly_resetattline 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetLineAttributes" c_th2poly_setlineattributes 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetLineColor" c_th2poly_setlinecolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetLineStyle" c_th2poly_setlinestyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetLineWidth" c_th2poly_setlinewidth 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetFillColor" c_th2poly_setfillcolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetFillStyle" c_th2poly_setfillstyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMarkerColor" c_th2poly_getmarkercolor 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMarkerStyle" c_th2poly_getmarkerstyle 
  :: (Ptr RawTH2Poly) -> IO CInt

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_GetMarkerSize" c_th2poly_getmarkersize 
  :: (Ptr RawTH2Poly) -> IO CDouble

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_ResetAttMarker" c_th2poly_resetattmarker 
  :: (Ptr RawTH2Poly) -> CString -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMarkerAttributes" c_th2poly_setmarkerattributes 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMarkerColor" c_th2poly_setmarkercolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMarkerStyle" c_th2poly_setmarkerstyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_SetMarkerSize" c_th2poly_setmarkersize 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()

foreign import ccall "HROOTHistTH2Poly.h TH2Poly_delete" c_th2poly_delete 
  :: (Ptr RawTH2Poly) -> IO ()