{-# LINE 1 "src/HROOT/Hist/TH2D/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Hist.TH2D.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Hist.TH2D.RawType
import HROOT.Hist.TH2D.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

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fill2"
               c_th2d_fill2 :: Ptr RawTH2D -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fill2w"
               c_th2d_fill2w ::
               Ptr RawTH2D -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fillN2"
               c_th2d_filln2 ::
               Ptr RawTH2D ->
                 CInt -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_fillRandom2" c_th2d_fillrandom2 ::
               Ptr RawTH2D -> Ptr RawTH1 -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_findFirstBinAbove2" c_th2d_findfirstbinabove2
               :: Ptr RawTH2D -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_findLastBinAbove2" c_th2d_findlastbinabove2
               :: Ptr RawTH2D -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FitSlicesX" c_th2d_fitslicesx ::
               Ptr RawTH2D ->
                 Ptr RawTF1 ->
                   CInt -> CInt -> CInt -> CString -> Ptr RawTObjArray -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FitSlicesY" c_th2d_fitslicesy ::
               Ptr RawTH2D ->
                 Ptr RawTF1 ->
                   CInt -> CInt -> CInt -> CString -> Ptr RawTObjArray -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getCorrelationFactor2"
               c_th2d_getcorrelationfactor2 ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getCovariance2" c_th2d_getcovariance2 ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_integral2"
               c_th2d_integral2 ::
               Ptr RawTH2D ->
                 CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_rebinX2"
               c_th2d_rebinx2 :: Ptr RawTH2D -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_rebinY2"
               c_th2d_rebiny2 :: Ptr RawTH2D -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Rebin2D"
               c_th2d_rebin2d ::
               Ptr RawTH2D -> CInt -> CInt -> CString -> IO (Ptr RawTH2)

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetShowProjectionX" c_th2d_setshowprojectionx
               :: Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetShowProjectionY" c_th2d_setshowprojectiony
               :: Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Add"
               c_th2d_add :: Ptr RawTH2D -> Ptr RawTH1 -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_AddBinContent" c_th2d_addbincontent ::
               Ptr RawTH2D -> CInt -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Chi2Test"
               c_th2d_chi2test ::
               Ptr RawTH2D -> Ptr RawTH1 -> CString -> Ptr CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_DirectoryAutoAdd" c_th2d_directoryautoadd ::
               Ptr RawTH2D -> Ptr RawTDirectory -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Divide"
               c_th2d_divide ::
               Ptr RawTH2D ->
                 Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_drawCopyTH1" c_th2d_drawcopyth1 ::
               Ptr RawTH2D -> CString -> IO (Ptr RawTH2D)

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_DrawNormalized" c_th2d_drawnormalized ::
               Ptr RawTH2D -> CString -> CDouble -> IO (Ptr RawTH1)

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_drawPanelTH1" c_th2d_drawpanelth1 ::
               Ptr RawTH2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_BufferEmpty" c_th2d_bufferempty ::
               Ptr RawTH2D -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_evalF"
               c_th2d_evalf :: Ptr RawTH2D -> Ptr RawTF1 -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_FFT"
               c_th2d_fft ::
               Ptr RawTH2D -> Ptr RawTH1 -> CString -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fill1"
               c_th2d_fill1 :: Ptr RawTH2D -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fill1w"
               c_th2d_fill1w :: Ptr RawTH2D -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_fillN1"
               c_th2d_filln1 ::
               Ptr RawTH2D -> CInt -> Ptr CDouble -> Ptr CDouble -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FillRandom" c_th2d_fillrandom ::
               Ptr RawTH2D -> Ptr RawTH1 -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_FindBin"
               c_th2d_findbin ::
               Ptr RawTH2D -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FindFixBin" c_th2d_findfixbin ::
               Ptr RawTH2D -> CDouble -> CDouble -> CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FindFirstBinAbove" c_th2d_findfirstbinabove
               :: Ptr RawTH2D -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FindLastBinAbove" c_th2d_findlastbinabove ::
               Ptr RawTH2D -> CDouble -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Fit"
               c_th2d_fit ::
               Ptr RawTH2D ->
                 Ptr RawTF1 -> CString -> CString -> CDouble -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FitPanelTH1" c_th2d_fitpanelth1 ::
               Ptr RawTH2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getNdivisionA" c_th2d_getndivisiona ::
               Ptr RawTH2D -> CString -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getAxisColorA" c_th2d_getaxiscolora ::
               Ptr RawTH2D -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getLabelColorA" c_th2d_getlabelcolora ::
               Ptr RawTH2D -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getLabelFontA" c_th2d_getlabelfonta ::
               Ptr RawTH2D -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getLabelOffsetA" c_th2d_getlabeloffseta ::
               Ptr RawTH2D -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getLabelSizeA" c_th2d_getlabelsizea ::
               Ptr RawTH2D -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getTitleFontA" c_th2d_gettitlefonta ::
               Ptr RawTH2D -> CString -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getTitleOffsetA" c_th2d_gettitleoffseta ::
               Ptr RawTH2D -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getTitleSizeA" c_th2d_gettitlesizea ::
               Ptr RawTH2D -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getTickLengthA" c_th2d_getticklengtha ::
               Ptr RawTH2D -> CString -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBarOffset" c_th2d_getbaroffset ::
               Ptr RawTH2D -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBarWidth" c_th2d_getbarwidth ::
               Ptr RawTH2D -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetContour" c_th2d_getcontour ::
               Ptr RawTH2D -> Ptr CDouble -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetContourLevel" c_th2d_getcontourlevel ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetContourLevelPad" c_th2d_getcontourlevelpad
               :: Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetBin"
               c_th2d_getbin :: Ptr RawTH2D -> CInt -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinCenter" c_th2d_getbincenter ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinContent1" c_th2d_getbincontent1 ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinContent2" c_th2d_getbincontent2 ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinContent3" c_th2d_getbincontent3 ::
               Ptr RawTH2D -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinError1" c_th2d_getbinerror1 ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinError2" c_th2d_getbinerror2 ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinError3" c_th2d_getbinerror3 ::
               Ptr RawTH2D -> CInt -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinLowEdge" c_th2d_getbinlowedge ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetBinWidth" c_th2d_getbinwidth ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetCellContent" c_th2d_getcellcontent ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetCellError" c_th2d_getcellerror ::
               Ptr RawTH2D -> CInt -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetEntries" c_th2d_getentries ::
               Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetEffectiveEntries"
               c_th2d_geteffectiveentries :: Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetFunction" c_th2d_getfunction ::
               Ptr RawTH2D -> CString -> IO (Ptr RawTF1)

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetDimension" c_th2d_getdimension ::
               Ptr RawTH2D -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetKurtosis" c_th2d_getkurtosis ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetLowEdge" c_th2d_getlowedge ::
               Ptr RawTH2D -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getMaximumTH1" c_th2d_getmaximumth1 ::
               Ptr RawTH2D -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMaximumBin" c_th2d_getmaximumbin ::
               Ptr RawTH2D -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMaximumStored" c_th2d_getmaximumstored ::
               Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getMinimumTH1" c_th2d_getminimumth1 ::
               Ptr RawTH2D -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMinimumBin" c_th2d_getminimumbin ::
               Ptr RawTH2D -> IO CInt

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMinimumStored" c_th2d_getminimumstored ::
               Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetMean"
               c_th2d_getmean :: Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMeanError" c_th2d_getmeanerror ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetNbinsX"
               c_th2d_getnbinsx :: Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetNbinsY"
               c_th2d_getnbinsy :: Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetNbinsZ"
               c_th2d_getnbinsz :: Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_getQuantilesTH1" c_th2d_getquantilesth1 ::
               Ptr RawTH2D -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetRandom"
               c_th2d_getrandom :: Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetStats"
               c_th2d_getstats :: Ptr RawTH2D -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetSumOfWeights" c_th2d_getsumofweights ::
               Ptr RawTH2D -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetSumw2"
               c_th2d_getsumw2 :: Ptr RawTH2D -> IO (Ptr RawTArrayD)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetSumw2N"
               c_th2d_getsumw2n :: Ptr RawTH2D -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetRMS"
               c_th2d_getrms :: Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetRMSError" c_th2d_getrmserror ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetSkewness" c_th2d_getskewness ::
               Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_interpolate3" c_th2d_interpolate3 ::
               Ptr RawTH2D -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_KolmogorovTest" c_th2d_kolmogorovtest ::
               Ptr RawTH2D -> Ptr RawTH1 -> CString -> IO CDouble

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_LabelsDeflate" c_th2d_labelsdeflate ::
               Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_LabelsInflate" c_th2d_labelsinflate ::
               Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_LabelsOption" c_th2d_labelsoption ::
               Ptr RawTH2D -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_multiflyF"
               c_th2d_multiflyf :: Ptr RawTH2D -> Ptr RawTF1 -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Multiply"
               c_th2d_multiply ::
               Ptr RawTH2D ->
                 Ptr RawTH1 -> Ptr RawTH1 -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_PutStats"
               c_th2d_putstats :: Ptr RawTH2D -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Rebin"
               c_th2d_rebin ::
               Ptr RawTH2D -> CInt -> CString -> Ptr CDouble -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_RebinAxis"
               c_th2d_rebinaxis :: Ptr RawTH2D -> CDouble -> Ptr RawTAxis -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Rebuild"
               c_th2d_rebuild :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_RecursiveRemove" c_th2d_recursiveremove ::
               Ptr RawTH2D -> Ptr RawTObject -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Reset"
               c_th2d_reset :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_ResetStats" c_th2d_resetstats ::
               Ptr RawTH2D -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Scale"
               c_th2d_scale :: Ptr RawTH2D -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setAxisColorA" c_th2d_setaxiscolora ::
               Ptr RawTH2D -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetAxisRange" c_th2d_setaxisrange ::
               Ptr RawTH2D -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetBarOffset" c_th2d_setbaroffset ::
               Ptr RawTH2D -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetBarWidth" c_th2d_setbarwidth ::
               Ptr RawTH2D -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinContent1" c_th2d_setbincontent1 ::
               Ptr RawTH2D -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinContent2" c_th2d_setbincontent2 ::
               Ptr RawTH2D -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinContent3" c_th2d_setbincontent3 ::
               Ptr RawTH2D -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinError1" c_th2d_setbinerror1 ::
               Ptr RawTH2D -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinError2" c_th2d_setbinerror2 ::
               Ptr RawTH2D -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setBinError3" c_th2d_setbinerror3 ::
               Ptr RawTH2D -> CInt -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_setBins1"
               c_th2d_setbins1 :: Ptr RawTH2D -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_setBins2"
               c_th2d_setbins2 ::
               Ptr RawTH2D -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_setBins3"
               c_th2d_setbins3 ::
               Ptr RawTH2D ->
                 CInt ->
                   Ptr CDouble -> CInt -> Ptr CDouble -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetBinsLength" c_th2d_setbinslength ::
               Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetBuffer"
               c_th2d_setbuffer :: Ptr RawTH2D -> CInt -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetCellContent" c_th2d_setcellcontent ::
               Ptr RawTH2D -> CInt -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetContent" c_th2d_setcontent ::
               Ptr RawTH2D -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetContour" c_th2d_setcontour ::
               Ptr RawTH2D -> CInt -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetContourLevel" c_th2d_setcontourlevel ::
               Ptr RawTH2D -> CInt -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetDirectory" c_th2d_setdirectory ::
               Ptr RawTH2D -> Ptr RawTDirectory -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetEntries" c_th2d_setentries ::
               Ptr RawTH2D -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetError"
               c_th2d_seterror :: Ptr RawTH2D -> Ptr CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setLabelColorA" c_th2d_setlabelcolora ::
               Ptr RawTH2D -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setLabelSizeA" c_th2d_setlabelsizea ::
               Ptr RawTH2D -> CFloat -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setLabelFontA" c_th2d_setlabelfonta ::
               Ptr RawTH2D -> CShort -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_setLabelOffsetA" c_th2d_setlabeloffseta ::
               Ptr RawTH2D -> CFloat -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMaximum" c_th2d_setmaximum ::
               Ptr RawTH2D -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMinimum" c_th2d_setminimum ::
               Ptr RawTH2D -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetNormFactor" c_th2d_setnormfactor ::
               Ptr RawTH2D -> CDouble -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetStats"
               c_th2d_setstats :: Ptr RawTH2D -> CBool -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetOption"
               c_th2d_setoption :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetXTitle"
               c_th2d_setxtitle :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetYTitle"
               c_th2d_setytitle :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetZTitle"
               c_th2d_setztitle :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_ShowBackground" c_th2d_showbackground ::
               Ptr RawTH2D -> CInt -> CString -> IO (Ptr RawTH1)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_ShowPeaks"
               c_th2d_showpeaks ::
               Ptr RawTH2D -> CDouble -> CString -> CDouble -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Smooth"
               c_th2d_smooth :: Ptr RawTH2D -> CInt -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Sumw2"
               c_th2d_sumw2 :: Ptr RawTH2D -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetName"
               c_th2d_setname :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetNameTitle" c_th2d_setnametitle ::
               Ptr RawTH2D -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetTitle"
               c_th2d_settitle :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetLineColor" c_th2d_getlinecolor ::
               Ptr RawTH2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetLineStyle" c_th2d_getlinestyle ::
               Ptr RawTH2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetLineWidth" c_th2d_getlinewidth ::
               Ptr RawTH2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_ResetAttLine" c_th2d_resetattline ::
               Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetLineAttributes" c_th2d_setlineattributes
               :: Ptr RawTH2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetLineColor" c_th2d_setlinecolor ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetLineStyle" c_th2d_setlinestyle ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetLineWidth" c_th2d_setlinewidth ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetFillColor" c_th2d_setfillcolor ::
               Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetFillStyle" c_th2d_setfillstyle ::
               Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMarkerColor" c_th2d_getmarkercolor ::
               Ptr RawTH2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMarkerStyle" c_th2d_getmarkerstyle ::
               Ptr RawTH2D -> IO CShort

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_GetMarkerSize" c_th2d_getmarkersize ::
               Ptr RawTH2D -> IO CFloat

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_ResetAttMarker" c_th2d_resetattmarker ::
               Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMarkerAttributes"
               c_th2d_setmarkerattributes :: Ptr RawTH2D -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMarkerColor" c_th2d_setmarkercolor ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMarkerStyle" c_th2d_setmarkerstyle ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_SetMarkerSize" c_th2d_setmarkersize ::
               Ptr RawTH2D -> CShort -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Clear"
               c_th2d_clear :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Draw"
               c_th2d_draw :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible
               "HROOTHistTH2D.h TH2D_FindObject" c_th2d_findobject ::
               Ptr RawTH2D -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetName"
               c_th2d_getname :: Ptr RawTH2D -> IO CString

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_IsA"
               c_th2d_isa :: Ptr RawTH2D -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Paint"
               c_th2d_paint :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_printObj"
               c_th2d_printobj :: Ptr RawTH2D -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SaveAs"
               c_th2d_saveas :: Ptr RawTH2D -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Write"
               c_th2d_write :: Ptr RawTH2D -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_Write_"
               c_th2d_write_ :: Ptr RawTH2D -> IO CInt

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_delete"
               c_th2d_delete :: Ptr RawTH2D -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_GetAt"
               c_th2d_getat :: Ptr RawTH2D -> CInt -> IO CDouble

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetArray"
               c_th2d_setarray :: Ptr RawTH2D -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_SetAt"
               c_th2d_setat :: Ptr RawTH2D -> CDouble -> CInt -> IO ()

foreign import ccall interruptible "HROOTHistTH2D.h TH2D_newTH2D"
               c_th2d_newth2d ::
               CString ->
                 CString ->
                   CInt ->
                     CDouble ->
                       CDouble -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH2D)