{-# LINE 1 "src/HROOT/Function.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/HROOT/Function.hsc" #-}

module HROOT.Function where

import Foreign.C            
import Foreign.Ptr

import HROOT.Type


{-# LINE 11 "src/HROOT/Function.hsc" #-}



foreign import ccall "HROOT.h TObject_delete" c_tobject_delete 
  :: (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TObject_newTObject" c_tobject_newtobject 
  :: IO (Ptr RawTObject)
foreign import ccall "HROOT.h TObject_GetName" c_tobject_getname 
  :: (Ptr RawTObject) -> IO CString
foreign import ccall "HROOT.h TObject_Draw" c_tobject_draw 
  :: (Ptr RawTObject) -> CString -> IO ()
foreign import ccall "HROOT.h TObject_FindObject" c_tobject_findobject 
  :: (Ptr RawTObject) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TObject_SaveAs" c_tobject_saveas 
  :: (Ptr RawTObject) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TObject_Write" c_tobject_write 
  :: (Ptr RawTObject) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOT.h TNamed_GetName" c_tnamed_getname 
  :: (Ptr RawTNamed) -> IO CString
foreign import ccall "HROOT.h TNamed_Draw" c_tnamed_draw 
  :: (Ptr RawTNamed) -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_FindObject" c_tnamed_findobject 
  :: (Ptr RawTNamed) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNamed_SaveAs" c_tnamed_saveas 
  :: (Ptr RawTNamed) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_Write" c_tnamed_write 
  :: (Ptr RawTNamed) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNamed_delete" c_tnamed_delete 
  :: (Ptr RawTNamed) -> IO ()
foreign import ccall "HROOT.h TNamed_newTNamed" c_tnamed_newtnamed 
  :: CString -> CString -> IO (Ptr RawTNamed)
foreign import ccall "HROOT.h TNamed_SetTitle" c_tnamed_settitle 
  :: (Ptr RawTNamed) -> CString -> IO ()

foreign import ccall "HROOT.h TFormula_SetTitle" c_tformula_settitle 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_GetName" c_tformula_getname 
  :: (Ptr RawTFormula) -> IO CString
foreign import ccall "HROOT.h TFormula_Draw" c_tformula_draw 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_FindObject" c_tformula_findobject 
  :: (Ptr RawTFormula) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFormula_SaveAs" c_tformula_saveas 
  :: (Ptr RawTFormula) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_Write" c_tformula_write 
  :: (Ptr RawTFormula) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFormula_delete" c_tformula_delete 
  :: (Ptr RawTFormula) -> IO ()
foreign import ccall "HROOT.h TFormula_newTFormula" c_tformula_newtformula 
  :: CString -> CString -> IO (Ptr RawTFormula)
foreign import ccall "HROOT.h TFormula_GetParameter" c_tformula_getparameter 
  :: (Ptr RawTFormula) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TFormula_SetParameter" c_tformula_setparameter 
  :: (Ptr RawTFormula) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOT.h TAtt3D_delete" c_tatt3d_delete 
  :: (Ptr RawTAtt3D) -> IO ()

foreign import ccall "HROOT.h TAttAxis_delete" c_tattaxis_delete 
  :: (Ptr RawTAttAxis) -> IO ()
foreign import ccall "HROOT.h TAttAxis_newTAttAxis" c_tattaxis_newtattaxis 
  :: IO (Ptr RawTAttAxis)
foreign import ccall "HROOT.h TAttAxis_SetLabelColor" c_tattaxis_setlabelcolor 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetLabelSize" c_tattaxis_setlabelsize 
  :: (Ptr RawTAttAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetTickLength" c_tattaxis_setticklength 
  :: (Ptr RawTAttAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetTitleOffset" c_tattaxis_settitleoffset 
  :: (Ptr RawTAttAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetNdivisions" c_tattaxis_setndivisions 
  :: (Ptr RawTAttAxis) -> CInt -> CInt -> IO ()

foreign import ccall "HROOT.h TAttBBox_delete" c_tattbbox_delete 
  :: (Ptr RawTAttBBox) -> IO ()

foreign import ccall "HROOT.h TAttCanvas_delete" c_tattcanvas_delete 
  :: (Ptr RawTAttCanvas) -> IO ()
foreign import ccall "HROOT.h TAttCanvas_newTAttCanvas" c_tattcanvas_newtattcanvas 
  :: IO (Ptr RawTAttCanvas)

foreign import ccall "HROOT.h TAttFill_delete" c_tattfill_delete 
  :: (Ptr RawTAttFill) -> IO ()
foreign import ccall "HROOT.h TAttFill_newTAttFill" c_tattfill_newtattfill 
  :: CInt -> CInt -> IO (Ptr RawTAttFill)
foreign import ccall "HROOT.h TAttFill_SetFillColor" c_tattfill_setfillcolor 
  :: (Ptr RawTAttFill) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttFill_SetFillStyle" c_tattfill_setfillstyle 
  :: (Ptr RawTAttFill) -> CInt -> IO ()

foreign import ccall "HROOT.h TAttImage_delete" c_tattimage_delete 
  :: (Ptr RawTAttImage) -> IO ()

foreign import ccall "HROOT.h TAttLine_delete" c_tattline_delete 
  :: (Ptr RawTAttLine) -> IO ()
foreign import ccall "HROOT.h TAttLine_newTAttLine" c_tattline_newtattline 
  :: CInt -> CInt -> CInt -> IO (Ptr RawTAttLine)
foreign import ccall "HROOT.h TAttLine_SetLineColor" c_tattline_setlinecolor 
  :: (Ptr RawTAttLine) -> CInt -> IO ()

foreign import ccall "HROOT.h TAttMarker_delete" c_tattmarker_delete 
  :: (Ptr RawTAttMarker) -> IO ()
foreign import ccall "HROOT.h TAttMarker_newTAttMarker" c_tattmarker_newtattmarker 
  :: CInt -> CInt -> CInt -> IO (Ptr RawTAttMarker)

foreign import ccall "HROOT.h TAttPad_delete" c_tattpad_delete 
  :: (Ptr RawTAttPad) -> IO ()
foreign import ccall "HROOT.h TAttPad_newTAttPad" c_tattpad_newtattpad 
  :: IO (Ptr RawTAttPad)

foreign import ccall "HROOT.h TAttParticle_SetTitle" c_tattparticle_settitle 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_GetName" c_tattparticle_getname 
  :: (Ptr RawTAttParticle) -> IO CString
foreign import ccall "HROOT.h TAttParticle_Draw" c_tattparticle_draw 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_FindObject" c_tattparticle_findobject 
  :: (Ptr RawTAttParticle) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TAttParticle_SaveAs" c_tattparticle_saveas 
  :: (Ptr RawTAttParticle) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_Write" c_tattparticle_write 
  :: (Ptr RawTAttParticle) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TAttParticle_delete" c_tattparticle_delete 
  :: (Ptr RawTAttParticle) -> IO ()

foreign import ccall "HROOT.h TAttText_delete" c_tatttext_delete 
  :: (Ptr RawTAttText) -> IO ()
foreign import ccall "HROOT.h TAttText_newTAttText" c_tatttext_newtatttext 
  :: CInt -> CDouble -> CInt -> CInt -> CDouble -> IO (Ptr RawTAttText)
foreign import ccall "HROOT.h TAttText_SetTextColor" c_tatttext_settextcolor 
  :: (Ptr RawTAttText) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextAlign" c_tatttext_settextalign 
  :: (Ptr RawTAttText) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextSize" c_tatttext_settextsize 
  :: (Ptr RawTAttText) -> CDouble -> IO ()

foreign import ccall "HROOT.h THStack_SetTitle" c_thstack_settitle 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_GetName" c_thstack_getname 
  :: (Ptr RawTHStack) -> IO CString
foreign import ccall "HROOT.h THStack_Draw" c_thstack_draw 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_FindObject" c_thstack_findobject 
  :: (Ptr RawTHStack) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h THStack_SaveAs" c_thstack_saveas 
  :: (Ptr RawTHStack) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h THStack_Write" c_thstack_write 
  :: (Ptr RawTHStack) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h THStack_delete" c_thstack_delete 
  :: (Ptr RawTHStack) -> IO ()
foreign import ccall "HROOT.h THStack_newTHStack" c_thstack_newthstack 
  :: CString -> CString -> IO (Ptr RawTHStack)

foreign import ccall "HROOT.h TF1_GetParameter" c_tf1_getparameter 
  :: (Ptr RawTF1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_SetParameter" c_tf1_setparameter 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetLineColor" c_tf1_setlinecolor 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetFillColor" c_tf1_setfillcolor 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetFillStyle" c_tf1_setfillstyle 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetTitle" c_tf1_settitle 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_GetName" c_tf1_getname 
  :: (Ptr RawTF1) -> IO CString
foreign import ccall "HROOT.h TF1_Draw" c_tf1_draw 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_FindObject" c_tf1_findobject 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TF1_SaveAs" c_tf1_saveas 
  :: (Ptr RawTF1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TF1_Write" c_tf1_write 
  :: (Ptr RawTF1) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TF1_delete" c_tf1_delete 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_newTF1" c_tf1_newtf1 
  :: CString -> CString -> CDouble -> CDouble -> IO (Ptr RawTF1)

foreign import ccall "HROOT.h TGraph_SetTitle" c_tgraph_settitle 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_SetLineColor" c_tgraph_setlinecolor 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetFillColor" c_tgraph_setfillcolor 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetFillStyle" c_tgraph_setfillstyle 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_GetName" c_tgraph_getname 
  :: (Ptr RawTGraph) -> IO CString
foreign import ccall "HROOT.h TGraph_Draw" c_tgraph_draw 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_FindObject" c_tgraph_findobject 
  :: (Ptr RawTGraph) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraph_SaveAs" c_tgraph_saveas 
  :: (Ptr RawTGraph) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_Write" c_tgraph_write 
  :: (Ptr RawTGraph) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraph_delete" c_tgraph_delete 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_newTGraph" c_tgraph_newtgraph 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraph)

foreign import ccall "HROOT.h TGraphAsymmErrors_SetTitle" c_tgraphasymmerrors_settitle 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetLineColor" c_tgraphasymmerrors_setlinecolor 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetFillColor" c_tgraphasymmerrors_setfillcolor 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetFillStyle" c_tgraphasymmerrors_setfillstyle 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_GetName" c_tgraphasymmerrors_getname 
  :: (Ptr RawTGraphAsymmErrors) -> IO CString
foreign import ccall "HROOT.h TGraphAsymmErrors_Draw" c_tgraphasymmerrors_draw 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_FindObject" c_tgraphasymmerrors_findobject 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphAsymmErrors_SaveAs" c_tgraphasymmerrors_saveas 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Write" c_tgraphasymmerrors_write 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_delete" c_tgraphasymmerrors_delete 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_newTGraphAsymmErrors" c_tgraphasymmerrors_newtgraphasymmerrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphAsymmErrors)

foreign import ccall "HROOT.h TCutG_SetTitle" c_tcutg_settitle 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_SetLineColor" c_tcutg_setlinecolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetFillColor" c_tcutg_setfillcolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetFillStyle" c_tcutg_setfillstyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_GetName" c_tcutg_getname 
  :: (Ptr RawTCutG) -> IO CString
foreign import ccall "HROOT.h TCutG_Draw" c_tcutg_draw 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_FindObject" c_tcutg_findobject 
  :: (Ptr RawTCutG) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCutG_SaveAs" c_tcutg_saveas 
  :: (Ptr RawTCutG) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_Write" c_tcutg_write 
  :: (Ptr RawTCutG) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCutG_delete" c_tcutg_delete 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_newTCutG" c_tcutg_newtcutg 
  :: CString -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTCutG)

foreign import ccall "HROOT.h TGraphBentErrors_SetTitle" c_tgraphbenterrors_settitle 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetLineColor" c_tgraphbenterrors_setlinecolor 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetFillColor" c_tgraphbenterrors_setfillcolor 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetFillStyle" c_tgraphbenterrors_setfillstyle 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_GetName" c_tgraphbenterrors_getname 
  :: (Ptr RawTGraphBentErrors) -> IO CString
foreign import ccall "HROOT.h TGraphBentErrors_Draw" c_tgraphbenterrors_draw 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_FindObject" c_tgraphbenterrors_findobject 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphBentErrors_SaveAs" c_tgraphbenterrors_saveas 
  :: (Ptr RawTGraphBentErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Write" c_tgraphbenterrors_write 
  :: (Ptr RawTGraphBentErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_delete" c_tgraphbenterrors_delete 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_newTGraphBentErrors" c_tgraphbenterrors_newtgraphbenterrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphBentErrors)

foreign import ccall "HROOT.h TGraphErrors_SetTitle" c_tgrapherrors_settitle 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetLineColor" c_tgrapherrors_setlinecolor 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetFillColor" c_tgrapherrors_setfillcolor 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetFillStyle" c_tgrapherrors_setfillstyle 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_GetName" c_tgrapherrors_getname 
  :: (Ptr RawTGraphErrors) -> IO CString
foreign import ccall "HROOT.h TGraphErrors_Draw" c_tgrapherrors_draw 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_FindObject" c_tgrapherrors_findobject 
  :: (Ptr RawTGraphErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphErrors_SaveAs" c_tgrapherrors_saveas 
  :: (Ptr RawTGraphErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Write" c_tgrapherrors_write 
  :: (Ptr RawTGraphErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_delete" c_tgrapherrors_delete 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_newTGraphErrors" c_tgrapherrors_newtgrapherrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphErrors)

foreign import ccall "HROOT.h TGraphPolar_SetTitle" c_tgraphpolar_settitle 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetLineColor" c_tgraphpolar_setlinecolor 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetFillColor" c_tgraphpolar_setfillcolor 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetFillStyle" c_tgraphpolar_setfillstyle 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_GetName" c_tgraphpolar_getname 
  :: (Ptr RawTGraphPolar) -> IO CString
foreign import ccall "HROOT.h TGraphPolar_Draw" c_tgraphpolar_draw 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_FindObject" c_tgraphpolar_findobject 
  :: (Ptr RawTGraphPolar) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphPolar_SaveAs" c_tgraphpolar_saveas 
  :: (Ptr RawTGraphPolar) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Write" c_tgraphpolar_write 
  :: (Ptr RawTGraphPolar) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_delete" c_tgraphpolar_delete 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_newTGraphPolar" c_tgraphpolar_newtgraphpolar 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphPolar)

foreign import ccall "HROOT.h TGraphQQ_SetTitle" c_tgraphqq_settitle 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetLineColor" c_tgraphqq_setlinecolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetFillColor" c_tgraphqq_setfillcolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetFillStyle" c_tgraphqq_setfillstyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_GetName" c_tgraphqq_getname 
  :: (Ptr RawTGraphQQ) -> IO CString
foreign import ccall "HROOT.h TGraphQQ_Draw" c_tgraphqq_draw 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_FindObject" c_tgraphqq_findobject 
  :: (Ptr RawTGraphQQ) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphQQ_SaveAs" c_tgraphqq_saveas 
  :: (Ptr RawTGraphQQ) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Write" c_tgraphqq_write 
  :: (Ptr RawTGraphQQ) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_delete" c_tgraphqq_delete 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_newTGraphQQ" c_tgraphqq_newtgraphqq 
  :: CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO (Ptr RawTGraphQQ)

foreign import ccall "HROOT.h TEllipse_GetName" c_tellipse_getname 
  :: (Ptr RawTEllipse) -> IO CString
foreign import ccall "HROOT.h TEllipse_Draw" c_tellipse_draw 
  :: (Ptr RawTEllipse) -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_FindObject" c_tellipse_findobject 
  :: (Ptr RawTEllipse) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEllipse_SaveAs" c_tellipse_saveas 
  :: (Ptr RawTEllipse) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_Write" c_tellipse_write 
  :: (Ptr RawTEllipse) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEllipse_SetLineColor" c_tellipse_setlinecolor 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetFillColor" c_tellipse_setfillcolor 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetFillStyle" c_tellipse_setfillstyle 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_delete" c_tellipse_delete 
  :: (Ptr RawTEllipse) -> IO ()
foreign import ccall "HROOT.h TEllipse_newTEllipse" c_tellipse_newtellipse 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTEllipse)

foreign import ccall "HROOT.h TArc_GetName" c_tarc_getname 
  :: (Ptr RawTArc) -> IO CString
foreign import ccall "HROOT.h TArc_Draw" c_tarc_draw 
  :: (Ptr RawTArc) -> CString -> IO ()
foreign import ccall "HROOT.h TArc_FindObject" c_tarc_findobject 
  :: (Ptr RawTArc) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TArc_SaveAs" c_tarc_saveas 
  :: (Ptr RawTArc) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TArc_Write" c_tarc_write 
  :: (Ptr RawTArc) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TArc_SetLineColor" c_tarc_setlinecolor 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetFillColor" c_tarc_setfillcolor 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetFillStyle" c_tarc_setfillstyle 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_delete" c_tarc_delete 
  :: (Ptr RawTArc) -> IO ()
foreign import ccall "HROOT.h TArc_newTArc" c_tarc_newtarc 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTArc)

foreign import ccall "HROOT.h TCrown_GetName" c_tcrown_getname 
  :: (Ptr RawTCrown) -> IO CString
foreign import ccall "HROOT.h TCrown_Draw" c_tcrown_draw 
  :: (Ptr RawTCrown) -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_FindObject" c_tcrown_findobject 
  :: (Ptr RawTCrown) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCrown_SaveAs" c_tcrown_saveas 
  :: (Ptr RawTCrown) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_Write" c_tcrown_write 
  :: (Ptr RawTCrown) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCrown_SetLineColor" c_tcrown_setlinecolor 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetFillColor" c_tcrown_setfillcolor 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetFillStyle" c_tcrown_setfillstyle 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_delete" c_tcrown_delete 
  :: (Ptr RawTCrown) -> IO ()
foreign import ccall "HROOT.h TCrown_newTCrown" c_tcrown_newtcrown 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCrown)

foreign import ccall "HROOT.h TLine_GetName" c_tline_getname 
  :: (Ptr RawTLine) -> IO CString
foreign import ccall "HROOT.h TLine_Draw" c_tline_draw 
  :: (Ptr RawTLine) -> CString -> IO ()
foreign import ccall "HROOT.h TLine_FindObject" c_tline_findobject 
  :: (Ptr RawTLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLine_SaveAs" c_tline_saveas 
  :: (Ptr RawTLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLine_Write" c_tline_write 
  :: (Ptr RawTLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLine_SetLineColor" c_tline_setlinecolor 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_delete" c_tline_delete 
  :: (Ptr RawTLine) -> IO ()
foreign import ccall "HROOT.h TLine_newTLine" c_tline_newtline 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)

foreign import ccall "HROOT.h TArrow_SetFillColor" c_tarrow_setfillcolor 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_SetFillStyle" c_tarrow_setfillstyle 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_GetName" c_tarrow_getname 
  :: (Ptr RawTArrow) -> IO CString
foreign import ccall "HROOT.h TArrow_Draw" c_tarrow_draw 
  :: (Ptr RawTArrow) -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_FindObject" c_tarrow_findobject 
  :: (Ptr RawTArrow) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TArrow_SaveAs" c_tarrow_saveas 
  :: (Ptr RawTArrow) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_Write" c_tarrow_write 
  :: (Ptr RawTArrow) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TArrow_SetLineColor" c_tarrow_setlinecolor 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_delete" c_tarrow_delete 
  :: (Ptr RawTArrow) -> IO ()
foreign import ccall "HROOT.h TArrow_newTArrow" c_tarrow_newtarrow 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTArrow)

foreign import ccall "HROOT.h TGaxis_SetTextColor" c_tgaxis_settextcolor 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextAlign" c_tgaxis_settextalign 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextSize" c_tgaxis_settextsize 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_GetName" c_tgaxis_getname 
  :: (Ptr RawTGaxis) -> IO CString
foreign import ccall "HROOT.h TGaxis_Draw" c_tgaxis_draw 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_FindObject" c_tgaxis_findobject 
  :: (Ptr RawTGaxis) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGaxis_SaveAs" c_tgaxis_saveas 
  :: (Ptr RawTGaxis) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_Write" c_tgaxis_write 
  :: (Ptr RawTGaxis) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGaxis_SetLineColor" c_tgaxis_setlinecolor 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_delete" c_tgaxis_delete 
  :: (Ptr RawTGaxis) -> IO ()
foreign import ccall "HROOT.h TGaxis_newTGaxis" c_tgaxis_newtgaxis 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> CDouble -> IO (Ptr RawTGaxis)

foreign import ccall "HROOT.h TShape_SetTitle" c_tshape_settitle 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_SetLineColor" c_tshape_setlinecolor 
  :: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TShape_SetFillColor" c_tshape_setfillcolor 
  :: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TShape_SetFillStyle" c_tshape_setfillstyle 
  :: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TShape_GetName" c_tshape_getname 
  :: (Ptr RawTShape) -> IO CString
foreign import ccall "HROOT.h TShape_Draw" c_tshape_draw 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_FindObject" c_tshape_findobject 
  :: (Ptr RawTShape) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TShape_SaveAs" c_tshape_saveas 
  :: (Ptr RawTShape) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TShape_Write" c_tshape_write 
  :: (Ptr RawTShape) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TShape_delete" c_tshape_delete 
  :: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOT.h TShape_newTShape" c_tshape_newtshape 
  :: CString -> CString -> CString -> IO (Ptr RawTShape)

foreign import ccall "HROOT.h TBRIK_SetTitle" c_tbrik_settitle 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_SetLineColor" c_tbrik_setlinecolor 
  :: (Ptr RawTBRIK) -> CInt -> IO ()
foreign import ccall "HROOT.h TBRIK_SetFillColor" c_tbrik_setfillcolor 
  :: (Ptr RawTBRIK) -> CInt -> IO ()
foreign import ccall "HROOT.h TBRIK_SetFillStyle" c_tbrik_setfillstyle 
  :: (Ptr RawTBRIK) -> CInt -> IO ()
foreign import ccall "HROOT.h TBRIK_GetName" c_tbrik_getname 
  :: (Ptr RawTBRIK) -> IO CString
foreign import ccall "HROOT.h TBRIK_Draw" c_tbrik_draw 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_FindObject" c_tbrik_findobject 
  :: (Ptr RawTBRIK) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBRIK_SaveAs" c_tbrik_saveas 
  :: (Ptr RawTBRIK) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_Write" c_tbrik_write 
  :: (Ptr RawTBRIK) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBRIK_delete" c_tbrik_delete 
  :: (Ptr RawTBRIK) -> IO ()
foreign import ccall "HROOT.h TBRIK_newTBRIK" c_tbrik_newtbrik 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTBRIK)

foreign import ccall "HROOT.h TTUBE_SetTitle" c_ttube_settitle 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_SetLineColor" c_ttube_setlinecolor 
  :: (Ptr RawTTUBE) -> CInt -> IO ()
foreign import ccall "HROOT.h TTUBE_SetFillColor" c_ttube_setfillcolor 
  :: (Ptr RawTTUBE) -> CInt -> IO ()
foreign import ccall "HROOT.h TTUBE_SetFillStyle" c_ttube_setfillstyle 
  :: (Ptr RawTTUBE) -> CInt -> IO ()
foreign import ccall "HROOT.h TTUBE_GetName" c_ttube_getname 
  :: (Ptr RawTTUBE) -> IO CString
foreign import ccall "HROOT.h TTUBE_Draw" c_ttube_draw 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_FindObject" c_ttube_findobject 
  :: (Ptr RawTTUBE) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTUBE_SaveAs" c_ttube_saveas 
  :: (Ptr RawTTUBE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_Write" c_ttube_write 
  :: (Ptr RawTTUBE) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTUBE_delete" c_ttube_delete 
  :: (Ptr RawTTUBE) -> IO ()
foreign import ccall "HROOT.h TTUBE_newTTUBE" c_ttube_newttube 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTTUBE)

foreign import ccall "HROOT.h TPCON_SetTitle" c_tpcon_settitle 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_SetLineColor" c_tpcon_setlinecolor 
  :: (Ptr RawTPCON) -> CInt -> IO ()
foreign import ccall "HROOT.h TPCON_SetFillColor" c_tpcon_setfillcolor 
  :: (Ptr RawTPCON) -> CInt -> IO ()
foreign import ccall "HROOT.h TPCON_SetFillStyle" c_tpcon_setfillstyle 
  :: (Ptr RawTPCON) -> CInt -> IO ()
foreign import ccall "HROOT.h TPCON_GetName" c_tpcon_getname 
  :: (Ptr RawTPCON) -> IO CString
foreign import ccall "HROOT.h TPCON_Draw" c_tpcon_draw 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_FindObject" c_tpcon_findobject 
  :: (Ptr RawTPCON) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPCON_SaveAs" c_tpcon_saveas 
  :: (Ptr RawTPCON) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_Write" c_tpcon_write 
  :: (Ptr RawTPCON) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPCON_delete" c_tpcon_delete 
  :: (Ptr RawTPCON) -> IO ()
foreign import ccall "HROOT.h TPCON_newTPCON" c_tpcon_newtpcon 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CInt -> IO (Ptr RawTPCON)

foreign import ccall "HROOT.h TSPHE_SetTitle" c_tsphe_settitle 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_SetLineColor" c_tsphe_setlinecolor 
  :: (Ptr RawTSPHE) -> CInt -> IO ()
foreign import ccall "HROOT.h TSPHE_SetFillColor" c_tsphe_setfillcolor 
  :: (Ptr RawTSPHE) -> CInt -> IO ()
foreign import ccall "HROOT.h TSPHE_SetFillStyle" c_tsphe_setfillstyle 
  :: (Ptr RawTSPHE) -> CInt -> IO ()
foreign import ccall "HROOT.h TSPHE_GetName" c_tsphe_getname 
  :: (Ptr RawTSPHE) -> IO CString
foreign import ccall "HROOT.h TSPHE_Draw" c_tsphe_draw 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_FindObject" c_tsphe_findobject 
  :: (Ptr RawTSPHE) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSPHE_SaveAs" c_tsphe_saveas 
  :: (Ptr RawTSPHE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_Write" c_tsphe_write 
  :: (Ptr RawTSPHE) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSPHE_delete" c_tsphe_delete 
  :: (Ptr RawTSPHE) -> IO ()
foreign import ccall "HROOT.h TSPHE_newTSPHE" c_tsphe_newtsphe 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTSPHE)

foreign import ccall "HROOT.h TXTRU_SetTitle" c_txtru_settitle 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_SetLineColor" c_txtru_setlinecolor 
  :: (Ptr RawTXTRU) -> CInt -> IO ()
foreign import ccall "HROOT.h TXTRU_SetFillColor" c_txtru_setfillcolor 
  :: (Ptr RawTXTRU) -> CInt -> IO ()
foreign import ccall "HROOT.h TXTRU_SetFillStyle" c_txtru_setfillstyle 
  :: (Ptr RawTXTRU) -> CInt -> IO ()
foreign import ccall "HROOT.h TXTRU_GetName" c_txtru_getname 
  :: (Ptr RawTXTRU) -> IO CString
foreign import ccall "HROOT.h TXTRU_Draw" c_txtru_draw 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_FindObject" c_txtru_findobject 
  :: (Ptr RawTXTRU) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TXTRU_SaveAs" c_txtru_saveas 
  :: (Ptr RawTXTRU) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_Write" c_txtru_write 
  :: (Ptr RawTXTRU) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TXTRU_delete" c_txtru_delete 
  :: (Ptr RawTXTRU) -> IO ()
foreign import ccall "HROOT.h TXTRU_newTXTRU" c_txtru_newtxtru 
  :: CString -> CString -> CString -> CInt -> CInt -> IO (Ptr RawTXTRU)

foreign import ccall "HROOT.h TBox_GetName" c_tbox_getname 
  :: (Ptr RawTBox) -> IO CString
foreign import ccall "HROOT.h TBox_Draw" c_tbox_draw 
  :: (Ptr RawTBox) -> CString -> IO ()
foreign import ccall "HROOT.h TBox_FindObject" c_tbox_findobject 
  :: (Ptr RawTBox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBox_SaveAs" c_tbox_saveas 
  :: (Ptr RawTBox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBox_Write" c_tbox_write 
  :: (Ptr RawTBox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBox_SetLineColor" c_tbox_setlinecolor 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetFillColor" c_tbox_setfillcolor 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetFillStyle" c_tbox_setfillstyle 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_delete" c_tbox_delete 
  :: (Ptr RawTBox) -> IO ()
foreign import ccall "HROOT.h TBox_newTBox" c_tbox_newtbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTBox)

foreign import ccall "HROOT.h TPave_GetName" c_tpave_getname 
  :: (Ptr RawTPave) -> IO CString
foreign import ccall "HROOT.h TPave_Draw" c_tpave_draw 
  :: (Ptr RawTPave) -> CString -> IO ()
foreign import ccall "HROOT.h TPave_FindObject" c_tpave_findobject 
  :: (Ptr RawTPave) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPave_SaveAs" c_tpave_saveas 
  :: (Ptr RawTPave) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPave_Write" c_tpave_write 
  :: (Ptr RawTPave) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPave_SetLineColor" c_tpave_setlinecolor 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetFillColor" c_tpave_setfillcolor 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetFillStyle" c_tpave_setfillstyle 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_delete" c_tpave_delete 
  :: (Ptr RawTPave) -> IO ()
foreign import ccall "HROOT.h TPave_newTPave" c_tpave_newtpave 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> IO (Ptr RawTPave)

foreign import ccall "HROOT.h TPaveText_SetTextColor" c_tpavetext_settextcolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextAlign" c_tpavetext_settextalign 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextSize" c_tpavetext_settextsize 
  :: (Ptr RawTPaveText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveText_GetName" c_tpavetext_getname 
  :: (Ptr RawTPaveText) -> IO CString
foreign import ccall "HROOT.h TPaveText_Draw" c_tpavetext_draw 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_FindObject" c_tpavetext_findobject 
  :: (Ptr RawTPaveText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveText_SaveAs" c_tpavetext_saveas 
  :: (Ptr RawTPaveText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_Write" c_tpavetext_write 
  :: (Ptr RawTPaveText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveText_SetLineColor" c_tpavetext_setlinecolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetFillColor" c_tpavetext_setfillcolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetFillStyle" c_tpavetext_setfillstyle 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_delete" c_tpavetext_delete 
  :: (Ptr RawTPaveText) -> IO ()
foreign import ccall "HROOT.h TPaveText_newTPaveText" c_tpavetext_newtpavetext 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTPaveText)

foreign import ccall "HROOT.h TDiamond_SetTextColor" c_tdiamond_settextcolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextAlign" c_tdiamond_settextalign 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextSize" c_tdiamond_settextsize 
  :: (Ptr RawTDiamond) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDiamond_GetName" c_tdiamond_getname 
  :: (Ptr RawTDiamond) -> IO CString
foreign import ccall "HROOT.h TDiamond_Draw" c_tdiamond_draw 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_FindObject" c_tdiamond_findobject 
  :: (Ptr RawTDiamond) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDiamond_SaveAs" c_tdiamond_saveas 
  :: (Ptr RawTDiamond) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_Write" c_tdiamond_write 
  :: (Ptr RawTDiamond) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDiamond_SetLineColor" c_tdiamond_setlinecolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetFillColor" c_tdiamond_setfillcolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetFillStyle" c_tdiamond_setfillstyle 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_delete" c_tdiamond_delete 
  :: (Ptr RawTDiamond) -> IO ()
foreign import ccall "HROOT.h TDiamond_newTDiamond" c_tdiamond_newtdiamond 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTDiamond)

foreign import ccall "HROOT.h TPaveStats_SetTextColor" c_tpavestats_settextcolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextAlign" c_tpavestats_settextalign 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextSize" c_tpavestats_settextsize 
  :: (Ptr RawTPaveStats) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveStats_GetName" c_tpavestats_getname 
  :: (Ptr RawTPaveStats) -> IO CString
foreign import ccall "HROOT.h TPaveStats_Draw" c_tpavestats_draw 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_FindObject" c_tpavestats_findobject 
  :: (Ptr RawTPaveStats) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveStats_SaveAs" c_tpavestats_saveas 
  :: (Ptr RawTPaveStats) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_Write" c_tpavestats_write 
  :: (Ptr RawTPaveStats) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveStats_SetLineColor" c_tpavestats_setlinecolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetFillColor" c_tpavestats_setfillcolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetFillStyle" c_tpavestats_setfillstyle 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_delete" c_tpavestats_delete 
  :: (Ptr RawTPaveStats) -> IO ()
foreign import ccall "HROOT.h TPaveStats_newTPaveStats" c_tpavestats_newtpavestats 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTPaveStats)

foreign import ccall "HROOT.h TPavesText_SetTextColor" c_tpavestext_settextcolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextAlign" c_tpavestext_settextalign 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextSize" c_tpavestext_settextsize 
  :: (Ptr RawTPavesText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPavesText_GetName" c_tpavestext_getname 
  :: (Ptr RawTPavesText) -> IO CString
foreign import ccall "HROOT.h TPavesText_Draw" c_tpavestext_draw 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_FindObject" c_tpavestext_findobject 
  :: (Ptr RawTPavesText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPavesText_SaveAs" c_tpavestext_saveas 
  :: (Ptr RawTPavesText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_Write" c_tpavestext_write 
  :: (Ptr RawTPavesText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPavesText_SetLineColor" c_tpavestext_setlinecolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetFillColor" c_tpavestext_setfillcolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetFillStyle" c_tpavestext_setfillstyle 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_delete" c_tpavestext_delete 
  :: (Ptr RawTPavesText) -> IO ()
foreign import ccall "HROOT.h TPavesText_newTPavesText" c_tpavestext_newtpavestext 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> IO (Ptr RawTPavesText)

foreign import ccall "HROOT.h TLegend_SetTextColor" c_tlegend_settextcolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextAlign" c_tlegend_settextalign 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextSize" c_tlegend_settextsize 
  :: (Ptr RawTLegend) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLegend_GetName" c_tlegend_getname 
  :: (Ptr RawTLegend) -> IO CString
foreign import ccall "HROOT.h TLegend_Draw" c_tlegend_draw 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_FindObject" c_tlegend_findobject 
  :: (Ptr RawTLegend) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLegend_SaveAs" c_tlegend_saveas 
  :: (Ptr RawTLegend) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_Write" c_tlegend_write 
  :: (Ptr RawTLegend) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLegend_SetLineColor" c_tlegend_setlinecolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetFillColor" c_tlegend_setfillcolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetFillStyle" c_tlegend_setfillstyle 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_delete" c_tlegend_delete 
  :: (Ptr RawTLegend) -> IO ()
foreign import ccall "HROOT.h TLegend_newTLegend" c_tlegend_newtlegend 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> CString -> IO (Ptr RawTLegend)

foreign import ccall "HROOT.h TPaveLabel_SetTextColor" c_tpavelabel_settextcolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextAlign" c_tpavelabel_settextalign 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextSize" c_tpavelabel_settextsize 
  :: (Ptr RawTPaveLabel) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveLabel_GetName" c_tpavelabel_getname 
  :: (Ptr RawTPaveLabel) -> IO CString
foreign import ccall "HROOT.h TPaveLabel_Draw" c_tpavelabel_draw 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_FindObject" c_tpavelabel_findobject 
  :: (Ptr RawTPaveLabel) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveLabel_SaveAs" c_tpavelabel_saveas 
  :: (Ptr RawTPaveLabel) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_Write" c_tpavelabel_write 
  :: (Ptr RawTPaveLabel) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_SetLineColor" c_tpavelabel_setlinecolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetFillColor" c_tpavelabel_setfillcolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetFillStyle" c_tpavelabel_setfillstyle 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_delete" c_tpavelabel_delete 
  :: (Ptr RawTPaveLabel) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_newTPaveLabel" c_tpavelabel_newtpavelabel 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> CString -> IO (Ptr RawTPaveLabel)

foreign import ccall "HROOT.h TPaveClass_SetTextColor" c_tpaveclass_settextcolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextAlign" c_tpaveclass_settextalign 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextSize" c_tpaveclass_settextsize 
  :: (Ptr RawTPaveClass) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveClass_GetName" c_tpaveclass_getname 
  :: (Ptr RawTPaveClass) -> IO CString
foreign import ccall "HROOT.h TPaveClass_Draw" c_tpaveclass_draw 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_FindObject" c_tpaveclass_findobject 
  :: (Ptr RawTPaveClass) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveClass_SaveAs" c_tpaveclass_saveas 
  :: (Ptr RawTPaveClass) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_Write" c_tpaveclass_write 
  :: (Ptr RawTPaveClass) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveClass_SetLineColor" c_tpaveclass_setlinecolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetFillColor" c_tpaveclass_setfillcolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetFillStyle" c_tpaveclass_setfillstyle 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_delete" c_tpaveclass_delete 
  :: (Ptr RawTPaveClass) -> IO ()

foreign import ccall "HROOT.h TWbox_GetName" c_twbox_getname 
  :: (Ptr RawTWbox) -> IO CString
foreign import ccall "HROOT.h TWbox_Draw" c_twbox_draw 
  :: (Ptr RawTWbox) -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_FindObject" c_twbox_findobject 
  :: (Ptr RawTWbox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TWbox_SaveAs" c_twbox_saveas 
  :: (Ptr RawTWbox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_Write" c_twbox_write 
  :: (Ptr RawTWbox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TWbox_SetLineColor" c_twbox_setlinecolor 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetFillColor" c_twbox_setfillcolor 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetFillStyle" c_twbox_setfillstyle 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_delete" c_twbox_delete 
  :: (Ptr RawTWbox) -> IO ()
foreign import ccall "HROOT.h TWbox_newTWbox" c_twbox_newtwbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr RawTWbox)
foreign import ccall "HROOT.h TWbox_SetBorderMode" c_twbox_setbordermode 
  :: (Ptr RawTWbox) -> CInt -> IO ()

foreign import ccall "HROOT.h TFrame_SetBorderMode" c_tframe_setbordermode 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_GetName" c_tframe_getname 
  :: (Ptr RawTFrame) -> IO CString
foreign import ccall "HROOT.h TFrame_Draw" c_tframe_draw 
  :: (Ptr RawTFrame) -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_FindObject" c_tframe_findobject 
  :: (Ptr RawTFrame) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFrame_SaveAs" c_tframe_saveas 
  :: (Ptr RawTFrame) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_Write" c_tframe_write 
  :: (Ptr RawTFrame) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFrame_SetLineColor" c_tframe_setlinecolor 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetFillColor" c_tframe_setfillcolor 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetFillStyle" c_tframe_setfillstyle 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_delete" c_tframe_delete 
  :: (Ptr RawTFrame) -> IO ()
foreign import ccall "HROOT.h TFrame_newTFrame" c_tframe_newtframe 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTFrame)

foreign import ccall "HROOT.h TSliderBox_SetBorderMode" c_tsliderbox_setbordermode 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_GetName" c_tsliderbox_getname 
  :: (Ptr RawTSliderBox) -> IO CString
foreign import ccall "HROOT.h TSliderBox_Draw" c_tsliderbox_draw 
  :: (Ptr RawTSliderBox) -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_FindObject" c_tsliderbox_findobject 
  :: (Ptr RawTSliderBox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSliderBox_SaveAs" c_tsliderbox_saveas 
  :: (Ptr RawTSliderBox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_Write" c_tsliderbox_write 
  :: (Ptr RawTSliderBox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSliderBox_SetLineColor" c_tsliderbox_setlinecolor 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetFillColor" c_tsliderbox_setfillcolor 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetFillStyle" c_tsliderbox_setfillstyle 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_delete" c_tsliderbox_delete 
  :: (Ptr RawTSliderBox) -> IO ()
foreign import ccall "HROOT.h TSliderBox_newTSliderBox" c_tsliderbox_newtsliderbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr RawTSliderBox)

foreign import ccall "HROOT.h TTree_SetTitle" c_ttree_settitle 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_SetLineColor" c_ttree_setlinecolor 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetFillColor" c_ttree_setfillcolor 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetFillStyle" c_ttree_setfillstyle 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_GetName" c_ttree_getname 
  :: (Ptr RawTTree) -> IO CString
foreign import ccall "HROOT.h TTree_Draw" c_ttree_draw 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_FindObject" c_ttree_findobject 
  :: (Ptr RawTTree) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTree_SaveAs" c_ttree_saveas 
  :: (Ptr RawTTree) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTree_Write" c_ttree_write 
  :: (Ptr RawTTree) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTree_delete" c_ttree_delete 
  :: (Ptr RawTTree) -> IO ()
foreign import ccall "HROOT.h TTree_newTTree" c_ttree_newttree 
  :: CString -> CString -> CInt -> IO (Ptr RawTTree)

foreign import ccall "HROOT.h TChain_SetTitle" c_tchain_settitle 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_SetLineColor" c_tchain_setlinecolor 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetFillColor" c_tchain_setfillcolor 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetFillStyle" c_tchain_setfillstyle 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_GetName" c_tchain_getname 
  :: (Ptr RawTChain) -> IO CString
foreign import ccall "HROOT.h TChain_Draw" c_tchain_draw 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_FindObject" c_tchain_findobject 
  :: (Ptr RawTChain) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TChain_SaveAs" c_tchain_saveas 
  :: (Ptr RawTChain) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TChain_Write" c_tchain_write 
  :: (Ptr RawTChain) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TChain_delete" c_tchain_delete 
  :: (Ptr RawTChain) -> IO ()
foreign import ccall "HROOT.h TChain_newTChain" c_tchain_newtchain 
  :: CString -> CString -> IO (Ptr RawTChain)

foreign import ccall "HROOT.h TNtuple_SetTitle" c_tntuple_settitle 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_SetLineColor" c_tntuple_setlinecolor 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetFillColor" c_tntuple_setfillcolor 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetFillStyle" c_tntuple_setfillstyle 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_GetName" c_tntuple_getname 
  :: (Ptr RawTNtuple) -> IO CString
foreign import ccall "HROOT.h TNtuple_Draw" c_tntuple_draw 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_FindObject" c_tntuple_findobject 
  :: (Ptr RawTNtuple) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNtuple_SaveAs" c_tntuple_saveas 
  :: (Ptr RawTNtuple) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_Write" c_tntuple_write 
  :: (Ptr RawTNtuple) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNtuple_delete" c_tntuple_delete 
  :: (Ptr RawTNtuple) -> IO ()
foreign import ccall "HROOT.h TNtuple_newTNtuple" c_tntuple_newtntuple 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTNtuple)

foreign import ccall "HROOT.h TNtupleD_SetTitle" c_tntupled_settitle 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetLineColor" c_tntupled_setlinecolor 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetFillColor" c_tntupled_setfillcolor 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetFillStyle" c_tntupled_setfillstyle 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_GetName" c_tntupled_getname 
  :: (Ptr RawTNtupleD) -> IO CString
foreign import ccall "HROOT.h TNtupleD_Draw" c_tntupled_draw 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_FindObject" c_tntupled_findobject 
  :: (Ptr RawTNtupleD) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNtupleD_SaveAs" c_tntupled_saveas 
  :: (Ptr RawTNtupleD) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_Write" c_tntupled_write 
  :: (Ptr RawTNtupleD) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNtupleD_delete" c_tntupled_delete 
  :: (Ptr RawTNtupleD) -> IO ()
foreign import ccall "HROOT.h TNtupleD_newTNtupleD" c_tntupled_newtntupled 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTNtupleD)

foreign import ccall "HROOT.h TTreeSQL_SetTitle" c_ttreesql_settitle 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetLineColor" c_ttreesql_setlinecolor 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetFillColor" c_ttreesql_setfillcolor 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetFillStyle" c_ttreesql_setfillstyle 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_GetName" c_ttreesql_getname 
  :: (Ptr RawTTreeSQL) -> IO CString
foreign import ccall "HROOT.h TTreeSQL_Draw" c_ttreesql_draw 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_FindObject" c_ttreesql_findobject 
  :: (Ptr RawTTreeSQL) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTreeSQL_SaveAs" c_ttreesql_saveas 
  :: (Ptr RawTTreeSQL) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_Write" c_ttreesql_write 
  :: (Ptr RawTTreeSQL) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_delete" c_ttreesql_delete 
  :: (Ptr RawTTreeSQL) -> IO ()

foreign import ccall "HROOT.h TPolyLine_GetName" c_tpolyline_getname 
  :: (Ptr RawTPolyLine) -> IO CString
foreign import ccall "HROOT.h TPolyLine_Draw" c_tpolyline_draw 
  :: (Ptr RawTPolyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_FindObject" c_tpolyline_findobject 
  :: (Ptr RawTPolyLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPolyLine_SaveAs" c_tpolyline_saveas 
  :: (Ptr RawTPolyLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_Write" c_tpolyline_write 
  :: (Ptr RawTPolyLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPolyLine_SetLineColor" c_tpolyline_setlinecolor 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetFillColor" c_tpolyline_setfillcolor 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetFillStyle" c_tpolyline_setfillstyle 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_delete" c_tpolyline_delete 
  :: (Ptr RawTPolyLine) -> IO ()
foreign import ccall "HROOT.h TPolyLine_newTPolyLine" c_tpolyline_newtpolyline 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO (Ptr RawTPolyLine)

foreign import ccall "HROOT.h TCurlyLine_GetName" c_tcurlyline_getname 
  :: (Ptr RawTCurlyLine) -> IO CString
foreign import ccall "HROOT.h TCurlyLine_Draw" c_tcurlyline_draw 
  :: (Ptr RawTCurlyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_FindObject" c_tcurlyline_findobject 
  :: (Ptr RawTCurlyLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCurlyLine_SaveAs" c_tcurlyline_saveas 
  :: (Ptr RawTCurlyLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_Write" c_tcurlyline_write 
  :: (Ptr RawTCurlyLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_SetLineColor" c_tcurlyline_setlinecolor 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetFillColor" c_tcurlyline_setfillcolor 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetFillStyle" c_tcurlyline_setfillstyle 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_delete" c_tcurlyline_delete 
  :: (Ptr RawTCurlyLine) -> IO ()
foreign import ccall "HROOT.h TCurlyLine_newTCurlyLine" c_tcurlyline_newtcurlyline 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCurlyLine)

foreign import ccall "HROOT.h TCurlyArc_GetName" c_tcurlyarc_getname 
  :: (Ptr RawTCurlyArc) -> IO CString
foreign import ccall "HROOT.h TCurlyArc_Draw" c_tcurlyarc_draw 
  :: (Ptr RawTCurlyArc) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_FindObject" c_tcurlyarc_findobject 
  :: (Ptr RawTCurlyArc) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCurlyArc_SaveAs" c_tcurlyarc_saveas 
  :: (Ptr RawTCurlyArc) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_Write" c_tcurlyarc_write 
  :: (Ptr RawTCurlyArc) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_SetLineColor" c_tcurlyarc_setlinecolor 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetFillColor" c_tcurlyarc_setfillcolor 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetFillStyle" c_tcurlyarc_setfillstyle 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_delete" c_tcurlyarc_delete 
  :: (Ptr RawTCurlyArc) -> IO ()
foreign import ccall "HROOT.h TCurlyArc_newTCurlyArc" c_tcurlyarc_newtcurlyarc 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCurlyArc)

foreign import ccall "HROOT.h TEfficiency_SetTitle" c_tefficiency_settitle 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetLineColor" c_tefficiency_setlinecolor 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetFillColor" c_tefficiency_setfillcolor 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetFillStyle" c_tefficiency_setfillstyle 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_GetName" c_tefficiency_getname 
  :: (Ptr RawTEfficiency) -> IO CString
foreign import ccall "HROOT.h TEfficiency_Draw" c_tefficiency_draw 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_FindObject" c_tefficiency_findobject 
  :: (Ptr RawTEfficiency) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEfficiency_SaveAs" c_tefficiency_saveas 
  :: (Ptr RawTEfficiency) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_Write" c_tefficiency_write 
  :: (Ptr RawTEfficiency) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEfficiency_delete" c_tefficiency_delete 
  :: (Ptr RawTEfficiency) -> IO ()

foreign import ccall "HROOT.h TAxis_SetTitle" c_taxis_settitle 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_SetLabelColor" c_taxis_setlabelcolor 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetLabelSize" c_taxis_setlabelsize 
  :: (Ptr RawTAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAxis_SetTickLength" c_taxis_setticklength 
  :: (Ptr RawTAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAxis_SetTitleOffset" c_taxis_settitleoffset 
  :: (Ptr RawTAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAxis_SetNdivisions" c_taxis_setndivisions 
  :: (Ptr RawTAxis) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_GetName" c_taxis_getname 
  :: (Ptr RawTAxis) -> IO CString
foreign import ccall "HROOT.h TAxis_Draw" c_taxis_draw 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_FindObject" c_taxis_findobject 
  :: (Ptr RawTAxis) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TAxis_SaveAs" c_taxis_saveas 
  :: (Ptr RawTAxis) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_Write" c_taxis_write 
  :: (Ptr RawTAxis) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TAxis_delete" c_taxis_delete 
  :: (Ptr RawTAxis) -> IO ()

foreign import ccall "HROOT.h TLatex_SetLineColor" c_tlatex_setlinecolor 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTitle" c_tlatex_settitle 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextColor" c_tlatex_settextcolor 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextAlign" c_tlatex_settextalign 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextSize" c_tlatex_settextsize 
  :: (Ptr RawTLatex) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLatex_GetName" c_tlatex_getname 
  :: (Ptr RawTLatex) -> IO CString
foreign import ccall "HROOT.h TLatex_Draw" c_tlatex_draw 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_FindObject" c_tlatex_findobject 
  :: (Ptr RawTLatex) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLatex_SaveAs" c_tlatex_saveas 
  :: (Ptr RawTLatex) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_Write" c_tlatex_write 
  :: (Ptr RawTLatex) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLatex_delete" c_tlatex_delete 
  :: (Ptr RawTLatex) -> IO ()
foreign import ccall "HROOT.h TLatex_newTLatex" c_tlatex_newtlatex 
  :: CDouble -> CDouble -> CString -> IO (Ptr RawTLatex)
foreign import ccall "HROOT.h TLatex_tLatexDrawLatex" c_tlatex_tlatexdrawlatex 
  :: (Ptr RawTLatex) -> CDouble -> CDouble -> CString -> IO (Ptr RawTLatex)

foreign import ccall "HROOT.h TText_SetTitle" c_ttext_settitle 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_SetTextColor" c_ttext_settextcolor 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_SetTextAlign" c_ttext_settextalign 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_SetTextSize" c_ttext_settextsize 
  :: (Ptr RawTText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TText_GetName" c_ttext_getname 
  :: (Ptr RawTText) -> IO CString
foreign import ccall "HROOT.h TText_Draw" c_ttext_draw 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_FindObject" c_ttext_findobject 
  :: (Ptr RawTText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TText_SaveAs" c_ttext_saveas 
  :: (Ptr RawTText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TText_Write" c_ttext_write 
  :: (Ptr RawTText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TText_delete" c_ttext_delete 
  :: (Ptr RawTText) -> IO ()

foreign import ccall "HROOT.h TDirectory_SetTitle" c_tdirectory_settitle 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_GetName" c_tdirectory_getname 
  :: (Ptr RawTDirectory) -> IO CString
foreign import ccall "HROOT.h TDirectory_Draw" c_tdirectory_draw 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_FindObject" c_tdirectory_findobject 
  :: (Ptr RawTDirectory) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDirectory_SaveAs" c_tdirectory_saveas 
  :: (Ptr RawTDirectory) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_Write" c_tdirectory_write 
  :: (Ptr RawTDirectory) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDirectory_delete" c_tdirectory_delete 
  :: (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TDirectory_Close" c_tdirectory_close 
  :: (Ptr RawTDirectory) -> CString -> IO ()

foreign import ccall "HROOT.h TDirectoryFile_Close" c_tdirectoryfile_close 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_SetTitle" c_tdirectoryfile_settitle 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_GetName" c_tdirectoryfile_getname 
  :: (Ptr RawTDirectoryFile) -> IO CString
foreign import ccall "HROOT.h TDirectoryFile_Draw" c_tdirectoryfile_draw 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_FindObject" c_tdirectoryfile_findobject 
  :: (Ptr RawTDirectoryFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDirectoryFile_SaveAs" c_tdirectoryfile_saveas 
  :: (Ptr RawTDirectoryFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_Write" c_tdirectoryfile_write 
  :: (Ptr RawTDirectoryFile) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_delete" c_tdirectoryfile_delete 
  :: (Ptr RawTDirectoryFile) -> IO ()

foreign import ccall "HROOT.h TFile_Close" c_tfile_close 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_SetTitle" c_tfile_settitle 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_GetName" c_tfile_getname 
  :: (Ptr RawTFile) -> IO CString
foreign import ccall "HROOT.h TFile_Draw" c_tfile_draw 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_FindObject" c_tfile_findobject 
  :: (Ptr RawTFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFile_SaveAs" c_tfile_saveas 
  :: (Ptr RawTFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFile_Write" c_tfile_write 
  :: (Ptr RawTFile) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFile_delete" c_tfile_delete 
  :: (Ptr RawTFile) -> IO ()
foreign import ccall "HROOT.h TFile_newTFile" c_tfile_newtfile 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTFile)

foreign import ccall "HROOT.h TBranch_SetTitle" c_tbranch_settitle 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_SetFillColor" c_tbranch_setfillcolor 
  :: (Ptr RawTBranch) -> CInt -> IO ()
foreign import ccall "HROOT.h TBranch_SetFillStyle" c_tbranch_setfillstyle 
  :: (Ptr RawTBranch) -> CInt -> IO ()
foreign import ccall "HROOT.h TBranch_GetName" c_tbranch_getname 
  :: (Ptr RawTBranch) -> IO CString
foreign import ccall "HROOT.h TBranch_Draw" c_tbranch_draw 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_FindObject" c_tbranch_findobject 
  :: (Ptr RawTBranch) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBranch_SaveAs" c_tbranch_saveas 
  :: (Ptr RawTBranch) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_Write" c_tbranch_write 
  :: (Ptr RawTBranch) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBranch_delete" c_tbranch_delete 
  :: (Ptr RawTBranch) -> IO ()

foreign import ccall "HROOT.h TVirtualTreePlayer_GetName" c_tvirtualtreeplayer_getname 
  :: (Ptr RawTVirtualTreePlayer) -> IO CString
foreign import ccall "HROOT.h TVirtualTreePlayer_Draw" c_tvirtualtreeplayer_draw 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_FindObject" c_tvirtualtreeplayer_findobject 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TVirtualTreePlayer_SaveAs" c_tvirtualtreeplayer_saveas 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_Write" c_tvirtualtreeplayer_write 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TVirtualTreePlayer_delete" c_tvirtualtreeplayer_delete 
  :: (Ptr RawTVirtualTreePlayer) -> IO ()

foreign import ccall "HROOT.h TTreePlayer_GetName" c_ttreeplayer_getname 
  :: (Ptr RawTTreePlayer) -> IO CString
foreign import ccall "HROOT.h TTreePlayer_Draw" c_ttreeplayer_draw 
  :: (Ptr RawTTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_FindObject" c_ttreeplayer_findobject 
  :: (Ptr RawTTreePlayer) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTreePlayer_SaveAs" c_ttreeplayer_saveas 
  :: (Ptr RawTTreePlayer) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_Write" c_ttreeplayer_write 
  :: (Ptr RawTTreePlayer) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTreePlayer_delete" c_ttreeplayer_delete 
  :: (Ptr RawTTreePlayer) -> IO ()

foreign import ccall "HROOT.h TArray_delete" c_tarray_delete 
  :: (Ptr RawTArray) -> IO ()

foreign import ccall "HROOT.h TArrayC_delete" c_tarrayc_delete 
  :: (Ptr RawTArrayC) -> IO ()

foreign import ccall "HROOT.h TArrayD_delete" c_tarrayd_delete 
  :: (Ptr RawTArrayD) -> IO ()

foreign import ccall "HROOT.h TArrayF_delete" c_tarrayf_delete 
  :: (Ptr RawTArrayF) -> IO ()

foreign import ccall "HROOT.h TArrayI_delete" c_tarrayi_delete 
  :: (Ptr RawTArrayI) -> IO ()

foreign import ccall "HROOT.h TArrayL_delete" c_tarrayl_delete 
  :: (Ptr RawTArrayL) -> IO ()

foreign import ccall "HROOT.h TArrayL64_delete" c_tarrayl64_delete 
  :: (Ptr RawTArrayL64) -> IO ()

foreign import ccall "HROOT.h TArrayS_delete" c_tarrays_delete 
  :: (Ptr RawTArrayS) -> IO ()

foreign import ccall "HROOT.h TH1_SetTitle" c_th1_settitle 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetLineColor" c_th1_setlinecolor 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetFillColor" c_th1_setfillcolor 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetFillStyle" c_th1_setfillstyle 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_GetName" c_th1_getname 
  :: (Ptr RawTH1) -> IO CString
foreign import ccall "HROOT.h TH1_Draw" c_th1_draw 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_FindObject" c_th1_findobject 
  :: (Ptr RawTH1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1_SaveAs" c_th1_saveas 
  :: (Ptr RawTH1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1_Write" c_th1_write 
  :: (Ptr RawTH1) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_delete" c_th1_delete 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_Add" c_th1_add 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_AddBinContent" c_th1_addbincontent 
  :: (Ptr RawTH1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_Chi2Test" c_th1_chi2test 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1_ComputeIntegral" c_th1_computeintegral 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_DirectoryAutoAdd" c_th1_directoryautoadd 
  :: (Ptr RawTH1) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1_DistancetoPrimitive" c_th1_distancetoprimitive 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_Divide" c_th1_divide 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_DrawCopy" c_th1_drawcopy 
  :: (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_DrawNormalized" c_th1_drawnormalized 
  :: (Ptr RawTH1) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_DrawPanel" c_th1_drawpanel 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_BufferEmpty" c_th1_bufferempty 
  :: (Ptr RawTH1) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_Eval" c_th1_eval 
  :: (Ptr RawTH1) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_ExecuteEvent" c_th1_executeevent 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_FFT" c_th1_fft 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_fill1" c_th1_fill1 
  :: (Ptr RawTH1) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_FillN" c_th1_filln 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_FillRandom" c_th1_fillrandom 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_FindBin" c_th1_findbin 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_FindFixBin" c_th1_findfixbin 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_FindFirstBinAbove" c_th1_findfirstbinabove 
  :: (Ptr RawTH1) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_FindLastBinAbove" c_th1_findlastbinabove 
  :: (Ptr RawTH1) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_FitPanel" c_th1_fitpanel 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_tH1GetAsymmetry" c_th1_th1getasymmetry 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_tH1GetBufferLength" c_th1_th1getbufferlength 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_tH1GetBufferSize" c_th1_th1getbuffersize 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetNdivisions" c_th1_getndivisions 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_GetAxisColor" c_th1_getaxiscolor 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_GetLabelColor" c_th1_getlabelcolor 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_GetLabelFont" c_th1_getlabelfont 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_GetLabelOffset" c_th1_getlabeloffset 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetLabelSize" c_th1_getlabelsize 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetTitleFont" c_th1_gettitlefont 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_GetTitleOffset" c_th1_gettitleoffset 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetTitleSize" c_th1_gettitlesize 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetTickLength" c_th1_getticklength 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBarOffset" c_th1_getbaroffset 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBarWidth" c_th1_getbarwidth 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetContour" c_th1_getcontour 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1_GetContourLevel" c_th1_getcontourlevel 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetContourLevelPad" c_th1_getcontourlevelpad 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBin" c_th1_getbin 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_GetBinCenter" c_th1_getbincenter 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent1" c_th1_getbincontent1 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent2" c_th1_getbincontent2 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent3" c_th1_getbincontent3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError1" c_th1_getbinerror1 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError2" c_th1_getbinerror2 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError3" c_th1_getbinerror3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinLowEdge" c_th1_getbinlowedge 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinWidth" c_th1_getbinwidth 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetCellContent" c_th1_getcellcontent 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetCellError" c_th1_getcellerror 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_tH1GetDirectory" c_th1_th1getdirectory 
  :: (Ptr RawTH1) -> IO (Ptr RawTDirectory)
foreign import ccall "HROOT.h TH1_tH1GetXaxis" c_th1_th1getxaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_tH1GetYaxis" c_th1_th1getyaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_tH1GetZaxis" c_th1_th1getzaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)

foreign import ccall "HROOT.h TH2_Add" c_th2_add 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_AddBinContent" c_th2_addbincontent 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_Chi2Test" c_th2_chi2test 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2_ComputeIntegral" c_th2_computeintegral 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_DirectoryAutoAdd" c_th2_directoryautoadd 
  :: (Ptr RawTH2) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2_DistancetoPrimitive" c_th2_distancetoprimitive 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_Divide" c_th2_divide 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_DrawCopy" c_th2_drawcopy 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2_DrawNormalized" c_th2_drawnormalized 
  :: (Ptr RawTH2) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_DrawPanel" c_th2_drawpanel 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_BufferEmpty" c_th2_bufferempty 
  :: (Ptr RawTH2) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_Eval" c_th2_eval 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_ExecuteEvent" c_th2_executeevent 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_FFT" c_th2_fft 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_fill1" c_th2_fill1 
  :: (Ptr RawTH2) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_FillN" c_th2_filln 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_FillRandom" c_th2_fillrandom 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_FindBin" c_th2_findbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_FindFixBin" c_th2_findfixbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_FindFirstBinAbove" c_th2_findfirstbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_FindLastBinAbove" c_th2_findlastbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_FitPanel" c_th2_fitpanel 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_GetNdivisions" c_th2_getndivisions 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_GetAxisColor" c_th2_getaxiscolor 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_GetLabelColor" c_th2_getlabelcolor 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_GetLabelFont" c_th2_getlabelfont 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_GetLabelOffset" c_th2_getlabeloffset 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetLabelSize" c_th2_getlabelsize 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetTitleFont" c_th2_gettitlefont 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_GetTitleOffset" c_th2_gettitleoffset 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetTitleSize" c_th2_gettitlesize 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetTickLength" c_th2_getticklength 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBarOffset" c_th2_getbaroffset 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBarWidth" c_th2_getbarwidth 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetContour" c_th2_getcontour 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2_GetContourLevel" c_th2_getcontourlevel 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetContourLevelPad" c_th2_getcontourlevelpad 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBin" c_th2_getbin 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_GetBinCenter" c_th2_getbincenter 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent1" c_th2_getbincontent1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent2" c_th2_getbincontent2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent3" c_th2_getbincontent3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError1" c_th2_getbinerror1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError2" c_th2_getbinerror2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError3" c_th2_getbinerror3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinLowEdge" c_th2_getbinlowedge 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinWidth" c_th2_getbinwidth 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetCellContent" c_th2_getcellcontent 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetCellError" c_th2_getcellerror 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_SetTitle" c_th2_settitle 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetLineColor" c_th2_setlinecolor 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetFillColor" c_th2_setfillcolor 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetFillStyle" c_th2_setfillstyle 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_GetName" c_th2_getname 
  :: (Ptr RawTH2) -> IO CString
foreign import ccall "HROOT.h TH2_Draw" c_th2_draw 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_FindObject" c_th2_findobject 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2_SaveAs" c_th2_saveas 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2_Write" c_th2_write 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_delete" c_th2_delete 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_fill2" c_th2_fill2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt

foreign import ccall "HROOT.h TH3_Add" c_th3_add 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_AddBinContent" c_th3_addbincontent 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_Chi2Test" c_th3_chi2test 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3_ComputeIntegral" c_th3_computeintegral 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_DirectoryAutoAdd" c_th3_directoryautoadd 
  :: (Ptr RawTH3) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3_DistancetoPrimitive" c_th3_distancetoprimitive 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_Divide" c_th3_divide 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_DrawCopy" c_th3_drawcopy 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3_DrawNormalized" c_th3_drawnormalized 
  :: (Ptr RawTH3) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_DrawPanel" c_th3_drawpanel 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_BufferEmpty" c_th3_bufferempty 
  :: (Ptr RawTH3) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_Eval" c_th3_eval 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_ExecuteEvent" c_th3_executeevent 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_FFT" c_th3_fft 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_fill1" c_th3_fill1 
  :: (Ptr RawTH3) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FillN" c_th3_filln 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_FillRandom" c_th3_fillrandom 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_FindBin" c_th3_findbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FindFixBin" c_th3_findfixbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FindFirstBinAbove" c_th3_findfirstbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_FindLastBinAbove" c_th3_findlastbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_FitPanel" c_th3_fitpanel 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_GetNdivisions" c_th3_getndivisions 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_GetAxisColor" c_th3_getaxiscolor 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_GetLabelColor" c_th3_getlabelcolor 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_GetLabelFont" c_th3_getlabelfont 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_GetLabelOffset" c_th3_getlabeloffset 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetLabelSize" c_th3_getlabelsize 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetTitleFont" c_th3_gettitlefont 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_GetTitleOffset" c_th3_gettitleoffset 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetTitleSize" c_th3_gettitlesize 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetTickLength" c_th3_getticklength 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBarOffset" c_th3_getbaroffset 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBarWidth" c_th3_getbarwidth 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetContour" c_th3_getcontour 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3_GetContourLevel" c_th3_getcontourlevel 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetContourLevelPad" c_th3_getcontourlevelpad 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBin" c_th3_getbin 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_GetBinCenter" c_th3_getbincenter 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent1" c_th3_getbincontent1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent2" c_th3_getbincontent2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent3" c_th3_getbincontent3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError1" c_th3_getbinerror1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError2" c_th3_getbinerror2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError3" c_th3_getbinerror3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinLowEdge" c_th3_getbinlowedge 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinWidth" c_th3_getbinwidth 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetCellContent" c_th3_getcellcontent 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetCellError" c_th3_getcellerror 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_SetTitle" c_th3_settitle 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetLineColor" c_th3_setlinecolor 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetFillColor" c_th3_setfillcolor 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetFillStyle" c_th3_setfillstyle 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_GetName" c_th3_getname 
  :: (Ptr RawTH3) -> IO CString
foreign import ccall "HROOT.h TH3_Draw" c_th3_draw 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_FindObject" c_th3_findobject 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3_SaveAs" c_th3_saveas 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3_Write" c_th3_write 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_delete" c_th3_delete 
  :: (Ptr RawTH3) -> IO ()

foreign import ccall "HROOT.h TH1C_Add" c_th1c_add 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_AddBinContent" c_th1c_addbincontent 
  :: (Ptr RawTH1C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_Chi2Test" c_th1c_chi2test 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1C_ComputeIntegral" c_th1c_computeintegral 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_DirectoryAutoAdd" c_th1c_directoryautoadd 
  :: (Ptr RawTH1C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1C_DistancetoPrimitive" c_th1c_distancetoprimitive 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_Divide" c_th1c_divide 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_DrawCopy" c_th1c_drawcopy 
  :: (Ptr RawTH1C) -> CString -> IO (Ptr RawTH1C)
foreign import ccall "HROOT.h TH1C_DrawNormalized" c_th1c_drawnormalized 
  :: (Ptr RawTH1C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_DrawPanel" c_th1c_drawpanel 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_BufferEmpty" c_th1c_bufferempty 
  :: (Ptr RawTH1C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_Eval" c_th1c_eval 
  :: (Ptr RawTH1C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_ExecuteEvent" c_th1c_executeevent 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_FFT" c_th1c_fft 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_fill1" c_th1c_fill1 
  :: (Ptr RawTH1C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_FillN" c_th1c_filln 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_FillRandom" c_th1c_fillrandom 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_FindBin" c_th1c_findbin 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_FindFixBin" c_th1c_findfixbin 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_FindFirstBinAbove" c_th1c_findfirstbinabove 
  :: (Ptr RawTH1C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_FindLastBinAbove" c_th1c_findlastbinabove 
  :: (Ptr RawTH1C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_FitPanel" c_th1c_fitpanel 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_GetNdivisions" c_th1c_getndivisions 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_GetAxisColor" c_th1c_getaxiscolor 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_GetLabelColor" c_th1c_getlabelcolor 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_GetLabelFont" c_th1c_getlabelfont 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_GetLabelOffset" c_th1c_getlabeloffset 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetLabelSize" c_th1c_getlabelsize 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetTitleFont" c_th1c_gettitlefont 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_GetTitleOffset" c_th1c_gettitleoffset 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetTitleSize" c_th1c_gettitlesize 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetTickLength" c_th1c_getticklength 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBarOffset" c_th1c_getbaroffset 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBarWidth" c_th1c_getbarwidth 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetContour" c_th1c_getcontour 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetContourLevel" c_th1c_getcontourlevel 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetContourLevelPad" c_th1c_getcontourlevelpad 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBin" c_th1c_getbin 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_GetBinCenter" c_th1c_getbincenter 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent1" c_th1c_getbincontent1 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent2" c_th1c_getbincontent2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent3" c_th1c_getbincontent3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError1" c_th1c_getbinerror1 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError2" c_th1c_getbinerror2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError3" c_th1c_getbinerror3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinLowEdge" c_th1c_getbinlowedge 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinWidth" c_th1c_getbinwidth 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetCellContent" c_th1c_getcellcontent 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetCellError" c_th1c_getcellerror 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_SetTitle" c_th1c_settitle 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetLineColor" c_th1c_setlinecolor 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetFillColor" c_th1c_setfillcolor 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetFillStyle" c_th1c_setfillstyle 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_GetName" c_th1c_getname 
  :: (Ptr RawTH1C) -> IO CString
foreign import ccall "HROOT.h TH1C_Draw" c_th1c_draw 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_FindObject" c_th1c_findobject 
  :: (Ptr RawTH1C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1C_SaveAs" c_th1c_saveas 
  :: (Ptr RawTH1C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_Write" c_th1c_write 
  :: (Ptr RawTH1C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_delete" c_th1c_delete 
  :: (Ptr RawTH1C) -> IO ()

foreign import ccall "HROOT.h TH1D_Add" c_th1d_add 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_AddBinContent" c_th1d_addbincontent 
  :: (Ptr RawTH1D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_Chi2Test" c_th1d_chi2test 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1D_ComputeIntegral" c_th1d_computeintegral 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_DirectoryAutoAdd" c_th1d_directoryautoadd 
  :: (Ptr RawTH1D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1D_DistancetoPrimitive" c_th1d_distancetoprimitive 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_Divide" c_th1d_divide 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_DrawCopy" c_th1d_drawcopy 
  :: (Ptr RawTH1D) -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH1D_DrawNormalized" c_th1d_drawnormalized 
  :: (Ptr RawTH1D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_DrawPanel" c_th1d_drawpanel 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_BufferEmpty" c_th1d_bufferempty 
  :: (Ptr RawTH1D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_Eval" c_th1d_eval 
  :: (Ptr RawTH1D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_ExecuteEvent" c_th1d_executeevent 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_FFT" c_th1d_fft 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_fill1" c_th1d_fill1 
  :: (Ptr RawTH1D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_FillN" c_th1d_filln 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_FillRandom" c_th1d_fillrandom 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_FindBin" c_th1d_findbin 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_FindFixBin" c_th1d_findfixbin 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_FindFirstBinAbove" c_th1d_findfirstbinabove 
  :: (Ptr RawTH1D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_FindLastBinAbove" c_th1d_findlastbinabove 
  :: (Ptr RawTH1D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_FitPanel" c_th1d_fitpanel 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_GetNdivisions" c_th1d_getndivisions 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_GetAxisColor" c_th1d_getaxiscolor 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_GetLabelColor" c_th1d_getlabelcolor 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_GetLabelFont" c_th1d_getlabelfont 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_GetLabelOffset" c_th1d_getlabeloffset 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetLabelSize" c_th1d_getlabelsize 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetTitleFont" c_th1d_gettitlefont 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_GetTitleOffset" c_th1d_gettitleoffset 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetTitleSize" c_th1d_gettitlesize 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetTickLength" c_th1d_getticklength 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBarOffset" c_th1d_getbaroffset 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBarWidth" c_th1d_getbarwidth 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetContour" c_th1d_getcontour 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetContourLevel" c_th1d_getcontourlevel 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetContourLevelPad" c_th1d_getcontourlevelpad 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBin" c_th1d_getbin 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_GetBinCenter" c_th1d_getbincenter 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent1" c_th1d_getbincontent1 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent2" c_th1d_getbincontent2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent3" c_th1d_getbincontent3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError1" c_th1d_getbinerror1 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError2" c_th1d_getbinerror2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError3" c_th1d_getbinerror3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinLowEdge" c_th1d_getbinlowedge 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinWidth" c_th1d_getbinwidth 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetCellContent" c_th1d_getcellcontent 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetCellError" c_th1d_getcellerror 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_SetTitle" c_th1d_settitle 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetLineColor" c_th1d_setlinecolor 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetFillColor" c_th1d_setfillcolor 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetFillStyle" c_th1d_setfillstyle 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_GetName" c_th1d_getname 
  :: (Ptr RawTH1D) -> IO CString
foreign import ccall "HROOT.h TH1D_Draw" c_th1d_draw 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_FindObject" c_th1d_findobject 
  :: (Ptr RawTH1D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1D_SaveAs" c_th1d_saveas 
  :: (Ptr RawTH1D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_Write" c_th1d_write 
  :: (Ptr RawTH1D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_delete" c_th1d_delete 
  :: (Ptr RawTH1D) -> IO ()

foreign import ccall "HROOT.h TH1F_Add" c_th1f_add 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_AddBinContent" c_th1f_addbincontent 
  :: (Ptr RawTH1F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_Chi2Test" c_th1f_chi2test 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1F_ComputeIntegral" c_th1f_computeintegral 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_DirectoryAutoAdd" c_th1f_directoryautoadd 
  :: (Ptr RawTH1F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1F_DistancetoPrimitive" c_th1f_distancetoprimitive 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_Divide" c_th1f_divide 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_DrawCopy" c_th1f_drawcopy 
  :: (Ptr RawTH1F) -> CString -> IO (Ptr RawTH1F)
foreign import ccall "HROOT.h TH1F_DrawNormalized" c_th1f_drawnormalized 
  :: (Ptr RawTH1F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_DrawPanel" c_th1f_drawpanel 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_BufferEmpty" c_th1f_bufferempty 
  :: (Ptr RawTH1F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_Eval" c_th1f_eval 
  :: (Ptr RawTH1F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_ExecuteEvent" c_th1f_executeevent 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_FFT" c_th1f_fft 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_fill1" c_th1f_fill1 
  :: (Ptr RawTH1F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_FillN" c_th1f_filln 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_FillRandom" c_th1f_fillrandom 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_FindBin" c_th1f_findbin 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_FindFixBin" c_th1f_findfixbin 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_FindFirstBinAbove" c_th1f_findfirstbinabove 
  :: (Ptr RawTH1F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_FindLastBinAbove" c_th1f_findlastbinabove 
  :: (Ptr RawTH1F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_FitPanel" c_th1f_fitpanel 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_GetNdivisions" c_th1f_getndivisions 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_GetAxisColor" c_th1f_getaxiscolor 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_GetLabelColor" c_th1f_getlabelcolor 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_GetLabelFont" c_th1f_getlabelfont 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_GetLabelOffset" c_th1f_getlabeloffset 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetLabelSize" c_th1f_getlabelsize 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetTitleFont" c_th1f_gettitlefont 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_GetTitleOffset" c_th1f_gettitleoffset 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetTitleSize" c_th1f_gettitlesize 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetTickLength" c_th1f_getticklength 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBarOffset" c_th1f_getbaroffset 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBarWidth" c_th1f_getbarwidth 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetContour" c_th1f_getcontour 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetContourLevel" c_th1f_getcontourlevel 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetContourLevelPad" c_th1f_getcontourlevelpad 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBin" c_th1f_getbin 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_GetBinCenter" c_th1f_getbincenter 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent1" c_th1f_getbincontent1 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent2" c_th1f_getbincontent2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent3" c_th1f_getbincontent3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError1" c_th1f_getbinerror1 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError2" c_th1f_getbinerror2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError3" c_th1f_getbinerror3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinLowEdge" c_th1f_getbinlowedge 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinWidth" c_th1f_getbinwidth 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetCellContent" c_th1f_getcellcontent 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetCellError" c_th1f_getcellerror 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_SetTitle" c_th1f_settitle 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetLineColor" c_th1f_setlinecolor 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetFillColor" c_th1f_setfillcolor 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetFillStyle" c_th1f_setfillstyle 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_GetName" c_th1f_getname 
  :: (Ptr RawTH1F) -> IO CString
foreign import ccall "HROOT.h TH1F_Draw" c_th1f_draw 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_FindObject" c_th1f_findobject 
  :: (Ptr RawTH1F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1F_SaveAs" c_th1f_saveas 
  :: (Ptr RawTH1F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_Write" c_th1f_write 
  :: (Ptr RawTH1F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_delete" c_th1f_delete 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_newTH1F" c_th1f_newth1f 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1F)

foreign import ccall "HROOT.h TH1I_Add" c_th1i_add 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_AddBinContent" c_th1i_addbincontent 
  :: (Ptr RawTH1I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_Chi2Test" c_th1i_chi2test 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1I_ComputeIntegral" c_th1i_computeintegral 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_DirectoryAutoAdd" c_th1i_directoryautoadd 
  :: (Ptr RawTH1I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1I_DistancetoPrimitive" c_th1i_distancetoprimitive 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_Divide" c_th1i_divide 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_DrawCopy" c_th1i_drawcopy 
  :: (Ptr RawTH1I) -> CString -> IO (Ptr RawTH1I)
foreign import ccall "HROOT.h TH1I_DrawNormalized" c_th1i_drawnormalized 
  :: (Ptr RawTH1I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_DrawPanel" c_th1i_drawpanel 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_BufferEmpty" c_th1i_bufferempty 
  :: (Ptr RawTH1I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_Eval" c_th1i_eval 
  :: (Ptr RawTH1I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_ExecuteEvent" c_th1i_executeevent 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_FFT" c_th1i_fft 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_fill1" c_th1i_fill1 
  :: (Ptr RawTH1I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_FillN" c_th1i_filln 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_FillRandom" c_th1i_fillrandom 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_FindBin" c_th1i_findbin 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_FindFixBin" c_th1i_findfixbin 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_FindFirstBinAbove" c_th1i_findfirstbinabove 
  :: (Ptr RawTH1I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_FindLastBinAbove" c_th1i_findlastbinabove 
  :: (Ptr RawTH1I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_FitPanel" c_th1i_fitpanel 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_GetNdivisions" c_th1i_getndivisions 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_GetAxisColor" c_th1i_getaxiscolor 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_GetLabelColor" c_th1i_getlabelcolor 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_GetLabelFont" c_th1i_getlabelfont 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_GetLabelOffset" c_th1i_getlabeloffset 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetLabelSize" c_th1i_getlabelsize 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetTitleFont" c_th1i_gettitlefont 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_GetTitleOffset" c_th1i_gettitleoffset 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetTitleSize" c_th1i_gettitlesize 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetTickLength" c_th1i_getticklength 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBarOffset" c_th1i_getbaroffset 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBarWidth" c_th1i_getbarwidth 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetContour" c_th1i_getcontour 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetContourLevel" c_th1i_getcontourlevel 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetContourLevelPad" c_th1i_getcontourlevelpad 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBin" c_th1i_getbin 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_GetBinCenter" c_th1i_getbincenter 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent1" c_th1i_getbincontent1 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent2" c_th1i_getbincontent2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent3" c_th1i_getbincontent3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError1" c_th1i_getbinerror1 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError2" c_th1i_getbinerror2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError3" c_th1i_getbinerror3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinLowEdge" c_th1i_getbinlowedge 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinWidth" c_th1i_getbinwidth 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetCellContent" c_th1i_getcellcontent 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetCellError" c_th1i_getcellerror 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_SetTitle" c_th1i_settitle 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetLineColor" c_th1i_setlinecolor 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetFillColor" c_th1i_setfillcolor 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetFillStyle" c_th1i_setfillstyle 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_GetName" c_th1i_getname 
  :: (Ptr RawTH1I) -> IO CString
foreign import ccall "HROOT.h TH1I_Draw" c_th1i_draw 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_FindObject" c_th1i_findobject 
  :: (Ptr RawTH1I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1I_SaveAs" c_th1i_saveas 
  :: (Ptr RawTH1I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_Write" c_th1i_write 
  :: (Ptr RawTH1I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_delete" c_th1i_delete 
  :: (Ptr RawTH1I) -> IO ()

foreign import ccall "HROOT.h TH1S_Add" c_th1s_add 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_AddBinContent" c_th1s_addbincontent 
  :: (Ptr RawTH1S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_Chi2Test" c_th1s_chi2test 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1S_ComputeIntegral" c_th1s_computeintegral 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_DirectoryAutoAdd" c_th1s_directoryautoadd 
  :: (Ptr RawTH1S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1S_DistancetoPrimitive" c_th1s_distancetoprimitive 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_Divide" c_th1s_divide 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_DrawCopy" c_th1s_drawcopy 
  :: (Ptr RawTH1S) -> CString -> IO (Ptr RawTH1S)
foreign import ccall "HROOT.h TH1S_DrawNormalized" c_th1s_drawnormalized 
  :: (Ptr RawTH1S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_DrawPanel" c_th1s_drawpanel 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_BufferEmpty" c_th1s_bufferempty 
  :: (Ptr RawTH1S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_Eval" c_th1s_eval 
  :: (Ptr RawTH1S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_ExecuteEvent" c_th1s_executeevent 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_FFT" c_th1s_fft 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_fill1" c_th1s_fill1 
  :: (Ptr RawTH1S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_FillN" c_th1s_filln 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_FillRandom" c_th1s_fillrandom 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_FindBin" c_th1s_findbin 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_FindFixBin" c_th1s_findfixbin 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_FindFirstBinAbove" c_th1s_findfirstbinabove 
  :: (Ptr RawTH1S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_FindLastBinAbove" c_th1s_findlastbinabove 
  :: (Ptr RawTH1S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_FitPanel" c_th1s_fitpanel 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_GetNdivisions" c_th1s_getndivisions 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_GetAxisColor" c_th1s_getaxiscolor 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_GetLabelColor" c_th1s_getlabelcolor 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_GetLabelFont" c_th1s_getlabelfont 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_GetLabelOffset" c_th1s_getlabeloffset 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetLabelSize" c_th1s_getlabelsize 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetTitleFont" c_th1s_gettitlefont 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_GetTitleOffset" c_th1s_gettitleoffset 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetTitleSize" c_th1s_gettitlesize 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetTickLength" c_th1s_getticklength 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBarOffset" c_th1s_getbaroffset 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBarWidth" c_th1s_getbarwidth 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetContour" c_th1s_getcontour 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetContourLevel" c_th1s_getcontourlevel 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetContourLevelPad" c_th1s_getcontourlevelpad 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBin" c_th1s_getbin 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_GetBinCenter" c_th1s_getbincenter 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent1" c_th1s_getbincontent1 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent2" c_th1s_getbincontent2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent3" c_th1s_getbincontent3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError1" c_th1s_getbinerror1 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError2" c_th1s_getbinerror2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError3" c_th1s_getbinerror3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinLowEdge" c_th1s_getbinlowedge 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinWidth" c_th1s_getbinwidth 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetCellContent" c_th1s_getcellcontent 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetCellError" c_th1s_getcellerror 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_SetTitle" c_th1s_settitle 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetLineColor" c_th1s_setlinecolor 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetFillColor" c_th1s_setfillcolor 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetFillStyle" c_th1s_setfillstyle 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_GetName" c_th1s_getname 
  :: (Ptr RawTH1S) -> IO CString
foreign import ccall "HROOT.h TH1S_Draw" c_th1s_draw 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_FindObject" c_th1s_findobject 
  :: (Ptr RawTH1S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1S_SaveAs" c_th1s_saveas 
  :: (Ptr RawTH1S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_Write" c_th1s_write 
  :: (Ptr RawTH1S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_delete" c_th1s_delete 
  :: (Ptr RawTH1S) -> IO ()

foreign import ccall "HROOT.h TH2C_fill2" c_th2c_fill2 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_Add" c_th2c_add 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_AddBinContent" c_th2c_addbincontent 
  :: (Ptr RawTH2C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_Chi2Test" c_th2c_chi2test 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2C_ComputeIntegral" c_th2c_computeintegral 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_DirectoryAutoAdd" c_th2c_directoryautoadd 
  :: (Ptr RawTH2C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2C_DistancetoPrimitive" c_th2c_distancetoprimitive 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_Divide" c_th2c_divide 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_DrawCopy" c_th2c_drawcopy 
  :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTH2C)
foreign import ccall "HROOT.h TH2C_DrawNormalized" c_th2c_drawnormalized 
  :: (Ptr RawTH2C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_DrawPanel" c_th2c_drawpanel 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_BufferEmpty" c_th2c_bufferempty 
  :: (Ptr RawTH2C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_Eval" c_th2c_eval 
  :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_ExecuteEvent" c_th2c_executeevent 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_FFT" c_th2c_fft 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_fill1" c_th2c_fill1 
  :: (Ptr RawTH2C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_FillN" c_th2c_filln 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_FillRandom" c_th2c_fillrandom 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_FindBin" c_th2c_findbin 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_FindFixBin" c_th2c_findfixbin 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_FindFirstBinAbove" c_th2c_findfirstbinabove 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_FindLastBinAbove" c_th2c_findlastbinabove 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_FitPanel" c_th2c_fitpanel 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_GetNdivisions" c_th2c_getndivisions 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_GetAxisColor" c_th2c_getaxiscolor 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_GetLabelColor" c_th2c_getlabelcolor 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_GetLabelFont" c_th2c_getlabelfont 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_GetLabelOffset" c_th2c_getlabeloffset 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetLabelSize" c_th2c_getlabelsize 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetTitleFont" c_th2c_gettitlefont 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_GetTitleOffset" c_th2c_gettitleoffset 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetTitleSize" c_th2c_gettitlesize 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetTickLength" c_th2c_getticklength 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBarOffset" c_th2c_getbaroffset 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBarWidth" c_th2c_getbarwidth 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetContour" c_th2c_getcontour 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetContourLevel" c_th2c_getcontourlevel 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetContourLevelPad" c_th2c_getcontourlevelpad 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBin" c_th2c_getbin 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_GetBinCenter" c_th2c_getbincenter 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent1" c_th2c_getbincontent1 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent2" c_th2c_getbincontent2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent3" c_th2c_getbincontent3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError1" c_th2c_getbinerror1 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError2" c_th2c_getbinerror2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError3" c_th2c_getbinerror3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinLowEdge" c_th2c_getbinlowedge 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinWidth" c_th2c_getbinwidth 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetCellContent" c_th2c_getcellcontent 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetCellError" c_th2c_getcellerror 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_SetTitle" c_th2c_settitle 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetLineColor" c_th2c_setlinecolor 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetFillColor" c_th2c_setfillcolor 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetFillStyle" c_th2c_setfillstyle 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_GetName" c_th2c_getname 
  :: (Ptr RawTH2C) -> IO CString
foreign import ccall "HROOT.h TH2C_Draw" c_th2c_draw 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_FindObject" c_th2c_findobject 
  :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2C_SaveAs" c_th2c_saveas 
  :: (Ptr RawTH2C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_Write" c_th2c_write 
  :: (Ptr RawTH2C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_delete" c_th2c_delete 
  :: (Ptr RawTH2C) -> IO ()

foreign import ccall "HROOT.h TH2D_fill2" c_th2d_fill2 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_Add" c_th2d_add 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_AddBinContent" c_th2d_addbincontent 
  :: (Ptr RawTH2D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_Chi2Test" c_th2d_chi2test 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2D_ComputeIntegral" c_th2d_computeintegral 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_DirectoryAutoAdd" c_th2d_directoryautoadd 
  :: (Ptr RawTH2D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2D_DistancetoPrimitive" c_th2d_distancetoprimitive 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_Divide" c_th2d_divide 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_DrawCopy" c_th2d_drawcopy 
  :: (Ptr RawTH2D) -> CString -> IO (Ptr RawTH2D)
foreign import ccall "HROOT.h TH2D_DrawNormalized" c_th2d_drawnormalized 
  :: (Ptr RawTH2D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_DrawPanel" c_th2d_drawpanel 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_BufferEmpty" c_th2d_bufferempty 
  :: (Ptr RawTH2D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_Eval" c_th2d_eval 
  :: (Ptr RawTH2D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_ExecuteEvent" c_th2d_executeevent 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_FFT" c_th2d_fft 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_fill1" c_th2d_fill1 
  :: (Ptr RawTH2D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_FillN" c_th2d_filln 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_FillRandom" c_th2d_fillrandom 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_FindBin" c_th2d_findbin 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_FindFixBin" c_th2d_findfixbin 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_FindFirstBinAbove" c_th2d_findfirstbinabove 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_FindLastBinAbove" c_th2d_findlastbinabove 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_FitPanel" c_th2d_fitpanel 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_GetNdivisions" c_th2d_getndivisions 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_GetAxisColor" c_th2d_getaxiscolor 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_GetLabelColor" c_th2d_getlabelcolor 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_GetLabelFont" c_th2d_getlabelfont 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_GetLabelOffset" c_th2d_getlabeloffset 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetLabelSize" c_th2d_getlabelsize 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetTitleFont" c_th2d_gettitlefont 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_GetTitleOffset" c_th2d_gettitleoffset 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetTitleSize" c_th2d_gettitlesize 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetTickLength" c_th2d_getticklength 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBarOffset" c_th2d_getbaroffset 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBarWidth" c_th2d_getbarwidth 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetContour" c_th2d_getcontour 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetContourLevel" c_th2d_getcontourlevel 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetContourLevelPad" c_th2d_getcontourlevelpad 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBin" c_th2d_getbin 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_GetBinCenter" c_th2d_getbincenter 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent1" c_th2d_getbincontent1 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent2" c_th2d_getbincontent2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent3" c_th2d_getbincontent3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError1" c_th2d_getbinerror1 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError2" c_th2d_getbinerror2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError3" c_th2d_getbinerror3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinLowEdge" c_th2d_getbinlowedge 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinWidth" c_th2d_getbinwidth 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetCellContent" c_th2d_getcellcontent 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetCellError" c_th2d_getcellerror 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_SetTitle" c_th2d_settitle 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetLineColor" c_th2d_setlinecolor 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetFillColor" c_th2d_setfillcolor 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetFillStyle" c_th2d_setfillstyle 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_GetName" c_th2d_getname 
  :: (Ptr RawTH2D) -> IO CString
foreign import ccall "HROOT.h TH2D_Draw" c_th2d_draw 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_FindObject" c_th2d_findobject 
  :: (Ptr RawTH2D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2D_SaveAs" c_th2d_saveas 
  :: (Ptr RawTH2D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_Write" c_th2d_write 
  :: (Ptr RawTH2D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_delete" c_th2d_delete 
  :: (Ptr RawTH2D) -> IO ()

foreign import ccall "HROOT.h TH2F_fill2" c_th2f_fill2 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_Add" c_th2f_add 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_AddBinContent" c_th2f_addbincontent 
  :: (Ptr RawTH2F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_Chi2Test" c_th2f_chi2test 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2F_ComputeIntegral" c_th2f_computeintegral 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_DirectoryAutoAdd" c_th2f_directoryautoadd 
  :: (Ptr RawTH2F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2F_DistancetoPrimitive" c_th2f_distancetoprimitive 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_Divide" c_th2f_divide 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_DrawCopy" c_th2f_drawcopy 
  :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTH2F)
foreign import ccall "HROOT.h TH2F_DrawNormalized" c_th2f_drawnormalized 
  :: (Ptr RawTH2F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_DrawPanel" c_th2f_drawpanel 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_BufferEmpty" c_th2f_bufferempty 
  :: (Ptr RawTH2F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_Eval" c_th2f_eval 
  :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_ExecuteEvent" c_th2f_executeevent 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_FFT" c_th2f_fft 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_fill1" c_th2f_fill1 
  :: (Ptr RawTH2F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_FillN" c_th2f_filln 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_FillRandom" c_th2f_fillrandom 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_FindBin" c_th2f_findbin 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_FindFixBin" c_th2f_findfixbin 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_FindFirstBinAbove" c_th2f_findfirstbinabove 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_FindLastBinAbove" c_th2f_findlastbinabove 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_FitPanel" c_th2f_fitpanel 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_GetNdivisions" c_th2f_getndivisions 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_GetAxisColor" c_th2f_getaxiscolor 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_GetLabelColor" c_th2f_getlabelcolor 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_GetLabelFont" c_th2f_getlabelfont 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_GetLabelOffset" c_th2f_getlabeloffset 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetLabelSize" c_th2f_getlabelsize 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetTitleFont" c_th2f_gettitlefont 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_GetTitleOffset" c_th2f_gettitleoffset 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetTitleSize" c_th2f_gettitlesize 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetTickLength" c_th2f_getticklength 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBarOffset" c_th2f_getbaroffset 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBarWidth" c_th2f_getbarwidth 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetContour" c_th2f_getcontour 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetContourLevel" c_th2f_getcontourlevel 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetContourLevelPad" c_th2f_getcontourlevelpad 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBin" c_th2f_getbin 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_GetBinCenter" c_th2f_getbincenter 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent1" c_th2f_getbincontent1 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent2" c_th2f_getbincontent2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent3" c_th2f_getbincontent3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError1" c_th2f_getbinerror1 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError2" c_th2f_getbinerror2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError3" c_th2f_getbinerror3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinLowEdge" c_th2f_getbinlowedge 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinWidth" c_th2f_getbinwidth 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetCellContent" c_th2f_getcellcontent 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetCellError" c_th2f_getcellerror 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_SetTitle" c_th2f_settitle 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetLineColor" c_th2f_setlinecolor 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetFillColor" c_th2f_setfillcolor 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetFillStyle" c_th2f_setfillstyle 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_GetName" c_th2f_getname 
  :: (Ptr RawTH2F) -> IO CString
foreign import ccall "HROOT.h TH2F_Draw" c_th2f_draw 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_FindObject" c_th2f_findobject 
  :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2F_SaveAs" c_th2f_saveas 
  :: (Ptr RawTH2F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_Write" c_th2f_write 
  :: (Ptr RawTH2F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_delete" c_th2f_delete 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_newTH2F" c_th2f_newth2f 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH2F)

foreign import ccall "HROOT.h TH2I_fill2" c_th2i_fill2 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_Add" c_th2i_add 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_AddBinContent" c_th2i_addbincontent 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_Chi2Test" c_th2i_chi2test 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2I_ComputeIntegral" c_th2i_computeintegral 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_DirectoryAutoAdd" c_th2i_directoryautoadd 
  :: (Ptr RawTH2I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2I_DistancetoPrimitive" c_th2i_distancetoprimitive 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_Divide" c_th2i_divide 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_DrawCopy" c_th2i_drawcopy 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTH2I)
foreign import ccall "HROOT.h TH2I_DrawNormalized" c_th2i_drawnormalized 
  :: (Ptr RawTH2I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_DrawPanel" c_th2i_drawpanel 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_BufferEmpty" c_th2i_bufferempty 
  :: (Ptr RawTH2I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_Eval" c_th2i_eval 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_ExecuteEvent" c_th2i_executeevent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_FFT" c_th2i_fft 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_fill1" c_th2i_fill1 
  :: (Ptr RawTH2I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_FillN" c_th2i_filln 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_FillRandom" c_th2i_fillrandom 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_FindBin" c_th2i_findbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_FindFixBin" c_th2i_findfixbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_FindFirstBinAbove" c_th2i_findfirstbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_FindLastBinAbove" c_th2i_findlastbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_FitPanel" c_th2i_fitpanel 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_GetNdivisions" c_th2i_getndivisions 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_GetAxisColor" c_th2i_getaxiscolor 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_GetLabelColor" c_th2i_getlabelcolor 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_GetLabelFont" c_th2i_getlabelfont 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_GetLabelOffset" c_th2i_getlabeloffset 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetLabelSize" c_th2i_getlabelsize 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetTitleFont" c_th2i_gettitlefont 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_GetTitleOffset" c_th2i_gettitleoffset 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetTitleSize" c_th2i_gettitlesize 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetTickLength" c_th2i_getticklength 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBarOffset" c_th2i_getbaroffset 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBarWidth" c_th2i_getbarwidth 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetContour" c_th2i_getcontour 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetContourLevel" c_th2i_getcontourlevel 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetContourLevelPad" c_th2i_getcontourlevelpad 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBin" c_th2i_getbin 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_GetBinCenter" c_th2i_getbincenter 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent1" c_th2i_getbincontent1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent2" c_th2i_getbincontent2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent3" c_th2i_getbincontent3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError1" c_th2i_getbinerror1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError2" c_th2i_getbinerror2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError3" c_th2i_getbinerror3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinLowEdge" c_th2i_getbinlowedge 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinWidth" c_th2i_getbinwidth 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetCellContent" c_th2i_getcellcontent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetCellError" c_th2i_getcellerror 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_SetTitle" c_th2i_settitle 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetLineColor" c_th2i_setlinecolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetFillColor" c_th2i_setfillcolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetFillStyle" c_th2i_setfillstyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_GetName" c_th2i_getname 
  :: (Ptr RawTH2I) -> IO CString
foreign import ccall "HROOT.h TH2I_Draw" c_th2i_draw 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_FindObject" c_th2i_findobject 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2I_SaveAs" c_th2i_saveas 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_Write" c_th2i_write 
  :: (Ptr RawTH2I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_delete" c_th2i_delete 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOT.h TH2Poly_fill2" c_th2poly_fill2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_Add" c_th2poly_add 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_AddBinContent" c_th2poly_addbincontent 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_Chi2Test" c_th2poly_chi2test 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_ComputeIntegral" c_th2poly_computeintegral 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_DirectoryAutoAdd" c_th2poly_directoryautoadd 
  :: (Ptr RawTH2Poly) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2Poly_DistancetoPrimitive" c_th2poly_distancetoprimitive 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_Divide" c_th2poly_divide 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_DrawCopy" c_th2poly_drawcopy 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTH2Poly)
foreign import ccall "HROOT.h TH2Poly_DrawNormalized" c_th2poly_drawnormalized 
  :: (Ptr RawTH2Poly) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_DrawPanel" c_th2poly_drawpanel 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_BufferEmpty" c_th2poly_bufferempty 
  :: (Ptr RawTH2Poly) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_Eval" c_th2poly_eval 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_ExecuteEvent" c_th2poly_executeevent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_FFT" c_th2poly_fft 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_fill1" c_th2poly_fill1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FillN" c_th2poly_filln 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_FillRandom" c_th2poly_fillrandom 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_FindBin" c_th2poly_findbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindFixBin" c_th2poly_findfixbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindFirstBinAbove" c_th2poly_findfirstbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindLastBinAbove" c_th2poly_findlastbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FitPanel" c_th2poly_fitpanel 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_GetNdivisions" c_th2poly_getndivisions 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetAxisColor" c_th2poly_getaxiscolor 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetLabelColor" c_th2poly_getlabelcolor 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetLabelFont" c_th2poly_getlabelfont 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetLabelOffset" c_th2poly_getlabeloffset 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetLabelSize" c_th2poly_getlabelsize 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetTitleFont" c_th2poly_gettitlefont 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetTitleOffset" c_th2poly_gettitleoffset 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetTitleSize" c_th2poly_gettitlesize 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetTickLength" c_th2poly_getticklength 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBarOffset" c_th2poly_getbaroffset 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBarWidth" c_th2poly_getbarwidth 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetContour" c_th2poly_getcontour 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetContourLevel" c_th2poly_getcontourlevel 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetContourLevelPad" c_th2poly_getcontourlevelpad 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBin" c_th2poly_getbin 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetBinCenter" c_th2poly_getbincenter 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent1" c_th2poly_getbincontent1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent2" c_th2poly_getbincontent2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent3" c_th2poly_getbincontent3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError1" c_th2poly_getbinerror1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError2" c_th2poly_getbinerror2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError3" c_th2poly_getbinerror3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinLowEdge" c_th2poly_getbinlowedge 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinWidth" c_th2poly_getbinwidth 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetCellContent" c_th2poly_getcellcontent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetCellError" c_th2poly_getcellerror 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_SetTitle" c_th2poly_settitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetLineColor" c_th2poly_setlinecolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetFillColor" c_th2poly_setfillcolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetFillStyle" c_th2poly_setfillstyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_GetName" c_th2poly_getname 
  :: (Ptr RawTH2Poly) -> IO CString
foreign import ccall "HROOT.h TH2Poly_Draw" c_th2poly_draw 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_FindObject" c_th2poly_findobject 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2Poly_SaveAs" c_th2poly_saveas 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_Write" c_th2poly_write 
  :: (Ptr RawTH2Poly) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_delete" c_th2poly_delete 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOT.h TH2S_fill2" c_th2s_fill2 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_Add" c_th2s_add 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_AddBinContent" c_th2s_addbincontent 
  :: (Ptr RawTH2S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_Chi2Test" c_th2s_chi2test 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2S_ComputeIntegral" c_th2s_computeintegral 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_DirectoryAutoAdd" c_th2s_directoryautoadd 
  :: (Ptr RawTH2S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2S_DistancetoPrimitive" c_th2s_distancetoprimitive 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_Divide" c_th2s_divide 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_DrawCopy" c_th2s_drawcopy 
  :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTH2S)
foreign import ccall "HROOT.h TH2S_DrawNormalized" c_th2s_drawnormalized 
  :: (Ptr RawTH2S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_DrawPanel" c_th2s_drawpanel 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_BufferEmpty" c_th2s_bufferempty 
  :: (Ptr RawTH2S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_Eval" c_th2s_eval 
  :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_ExecuteEvent" c_th2s_executeevent 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_FFT" c_th2s_fft 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_fill1" c_th2s_fill1 
  :: (Ptr RawTH2S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_FillN" c_th2s_filln 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_FillRandom" c_th2s_fillrandom 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_FindBin" c_th2s_findbin 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_FindFixBin" c_th2s_findfixbin 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_FindFirstBinAbove" c_th2s_findfirstbinabove 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_FindLastBinAbove" c_th2s_findlastbinabove 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_FitPanel" c_th2s_fitpanel 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_GetNdivisions" c_th2s_getndivisions 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_GetAxisColor" c_th2s_getaxiscolor 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_GetLabelColor" c_th2s_getlabelcolor 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_GetLabelFont" c_th2s_getlabelfont 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_GetLabelOffset" c_th2s_getlabeloffset 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetLabelSize" c_th2s_getlabelsize 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetTitleFont" c_th2s_gettitlefont 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_GetTitleOffset" c_th2s_gettitleoffset 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetTitleSize" c_th2s_gettitlesize 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetTickLength" c_th2s_getticklength 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBarOffset" c_th2s_getbaroffset 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBarWidth" c_th2s_getbarwidth 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetContour" c_th2s_getcontour 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetContourLevel" c_th2s_getcontourlevel 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetContourLevelPad" c_th2s_getcontourlevelpad 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBin" c_th2s_getbin 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_GetBinCenter" c_th2s_getbincenter 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent1" c_th2s_getbincontent1 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent2" c_th2s_getbincontent2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent3" c_th2s_getbincontent3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError1" c_th2s_getbinerror1 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError2" c_th2s_getbinerror2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError3" c_th2s_getbinerror3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinLowEdge" c_th2s_getbinlowedge 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinWidth" c_th2s_getbinwidth 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetCellContent" c_th2s_getcellcontent 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetCellError" c_th2s_getcellerror 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_SetTitle" c_th2s_settitle 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetLineColor" c_th2s_setlinecolor 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetFillColor" c_th2s_setfillcolor 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetFillStyle" c_th2s_setfillstyle 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_GetName" c_th2s_getname 
  :: (Ptr RawTH2S) -> IO CString
foreign import ccall "HROOT.h TH2S_Draw" c_th2s_draw 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_FindObject" c_th2s_findobject 
  :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2S_SaveAs" c_th2s_saveas 
  :: (Ptr RawTH2S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_Write" c_th2s_write 
  :: (Ptr RawTH2S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_delete" c_th2s_delete 
  :: (Ptr RawTH2S) -> IO ()

foreign import ccall "HROOT.h TH3C_Add" c_th3c_add 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_AddBinContent" c_th3c_addbincontent 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_Chi2Test" c_th3c_chi2test 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3C_ComputeIntegral" c_th3c_computeintegral 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_DirectoryAutoAdd" c_th3c_directoryautoadd 
  :: (Ptr RawTH3C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3C_DistancetoPrimitive" c_th3c_distancetoprimitive 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_Divide" c_th3c_divide 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_DrawCopy" c_th3c_drawcopy 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTH3C)
foreign import ccall "HROOT.h TH3C_DrawNormalized" c_th3c_drawnormalized 
  :: (Ptr RawTH3C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_DrawPanel" c_th3c_drawpanel 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_BufferEmpty" c_th3c_bufferempty 
  :: (Ptr RawTH3C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_Eval" c_th3c_eval 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_ExecuteEvent" c_th3c_executeevent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_FFT" c_th3c_fft 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_fill1" c_th3c_fill1 
  :: (Ptr RawTH3C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FillN" c_th3c_filln 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_FillRandom" c_th3c_fillrandom 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_FindBin" c_th3c_findbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FindFixBin" c_th3c_findfixbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FindFirstBinAbove" c_th3c_findfirstbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_FindLastBinAbove" c_th3c_findlastbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_FitPanel" c_th3c_fitpanel 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_GetNdivisions" c_th3c_getndivisions 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_GetAxisColor" c_th3c_getaxiscolor 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_GetLabelColor" c_th3c_getlabelcolor 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_GetLabelFont" c_th3c_getlabelfont 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_GetLabelOffset" c_th3c_getlabeloffset 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetLabelSize" c_th3c_getlabelsize 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetTitleFont" c_th3c_gettitlefont 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_GetTitleOffset" c_th3c_gettitleoffset 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetTitleSize" c_th3c_gettitlesize 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetTickLength" c_th3c_getticklength 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBarOffset" c_th3c_getbaroffset 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBarWidth" c_th3c_getbarwidth 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetContour" c_th3c_getcontour 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetContourLevel" c_th3c_getcontourlevel 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetContourLevelPad" c_th3c_getcontourlevelpad 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBin" c_th3c_getbin 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_GetBinCenter" c_th3c_getbincenter 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent1" c_th3c_getbincontent1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent2" c_th3c_getbincontent2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent3" c_th3c_getbincontent3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError1" c_th3c_getbinerror1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError2" c_th3c_getbinerror2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError3" c_th3c_getbinerror3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinLowEdge" c_th3c_getbinlowedge 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinWidth" c_th3c_getbinwidth 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetCellContent" c_th3c_getcellcontent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetCellError" c_th3c_getcellerror 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_SetTitle" c_th3c_settitle 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetLineColor" c_th3c_setlinecolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetFillColor" c_th3c_setfillcolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetFillStyle" c_th3c_setfillstyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_GetName" c_th3c_getname 
  :: (Ptr RawTH3C) -> IO CString
foreign import ccall "HROOT.h TH3C_Draw" c_th3c_draw 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_FindObject" c_th3c_findobject 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3C_SaveAs" c_th3c_saveas 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_Write" c_th3c_write 
  :: (Ptr RawTH3C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_delete" c_th3c_delete 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOT.h TH3D_Add" c_th3d_add 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_AddBinContent" c_th3d_addbincontent 
  :: (Ptr RawTH3D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_Chi2Test" c_th3d_chi2test 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3D_ComputeIntegral" c_th3d_computeintegral 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_DirectoryAutoAdd" c_th3d_directoryautoadd 
  :: (Ptr RawTH3D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3D_DistancetoPrimitive" c_th3d_distancetoprimitive 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_Divide" c_th3d_divide 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_DrawCopy" c_th3d_drawcopy 
  :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTH3D)
foreign import ccall "HROOT.h TH3D_DrawNormalized" c_th3d_drawnormalized 
  :: (Ptr RawTH3D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_DrawPanel" c_th3d_drawpanel 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_BufferEmpty" c_th3d_bufferempty 
  :: (Ptr RawTH3D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_Eval" c_th3d_eval 
  :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_ExecuteEvent" c_th3d_executeevent 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_FFT" c_th3d_fft 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_fill1" c_th3d_fill1 
  :: (Ptr RawTH3D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FillN" c_th3d_filln 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_FillRandom" c_th3d_fillrandom 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_FindBin" c_th3d_findbin 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FindFixBin" c_th3d_findfixbin 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FindFirstBinAbove" c_th3d_findfirstbinabove 
  :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_FindLastBinAbove" c_th3d_findlastbinabove 
  :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_FitPanel" c_th3d_fitpanel 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_GetNdivisions" c_th3d_getndivisions 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_GetAxisColor" c_th3d_getaxiscolor 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_GetLabelColor" c_th3d_getlabelcolor 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_GetLabelFont" c_th3d_getlabelfont 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_GetLabelOffset" c_th3d_getlabeloffset 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetLabelSize" c_th3d_getlabelsize 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetTitleFont" c_th3d_gettitlefont 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_GetTitleOffset" c_th3d_gettitleoffset 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetTitleSize" c_th3d_gettitlesize 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetTickLength" c_th3d_getticklength 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBarOffset" c_th3d_getbaroffset 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBarWidth" c_th3d_getbarwidth 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetContour" c_th3d_getcontour 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetContourLevel" c_th3d_getcontourlevel 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetContourLevelPad" c_th3d_getcontourlevelpad 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBin" c_th3d_getbin 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_GetBinCenter" c_th3d_getbincenter 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent1" c_th3d_getbincontent1 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent2" c_th3d_getbincontent2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent3" c_th3d_getbincontent3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError1" c_th3d_getbinerror1 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError2" c_th3d_getbinerror2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError3" c_th3d_getbinerror3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinLowEdge" c_th3d_getbinlowedge 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinWidth" c_th3d_getbinwidth 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetCellContent" c_th3d_getcellcontent 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetCellError" c_th3d_getcellerror 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_SetTitle" c_th3d_settitle 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetLineColor" c_th3d_setlinecolor 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetFillColor" c_th3d_setfillcolor 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetFillStyle" c_th3d_setfillstyle 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_GetName" c_th3d_getname 
  :: (Ptr RawTH3D) -> IO CString
foreign import ccall "HROOT.h TH3D_Draw" c_th3d_draw 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_FindObject" c_th3d_findobject 
  :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3D_SaveAs" c_th3d_saveas 
  :: (Ptr RawTH3D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_Write" c_th3d_write 
  :: (Ptr RawTH3D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_delete" c_th3d_delete 
  :: (Ptr RawTH3D) -> IO ()

foreign import ccall "HROOT.h TH3F_Add" c_th3f_add 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_AddBinContent" c_th3f_addbincontent 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_Chi2Test" c_th3f_chi2test 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3F_ComputeIntegral" c_th3f_computeintegral 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_DirectoryAutoAdd" c_th3f_directoryautoadd 
  :: (Ptr RawTH3F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3F_DistancetoPrimitive" c_th3f_distancetoprimitive 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_Divide" c_th3f_divide 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_DrawCopy" c_th3f_drawcopy 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTH3F)
foreign import ccall "HROOT.h TH3F_DrawNormalized" c_th3f_drawnormalized 
  :: (Ptr RawTH3F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_DrawPanel" c_th3f_drawpanel 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_BufferEmpty" c_th3f_bufferempty 
  :: (Ptr RawTH3F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_Eval" c_th3f_eval 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_ExecuteEvent" c_th3f_executeevent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_FFT" c_th3f_fft 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_fill1" c_th3f_fill1 
  :: (Ptr RawTH3F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FillN" c_th3f_filln 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_FillRandom" c_th3f_fillrandom 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_FindBin" c_th3f_findbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FindFixBin" c_th3f_findfixbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FindFirstBinAbove" c_th3f_findfirstbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_FindLastBinAbove" c_th3f_findlastbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_FitPanel" c_th3f_fitpanel 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_GetNdivisions" c_th3f_getndivisions 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_GetAxisColor" c_th3f_getaxiscolor 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_GetLabelColor" c_th3f_getlabelcolor 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_GetLabelFont" c_th3f_getlabelfont 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_GetLabelOffset" c_th3f_getlabeloffset 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetLabelSize" c_th3f_getlabelsize 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetTitleFont" c_th3f_gettitlefont 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_GetTitleOffset" c_th3f_gettitleoffset 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetTitleSize" c_th3f_gettitlesize 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetTickLength" c_th3f_getticklength 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBarOffset" c_th3f_getbaroffset 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBarWidth" c_th3f_getbarwidth 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetContour" c_th3f_getcontour 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetContourLevel" c_th3f_getcontourlevel 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetContourLevelPad" c_th3f_getcontourlevelpad 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBin" c_th3f_getbin 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_GetBinCenter" c_th3f_getbincenter 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent1" c_th3f_getbincontent1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent2" c_th3f_getbincontent2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent3" c_th3f_getbincontent3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError1" c_th3f_getbinerror1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError2" c_th3f_getbinerror2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError3" c_th3f_getbinerror3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinLowEdge" c_th3f_getbinlowedge 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinWidth" c_th3f_getbinwidth 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetCellContent" c_th3f_getcellcontent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetCellError" c_th3f_getcellerror 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_SetTitle" c_th3f_settitle 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetLineColor" c_th3f_setlinecolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetFillColor" c_th3f_setfillcolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetFillStyle" c_th3f_setfillstyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_GetName" c_th3f_getname 
  :: (Ptr RawTH3F) -> IO CString
foreign import ccall "HROOT.h TH3F_Draw" c_th3f_draw 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_FindObject" c_th3f_findobject 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3F_SaveAs" c_th3f_saveas 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_Write" c_th3f_write 
  :: (Ptr RawTH3F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_delete" c_th3f_delete 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOT.h TH3I_Add" c_th3i_add 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_AddBinContent" c_th3i_addbincontent 
  :: (Ptr RawTH3I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_Chi2Test" c_th3i_chi2test 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3I_ComputeIntegral" c_th3i_computeintegral 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_DirectoryAutoAdd" c_th3i_directoryautoadd 
  :: (Ptr RawTH3I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3I_DistancetoPrimitive" c_th3i_distancetoprimitive 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_Divide" c_th3i_divide 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_DrawCopy" c_th3i_drawcopy 
  :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTH3I)
foreign import ccall "HROOT.h TH3I_DrawNormalized" c_th3i_drawnormalized 
  :: (Ptr RawTH3I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_DrawPanel" c_th3i_drawpanel 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_BufferEmpty" c_th3i_bufferempty 
  :: (Ptr RawTH3I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_Eval" c_th3i_eval 
  :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_ExecuteEvent" c_th3i_executeevent 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_FFT" c_th3i_fft 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_fill1" c_th3i_fill1 
  :: (Ptr RawTH3I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FillN" c_th3i_filln 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_FillRandom" c_th3i_fillrandom 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_FindBin" c_th3i_findbin 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FindFixBin" c_th3i_findfixbin 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FindFirstBinAbove" c_th3i_findfirstbinabove 
  :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_FindLastBinAbove" c_th3i_findlastbinabove 
  :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_FitPanel" c_th3i_fitpanel 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_GetNdivisions" c_th3i_getndivisions 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_GetAxisColor" c_th3i_getaxiscolor 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_GetLabelColor" c_th3i_getlabelcolor 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_GetLabelFont" c_th3i_getlabelfont 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_GetLabelOffset" c_th3i_getlabeloffset 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetLabelSize" c_th3i_getlabelsize 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetTitleFont" c_th3i_gettitlefont 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_GetTitleOffset" c_th3i_gettitleoffset 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetTitleSize" c_th3i_gettitlesize 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetTickLength" c_th3i_getticklength 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBarOffset" c_th3i_getbaroffset 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBarWidth" c_th3i_getbarwidth 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetContour" c_th3i_getcontour 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetContourLevel" c_th3i_getcontourlevel 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetContourLevelPad" c_th3i_getcontourlevelpad 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBin" c_th3i_getbin 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_GetBinCenter" c_th3i_getbincenter 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent1" c_th3i_getbincontent1 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent2" c_th3i_getbincontent2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent3" c_th3i_getbincontent3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError1" c_th3i_getbinerror1 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError2" c_th3i_getbinerror2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError3" c_th3i_getbinerror3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinLowEdge" c_th3i_getbinlowedge 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinWidth" c_th3i_getbinwidth 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetCellContent" c_th3i_getcellcontent 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetCellError" c_th3i_getcellerror 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_SetTitle" c_th3i_settitle 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetLineColor" c_th3i_setlinecolor 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetFillColor" c_th3i_setfillcolor 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetFillStyle" c_th3i_setfillstyle 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_GetName" c_th3i_getname 
  :: (Ptr RawTH3I) -> IO CString
foreign import ccall "HROOT.h TH3I_Draw" c_th3i_draw 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_FindObject" c_th3i_findobject 
  :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3I_SaveAs" c_th3i_saveas 
  :: (Ptr RawTH3I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_Write" c_th3i_write 
  :: (Ptr RawTH3I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_delete" c_th3i_delete 
  :: (Ptr RawTH3I) -> IO ()

foreign import ccall "HROOT.h TH3S_Add" c_th3s_add 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_AddBinContent" c_th3s_addbincontent 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_Chi2Test" c_th3s_chi2test 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3S_ComputeIntegral" c_th3s_computeintegral 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_DirectoryAutoAdd" c_th3s_directoryautoadd 
  :: (Ptr RawTH3S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3S_DistancetoPrimitive" c_th3s_distancetoprimitive 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_Divide" c_th3s_divide 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_DrawCopy" c_th3s_drawcopy 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTH3S)
foreign import ccall "HROOT.h TH3S_DrawNormalized" c_th3s_drawnormalized 
  :: (Ptr RawTH3S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_DrawPanel" c_th3s_drawpanel 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_BufferEmpty" c_th3s_bufferempty 
  :: (Ptr RawTH3S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_Eval" c_th3s_eval 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_ExecuteEvent" c_th3s_executeevent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_FFT" c_th3s_fft 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_fill1" c_th3s_fill1 
  :: (Ptr RawTH3S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FillN" c_th3s_filln 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_FillRandom" c_th3s_fillrandom 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_FindBin" c_th3s_findbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FindFixBin" c_th3s_findfixbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FindFirstBinAbove" c_th3s_findfirstbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_FindLastBinAbove" c_th3s_findlastbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_FitPanel" c_th3s_fitpanel 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_GetNdivisions" c_th3s_getndivisions 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_GetAxisColor" c_th3s_getaxiscolor 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_GetLabelColor" c_th3s_getlabelcolor 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_GetLabelFont" c_th3s_getlabelfont 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_GetLabelOffset" c_th3s_getlabeloffset 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetLabelSize" c_th3s_getlabelsize 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetTitleFont" c_th3s_gettitlefont 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_GetTitleOffset" c_th3s_gettitleoffset 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetTitleSize" c_th3s_gettitlesize 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetTickLength" c_th3s_getticklength 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBarOffset" c_th3s_getbaroffset 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBarWidth" c_th3s_getbarwidth 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetContour" c_th3s_getcontour 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetContourLevel" c_th3s_getcontourlevel 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetContourLevelPad" c_th3s_getcontourlevelpad 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBin" c_th3s_getbin 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_GetBinCenter" c_th3s_getbincenter 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent1" c_th3s_getbincontent1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent2" c_th3s_getbincontent2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent3" c_th3s_getbincontent3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError1" c_th3s_getbinerror1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError2" c_th3s_getbinerror2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError3" c_th3s_getbinerror3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinLowEdge" c_th3s_getbinlowedge 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinWidth" c_th3s_getbinwidth 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetCellContent" c_th3s_getcellcontent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetCellError" c_th3s_getcellerror 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_SetTitle" c_th3s_settitle 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetLineColor" c_th3s_setlinecolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetFillColor" c_th3s_setfillcolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetFillStyle" c_th3s_setfillstyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_GetName" c_th3s_getname 
  :: (Ptr RawTH3S) -> IO CString
foreign import ccall "HROOT.h TH3S_Draw" c_th3s_draw 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_FindObject" c_th3s_findobject 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3S_SaveAs" c_th3s_saveas 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_Write" c_th3s_write 
  :: (Ptr RawTH3S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_delete" c_th3s_delete 
  :: (Ptr RawTH3S) -> IO ()

foreign import ccall "HROOT.h TQObject_delete" c_tqobject_delete 
  :: (Ptr RawTQObject) -> IO ()

foreign import ccall "HROOT.h TVirtualPad_GetName" c_tvirtualpad_getname 
  :: (Ptr RawTVirtualPad) -> IO CString
foreign import ccall "HROOT.h TVirtualPad_Draw" c_tvirtualpad_draw 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_FindObject" c_tvirtualpad_findobject 
  :: (Ptr RawTVirtualPad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TVirtualPad_SaveAs" c_tvirtualpad_saveas 
  :: (Ptr RawTVirtualPad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_Write" c_tvirtualpad_write 
  :: (Ptr RawTVirtualPad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_SetLineColor" c_tvirtualpad_setlinecolor 
  :: (Ptr RawTVirtualPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetFillColor" c_tvirtualpad_setfillcolor 
  :: (Ptr RawTVirtualPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetFillStyle" c_tvirtualpad_setfillstyle 
  :: (Ptr RawTVirtualPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TVirtualPad_delete" c_tvirtualpad_delete 
  :: (Ptr RawTVirtualPad) -> IO ()
foreign import ccall "HROOT.h TVirtualPad_GetFrame" c_tvirtualpad_getframe 
  :: (Ptr RawTVirtualPad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TVirtualPad_Range" c_tvirtualpad_range 
  :: (Ptr RawTVirtualPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOT.h TPad_GetFrame" c_tpad_getframe 
  :: (Ptr RawTPad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TPad_Range" c_tpad_range 
  :: (Ptr RawTPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_GetName" c_tpad_getname 
  :: (Ptr RawTPad) -> IO CString
foreign import ccall "HROOT.h TPad_Draw" c_tpad_draw 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_FindObject" c_tpad_findobject 
  :: (Ptr RawTPad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPad_SaveAs" c_tpad_saveas 
  :: (Ptr RawTPad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPad_Write" c_tpad_write 
  :: (Ptr RawTPad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPad_SetLineColor" c_tpad_setlinecolor 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetFillColor" c_tpad_setfillcolor 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetFillStyle" c_tpad_setfillstyle 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_delete" c_tpad_delete 
  :: (Ptr RawTPad) -> IO ()

foreign import ccall "HROOT.h TButton_SetTextColor" c_tbutton_settextcolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetTextAlign" c_tbutton_settextalign 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetTextSize" c_tbutton_settextsize 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_GetFrame" c_tbutton_getframe 
  :: (Ptr RawTButton) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TButton_Range" c_tbutton_range 
  :: (Ptr RawTButton) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_GetName" c_tbutton_getname 
  :: (Ptr RawTButton) -> IO CString
foreign import ccall "HROOT.h TButton_Draw" c_tbutton_draw 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_FindObject" c_tbutton_findobject 
  :: (Ptr RawTButton) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TButton_SaveAs" c_tbutton_saveas 
  :: (Ptr RawTButton) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TButton_Write" c_tbutton_write 
  :: (Ptr RawTButton) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TButton_SetLineColor" c_tbutton_setlinecolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetFillColor" c_tbutton_setfillcolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetFillStyle" c_tbutton_setfillstyle 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_delete" c_tbutton_delete 
  :: (Ptr RawTButton) -> IO ()

foreign import ccall "HROOT.h TGroupButton_SetTextColor" c_tgroupbutton_settextcolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextAlign" c_tgroupbutton_settextalign 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextSize" c_tgroupbutton_settextsize 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_GetFrame" c_tgroupbutton_getframe 
  :: (Ptr RawTGroupButton) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TGroupButton_Range" c_tgroupbutton_range 
  :: (Ptr RawTGroupButton) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_GetName" c_tgroupbutton_getname 
  :: (Ptr RawTGroupButton) -> IO CString
foreign import ccall "HROOT.h TGroupButton_Draw" c_tgroupbutton_draw 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_FindObject" c_tgroupbutton_findobject 
  :: (Ptr RawTGroupButton) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGroupButton_SaveAs" c_tgroupbutton_saveas 
  :: (Ptr RawTGroupButton) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_Write" c_tgroupbutton_write 
  :: (Ptr RawTGroupButton) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGroupButton_SetLineColor" c_tgroupbutton_setlinecolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetFillColor" c_tgroupbutton_setfillcolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetFillStyle" c_tgroupbutton_setfillstyle 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_delete" c_tgroupbutton_delete 
  :: (Ptr RawTGroupButton) -> IO ()

foreign import ccall "HROOT.h TCanvas_GetFrame" c_tcanvas_getframe 
  :: (Ptr RawTCanvas) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TCanvas_Range" c_tcanvas_range 
  :: (Ptr RawTCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_GetName" c_tcanvas_getname 
  :: (Ptr RawTCanvas) -> IO CString
foreign import ccall "HROOT.h TCanvas_Draw" c_tcanvas_draw 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_FindObject" c_tcanvas_findobject 
  :: (Ptr RawTCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCanvas_SaveAs" c_tcanvas_saveas 
  :: (Ptr RawTCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_Write" c_tcanvas_write 
  :: (Ptr RawTCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCanvas_SetLineColor" c_tcanvas_setlinecolor 
  :: (Ptr RawTCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TCanvas_SetFillColor" c_tcanvas_setfillcolor 
  :: (Ptr RawTCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TCanvas_SetFillStyle" c_tcanvas_setfillstyle 
  :: (Ptr RawTCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TCanvas_delete" c_tcanvas_delete 
  :: (Ptr RawTCanvas) -> IO ()
foreign import ccall "HROOT.h TCanvas_newTCanvas" c_tcanvas_newtcanvas 
  :: CString -> CString -> CInt -> CInt -> IO (Ptr RawTCanvas)

foreign import ccall "HROOT.h TDialogCanvas_SetTextColor" c_tdialogcanvas_settextcolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextAlign" c_tdialogcanvas_settextalign 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextSize" c_tdialogcanvas_settextsize 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_GetFrame" c_tdialogcanvas_getframe 
  :: (Ptr RawTDialogCanvas) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TDialogCanvas_Range" c_tdialogcanvas_range 
  :: (Ptr RawTDialogCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_GetName" c_tdialogcanvas_getname 
  :: (Ptr RawTDialogCanvas) -> IO CString
foreign import ccall "HROOT.h TDialogCanvas_Draw" c_tdialogcanvas_draw 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_FindObject" c_tdialogcanvas_findobject 
  :: (Ptr RawTDialogCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDialogCanvas_SaveAs" c_tdialogcanvas_saveas 
  :: (Ptr RawTDialogCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_Write" c_tdialogcanvas_write 
  :: (Ptr RawTDialogCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_SetLineColor" c_tdialogcanvas_setlinecolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetFillColor" c_tdialogcanvas_setfillcolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetFillStyle" c_tdialogcanvas_setfillstyle 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_delete" c_tdialogcanvas_delete 
  :: (Ptr RawTDialogCanvas) -> IO ()

foreign import ccall "HROOT.h TInspectCanvas_SetTextColor" c_tinspectcanvas_settextcolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextAlign" c_tinspectcanvas_settextalign 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextSize" c_tinspectcanvas_settextsize 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_GetFrame" c_tinspectcanvas_getframe 
  :: (Ptr RawTInspectCanvas) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TInspectCanvas_Range" c_tinspectcanvas_range 
  :: (Ptr RawTInspectCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_GetName" c_tinspectcanvas_getname 
  :: (Ptr RawTInspectCanvas) -> IO CString
foreign import ccall "HROOT.h TInspectCanvas_Draw" c_tinspectcanvas_draw 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_FindObject" c_tinspectcanvas_findobject 
  :: (Ptr RawTInspectCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TInspectCanvas_SaveAs" c_tinspectcanvas_saveas 
  :: (Ptr RawTInspectCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_Write" c_tinspectcanvas_write 
  :: (Ptr RawTInspectCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_SetLineColor" c_tinspectcanvas_setlinecolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetFillColor" c_tinspectcanvas_setfillcolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetFillStyle" c_tinspectcanvas_setfillstyle 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_delete" c_tinspectcanvas_delete 
  :: (Ptr RawTInspectCanvas) -> IO ()

foreign import ccall "HROOT.h TEvePad_GetFrame" c_tevepad_getframe 
  :: (Ptr RawTEvePad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TEvePad_Range" c_tevepad_range 
  :: (Ptr RawTEvePad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_GetName" c_tevepad_getname 
  :: (Ptr RawTEvePad) -> IO CString
foreign import ccall "HROOT.h TEvePad_Draw" c_tevepad_draw 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_FindObject" c_tevepad_findobject 
  :: (Ptr RawTEvePad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEvePad_SaveAs" c_tevepad_saveas 
  :: (Ptr RawTEvePad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_Write" c_tevepad_write 
  :: (Ptr RawTEvePad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEvePad_SetLineColor" c_tevepad_setlinecolor 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetFillColor" c_tevepad_setfillcolor 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetFillStyle" c_tevepad_setfillstyle 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_delete" c_tevepad_delete 
  :: (Ptr RawTEvePad) -> IO ()

foreign import ccall "HROOT.h TSlider_GetFrame" c_tslider_getframe 
  :: (Ptr RawTSlider) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TSlider_Range" c_tslider_range 
  :: (Ptr RawTSlider) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_GetName" c_tslider_getname 
  :: (Ptr RawTSlider) -> IO CString
foreign import ccall "HROOT.h TSlider_Draw" c_tslider_draw 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_FindObject" c_tslider_findobject 
  :: (Ptr RawTSlider) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSlider_SaveAs" c_tslider_saveas 
  :: (Ptr RawTSlider) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_Write" c_tslider_write 
  :: (Ptr RawTSlider) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSlider_SetLineColor" c_tslider_setlinecolor 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetFillColor" c_tslider_setfillcolor 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetFillStyle" c_tslider_setfillstyle 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_delete" c_tslider_delete 
  :: (Ptr RawTSlider) -> IO ()

foreign import ccall "HROOT.h TApplication_GetName" c_tapplication_getname 
  :: (Ptr RawTApplication) -> IO CString
foreign import ccall "HROOT.h TApplication_Draw" c_tapplication_draw 
  :: (Ptr RawTApplication) -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_FindObject" c_tapplication_findobject 
  :: (Ptr RawTApplication) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TApplication_SaveAs" c_tapplication_saveas 
  :: (Ptr RawTApplication) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_Write" c_tapplication_write 
  :: (Ptr RawTApplication) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TApplication_delete" c_tapplication_delete 
  :: (Ptr RawTApplication) -> IO ()
foreign import ccall "HROOT.h TApplication_newTApplication" c_tapplication_newtapplication 
  :: CString -> (Ptr CInt) -> (Ptr (CString)) -> IO (Ptr RawTApplication)
foreign import ccall "HROOT.h TApplication_Run" c_tapplication_run 
  :: (Ptr RawTApplication) -> CInt -> IO ()

foreign import ccall "HROOT.h TRint_Run" c_trint_run 
  :: (Ptr RawTRint) -> CInt -> IO ()
foreign import ccall "HROOT.h TRint_GetName" c_trint_getname 
  :: (Ptr RawTRint) -> IO CString
foreign import ccall "HROOT.h TRint_Draw" c_trint_draw 
  :: (Ptr RawTRint) -> CString -> IO ()
foreign import ccall "HROOT.h TRint_FindObject" c_trint_findobject 
  :: (Ptr RawTRint) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TRint_SaveAs" c_trint_saveas 
  :: (Ptr RawTRint) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TRint_Write" c_trint_write 
  :: (Ptr RawTRint) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TRint_delete" c_trint_delete 
  :: (Ptr RawTRint) -> IO ()
foreign import ccall "HROOT.h TRint_newTRint" c_trint_newtrint 
  :: CString -> (Ptr CInt) -> (Ptr (CString)) -> IO (Ptr RawTRint)