{-# 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_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_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_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_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_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 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 TAttCanvas_newTAttCanvas" c_tattcanvas_newtattcanvas 
  :: IO (Ptr RawTAttCanvas)


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 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_newTAttMarker" c_tattmarker_newtattmarker 
  :: CInt -> CInt -> CInt -> IO (Ptr RawTAttMarker)


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_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 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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_newTPCON" c_tpcon_newtpcon 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CInt -> IO (Ptr RawTPCON)


foreign import ccall "HROOT.h TPolyLineShape_SetTitle" c_tpolylineshape_settitle 
  :: (Ptr RawTPolyLineShape) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_SetLineColor" c_tpolylineshape_setlinecolor 
  :: (Ptr RawTPolyLineShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_SetFillColor" c_tpolylineshape_setfillcolor 
  :: (Ptr RawTPolyLineShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_SetFillStyle" c_tpolylineshape_setfillstyle 
  :: (Ptr RawTPolyLineShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_GetName" c_tpolylineshape_getname 
  :: (Ptr RawTPolyLineShape) -> IO CString
foreign import ccall "HROOT.h TPolyLineShape_Draw" c_tpolylineshape_draw 
  :: (Ptr RawTPolyLineShape) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_SaveAs" c_tpolylineshape_saveas 
  :: (Ptr RawTPolyLineShape) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLineShape_Write" c_tpolylineshape_write 
  :: (Ptr RawTPolyLineShape) -> CString -> CInt -> CInt -> IO CInt

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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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 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_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_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_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_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_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_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_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_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_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_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_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_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_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_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_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 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_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_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_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_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_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_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_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 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_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 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_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_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_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 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_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_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_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 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_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_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_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 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_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 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_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 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_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_GetXaxis" c_th1_getxaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_GetYaxis" c_th1_getyaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_GetZaxis" c_th1_getzaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_Add" c_th1_add 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_fill1" c_th1_fill1 
  :: (Ptr RawTH1) -> CDouble -> IO CInt


foreign import ccall "HROOT.h TH2_GetXaxis" c_th2_getxaxis 
  :: (Ptr RawTH2) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2_GetYaxis" c_th2_getyaxis 
  :: (Ptr RawTH2) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2_GetZaxis" c_th2_getzaxis 
  :: (Ptr RawTH2) -> 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_fill1" c_th2_fill1 
  :: (Ptr RawTH2) -> CDouble -> IO CInt
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_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_fill2" c_th2_fill2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt


foreign import ccall "HROOT.h TH3_GetXaxis" c_th3_getxaxis 
  :: (Ptr RawTH3) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3_GetYaxis" c_th3_getyaxis 
  :: (Ptr RawTH3) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3_GetZaxis" c_th3_getzaxis 
  :: (Ptr RawTH3) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3_Add" c_th3_add 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_fill1" c_th3_fill1 
  :: (Ptr RawTH3) -> CDouble -> IO CInt
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_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 TH1C_GetXaxis" c_th1c_getxaxis 
  :: (Ptr RawTH1C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1C_GetYaxis" c_th1c_getyaxis 
  :: (Ptr RawTH1C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1C_GetZaxis" c_th1c_getzaxis 
  :: (Ptr RawTH1C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1C_Add" c_th1c_add 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_fill1" c_th1c_fill1 
  :: (Ptr RawTH1C) -> CDouble -> IO CInt
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_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 TH1D_GetXaxis" c_th1d_getxaxis 
  :: (Ptr RawTH1D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1D_GetYaxis" c_th1d_getyaxis 
  :: (Ptr RawTH1D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1D_GetZaxis" c_th1d_getzaxis 
  :: (Ptr RawTH1D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1D_Add" c_th1d_add 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_fill1" c_th1d_fill1 
  :: (Ptr RawTH1D) -> CDouble -> IO CInt
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_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 TH1F_GetXaxis" c_th1f_getxaxis 
  :: (Ptr RawTH1F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1F_GetYaxis" c_th1f_getyaxis 
  :: (Ptr RawTH1F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1F_GetZaxis" c_th1f_getzaxis 
  :: (Ptr RawTH1F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1F_Add" c_th1f_add 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_fill1" c_th1f_fill1 
  :: (Ptr RawTH1F) -> CDouble -> IO CInt
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_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_newTH1F" c_th1f_newth1f 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1F)


foreign import ccall "HROOT.h TH1I_GetXaxis" c_th1i_getxaxis 
  :: (Ptr RawTH1I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1I_GetYaxis" c_th1i_getyaxis 
  :: (Ptr RawTH1I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1I_GetZaxis" c_th1i_getzaxis 
  :: (Ptr RawTH1I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1I_Add" c_th1i_add 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_fill1" c_th1i_fill1 
  :: (Ptr RawTH1I) -> CDouble -> IO CInt
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_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 TH1S_GetXaxis" c_th1s_getxaxis 
  :: (Ptr RawTH1S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1S_GetYaxis" c_th1s_getyaxis 
  :: (Ptr RawTH1S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1S_GetZaxis" c_th1s_getzaxis 
  :: (Ptr RawTH1S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1S_Add" c_th1s_add 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_fill1" c_th1s_fill1 
  :: (Ptr RawTH1S) -> CDouble -> IO CInt
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_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 TH2C_fill2" c_th2c_fill2 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_GetXaxis" c_th2c_getxaxis 
  :: (Ptr RawTH2C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2C_GetYaxis" c_th2c_getyaxis 
  :: (Ptr RawTH2C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2C_GetZaxis" c_th2c_getzaxis 
  :: (Ptr RawTH2C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2C_Add" c_th2c_add 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_fill1" c_th2c_fill1 
  :: (Ptr RawTH2C) -> CDouble -> IO CInt
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_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 TH2D_fill2" c_th2d_fill2 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_GetXaxis" c_th2d_getxaxis 
  :: (Ptr RawTH2D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2D_GetYaxis" c_th2d_getyaxis 
  :: (Ptr RawTH2D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2D_GetZaxis" c_th2d_getzaxis 
  :: (Ptr RawTH2D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2D_Add" c_th2d_add 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_fill1" c_th2d_fill1 
  :: (Ptr RawTH2D) -> CDouble -> IO CInt
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_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 TH2F_fill2" c_th2f_fill2 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_GetXaxis" c_th2f_getxaxis 
  :: (Ptr RawTH2F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2F_GetYaxis" c_th2f_getyaxis 
  :: (Ptr RawTH2F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2F_GetZaxis" c_th2f_getzaxis 
  :: (Ptr RawTH2F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2F_Add" c_th2f_add 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_fill1" c_th2f_fill1 
  :: (Ptr RawTH2F) -> CDouble -> IO CInt
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_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_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_GetXaxis" c_th2i_getxaxis 
  :: (Ptr RawTH2I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2I_GetYaxis" c_th2i_getyaxis 
  :: (Ptr RawTH2I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2I_GetZaxis" c_th2i_getzaxis 
  :: (Ptr RawTH2I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2I_Add" c_th2i_add 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_fill1" c_th2i_fill1 
  :: (Ptr RawTH2I) -> CDouble -> IO CInt
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_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 TH2Poly_fill2" c_th2poly_fill2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetXaxis" c_th2poly_getxaxis 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2Poly_GetYaxis" c_th2poly_getyaxis 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2Poly_GetZaxis" c_th2poly_getzaxis 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2Poly_Add" c_th2poly_add 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_fill1" c_th2poly_fill1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CInt
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_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 TH2S_fill2" c_th2s_fill2 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_GetXaxis" c_th2s_getxaxis 
  :: (Ptr RawTH2S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2S_GetYaxis" c_th2s_getyaxis 
  :: (Ptr RawTH2S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2S_GetZaxis" c_th2s_getzaxis 
  :: (Ptr RawTH2S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH2S_Add" c_th2s_add 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_fill1" c_th2s_fill1 
  :: (Ptr RawTH2S) -> CDouble -> IO CInt
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_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 TH3C_GetXaxis" c_th3c_getxaxis 
  :: (Ptr RawTH3C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3C_GetYaxis" c_th3c_getyaxis 
  :: (Ptr RawTH3C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3C_GetZaxis" c_th3c_getzaxis 
  :: (Ptr RawTH3C) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3C_Add" c_th3c_add 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_fill1" c_th3c_fill1 
  :: (Ptr RawTH3C) -> CDouble -> IO CInt
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_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 TH3D_GetXaxis" c_th3d_getxaxis 
  :: (Ptr RawTH3D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3D_GetYaxis" c_th3d_getyaxis 
  :: (Ptr RawTH3D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3D_GetZaxis" c_th3d_getzaxis 
  :: (Ptr RawTH3D) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3D_Add" c_th3d_add 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_fill1" c_th3d_fill1 
  :: (Ptr RawTH3D) -> CDouble -> IO CInt
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_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 TH3F_GetXaxis" c_th3f_getxaxis 
  :: (Ptr RawTH3F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3F_GetYaxis" c_th3f_getyaxis 
  :: (Ptr RawTH3F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3F_GetZaxis" c_th3f_getzaxis 
  :: (Ptr RawTH3F) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3F_Add" c_th3f_add 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_fill1" c_th3f_fill1 
  :: (Ptr RawTH3F) -> CDouble -> IO CInt
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_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 TH3I_GetXaxis" c_th3i_getxaxis 
  :: (Ptr RawTH3I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3I_GetYaxis" c_th3i_getyaxis 
  :: (Ptr RawTH3I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3I_GetZaxis" c_th3i_getzaxis 
  :: (Ptr RawTH3I) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3I_Add" c_th3i_add 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_fill1" c_th3i_fill1 
  :: (Ptr RawTH3I) -> CDouble -> IO CInt
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_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 TH3S_GetXaxis" c_th3s_getxaxis 
  :: (Ptr RawTH3S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3S_GetYaxis" c_th3s_getyaxis 
  :: (Ptr RawTH3S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3S_GetZaxis" c_th3s_getzaxis 
  :: (Ptr RawTH3S) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH3S_Add" c_th3s_add 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_fill1" c_th3s_fill1 
  :: (Ptr RawTH3S) -> CDouble -> IO CInt
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_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 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_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_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_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 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_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 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_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 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_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_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_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 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_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 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_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 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_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 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_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_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_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_newTRint" c_trint_newtrint 
  :: CString -> (Ptr CInt) -> (Ptr (CString)) -> IO (Ptr RawTRint)