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

module HROOT.Class.FFI where

import Foreign.C            
import Foreign.Ptr

import HROOT.Class.Interface


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



foreign import ccall "HROOT.h TObject_delete" c_tobject_delete 
  :: (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TObject_newTObject" c_tobject_newtobject 
  :: IO (Ptr RawTObject)
foreign import ccall "HROOT.h TObject_Draw" c_tobject_draw 
  :: (Ptr RawTObject) -> CString -> IO ()
foreign import ccall "HROOT.h TObject_FindObject" c_tobject_findobject 
  :: (Ptr RawTObject) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TObject_GetName" c_tobject_getname 
  :: (Ptr RawTObject) -> IO CString
foreign import ccall "HROOT.h TObject_IsA" c_tobject_isa 
  :: (Ptr RawTObject) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TObject_IsFolder" c_tobject_isfolder 
  :: (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObject_IsEqual" c_tobject_isequal 
  :: (Ptr RawTObject) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObject_IsSortable" c_tobject_issortable 
  :: (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObject_tObjectIsOnHeap" c_tobject_tobjectisonheap 
  :: (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObject_tObjectIsZombie" c_tobject_tobjectiszombie 
  :: (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObject_Paint" c_tobject_paint 
  :: (Ptr RawTObject) -> CString -> IO ()
foreign import ccall "HROOT.h TObject_printObj" c_tobject_printobj 
  :: (Ptr RawTObject) -> CString -> IO ()
foreign import ccall "HROOT.h TObject_RecursiveRemove" c_tobject_recursiveremove 
  :: (Ptr RawTObject) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TObject_SaveAs" c_tobject_saveas 
  :: (Ptr RawTObject) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TObject_UseCurrentStyle" c_tobject_usecurrentstyle 
  :: (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TObject_Write" c_tobject_write 
  :: (Ptr RawTObject) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOT.h TNamed_Draw" c_tnamed_draw 
  :: (Ptr RawTNamed) -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_FindObject" c_tnamed_findobject 
  :: (Ptr RawTNamed) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNamed_GetName" c_tnamed_getname 
  :: (Ptr RawTNamed) -> IO CString
foreign import ccall "HROOT.h TNamed_IsA" c_tnamed_isa 
  :: (Ptr RawTNamed) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TNamed_IsFolder" c_tnamed_isfolder 
  :: (Ptr RawTNamed) -> IO CInt
foreign import ccall "HROOT.h TNamed_IsEqual" c_tnamed_isequal 
  :: (Ptr RawTNamed) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TNamed_IsSortable" c_tnamed_issortable 
  :: (Ptr RawTNamed) -> IO CInt
foreign import ccall "HROOT.h TNamed_Paint" c_tnamed_paint 
  :: (Ptr RawTNamed) -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_printObj" c_tnamed_printobj 
  :: (Ptr RawTNamed) -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_RecursiveRemove" c_tnamed_recursiveremove 
  :: (Ptr RawTNamed) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TNamed_SaveAs" c_tnamed_saveas 
  :: (Ptr RawTNamed) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_UseCurrentStyle" c_tnamed_usecurrentstyle 
  :: (Ptr RawTNamed) -> IO ()
foreign import ccall "HROOT.h TNamed_Write" c_tnamed_write 
  :: (Ptr RawTNamed) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNamed_delete" c_tnamed_delete 
  :: (Ptr RawTNamed) -> IO ()
foreign import ccall "HROOT.h TNamed_newTNamed" c_tnamed_newtnamed 
  :: CString -> CString -> IO (Ptr RawTNamed)
foreign import ccall "HROOT.h TNamed_SetName" c_tnamed_setname 
  :: (Ptr RawTNamed) -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_SetNameTitle" c_tnamed_setnametitle 
  :: (Ptr RawTNamed) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNamed_SetTitle" c_tnamed_settitle 
  :: (Ptr RawTNamed) -> CString -> IO ()



















foreign import ccall "HROOT.h TClass_SetName" c_tclass_setname 
  :: (Ptr RawTClass) -> CString -> IO ()
foreign import ccall "HROOT.h TClass_SetNameTitle" c_tclass_setnametitle 
  :: (Ptr RawTClass) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TClass_SetTitle" c_tclass_settitle 
  :: (Ptr RawTClass) -> CString -> IO ()
foreign import ccall "HROOT.h TClass_Draw" c_tclass_draw 
  :: (Ptr RawTClass) -> CString -> IO ()
foreign import ccall "HROOT.h TClass_FindObject" c_tclass_findobject 
  :: (Ptr RawTClass) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TClass_GetName" c_tclass_getname 
  :: (Ptr RawTClass) -> IO CString
foreign import ccall "HROOT.h TClass_IsA" c_tclass_isa 
  :: (Ptr RawTClass) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TClass_IsFolder" c_tclass_isfolder 
  :: (Ptr RawTClass) -> IO CInt
foreign import ccall "HROOT.h TClass_IsEqual" c_tclass_isequal 
  :: (Ptr RawTClass) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TClass_IsSortable" c_tclass_issortable 
  :: (Ptr RawTClass) -> IO CInt
foreign import ccall "HROOT.h TClass_Paint" c_tclass_paint 
  :: (Ptr RawTClass) -> CString -> IO ()
foreign import ccall "HROOT.h TClass_printObj" c_tclass_printobj 
  :: (Ptr RawTClass) -> CString -> IO ()
foreign import ccall "HROOT.h TClass_RecursiveRemove" c_tclass_recursiveremove 
  :: (Ptr RawTClass) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TClass_SaveAs" c_tclass_saveas 
  :: (Ptr RawTClass) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TClass_UseCurrentStyle" c_tclass_usecurrentstyle 
  :: (Ptr RawTClass) -> IO ()
foreign import ccall "HROOT.h TClass_Write" c_tclass_write 
  :: (Ptr RawTClass) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TClass_delete" c_tclass_delete 
  :: (Ptr RawTClass) -> IO ()

foreign import ccall "HROOT.h TFormula_SetName" c_tformula_setname 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_SetNameTitle" c_tformula_setnametitle 
  :: (Ptr RawTFormula) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_SetTitle" c_tformula_settitle 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_Draw" c_tformula_draw 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_FindObject" c_tformula_findobject 
  :: (Ptr RawTFormula) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFormula_GetName" c_tformula_getname 
  :: (Ptr RawTFormula) -> IO CString
foreign import ccall "HROOT.h TFormula_IsA" c_tformula_isa 
  :: (Ptr RawTFormula) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TFormula_IsFolder" c_tformula_isfolder 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_IsEqual" c_tformula_isequal 
  :: (Ptr RawTFormula) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TFormula_IsSortable" c_tformula_issortable 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_Paint" c_tformula_paint 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_printObj" c_tformula_printobj 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_RecursiveRemove" c_tformula_recursiveremove 
  :: (Ptr RawTFormula) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TFormula_SaveAs" c_tformula_saveas 
  :: (Ptr RawTFormula) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_UseCurrentStyle" c_tformula_usecurrentstyle 
  :: (Ptr RawTFormula) -> IO ()
foreign import ccall "HROOT.h TFormula_Write" c_tformula_write 
  :: (Ptr RawTFormula) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFormula_delete" c_tformula_delete 
  :: (Ptr RawTFormula) -> IO ()
foreign import ccall "HROOT.h TFormula_newTFormula" c_tformula_newtformula 
  :: CString -> CString -> IO (Ptr RawTFormula)
foreign import ccall "HROOT.h TFormula_tFormulaOptimize" c_tformula_tformulaoptimize 
  :: (Ptr RawTFormula) -> IO ()
foreign import ccall "HROOT.h TFormula_Compile" c_tformula_compile 
  :: (Ptr RawTFormula) -> CString -> IO CInt
foreign import ccall "HROOT.h TFormula_Clear" c_tformula_clear 
  :: (Ptr RawTFormula) -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_DefinedValue" c_tformula_definedvalue 
  :: (Ptr RawTFormula) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TFormula_Eval" c_tformula_eval 
  :: (Ptr RawTFormula) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TFormula_EvalParOld" c_tformula_evalparold 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TFormula_EvalPar" c_tformula_evalpar 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TFormula_GetNdim" c_tformula_getndim 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_GetNpar" c_tformula_getnpar 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_GetNumber" c_tformula_getnumber 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_tFormulaGetParameter" c_tformula_tformulagetparameter 
  :: (Ptr RawTFormula) -> CString -> IO CDouble
foreign import ccall "HROOT.h TFormula_GetParNumber" c_tformula_getparnumber 
  :: (Ptr RawTFormula) -> CString -> IO CInt
foreign import ccall "HROOT.h TFormula_IsLinear" c_tformula_islinear 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_IsNormalized" c_tformula_isnormalized 
  :: (Ptr RawTFormula) -> IO CInt
foreign import ccall "HROOT.h TFormula_SetNumber" c_tformula_setnumber 
  :: (Ptr RawTFormula) -> CInt -> IO ()
foreign import ccall "HROOT.h TFormula_SetParameter" c_tformula_setparameter 
  :: (Ptr RawTFormula) -> CString -> CDouble -> IO ()
foreign import ccall "HROOT.h TFormula_SetParameters" c_tformula_setparameters 
  :: (Ptr RawTFormula) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TFormula_SetParName" c_tformula_setparname 
  :: (Ptr RawTFormula) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_SetParNames" c_tformula_setparnames 
  :: (Ptr RawTFormula) -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFormula_Update" c_tformula_update 
  :: (Ptr RawTFormula) -> IO ()

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

foreign import ccall "HROOT.h TAttAxis_delete" c_tattaxis_delete 
  :: (Ptr RawTAttAxis) -> IO ()
foreign import ccall "HROOT.h TAttAxis_newTAttAxis" c_tattaxis_newtattaxis 
  :: IO (Ptr RawTAttAxis)
foreign import ccall "HROOT.h TAttAxis_GetNdivisions" c_tattaxis_getndivisions 
  :: (Ptr RawTAttAxis) -> IO CInt
foreign import ccall "HROOT.h TAttAxis_GetAxisColor" c_tattaxis_getaxiscolor 
  :: (Ptr RawTAttAxis) -> IO CInt
foreign import ccall "HROOT.h TAttAxis_GetLabelColor" c_tattaxis_getlabelcolor 
  :: (Ptr RawTAttAxis) -> IO CInt
foreign import ccall "HROOT.h TAttAxis_GetLabelFont" c_tattaxis_getlabelfont 
  :: (Ptr RawTAttAxis) -> IO CInt
foreign import ccall "HROOT.h TAttAxis_GetLabelOffset" c_tattaxis_getlabeloffset 
  :: (Ptr RawTAttAxis) -> IO CDouble
foreign import ccall "HROOT.h TAttAxis_GetLabelSize" c_tattaxis_getlabelsize 
  :: (Ptr RawTAttAxis) -> IO CDouble
foreign import ccall "HROOT.h TAttAxis_GetTitleOffset" c_tattaxis_gettitleoffset 
  :: (Ptr RawTAttAxis) -> IO CDouble
foreign import ccall "HROOT.h TAttAxis_GetTitleSize" c_tattaxis_gettitlesize 
  :: (Ptr RawTAttAxis) -> IO CDouble
foreign import ccall "HROOT.h TAttAxis_GetTickLength" c_tattaxis_getticklength 
  :: (Ptr RawTAttAxis) -> IO CDouble
foreign import ccall "HROOT.h TAttAxis_GetTitleFont" c_tattaxis_gettitlefont 
  :: (Ptr RawTAttAxis) -> IO CInt
foreign import ccall "HROOT.h TAttAxis_SetNdivisions" c_tattaxis_setndivisions 
  :: (Ptr RawTAttAxis) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetAxisColor" c_tattaxis_setaxiscolor 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetLabelColor" c_tattaxis_setlabelcolor 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetLabelFont" c_tattaxis_setlabelfont 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetLabelOffset" c_tattaxis_setlabeloffset 
  :: (Ptr RawTAttAxis) -> CDouble -> 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_SetTitleSize" c_tattaxis_settitlesize 
  :: (Ptr RawTAttAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetTitleColor" c_tattaxis_settitlecolor 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttAxis_SetTitleFont" c_tattaxis_settitlefont 
  :: (Ptr RawTAttAxis) -> CInt -> IO ()

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

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

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

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

foreign import ccall "HROOT.h TAttLine_delete" c_tattline_delete 
  :: (Ptr RawTAttLine) -> IO ()
foreign import ccall "HROOT.h TAttLine_newTAttLine" c_tattline_newtattline 
  :: CInt -> CInt -> CInt -> IO (Ptr RawTAttLine)
foreign import ccall "HROOT.h TAttLine_tAttLineDistancetoLine" c_tattline_tattlinedistancetoline 
  :: (Ptr RawTAttLine) -> CInt -> CInt -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TAttLine_GetLineColor" c_tattline_getlinecolor 
  :: (Ptr RawTAttLine) -> IO CInt
foreign import ccall "HROOT.h TAttLine_GetLineStyle" c_tattline_getlinestyle 
  :: (Ptr RawTAttLine) -> IO CInt
foreign import ccall "HROOT.h TAttLine_GetLineWidth" c_tattline_getlinewidth 
  :: (Ptr RawTAttLine) -> IO CInt
foreign import ccall "HROOT.h TAttLine_ResetAttLine" c_tattline_resetattline 
  :: (Ptr RawTAttLine) -> CString -> IO ()
foreign import ccall "HROOT.h TAttLine_SetLineAttributes" c_tattline_setlineattributes 
  :: (Ptr RawTAttLine) -> IO ()
foreign import ccall "HROOT.h TAttLine_SetLineColor" c_tattline_setlinecolor 
  :: (Ptr RawTAttLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttLine_SetLineStyle" c_tattline_setlinestyle 
  :: (Ptr RawTAttLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttLine_SetLineWidth" c_tattline_setlinewidth 
  :: (Ptr RawTAttLine) -> CInt -> IO ()

foreign import ccall "HROOT.h TAttMarker_delete" c_tattmarker_delete 
  :: (Ptr RawTAttMarker) -> IO ()
foreign import ccall "HROOT.h TAttMarker_newTAttMarker" c_tattmarker_newtattmarker 
  :: CInt -> CInt -> CInt -> IO (Ptr RawTAttMarker)
foreign import ccall "HROOT.h TAttMarker_GetMarkerColor" c_tattmarker_getmarkercolor 
  :: (Ptr RawTAttMarker) -> IO CInt
foreign import ccall "HROOT.h TAttMarker_GetMarkerStyle" c_tattmarker_getmarkerstyle 
  :: (Ptr RawTAttMarker) -> IO CInt
foreign import ccall "HROOT.h TAttMarker_GetMarkerSize" c_tattmarker_getmarkersize 
  :: (Ptr RawTAttMarker) -> IO CDouble
foreign import ccall "HROOT.h TAttMarker_ResetAttMarker" c_tattmarker_resetattmarker 
  :: (Ptr RawTAttMarker) -> CString -> IO ()
foreign import ccall "HROOT.h TAttMarker_SetMarkerAttributes" c_tattmarker_setmarkerattributes 
  :: (Ptr RawTAttMarker) -> IO ()
foreign import ccall "HROOT.h TAttMarker_SetMarkerColor" c_tattmarker_setmarkercolor 
  :: (Ptr RawTAttMarker) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttMarker_SetMarkerStyle" c_tattmarker_setmarkerstyle 
  :: (Ptr RawTAttMarker) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttMarker_SetMarkerSize" c_tattmarker_setmarkersize 
  :: (Ptr RawTAttMarker) -> CInt -> IO ()

foreign import ccall "HROOT.h TAttPad_delete" c_tattpad_delete 
  :: (Ptr RawTAttPad) -> IO ()
foreign import ccall "HROOT.h TAttPad_newTAttPad" c_tattpad_newtattpad 
  :: IO (Ptr RawTAttPad)
foreign import ccall "HROOT.h TAttPad_tAttPadGetBottomMargin" c_tattpad_tattpadgetbottommargin 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetLeftMargin" c_tattpad_tattpadgetleftmargin 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetRightMargin" c_tattpad_tattpadgetrightmargin 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetTopMargin" c_tattpad_tattpadgettopmargin 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetAfile" c_tattpad_tattpadgetafile 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetXfile" c_tattpad_tattpadgetxfile 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetYfile" c_tattpad_tattpadgetyfile 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetAstat" c_tattpad_tattpadgetastat 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetXstat" c_tattpad_tattpadgetxstat 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetYstat" c_tattpad_tattpadgetystat 
  :: (Ptr RawTAttPad) -> IO CDouble
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameFillColor" c_tattpad_tattpadgetframefillcolor 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameLineColor" c_tattpad_tattpadgetframelinecolor 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameFillStyle" c_tattpad_tattpadgetframefillstyle 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameLineStyle" c_tattpad_tattpadgetframelinestyle 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameLineWidth" c_tattpad_tattpadgetframelinewidth 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameBorderSize" c_tattpad_tattpadgetframebordersize 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_tAttPadGetFrameBorderMode" c_tattpad_tattpadgetframebordermode 
  :: (Ptr RawTAttPad) -> IO CInt
foreign import ccall "HROOT.h TAttPad_ResetAttPad" c_tattpad_resetattpad 
  :: (Ptr RawTAttPad) -> CString -> IO ()
foreign import ccall "HROOT.h TAttPad_SetBottomMargin" c_tattpad_setbottommargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetLeftMargin" c_tattpad_setleftmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetRightMargin" c_tattpad_setrightmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetTopMargin" c_tattpad_settopmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetMargin" c_tattpad_setmargin 
  :: (Ptr RawTAttPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetAfile" c_tattpad_setafile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetXfile" c_tattpad_setxfile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetYfile" c_tattpad_setyfile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetAstat" c_tattpad_setastat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetXstat" c_tattpad_setxstat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_SetYstat" c_tattpad_setystat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameFillColor" c_tattpad_tattpadsetframefillcolor 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameLineColor" c_tattpad_tattpadsetframelinecolor 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameFillStyle" c_tattpad_tattpadsetframefillstyle 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameLineStyle" c_tattpad_tattpadsetframelinestyle 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameLineWidth" c_tattpad_tattpadsetframelinewidth 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameBorderSize" c_tattpad_tattpadsetframebordersize 
  :: (Ptr RawTAttPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttPad_tAttPadSetFrameBorderMode" c_tattpad_tattpadsetframebordermode 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOT.h TAttParticle_SetName" c_tattparticle_setname 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_SetNameTitle" c_tattparticle_setnametitle 
  :: (Ptr RawTAttParticle) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_SetTitle" c_tattparticle_settitle 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_Draw" c_tattparticle_draw 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_FindObject" c_tattparticle_findobject 
  :: (Ptr RawTAttParticle) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TAttParticle_GetName" c_tattparticle_getname 
  :: (Ptr RawTAttParticle) -> IO CString
foreign import ccall "HROOT.h TAttParticle_IsA" c_tattparticle_isa 
  :: (Ptr RawTAttParticle) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TAttParticle_IsFolder" c_tattparticle_isfolder 
  :: (Ptr RawTAttParticle) -> IO CInt
foreign import ccall "HROOT.h TAttParticle_IsEqual" c_tattparticle_isequal 
  :: (Ptr RawTAttParticle) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TAttParticle_IsSortable" c_tattparticle_issortable 
  :: (Ptr RawTAttParticle) -> IO CInt
foreign import ccall "HROOT.h TAttParticle_Paint" c_tattparticle_paint 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_printObj" c_tattparticle_printobj 
  :: (Ptr RawTAttParticle) -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_RecursiveRemove" c_tattparticle_recursiveremove 
  :: (Ptr RawTAttParticle) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TAttParticle_SaveAs" c_tattparticle_saveas 
  :: (Ptr RawTAttParticle) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAttParticle_UseCurrentStyle" c_tattparticle_usecurrentstyle 
  :: (Ptr RawTAttParticle) -> IO ()
foreign import ccall "HROOT.h TAttParticle_Write" c_tattparticle_write 
  :: (Ptr RawTAttParticle) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TAttParticle_delete" c_tattparticle_delete 
  :: (Ptr RawTAttParticle) -> IO ()

foreign import ccall "HROOT.h TAttText_delete" c_tatttext_delete 
  :: (Ptr RawTAttText) -> IO ()
foreign import ccall "HROOT.h TAttText_newTAttText" c_tatttext_newtatttext 
  :: CInt -> CDouble -> CInt -> CInt -> CDouble -> IO (Ptr RawTAttText)
foreign import ccall "HROOT.h TAttText_GetTextAlign" c_tatttext_gettextalign 
  :: (Ptr RawTAttText) -> IO CInt
foreign import ccall "HROOT.h TAttText_GetTextAngle" c_tatttext_gettextangle 
  :: (Ptr RawTAttText) -> IO CDouble
foreign import ccall "HROOT.h TAttText_GetTextColor" c_tatttext_gettextcolor 
  :: (Ptr RawTAttText) -> IO CInt
foreign import ccall "HROOT.h TAttText_GetTextFont" c_tatttext_gettextfont 
  :: (Ptr RawTAttText) -> IO CInt
foreign import ccall "HROOT.h TAttText_GetTextSize" c_tatttext_gettextsize 
  :: (Ptr RawTAttText) -> IO CDouble
foreign import ccall "HROOT.h TAttText_ResetAttText" c_tatttext_resetatttext 
  :: (Ptr RawTAttText) -> CString -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextAttributes" c_tatttext_settextattributes 
  :: (Ptr RawTAttText) -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextAlign" c_tatttext_settextalign 
  :: (Ptr RawTAttText) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextAngle" c_tatttext_settextangle 
  :: (Ptr RawTAttText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextColor" c_tatttext_settextcolor 
  :: (Ptr RawTAttText) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextFont" c_tatttext_settextfont 
  :: (Ptr RawTAttText) -> CInt -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextSize" c_tatttext_settextsize 
  :: (Ptr RawTAttText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAttText_SetTextSizePixels" c_tatttext_settextsizepixels 
  :: (Ptr RawTAttText) -> CInt -> IO ()

foreign import ccall "HROOT.h THStack_SetName" c_thstack_setname 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_SetNameTitle" c_thstack_setnametitle 
  :: (Ptr RawTHStack) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h THStack_SetTitle" c_thstack_settitle 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_Draw" c_thstack_draw 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_FindObject" c_thstack_findobject 
  :: (Ptr RawTHStack) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h THStack_GetName" c_thstack_getname 
  :: (Ptr RawTHStack) -> IO CString
foreign import ccall "HROOT.h THStack_IsA" c_thstack_isa 
  :: (Ptr RawTHStack) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h THStack_IsFolder" c_thstack_isfolder 
  :: (Ptr RawTHStack) -> IO CInt
foreign import ccall "HROOT.h THStack_IsEqual" c_thstack_isequal 
  :: (Ptr RawTHStack) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h THStack_IsSortable" c_thstack_issortable 
  :: (Ptr RawTHStack) -> IO CInt
foreign import ccall "HROOT.h THStack_Paint" c_thstack_paint 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_printObj" c_thstack_printobj 
  :: (Ptr RawTHStack) -> CString -> IO ()
foreign import ccall "HROOT.h THStack_RecursiveRemove" c_thstack_recursiveremove 
  :: (Ptr RawTHStack) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h THStack_SaveAs" c_thstack_saveas 
  :: (Ptr RawTHStack) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h THStack_UseCurrentStyle" c_thstack_usecurrentstyle 
  :: (Ptr RawTHStack) -> IO ()
foreign import ccall "HROOT.h THStack_Write" c_thstack_write 
  :: (Ptr RawTHStack) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h THStack_delete" c_thstack_delete 
  :: (Ptr RawTHStack) -> IO ()
foreign import ccall "HROOT.h THStack_newTHStack" c_thstack_newthstack 
  :: CString -> CString -> IO (Ptr RawTHStack)

foreign import ccall "HROOT.h TF1_Compile" c_tf1_compile 
  :: (Ptr RawTF1) -> CString -> IO CInt
foreign import ccall "HROOT.h TF1_Clear" c_tf1_clear 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_DefinedValue" c_tf1_definedvalue 
  :: (Ptr RawTF1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_Eval" c_tf1_eval 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_EvalParOld" c_tf1_evalparold 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TF1_EvalPar" c_tf1_evalpar 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TF1_GetNdim" c_tf1_getndim 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetNpar" c_tf1_getnpar 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetNumber" c_tf1_getnumber 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetParNumber" c_tf1_getparnumber 
  :: (Ptr RawTF1) -> CString -> IO CInt
foreign import ccall "HROOT.h TF1_IsLinear" c_tf1_islinear 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_IsNormalized" c_tf1_isnormalized 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_SetNumber" c_tf1_setnumber 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetParameter" c_tf1_setparameter 
  :: (Ptr RawTF1) -> CString -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetParameters" c_tf1_setparameters 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TF1_SetParName" c_tf1_setparname 
  :: (Ptr RawTF1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TF1_SetParNames" c_tf1_setparnames 
  :: (Ptr RawTF1) -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TF1_Update" c_tf1_update 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_GetLineColor" c_tf1_getlinecolor 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetLineStyle" c_tf1_getlinestyle 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetLineWidth" c_tf1_getlinewidth 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_ResetAttLine" c_tf1_resetattline 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_SetLineAttributes" c_tf1_setlineattributes 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_SetLineColor" c_tf1_setlinecolor 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetLineStyle" c_tf1_setlinestyle 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetLineWidth" c_tf1_setlinewidth 
  :: (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_GetMarkerColor" c_tf1_getmarkercolor 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetMarkerStyle" c_tf1_getmarkerstyle 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetMarkerSize" c_tf1_getmarkersize 
  :: (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TF1_ResetAttMarker" c_tf1_resetattmarker 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_SetMarkerAttributes" c_tf1_setmarkerattributes 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_SetMarkerColor" c_tf1_setmarkercolor 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetMarkerStyle" c_tf1_setmarkerstyle 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetMarkerSize" c_tf1_setmarkersize 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetName" c_tf1_setname 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_SetNameTitle" c_tf1_setnametitle 
  :: (Ptr RawTF1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TF1_SetTitle" c_tf1_settitle 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_Draw" c_tf1_draw 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_FindObject" c_tf1_findobject 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TF1_GetName" c_tf1_getname 
  :: (Ptr RawTF1) -> IO CString
foreign import ccall "HROOT.h TF1_IsA" c_tf1_isa 
  :: (Ptr RawTF1) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TF1_IsFolder" c_tf1_isfolder 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_IsEqual" c_tf1_isequal 
  :: (Ptr RawTF1) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TF1_IsSortable" c_tf1_issortable 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_Paint" c_tf1_paint 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_printObj" c_tf1_printobj 
  :: (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TF1_RecursiveRemove" c_tf1_recursiveremove 
  :: (Ptr RawTF1) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TF1_SaveAs" c_tf1_saveas 
  :: (Ptr RawTF1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TF1_UseCurrentStyle" c_tf1_usecurrentstyle 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_Write" c_tf1_write 
  :: (Ptr RawTF1) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TF1_delete" c_tf1_delete 
  :: (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TF1_newTF1" c_tf1_newtf1 
  :: CString -> CString -> CDouble -> CDouble -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TF1_Derivative" c_tf1_derivative 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_Derivative2" c_tf1_derivative2 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_Derivative3" c_tf1_derivative3 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_drawCopyTF1" c_tf1_drawcopytf1 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TF1_DrawDerivative" c_tf1_drawderivative 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TF1_DrawIntegral" c_tf1_drawintegral 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TF1_DrawF1" c_tf1_drawf1 
  :: (Ptr RawTF1) -> CString -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TF1_FixParameter" c_tf1_fixparameter 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_tF1GetChisquare" c_tf1_tf1getchisquare 
  :: (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TF1_tF1GetHistogram" c_tf1_tf1gethistogram 
  :: (Ptr RawTF1) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TF1_getMaximumTF1" c_tf1_getmaximumtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_getMinimumTF1" c_tf1_getminimumtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_GetMaximumX" c_tf1_getmaximumx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_GetMinimumX" c_tf1_getminimumx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_GetNDF" c_tf1_getndf 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetNpx" c_tf1_getnpx 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetNumberFreeParameters" c_tf1_getnumberfreeparameters 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_GetNumberFitPoints" c_tf1_getnumberfitpoints 
  :: (Ptr RawTF1) -> IO CInt
foreign import ccall "HROOT.h TF1_tF1GetParent" c_tf1_tf1getparent 
  :: (Ptr RawTF1) -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TF1_GetParError" c_tf1_getparerror 
  :: (Ptr RawTF1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_GetProb" c_tf1_getprob 
  :: (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TF1_getQuantilesTF1" c_tf1_getquantilestf1 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TF1_getRandomTF1" c_tf1_getrandomtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_GetSave" c_tf1_getsave 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TF1_GetX" c_tf1_getx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
foreign import ccall "HROOT.h TF1_GetXmin" c_tf1_getxmin 
  :: (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TF1_GetXmax" c_tf1_getxmax 
  :: (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TF1_tF1GetXaxis" c_tf1_tf1getxaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TF1_tF1GetYaxis" c_tf1_tf1getyaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TF1_tF1GetZaxis" c_tf1_tf1getzaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TF1_GradientPar" c_tf1_gradientpar 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_InitArgs" c_tf1_initargs 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TF1_IntegralTF1" c_tf1_integraltf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_IntegralError" c_tf1_integralerror 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_IntegralFast" c_tf1_integralfast 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_IsInside" c_tf1_isinside 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TF1_ReleaseParameter" c_tf1_releaseparameter 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetChisquare" c_tf1_setchisquare 
  :: (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_setMaximumTF1" c_tf1_setmaximumtf1 
  :: (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_setMinimumTF1" c_tf1_setminimumtf1 
  :: (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetNDF" c_tf1_setndf 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetNumberFitPoints" c_tf1_setnumberfitpoints 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetNpx" c_tf1_setnpx 
  :: (Ptr RawTF1) -> CInt -> IO ()
foreign import ccall "HROOT.h TF1_SetParError" c_tf1_setparerror 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetParErrors" c_tf1_setparerrors 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TF1_SetParLimits" c_tf1_setparlimits 
  :: (Ptr RawTF1) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetParent" c_tf1_setparent 
  :: (Ptr RawTF1) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TF1_setRange1" c_tf1_setrange1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_setRange2" c_tf1_setrange2 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_setRange3" c_tf1_setrange3 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_SetSavedPoint" c_tf1_setsavedpoint 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TF1_Moment" c_tf1_moment 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_CentralMoment" c_tf1_centralmoment 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_Mean" c_tf1_mean 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TF1_Variance" c_tf1_variance 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOT.h TGraph_SetName" c_tgraph_setname 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_SetNameTitle" c_tgraph_setnametitle 
  :: (Ptr RawTGraph) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_SetTitle" c_tgraph_settitle 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_GetLineColor" c_tgraph_getlinecolor 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_GetLineStyle" c_tgraph_getlinestyle 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_GetLineWidth" c_tgraph_getlinewidth 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_ResetAttLine" c_tgraph_resetattline 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_SetLineAttributes" c_tgraph_setlineattributes 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_SetLineColor" c_tgraph_setlinecolor 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetLineStyle" c_tgraph_setlinestyle 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetLineWidth" c_tgraph_setlinewidth 
  :: (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_GetMarkerColor" c_tgraph_getmarkercolor 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_GetMarkerStyle" c_tgraph_getmarkerstyle 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_GetMarkerSize" c_tgraph_getmarkersize 
  :: (Ptr RawTGraph) -> IO CDouble
foreign import ccall "HROOT.h TGraph_ResetAttMarker" c_tgraph_resetattmarker 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_SetMarkerAttributes" c_tgraph_setmarkerattributes 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_SetMarkerColor" c_tgraph_setmarkercolor 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetMarkerStyle" c_tgraph_setmarkerstyle 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetMarkerSize" c_tgraph_setmarkersize 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_Draw" c_tgraph_draw 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_FindObject" c_tgraph_findobject 
  :: (Ptr RawTGraph) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraph_GetName" c_tgraph_getname 
  :: (Ptr RawTGraph) -> IO CString
foreign import ccall "HROOT.h TGraph_IsA" c_tgraph_isa 
  :: (Ptr RawTGraph) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraph_IsFolder" c_tgraph_isfolder 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_IsEqual" c_tgraph_isequal 
  :: (Ptr RawTGraph) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraph_IsSortable" c_tgraph_issortable 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_Paint" c_tgraph_paint 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_printObj" c_tgraph_printobj 
  :: (Ptr RawTGraph) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_RecursiveRemove" c_tgraph_recursiveremove 
  :: (Ptr RawTGraph) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraph_SaveAs" c_tgraph_saveas 
  :: (Ptr RawTGraph) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_UseCurrentStyle" c_tgraph_usecurrentstyle 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_Write" c_tgraph_write 
  :: (Ptr RawTGraph) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraph_delete" c_tgraph_delete 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_newTGraph" c_tgraph_newtgraph 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraph)
foreign import ccall "HROOT.h TGraph_Apply" c_tgraph_apply 
  :: (Ptr RawTGraph) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraph_Chisquare" c_tgraph_chisquare 
  :: (Ptr RawTGraph) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraph_DrawGraph" c_tgraph_drawgraph 
  :: (Ptr RawTGraph) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_drawPanelTGraph" c_tgraph_drawpaneltgraph 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_Expand" c_tgraph_expand 
  :: (Ptr RawTGraph) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_FitPanelTGraph" c_tgraph_fitpaneltgraph 
  :: (Ptr RawTGraph) -> IO ()
foreign import ccall "HROOT.h TGraph_tGraphGetEditable" c_tgraph_tgraphgeteditable 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_tGraphGetFunction" c_tgraph_tgraphgetfunction 
  :: (Ptr RawTGraph) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TGraph_tGraphGetHistogram" c_tgraph_tgraphgethistogram 
  :: (Ptr RawTGraph) -> IO (Ptr RawTH1F)
foreign import ccall "HROOT.h TGraph_tGraphGetListOfFunctions" c_tgraph_tgraphgetlistoffunctions 
  :: (Ptr RawTGraph) -> IO (Ptr RawTList)
foreign import ccall "HROOT.h TGraph_getCorrelationFactorTGraph" c_tgraph_getcorrelationfactortgraph 
  :: (Ptr RawTGraph) -> IO CDouble
foreign import ccall "HROOT.h TGraph_getCovarianceTGraph" c_tgraph_getcovariancetgraph 
  :: (Ptr RawTGraph) -> IO CDouble
foreign import ccall "HROOT.h TGraph_getMeanTGraph" c_tgraph_getmeantgraph 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_getRMSTGraph" c_tgraph_getrmstgraph 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_tGraphGetMaxSize" c_tgraph_tgraphgetmaxsize 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_tGraphGetN" c_tgraph_tgraphgetn 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_GetErrorX" c_tgraph_geterrorx 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_GetErrorY" c_tgraph_geterrory 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_GetErrorXhigh" c_tgraph_geterrorxhigh 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_GetErrorXlow" c_tgraph_geterrorxlow 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_GetErrorYhigh" c_tgraph_geterroryhigh 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_GetErrorYlow" c_tgraph_geterrorylow 
  :: (Ptr RawTGraph) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_tGraphGetMaximum" c_tgraph_tgraphgetmaximum 
  :: (Ptr RawTGraph) -> IO CDouble
foreign import ccall "HROOT.h TGraph_tGraphGetMinimum" c_tgraph_tgraphgetminimum 
  :: (Ptr RawTGraph) -> IO CDouble
foreign import ccall "HROOT.h TGraph_tGraphGetXaxis" c_tgraph_tgraphgetxaxis 
  :: (Ptr RawTGraph) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TGraph_tGraphGetYaxis" c_tgraph_tgraphgetyaxis 
  :: (Ptr RawTGraph) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TGraph_InitExpo" c_tgraph_initexpo 
  :: (Ptr RawTGraph) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_InitGaus" c_tgraph_initgaus 
  :: (Ptr RawTGraph) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_InitPolynom" c_tgraph_initpolynom 
  :: (Ptr RawTGraph) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_InsertPoint" c_tgraph_insertpoint 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_integralTGraph" c_tgraph_integraltgraph 
  :: (Ptr RawTGraph) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraph_IsEditable" c_tgraph_iseditable 
  :: (Ptr RawTGraph) -> IO CInt
foreign import ccall "HROOT.h TGraph_isInsideTGraph" c_tgraph_isinsidetgraph 
  :: (Ptr RawTGraph) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraph_LeastSquareFit" c_tgraph_leastsquarefit 
  :: (Ptr RawTGraph) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_tGraphPaintGraph" c_tgraph_tgraphpaintgraph 
  :: (Ptr RawTGraph) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_tGraphPaintGrapHist" c_tgraph_tgraphpaintgraphist 
  :: (Ptr RawTGraph) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraph_PaintStats" c_tgraph_paintstats 
  :: (Ptr RawTGraph) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraph_RemovePoint" c_tgraph_removepoint 
  :: (Ptr RawTGraph) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraph_SetEditable" c_tgraph_seteditable 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetHistogram" c_tgraph_sethistogram 
  :: (Ptr RawTGraph) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraph_setMaximumTGraph" c_tgraph_setmaximumtgraph 
  :: (Ptr RawTGraph) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_setMinimumTGraph" c_tgraph_setminimumtgraph 
  :: (Ptr RawTGraph) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraph_Set" c_tgraph_set 
  :: (Ptr RawTGraph) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraph_SetPoint" c_tgraph_setpoint 
  :: (Ptr RawTGraph) -> CInt -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOT.h TGraphAsymmErrors_Apply" c_tgraphasymmerrors_apply 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Chisquare" c_tgraphasymmerrors_chisquare 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_DrawGraph" c_tgraphasymmerrors_drawgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_drawPanelTGraph" c_tgraphasymmerrors_drawpaneltgraph 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Expand" c_tgraphasymmerrors_expand 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_FitPanelTGraph" c_tgraphasymmerrors_fitpaneltgraph 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_getCorrelationFactorTGraph" c_tgraphasymmerrors_getcorrelationfactortgraph 
  :: (Ptr RawTGraphAsymmErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_getCovarianceTGraph" c_tgraphasymmerrors_getcovariancetgraph 
  :: (Ptr RawTGraphAsymmErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_getMeanTGraph" c_tgraphasymmerrors_getmeantgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_getRMSTGraph" c_tgraphasymmerrors_getrmstgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorX" c_tgraphasymmerrors_geterrorx 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorY" c_tgraphasymmerrors_geterrory 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorXhigh" c_tgraphasymmerrors_geterrorxhigh 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorXlow" c_tgraphasymmerrors_geterrorxlow 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorYhigh" c_tgraphasymmerrors_geterroryhigh 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_GetErrorYlow" c_tgraphasymmerrors_geterrorylow 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_InitExpo" c_tgraphasymmerrors_initexpo 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_InitGaus" c_tgraphasymmerrors_initgaus 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_InitPolynom" c_tgraphasymmerrors_initpolynom 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_InsertPoint" c_tgraphasymmerrors_insertpoint 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_integralTGraph" c_tgraphasymmerrors_integraltgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_IsEditable" c_tgraphasymmerrors_iseditable 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_isInsideTGraph" c_tgraphasymmerrors_isinsidetgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_LeastSquareFit" c_tgraphasymmerrors_leastsquarefit 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_PaintStats" c_tgraphasymmerrors_paintstats 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_RemovePoint" c_tgraphasymmerrors_removepoint 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_SetEditable" c_tgraphasymmerrors_seteditable 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetHistogram" c_tgraphasymmerrors_sethistogram 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_setMaximumTGraph" c_tgraphasymmerrors_setmaximumtgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_setMinimumTGraph" c_tgraphasymmerrors_setminimumtgraph 
  :: (Ptr RawTGraphAsymmErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Set" c_tgraphasymmerrors_set 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetPoint" c_tgraphasymmerrors_setpoint 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetName" c_tgraphasymmerrors_setname 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetNameTitle" c_tgraphasymmerrors_setnametitle 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetTitle" c_tgraphasymmerrors_settitle 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_GetLineColor" c_tgraphasymmerrors_getlinecolor 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_GetLineStyle" c_tgraphasymmerrors_getlinestyle 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_GetLineWidth" c_tgraphasymmerrors_getlinewidth 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_ResetAttLine" c_tgraphasymmerrors_resetattline 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetLineAttributes" c_tgraphasymmerrors_setlineattributes 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetLineColor" c_tgraphasymmerrors_setlinecolor 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetLineStyle" c_tgraphasymmerrors_setlinestyle 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetLineWidth" c_tgraphasymmerrors_setlinewidth 
  :: (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_GetMarkerColor" c_tgraphasymmerrors_getmarkercolor 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_GetMarkerStyle" c_tgraphasymmerrors_getmarkerstyle 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_GetMarkerSize" c_tgraphasymmerrors_getmarkersize 
  :: (Ptr RawTGraphAsymmErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphAsymmErrors_ResetAttMarker" c_tgraphasymmerrors_resetattmarker 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetMarkerAttributes" c_tgraphasymmerrors_setmarkerattributes 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetMarkerColor" c_tgraphasymmerrors_setmarkercolor 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetMarkerStyle" c_tgraphasymmerrors_setmarkerstyle 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SetMarkerSize" c_tgraphasymmerrors_setmarkersize 
  :: (Ptr RawTGraphAsymmErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Draw" c_tgraphasymmerrors_draw 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_FindObject" c_tgraphasymmerrors_findobject 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphAsymmErrors_GetName" c_tgraphasymmerrors_getname 
  :: (Ptr RawTGraphAsymmErrors) -> IO CString
foreign import ccall "HROOT.h TGraphAsymmErrors_IsA" c_tgraphasymmerrors_isa 
  :: (Ptr RawTGraphAsymmErrors) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraphAsymmErrors_IsFolder" c_tgraphasymmerrors_isfolder 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_IsEqual" c_tgraphasymmerrors_isequal 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_IsSortable" c_tgraphasymmerrors_issortable 
  :: (Ptr RawTGraphAsymmErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_Paint" c_tgraphasymmerrors_paint 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_printObj" c_tgraphasymmerrors_printobj 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_RecursiveRemove" c_tgraphasymmerrors_recursiveremove 
  :: (Ptr RawTGraphAsymmErrors) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_SaveAs" c_tgraphasymmerrors_saveas 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_UseCurrentStyle" c_tgraphasymmerrors_usecurrentstyle 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_Write" c_tgraphasymmerrors_write 
  :: (Ptr RawTGraphAsymmErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphAsymmErrors_delete" c_tgraphasymmerrors_delete 
  :: (Ptr RawTGraphAsymmErrors) -> IO ()
foreign import ccall "HROOT.h TGraphAsymmErrors_newTGraphAsymmErrors" c_tgraphasymmerrors_newtgraphasymmerrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphAsymmErrors)

foreign import ccall "HROOT.h TCutG_Apply" c_tcutg_apply 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TCutG_Chisquare" c_tcutg_chisquare 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TCutG_DrawGraph" c_tcutg_drawgraph 
  :: (Ptr RawTCutG) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_drawPanelTGraph" c_tcutg_drawpaneltgraph 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_Expand" c_tcutg_expand 
  :: (Ptr RawTCutG) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_FitPanelTGraph" c_tcutg_fitpaneltgraph 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_getCorrelationFactorTGraph" c_tcutg_getcorrelationfactortgraph 
  :: (Ptr RawTCutG) -> IO CDouble
foreign import ccall "HROOT.h TCutG_getCovarianceTGraph" c_tcutg_getcovariancetgraph 
  :: (Ptr RawTCutG) -> IO CDouble
foreign import ccall "HROOT.h TCutG_getMeanTGraph" c_tcutg_getmeantgraph 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_getRMSTGraph" c_tcutg_getrmstgraph 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorX" c_tcutg_geterrorx 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorY" c_tcutg_geterrory 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorXhigh" c_tcutg_geterrorxhigh 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorXlow" c_tcutg_geterrorxlow 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorYhigh" c_tcutg_geterroryhigh 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_GetErrorYlow" c_tcutg_geterrorylow 
  :: (Ptr RawTCutG) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_InitExpo" c_tcutg_initexpo 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_InitGaus" c_tcutg_initgaus 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_InitPolynom" c_tcutg_initpolynom 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_InsertPoint" c_tcutg_insertpoint 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_integralTGraph" c_tcutg_integraltgraph 
  :: (Ptr RawTCutG) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TCutG_IsEditable" c_tcutg_iseditable 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_isInsideTGraph" c_tcutg_isinsidetgraph 
  :: (Ptr RawTCutG) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TCutG_LeastSquareFit" c_tcutg_leastsquarefit 
  :: (Ptr RawTCutG) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_PaintStats" c_tcutg_paintstats 
  :: (Ptr RawTCutG) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TCutG_RemovePoint" c_tcutg_removepoint 
  :: (Ptr RawTCutG) -> CInt -> IO CInt
foreign import ccall "HROOT.h TCutG_SetEditable" c_tcutg_seteditable 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetHistogram" c_tcutg_sethistogram 
  :: (Ptr RawTCutG) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TCutG_setMaximumTGraph" c_tcutg_setmaximumtgraph 
  :: (Ptr RawTCutG) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_setMinimumTGraph" c_tcutg_setminimumtgraph 
  :: (Ptr RawTCutG) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_Set" c_tcutg_set 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetPoint" c_tcutg_setpoint 
  :: (Ptr RawTCutG) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCutG_SetName" c_tcutg_setname 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_SetNameTitle" c_tcutg_setnametitle 
  :: (Ptr RawTCutG) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_SetTitle" c_tcutg_settitle 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_GetLineColor" c_tcutg_getlinecolor 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_GetLineStyle" c_tcutg_getlinestyle 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_GetLineWidth" c_tcutg_getlinewidth 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_ResetAttLine" c_tcutg_resetattline 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_SetLineAttributes" c_tcutg_setlineattributes 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_SetLineColor" c_tcutg_setlinecolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetLineStyle" c_tcutg_setlinestyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetLineWidth" c_tcutg_setlinewidth 
  :: (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_GetMarkerColor" c_tcutg_getmarkercolor 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_GetMarkerStyle" c_tcutg_getmarkerstyle 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_GetMarkerSize" c_tcutg_getmarkersize 
  :: (Ptr RawTCutG) -> IO CDouble
foreign import ccall "HROOT.h TCutG_ResetAttMarker" c_tcutg_resetattmarker 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_SetMarkerAttributes" c_tcutg_setmarkerattributes 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_SetMarkerColor" c_tcutg_setmarkercolor 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetMarkerStyle" c_tcutg_setmarkerstyle 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_SetMarkerSize" c_tcutg_setmarkersize 
  :: (Ptr RawTCutG) -> CInt -> IO ()
foreign import ccall "HROOT.h TCutG_Draw" c_tcutg_draw 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_FindObject" c_tcutg_findobject 
  :: (Ptr RawTCutG) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCutG_GetName" c_tcutg_getname 
  :: (Ptr RawTCutG) -> IO CString
foreign import ccall "HROOT.h TCutG_IsA" c_tcutg_isa 
  :: (Ptr RawTCutG) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCutG_IsFolder" c_tcutg_isfolder 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_IsEqual" c_tcutg_isequal 
  :: (Ptr RawTCutG) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCutG_IsSortable" c_tcutg_issortable 
  :: (Ptr RawTCutG) -> IO CInt
foreign import ccall "HROOT.h TCutG_Paint" c_tcutg_paint 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_printObj" c_tcutg_printobj 
  :: (Ptr RawTCutG) -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_RecursiveRemove" c_tcutg_recursiveremove 
  :: (Ptr RawTCutG) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCutG_SaveAs" c_tcutg_saveas 
  :: (Ptr RawTCutG) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCutG_UseCurrentStyle" c_tcutg_usecurrentstyle 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_Write" c_tcutg_write 
  :: (Ptr RawTCutG) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCutG_delete" c_tcutg_delete 
  :: (Ptr RawTCutG) -> IO ()
foreign import ccall "HROOT.h TCutG_newTCutG" c_tcutg_newtcutg 
  :: CString -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTCutG)

foreign import ccall "HROOT.h TGraphBentErrors_Apply" c_tgraphbenterrors_apply 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Chisquare" c_tgraphbenterrors_chisquare 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_DrawGraph" c_tgraphbenterrors_drawgraph 
  :: (Ptr RawTGraphBentErrors) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_drawPanelTGraph" c_tgraphbenterrors_drawpaneltgraph 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Expand" c_tgraphbenterrors_expand 
  :: (Ptr RawTGraphBentErrors) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_FitPanelTGraph" c_tgraphbenterrors_fitpaneltgraph 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_getCorrelationFactorTGraph" c_tgraphbenterrors_getcorrelationfactortgraph 
  :: (Ptr RawTGraphBentErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_getCovarianceTGraph" c_tgraphbenterrors_getcovariancetgraph 
  :: (Ptr RawTGraphBentErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_getMeanTGraph" c_tgraphbenterrors_getmeantgraph 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_getRMSTGraph" c_tgraphbenterrors_getrmstgraph 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorX" c_tgraphbenterrors_geterrorx 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorY" c_tgraphbenterrors_geterrory 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorXhigh" c_tgraphbenterrors_geterrorxhigh 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorXlow" c_tgraphbenterrors_geterrorxlow 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorYhigh" c_tgraphbenterrors_geterroryhigh 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_GetErrorYlow" c_tgraphbenterrors_geterrorylow 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_InitExpo" c_tgraphbenterrors_initexpo 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_InitGaus" c_tgraphbenterrors_initgaus 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_InitPolynom" c_tgraphbenterrors_initpolynom 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_InsertPoint" c_tgraphbenterrors_insertpoint 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_integralTGraph" c_tgraphbenterrors_integraltgraph 
  :: (Ptr RawTGraphBentErrors) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_IsEditable" c_tgraphbenterrors_iseditable 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_isInsideTGraph" c_tgraphbenterrors_isinsidetgraph 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_LeastSquareFit" c_tgraphbenterrors_leastsquarefit 
  :: (Ptr RawTGraphBentErrors) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_PaintStats" c_tgraphbenterrors_paintstats 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_RemovePoint" c_tgraphbenterrors_removepoint 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_SetEditable" c_tgraphbenterrors_seteditable 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetHistogram" c_tgraphbenterrors_sethistogram 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_setMaximumTGraph" c_tgraphbenterrors_setmaximumtgraph 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_setMinimumTGraph" c_tgraphbenterrors_setminimumtgraph 
  :: (Ptr RawTGraphBentErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Set" c_tgraphbenterrors_set 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetPoint" c_tgraphbenterrors_setpoint 
  :: (Ptr RawTGraphBentErrors) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetName" c_tgraphbenterrors_setname 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetNameTitle" c_tgraphbenterrors_setnametitle 
  :: (Ptr RawTGraphBentErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetTitle" c_tgraphbenterrors_settitle 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_GetLineColor" c_tgraphbenterrors_getlinecolor 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_GetLineStyle" c_tgraphbenterrors_getlinestyle 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_GetLineWidth" c_tgraphbenterrors_getlinewidth 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_ResetAttLine" c_tgraphbenterrors_resetattline 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetLineAttributes" c_tgraphbenterrors_setlineattributes 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetLineColor" c_tgraphbenterrors_setlinecolor 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetLineStyle" c_tgraphbenterrors_setlinestyle 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetLineWidth" c_tgraphbenterrors_setlinewidth 
  :: (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_GetMarkerColor" c_tgraphbenterrors_getmarkercolor 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_GetMarkerStyle" c_tgraphbenterrors_getmarkerstyle 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_GetMarkerSize" c_tgraphbenterrors_getmarkersize 
  :: (Ptr RawTGraphBentErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphBentErrors_ResetAttMarker" c_tgraphbenterrors_resetattmarker 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetMarkerAttributes" c_tgraphbenterrors_setmarkerattributes 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetMarkerColor" c_tgraphbenterrors_setmarkercolor 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetMarkerStyle" c_tgraphbenterrors_setmarkerstyle 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SetMarkerSize" c_tgraphbenterrors_setmarkersize 
  :: (Ptr RawTGraphBentErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Draw" c_tgraphbenterrors_draw 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_FindObject" c_tgraphbenterrors_findobject 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphBentErrors_GetName" c_tgraphbenterrors_getname 
  :: (Ptr RawTGraphBentErrors) -> IO CString
foreign import ccall "HROOT.h TGraphBentErrors_IsA" c_tgraphbenterrors_isa 
  :: (Ptr RawTGraphBentErrors) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraphBentErrors_IsFolder" c_tgraphbenterrors_isfolder 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_IsEqual" c_tgraphbenterrors_isequal 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_IsSortable" c_tgraphbenterrors_issortable 
  :: (Ptr RawTGraphBentErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_Paint" c_tgraphbenterrors_paint 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_printObj" c_tgraphbenterrors_printobj 
  :: (Ptr RawTGraphBentErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_RecursiveRemove" c_tgraphbenterrors_recursiveremove 
  :: (Ptr RawTGraphBentErrors) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_SaveAs" c_tgraphbenterrors_saveas 
  :: (Ptr RawTGraphBentErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_UseCurrentStyle" c_tgraphbenterrors_usecurrentstyle 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_Write" c_tgraphbenterrors_write 
  :: (Ptr RawTGraphBentErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphBentErrors_delete" c_tgraphbenterrors_delete 
  :: (Ptr RawTGraphBentErrors) -> IO ()
foreign import ccall "HROOT.h TGraphBentErrors_newTGraphBentErrors" c_tgraphbenterrors_newtgraphbenterrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphBentErrors)

foreign import ccall "HROOT.h TGraphErrors_Apply" c_tgrapherrors_apply 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Chisquare" c_tgrapherrors_chisquare 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_DrawGraph" c_tgrapherrors_drawgraph 
  :: (Ptr RawTGraphErrors) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_drawPanelTGraph" c_tgrapherrors_drawpaneltgraph 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Expand" c_tgrapherrors_expand 
  :: (Ptr RawTGraphErrors) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_FitPanelTGraph" c_tgrapherrors_fitpaneltgraph 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_getCorrelationFactorTGraph" c_tgrapherrors_getcorrelationfactortgraph 
  :: (Ptr RawTGraphErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_getCovarianceTGraph" c_tgrapherrors_getcovariancetgraph 
  :: (Ptr RawTGraphErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_getMeanTGraph" c_tgrapherrors_getmeantgraph 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_getRMSTGraph" c_tgrapherrors_getrmstgraph 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorX" c_tgrapherrors_geterrorx 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorY" c_tgrapherrors_geterrory 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorXhigh" c_tgrapherrors_geterrorxhigh 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorXlow" c_tgrapherrors_geterrorxlow 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorYhigh" c_tgrapherrors_geterroryhigh 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_GetErrorYlow" c_tgrapherrors_geterrorylow 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_InitExpo" c_tgrapherrors_initexpo 
  :: (Ptr RawTGraphErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_InitGaus" c_tgrapherrors_initgaus 
  :: (Ptr RawTGraphErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_InitPolynom" c_tgrapherrors_initpolynom 
  :: (Ptr RawTGraphErrors) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_InsertPoint" c_tgrapherrors_insertpoint 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_integralTGraph" c_tgrapherrors_integraltgraph 
  :: (Ptr RawTGraphErrors) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_IsEditable" c_tgrapherrors_iseditable 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_isInsideTGraph" c_tgrapherrors_isinsidetgraph 
  :: (Ptr RawTGraphErrors) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_LeastSquareFit" c_tgrapherrors_leastsquarefit 
  :: (Ptr RawTGraphErrors) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_PaintStats" c_tgrapherrors_paintstats 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_RemovePoint" c_tgrapherrors_removepoint 
  :: (Ptr RawTGraphErrors) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_SetEditable" c_tgrapherrors_seteditable 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetHistogram" c_tgrapherrors_sethistogram 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_setMaximumTGraph" c_tgrapherrors_setmaximumtgraph 
  :: (Ptr RawTGraphErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_setMinimumTGraph" c_tgrapherrors_setminimumtgraph 
  :: (Ptr RawTGraphErrors) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Set" c_tgrapherrors_set 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetPoint" c_tgrapherrors_setpoint 
  :: (Ptr RawTGraphErrors) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetName" c_tgrapherrors_setname 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetNameTitle" c_tgrapherrors_setnametitle 
  :: (Ptr RawTGraphErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetTitle" c_tgrapherrors_settitle 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_GetLineColor" c_tgrapherrors_getlinecolor 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_GetLineStyle" c_tgrapherrors_getlinestyle 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_GetLineWidth" c_tgrapherrors_getlinewidth 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_ResetAttLine" c_tgrapherrors_resetattline 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetLineAttributes" c_tgrapherrors_setlineattributes 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetLineColor" c_tgrapherrors_setlinecolor 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetLineStyle" c_tgrapherrors_setlinestyle 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetLineWidth" c_tgrapherrors_setlinewidth 
  :: (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_GetMarkerColor" c_tgrapherrors_getmarkercolor 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_GetMarkerStyle" c_tgrapherrors_getmarkerstyle 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_GetMarkerSize" c_tgrapherrors_getmarkersize 
  :: (Ptr RawTGraphErrors) -> IO CDouble
foreign import ccall "HROOT.h TGraphErrors_ResetAttMarker" c_tgrapherrors_resetattmarker 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetMarkerAttributes" c_tgrapherrors_setmarkerattributes 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetMarkerColor" c_tgrapherrors_setmarkercolor 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetMarkerStyle" c_tgrapherrors_setmarkerstyle 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SetMarkerSize" c_tgrapherrors_setmarkersize 
  :: (Ptr RawTGraphErrors) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Draw" c_tgrapherrors_draw 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_FindObject" c_tgrapherrors_findobject 
  :: (Ptr RawTGraphErrors) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphErrors_GetName" c_tgrapherrors_getname 
  :: (Ptr RawTGraphErrors) -> IO CString
foreign import ccall "HROOT.h TGraphErrors_IsA" c_tgrapherrors_isa 
  :: (Ptr RawTGraphErrors) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraphErrors_IsFolder" c_tgrapherrors_isfolder 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_IsEqual" c_tgrapherrors_isequal 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_IsSortable" c_tgrapherrors_issortable 
  :: (Ptr RawTGraphErrors) -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_Paint" c_tgrapherrors_paint 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_printObj" c_tgrapherrors_printobj 
  :: (Ptr RawTGraphErrors) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_RecursiveRemove" c_tgrapherrors_recursiveremove 
  :: (Ptr RawTGraphErrors) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_SaveAs" c_tgrapherrors_saveas 
  :: (Ptr RawTGraphErrors) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphErrors_UseCurrentStyle" c_tgrapherrors_usecurrentstyle 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_Write" c_tgrapherrors_write 
  :: (Ptr RawTGraphErrors) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphErrors_delete" c_tgrapherrors_delete 
  :: (Ptr RawTGraphErrors) -> IO ()
foreign import ccall "HROOT.h TGraphErrors_newTGraphErrors" c_tgrapherrors_newtgrapherrors 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphErrors)

foreign import ccall "HROOT.h TGraphPolar_Apply" c_tgraphpolar_apply 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Chisquare" c_tgraphpolar_chisquare 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_DrawGraph" c_tgraphpolar_drawgraph 
  :: (Ptr RawTGraphPolar) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_drawPanelTGraph" c_tgraphpolar_drawpaneltgraph 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Expand" c_tgraphpolar_expand 
  :: (Ptr RawTGraphPolar) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_FitPanelTGraph" c_tgraphpolar_fitpaneltgraph 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_getCorrelationFactorTGraph" c_tgraphpolar_getcorrelationfactortgraph 
  :: (Ptr RawTGraphPolar) -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_getCovarianceTGraph" c_tgraphpolar_getcovariancetgraph 
  :: (Ptr RawTGraphPolar) -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_getMeanTGraph" c_tgraphpolar_getmeantgraph 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_getRMSTGraph" c_tgraphpolar_getrmstgraph 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorX" c_tgraphpolar_geterrorx 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorY" c_tgraphpolar_geterrory 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorXhigh" c_tgraphpolar_geterrorxhigh 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorXlow" c_tgraphpolar_geterrorxlow 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorYhigh" c_tgraphpolar_geterroryhigh 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_GetErrorYlow" c_tgraphpolar_geterrorylow 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_InitExpo" c_tgraphpolar_initexpo 
  :: (Ptr RawTGraphPolar) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_InitGaus" c_tgraphpolar_initgaus 
  :: (Ptr RawTGraphPolar) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_InitPolynom" c_tgraphpolar_initpolynom 
  :: (Ptr RawTGraphPolar) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_InsertPoint" c_tgraphpolar_insertpoint 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_integralTGraph" c_tgraphpolar_integraltgraph 
  :: (Ptr RawTGraphPolar) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_IsEditable" c_tgraphpolar_iseditable 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_isInsideTGraph" c_tgraphpolar_isinsidetgraph 
  :: (Ptr RawTGraphPolar) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_LeastSquareFit" c_tgraphpolar_leastsquarefit 
  :: (Ptr RawTGraphPolar) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_PaintStats" c_tgraphpolar_paintstats 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_RemovePoint" c_tgraphpolar_removepoint 
  :: (Ptr RawTGraphPolar) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_SetEditable" c_tgraphpolar_seteditable 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetHistogram" c_tgraphpolar_sethistogram 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_setMaximumTGraph" c_tgraphpolar_setmaximumtgraph 
  :: (Ptr RawTGraphPolar) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_setMinimumTGraph" c_tgraphpolar_setminimumtgraph 
  :: (Ptr RawTGraphPolar) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Set" c_tgraphpolar_set 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetPoint" c_tgraphpolar_setpoint 
  :: (Ptr RawTGraphPolar) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetName" c_tgraphpolar_setname 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetNameTitle" c_tgraphpolar_setnametitle 
  :: (Ptr RawTGraphPolar) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetTitle" c_tgraphpolar_settitle 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_GetLineColor" c_tgraphpolar_getlinecolor 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_GetLineStyle" c_tgraphpolar_getlinestyle 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_GetLineWidth" c_tgraphpolar_getlinewidth 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_ResetAttLine" c_tgraphpolar_resetattline 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetLineAttributes" c_tgraphpolar_setlineattributes 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetLineColor" c_tgraphpolar_setlinecolor 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetLineStyle" c_tgraphpolar_setlinestyle 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetLineWidth" c_tgraphpolar_setlinewidth 
  :: (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_GetMarkerColor" c_tgraphpolar_getmarkercolor 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_GetMarkerStyle" c_tgraphpolar_getmarkerstyle 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_GetMarkerSize" c_tgraphpolar_getmarkersize 
  :: (Ptr RawTGraphPolar) -> IO CDouble
foreign import ccall "HROOT.h TGraphPolar_ResetAttMarker" c_tgraphpolar_resetattmarker 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetMarkerAttributes" c_tgraphpolar_setmarkerattributes 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetMarkerColor" c_tgraphpolar_setmarkercolor 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetMarkerStyle" c_tgraphpolar_setmarkerstyle 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SetMarkerSize" c_tgraphpolar_setmarkersize 
  :: (Ptr RawTGraphPolar) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Draw" c_tgraphpolar_draw 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_FindObject" c_tgraphpolar_findobject 
  :: (Ptr RawTGraphPolar) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphPolar_GetName" c_tgraphpolar_getname 
  :: (Ptr RawTGraphPolar) -> IO CString
foreign import ccall "HROOT.h TGraphPolar_IsA" c_tgraphpolar_isa 
  :: (Ptr RawTGraphPolar) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraphPolar_IsFolder" c_tgraphpolar_isfolder 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_IsEqual" c_tgraphpolar_isequal 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_IsSortable" c_tgraphpolar_issortable 
  :: (Ptr RawTGraphPolar) -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_Paint" c_tgraphpolar_paint 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_printObj" c_tgraphpolar_printobj 
  :: (Ptr RawTGraphPolar) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_RecursiveRemove" c_tgraphpolar_recursiveremove 
  :: (Ptr RawTGraphPolar) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_SaveAs" c_tgraphpolar_saveas 
  :: (Ptr RawTGraphPolar) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphPolar_UseCurrentStyle" c_tgraphpolar_usecurrentstyle 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_Write" c_tgraphpolar_write 
  :: (Ptr RawTGraphPolar) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphPolar_delete" c_tgraphpolar_delete 
  :: (Ptr RawTGraphPolar) -> IO ()
foreign import ccall "HROOT.h TGraphPolar_newTGraphPolar" c_tgraphpolar_newtgraphpolar 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO (Ptr RawTGraphPolar)

foreign import ccall "HROOT.h TGraphQQ_Apply" c_tgraphqq_apply 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Chisquare" c_tgraphqq_chisquare 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_DrawGraph" c_tgraphqq_drawgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_drawPanelTGraph" c_tgraphqq_drawpaneltgraph 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Expand" c_tgraphqq_expand 
  :: (Ptr RawTGraphQQ) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_FitPanelTGraph" c_tgraphqq_fitpaneltgraph 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_getCorrelationFactorTGraph" c_tgraphqq_getcorrelationfactortgraph 
  :: (Ptr RawTGraphQQ) -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_getCovarianceTGraph" c_tgraphqq_getcovariancetgraph 
  :: (Ptr RawTGraphQQ) -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_getMeanTGraph" c_tgraphqq_getmeantgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_getRMSTGraph" c_tgraphqq_getrmstgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorX" c_tgraphqq_geterrorx 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorY" c_tgraphqq_geterrory 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorXhigh" c_tgraphqq_geterrorxhigh 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorXlow" c_tgraphqq_geterrorxlow 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorYhigh" c_tgraphqq_geterroryhigh 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_GetErrorYlow" c_tgraphqq_geterrorylow 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_InitExpo" c_tgraphqq_initexpo 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_InitGaus" c_tgraphqq_initgaus 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_InitPolynom" c_tgraphqq_initpolynom 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_InsertPoint" c_tgraphqq_insertpoint 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_integralTGraph" c_tgraphqq_integraltgraph 
  :: (Ptr RawTGraphQQ) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_IsEditable" c_tgraphqq_iseditable 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_isInsideTGraph" c_tgraphqq_isinsidetgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_LeastSquareFit" c_tgraphqq_leastsquarefit 
  :: (Ptr RawTGraphQQ) -> CInt -> (Ptr CDouble) -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_PaintStats" c_tgraphqq_paintstats 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTF1) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_RemovePoint" c_tgraphqq_removepoint 
  :: (Ptr RawTGraphQQ) -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_SetEditable" c_tgraphqq_seteditable 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetHistogram" c_tgraphqq_sethistogram 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_setMaximumTGraph" c_tgraphqq_setmaximumtgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_setMinimumTGraph" c_tgraphqq_setminimumtgraph 
  :: (Ptr RawTGraphQQ) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Set" c_tgraphqq_set 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetPoint" c_tgraphqq_setpoint 
  :: (Ptr RawTGraphQQ) -> CInt -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetName" c_tgraphqq_setname 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetNameTitle" c_tgraphqq_setnametitle 
  :: (Ptr RawTGraphQQ) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetTitle" c_tgraphqq_settitle 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_GetLineColor" c_tgraphqq_getlinecolor 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_GetLineStyle" c_tgraphqq_getlinestyle 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_GetLineWidth" c_tgraphqq_getlinewidth 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_ResetAttLine" c_tgraphqq_resetattline 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetLineAttributes" c_tgraphqq_setlineattributes 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetLineColor" c_tgraphqq_setlinecolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetLineStyle" c_tgraphqq_setlinestyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetLineWidth" c_tgraphqq_setlinewidth 
  :: (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_GetMarkerColor" c_tgraphqq_getmarkercolor 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_GetMarkerStyle" c_tgraphqq_getmarkerstyle 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_GetMarkerSize" c_tgraphqq_getmarkersize 
  :: (Ptr RawTGraphQQ) -> IO CDouble
foreign import ccall "HROOT.h TGraphQQ_ResetAttMarker" c_tgraphqq_resetattmarker 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetMarkerAttributes" c_tgraphqq_setmarkerattributes 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetMarkerColor" c_tgraphqq_setmarkercolor 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetMarkerStyle" c_tgraphqq_setmarkerstyle 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SetMarkerSize" c_tgraphqq_setmarkersize 
  :: (Ptr RawTGraphQQ) -> CInt -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Draw" c_tgraphqq_draw 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_FindObject" c_tgraphqq_findobject 
  :: (Ptr RawTGraphQQ) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGraphQQ_GetName" c_tgraphqq_getname 
  :: (Ptr RawTGraphQQ) -> IO CString
foreign import ccall "HROOT.h TGraphQQ_IsA" c_tgraphqq_isa 
  :: (Ptr RawTGraphQQ) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGraphQQ_IsFolder" c_tgraphqq_isfolder 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_IsEqual" c_tgraphqq_isequal 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_IsSortable" c_tgraphqq_issortable 
  :: (Ptr RawTGraphQQ) -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_Paint" c_tgraphqq_paint 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_printObj" c_tgraphqq_printobj 
  :: (Ptr RawTGraphQQ) -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_RecursiveRemove" c_tgraphqq_recursiveremove 
  :: (Ptr RawTGraphQQ) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_SaveAs" c_tgraphqq_saveas 
  :: (Ptr RawTGraphQQ) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGraphQQ_UseCurrentStyle" c_tgraphqq_usecurrentstyle 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_Write" c_tgraphqq_write 
  :: (Ptr RawTGraphQQ) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGraphQQ_delete" c_tgraphqq_delete 
  :: (Ptr RawTGraphQQ) -> IO ()
foreign import ccall "HROOT.h TGraphQQ_newTGraphQQ" c_tgraphqq_newtgraphqq 
  :: CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO (Ptr RawTGraphQQ)

foreign import ccall "HROOT.h TEllipse_Draw" c_tellipse_draw 
  :: (Ptr RawTEllipse) -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_FindObject" c_tellipse_findobject 
  :: (Ptr RawTEllipse) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEllipse_GetName" c_tellipse_getname 
  :: (Ptr RawTEllipse) -> IO CString
foreign import ccall "HROOT.h TEllipse_IsA" c_tellipse_isa 
  :: (Ptr RawTEllipse) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TEllipse_IsFolder" c_tellipse_isfolder 
  :: (Ptr RawTEllipse) -> IO CInt
foreign import ccall "HROOT.h TEllipse_IsEqual" c_tellipse_isequal 
  :: (Ptr RawTEllipse) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TEllipse_IsSortable" c_tellipse_issortable 
  :: (Ptr RawTEllipse) -> IO CInt
foreign import ccall "HROOT.h TEllipse_Paint" c_tellipse_paint 
  :: (Ptr RawTEllipse) -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_printObj" c_tellipse_printobj 
  :: (Ptr RawTEllipse) -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_RecursiveRemove" c_tellipse_recursiveremove 
  :: (Ptr RawTEllipse) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TEllipse_SaveAs" c_tellipse_saveas 
  :: (Ptr RawTEllipse) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_UseCurrentStyle" c_tellipse_usecurrentstyle 
  :: (Ptr RawTEllipse) -> IO ()
foreign import ccall "HROOT.h TEllipse_Write" c_tellipse_write 
  :: (Ptr RawTEllipse) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEllipse_GetLineColor" c_tellipse_getlinecolor 
  :: (Ptr RawTEllipse) -> IO CInt
foreign import ccall "HROOT.h TEllipse_GetLineStyle" c_tellipse_getlinestyle 
  :: (Ptr RawTEllipse) -> IO CInt
foreign import ccall "HROOT.h TEllipse_GetLineWidth" c_tellipse_getlinewidth 
  :: (Ptr RawTEllipse) -> IO CInt
foreign import ccall "HROOT.h TEllipse_ResetAttLine" c_tellipse_resetattline 
  :: (Ptr RawTEllipse) -> CString -> IO ()
foreign import ccall "HROOT.h TEllipse_SetLineAttributes" c_tellipse_setlineattributes 
  :: (Ptr RawTEllipse) -> IO ()
foreign import ccall "HROOT.h TEllipse_SetLineColor" c_tellipse_setlinecolor 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetLineStyle" c_tellipse_setlinestyle 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetLineWidth" c_tellipse_setlinewidth 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetFillColor" c_tellipse_setfillcolor 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_SetFillStyle" c_tellipse_setfillstyle 
  :: (Ptr RawTEllipse) -> CInt -> IO ()
foreign import ccall "HROOT.h TEllipse_delete" c_tellipse_delete 
  :: (Ptr RawTEllipse) -> IO ()
foreign import ccall "HROOT.h TEllipse_newTEllipse" c_tellipse_newtellipse 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTEllipse)

foreign import ccall "HROOT.h TArc_Draw" c_tarc_draw 
  :: (Ptr RawTArc) -> CString -> IO ()
foreign import ccall "HROOT.h TArc_FindObject" c_tarc_findobject 
  :: (Ptr RawTArc) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TArc_GetName" c_tarc_getname 
  :: (Ptr RawTArc) -> IO CString
foreign import ccall "HROOT.h TArc_IsA" c_tarc_isa 
  :: (Ptr RawTArc) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TArc_IsFolder" c_tarc_isfolder 
  :: (Ptr RawTArc) -> IO CInt
foreign import ccall "HROOT.h TArc_IsEqual" c_tarc_isequal 
  :: (Ptr RawTArc) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TArc_IsSortable" c_tarc_issortable 
  :: (Ptr RawTArc) -> IO CInt
foreign import ccall "HROOT.h TArc_Paint" c_tarc_paint 
  :: (Ptr RawTArc) -> CString -> IO ()
foreign import ccall "HROOT.h TArc_printObj" c_tarc_printobj 
  :: (Ptr RawTArc) -> CString -> IO ()
foreign import ccall "HROOT.h TArc_RecursiveRemove" c_tarc_recursiveremove 
  :: (Ptr RawTArc) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TArc_SaveAs" c_tarc_saveas 
  :: (Ptr RawTArc) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TArc_UseCurrentStyle" c_tarc_usecurrentstyle 
  :: (Ptr RawTArc) -> IO ()
foreign import ccall "HROOT.h TArc_Write" c_tarc_write 
  :: (Ptr RawTArc) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TArc_GetLineColor" c_tarc_getlinecolor 
  :: (Ptr RawTArc) -> IO CInt
foreign import ccall "HROOT.h TArc_GetLineStyle" c_tarc_getlinestyle 
  :: (Ptr RawTArc) -> IO CInt
foreign import ccall "HROOT.h TArc_GetLineWidth" c_tarc_getlinewidth 
  :: (Ptr RawTArc) -> IO CInt
foreign import ccall "HROOT.h TArc_ResetAttLine" c_tarc_resetattline 
  :: (Ptr RawTArc) -> CString -> IO ()
foreign import ccall "HROOT.h TArc_SetLineAttributes" c_tarc_setlineattributes 
  :: (Ptr RawTArc) -> IO ()
foreign import ccall "HROOT.h TArc_SetLineColor" c_tarc_setlinecolor 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetLineStyle" c_tarc_setlinestyle 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetLineWidth" c_tarc_setlinewidth 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetFillColor" c_tarc_setfillcolor 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_SetFillStyle" c_tarc_setfillstyle 
  :: (Ptr RawTArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TArc_delete" c_tarc_delete 
  :: (Ptr RawTArc) -> IO ()
foreign import ccall "HROOT.h TArc_newTArc" c_tarc_newtarc 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTArc)

foreign import ccall "HROOT.h TCrown_Draw" c_tcrown_draw 
  :: (Ptr RawTCrown) -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_FindObject" c_tcrown_findobject 
  :: (Ptr RawTCrown) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCrown_GetName" c_tcrown_getname 
  :: (Ptr RawTCrown) -> IO CString
foreign import ccall "HROOT.h TCrown_IsA" c_tcrown_isa 
  :: (Ptr RawTCrown) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCrown_IsFolder" c_tcrown_isfolder 
  :: (Ptr RawTCrown) -> IO CInt
foreign import ccall "HROOT.h TCrown_IsEqual" c_tcrown_isequal 
  :: (Ptr RawTCrown) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCrown_IsSortable" c_tcrown_issortable 
  :: (Ptr RawTCrown) -> IO CInt
foreign import ccall "HROOT.h TCrown_Paint" c_tcrown_paint 
  :: (Ptr RawTCrown) -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_printObj" c_tcrown_printobj 
  :: (Ptr RawTCrown) -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_RecursiveRemove" c_tcrown_recursiveremove 
  :: (Ptr RawTCrown) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCrown_SaveAs" c_tcrown_saveas 
  :: (Ptr RawTCrown) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_UseCurrentStyle" c_tcrown_usecurrentstyle 
  :: (Ptr RawTCrown) -> IO ()
foreign import ccall "HROOT.h TCrown_Write" c_tcrown_write 
  :: (Ptr RawTCrown) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCrown_GetLineColor" c_tcrown_getlinecolor 
  :: (Ptr RawTCrown) -> IO CInt
foreign import ccall "HROOT.h TCrown_GetLineStyle" c_tcrown_getlinestyle 
  :: (Ptr RawTCrown) -> IO CInt
foreign import ccall "HROOT.h TCrown_GetLineWidth" c_tcrown_getlinewidth 
  :: (Ptr RawTCrown) -> IO CInt
foreign import ccall "HROOT.h TCrown_ResetAttLine" c_tcrown_resetattline 
  :: (Ptr RawTCrown) -> CString -> IO ()
foreign import ccall "HROOT.h TCrown_SetLineAttributes" c_tcrown_setlineattributes 
  :: (Ptr RawTCrown) -> IO ()
foreign import ccall "HROOT.h TCrown_SetLineColor" c_tcrown_setlinecolor 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetLineStyle" c_tcrown_setlinestyle 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetLineWidth" c_tcrown_setlinewidth 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetFillColor" c_tcrown_setfillcolor 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_SetFillStyle" c_tcrown_setfillstyle 
  :: (Ptr RawTCrown) -> CInt -> IO ()
foreign import ccall "HROOT.h TCrown_delete" c_tcrown_delete 
  :: (Ptr RawTCrown) -> IO ()
foreign import ccall "HROOT.h TCrown_newTCrown" c_tcrown_newtcrown 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCrown)

foreign import ccall "HROOT.h TLine_Draw" c_tline_draw 
  :: (Ptr RawTLine) -> CString -> IO ()
foreign import ccall "HROOT.h TLine_FindObject" c_tline_findobject 
  :: (Ptr RawTLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLine_GetName" c_tline_getname 
  :: (Ptr RawTLine) -> IO CString
foreign import ccall "HROOT.h TLine_IsA" c_tline_isa 
  :: (Ptr RawTLine) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TLine_IsFolder" c_tline_isfolder 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_IsEqual" c_tline_isequal 
  :: (Ptr RawTLine) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TLine_IsSortable" c_tline_issortable 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_Paint" c_tline_paint 
  :: (Ptr RawTLine) -> CString -> IO ()
foreign import ccall "HROOT.h TLine_printObj" c_tline_printobj 
  :: (Ptr RawTLine) -> CString -> IO ()
foreign import ccall "HROOT.h TLine_RecursiveRemove" c_tline_recursiveremove 
  :: (Ptr RawTLine) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TLine_SaveAs" c_tline_saveas 
  :: (Ptr RawTLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLine_UseCurrentStyle" c_tline_usecurrentstyle 
  :: (Ptr RawTLine) -> IO ()
foreign import ccall "HROOT.h TLine_Write" c_tline_write 
  :: (Ptr RawTLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLine_GetLineColor" c_tline_getlinecolor 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_GetLineStyle" c_tline_getlinestyle 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_GetLineWidth" c_tline_getlinewidth 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_ResetAttLine" c_tline_resetattline 
  :: (Ptr RawTLine) -> CString -> IO ()
foreign import ccall "HROOT.h TLine_SetLineAttributes" c_tline_setlineattributes 
  :: (Ptr RawTLine) -> IO ()
foreign import ccall "HROOT.h TLine_SetLineColor" c_tline_setlinecolor 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_SetLineStyle" c_tline_setlinestyle 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_SetLineWidth" c_tline_setlinewidth 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_delete" c_tline_delete 
  :: (Ptr RawTLine) -> IO ()
foreign import ccall "HROOT.h TLine_newTLine" c_tline_newtline 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TLine_DrawLine" c_tline_drawline 
  :: (Ptr RawTLine) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TLine_DrawLineNDC" c_tline_drawlinendc 
  :: (Ptr RawTLine) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TLine_tLineGetX1" c_tline_tlinegetx1 
  :: (Ptr RawTLine) -> IO CDouble
foreign import ccall "HROOT.h TLine_tLineGetX2" c_tline_tlinegetx2 
  :: (Ptr RawTLine) -> IO CDouble
foreign import ccall "HROOT.h TLine_tLineGetY1" c_tline_tlinegety1 
  :: (Ptr RawTLine) -> IO CDouble
foreign import ccall "HROOT.h TLine_tLineGetY2" c_tline_tlinegety2 
  :: (Ptr RawTLine) -> IO CDouble
foreign import ccall "HROOT.h TLine_tLineIsHorizontal" c_tline_tlineishorizontal 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_tLineIsVertical" c_tline_tlineisvertical 
  :: (Ptr RawTLine) -> IO CInt
foreign import ccall "HROOT.h TLine_PaintLine" c_tline_paintline 
  :: (Ptr RawTLine) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TLine_PaintLineNDC" c_tline_paintlinendc 
  :: (Ptr RawTLine) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TLine_tLineSetHorizontal" c_tline_tlinesethorizontal 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_tLineSetVertical" c_tline_tlinesetvertical 
  :: (Ptr RawTLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TLine_SetX1" c_tline_setx1 
  :: (Ptr RawTLine) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLine_SetX2" c_tline_setx2 
  :: (Ptr RawTLine) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLine_SetY1" c_tline_sety1 
  :: (Ptr RawTLine) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLine_SetY2" c_tline_sety2 
  :: (Ptr RawTLine) -> CDouble -> IO ()

foreign import ccall "HROOT.h TArrow_DrawLine" c_tarrow_drawline 
  :: (Ptr RawTArrow) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TArrow_DrawLineNDC" c_tarrow_drawlinendc 
  :: (Ptr RawTArrow) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TArrow_PaintLine" c_tarrow_paintline 
  :: (Ptr RawTArrow) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TArrow_PaintLineNDC" c_tarrow_paintlinendc 
  :: (Ptr RawTArrow) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TArrow_SetX1" c_tarrow_setx1 
  :: (Ptr RawTArrow) -> CDouble -> IO ()
foreign import ccall "HROOT.h TArrow_SetX2" c_tarrow_setx2 
  :: (Ptr RawTArrow) -> CDouble -> IO ()
foreign import ccall "HROOT.h TArrow_SetY1" c_tarrow_sety1 
  :: (Ptr RawTArrow) -> CDouble -> IO ()
foreign import ccall "HROOT.h TArrow_SetY2" c_tarrow_sety2 
  :: (Ptr RawTArrow) -> CDouble -> IO ()
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_Draw" c_tarrow_draw 
  :: (Ptr RawTArrow) -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_FindObject" c_tarrow_findobject 
  :: (Ptr RawTArrow) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TArrow_GetName" c_tarrow_getname 
  :: (Ptr RawTArrow) -> IO CString
foreign import ccall "HROOT.h TArrow_IsA" c_tarrow_isa 
  :: (Ptr RawTArrow) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TArrow_IsFolder" c_tarrow_isfolder 
  :: (Ptr RawTArrow) -> IO CInt
foreign import ccall "HROOT.h TArrow_IsEqual" c_tarrow_isequal 
  :: (Ptr RawTArrow) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TArrow_IsSortable" c_tarrow_issortable 
  :: (Ptr RawTArrow) -> IO CInt
foreign import ccall "HROOT.h TArrow_Paint" c_tarrow_paint 
  :: (Ptr RawTArrow) -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_printObj" c_tarrow_printobj 
  :: (Ptr RawTArrow) -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_RecursiveRemove" c_tarrow_recursiveremove 
  :: (Ptr RawTArrow) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TArrow_SaveAs" c_tarrow_saveas 
  :: (Ptr RawTArrow) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_UseCurrentStyle" c_tarrow_usecurrentstyle 
  :: (Ptr RawTArrow) -> IO ()
foreign import ccall "HROOT.h TArrow_Write" c_tarrow_write 
  :: (Ptr RawTArrow) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TArrow_GetLineColor" c_tarrow_getlinecolor 
  :: (Ptr RawTArrow) -> IO CInt
foreign import ccall "HROOT.h TArrow_GetLineStyle" c_tarrow_getlinestyle 
  :: (Ptr RawTArrow) -> IO CInt
foreign import ccall "HROOT.h TArrow_GetLineWidth" c_tarrow_getlinewidth 
  :: (Ptr RawTArrow) -> IO CInt
foreign import ccall "HROOT.h TArrow_ResetAttLine" c_tarrow_resetattline 
  :: (Ptr RawTArrow) -> CString -> IO ()
foreign import ccall "HROOT.h TArrow_SetLineAttributes" c_tarrow_setlineattributes 
  :: (Ptr RawTArrow) -> IO ()
foreign import ccall "HROOT.h TArrow_SetLineColor" c_tarrow_setlinecolor 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_SetLineStyle" c_tarrow_setlinestyle 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_SetLineWidth" c_tarrow_setlinewidth 
  :: (Ptr RawTArrow) -> CInt -> IO ()
foreign import ccall "HROOT.h TArrow_delete" c_tarrow_delete 
  :: (Ptr RawTArrow) -> IO ()
foreign import ccall "HROOT.h TArrow_newTArrow" c_tarrow_newtarrow 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTArrow)

foreign import ccall "HROOT.h TGaxis_DrawLine" c_tgaxis_drawline 
  :: (Ptr RawTGaxis) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TGaxis_DrawLineNDC" c_tgaxis_drawlinendc 
  :: (Ptr RawTGaxis) -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)
foreign import ccall "HROOT.h TGaxis_PaintLine" c_tgaxis_paintline 
  :: (Ptr RawTGaxis) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_PaintLineNDC" c_tgaxis_paintlinendc 
  :: (Ptr RawTGaxis) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetX1" c_tgaxis_setx1 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetX2" c_tgaxis_setx2 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetY1" c_tgaxis_sety1 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetY2" c_tgaxis_sety2 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_GetTextAlign" c_tgaxis_gettextalign 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetTextAngle" c_tgaxis_gettextangle 
  :: (Ptr RawTGaxis) -> IO CDouble
foreign import ccall "HROOT.h TGaxis_GetTextColor" c_tgaxis_gettextcolor 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetTextFont" c_tgaxis_gettextfont 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetTextSize" c_tgaxis_gettextsize 
  :: (Ptr RawTGaxis) -> IO CDouble
foreign import ccall "HROOT.h TGaxis_ResetAttText" c_tgaxis_resetatttext 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextAttributes" c_tgaxis_settextattributes 
  :: (Ptr RawTGaxis) -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextAlign" c_tgaxis_settextalign 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextAngle" c_tgaxis_settextangle 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextColor" c_tgaxis_settextcolor 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextFont" c_tgaxis_settextfont 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextSize" c_tgaxis_settextsize 
  :: (Ptr RawTGaxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGaxis_SetTextSizePixels" c_tgaxis_settextsizepixels 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_Draw" c_tgaxis_draw 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_FindObject" c_tgaxis_findobject 
  :: (Ptr RawTGaxis) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGaxis_GetName" c_tgaxis_getname 
  :: (Ptr RawTGaxis) -> IO CString
foreign import ccall "HROOT.h TGaxis_IsA" c_tgaxis_isa 
  :: (Ptr RawTGaxis) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGaxis_IsFolder" c_tgaxis_isfolder 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_IsEqual" c_tgaxis_isequal 
  :: (Ptr RawTGaxis) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGaxis_IsSortable" c_tgaxis_issortable 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_Paint" c_tgaxis_paint 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_printObj" c_tgaxis_printobj 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_RecursiveRemove" c_tgaxis_recursiveremove 
  :: (Ptr RawTGaxis) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGaxis_SaveAs" c_tgaxis_saveas 
  :: (Ptr RawTGaxis) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_UseCurrentStyle" c_tgaxis_usecurrentstyle 
  :: (Ptr RawTGaxis) -> IO ()
foreign import ccall "HROOT.h TGaxis_Write" c_tgaxis_write 
  :: (Ptr RawTGaxis) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetLineColor" c_tgaxis_getlinecolor 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetLineStyle" c_tgaxis_getlinestyle 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_GetLineWidth" c_tgaxis_getlinewidth 
  :: (Ptr RawTGaxis) -> IO CInt
foreign import ccall "HROOT.h TGaxis_ResetAttLine" c_tgaxis_resetattline 
  :: (Ptr RawTGaxis) -> CString -> IO ()
foreign import ccall "HROOT.h TGaxis_SetLineAttributes" c_tgaxis_setlineattributes 
  :: (Ptr RawTGaxis) -> IO ()
foreign import ccall "HROOT.h TGaxis_SetLineColor" c_tgaxis_setlinecolor 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetLineStyle" c_tgaxis_setlinestyle 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_SetLineWidth" c_tgaxis_setlinewidth 
  :: (Ptr RawTGaxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TGaxis_delete" c_tgaxis_delete 
  :: (Ptr RawTGaxis) -> IO ()
foreign import ccall "HROOT.h TGaxis_newTGaxis" c_tgaxis_newtgaxis 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> CDouble -> IO (Ptr RawTGaxis)

foreign import ccall "HROOT.h TShape_SetName" c_tshape_setname 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_SetNameTitle" c_tshape_setnametitle 
  :: (Ptr RawTShape) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TShape_SetTitle" c_tshape_settitle 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_GetLineColor" c_tshape_getlinecolor 
  :: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOT.h TShape_GetLineStyle" c_tshape_getlinestyle 
  :: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOT.h TShape_GetLineWidth" c_tshape_getlinewidth 
  :: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOT.h TShape_ResetAttLine" c_tshape_resetattline 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_SetLineAttributes" c_tshape_setlineattributes 
  :: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOT.h TShape_SetLineColor" c_tshape_setlinecolor 
  :: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TShape_SetLineStyle" c_tshape_setlinestyle 
  :: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOT.h TShape_SetLineWidth" c_tshape_setlinewidth 
  :: (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_Draw" c_tshape_draw 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_FindObject" c_tshape_findobject 
  :: (Ptr RawTShape) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TShape_GetName" c_tshape_getname 
  :: (Ptr RawTShape) -> IO CString
foreign import ccall "HROOT.h TShape_IsA" c_tshape_isa 
  :: (Ptr RawTShape) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TShape_IsFolder" c_tshape_isfolder 
  :: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOT.h TShape_IsEqual" c_tshape_isequal 
  :: (Ptr RawTShape) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TShape_IsSortable" c_tshape_issortable 
  :: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOT.h TShape_Paint" c_tshape_paint 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_printObj" c_tshape_printobj 
  :: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOT.h TShape_RecursiveRemove" c_tshape_recursiveremove 
  :: (Ptr RawTShape) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TShape_SaveAs" c_tshape_saveas 
  :: (Ptr RawTShape) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TShape_UseCurrentStyle" c_tshape_usecurrentstyle 
  :: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOT.h TShape_Write" c_tshape_write 
  :: (Ptr RawTShape) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TShape_delete" c_tshape_delete 
  :: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOT.h TShape_newTShape" c_tshape_newtshape 
  :: CString -> CString -> CString -> IO (Ptr RawTShape)

foreign import ccall "HROOT.h TBRIK_SetName" c_tbrik_setname 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_SetNameTitle" c_tbrik_setnametitle 
  :: (Ptr RawTBRIK) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_SetTitle" c_tbrik_settitle 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_GetLineColor" c_tbrik_getlinecolor 
  :: (Ptr RawTBRIK) -> IO CInt
foreign import ccall "HROOT.h TBRIK_GetLineStyle" c_tbrik_getlinestyle 
  :: (Ptr RawTBRIK) -> IO CInt
foreign import ccall "HROOT.h TBRIK_GetLineWidth" c_tbrik_getlinewidth 
  :: (Ptr RawTBRIK) -> IO CInt
foreign import ccall "HROOT.h TBRIK_ResetAttLine" c_tbrik_resetattline 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_SetLineAttributes" c_tbrik_setlineattributes 
  :: (Ptr RawTBRIK) -> IO ()
foreign import ccall "HROOT.h TBRIK_SetLineColor" c_tbrik_setlinecolor 
  :: (Ptr RawTBRIK) -> CInt -> IO ()
foreign import ccall "HROOT.h TBRIK_SetLineStyle" c_tbrik_setlinestyle 
  :: (Ptr RawTBRIK) -> CInt -> IO ()
foreign import ccall "HROOT.h TBRIK_SetLineWidth" c_tbrik_setlinewidth 
  :: (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_Draw" c_tbrik_draw 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_FindObject" c_tbrik_findobject 
  :: (Ptr RawTBRIK) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBRIK_GetName" c_tbrik_getname 
  :: (Ptr RawTBRIK) -> IO CString
foreign import ccall "HROOT.h TBRIK_IsA" c_tbrik_isa 
  :: (Ptr RawTBRIK) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TBRIK_IsFolder" c_tbrik_isfolder 
  :: (Ptr RawTBRIK) -> IO CInt
foreign import ccall "HROOT.h TBRIK_IsEqual" c_tbrik_isequal 
  :: (Ptr RawTBRIK) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TBRIK_IsSortable" c_tbrik_issortable 
  :: (Ptr RawTBRIK) -> IO CInt
foreign import ccall "HROOT.h TBRIK_Paint" c_tbrik_paint 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_printObj" c_tbrik_printobj 
  :: (Ptr RawTBRIK) -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_RecursiveRemove" c_tbrik_recursiveremove 
  :: (Ptr RawTBRIK) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TBRIK_SaveAs" c_tbrik_saveas 
  :: (Ptr RawTBRIK) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBRIK_UseCurrentStyle" c_tbrik_usecurrentstyle 
  :: (Ptr RawTBRIK) -> IO ()
foreign import ccall "HROOT.h TBRIK_Write" c_tbrik_write 
  :: (Ptr RawTBRIK) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBRIK_delete" c_tbrik_delete 
  :: (Ptr RawTBRIK) -> IO ()
foreign import ccall "HROOT.h TBRIK_newTBRIK" c_tbrik_newtbrik 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTBRIK)

foreign import ccall "HROOT.h TTUBE_SetName" c_ttube_setname 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_SetNameTitle" c_ttube_setnametitle 
  :: (Ptr RawTTUBE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_SetTitle" c_ttube_settitle 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_GetLineColor" c_ttube_getlinecolor 
  :: (Ptr RawTTUBE) -> IO CInt
foreign import ccall "HROOT.h TTUBE_GetLineStyle" c_ttube_getlinestyle 
  :: (Ptr RawTTUBE) -> IO CInt
foreign import ccall "HROOT.h TTUBE_GetLineWidth" c_ttube_getlinewidth 
  :: (Ptr RawTTUBE) -> IO CInt
foreign import ccall "HROOT.h TTUBE_ResetAttLine" c_ttube_resetattline 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_SetLineAttributes" c_ttube_setlineattributes 
  :: (Ptr RawTTUBE) -> IO ()
foreign import ccall "HROOT.h TTUBE_SetLineColor" c_ttube_setlinecolor 
  :: (Ptr RawTTUBE) -> CInt -> IO ()
foreign import ccall "HROOT.h TTUBE_SetLineStyle" c_ttube_setlinestyle 
  :: (Ptr RawTTUBE) -> CInt -> IO ()
foreign import ccall "HROOT.h TTUBE_SetLineWidth" c_ttube_setlinewidth 
  :: (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_Draw" c_ttube_draw 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_FindObject" c_ttube_findobject 
  :: (Ptr RawTTUBE) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTUBE_GetName" c_ttube_getname 
  :: (Ptr RawTTUBE) -> IO CString
foreign import ccall "HROOT.h TTUBE_IsA" c_ttube_isa 
  :: (Ptr RawTTUBE) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TTUBE_IsFolder" c_ttube_isfolder 
  :: (Ptr RawTTUBE) -> IO CInt
foreign import ccall "HROOT.h TTUBE_IsEqual" c_ttube_isequal 
  :: (Ptr RawTTUBE) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TTUBE_IsSortable" c_ttube_issortable 
  :: (Ptr RawTTUBE) -> IO CInt
foreign import ccall "HROOT.h TTUBE_Paint" c_ttube_paint 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_printObj" c_ttube_printobj 
  :: (Ptr RawTTUBE) -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_RecursiveRemove" c_ttube_recursiveremove 
  :: (Ptr RawTTUBE) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TTUBE_SaveAs" c_ttube_saveas 
  :: (Ptr RawTTUBE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTUBE_UseCurrentStyle" c_ttube_usecurrentstyle 
  :: (Ptr RawTTUBE) -> IO ()
foreign import ccall "HROOT.h TTUBE_Write" c_ttube_write 
  :: (Ptr RawTTUBE) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTUBE_delete" c_ttube_delete 
  :: (Ptr RawTTUBE) -> IO ()
foreign import ccall "HROOT.h TTUBE_newTTUBE" c_ttube_newttube 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTTUBE)

foreign import ccall "HROOT.h TPCON_SetName" c_tpcon_setname 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_SetNameTitle" c_tpcon_setnametitle 
  :: (Ptr RawTPCON) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_SetTitle" c_tpcon_settitle 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_GetLineColor" c_tpcon_getlinecolor 
  :: (Ptr RawTPCON) -> IO CInt
foreign import ccall "HROOT.h TPCON_GetLineStyle" c_tpcon_getlinestyle 
  :: (Ptr RawTPCON) -> IO CInt
foreign import ccall "HROOT.h TPCON_GetLineWidth" c_tpcon_getlinewidth 
  :: (Ptr RawTPCON) -> IO CInt
foreign import ccall "HROOT.h TPCON_ResetAttLine" c_tpcon_resetattline 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_SetLineAttributes" c_tpcon_setlineattributes 
  :: (Ptr RawTPCON) -> IO ()
foreign import ccall "HROOT.h TPCON_SetLineColor" c_tpcon_setlinecolor 
  :: (Ptr RawTPCON) -> CInt -> IO ()
foreign import ccall "HROOT.h TPCON_SetLineStyle" c_tpcon_setlinestyle 
  :: (Ptr RawTPCON) -> CInt -> IO ()
foreign import ccall "HROOT.h TPCON_SetLineWidth" c_tpcon_setlinewidth 
  :: (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_Draw" c_tpcon_draw 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_FindObject" c_tpcon_findobject 
  :: (Ptr RawTPCON) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPCON_GetName" c_tpcon_getname 
  :: (Ptr RawTPCON) -> IO CString
foreign import ccall "HROOT.h TPCON_IsA" c_tpcon_isa 
  :: (Ptr RawTPCON) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPCON_IsFolder" c_tpcon_isfolder 
  :: (Ptr RawTPCON) -> IO CInt
foreign import ccall "HROOT.h TPCON_IsEqual" c_tpcon_isequal 
  :: (Ptr RawTPCON) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPCON_IsSortable" c_tpcon_issortable 
  :: (Ptr RawTPCON) -> IO CInt
foreign import ccall "HROOT.h TPCON_Paint" c_tpcon_paint 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_printObj" c_tpcon_printobj 
  :: (Ptr RawTPCON) -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_RecursiveRemove" c_tpcon_recursiveremove 
  :: (Ptr RawTPCON) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPCON_SaveAs" c_tpcon_saveas 
  :: (Ptr RawTPCON) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPCON_UseCurrentStyle" c_tpcon_usecurrentstyle 
  :: (Ptr RawTPCON) -> IO ()
foreign import ccall "HROOT.h TPCON_Write" c_tpcon_write 
  :: (Ptr RawTPCON) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPCON_delete" c_tpcon_delete 
  :: (Ptr RawTPCON) -> IO ()
foreign import ccall "HROOT.h TPCON_newTPCON" c_tpcon_newtpcon 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CInt -> IO (Ptr RawTPCON)

foreign import ccall "HROOT.h TSPHE_SetName" c_tsphe_setname 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_SetNameTitle" c_tsphe_setnametitle 
  :: (Ptr RawTSPHE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_SetTitle" c_tsphe_settitle 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_GetLineColor" c_tsphe_getlinecolor 
  :: (Ptr RawTSPHE) -> IO CInt
foreign import ccall "HROOT.h TSPHE_GetLineStyle" c_tsphe_getlinestyle 
  :: (Ptr RawTSPHE) -> IO CInt
foreign import ccall "HROOT.h TSPHE_GetLineWidth" c_tsphe_getlinewidth 
  :: (Ptr RawTSPHE) -> IO CInt
foreign import ccall "HROOT.h TSPHE_ResetAttLine" c_tsphe_resetattline 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_SetLineAttributes" c_tsphe_setlineattributes 
  :: (Ptr RawTSPHE) -> IO ()
foreign import ccall "HROOT.h TSPHE_SetLineColor" c_tsphe_setlinecolor 
  :: (Ptr RawTSPHE) -> CInt -> IO ()
foreign import ccall "HROOT.h TSPHE_SetLineStyle" c_tsphe_setlinestyle 
  :: (Ptr RawTSPHE) -> CInt -> IO ()
foreign import ccall "HROOT.h TSPHE_SetLineWidth" c_tsphe_setlinewidth 
  :: (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_Draw" c_tsphe_draw 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_FindObject" c_tsphe_findobject 
  :: (Ptr RawTSPHE) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSPHE_GetName" c_tsphe_getname 
  :: (Ptr RawTSPHE) -> IO CString
foreign import ccall "HROOT.h TSPHE_IsA" c_tsphe_isa 
  :: (Ptr RawTSPHE) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TSPHE_IsFolder" c_tsphe_isfolder 
  :: (Ptr RawTSPHE) -> IO CInt
foreign import ccall "HROOT.h TSPHE_IsEqual" c_tsphe_isequal 
  :: (Ptr RawTSPHE) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TSPHE_IsSortable" c_tsphe_issortable 
  :: (Ptr RawTSPHE) -> IO CInt
foreign import ccall "HROOT.h TSPHE_Paint" c_tsphe_paint 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_printObj" c_tsphe_printobj 
  :: (Ptr RawTSPHE) -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_RecursiveRemove" c_tsphe_recursiveremove 
  :: (Ptr RawTSPHE) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TSPHE_SaveAs" c_tsphe_saveas 
  :: (Ptr RawTSPHE) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSPHE_UseCurrentStyle" c_tsphe_usecurrentstyle 
  :: (Ptr RawTSPHE) -> IO ()
foreign import ccall "HROOT.h TSPHE_Write" c_tsphe_write 
  :: (Ptr RawTSPHE) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSPHE_delete" c_tsphe_delete 
  :: (Ptr RawTSPHE) -> IO ()
foreign import ccall "HROOT.h TSPHE_newTSPHE" c_tsphe_newtsphe 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTSPHE)

foreign import ccall "HROOT.h TXTRU_SetName" c_txtru_setname 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_SetNameTitle" c_txtru_setnametitle 
  :: (Ptr RawTXTRU) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_SetTitle" c_txtru_settitle 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_GetLineColor" c_txtru_getlinecolor 
  :: (Ptr RawTXTRU) -> IO CInt
foreign import ccall "HROOT.h TXTRU_GetLineStyle" c_txtru_getlinestyle 
  :: (Ptr RawTXTRU) -> IO CInt
foreign import ccall "HROOT.h TXTRU_GetLineWidth" c_txtru_getlinewidth 
  :: (Ptr RawTXTRU) -> IO CInt
foreign import ccall "HROOT.h TXTRU_ResetAttLine" c_txtru_resetattline 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_SetLineAttributes" c_txtru_setlineattributes 
  :: (Ptr RawTXTRU) -> IO ()
foreign import ccall "HROOT.h TXTRU_SetLineColor" c_txtru_setlinecolor 
  :: (Ptr RawTXTRU) -> CInt -> IO ()
foreign import ccall "HROOT.h TXTRU_SetLineStyle" c_txtru_setlinestyle 
  :: (Ptr RawTXTRU) -> CInt -> IO ()
foreign import ccall "HROOT.h TXTRU_SetLineWidth" c_txtru_setlinewidth 
  :: (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_Draw" c_txtru_draw 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_FindObject" c_txtru_findobject 
  :: (Ptr RawTXTRU) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TXTRU_GetName" c_txtru_getname 
  :: (Ptr RawTXTRU) -> IO CString
foreign import ccall "HROOT.h TXTRU_IsA" c_txtru_isa 
  :: (Ptr RawTXTRU) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TXTRU_IsFolder" c_txtru_isfolder 
  :: (Ptr RawTXTRU) -> IO CInt
foreign import ccall "HROOT.h TXTRU_IsEqual" c_txtru_isequal 
  :: (Ptr RawTXTRU) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TXTRU_IsSortable" c_txtru_issortable 
  :: (Ptr RawTXTRU) -> IO CInt
foreign import ccall "HROOT.h TXTRU_Paint" c_txtru_paint 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_printObj" c_txtru_printobj 
  :: (Ptr RawTXTRU) -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_RecursiveRemove" c_txtru_recursiveremove 
  :: (Ptr RawTXTRU) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TXTRU_SaveAs" c_txtru_saveas 
  :: (Ptr RawTXTRU) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TXTRU_UseCurrentStyle" c_txtru_usecurrentstyle 
  :: (Ptr RawTXTRU) -> IO ()
foreign import ccall "HROOT.h TXTRU_Write" c_txtru_write 
  :: (Ptr RawTXTRU) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TXTRU_delete" c_txtru_delete 
  :: (Ptr RawTXTRU) -> IO ()
foreign import ccall "HROOT.h TXTRU_newTXTRU" c_txtru_newtxtru 
  :: CString -> CString -> CString -> CInt -> CInt -> IO (Ptr RawTXTRU)

foreign import ccall "HROOT.h TBox_Draw" c_tbox_draw 
  :: (Ptr RawTBox) -> CString -> IO ()
foreign import ccall "HROOT.h TBox_FindObject" c_tbox_findobject 
  :: (Ptr RawTBox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBox_GetName" c_tbox_getname 
  :: (Ptr RawTBox) -> IO CString
foreign import ccall "HROOT.h TBox_IsA" c_tbox_isa 
  :: (Ptr RawTBox) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TBox_IsFolder" c_tbox_isfolder 
  :: (Ptr RawTBox) -> IO CInt
foreign import ccall "HROOT.h TBox_IsEqual" c_tbox_isequal 
  :: (Ptr RawTBox) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TBox_IsSortable" c_tbox_issortable 
  :: (Ptr RawTBox) -> IO CInt
foreign import ccall "HROOT.h TBox_Paint" c_tbox_paint 
  :: (Ptr RawTBox) -> CString -> IO ()
foreign import ccall "HROOT.h TBox_printObj" c_tbox_printobj 
  :: (Ptr RawTBox) -> CString -> IO ()
foreign import ccall "HROOT.h TBox_RecursiveRemove" c_tbox_recursiveremove 
  :: (Ptr RawTBox) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TBox_SaveAs" c_tbox_saveas 
  :: (Ptr RawTBox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBox_UseCurrentStyle" c_tbox_usecurrentstyle 
  :: (Ptr RawTBox) -> IO ()
foreign import ccall "HROOT.h TBox_Write" c_tbox_write 
  :: (Ptr RawTBox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBox_GetLineColor" c_tbox_getlinecolor 
  :: (Ptr RawTBox) -> IO CInt
foreign import ccall "HROOT.h TBox_GetLineStyle" c_tbox_getlinestyle 
  :: (Ptr RawTBox) -> IO CInt
foreign import ccall "HROOT.h TBox_GetLineWidth" c_tbox_getlinewidth 
  :: (Ptr RawTBox) -> IO CInt
foreign import ccall "HROOT.h TBox_ResetAttLine" c_tbox_resetattline 
  :: (Ptr RawTBox) -> CString -> IO ()
foreign import ccall "HROOT.h TBox_SetLineAttributes" c_tbox_setlineattributes 
  :: (Ptr RawTBox) -> IO ()
foreign import ccall "HROOT.h TBox_SetLineColor" c_tbox_setlinecolor 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetLineStyle" c_tbox_setlinestyle 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetLineWidth" c_tbox_setlinewidth 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetFillColor" c_tbox_setfillcolor 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_SetFillStyle" c_tbox_setfillstyle 
  :: (Ptr RawTBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TBox_delete" c_tbox_delete 
  :: (Ptr RawTBox) -> IO ()
foreign import ccall "HROOT.h TBox_newTBox" c_tbox_newtbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTBox)

foreign import ccall "HROOT.h TPave_Draw" c_tpave_draw 
  :: (Ptr RawTPave) -> CString -> IO ()
foreign import ccall "HROOT.h TPave_FindObject" c_tpave_findobject 
  :: (Ptr RawTPave) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPave_GetName" c_tpave_getname 
  :: (Ptr RawTPave) -> IO CString
foreign import ccall "HROOT.h TPave_IsA" c_tpave_isa 
  :: (Ptr RawTPave) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPave_IsFolder" c_tpave_isfolder 
  :: (Ptr RawTPave) -> IO CInt
foreign import ccall "HROOT.h TPave_IsEqual" c_tpave_isequal 
  :: (Ptr RawTPave) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPave_IsSortable" c_tpave_issortable 
  :: (Ptr RawTPave) -> IO CInt
foreign import ccall "HROOT.h TPave_Paint" c_tpave_paint 
  :: (Ptr RawTPave) -> CString -> IO ()
foreign import ccall "HROOT.h TPave_printObj" c_tpave_printobj 
  :: (Ptr RawTPave) -> CString -> IO ()
foreign import ccall "HROOT.h TPave_RecursiveRemove" c_tpave_recursiveremove 
  :: (Ptr RawTPave) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPave_SaveAs" c_tpave_saveas 
  :: (Ptr RawTPave) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPave_UseCurrentStyle" c_tpave_usecurrentstyle 
  :: (Ptr RawTPave) -> IO ()
foreign import ccall "HROOT.h TPave_Write" c_tpave_write 
  :: (Ptr RawTPave) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPave_GetLineColor" c_tpave_getlinecolor 
  :: (Ptr RawTPave) -> IO CInt
foreign import ccall "HROOT.h TPave_GetLineStyle" c_tpave_getlinestyle 
  :: (Ptr RawTPave) -> IO CInt
foreign import ccall "HROOT.h TPave_GetLineWidth" c_tpave_getlinewidth 
  :: (Ptr RawTPave) -> IO CInt
foreign import ccall "HROOT.h TPave_ResetAttLine" c_tpave_resetattline 
  :: (Ptr RawTPave) -> CString -> IO ()
foreign import ccall "HROOT.h TPave_SetLineAttributes" c_tpave_setlineattributes 
  :: (Ptr RawTPave) -> IO ()
foreign import ccall "HROOT.h TPave_SetLineColor" c_tpave_setlinecolor 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetLineStyle" c_tpave_setlinestyle 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetLineWidth" c_tpave_setlinewidth 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetFillColor" c_tpave_setfillcolor 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_SetFillStyle" c_tpave_setfillstyle 
  :: (Ptr RawTPave) -> CInt -> IO ()
foreign import ccall "HROOT.h TPave_delete" c_tpave_delete 
  :: (Ptr RawTPave) -> IO ()
foreign import ccall "HROOT.h TPave_newTPave" c_tpave_newtpave 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> IO (Ptr RawTPave)

foreign import ccall "HROOT.h TPaveText_GetTextAlign" c_tpavetext_gettextalign 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetTextAngle" c_tpavetext_gettextangle 
  :: (Ptr RawTPaveText) -> IO CDouble
foreign import ccall "HROOT.h TPaveText_GetTextColor" c_tpavetext_gettextcolor 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetTextFont" c_tpavetext_gettextfont 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetTextSize" c_tpavetext_gettextsize 
  :: (Ptr RawTPaveText) -> IO CDouble
foreign import ccall "HROOT.h TPaveText_ResetAttText" c_tpavetext_resetatttext 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextAttributes" c_tpavetext_settextattributes 
  :: (Ptr RawTPaveText) -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextAlign" c_tpavetext_settextalign 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextAngle" c_tpavetext_settextangle 
  :: (Ptr RawTPaveText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextColor" c_tpavetext_settextcolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextFont" c_tpavetext_settextfont 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextSize" c_tpavetext_settextsize 
  :: (Ptr RawTPaveText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveText_SetTextSizePixels" c_tpavetext_settextsizepixels 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_Draw" c_tpavetext_draw 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_FindObject" c_tpavetext_findobject 
  :: (Ptr RawTPaveText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveText_GetName" c_tpavetext_getname 
  :: (Ptr RawTPaveText) -> IO CString
foreign import ccall "HROOT.h TPaveText_IsA" c_tpavetext_isa 
  :: (Ptr RawTPaveText) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPaveText_IsFolder" c_tpavetext_isfolder 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_IsEqual" c_tpavetext_isequal 
  :: (Ptr RawTPaveText) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPaveText_IsSortable" c_tpavetext_issortable 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_Paint" c_tpavetext_paint 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_printObj" c_tpavetext_printobj 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_RecursiveRemove" c_tpavetext_recursiveremove 
  :: (Ptr RawTPaveText) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPaveText_SaveAs" c_tpavetext_saveas 
  :: (Ptr RawTPaveText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_UseCurrentStyle" c_tpavetext_usecurrentstyle 
  :: (Ptr RawTPaveText) -> IO ()
foreign import ccall "HROOT.h TPaveText_Write" c_tpavetext_write 
  :: (Ptr RawTPaveText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetLineColor" c_tpavetext_getlinecolor 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetLineStyle" c_tpavetext_getlinestyle 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_GetLineWidth" c_tpavetext_getlinewidth 
  :: (Ptr RawTPaveText) -> IO CInt
foreign import ccall "HROOT.h TPaveText_ResetAttLine" c_tpavetext_resetattline 
  :: (Ptr RawTPaveText) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveText_SetLineAttributes" c_tpavetext_setlineattributes 
  :: (Ptr RawTPaveText) -> IO ()
foreign import ccall "HROOT.h TPaveText_SetLineColor" c_tpavetext_setlinecolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetLineStyle" c_tpavetext_setlinestyle 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetLineWidth" c_tpavetext_setlinewidth 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetFillColor" c_tpavetext_setfillcolor 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_SetFillStyle" c_tpavetext_setfillstyle 
  :: (Ptr RawTPaveText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveText_delete" c_tpavetext_delete 
  :: (Ptr RawTPaveText) -> IO ()
foreign import ccall "HROOT.h TPaveText_newTPaveText" c_tpavetext_newtpavetext 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTPaveText)

foreign import ccall "HROOT.h TDiamond_GetTextAlign" c_tdiamond_gettextalign 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetTextAngle" c_tdiamond_gettextangle 
  :: (Ptr RawTDiamond) -> IO CDouble
foreign import ccall "HROOT.h TDiamond_GetTextColor" c_tdiamond_gettextcolor 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetTextFont" c_tdiamond_gettextfont 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetTextSize" c_tdiamond_gettextsize 
  :: (Ptr RawTDiamond) -> IO CDouble
foreign import ccall "HROOT.h TDiamond_ResetAttText" c_tdiamond_resetatttext 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextAttributes" c_tdiamond_settextattributes 
  :: (Ptr RawTDiamond) -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextAlign" c_tdiamond_settextalign 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextAngle" c_tdiamond_settextangle 
  :: (Ptr RawTDiamond) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextColor" c_tdiamond_settextcolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextFont" c_tdiamond_settextfont 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextSize" c_tdiamond_settextsize 
  :: (Ptr RawTDiamond) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDiamond_SetTextSizePixels" c_tdiamond_settextsizepixels 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_Draw" c_tdiamond_draw 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_FindObject" c_tdiamond_findobject 
  :: (Ptr RawTDiamond) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDiamond_GetName" c_tdiamond_getname 
  :: (Ptr RawTDiamond) -> IO CString
foreign import ccall "HROOT.h TDiamond_IsA" c_tdiamond_isa 
  :: (Ptr RawTDiamond) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TDiamond_IsFolder" c_tdiamond_isfolder 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_IsEqual" c_tdiamond_isequal 
  :: (Ptr RawTDiamond) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TDiamond_IsSortable" c_tdiamond_issortable 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_Paint" c_tdiamond_paint 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_printObj" c_tdiamond_printobj 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_RecursiveRemove" c_tdiamond_recursiveremove 
  :: (Ptr RawTDiamond) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TDiamond_SaveAs" c_tdiamond_saveas 
  :: (Ptr RawTDiamond) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_UseCurrentStyle" c_tdiamond_usecurrentstyle 
  :: (Ptr RawTDiamond) -> IO ()
foreign import ccall "HROOT.h TDiamond_Write" c_tdiamond_write 
  :: (Ptr RawTDiamond) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetLineColor" c_tdiamond_getlinecolor 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetLineStyle" c_tdiamond_getlinestyle 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_GetLineWidth" c_tdiamond_getlinewidth 
  :: (Ptr RawTDiamond) -> IO CInt
foreign import ccall "HROOT.h TDiamond_ResetAttLine" c_tdiamond_resetattline 
  :: (Ptr RawTDiamond) -> CString -> IO ()
foreign import ccall "HROOT.h TDiamond_SetLineAttributes" c_tdiamond_setlineattributes 
  :: (Ptr RawTDiamond) -> IO ()
foreign import ccall "HROOT.h TDiamond_SetLineColor" c_tdiamond_setlinecolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetLineStyle" c_tdiamond_setlinestyle 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetLineWidth" c_tdiamond_setlinewidth 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetFillColor" c_tdiamond_setfillcolor 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_SetFillStyle" c_tdiamond_setfillstyle 
  :: (Ptr RawTDiamond) -> CInt -> IO ()
foreign import ccall "HROOT.h TDiamond_delete" c_tdiamond_delete 
  :: (Ptr RawTDiamond) -> IO ()
foreign import ccall "HROOT.h TDiamond_newTDiamond" c_tdiamond_newtdiamond 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTDiamond)

foreign import ccall "HROOT.h TPaveStats_GetTextAlign" c_tpavestats_gettextalign 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetTextAngle" c_tpavestats_gettextangle 
  :: (Ptr RawTPaveStats) -> IO CDouble
foreign import ccall "HROOT.h TPaveStats_GetTextColor" c_tpavestats_gettextcolor 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetTextFont" c_tpavestats_gettextfont 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetTextSize" c_tpavestats_gettextsize 
  :: (Ptr RawTPaveStats) -> IO CDouble
foreign import ccall "HROOT.h TPaveStats_ResetAttText" c_tpavestats_resetatttext 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextAttributes" c_tpavestats_settextattributes 
  :: (Ptr RawTPaveStats) -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextAlign" c_tpavestats_settextalign 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextAngle" c_tpavestats_settextangle 
  :: (Ptr RawTPaveStats) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextColor" c_tpavestats_settextcolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextFont" c_tpavestats_settextfont 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextSize" c_tpavestats_settextsize 
  :: (Ptr RawTPaveStats) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetTextSizePixels" c_tpavestats_settextsizepixels 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_Draw" c_tpavestats_draw 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_FindObject" c_tpavestats_findobject 
  :: (Ptr RawTPaveStats) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveStats_GetName" c_tpavestats_getname 
  :: (Ptr RawTPaveStats) -> IO CString
foreign import ccall "HROOT.h TPaveStats_IsA" c_tpavestats_isa 
  :: (Ptr RawTPaveStats) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPaveStats_IsFolder" c_tpavestats_isfolder 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_IsEqual" c_tpavestats_isequal 
  :: (Ptr RawTPaveStats) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_IsSortable" c_tpavestats_issortable 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_Paint" c_tpavestats_paint 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_printObj" c_tpavestats_printobj 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_RecursiveRemove" c_tpavestats_recursiveremove 
  :: (Ptr RawTPaveStats) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPaveStats_SaveAs" c_tpavestats_saveas 
  :: (Ptr RawTPaveStats) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_UseCurrentStyle" c_tpavestats_usecurrentstyle 
  :: (Ptr RawTPaveStats) -> IO ()
foreign import ccall "HROOT.h TPaveStats_Write" c_tpavestats_write 
  :: (Ptr RawTPaveStats) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetLineColor" c_tpavestats_getlinecolor 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetLineStyle" c_tpavestats_getlinestyle 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_GetLineWidth" c_tpavestats_getlinewidth 
  :: (Ptr RawTPaveStats) -> IO CInt
foreign import ccall "HROOT.h TPaveStats_ResetAttLine" c_tpavestats_resetattline 
  :: (Ptr RawTPaveStats) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetLineAttributes" c_tpavestats_setlineattributes 
  :: (Ptr RawTPaveStats) -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetLineColor" c_tpavestats_setlinecolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetLineStyle" c_tpavestats_setlinestyle 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetLineWidth" c_tpavestats_setlinewidth 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetFillColor" c_tpavestats_setfillcolor 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_SetFillStyle" c_tpavestats_setfillstyle 
  :: (Ptr RawTPaveStats) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveStats_delete" c_tpavestats_delete 
  :: (Ptr RawTPaveStats) -> IO ()
foreign import ccall "HROOT.h TPaveStats_newTPaveStats" c_tpavestats_newtpavestats 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> IO (Ptr RawTPaveStats)

foreign import ccall "HROOT.h TPavesText_GetTextAlign" c_tpavestext_gettextalign 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetTextAngle" c_tpavestext_gettextangle 
  :: (Ptr RawTPavesText) -> IO CDouble
foreign import ccall "HROOT.h TPavesText_GetTextColor" c_tpavestext_gettextcolor 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetTextFont" c_tpavestext_gettextfont 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetTextSize" c_tpavestext_gettextsize 
  :: (Ptr RawTPavesText) -> IO CDouble
foreign import ccall "HROOT.h TPavesText_ResetAttText" c_tpavestext_resetatttext 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextAttributes" c_tpavestext_settextattributes 
  :: (Ptr RawTPavesText) -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextAlign" c_tpavestext_settextalign 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextAngle" c_tpavestext_settextangle 
  :: (Ptr RawTPavesText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextColor" c_tpavestext_settextcolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextFont" c_tpavestext_settextfont 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextSize" c_tpavestext_settextsize 
  :: (Ptr RawTPavesText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPavesText_SetTextSizePixels" c_tpavestext_settextsizepixels 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_Draw" c_tpavestext_draw 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_FindObject" c_tpavestext_findobject 
  :: (Ptr RawTPavesText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPavesText_GetName" c_tpavestext_getname 
  :: (Ptr RawTPavesText) -> IO CString
foreign import ccall "HROOT.h TPavesText_IsA" c_tpavestext_isa 
  :: (Ptr RawTPavesText) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPavesText_IsFolder" c_tpavestext_isfolder 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_IsEqual" c_tpavestext_isequal 
  :: (Ptr RawTPavesText) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPavesText_IsSortable" c_tpavestext_issortable 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_Paint" c_tpavestext_paint 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_printObj" c_tpavestext_printobj 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_RecursiveRemove" c_tpavestext_recursiveremove 
  :: (Ptr RawTPavesText) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPavesText_SaveAs" c_tpavestext_saveas 
  :: (Ptr RawTPavesText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_UseCurrentStyle" c_tpavestext_usecurrentstyle 
  :: (Ptr RawTPavesText) -> IO ()
foreign import ccall "HROOT.h TPavesText_Write" c_tpavestext_write 
  :: (Ptr RawTPavesText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetLineColor" c_tpavestext_getlinecolor 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetLineStyle" c_tpavestext_getlinestyle 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_GetLineWidth" c_tpavestext_getlinewidth 
  :: (Ptr RawTPavesText) -> IO CInt
foreign import ccall "HROOT.h TPavesText_ResetAttLine" c_tpavestext_resetattline 
  :: (Ptr RawTPavesText) -> CString -> IO ()
foreign import ccall "HROOT.h TPavesText_SetLineAttributes" c_tpavestext_setlineattributes 
  :: (Ptr RawTPavesText) -> IO ()
foreign import ccall "HROOT.h TPavesText_SetLineColor" c_tpavestext_setlinecolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetLineStyle" c_tpavestext_setlinestyle 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetLineWidth" c_tpavestext_setlinewidth 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetFillColor" c_tpavestext_setfillcolor 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_SetFillStyle" c_tpavestext_setfillstyle 
  :: (Ptr RawTPavesText) -> CInt -> IO ()
foreign import ccall "HROOT.h TPavesText_delete" c_tpavestext_delete 
  :: (Ptr RawTPavesText) -> IO ()
foreign import ccall "HROOT.h TPavesText_newTPavesText" c_tpavestext_newtpavestext 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CString -> IO (Ptr RawTPavesText)

foreign import ccall "HROOT.h TLegend_GetTextAlign" c_tlegend_gettextalign 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_GetTextAngle" c_tlegend_gettextangle 
  :: (Ptr RawTLegend) -> IO CDouble
foreign import ccall "HROOT.h TLegend_GetTextColor" c_tlegend_gettextcolor 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_GetTextFont" c_tlegend_gettextfont 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_GetTextSize" c_tlegend_gettextsize 
  :: (Ptr RawTLegend) -> IO CDouble
foreign import ccall "HROOT.h TLegend_ResetAttText" c_tlegend_resetatttext 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextAttributes" c_tlegend_settextattributes 
  :: (Ptr RawTLegend) -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextAlign" c_tlegend_settextalign 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextAngle" c_tlegend_settextangle 
  :: (Ptr RawTLegend) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextColor" c_tlegend_settextcolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextFont" c_tlegend_settextfont 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextSize" c_tlegend_settextsize 
  :: (Ptr RawTLegend) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLegend_SetTextSizePixels" c_tlegend_settextsizepixels 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_Draw" c_tlegend_draw 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_FindObject" c_tlegend_findobject 
  :: (Ptr RawTLegend) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLegend_GetName" c_tlegend_getname 
  :: (Ptr RawTLegend) -> IO CString
foreign import ccall "HROOT.h TLegend_IsA" c_tlegend_isa 
  :: (Ptr RawTLegend) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TLegend_IsFolder" c_tlegend_isfolder 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_IsEqual" c_tlegend_isequal 
  :: (Ptr RawTLegend) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TLegend_IsSortable" c_tlegend_issortable 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_Paint" c_tlegend_paint 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_printObj" c_tlegend_printobj 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_RecursiveRemove" c_tlegend_recursiveremove 
  :: (Ptr RawTLegend) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TLegend_SaveAs" c_tlegend_saveas 
  :: (Ptr RawTLegend) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_UseCurrentStyle" c_tlegend_usecurrentstyle 
  :: (Ptr RawTLegend) -> IO ()
foreign import ccall "HROOT.h TLegend_Write" c_tlegend_write 
  :: (Ptr RawTLegend) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLegend_GetLineColor" c_tlegend_getlinecolor 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_GetLineStyle" c_tlegend_getlinestyle 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_GetLineWidth" c_tlegend_getlinewidth 
  :: (Ptr RawTLegend) -> IO CInt
foreign import ccall "HROOT.h TLegend_ResetAttLine" c_tlegend_resetattline 
  :: (Ptr RawTLegend) -> CString -> IO ()
foreign import ccall "HROOT.h TLegend_SetLineAttributes" c_tlegend_setlineattributes 
  :: (Ptr RawTLegend) -> IO ()
foreign import ccall "HROOT.h TLegend_SetLineColor" c_tlegend_setlinecolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetLineStyle" c_tlegend_setlinestyle 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetLineWidth" c_tlegend_setlinewidth 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetFillColor" c_tlegend_setfillcolor 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_SetFillStyle" c_tlegend_setfillstyle 
  :: (Ptr RawTLegend) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegend_delete" c_tlegend_delete 
  :: (Ptr RawTLegend) -> IO ()
foreign import ccall "HROOT.h TLegend_newTLegend" c_tlegend_newtlegend 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> CString -> IO (Ptr RawTLegend)
foreign import ccall "HROOT.h TLegend_AddEntry" c_tlegend_addentry 
  :: (Ptr RawTLegend) -> (Ptr RawTObject) -> CString -> CString -> IO (Ptr RawTLegendEntry)

foreign import ccall "HROOT.h TLegendEntry_Draw" c_tlegendentry_draw 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_FindObject" c_tlegendentry_findobject 
  :: (Ptr RawTLegendEntry) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLegendEntry_GetName" c_tlegendentry_getname 
  :: (Ptr RawTLegendEntry) -> IO CString
foreign import ccall "HROOT.h TLegendEntry_IsA" c_tlegendentry_isa 
  :: (Ptr RawTLegendEntry) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TLegendEntry_IsFolder" c_tlegendentry_isfolder 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_IsEqual" c_tlegendentry_isequal 
  :: (Ptr RawTLegendEntry) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_IsSortable" c_tlegendentry_issortable 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_Paint" c_tlegendentry_paint 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_printObj" c_tlegendentry_printobj 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_RecursiveRemove" c_tlegendentry_recursiveremove 
  :: (Ptr RawTLegendEntry) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SaveAs" c_tlegendentry_saveas 
  :: (Ptr RawTLegendEntry) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_UseCurrentStyle" c_tlegendentry_usecurrentstyle 
  :: (Ptr RawTLegendEntry) -> IO ()
foreign import ccall "HROOT.h TLegendEntry_Write" c_tlegendentry_write 
  :: (Ptr RawTLegendEntry) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetTextAlign" c_tlegendentry_gettextalign 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetTextAngle" c_tlegendentry_gettextangle 
  :: (Ptr RawTLegendEntry) -> IO CDouble
foreign import ccall "HROOT.h TLegendEntry_GetTextColor" c_tlegendentry_gettextcolor 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetTextFont" c_tlegendentry_gettextfont 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetTextSize" c_tlegendentry_gettextsize 
  :: (Ptr RawTLegendEntry) -> IO CDouble
foreign import ccall "HROOT.h TLegendEntry_ResetAttText" c_tlegendentry_resetatttext 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextAttributes" c_tlegendentry_settextattributes 
  :: (Ptr RawTLegendEntry) -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextAlign" c_tlegendentry_settextalign 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextAngle" c_tlegendentry_settextangle 
  :: (Ptr RawTLegendEntry) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextColor" c_tlegendentry_settextcolor 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextFont" c_tlegendentry_settextfont 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextSize" c_tlegendentry_settextsize 
  :: (Ptr RawTLegendEntry) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetTextSizePixels" c_tlegendentry_settextsizepixels 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_GetLineColor" c_tlegendentry_getlinecolor 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetLineStyle" c_tlegendentry_getlinestyle 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetLineWidth" c_tlegendentry_getlinewidth 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_ResetAttLine" c_tlegendentry_resetattline 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetLineAttributes" c_tlegendentry_setlineattributes 
  :: (Ptr RawTLegendEntry) -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetLineColor" c_tlegendentry_setlinecolor 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetLineStyle" c_tlegendentry_setlinestyle 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetLineWidth" c_tlegendentry_setlinewidth 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetFillColor" c_tlegendentry_setfillcolor 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetFillStyle" c_tlegendentry_setfillstyle 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_GetMarkerColor" c_tlegendentry_getmarkercolor 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetMarkerStyle" c_tlegendentry_getmarkerstyle 
  :: (Ptr RawTLegendEntry) -> IO CInt
foreign import ccall "HROOT.h TLegendEntry_GetMarkerSize" c_tlegendentry_getmarkersize 
  :: (Ptr RawTLegendEntry) -> IO CDouble
foreign import ccall "HROOT.h TLegendEntry_ResetAttMarker" c_tlegendentry_resetattmarker 
  :: (Ptr RawTLegendEntry) -> CString -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetMarkerAttributes" c_tlegendentry_setmarkerattributes 
  :: (Ptr RawTLegendEntry) -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetMarkerColor" c_tlegendentry_setmarkercolor 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetMarkerStyle" c_tlegendentry_setmarkerstyle 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_SetMarkerSize" c_tlegendentry_setmarkersize 
  :: (Ptr RawTLegendEntry) -> CInt -> IO ()
foreign import ccall "HROOT.h TLegendEntry_delete" c_tlegendentry_delete 
  :: (Ptr RawTLegendEntry) -> IO ()

foreign import ccall "HROOT.h TPaveLabel_GetTextAlign" c_tpavelabel_gettextalign 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetTextAngle" c_tpavelabel_gettextangle 
  :: (Ptr RawTPaveLabel) -> IO CDouble
foreign import ccall "HROOT.h TPaveLabel_GetTextColor" c_tpavelabel_gettextcolor 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetTextFont" c_tpavelabel_gettextfont 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetTextSize" c_tpavelabel_gettextsize 
  :: (Ptr RawTPaveLabel) -> IO CDouble
foreign import ccall "HROOT.h TPaveLabel_ResetAttText" c_tpavelabel_resetatttext 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextAttributes" c_tpavelabel_settextattributes 
  :: (Ptr RawTPaveLabel) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextAlign" c_tpavelabel_settextalign 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextAngle" c_tpavelabel_settextangle 
  :: (Ptr RawTPaveLabel) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextColor" c_tpavelabel_settextcolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextFont" c_tpavelabel_settextfont 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextSize" c_tpavelabel_settextsize 
  :: (Ptr RawTPaveLabel) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetTextSizePixels" c_tpavelabel_settextsizepixels 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_Draw" c_tpavelabel_draw 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_FindObject" c_tpavelabel_findobject 
  :: (Ptr RawTPaveLabel) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveLabel_GetName" c_tpavelabel_getname 
  :: (Ptr RawTPaveLabel) -> IO CString
foreign import ccall "HROOT.h TPaveLabel_IsA" c_tpavelabel_isa 
  :: (Ptr RawTPaveLabel) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPaveLabel_IsFolder" c_tpavelabel_isfolder 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_IsEqual" c_tpavelabel_isequal 
  :: (Ptr RawTPaveLabel) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_IsSortable" c_tpavelabel_issortable 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_Paint" c_tpavelabel_paint 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_printObj" c_tpavelabel_printobj 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_RecursiveRemove" c_tpavelabel_recursiveremove 
  :: (Ptr RawTPaveLabel) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SaveAs" c_tpavelabel_saveas 
  :: (Ptr RawTPaveLabel) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_UseCurrentStyle" c_tpavelabel_usecurrentstyle 
  :: (Ptr RawTPaveLabel) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_Write" c_tpavelabel_write 
  :: (Ptr RawTPaveLabel) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetLineColor" c_tpavelabel_getlinecolor 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetLineStyle" c_tpavelabel_getlinestyle 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_GetLineWidth" c_tpavelabel_getlinewidth 
  :: (Ptr RawTPaveLabel) -> IO CInt
foreign import ccall "HROOT.h TPaveLabel_ResetAttLine" c_tpavelabel_resetattline 
  :: (Ptr RawTPaveLabel) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetLineAttributes" c_tpavelabel_setlineattributes 
  :: (Ptr RawTPaveLabel) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetLineColor" c_tpavelabel_setlinecolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetLineStyle" c_tpavelabel_setlinestyle 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetLineWidth" c_tpavelabel_setlinewidth 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetFillColor" c_tpavelabel_setfillcolor 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_SetFillStyle" c_tpavelabel_setfillstyle 
  :: (Ptr RawTPaveLabel) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveLabel_delete" c_tpavelabel_delete 
  :: (Ptr RawTPaveLabel) -> IO ()
foreign import ccall "HROOT.h TPaveLabel_newTPaveLabel" c_tpavelabel_newtpavelabel 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CString -> CString -> IO (Ptr RawTPaveLabel)

foreign import ccall "HROOT.h TPaveClass_GetTextAlign" c_tpaveclass_gettextalign 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetTextAngle" c_tpaveclass_gettextangle 
  :: (Ptr RawTPaveClass) -> IO CDouble
foreign import ccall "HROOT.h TPaveClass_GetTextColor" c_tpaveclass_gettextcolor 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetTextFont" c_tpaveclass_gettextfont 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetTextSize" c_tpaveclass_gettextsize 
  :: (Ptr RawTPaveClass) -> IO CDouble
foreign import ccall "HROOT.h TPaveClass_ResetAttText" c_tpaveclass_resetatttext 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextAttributes" c_tpaveclass_settextattributes 
  :: (Ptr RawTPaveClass) -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextAlign" c_tpaveclass_settextalign 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextAngle" c_tpaveclass_settextangle 
  :: (Ptr RawTPaveClass) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextColor" c_tpaveclass_settextcolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextFont" c_tpaveclass_settextfont 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextSize" c_tpaveclass_settextsize 
  :: (Ptr RawTPaveClass) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetTextSizePixels" c_tpaveclass_settextsizepixels 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_Draw" c_tpaveclass_draw 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_FindObject" c_tpaveclass_findobject 
  :: (Ptr RawTPaveClass) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPaveClass_GetName" c_tpaveclass_getname 
  :: (Ptr RawTPaveClass) -> IO CString
foreign import ccall "HROOT.h TPaveClass_IsA" c_tpaveclass_isa 
  :: (Ptr RawTPaveClass) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPaveClass_IsFolder" c_tpaveclass_isfolder 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_IsEqual" c_tpaveclass_isequal 
  :: (Ptr RawTPaveClass) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_IsSortable" c_tpaveclass_issortable 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_Paint" c_tpaveclass_paint 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_printObj" c_tpaveclass_printobj 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_RecursiveRemove" c_tpaveclass_recursiveremove 
  :: (Ptr RawTPaveClass) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPaveClass_SaveAs" c_tpaveclass_saveas 
  :: (Ptr RawTPaveClass) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_UseCurrentStyle" c_tpaveclass_usecurrentstyle 
  :: (Ptr RawTPaveClass) -> IO ()
foreign import ccall "HROOT.h TPaveClass_Write" c_tpaveclass_write 
  :: (Ptr RawTPaveClass) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetLineColor" c_tpaveclass_getlinecolor 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetLineStyle" c_tpaveclass_getlinestyle 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_GetLineWidth" c_tpaveclass_getlinewidth 
  :: (Ptr RawTPaveClass) -> IO CInt
foreign import ccall "HROOT.h TPaveClass_ResetAttLine" c_tpaveclass_resetattline 
  :: (Ptr RawTPaveClass) -> CString -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetLineAttributes" c_tpaveclass_setlineattributes 
  :: (Ptr RawTPaveClass) -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetLineColor" c_tpaveclass_setlinecolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetLineStyle" c_tpaveclass_setlinestyle 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetLineWidth" c_tpaveclass_setlinewidth 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetFillColor" c_tpaveclass_setfillcolor 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_SetFillStyle" c_tpaveclass_setfillstyle 
  :: (Ptr RawTPaveClass) -> CInt -> IO ()
foreign import ccall "HROOT.h TPaveClass_delete" c_tpaveclass_delete 
  :: (Ptr RawTPaveClass) -> IO ()

foreign import ccall "HROOT.h TWbox_Draw" c_twbox_draw 
  :: (Ptr RawTWbox) -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_FindObject" c_twbox_findobject 
  :: (Ptr RawTWbox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TWbox_GetName" c_twbox_getname 
  :: (Ptr RawTWbox) -> IO CString
foreign import ccall "HROOT.h TWbox_IsA" c_twbox_isa 
  :: (Ptr RawTWbox) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TWbox_IsFolder" c_twbox_isfolder 
  :: (Ptr RawTWbox) -> IO CInt
foreign import ccall "HROOT.h TWbox_IsEqual" c_twbox_isequal 
  :: (Ptr RawTWbox) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TWbox_IsSortable" c_twbox_issortable 
  :: (Ptr RawTWbox) -> IO CInt
foreign import ccall "HROOT.h TWbox_Paint" c_twbox_paint 
  :: (Ptr RawTWbox) -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_printObj" c_twbox_printobj 
  :: (Ptr RawTWbox) -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_RecursiveRemove" c_twbox_recursiveremove 
  :: (Ptr RawTWbox) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TWbox_SaveAs" c_twbox_saveas 
  :: (Ptr RawTWbox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_UseCurrentStyle" c_twbox_usecurrentstyle 
  :: (Ptr RawTWbox) -> IO ()
foreign import ccall "HROOT.h TWbox_Write" c_twbox_write 
  :: (Ptr RawTWbox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TWbox_GetLineColor" c_twbox_getlinecolor 
  :: (Ptr RawTWbox) -> IO CInt
foreign import ccall "HROOT.h TWbox_GetLineStyle" c_twbox_getlinestyle 
  :: (Ptr RawTWbox) -> IO CInt
foreign import ccall "HROOT.h TWbox_GetLineWidth" c_twbox_getlinewidth 
  :: (Ptr RawTWbox) -> IO CInt
foreign import ccall "HROOT.h TWbox_ResetAttLine" c_twbox_resetattline 
  :: (Ptr RawTWbox) -> CString -> IO ()
foreign import ccall "HROOT.h TWbox_SetLineAttributes" c_twbox_setlineattributes 
  :: (Ptr RawTWbox) -> IO ()
foreign import ccall "HROOT.h TWbox_SetLineColor" c_twbox_setlinecolor 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetLineStyle" c_twbox_setlinestyle 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetLineWidth" c_twbox_setlinewidth 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetFillColor" c_twbox_setfillcolor 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_SetFillStyle" c_twbox_setfillstyle 
  :: (Ptr RawTWbox) -> CInt -> IO ()
foreign import ccall "HROOT.h TWbox_delete" c_twbox_delete 
  :: (Ptr RawTWbox) -> IO ()
foreign import ccall "HROOT.h TWbox_newTWbox" c_twbox_newtwbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr RawTWbox)
foreign import ccall "HROOT.h TWbox_SetBorderMode" c_twbox_setbordermode 
  :: (Ptr RawTWbox) -> CInt -> IO ()

foreign import ccall "HROOT.h TFrame_SetBorderMode" c_tframe_setbordermode 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_Draw" c_tframe_draw 
  :: (Ptr RawTFrame) -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_FindObject" c_tframe_findobject 
  :: (Ptr RawTFrame) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFrame_GetName" c_tframe_getname 
  :: (Ptr RawTFrame) -> IO CString
foreign import ccall "HROOT.h TFrame_IsA" c_tframe_isa 
  :: (Ptr RawTFrame) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TFrame_IsFolder" c_tframe_isfolder 
  :: (Ptr RawTFrame) -> IO CInt
foreign import ccall "HROOT.h TFrame_IsEqual" c_tframe_isequal 
  :: (Ptr RawTFrame) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TFrame_IsSortable" c_tframe_issortable 
  :: (Ptr RawTFrame) -> IO CInt
foreign import ccall "HROOT.h TFrame_Paint" c_tframe_paint 
  :: (Ptr RawTFrame) -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_printObj" c_tframe_printobj 
  :: (Ptr RawTFrame) -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_RecursiveRemove" c_tframe_recursiveremove 
  :: (Ptr RawTFrame) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TFrame_SaveAs" c_tframe_saveas 
  :: (Ptr RawTFrame) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_UseCurrentStyle" c_tframe_usecurrentstyle 
  :: (Ptr RawTFrame) -> IO ()
foreign import ccall "HROOT.h TFrame_Write" c_tframe_write 
  :: (Ptr RawTFrame) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFrame_GetLineColor" c_tframe_getlinecolor 
  :: (Ptr RawTFrame) -> IO CInt
foreign import ccall "HROOT.h TFrame_GetLineStyle" c_tframe_getlinestyle 
  :: (Ptr RawTFrame) -> IO CInt
foreign import ccall "HROOT.h TFrame_GetLineWidth" c_tframe_getlinewidth 
  :: (Ptr RawTFrame) -> IO CInt
foreign import ccall "HROOT.h TFrame_ResetAttLine" c_tframe_resetattline 
  :: (Ptr RawTFrame) -> CString -> IO ()
foreign import ccall "HROOT.h TFrame_SetLineAttributes" c_tframe_setlineattributes 
  :: (Ptr RawTFrame) -> IO ()
foreign import ccall "HROOT.h TFrame_SetLineColor" c_tframe_setlinecolor 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetLineStyle" c_tframe_setlinestyle 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetLineWidth" c_tframe_setlinewidth 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetFillColor" c_tframe_setfillcolor 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_SetFillStyle" c_tframe_setfillstyle 
  :: (Ptr RawTFrame) -> CInt -> IO ()
foreign import ccall "HROOT.h TFrame_delete" c_tframe_delete 
  :: (Ptr RawTFrame) -> IO ()
foreign import ccall "HROOT.h TFrame_newTFrame" c_tframe_newtframe 
  :: CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTFrame)

foreign import ccall "HROOT.h TSliderBox_SetBorderMode" c_tsliderbox_setbordermode 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_Draw" c_tsliderbox_draw 
  :: (Ptr RawTSliderBox) -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_FindObject" c_tsliderbox_findobject 
  :: (Ptr RawTSliderBox) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSliderBox_GetName" c_tsliderbox_getname 
  :: (Ptr RawTSliderBox) -> IO CString
foreign import ccall "HROOT.h TSliderBox_IsA" c_tsliderbox_isa 
  :: (Ptr RawTSliderBox) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TSliderBox_IsFolder" c_tsliderbox_isfolder 
  :: (Ptr RawTSliderBox) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_IsEqual" c_tsliderbox_isequal 
  :: (Ptr RawTSliderBox) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_IsSortable" c_tsliderbox_issortable 
  :: (Ptr RawTSliderBox) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_Paint" c_tsliderbox_paint 
  :: (Ptr RawTSliderBox) -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_printObj" c_tsliderbox_printobj 
  :: (Ptr RawTSliderBox) -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_RecursiveRemove" c_tsliderbox_recursiveremove 
  :: (Ptr RawTSliderBox) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TSliderBox_SaveAs" c_tsliderbox_saveas 
  :: (Ptr RawTSliderBox) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_UseCurrentStyle" c_tsliderbox_usecurrentstyle 
  :: (Ptr RawTSliderBox) -> IO ()
foreign import ccall "HROOT.h TSliderBox_Write" c_tsliderbox_write 
  :: (Ptr RawTSliderBox) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSliderBox_GetLineColor" c_tsliderbox_getlinecolor 
  :: (Ptr RawTSliderBox) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_GetLineStyle" c_tsliderbox_getlinestyle 
  :: (Ptr RawTSliderBox) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_GetLineWidth" c_tsliderbox_getlinewidth 
  :: (Ptr RawTSliderBox) -> IO CInt
foreign import ccall "HROOT.h TSliderBox_ResetAttLine" c_tsliderbox_resetattline 
  :: (Ptr RawTSliderBox) -> CString -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetLineAttributes" c_tsliderbox_setlineattributes 
  :: (Ptr RawTSliderBox) -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetLineColor" c_tsliderbox_setlinecolor 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetLineStyle" c_tsliderbox_setlinestyle 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetLineWidth" c_tsliderbox_setlinewidth 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetFillColor" c_tsliderbox_setfillcolor 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_SetFillStyle" c_tsliderbox_setfillstyle 
  :: (Ptr RawTSliderBox) -> CInt -> IO ()
foreign import ccall "HROOT.h TSliderBox_delete" c_tsliderbox_delete 
  :: (Ptr RawTSliderBox) -> IO ()
foreign import ccall "HROOT.h TSliderBox_newTSliderBox" c_tsliderbox_newtsliderbox 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> CInt -> IO (Ptr RawTSliderBox)

foreign import ccall "HROOT.h TTree_SetName" c_ttree_setname 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_SetNameTitle" c_ttree_setnametitle 
  :: (Ptr RawTTree) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTree_SetTitle" c_ttree_settitle 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_GetLineColor" c_ttree_getlinecolor 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_GetLineStyle" c_ttree_getlinestyle 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_GetLineWidth" c_ttree_getlinewidth 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_ResetAttLine" c_ttree_resetattline 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_SetLineAttributes" c_ttree_setlineattributes 
  :: (Ptr RawTTree) -> IO ()
foreign import ccall "HROOT.h TTree_SetLineColor" c_ttree_setlinecolor 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetLineStyle" c_ttree_setlinestyle 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetLineWidth" c_ttree_setlinewidth 
  :: (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_GetMarkerColor" c_ttree_getmarkercolor 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_GetMarkerStyle" c_ttree_getmarkerstyle 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_GetMarkerSize" c_ttree_getmarkersize 
  :: (Ptr RawTTree) -> IO CDouble
foreign import ccall "HROOT.h TTree_ResetAttMarker" c_ttree_resetattmarker 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_SetMarkerAttributes" c_ttree_setmarkerattributes 
  :: (Ptr RawTTree) -> IO ()
foreign import ccall "HROOT.h TTree_SetMarkerColor" c_ttree_setmarkercolor 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetMarkerStyle" c_ttree_setmarkerstyle 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_SetMarkerSize" c_ttree_setmarkersize 
  :: (Ptr RawTTree) -> CInt -> IO ()
foreign import ccall "HROOT.h TTree_Draw" c_ttree_draw 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_FindObject" c_ttree_findobject 
  :: (Ptr RawTTree) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTree_GetName" c_ttree_getname 
  :: (Ptr RawTTree) -> IO CString
foreign import ccall "HROOT.h TTree_IsA" c_ttree_isa 
  :: (Ptr RawTTree) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TTree_IsFolder" c_ttree_isfolder 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_IsEqual" c_ttree_isequal 
  :: (Ptr RawTTree) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TTree_IsSortable" c_ttree_issortable 
  :: (Ptr RawTTree) -> IO CInt
foreign import ccall "HROOT.h TTree_Paint" c_ttree_paint 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_printObj" c_ttree_printobj 
  :: (Ptr RawTTree) -> CString -> IO ()
foreign import ccall "HROOT.h TTree_RecursiveRemove" c_ttree_recursiveremove 
  :: (Ptr RawTTree) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TTree_SaveAs" c_ttree_saveas 
  :: (Ptr RawTTree) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTree_UseCurrentStyle" c_ttree_usecurrentstyle 
  :: (Ptr RawTTree) -> IO ()
foreign import ccall "HROOT.h TTree_Write" c_ttree_write 
  :: (Ptr RawTTree) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTree_delete" c_ttree_delete 
  :: (Ptr RawTTree) -> IO ()
foreign import ccall "HROOT.h TTree_newTTree" c_ttree_newttree 
  :: CString -> CString -> CInt -> IO (Ptr RawTTree)

foreign import ccall "HROOT.h TChain_SetName" c_tchain_setname 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_SetNameTitle" c_tchain_setnametitle 
  :: (Ptr RawTChain) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TChain_SetTitle" c_tchain_settitle 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_GetLineColor" c_tchain_getlinecolor 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_GetLineStyle" c_tchain_getlinestyle 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_GetLineWidth" c_tchain_getlinewidth 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_ResetAttLine" c_tchain_resetattline 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_SetLineAttributes" c_tchain_setlineattributes 
  :: (Ptr RawTChain) -> IO ()
foreign import ccall "HROOT.h TChain_SetLineColor" c_tchain_setlinecolor 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetLineStyle" c_tchain_setlinestyle 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetLineWidth" c_tchain_setlinewidth 
  :: (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_GetMarkerColor" c_tchain_getmarkercolor 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_GetMarkerStyle" c_tchain_getmarkerstyle 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_GetMarkerSize" c_tchain_getmarkersize 
  :: (Ptr RawTChain) -> IO CDouble
foreign import ccall "HROOT.h TChain_ResetAttMarker" c_tchain_resetattmarker 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_SetMarkerAttributes" c_tchain_setmarkerattributes 
  :: (Ptr RawTChain) -> IO ()
foreign import ccall "HROOT.h TChain_SetMarkerColor" c_tchain_setmarkercolor 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetMarkerStyle" c_tchain_setmarkerstyle 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_SetMarkerSize" c_tchain_setmarkersize 
  :: (Ptr RawTChain) -> CInt -> IO ()
foreign import ccall "HROOT.h TChain_Draw" c_tchain_draw 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_FindObject" c_tchain_findobject 
  :: (Ptr RawTChain) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TChain_GetName" c_tchain_getname 
  :: (Ptr RawTChain) -> IO CString
foreign import ccall "HROOT.h TChain_IsA" c_tchain_isa 
  :: (Ptr RawTChain) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TChain_IsFolder" c_tchain_isfolder 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_IsEqual" c_tchain_isequal 
  :: (Ptr RawTChain) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TChain_IsSortable" c_tchain_issortable 
  :: (Ptr RawTChain) -> IO CInt
foreign import ccall "HROOT.h TChain_Paint" c_tchain_paint 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_printObj" c_tchain_printobj 
  :: (Ptr RawTChain) -> CString -> IO ()
foreign import ccall "HROOT.h TChain_RecursiveRemove" c_tchain_recursiveremove 
  :: (Ptr RawTChain) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TChain_SaveAs" c_tchain_saveas 
  :: (Ptr RawTChain) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TChain_UseCurrentStyle" c_tchain_usecurrentstyle 
  :: (Ptr RawTChain) -> IO ()
foreign import ccall "HROOT.h TChain_Write" c_tchain_write 
  :: (Ptr RawTChain) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TChain_delete" c_tchain_delete 
  :: (Ptr RawTChain) -> IO ()
foreign import ccall "HROOT.h TChain_newTChain" c_tchain_newtchain 
  :: CString -> CString -> IO (Ptr RawTChain)

foreign import ccall "HROOT.h TNtuple_SetName" c_tntuple_setname 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_SetNameTitle" c_tntuple_setnametitle 
  :: (Ptr RawTNtuple) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_SetTitle" c_tntuple_settitle 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_GetLineColor" c_tntuple_getlinecolor 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_GetLineStyle" c_tntuple_getlinestyle 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_GetLineWidth" c_tntuple_getlinewidth 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_ResetAttLine" c_tntuple_resetattline 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_SetLineAttributes" c_tntuple_setlineattributes 
  :: (Ptr RawTNtuple) -> IO ()
foreign import ccall "HROOT.h TNtuple_SetLineColor" c_tntuple_setlinecolor 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetLineStyle" c_tntuple_setlinestyle 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetLineWidth" c_tntuple_setlinewidth 
  :: (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_GetMarkerColor" c_tntuple_getmarkercolor 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_GetMarkerStyle" c_tntuple_getmarkerstyle 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_GetMarkerSize" c_tntuple_getmarkersize 
  :: (Ptr RawTNtuple) -> IO CDouble
foreign import ccall "HROOT.h TNtuple_ResetAttMarker" c_tntuple_resetattmarker 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_SetMarkerAttributes" c_tntuple_setmarkerattributes 
  :: (Ptr RawTNtuple) -> IO ()
foreign import ccall "HROOT.h TNtuple_SetMarkerColor" c_tntuple_setmarkercolor 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetMarkerStyle" c_tntuple_setmarkerstyle 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_SetMarkerSize" c_tntuple_setmarkersize 
  :: (Ptr RawTNtuple) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtuple_Draw" c_tntuple_draw 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_FindObject" c_tntuple_findobject 
  :: (Ptr RawTNtuple) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNtuple_GetName" c_tntuple_getname 
  :: (Ptr RawTNtuple) -> IO CString
foreign import ccall "HROOT.h TNtuple_IsA" c_tntuple_isa 
  :: (Ptr RawTNtuple) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TNtuple_IsFolder" c_tntuple_isfolder 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_IsEqual" c_tntuple_isequal 
  :: (Ptr RawTNtuple) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TNtuple_IsSortable" c_tntuple_issortable 
  :: (Ptr RawTNtuple) -> IO CInt
foreign import ccall "HROOT.h TNtuple_Paint" c_tntuple_paint 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_printObj" c_tntuple_printobj 
  :: (Ptr RawTNtuple) -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_RecursiveRemove" c_tntuple_recursiveremove 
  :: (Ptr RawTNtuple) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TNtuple_SaveAs" c_tntuple_saveas 
  :: (Ptr RawTNtuple) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtuple_UseCurrentStyle" c_tntuple_usecurrentstyle 
  :: (Ptr RawTNtuple) -> IO ()
foreign import ccall "HROOT.h TNtuple_Write" c_tntuple_write 
  :: (Ptr RawTNtuple) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNtuple_delete" c_tntuple_delete 
  :: (Ptr RawTNtuple) -> IO ()
foreign import ccall "HROOT.h TNtuple_newTNtuple" c_tntuple_newtntuple 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTNtuple)

foreign import ccall "HROOT.h TNtupleD_SetName" c_tntupled_setname 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetNameTitle" c_tntupled_setnametitle 
  :: (Ptr RawTNtupleD) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetTitle" c_tntupled_settitle 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_GetLineColor" c_tntupled_getlinecolor 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_GetLineStyle" c_tntupled_getlinestyle 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_GetLineWidth" c_tntupled_getlinewidth 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_ResetAttLine" c_tntupled_resetattline 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetLineAttributes" c_tntupled_setlineattributes 
  :: (Ptr RawTNtupleD) -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetLineColor" c_tntupled_setlinecolor 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetLineStyle" c_tntupled_setlinestyle 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetLineWidth" c_tntupled_setlinewidth 
  :: (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_GetMarkerColor" c_tntupled_getmarkercolor 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_GetMarkerStyle" c_tntupled_getmarkerstyle 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_GetMarkerSize" c_tntupled_getmarkersize 
  :: (Ptr RawTNtupleD) -> IO CDouble
foreign import ccall "HROOT.h TNtupleD_ResetAttMarker" c_tntupled_resetattmarker 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetMarkerAttributes" c_tntupled_setmarkerattributes 
  :: (Ptr RawTNtupleD) -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetMarkerColor" c_tntupled_setmarkercolor 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetMarkerStyle" c_tntupled_setmarkerstyle 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_SetMarkerSize" c_tntupled_setmarkersize 
  :: (Ptr RawTNtupleD) -> CInt -> IO ()
foreign import ccall "HROOT.h TNtupleD_Draw" c_tntupled_draw 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_FindObject" c_tntupled_findobject 
  :: (Ptr RawTNtupleD) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TNtupleD_GetName" c_tntupled_getname 
  :: (Ptr RawTNtupleD) -> IO CString
foreign import ccall "HROOT.h TNtupleD_IsA" c_tntupled_isa 
  :: (Ptr RawTNtupleD) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TNtupleD_IsFolder" c_tntupled_isfolder 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_IsEqual" c_tntupled_isequal 
  :: (Ptr RawTNtupleD) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_IsSortable" c_tntupled_issortable 
  :: (Ptr RawTNtupleD) -> IO CInt
foreign import ccall "HROOT.h TNtupleD_Paint" c_tntupled_paint 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_printObj" c_tntupled_printobj 
  :: (Ptr RawTNtupleD) -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_RecursiveRemove" c_tntupled_recursiveremove 
  :: (Ptr RawTNtupleD) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TNtupleD_SaveAs" c_tntupled_saveas 
  :: (Ptr RawTNtupleD) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TNtupleD_UseCurrentStyle" c_tntupled_usecurrentstyle 
  :: (Ptr RawTNtupleD) -> IO ()
foreign import ccall "HROOT.h TNtupleD_Write" c_tntupled_write 
  :: (Ptr RawTNtupleD) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TNtupleD_delete" c_tntupled_delete 
  :: (Ptr RawTNtupleD) -> IO ()
foreign import ccall "HROOT.h TNtupleD_newTNtupleD" c_tntupled_newtntupled 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTNtupleD)

foreign import ccall "HROOT.h TTreeSQL_SetName" c_ttreesql_setname 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetNameTitle" c_ttreesql_setnametitle 
  :: (Ptr RawTTreeSQL) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetTitle" c_ttreesql_settitle 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_GetLineColor" c_ttreesql_getlinecolor 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_GetLineStyle" c_ttreesql_getlinestyle 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_GetLineWidth" c_ttreesql_getlinewidth 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_ResetAttLine" c_ttreesql_resetattline 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetLineAttributes" c_ttreesql_setlineattributes 
  :: (Ptr RawTTreeSQL) -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetLineColor" c_ttreesql_setlinecolor 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetLineStyle" c_ttreesql_setlinestyle 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetLineWidth" c_ttreesql_setlinewidth 
  :: (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_GetMarkerColor" c_ttreesql_getmarkercolor 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_GetMarkerStyle" c_ttreesql_getmarkerstyle 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_GetMarkerSize" c_ttreesql_getmarkersize 
  :: (Ptr RawTTreeSQL) -> IO CDouble
foreign import ccall "HROOT.h TTreeSQL_ResetAttMarker" c_ttreesql_resetattmarker 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetMarkerAttributes" c_ttreesql_setmarkerattributes 
  :: (Ptr RawTTreeSQL) -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetMarkerColor" c_ttreesql_setmarkercolor 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetMarkerStyle" c_ttreesql_setmarkerstyle 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SetMarkerSize" c_ttreesql_setmarkersize 
  :: (Ptr RawTTreeSQL) -> CInt -> IO ()
foreign import ccall "HROOT.h TTreeSQL_Draw" c_ttreesql_draw 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_FindObject" c_ttreesql_findobject 
  :: (Ptr RawTTreeSQL) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTreeSQL_GetName" c_ttreesql_getname 
  :: (Ptr RawTTreeSQL) -> IO CString
foreign import ccall "HROOT.h TTreeSQL_IsA" c_ttreesql_isa 
  :: (Ptr RawTTreeSQL) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TTreeSQL_IsFolder" c_ttreesql_isfolder 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_IsEqual" c_ttreesql_isequal 
  :: (Ptr RawTTreeSQL) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_IsSortable" c_ttreesql_issortable 
  :: (Ptr RawTTreeSQL) -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_Paint" c_ttreesql_paint 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_printObj" c_ttreesql_printobj 
  :: (Ptr RawTTreeSQL) -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_RecursiveRemove" c_ttreesql_recursiveremove 
  :: (Ptr RawTTreeSQL) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TTreeSQL_SaveAs" c_ttreesql_saveas 
  :: (Ptr RawTTreeSQL) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTreeSQL_UseCurrentStyle" c_ttreesql_usecurrentstyle 
  :: (Ptr RawTTreeSQL) -> IO ()
foreign import ccall "HROOT.h TTreeSQL_Write" c_ttreesql_write 
  :: (Ptr RawTTreeSQL) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTreeSQL_delete" c_ttreesql_delete 
  :: (Ptr RawTTreeSQL) -> IO ()

foreign import ccall "HROOT.h TPolyLine_Draw" c_tpolyline_draw 
  :: (Ptr RawTPolyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_FindObject" c_tpolyline_findobject 
  :: (Ptr RawTPolyLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPolyLine_GetName" c_tpolyline_getname 
  :: (Ptr RawTPolyLine) -> IO CString
foreign import ccall "HROOT.h TPolyLine_IsA" c_tpolyline_isa 
  :: (Ptr RawTPolyLine) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPolyLine_IsFolder" c_tpolyline_isfolder 
  :: (Ptr RawTPolyLine) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_IsEqual" c_tpolyline_isequal 
  :: (Ptr RawTPolyLine) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_IsSortable" c_tpolyline_issortable 
  :: (Ptr RawTPolyLine) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_Paint" c_tpolyline_paint 
  :: (Ptr RawTPolyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_printObj" c_tpolyline_printobj 
  :: (Ptr RawTPolyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_RecursiveRemove" c_tpolyline_recursiveremove 
  :: (Ptr RawTPolyLine) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPolyLine_SaveAs" c_tpolyline_saveas 
  :: (Ptr RawTPolyLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_UseCurrentStyle" c_tpolyline_usecurrentstyle 
  :: (Ptr RawTPolyLine) -> IO ()
foreign import ccall "HROOT.h TPolyLine_Write" c_tpolyline_write 
  :: (Ptr RawTPolyLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPolyLine_GetLineColor" c_tpolyline_getlinecolor 
  :: (Ptr RawTPolyLine) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_GetLineStyle" c_tpolyline_getlinestyle 
  :: (Ptr RawTPolyLine) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_GetLineWidth" c_tpolyline_getlinewidth 
  :: (Ptr RawTPolyLine) -> IO CInt
foreign import ccall "HROOT.h TPolyLine_ResetAttLine" c_tpolyline_resetattline 
  :: (Ptr RawTPolyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetLineAttributes" c_tpolyline_setlineattributes 
  :: (Ptr RawTPolyLine) -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetLineColor" c_tpolyline_setlinecolor 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetLineStyle" c_tpolyline_setlinestyle 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetLineWidth" c_tpolyline_setlinewidth 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetFillColor" c_tpolyline_setfillcolor 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_SetFillStyle" c_tpolyline_setfillstyle 
  :: (Ptr RawTPolyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TPolyLine_delete" c_tpolyline_delete 
  :: (Ptr RawTPolyLine) -> IO ()
foreign import ccall "HROOT.h TPolyLine_newTPolyLine" c_tpolyline_newtpolyline 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO (Ptr RawTPolyLine)

foreign import ccall "HROOT.h TCurlyLine_Draw" c_tcurlyline_draw 
  :: (Ptr RawTCurlyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_FindObject" c_tcurlyline_findobject 
  :: (Ptr RawTCurlyLine) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCurlyLine_GetName" c_tcurlyline_getname 
  :: (Ptr RawTCurlyLine) -> IO CString
foreign import ccall "HROOT.h TCurlyLine_IsA" c_tcurlyline_isa 
  :: (Ptr RawTCurlyLine) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCurlyLine_IsFolder" c_tcurlyline_isfolder 
  :: (Ptr RawTCurlyLine) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_IsEqual" c_tcurlyline_isequal 
  :: (Ptr RawTCurlyLine) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_IsSortable" c_tcurlyline_issortable 
  :: (Ptr RawTCurlyLine) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_Paint" c_tcurlyline_paint 
  :: (Ptr RawTCurlyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_printObj" c_tcurlyline_printobj 
  :: (Ptr RawTCurlyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_RecursiveRemove" c_tcurlyline_recursiveremove 
  :: (Ptr RawTCurlyLine) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SaveAs" c_tcurlyline_saveas 
  :: (Ptr RawTCurlyLine) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_UseCurrentStyle" c_tcurlyline_usecurrentstyle 
  :: (Ptr RawTCurlyLine) -> IO ()
foreign import ccall "HROOT.h TCurlyLine_Write" c_tcurlyline_write 
  :: (Ptr RawTCurlyLine) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_GetLineColor" c_tcurlyline_getlinecolor 
  :: (Ptr RawTCurlyLine) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_GetLineStyle" c_tcurlyline_getlinestyle 
  :: (Ptr RawTCurlyLine) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_GetLineWidth" c_tcurlyline_getlinewidth 
  :: (Ptr RawTCurlyLine) -> IO CInt
foreign import ccall "HROOT.h TCurlyLine_ResetAttLine" c_tcurlyline_resetattline 
  :: (Ptr RawTCurlyLine) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetLineAttributes" c_tcurlyline_setlineattributes 
  :: (Ptr RawTCurlyLine) -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetLineColor" c_tcurlyline_setlinecolor 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetLineStyle" c_tcurlyline_setlinestyle 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetLineWidth" c_tcurlyline_setlinewidth 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetFillColor" c_tcurlyline_setfillcolor 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_SetFillStyle" c_tcurlyline_setfillstyle 
  :: (Ptr RawTCurlyLine) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyLine_delete" c_tcurlyline_delete 
  :: (Ptr RawTCurlyLine) -> IO ()
foreign import ccall "HROOT.h TCurlyLine_newTCurlyLine" c_tcurlyline_newtcurlyline 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCurlyLine)

foreign import ccall "HROOT.h TCurlyArc_Draw" c_tcurlyarc_draw 
  :: (Ptr RawTCurlyArc) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_FindObject" c_tcurlyarc_findobject 
  :: (Ptr RawTCurlyArc) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCurlyArc_GetName" c_tcurlyarc_getname 
  :: (Ptr RawTCurlyArc) -> IO CString
foreign import ccall "HROOT.h TCurlyArc_IsA" c_tcurlyarc_isa 
  :: (Ptr RawTCurlyArc) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCurlyArc_IsFolder" c_tcurlyarc_isfolder 
  :: (Ptr RawTCurlyArc) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_IsEqual" c_tcurlyarc_isequal 
  :: (Ptr RawTCurlyArc) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_IsSortable" c_tcurlyarc_issortable 
  :: (Ptr RawTCurlyArc) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_Paint" c_tcurlyarc_paint 
  :: (Ptr RawTCurlyArc) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_printObj" c_tcurlyarc_printobj 
  :: (Ptr RawTCurlyArc) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_RecursiveRemove" c_tcurlyarc_recursiveremove 
  :: (Ptr RawTCurlyArc) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SaveAs" c_tcurlyarc_saveas 
  :: (Ptr RawTCurlyArc) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_UseCurrentStyle" c_tcurlyarc_usecurrentstyle 
  :: (Ptr RawTCurlyArc) -> IO ()
foreign import ccall "HROOT.h TCurlyArc_Write" c_tcurlyarc_write 
  :: (Ptr RawTCurlyArc) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_GetLineColor" c_tcurlyarc_getlinecolor 
  :: (Ptr RawTCurlyArc) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_GetLineStyle" c_tcurlyarc_getlinestyle 
  :: (Ptr RawTCurlyArc) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_GetLineWidth" c_tcurlyarc_getlinewidth 
  :: (Ptr RawTCurlyArc) -> IO CInt
foreign import ccall "HROOT.h TCurlyArc_ResetAttLine" c_tcurlyarc_resetattline 
  :: (Ptr RawTCurlyArc) -> CString -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetLineAttributes" c_tcurlyarc_setlineattributes 
  :: (Ptr RawTCurlyArc) -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetLineColor" c_tcurlyarc_setlinecolor 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetLineStyle" c_tcurlyarc_setlinestyle 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetLineWidth" c_tcurlyarc_setlinewidth 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetFillColor" c_tcurlyarc_setfillcolor 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_SetFillStyle" c_tcurlyarc_setfillstyle 
  :: (Ptr RawTCurlyArc) -> CInt -> IO ()
foreign import ccall "HROOT.h TCurlyArc_delete" c_tcurlyarc_delete 
  :: (Ptr RawTCurlyArc) -> IO ()
foreign import ccall "HROOT.h TCurlyArc_newTCurlyArc" c_tcurlyarc_newtcurlyarc 
  :: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTCurlyArc)

foreign import ccall "HROOT.h TEfficiency_SetName" c_tefficiency_setname 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetNameTitle" c_tefficiency_setnametitle 
  :: (Ptr RawTEfficiency) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetTitle" c_tefficiency_settitle 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_GetLineColor" c_tefficiency_getlinecolor 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_GetLineStyle" c_tefficiency_getlinestyle 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_GetLineWidth" c_tefficiency_getlinewidth 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_ResetAttLine" c_tefficiency_resetattline 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetLineAttributes" c_tefficiency_setlineattributes 
  :: (Ptr RawTEfficiency) -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetLineColor" c_tefficiency_setlinecolor 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetLineStyle" c_tefficiency_setlinestyle 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetLineWidth" c_tefficiency_setlinewidth 
  :: (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_GetMarkerColor" c_tefficiency_getmarkercolor 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_GetMarkerStyle" c_tefficiency_getmarkerstyle 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_GetMarkerSize" c_tefficiency_getmarkersize 
  :: (Ptr RawTEfficiency) -> IO CDouble
foreign import ccall "HROOT.h TEfficiency_ResetAttMarker" c_tefficiency_resetattmarker 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetMarkerAttributes" c_tefficiency_setmarkerattributes 
  :: (Ptr RawTEfficiency) -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetMarkerColor" c_tefficiency_setmarkercolor 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetMarkerStyle" c_tefficiency_setmarkerstyle 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_SetMarkerSize" c_tefficiency_setmarkersize 
  :: (Ptr RawTEfficiency) -> CInt -> IO ()
foreign import ccall "HROOT.h TEfficiency_Draw" c_tefficiency_draw 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_FindObject" c_tefficiency_findobject 
  :: (Ptr RawTEfficiency) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEfficiency_GetName" c_tefficiency_getname 
  :: (Ptr RawTEfficiency) -> IO CString
foreign import ccall "HROOT.h TEfficiency_IsA" c_tefficiency_isa 
  :: (Ptr RawTEfficiency) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TEfficiency_IsFolder" c_tefficiency_isfolder 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_IsEqual" c_tefficiency_isequal 
  :: (Ptr RawTEfficiency) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_IsSortable" c_tefficiency_issortable 
  :: (Ptr RawTEfficiency) -> IO CInt
foreign import ccall "HROOT.h TEfficiency_Paint" c_tefficiency_paint 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_printObj" c_tefficiency_printobj 
  :: (Ptr RawTEfficiency) -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_RecursiveRemove" c_tefficiency_recursiveremove 
  :: (Ptr RawTEfficiency) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TEfficiency_SaveAs" c_tefficiency_saveas 
  :: (Ptr RawTEfficiency) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEfficiency_UseCurrentStyle" c_tefficiency_usecurrentstyle 
  :: (Ptr RawTEfficiency) -> IO ()
foreign import ccall "HROOT.h TEfficiency_Write" c_tefficiency_write 
  :: (Ptr RawTEfficiency) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEfficiency_delete" c_tefficiency_delete 
  :: (Ptr RawTEfficiency) -> IO ()

foreign import ccall "HROOT.h TAxis_SetName" c_taxis_setname 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_SetNameTitle" c_taxis_setnametitle 
  :: (Ptr RawTAxis) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_SetTitle" c_taxis_settitle 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_GetNdivisions" c_taxis_getndivisions 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_GetAxisColor" c_taxis_getaxiscolor 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_GetLabelColor" c_taxis_getlabelcolor 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_GetLabelFont" c_taxis_getlabelfont 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_GetLabelOffset" c_taxis_getlabeloffset 
  :: (Ptr RawTAxis) -> IO CDouble
foreign import ccall "HROOT.h TAxis_GetLabelSize" c_taxis_getlabelsize 
  :: (Ptr RawTAxis) -> IO CDouble
foreign import ccall "HROOT.h TAxis_GetTitleOffset" c_taxis_gettitleoffset 
  :: (Ptr RawTAxis) -> IO CDouble
foreign import ccall "HROOT.h TAxis_GetTitleSize" c_taxis_gettitlesize 
  :: (Ptr RawTAxis) -> IO CDouble
foreign import ccall "HROOT.h TAxis_GetTickLength" c_taxis_getticklength 
  :: (Ptr RawTAxis) -> IO CDouble
foreign import ccall "HROOT.h TAxis_GetTitleFont" c_taxis_gettitlefont 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_SetNdivisions" c_taxis_setndivisions 
  :: (Ptr RawTAxis) -> CInt -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetAxisColor" c_taxis_setaxiscolor 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetLabelColor" c_taxis_setlabelcolor 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetLabelFont" c_taxis_setlabelfont 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetLabelOffset" c_taxis_setlabeloffset 
  :: (Ptr RawTAxis) -> CDouble -> 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_SetTitleSize" c_taxis_settitlesize 
  :: (Ptr RawTAxis) -> CDouble -> IO ()
foreign import ccall "HROOT.h TAxis_SetTitleColor" c_taxis_settitlecolor 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetTitleFont" c_taxis_settitlefont 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_Draw" c_taxis_draw 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_FindObject" c_taxis_findobject 
  :: (Ptr RawTAxis) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TAxis_GetName" c_taxis_getname 
  :: (Ptr RawTAxis) -> IO CString
foreign import ccall "HROOT.h TAxis_IsA" c_taxis_isa 
  :: (Ptr RawTAxis) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TAxis_IsFolder" c_taxis_isfolder 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_IsEqual" c_taxis_isequal 
  :: (Ptr RawTAxis) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TAxis_IsSortable" c_taxis_issortable 
  :: (Ptr RawTAxis) -> IO CInt
foreign import ccall "HROOT.h TAxis_Paint" c_taxis_paint 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_printObj" c_taxis_printobj 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_RecursiveRemove" c_taxis_recursiveremove 
  :: (Ptr RawTAxis) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TAxis_SaveAs" c_taxis_saveas 
  :: (Ptr RawTAxis) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_UseCurrentStyle" c_taxis_usecurrentstyle 
  :: (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TAxis_Write" c_taxis_write 
  :: (Ptr RawTAxis) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TAxis_delete" c_taxis_delete 
  :: (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TAxis_newTAxis" c_taxis_newtaxis 
  :: CInt -> CDouble -> CDouble -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TAxis_SetTimeDisplay" c_taxis_settimedisplay 
  :: (Ptr RawTAxis) -> CInt -> IO ()
foreign import ccall "HROOT.h TAxis_SetTimeFormat" c_taxis_settimeformat 
  :: (Ptr RawTAxis) -> CString -> IO ()
foreign import ccall "HROOT.h TAxis_SetTimeOffset" c_taxis_settimeoffset 
  :: (Ptr RawTAxis) -> CDouble -> CString -> IO ()

foreign import ccall "HROOT.h TLatex_GetLineColor" c_tlatex_getlinecolor 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_GetLineStyle" c_tlatex_getlinestyle 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_GetLineWidth" c_tlatex_getlinewidth 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_ResetAttLine" c_tlatex_resetattline 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_SetLineAttributes" c_tlatex_setlineattributes 
  :: (Ptr RawTLatex) -> IO ()
foreign import ccall "HROOT.h TLatex_SetLineColor" c_tlatex_setlinecolor 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetLineStyle" c_tlatex_setlinestyle 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetLineWidth" c_tlatex_setlinewidth 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetName" c_tlatex_setname 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_SetNameTitle" c_tlatex_setnametitle 
  :: (Ptr RawTLatex) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_SetTitle" c_tlatex_settitle 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_GetTextAlign" c_tlatex_gettextalign 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_GetTextAngle" c_tlatex_gettextangle 
  :: (Ptr RawTLatex) -> IO CDouble
foreign import ccall "HROOT.h TLatex_GetTextColor" c_tlatex_gettextcolor 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_GetTextFont" c_tlatex_gettextfont 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_GetTextSize" c_tlatex_gettextsize 
  :: (Ptr RawTLatex) -> IO CDouble
foreign import ccall "HROOT.h TLatex_ResetAttText" c_tlatex_resetatttext 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextAttributes" c_tlatex_settextattributes 
  :: (Ptr RawTLatex) -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextAlign" c_tlatex_settextalign 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextAngle" c_tlatex_settextangle 
  :: (Ptr RawTLatex) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextColor" c_tlatex_settextcolor 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextFont" c_tlatex_settextfont 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextSize" c_tlatex_settextsize 
  :: (Ptr RawTLatex) -> CDouble -> IO ()
foreign import ccall "HROOT.h TLatex_SetTextSizePixels" c_tlatex_settextsizepixels 
  :: (Ptr RawTLatex) -> CInt -> IO ()
foreign import ccall "HROOT.h TLatex_Draw" c_tlatex_draw 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_FindObject" c_tlatex_findobject 
  :: (Ptr RawTLatex) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TLatex_GetName" c_tlatex_getname 
  :: (Ptr RawTLatex) -> IO CString
foreign import ccall "HROOT.h TLatex_IsA" c_tlatex_isa 
  :: (Ptr RawTLatex) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TLatex_IsFolder" c_tlatex_isfolder 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_IsEqual" c_tlatex_isequal 
  :: (Ptr RawTLatex) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TLatex_IsSortable" c_tlatex_issortable 
  :: (Ptr RawTLatex) -> IO CInt
foreign import ccall "HROOT.h TLatex_Paint" c_tlatex_paint 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_printObj" c_tlatex_printobj 
  :: (Ptr RawTLatex) -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_RecursiveRemove" c_tlatex_recursiveremove 
  :: (Ptr RawTLatex) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TLatex_SaveAs" c_tlatex_saveas 
  :: (Ptr RawTLatex) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TLatex_UseCurrentStyle" c_tlatex_usecurrentstyle 
  :: (Ptr RawTLatex) -> IO ()
foreign import ccall "HROOT.h TLatex_Write" c_tlatex_write 
  :: (Ptr RawTLatex) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TLatex_delete" c_tlatex_delete 
  :: (Ptr RawTLatex) -> IO ()
foreign import ccall "HROOT.h TLatex_newTLatex" c_tlatex_newtlatex 
  :: CDouble -> CDouble -> CString -> IO (Ptr RawTLatex)
foreign import ccall "HROOT.h TLatex_tLatexDrawLatex" c_tlatex_tlatexdrawlatex 
  :: (Ptr RawTLatex) -> CDouble -> CDouble -> CString -> IO (Ptr RawTLatex)

foreign import ccall "HROOT.h TText_SetName" c_ttext_setname 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_SetNameTitle" c_ttext_setnametitle 
  :: (Ptr RawTText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TText_SetTitle" c_ttext_settitle 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_GetTextAlign" c_ttext_gettextalign 
  :: (Ptr RawTText) -> IO CInt
foreign import ccall "HROOT.h TText_GetTextAngle" c_ttext_gettextangle 
  :: (Ptr RawTText) -> IO CDouble
foreign import ccall "HROOT.h TText_GetTextColor" c_ttext_gettextcolor 
  :: (Ptr RawTText) -> IO CInt
foreign import ccall "HROOT.h TText_GetTextFont" c_ttext_gettextfont 
  :: (Ptr RawTText) -> IO CInt
foreign import ccall "HROOT.h TText_GetTextSize" c_ttext_gettextsize 
  :: (Ptr RawTText) -> IO CDouble
foreign import ccall "HROOT.h TText_ResetAttText" c_ttext_resetatttext 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_SetTextAttributes" c_ttext_settextattributes 
  :: (Ptr RawTText) -> IO ()
foreign import ccall "HROOT.h TText_SetTextAlign" c_ttext_settextalign 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_SetTextAngle" c_ttext_settextangle 
  :: (Ptr RawTText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TText_SetTextColor" c_ttext_settextcolor 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_SetTextFont" c_ttext_settextfont 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_SetTextSize" c_ttext_settextsize 
  :: (Ptr RawTText) -> CDouble -> IO ()
foreign import ccall "HROOT.h TText_SetTextSizePixels" c_ttext_settextsizepixels 
  :: (Ptr RawTText) -> CInt -> IO ()
foreign import ccall "HROOT.h TText_Draw" c_ttext_draw 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_FindObject" c_ttext_findobject 
  :: (Ptr RawTText) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TText_GetName" c_ttext_getname 
  :: (Ptr RawTText) -> IO CString
foreign import ccall "HROOT.h TText_IsA" c_ttext_isa 
  :: (Ptr RawTText) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TText_IsFolder" c_ttext_isfolder 
  :: (Ptr RawTText) -> IO CInt
foreign import ccall "HROOT.h TText_IsEqual" c_ttext_isequal 
  :: (Ptr RawTText) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TText_IsSortable" c_ttext_issortable 
  :: (Ptr RawTText) -> IO CInt
foreign import ccall "HROOT.h TText_Paint" c_ttext_paint 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_printObj" c_ttext_printobj 
  :: (Ptr RawTText) -> CString -> IO ()
foreign import ccall "HROOT.h TText_RecursiveRemove" c_ttext_recursiveremove 
  :: (Ptr RawTText) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TText_SaveAs" c_ttext_saveas 
  :: (Ptr RawTText) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TText_UseCurrentStyle" c_ttext_usecurrentstyle 
  :: (Ptr RawTText) -> IO ()
foreign import ccall "HROOT.h TText_Write" c_ttext_write 
  :: (Ptr RawTText) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TText_delete" c_ttext_delete 
  :: (Ptr RawTText) -> IO ()

foreign import ccall "HROOT.h TDirectory_SetName" c_tdirectory_setname 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_SetNameTitle" c_tdirectory_setnametitle 
  :: (Ptr RawTDirectory) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_SetTitle" c_tdirectory_settitle 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_Draw" c_tdirectory_draw 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_FindObject" c_tdirectory_findobject 
  :: (Ptr RawTDirectory) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDirectory_GetName" c_tdirectory_getname 
  :: (Ptr RawTDirectory) -> IO CString
foreign import ccall "HROOT.h TDirectory_IsA" c_tdirectory_isa 
  :: (Ptr RawTDirectory) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TDirectory_IsFolder" c_tdirectory_isfolder 
  :: (Ptr RawTDirectory) -> IO CInt
foreign import ccall "HROOT.h TDirectory_IsEqual" c_tdirectory_isequal 
  :: (Ptr RawTDirectory) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TDirectory_IsSortable" c_tdirectory_issortable 
  :: (Ptr RawTDirectory) -> IO CInt
foreign import ccall "HROOT.h TDirectory_Paint" c_tdirectory_paint 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_printObj" c_tdirectory_printobj 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_RecursiveRemove" c_tdirectory_recursiveremove 
  :: (Ptr RawTDirectory) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TDirectory_SaveAs" c_tdirectory_saveas 
  :: (Ptr RawTDirectory) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_UseCurrentStyle" c_tdirectory_usecurrentstyle 
  :: (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TDirectory_Write" c_tdirectory_write 
  :: (Ptr RawTDirectory) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDirectory_delete" c_tdirectory_delete 
  :: (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TDirectory_Append" c_tdirectory_append 
  :: (Ptr RawTDirectory) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TDirectory_addD" c_tdirectory_addd 
  :: (Ptr RawTDirectory) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TDirectory_AppendKey" c_tdirectory_appendkey 
  :: (Ptr RawTDirectory) -> (Ptr RawTKey) -> IO CInt
foreign import ccall "HROOT.h TDirectory_Close" c_tdirectory_close 
  :: (Ptr RawTDirectory) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectory_Get" c_tdirectory_get 
  :: (Ptr RawTDirectory) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOT.h TDirectoryFile_Append" c_tdirectoryfile_append 
  :: (Ptr RawTDirectoryFile) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_addD" c_tdirectoryfile_addd 
  :: (Ptr RawTDirectoryFile) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_AppendKey" c_tdirectoryfile_appendkey 
  :: (Ptr RawTDirectoryFile) -> (Ptr RawTKey) -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_Close" c_tdirectoryfile_close 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_Get" c_tdirectoryfile_get 
  :: (Ptr RawTDirectoryFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDirectoryFile_SetName" c_tdirectoryfile_setname 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_SetNameTitle" c_tdirectoryfile_setnametitle 
  :: (Ptr RawTDirectoryFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_SetTitle" c_tdirectoryfile_settitle 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_Draw" c_tdirectoryfile_draw 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_FindObject" c_tdirectoryfile_findobject 
  :: (Ptr RawTDirectoryFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDirectoryFile_GetName" c_tdirectoryfile_getname 
  :: (Ptr RawTDirectoryFile) -> IO CString
foreign import ccall "HROOT.h TDirectoryFile_IsA" c_tdirectoryfile_isa 
  :: (Ptr RawTDirectoryFile) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TDirectoryFile_IsFolder" c_tdirectoryfile_isfolder 
  :: (Ptr RawTDirectoryFile) -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_IsEqual" c_tdirectoryfile_isequal 
  :: (Ptr RawTDirectoryFile) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_IsSortable" c_tdirectoryfile_issortable 
  :: (Ptr RawTDirectoryFile) -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_Paint" c_tdirectoryfile_paint 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_printObj" c_tdirectoryfile_printobj 
  :: (Ptr RawTDirectoryFile) -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_RecursiveRemove" c_tdirectoryfile_recursiveremove 
  :: (Ptr RawTDirectoryFile) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_SaveAs" c_tdirectoryfile_saveas 
  :: (Ptr RawTDirectoryFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_UseCurrentStyle" c_tdirectoryfile_usecurrentstyle 
  :: (Ptr RawTDirectoryFile) -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_Write" c_tdirectoryfile_write 
  :: (Ptr RawTDirectoryFile) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDirectoryFile_delete" c_tdirectoryfile_delete 
  :: (Ptr RawTDirectoryFile) -> IO ()
foreign import ccall "HROOT.h TDirectoryFile_GetListOfKeys" c_tdirectoryfile_getlistofkeys 
  :: (Ptr RawTDirectoryFile) -> IO (Ptr RawTList)

foreign import ccall "HROOT.h TFile_GetListOfKeys" c_tfile_getlistofkeys 
  :: (Ptr RawTFile) -> IO (Ptr RawTList)
foreign import ccall "HROOT.h TFile_Append" c_tfile_append 
  :: (Ptr RawTFile) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TFile_addD" c_tfile_addd 
  :: (Ptr RawTFile) -> (Ptr RawTObject) -> CInt -> IO ()
foreign import ccall "HROOT.h TFile_AppendKey" c_tfile_appendkey 
  :: (Ptr RawTFile) -> (Ptr RawTKey) -> IO CInt
foreign import ccall "HROOT.h TFile_Close" c_tfile_close 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_Get" c_tfile_get 
  :: (Ptr RawTFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFile_SetName" c_tfile_setname 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_SetNameTitle" c_tfile_setnametitle 
  :: (Ptr RawTFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFile_SetTitle" c_tfile_settitle 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_Draw" c_tfile_draw 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_FindObject" c_tfile_findobject 
  :: (Ptr RawTFile) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TFile_GetName" c_tfile_getname 
  :: (Ptr RawTFile) -> IO CString
foreign import ccall "HROOT.h TFile_IsA" c_tfile_isa 
  :: (Ptr RawTFile) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TFile_IsFolder" c_tfile_isfolder 
  :: (Ptr RawTFile) -> IO CInt
foreign import ccall "HROOT.h TFile_IsEqual" c_tfile_isequal 
  :: (Ptr RawTFile) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TFile_IsSortable" c_tfile_issortable 
  :: (Ptr RawTFile) -> IO CInt
foreign import ccall "HROOT.h TFile_Paint" c_tfile_paint 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_printObj" c_tfile_printobj 
  :: (Ptr RawTFile) -> CString -> IO ()
foreign import ccall "HROOT.h TFile_RecursiveRemove" c_tfile_recursiveremove 
  :: (Ptr RawTFile) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TFile_SaveAs" c_tfile_saveas 
  :: (Ptr RawTFile) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TFile_UseCurrentStyle" c_tfile_usecurrentstyle 
  :: (Ptr RawTFile) -> IO ()
foreign import ccall "HROOT.h TFile_Write" c_tfile_write 
  :: (Ptr RawTFile) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TFile_delete" c_tfile_delete 
  :: (Ptr RawTFile) -> IO ()
foreign import ccall "HROOT.h TFile_newTFile" c_tfile_newtfile 
  :: CString -> CString -> CString -> CInt -> IO (Ptr RawTFile)

foreign import ccall "HROOT.h TBranch_SetName" c_tbranch_setname 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_SetNameTitle" c_tbranch_setnametitle 
  :: (Ptr RawTBranch) -> CString -> CString -> IO ()
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_Draw" c_tbranch_draw 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_FindObject" c_tbranch_findobject 
  :: (Ptr RawTBranch) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TBranch_GetName" c_tbranch_getname 
  :: (Ptr RawTBranch) -> IO CString
foreign import ccall "HROOT.h TBranch_IsA" c_tbranch_isa 
  :: (Ptr RawTBranch) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TBranch_IsFolder" c_tbranch_isfolder 
  :: (Ptr RawTBranch) -> IO CInt
foreign import ccall "HROOT.h TBranch_IsEqual" c_tbranch_isequal 
  :: (Ptr RawTBranch) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TBranch_IsSortable" c_tbranch_issortable 
  :: (Ptr RawTBranch) -> IO CInt
foreign import ccall "HROOT.h TBranch_Paint" c_tbranch_paint 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_printObj" c_tbranch_printobj 
  :: (Ptr RawTBranch) -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_RecursiveRemove" c_tbranch_recursiveremove 
  :: (Ptr RawTBranch) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TBranch_SaveAs" c_tbranch_saveas 
  :: (Ptr RawTBranch) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TBranch_UseCurrentStyle" c_tbranch_usecurrentstyle 
  :: (Ptr RawTBranch) -> IO ()
foreign import ccall "HROOT.h TBranch_Write" c_tbranch_write 
  :: (Ptr RawTBranch) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TBranch_delete" c_tbranch_delete 
  :: (Ptr RawTBranch) -> IO ()

foreign import ccall "HROOT.h TVirtualTreePlayer_Draw" c_tvirtualtreeplayer_draw 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_FindObject" c_tvirtualtreeplayer_findobject 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TVirtualTreePlayer_GetName" c_tvirtualtreeplayer_getname 
  :: (Ptr RawTVirtualTreePlayer) -> IO CString
foreign import ccall "HROOT.h TVirtualTreePlayer_IsA" c_tvirtualtreeplayer_isa 
  :: (Ptr RawTVirtualTreePlayer) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TVirtualTreePlayer_IsFolder" c_tvirtualtreeplayer_isfolder 
  :: (Ptr RawTVirtualTreePlayer) -> IO CInt
foreign import ccall "HROOT.h TVirtualTreePlayer_IsEqual" c_tvirtualtreeplayer_isequal 
  :: (Ptr RawTVirtualTreePlayer) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TVirtualTreePlayer_IsSortable" c_tvirtualtreeplayer_issortable 
  :: (Ptr RawTVirtualTreePlayer) -> IO CInt
foreign import ccall "HROOT.h TVirtualTreePlayer_Paint" c_tvirtualtreeplayer_paint 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_printObj" c_tvirtualtreeplayer_printobj 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_RecursiveRemove" c_tvirtualtreeplayer_recursiveremove 
  :: (Ptr RawTVirtualTreePlayer) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_SaveAs" c_tvirtualtreeplayer_saveas 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_UseCurrentStyle" c_tvirtualtreeplayer_usecurrentstyle 
  :: (Ptr RawTVirtualTreePlayer) -> IO ()
foreign import ccall "HROOT.h TVirtualTreePlayer_Write" c_tvirtualtreeplayer_write 
  :: (Ptr RawTVirtualTreePlayer) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TVirtualTreePlayer_delete" c_tvirtualtreeplayer_delete 
  :: (Ptr RawTVirtualTreePlayer) -> IO ()

foreign import ccall "HROOT.h TTreePlayer_Draw" c_ttreeplayer_draw 
  :: (Ptr RawTTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_FindObject" c_ttreeplayer_findobject 
  :: (Ptr RawTTreePlayer) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TTreePlayer_GetName" c_ttreeplayer_getname 
  :: (Ptr RawTTreePlayer) -> IO CString
foreign import ccall "HROOT.h TTreePlayer_IsA" c_ttreeplayer_isa 
  :: (Ptr RawTTreePlayer) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TTreePlayer_IsFolder" c_ttreeplayer_isfolder 
  :: (Ptr RawTTreePlayer) -> IO CInt
foreign import ccall "HROOT.h TTreePlayer_IsEqual" c_ttreeplayer_isequal 
  :: (Ptr RawTTreePlayer) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TTreePlayer_IsSortable" c_ttreeplayer_issortable 
  :: (Ptr RawTTreePlayer) -> IO CInt
foreign import ccall "HROOT.h TTreePlayer_Paint" c_ttreeplayer_paint 
  :: (Ptr RawTTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_printObj" c_ttreeplayer_printobj 
  :: (Ptr RawTTreePlayer) -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_RecursiveRemove" c_ttreeplayer_recursiveremove 
  :: (Ptr RawTTreePlayer) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TTreePlayer_SaveAs" c_ttreeplayer_saveas 
  :: (Ptr RawTTreePlayer) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TTreePlayer_UseCurrentStyle" c_ttreeplayer_usecurrentstyle 
  :: (Ptr RawTTreePlayer) -> IO ()
foreign import ccall "HROOT.h TTreePlayer_Write" c_ttreeplayer_write 
  :: (Ptr RawTTreePlayer) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TTreePlayer_delete" c_ttreeplayer_delete 
  :: (Ptr RawTTreePlayer) -> IO ()

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

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

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

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

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

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

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

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

foreign import ccall "HROOT.h TH1_SetName" c_th1_setname 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetNameTitle" c_th1_setnametitle 
  :: (Ptr RawTH1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetTitle" c_th1_settitle 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_GetLineColor" c_th1_getlinecolor 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetLineStyle" c_th1_getlinestyle 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetLineWidth" c_th1_getlinewidth 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_ResetAttLine" c_th1_resetattline 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetLineAttributes" c_th1_setlineattributes 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_SetLineColor" c_th1_setlinecolor 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetLineStyle" c_th1_setlinestyle 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetLineWidth" c_th1_setlinewidth 
  :: (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_GetMarkerColor" c_th1_getmarkercolor 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetMarkerStyle" c_th1_getmarkerstyle 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetMarkerSize" c_th1_getmarkersize 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_ResetAttMarker" c_th1_resetattmarker 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetMarkerAttributes" c_th1_setmarkerattributes 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_SetMarkerColor" c_th1_setmarkercolor 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetMarkerStyle" c_th1_setmarkerstyle 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetMarkerSize" c_th1_setmarkersize 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_Draw" c_th1_draw 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_FindObject" c_th1_findobject 
  :: (Ptr RawTH1) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1_GetName" c_th1_getname 
  :: (Ptr RawTH1) -> IO CString
foreign import ccall "HROOT.h TH1_IsA" c_th1_isa 
  :: (Ptr RawTH1) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1_IsFolder" c_th1_isfolder 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_IsEqual" c_th1_isequal 
  :: (Ptr RawTH1) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1_IsSortable" c_th1_issortable 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_Paint" c_th1_paint 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_printObj" c_th1_printobj 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_RecursiveRemove" c_th1_recursiveremove 
  :: (Ptr RawTH1) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1_SaveAs" c_th1_saveas 
  :: (Ptr RawTH1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1_UseCurrentStyle" c_th1_usecurrentstyle 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_Write" c_th1_write 
  :: (Ptr RawTH1) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_delete" c_th1_delete 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_Add" c_th1_add 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_AddBinContent" c_th1_addbincontent 
  :: (Ptr RawTH1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_Chi2Test" c_th1_chi2test 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1_ComputeIntegral" c_th1_computeintegral 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_DirectoryAutoAdd" c_th1_directoryautoadd 
  :: (Ptr RawTH1) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1_Divide" c_th1_divide 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_drawCopyTH1" c_th1_drawcopyth1 
  :: (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_DrawNormalized" c_th1_drawnormalized 
  :: (Ptr RawTH1) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_drawPanelTH1" c_th1_drawpanelth1 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_BufferEmpty" c_th1_bufferempty 
  :: (Ptr RawTH1) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_evalF" c_th1_evalf 
  :: (Ptr RawTH1) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_FFT" c_th1_fft 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_fill1" c_th1_fill1 
  :: (Ptr RawTH1) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_fill1w" c_th1_fill1w 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_fillN1" c_th1_filln1 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_FillRandom" c_th1_fillrandom 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_FindBin" c_th1_findbin 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_FindFixBin" c_th1_findfixbin 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_FindFirstBinAbove" c_th1_findfirstbinabove 
  :: (Ptr RawTH1) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_FindLastBinAbove" c_th1_findlastbinabove 
  :: (Ptr RawTH1) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_FitPanelTH1" c_th1_fitpanelth1 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_tH1GetAsymmetry" c_th1_th1getasymmetry 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_tH1GetBufferLength" c_th1_th1getbufferlength 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_tH1GetBufferSize" c_th1_th1getbuffersize 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_getNdivisionA" c_th1_getndivisiona 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_getAxisColorA" c_th1_getaxiscolora 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_getLabelColorA" c_th1_getlabelcolora 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_getLabelFontA" c_th1_getlabelfonta 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_getLabelOffsetA" c_th1_getlabeloffseta 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_getLabelSizeA" c_th1_getlabelsizea 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_getTitleFontA" c_th1_gettitlefonta 
  :: (Ptr RawTH1) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1_getTitleOffsetA" c_th1_gettitleoffseta 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_getTitleSizeA" c_th1_gettitlesizea 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_getTickLengthA" c_th1_getticklengtha 
  :: (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBarOffset" c_th1_getbaroffset 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBarWidth" c_th1_getbarwidth 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetContour" c_th1_getcontour 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1_GetContourLevel" c_th1_getcontourlevel 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetContourLevelPad" c_th1_getcontourlevelpad 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBin" c_th1_getbin 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_GetBinCenter" c_th1_getbincenter 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent1" c_th1_getbincontent1 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent2" c_th1_getbincontent2 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinContent3" c_th1_getbincontent3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError1" c_th1_getbinerror1 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError2" c_th1_getbinerror2 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinError3" c_th1_getbinerror3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinLowEdge" c_th1_getbinlowedge 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetBinWidth" c_th1_getbinwidth 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetCellContent" c_th1_getcellcontent 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetCellError" c_th1_getcellerror 
  :: (Ptr RawTH1) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_tH1GetDirectory" c_th1_th1getdirectory 
  :: (Ptr RawTH1) -> IO (Ptr RawTDirectory)
foreign import ccall "HROOT.h TH1_GetEntries" c_th1_getentries 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetEffectiveEntries" c_th1_geteffectiveentries 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetFunction" c_th1_getfunction 
  :: (Ptr RawTH1) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1_GetDimension" c_th1_getdimension 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetKurtosis" c_th1_getkurtosis 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetLowEdge" c_th1_getlowedge 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_getMaximumTH1" c_th1_getmaximumth1 
  :: (Ptr RawTH1) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1_GetMaximumBin" c_th1_getmaximumbin 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetMaximumStored" c_th1_getmaximumstored 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_getMinimumTH1" c_th1_getminimumth1 
  :: (Ptr RawTH1) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1_GetMinimumBin" c_th1_getminimumbin 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetMinimumStored" c_th1_getminimumstored 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetMean" c_th1_getmean 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetMeanError" c_th1_getmeanerror 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetNbinsX" c_th1_getnbinsx 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetNbinsY" c_th1_getnbinsy 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetNbinsZ" c_th1_getnbinsz 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_getQuantilesTH1" c_th1_getquantilesth1 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1_GetRandom" c_th1_getrandom 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetStats" c_th1_getstats 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_GetSumOfWeights" c_th1_getsumofweights 
  :: (Ptr RawTH1) -> IO CDouble
foreign import ccall "HROOT.h TH1_GetSumw2" c_th1_getsumw2 
  :: (Ptr RawTH1) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1_GetSumw2N" c_th1_getsumw2n 
  :: (Ptr RawTH1) -> IO CInt
foreign import ccall "HROOT.h TH1_GetRMS" c_th1_getrms 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetRMSError" c_th1_getrmserror 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_GetSkewness" c_th1_getskewness 
  :: (Ptr RawTH1) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1_tH1GetXaxis" c_th1_th1getxaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_tH1GetYaxis" c_th1_th1getyaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_tH1GetZaxis" c_th1_th1getzaxis 
  :: (Ptr RawTH1) -> IO (Ptr RawTAxis)
foreign import ccall "HROOT.h TH1_integral1" c_th1_integral1 
  :: (Ptr RawTH1) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_interpolate1" c_th1_interpolate1 
  :: (Ptr RawTH1) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1_interpolate2" c_th1_interpolate2 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1_interpolate3" c_th1_interpolate3 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1_tH1IsBinOverflow" c_th1_th1isbinoverflow 
  :: (Ptr RawTH1) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_tH1IsBinUnderflow" c_th1_th1isbinunderflow 
  :: (Ptr RawTH1) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1_KolmogorovTest" c_th1_kolmogorovtest 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1_LabelsDeflate" c_th1_labelsdeflate 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_LabelsInflate" c_th1_labelsinflate 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_LabelsOption" c_th1_labelsoption 
  :: (Ptr RawTH1) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1_multiflyF" c_th1_multiflyf 
  :: (Ptr RawTH1) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_Multiply" c_th1_multiply 
  :: (Ptr RawTH1) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_PutStats" c_th1_putstats 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_Rebin" c_th1_rebin 
  :: (Ptr RawTH1) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_RebinAxis" c_th1_rebinaxis 
  :: (Ptr RawTH1) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1_Rebuild" c_th1_rebuild 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_Reset" c_th1_reset 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_ResetStats" c_th1_resetstats 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_Scale" c_th1_scale 
  :: (Ptr RawTH1) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_setAxisColorA" c_th1_setaxiscolora 
  :: (Ptr RawTH1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetAxisRange" c_th1_setaxisrange 
  :: (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetBarOffset" c_th1_setbaroffset 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetBarWidth" c_th1_setbarwidth 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinContent1" c_th1_setbincontent1 
  :: (Ptr RawTH1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinContent2" c_th1_setbincontent2 
  :: (Ptr RawTH1) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinContent3" c_th1_setbincontent3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinError1" c_th1_setbinerror1 
  :: (Ptr RawTH1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinError2" c_th1_setbinerror2 
  :: (Ptr RawTH1) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBinError3" c_th1_setbinerror3 
  :: (Ptr RawTH1) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_setBins1" c_th1_setbins1 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_setBins2" c_th1_setbins2 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_setBins3" c_th1_setbins3 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_SetBinsLength" c_th1_setbinslength 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetBuffer" c_th1_setbuffer 
  :: (Ptr RawTH1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetCellContent" c_th1_setcellcontent 
  :: (Ptr RawTH1) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetContent" c_th1_setcontent 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_SetContour" c_th1_setcontour 
  :: (Ptr RawTH1) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_SetContourLevel" c_th1_setcontourlevel 
  :: (Ptr RawTH1) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetDirectory" c_th1_setdirectory 
  :: (Ptr RawTH1) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1_SetEntries" c_th1_setentries 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetError" c_th1_seterror 
  :: (Ptr RawTH1) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1_setLabelColorA" c_th1_setlabelcolora 
  :: (Ptr RawTH1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1_setLabelSizeA" c_th1_setlabelsizea 
  :: (Ptr RawTH1) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_setLabelFontA" c_th1_setlabelfonta 
  :: (Ptr RawTH1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1_setLabelOffsetA" c_th1_setlabeloffseta 
  :: (Ptr RawTH1) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetMaximum" c_th1_setmaximum 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetMinimum" c_th1_setminimum 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetNormFactor" c_th1_setnormfactor 
  :: (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1_SetStats" c_th1_setstats 
  :: (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1_SetOption" c_th1_setoption 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetXTitle" c_th1_setxtitle 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetYTitle" c_th1_setytitle 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_SetZTitle" c_th1_setztitle 
  :: (Ptr RawTH1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1_ShowBackground" c_th1_showbackground 
  :: (Ptr RawTH1) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1_ShowPeaks" c_th1_showpeaks 
  :: (Ptr RawTH1) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1_Smooth" c_th1_smooth 
  :: (Ptr RawTH1) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1_Sumw2" c_th1_sumw2 
  :: (Ptr RawTH1) -> IO ()
foreign import ccall "HROOT.h TH1_tH1UseCurrentStyle" c_th1_th1usecurrentstyle 
  :: (Ptr RawTH1) -> IO ()

foreign import ccall "HROOT.h TH2_Add" c_th2_add 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_AddBinContent" c_th2_addbincontent 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_Chi2Test" c_th2_chi2test 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2_ComputeIntegral" c_th2_computeintegral 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_DirectoryAutoAdd" c_th2_directoryautoadd 
  :: (Ptr RawTH2) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2_Divide" c_th2_divide 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_drawCopyTH1" c_th2_drawcopyth1 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2_DrawNormalized" c_th2_drawnormalized 
  :: (Ptr RawTH2) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_drawPanelTH1" c_th2_drawpanelth1 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_BufferEmpty" c_th2_bufferempty 
  :: (Ptr RawTH2) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_evalF" c_th2_evalf 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_FFT" c_th2_fft 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_fill1" c_th2_fill1 
  :: (Ptr RawTH2) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_fill1w" c_th2_fill1w 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_fillN1" c_th2_filln1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_FillRandom" c_th2_fillrandom 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_FindBin" c_th2_findbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_FindFixBin" c_th2_findfixbin 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_FindFirstBinAbove" c_th2_findfirstbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_FindLastBinAbove" c_th2_findlastbinabove 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_FitPanelTH1" c_th2_fitpanelth1 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_getNdivisionA" c_th2_getndivisiona 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_getAxisColorA" c_th2_getaxiscolora 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_getLabelColorA" c_th2_getlabelcolora 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_getLabelFontA" c_th2_getlabelfonta 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_getLabelOffsetA" c_th2_getlabeloffseta 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_getLabelSizeA" c_th2_getlabelsizea 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_getTitleFontA" c_th2_gettitlefonta 
  :: (Ptr RawTH2) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2_getTitleOffsetA" c_th2_gettitleoffseta 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_getTitleSizeA" c_th2_gettitlesizea 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_getTickLengthA" c_th2_getticklengtha 
  :: (Ptr RawTH2) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBarOffset" c_th2_getbaroffset 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBarWidth" c_th2_getbarwidth 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetContour" c_th2_getcontour 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2_GetContourLevel" c_th2_getcontourlevel 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetContourLevelPad" c_th2_getcontourlevelpad 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBin" c_th2_getbin 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_GetBinCenter" c_th2_getbincenter 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent1" c_th2_getbincontent1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent2" c_th2_getbincontent2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinContent3" c_th2_getbincontent3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError1" c_th2_getbinerror1 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError2" c_th2_getbinerror2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinError3" c_th2_getbinerror3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinLowEdge" c_th2_getbinlowedge 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetBinWidth" c_th2_getbinwidth 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetCellContent" c_th2_getcellcontent 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetCellError" c_th2_getcellerror 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetEntries" c_th2_getentries 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetEffectiveEntries" c_th2_geteffectiveentries 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetFunction" c_th2_getfunction 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2_GetDimension" c_th2_getdimension 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetKurtosis" c_th2_getkurtosis 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetLowEdge" c_th2_getlowedge 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_getMaximumTH1" c_th2_getmaximumth1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2_GetMaximumBin" c_th2_getmaximumbin 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetMaximumStored" c_th2_getmaximumstored 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_getMinimumTH1" c_th2_getminimumth1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2_GetMinimumBin" c_th2_getminimumbin 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetMinimumStored" c_th2_getminimumstored 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetMean" c_th2_getmean 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetMeanError" c_th2_getmeanerror 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetNbinsX" c_th2_getnbinsx 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetNbinsY" c_th2_getnbinsy 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetNbinsZ" c_th2_getnbinsz 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_getQuantilesTH1" c_th2_getquantilesth1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2_GetRandom" c_th2_getrandom 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetStats" c_th2_getstats 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_GetSumOfWeights" c_th2_getsumofweights 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_GetSumw2" c_th2_getsumw2 
  :: (Ptr RawTH2) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2_GetSumw2N" c_th2_getsumw2n 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetRMS" c_th2_getrms 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetRMSError" c_th2_getrmserror 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_GetSkewness" c_th2_getskewness 
  :: (Ptr RawTH2) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_integral1" c_th2_integral1 
  :: (Ptr RawTH2) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_interpolate1" c_th2_interpolate1 
  :: (Ptr RawTH2) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2_interpolate2" c_th2_interpolate2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2_interpolate3" c_th2_interpolate3 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2_KolmogorovTest" c_th2_kolmogorovtest 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_LabelsDeflate" c_th2_labelsdeflate 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_LabelsInflate" c_th2_labelsinflate 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_LabelsOption" c_th2_labelsoption 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2_multiflyF" c_th2_multiflyf 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_Multiply" c_th2_multiply 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_PutStats" c_th2_putstats 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_Rebin" c_th2_rebin 
  :: (Ptr RawTH2) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_RebinAxis" c_th2_rebinaxis 
  :: (Ptr RawTH2) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2_Rebuild" c_th2_rebuild 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_Reset" c_th2_reset 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_ResetStats" c_th2_resetstats 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_Scale" c_th2_scale 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_setAxisColorA" c_th2_setaxiscolora 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetAxisRange" c_th2_setaxisrange 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetBarOffset" c_th2_setbaroffset 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetBarWidth" c_th2_setbarwidth 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinContent1" c_th2_setbincontent1 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinContent2" c_th2_setbincontent2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinContent3" c_th2_setbincontent3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinError1" c_th2_setbinerror1 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinError2" c_th2_setbinerror2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBinError3" c_th2_setbinerror3 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_setBins1" c_th2_setbins1 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_setBins2" c_th2_setbins2 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_setBins3" c_th2_setbins3 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_SetBinsLength" c_th2_setbinslength 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetBuffer" c_th2_setbuffer 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetCellContent" c_th2_setcellcontent 
  :: (Ptr RawTH2) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetContent" c_th2_setcontent 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_SetContour" c_th2_setcontour 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_SetContourLevel" c_th2_setcontourlevel 
  :: (Ptr RawTH2) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetDirectory" c_th2_setdirectory 
  :: (Ptr RawTH2) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2_SetEntries" c_th2_setentries 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetError" c_th2_seterror 
  :: (Ptr RawTH2) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2_setLabelColorA" c_th2_setlabelcolora 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2_setLabelSizeA" c_th2_setlabelsizea 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_setLabelFontA" c_th2_setlabelfonta 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2_setLabelOffsetA" c_th2_setlabeloffseta 
  :: (Ptr RawTH2) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetMaximum" c_th2_setmaximum 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetMinimum" c_th2_setminimum 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetNormFactor" c_th2_setnormfactor 
  :: (Ptr RawTH2) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2_SetStats" c_th2_setstats 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetOption" c_th2_setoption 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetXTitle" c_th2_setxtitle 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetYTitle" c_th2_setytitle 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetZTitle" c_th2_setztitle 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_ShowBackground" c_th2_showbackground 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2_ShowPeaks" c_th2_showpeaks 
  :: (Ptr RawTH2) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_Smooth" c_th2_smooth 
  :: (Ptr RawTH2) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2_Sumw2" c_th2_sumw2 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_SetName" c_th2_setname 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetNameTitle" c_th2_setnametitle 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetTitle" c_th2_settitle 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_GetLineColor" c_th2_getlinecolor 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetLineStyle" c_th2_getlinestyle 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetLineWidth" c_th2_getlinewidth 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_ResetAttLine" c_th2_resetattline 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetLineAttributes" c_th2_setlineattributes 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_SetLineColor" c_th2_setlinecolor 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetLineStyle" c_th2_setlinestyle 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetLineWidth" c_th2_setlinewidth 
  :: (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_GetMarkerColor" c_th2_getmarkercolor 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetMarkerStyle" c_th2_getmarkerstyle 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_GetMarkerSize" c_th2_getmarkersize 
  :: (Ptr RawTH2) -> IO CDouble
foreign import ccall "HROOT.h TH2_ResetAttMarker" c_th2_resetattmarker 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_SetMarkerAttributes" c_th2_setmarkerattributes 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_SetMarkerColor" c_th2_setmarkercolor 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetMarkerStyle" c_th2_setmarkerstyle 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetMarkerSize" c_th2_setmarkersize 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_Draw" c_th2_draw 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_FindObject" c_th2_findobject 
  :: (Ptr RawTH2) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2_GetName" c_th2_getname 
  :: (Ptr RawTH2) -> IO CString
foreign import ccall "HROOT.h TH2_IsA" c_th2_isa 
  :: (Ptr RawTH2) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2_IsFolder" c_th2_isfolder 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_IsEqual" c_th2_isequal 
  :: (Ptr RawTH2) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2_IsSortable" c_th2_issortable 
  :: (Ptr RawTH2) -> IO CInt
foreign import ccall "HROOT.h TH2_Paint" c_th2_paint 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_printObj" c_th2_printobj 
  :: (Ptr RawTH2) -> CString -> IO ()
foreign import ccall "HROOT.h TH2_RecursiveRemove" c_th2_recursiveremove 
  :: (Ptr RawTH2) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2_SaveAs" c_th2_saveas 
  :: (Ptr RawTH2) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2_UseCurrentStyle" c_th2_usecurrentstyle 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_Write" c_th2_write 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_delete" c_th2_delete 
  :: (Ptr RawTH2) -> IO ()
foreign import ccall "HROOT.h TH2_fill2" c_th2_fill2 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_fill2w" c_th2_fill2w 
  :: (Ptr RawTH2) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2_fillN2" c_th2_filln2 
  :: (Ptr RawTH2) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_fillRandom2" c_th2_fillrandom2 
  :: (Ptr RawTH2) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_findFirstBinAbove2" c_th2_findfirstbinabove2 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_findLastBinAbove2" c_th2_findlastbinabove2 
  :: (Ptr RawTH2) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2_FitSlicesX" c_th2_fitslicesx 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2_FitSlicesY" c_th2_fitslicesy 
  :: (Ptr RawTH2) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2_getCorrelationFactor2" c_th2_getcorrelationfactor2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_getCovariance2" c_th2_getcovariance2 
  :: (Ptr RawTH2) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2_integral2" c_th2_integral2 
  :: (Ptr RawTH2) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2_tH2ProjectionX" c_th2_th2projectionx 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH2_tH2ProjectionY" c_th2_th2projectiony 
  :: (Ptr RawTH2) -> CString -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH2_rebinX2" c_th2_rebinx2 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2_rebinY2" c_th2_rebiny2 
  :: (Ptr RawTH2) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2_Rebin2D" c_th2_rebin2d 
  :: (Ptr RawTH2) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2_SetShowProjectionX" c_th2_setshowprojectionx 
  :: (Ptr RawTH2) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2_SetShowProjectionY" c_th2_setshowprojectiony 
  :: (Ptr RawTH2) -> CInt -> IO ()

foreign import ccall "HROOT.h TH3_Add" c_th3_add 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_AddBinContent" c_th3_addbincontent 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_Chi2Test" c_th3_chi2test 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3_ComputeIntegral" c_th3_computeintegral 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_DirectoryAutoAdd" c_th3_directoryautoadd 
  :: (Ptr RawTH3) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3_Divide" c_th3_divide 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_drawCopyTH1" c_th3_drawcopyth1 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3_DrawNormalized" c_th3_drawnormalized 
  :: (Ptr RawTH3) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_drawPanelTH1" c_th3_drawpanelth1 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_BufferEmpty" c_th3_bufferempty 
  :: (Ptr RawTH3) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_evalF" c_th3_evalf 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_FFT" c_th3_fft 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_fill1" c_th3_fill1 
  :: (Ptr RawTH3) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_fill1w" c_th3_fill1w 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_fillN1" c_th3_filln1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_FillRandom" c_th3_fillrandom 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_FindBin" c_th3_findbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FindFixBin" c_th3_findfixbin 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FindFirstBinAbove" c_th3_findfirstbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_FindLastBinAbove" c_th3_findlastbinabove 
  :: (Ptr RawTH3) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_FitPanelTH1" c_th3_fitpanelth1 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_getNdivisionA" c_th3_getndivisiona 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_getAxisColorA" c_th3_getaxiscolora 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_getLabelColorA" c_th3_getlabelcolora 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_getLabelFontA" c_th3_getlabelfonta 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_getLabelOffsetA" c_th3_getlabeloffseta 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_getLabelSizeA" c_th3_getlabelsizea 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_getTitleFontA" c_th3_gettitlefonta 
  :: (Ptr RawTH3) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3_getTitleOffsetA" c_th3_gettitleoffseta 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_getTitleSizeA" c_th3_gettitlesizea 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_getTickLengthA" c_th3_getticklengtha 
  :: (Ptr RawTH3) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBarOffset" c_th3_getbaroffset 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBarWidth" c_th3_getbarwidth 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetContour" c_th3_getcontour 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3_GetContourLevel" c_th3_getcontourlevel 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetContourLevelPad" c_th3_getcontourlevelpad 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBin" c_th3_getbin 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_GetBinCenter" c_th3_getbincenter 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent1" c_th3_getbincontent1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent2" c_th3_getbincontent2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinContent3" c_th3_getbincontent3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError1" c_th3_getbinerror1 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError2" c_th3_getbinerror2 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinError3" c_th3_getbinerror3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinLowEdge" c_th3_getbinlowedge 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetBinWidth" c_th3_getbinwidth 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetCellContent" c_th3_getcellcontent 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetCellError" c_th3_getcellerror 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetEntries" c_th3_getentries 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetEffectiveEntries" c_th3_geteffectiveentries 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetFunction" c_th3_getfunction 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3_GetDimension" c_th3_getdimension 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetKurtosis" c_th3_getkurtosis 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetLowEdge" c_th3_getlowedge 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_getMaximumTH1" c_th3_getmaximumth1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3_GetMaximumBin" c_th3_getmaximumbin 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetMaximumStored" c_th3_getmaximumstored 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_getMinimumTH1" c_th3_getminimumth1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3_GetMinimumBin" c_th3_getminimumbin 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetMinimumStored" c_th3_getminimumstored 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetMean" c_th3_getmean 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetMeanError" c_th3_getmeanerror 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetNbinsX" c_th3_getnbinsx 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetNbinsY" c_th3_getnbinsy 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetNbinsZ" c_th3_getnbinsz 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_getQuantilesTH1" c_th3_getquantilesth1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3_GetRandom" c_th3_getrandom 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetStats" c_th3_getstats 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_GetSumOfWeights" c_th3_getsumofweights 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_GetSumw2" c_th3_getsumw2 
  :: (Ptr RawTH3) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3_GetSumw2N" c_th3_getsumw2n 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetRMS" c_th3_getrms 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetRMSError" c_th3_getrmserror 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_GetSkewness" c_th3_getskewness 
  :: (Ptr RawTH3) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_integral1" c_th3_integral1 
  :: (Ptr RawTH3) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_interpolate1" c_th3_interpolate1 
  :: (Ptr RawTH3) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3_interpolate2" c_th3_interpolate2 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3_interpolate3" c_th3_interpolate3 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3_KolmogorovTest" c_th3_kolmogorovtest 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3_LabelsDeflate" c_th3_labelsdeflate 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_LabelsInflate" c_th3_labelsinflate 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_LabelsOption" c_th3_labelsoption 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3_multiflyF" c_th3_multiflyf 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_Multiply" c_th3_multiply 
  :: (Ptr RawTH3) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_PutStats" c_th3_putstats 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_Rebin" c_th3_rebin 
  :: (Ptr RawTH3) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_RebinAxis" c_th3_rebinaxis 
  :: (Ptr RawTH3) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3_Rebuild" c_th3_rebuild 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_Reset" c_th3_reset 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_ResetStats" c_th3_resetstats 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_Scale" c_th3_scale 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_setAxisColorA" c_th3_setaxiscolora 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetAxisRange" c_th3_setaxisrange 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetBarOffset" c_th3_setbaroffset 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetBarWidth" c_th3_setbarwidth 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinContent1" c_th3_setbincontent1 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinContent2" c_th3_setbincontent2 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinContent3" c_th3_setbincontent3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinError1" c_th3_setbinerror1 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinError2" c_th3_setbinerror2 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBinError3" c_th3_setbinerror3 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_setBins1" c_th3_setbins1 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_setBins2" c_th3_setbins2 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_setBins3" c_th3_setbins3 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_SetBinsLength" c_th3_setbinslength 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetBuffer" c_th3_setbuffer 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetCellContent" c_th3_setcellcontent 
  :: (Ptr RawTH3) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetContent" c_th3_setcontent 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_SetContour" c_th3_setcontour 
  :: (Ptr RawTH3) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_SetContourLevel" c_th3_setcontourlevel 
  :: (Ptr RawTH3) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetDirectory" c_th3_setdirectory 
  :: (Ptr RawTH3) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3_SetEntries" c_th3_setentries 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetError" c_th3_seterror 
  :: (Ptr RawTH3) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3_setLabelColorA" c_th3_setlabelcolora 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_setLabelSizeA" c_th3_setlabelsizea 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_setLabelFontA" c_th3_setlabelfonta 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_setLabelOffsetA" c_th3_setlabeloffseta 
  :: (Ptr RawTH3) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetMaximum" c_th3_setmaximum 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetMinimum" c_th3_setminimum 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetNormFactor" c_th3_setnormfactor 
  :: (Ptr RawTH3) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3_SetStats" c_th3_setstats 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetOption" c_th3_setoption 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetXTitle" c_th3_setxtitle 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetYTitle" c_th3_setytitle 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetZTitle" c_th3_setztitle 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_ShowBackground" c_th3_showbackground 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_ShowPeaks" c_th3_showpeaks 
  :: (Ptr RawTH3) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_Smooth" c_th3_smooth 
  :: (Ptr RawTH3) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_Sumw2" c_th3_sumw2 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_SetName" c_th3_setname 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetNameTitle" c_th3_setnametitle 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetTitle" c_th3_settitle 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_GetLineColor" c_th3_getlinecolor 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetLineStyle" c_th3_getlinestyle 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetLineWidth" c_th3_getlinewidth 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_ResetAttLine" c_th3_resetattline 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetLineAttributes" c_th3_setlineattributes 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_SetLineColor" c_th3_setlinecolor 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetLineStyle" c_th3_setlinestyle 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetLineWidth" c_th3_setlinewidth 
  :: (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_GetMarkerColor" c_th3_getmarkercolor 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetMarkerStyle" c_th3_getmarkerstyle 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_GetMarkerSize" c_th3_getmarkersize 
  :: (Ptr RawTH3) -> IO CDouble
foreign import ccall "HROOT.h TH3_ResetAttMarker" c_th3_resetattmarker 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_SetMarkerAttributes" c_th3_setmarkerattributes 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_SetMarkerColor" c_th3_setmarkercolor 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetMarkerStyle" c_th3_setmarkerstyle 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_SetMarkerSize" c_th3_setmarkersize 
  :: (Ptr RawTH3) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3_Draw" c_th3_draw 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_FindObject" c_th3_findobject 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3_GetName" c_th3_getname 
  :: (Ptr RawTH3) -> IO CString
foreign import ccall "HROOT.h TH3_IsA" c_th3_isa 
  :: (Ptr RawTH3) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3_IsFolder" c_th3_isfolder 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_IsEqual" c_th3_isequal 
  :: (Ptr RawTH3) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3_IsSortable" c_th3_issortable 
  :: (Ptr RawTH3) -> IO CInt
foreign import ccall "HROOT.h TH3_Paint" c_th3_paint 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_printObj" c_th3_printobj 
  :: (Ptr RawTH3) -> CString -> IO ()
foreign import ccall "HROOT.h TH3_RecursiveRemove" c_th3_recursiveremove 
  :: (Ptr RawTH3) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3_SaveAs" c_th3_saveas 
  :: (Ptr RawTH3) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3_UseCurrentStyle" c_th3_usecurrentstyle 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_Write" c_th3_write 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3_delete" c_th3_delete 
  :: (Ptr RawTH3) -> IO ()
foreign import ccall "HROOT.h TH3_fill3" c_th3_fill3 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_fill3w" c_th3_fill3w 
  :: (Ptr RawTH3) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3_FitSlicesZ" c_th3_fitslicesz 
  :: (Ptr RawTH3) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3_getCorrelationFactor3" c_th3_getcorrelationfactor3 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_getCovariance3" c_th3_getcovariance3 
  :: (Ptr RawTH3) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3_tH3ProjectionX" c_th3_th3projectionx 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH3_tH3ProjectionY" c_th3_th3projectiony 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH3_tH3ProjectionZ" c_th3_th3projectionz 
  :: (Ptr RawTH3) -> CString -> CInt -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH3_tH3Project3D" c_th3_th3project3d 
  :: (Ptr RawTH3) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3_rebinX3" c_th3_rebinx3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3_rebinY3" c_th3_rebiny3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3_rebinZ3" c_th3_rebinz3 
  :: (Ptr RawTH3) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3_Rebin3D" c_th3_rebin3d 
  :: (Ptr RawTH3) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)

foreign import ccall "HROOT.h TH1C_Add" c_th1c_add 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_AddBinContent" c_th1c_addbincontent 
  :: (Ptr RawTH1C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_Chi2Test" c_th1c_chi2test 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1C_ComputeIntegral" c_th1c_computeintegral 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_DirectoryAutoAdd" c_th1c_directoryautoadd 
  :: (Ptr RawTH1C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1C_Divide" c_th1c_divide 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_drawCopyTH1" c_th1c_drawcopyth1 
  :: (Ptr RawTH1C) -> CString -> IO (Ptr RawTH1C)
foreign import ccall "HROOT.h TH1C_DrawNormalized" c_th1c_drawnormalized 
  :: (Ptr RawTH1C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_drawPanelTH1" c_th1c_drawpanelth1 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_BufferEmpty" c_th1c_bufferempty 
  :: (Ptr RawTH1C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_evalF" c_th1c_evalf 
  :: (Ptr RawTH1C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_FFT" c_th1c_fft 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_fill1" c_th1c_fill1 
  :: (Ptr RawTH1C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_fill1w" c_th1c_fill1w 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_fillN1" c_th1c_filln1 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_FillRandom" c_th1c_fillrandom 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_FindBin" c_th1c_findbin 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_FindFixBin" c_th1c_findfixbin 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_FindFirstBinAbove" c_th1c_findfirstbinabove 
  :: (Ptr RawTH1C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_FindLastBinAbove" c_th1c_findlastbinabove 
  :: (Ptr RawTH1C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_FitPanelTH1" c_th1c_fitpanelth1 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_getNdivisionA" c_th1c_getndivisiona 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_getAxisColorA" c_th1c_getaxiscolora 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_getLabelColorA" c_th1c_getlabelcolora 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_getLabelFontA" c_th1c_getlabelfonta 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_getLabelOffsetA" c_th1c_getlabeloffseta 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_getLabelSizeA" c_th1c_getlabelsizea 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_getTitleFontA" c_th1c_gettitlefonta 
  :: (Ptr RawTH1C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1C_getTitleOffsetA" c_th1c_gettitleoffseta 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_getTitleSizeA" c_th1c_gettitlesizea 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_getTickLengthA" c_th1c_getticklengtha 
  :: (Ptr RawTH1C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBarOffset" c_th1c_getbaroffset 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBarWidth" c_th1c_getbarwidth 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetContour" c_th1c_getcontour 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetContourLevel" c_th1c_getcontourlevel 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetContourLevelPad" c_th1c_getcontourlevelpad 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBin" c_th1c_getbin 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_GetBinCenter" c_th1c_getbincenter 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent1" c_th1c_getbincontent1 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent2" c_th1c_getbincontent2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinContent3" c_th1c_getbincontent3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError1" c_th1c_getbinerror1 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError2" c_th1c_getbinerror2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinError3" c_th1c_getbinerror3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinLowEdge" c_th1c_getbinlowedge 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetBinWidth" c_th1c_getbinwidth 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetCellContent" c_th1c_getcellcontent 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetCellError" c_th1c_getcellerror 
  :: (Ptr RawTH1C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetEntries" c_th1c_getentries 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetEffectiveEntries" c_th1c_geteffectiveentries 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetFunction" c_th1c_getfunction 
  :: (Ptr RawTH1C) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1C_GetDimension" c_th1c_getdimension 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetKurtosis" c_th1c_getkurtosis 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetLowEdge" c_th1c_getlowedge 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_getMaximumTH1" c_th1c_getmaximumth1 
  :: (Ptr RawTH1C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetMaximumBin" c_th1c_getmaximumbin 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetMaximumStored" c_th1c_getmaximumstored 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_getMinimumTH1" c_th1c_getminimumth1 
  :: (Ptr RawTH1C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetMinimumBin" c_th1c_getminimumbin 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetMinimumStored" c_th1c_getminimumstored 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetMean" c_th1c_getmean 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetMeanError" c_th1c_getmeanerror 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetNbinsX" c_th1c_getnbinsx 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetNbinsY" c_th1c_getnbinsy 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetNbinsZ" c_th1c_getnbinsz 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_getQuantilesTH1" c_th1c_getquantilesth1 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetRandom" c_th1c_getrandom 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetStats" c_th1c_getstats 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_GetSumOfWeights" c_th1c_getsumofweights 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetSumw2" c_th1c_getsumw2 
  :: (Ptr RawTH1C) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1C_GetSumw2N" c_th1c_getsumw2n 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetRMS" c_th1c_getrms 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetRMSError" c_th1c_getrmserror 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_GetSkewness" c_th1c_getskewness 
  :: (Ptr RawTH1C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1C_integral1" c_th1c_integral1 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_interpolate1" c_th1c_interpolate1 
  :: (Ptr RawTH1C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1C_interpolate2" c_th1c_interpolate2 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1C_interpolate3" c_th1c_interpolate3 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1C_KolmogorovTest" c_th1c_kolmogorovtest 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1C_LabelsDeflate" c_th1c_labelsdeflate 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_LabelsInflate" c_th1c_labelsinflate 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_LabelsOption" c_th1c_labelsoption 
  :: (Ptr RawTH1C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_multiflyF" c_th1c_multiflyf 
  :: (Ptr RawTH1C) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_Multiply" c_th1c_multiply 
  :: (Ptr RawTH1C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_PutStats" c_th1c_putstats 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_Rebin" c_th1c_rebin 
  :: (Ptr RawTH1C) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_RebinAxis" c_th1c_rebinaxis 
  :: (Ptr RawTH1C) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1C_Rebuild" c_th1c_rebuild 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_Reset" c_th1c_reset 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_ResetStats" c_th1c_resetstats 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_Scale" c_th1c_scale 
  :: (Ptr RawTH1C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_setAxisColorA" c_th1c_setaxiscolora 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetAxisRange" c_th1c_setaxisrange 
  :: (Ptr RawTH1C) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetBarOffset" c_th1c_setbaroffset 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetBarWidth" c_th1c_setbarwidth 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinContent1" c_th1c_setbincontent1 
  :: (Ptr RawTH1C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinContent2" c_th1c_setbincontent2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinContent3" c_th1c_setbincontent3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinError1" c_th1c_setbinerror1 
  :: (Ptr RawTH1C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinError2" c_th1c_setbinerror2 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBinError3" c_th1c_setbinerror3 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_setBins1" c_th1c_setbins1 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_setBins2" c_th1c_setbins2 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_setBins3" c_th1c_setbins3 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_SetBinsLength" c_th1c_setbinslength 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetBuffer" c_th1c_setbuffer 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetCellContent" c_th1c_setcellcontent 
  :: (Ptr RawTH1C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetContent" c_th1c_setcontent 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_SetContour" c_th1c_setcontour 
  :: (Ptr RawTH1C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_SetContourLevel" c_th1c_setcontourlevel 
  :: (Ptr RawTH1C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetDirectory" c_th1c_setdirectory 
  :: (Ptr RawTH1C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1C_SetEntries" c_th1c_setentries 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetError" c_th1c_seterror 
  :: (Ptr RawTH1C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1C_setLabelColorA" c_th1c_setlabelcolora 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_setLabelSizeA" c_th1c_setlabelsizea 
  :: (Ptr RawTH1C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_setLabelFontA" c_th1c_setlabelfonta 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_setLabelOffsetA" c_th1c_setlabeloffseta 
  :: (Ptr RawTH1C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetMaximum" c_th1c_setmaximum 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetMinimum" c_th1c_setminimum 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetNormFactor" c_th1c_setnormfactor 
  :: (Ptr RawTH1C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1C_SetStats" c_th1c_setstats 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetOption" c_th1c_setoption 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetXTitle" c_th1c_setxtitle 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetYTitle" c_th1c_setytitle 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetZTitle" c_th1c_setztitle 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_ShowBackground" c_th1c_showbackground 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1C_ShowPeaks" c_th1c_showpeaks 
  :: (Ptr RawTH1C) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1C_Smooth" c_th1c_smooth 
  :: (Ptr RawTH1C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_Sumw2" c_th1c_sumw2 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_SetName" c_th1c_setname 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetNameTitle" c_th1c_setnametitle 
  :: (Ptr RawTH1C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetTitle" c_th1c_settitle 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_GetLineColor" c_th1c_getlinecolor 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetLineStyle" c_th1c_getlinestyle 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetLineWidth" c_th1c_getlinewidth 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_ResetAttLine" c_th1c_resetattline 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetLineAttributes" c_th1c_setlineattributes 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_SetLineColor" c_th1c_setlinecolor 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetLineStyle" c_th1c_setlinestyle 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetLineWidth" c_th1c_setlinewidth 
  :: (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_GetMarkerColor" c_th1c_getmarkercolor 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetMarkerStyle" c_th1c_getmarkerstyle 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_GetMarkerSize" c_th1c_getmarkersize 
  :: (Ptr RawTH1C) -> IO CDouble
foreign import ccall "HROOT.h TH1C_ResetAttMarker" c_th1c_resetattmarker 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_SetMarkerAttributes" c_th1c_setmarkerattributes 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_SetMarkerColor" c_th1c_setmarkercolor 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetMarkerStyle" c_th1c_setmarkerstyle 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_SetMarkerSize" c_th1c_setmarkersize 
  :: (Ptr RawTH1C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1C_Draw" c_th1c_draw 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_FindObject" c_th1c_findobject 
  :: (Ptr RawTH1C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1C_GetName" c_th1c_getname 
  :: (Ptr RawTH1C) -> IO CString
foreign import ccall "HROOT.h TH1C_IsA" c_th1c_isa 
  :: (Ptr RawTH1C) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1C_IsFolder" c_th1c_isfolder 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_IsEqual" c_th1c_isequal 
  :: (Ptr RawTH1C) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1C_IsSortable" c_th1c_issortable 
  :: (Ptr RawTH1C) -> IO CInt
foreign import ccall "HROOT.h TH1C_Paint" c_th1c_paint 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_printObj" c_th1c_printobj 
  :: (Ptr RawTH1C) -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_RecursiveRemove" c_th1c_recursiveremove 
  :: (Ptr RawTH1C) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1C_SaveAs" c_th1c_saveas 
  :: (Ptr RawTH1C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1C_UseCurrentStyle" c_th1c_usecurrentstyle 
  :: (Ptr RawTH1C) -> IO ()
foreign import ccall "HROOT.h TH1C_Write" c_th1c_write 
  :: (Ptr RawTH1C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1C_delete" c_th1c_delete 
  :: (Ptr RawTH1C) -> IO ()

foreign import ccall "HROOT.h TH1D_Add" c_th1d_add 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_AddBinContent" c_th1d_addbincontent 
  :: (Ptr RawTH1D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_Chi2Test" c_th1d_chi2test 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1D_ComputeIntegral" c_th1d_computeintegral 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_DirectoryAutoAdd" c_th1d_directoryautoadd 
  :: (Ptr RawTH1D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1D_Divide" c_th1d_divide 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_drawCopyTH1" c_th1d_drawcopyth1 
  :: (Ptr RawTH1D) -> CString -> IO (Ptr RawTH1D)
foreign import ccall "HROOT.h TH1D_DrawNormalized" c_th1d_drawnormalized 
  :: (Ptr RawTH1D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_drawPanelTH1" c_th1d_drawpanelth1 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_BufferEmpty" c_th1d_bufferempty 
  :: (Ptr RawTH1D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_evalF" c_th1d_evalf 
  :: (Ptr RawTH1D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_FFT" c_th1d_fft 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_fill1" c_th1d_fill1 
  :: (Ptr RawTH1D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_fill1w" c_th1d_fill1w 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_fillN1" c_th1d_filln1 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_FillRandom" c_th1d_fillrandom 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_FindBin" c_th1d_findbin 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_FindFixBin" c_th1d_findfixbin 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_FindFirstBinAbove" c_th1d_findfirstbinabove 
  :: (Ptr RawTH1D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_FindLastBinAbove" c_th1d_findlastbinabove 
  :: (Ptr RawTH1D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_FitPanelTH1" c_th1d_fitpanelth1 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_getNdivisionA" c_th1d_getndivisiona 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_getAxisColorA" c_th1d_getaxiscolora 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_getLabelColorA" c_th1d_getlabelcolora 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_getLabelFontA" c_th1d_getlabelfonta 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_getLabelOffsetA" c_th1d_getlabeloffseta 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_getLabelSizeA" c_th1d_getlabelsizea 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_getTitleFontA" c_th1d_gettitlefonta 
  :: (Ptr RawTH1D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1D_getTitleOffsetA" c_th1d_gettitleoffseta 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_getTitleSizeA" c_th1d_gettitlesizea 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_getTickLengthA" c_th1d_getticklengtha 
  :: (Ptr RawTH1D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBarOffset" c_th1d_getbaroffset 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBarWidth" c_th1d_getbarwidth 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetContour" c_th1d_getcontour 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetContourLevel" c_th1d_getcontourlevel 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetContourLevelPad" c_th1d_getcontourlevelpad 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBin" c_th1d_getbin 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_GetBinCenter" c_th1d_getbincenter 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent1" c_th1d_getbincontent1 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent2" c_th1d_getbincontent2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinContent3" c_th1d_getbincontent3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError1" c_th1d_getbinerror1 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError2" c_th1d_getbinerror2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinError3" c_th1d_getbinerror3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinLowEdge" c_th1d_getbinlowedge 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetBinWidth" c_th1d_getbinwidth 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetCellContent" c_th1d_getcellcontent 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetCellError" c_th1d_getcellerror 
  :: (Ptr RawTH1D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetEntries" c_th1d_getentries 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetEffectiveEntries" c_th1d_geteffectiveentries 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetFunction" c_th1d_getfunction 
  :: (Ptr RawTH1D) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1D_GetDimension" c_th1d_getdimension 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetKurtosis" c_th1d_getkurtosis 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetLowEdge" c_th1d_getlowedge 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_getMaximumTH1" c_th1d_getmaximumth1 
  :: (Ptr RawTH1D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetMaximumBin" c_th1d_getmaximumbin 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetMaximumStored" c_th1d_getmaximumstored 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_getMinimumTH1" c_th1d_getminimumth1 
  :: (Ptr RawTH1D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetMinimumBin" c_th1d_getminimumbin 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetMinimumStored" c_th1d_getminimumstored 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetMean" c_th1d_getmean 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetMeanError" c_th1d_getmeanerror 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetNbinsX" c_th1d_getnbinsx 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetNbinsY" c_th1d_getnbinsy 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetNbinsZ" c_th1d_getnbinsz 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_getQuantilesTH1" c_th1d_getquantilesth1 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetRandom" c_th1d_getrandom 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetStats" c_th1d_getstats 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_GetSumOfWeights" c_th1d_getsumofweights 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetSumw2" c_th1d_getsumw2 
  :: (Ptr RawTH1D) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1D_GetSumw2N" c_th1d_getsumw2n 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetRMS" c_th1d_getrms 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetRMSError" c_th1d_getrmserror 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_GetSkewness" c_th1d_getskewness 
  :: (Ptr RawTH1D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1D_integral1" c_th1d_integral1 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_interpolate1" c_th1d_interpolate1 
  :: (Ptr RawTH1D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1D_interpolate2" c_th1d_interpolate2 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1D_interpolate3" c_th1d_interpolate3 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1D_KolmogorovTest" c_th1d_kolmogorovtest 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1D_LabelsDeflate" c_th1d_labelsdeflate 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_LabelsInflate" c_th1d_labelsinflate 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_LabelsOption" c_th1d_labelsoption 
  :: (Ptr RawTH1D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_multiflyF" c_th1d_multiflyf 
  :: (Ptr RawTH1D) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_Multiply" c_th1d_multiply 
  :: (Ptr RawTH1D) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_PutStats" c_th1d_putstats 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_Rebin" c_th1d_rebin 
  :: (Ptr RawTH1D) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_RebinAxis" c_th1d_rebinaxis 
  :: (Ptr RawTH1D) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1D_Rebuild" c_th1d_rebuild 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_Reset" c_th1d_reset 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_ResetStats" c_th1d_resetstats 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_Scale" c_th1d_scale 
  :: (Ptr RawTH1D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_setAxisColorA" c_th1d_setaxiscolora 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetAxisRange" c_th1d_setaxisrange 
  :: (Ptr RawTH1D) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetBarOffset" c_th1d_setbaroffset 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetBarWidth" c_th1d_setbarwidth 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinContent1" c_th1d_setbincontent1 
  :: (Ptr RawTH1D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinContent2" c_th1d_setbincontent2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinContent3" c_th1d_setbincontent3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinError1" c_th1d_setbinerror1 
  :: (Ptr RawTH1D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinError2" c_th1d_setbinerror2 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBinError3" c_th1d_setbinerror3 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_setBins1" c_th1d_setbins1 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_setBins2" c_th1d_setbins2 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_setBins3" c_th1d_setbins3 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_SetBinsLength" c_th1d_setbinslength 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetBuffer" c_th1d_setbuffer 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetCellContent" c_th1d_setcellcontent 
  :: (Ptr RawTH1D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetContent" c_th1d_setcontent 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_SetContour" c_th1d_setcontour 
  :: (Ptr RawTH1D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_SetContourLevel" c_th1d_setcontourlevel 
  :: (Ptr RawTH1D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetDirectory" c_th1d_setdirectory 
  :: (Ptr RawTH1D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1D_SetEntries" c_th1d_setentries 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetError" c_th1d_seterror 
  :: (Ptr RawTH1D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1D_setLabelColorA" c_th1d_setlabelcolora 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_setLabelSizeA" c_th1d_setlabelsizea 
  :: (Ptr RawTH1D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_setLabelFontA" c_th1d_setlabelfonta 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_setLabelOffsetA" c_th1d_setlabeloffseta 
  :: (Ptr RawTH1D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetMaximum" c_th1d_setmaximum 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetMinimum" c_th1d_setminimum 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetNormFactor" c_th1d_setnormfactor 
  :: (Ptr RawTH1D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1D_SetStats" c_th1d_setstats 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetOption" c_th1d_setoption 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetXTitle" c_th1d_setxtitle 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetYTitle" c_th1d_setytitle 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetZTitle" c_th1d_setztitle 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_ShowBackground" c_th1d_showbackground 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1D_ShowPeaks" c_th1d_showpeaks 
  :: (Ptr RawTH1D) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1D_Smooth" c_th1d_smooth 
  :: (Ptr RawTH1D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_Sumw2" c_th1d_sumw2 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_SetName" c_th1d_setname 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetNameTitle" c_th1d_setnametitle 
  :: (Ptr RawTH1D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetTitle" c_th1d_settitle 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_GetLineColor" c_th1d_getlinecolor 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetLineStyle" c_th1d_getlinestyle 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetLineWidth" c_th1d_getlinewidth 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_ResetAttLine" c_th1d_resetattline 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetLineAttributes" c_th1d_setlineattributes 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_SetLineColor" c_th1d_setlinecolor 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetLineStyle" c_th1d_setlinestyle 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetLineWidth" c_th1d_setlinewidth 
  :: (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_GetMarkerColor" c_th1d_getmarkercolor 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetMarkerStyle" c_th1d_getmarkerstyle 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_GetMarkerSize" c_th1d_getmarkersize 
  :: (Ptr RawTH1D) -> IO CDouble
foreign import ccall "HROOT.h TH1D_ResetAttMarker" c_th1d_resetattmarker 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_SetMarkerAttributes" c_th1d_setmarkerattributes 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_SetMarkerColor" c_th1d_setmarkercolor 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetMarkerStyle" c_th1d_setmarkerstyle 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_SetMarkerSize" c_th1d_setmarkersize 
  :: (Ptr RawTH1D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1D_Draw" c_th1d_draw 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_FindObject" c_th1d_findobject 
  :: (Ptr RawTH1D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1D_GetName" c_th1d_getname 
  :: (Ptr RawTH1D) -> IO CString
foreign import ccall "HROOT.h TH1D_IsA" c_th1d_isa 
  :: (Ptr RawTH1D) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1D_IsFolder" c_th1d_isfolder 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_IsEqual" c_th1d_isequal 
  :: (Ptr RawTH1D) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1D_IsSortable" c_th1d_issortable 
  :: (Ptr RawTH1D) -> IO CInt
foreign import ccall "HROOT.h TH1D_Paint" c_th1d_paint 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_printObj" c_th1d_printobj 
  :: (Ptr RawTH1D) -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_RecursiveRemove" c_th1d_recursiveremove 
  :: (Ptr RawTH1D) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1D_SaveAs" c_th1d_saveas 
  :: (Ptr RawTH1D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1D_UseCurrentStyle" c_th1d_usecurrentstyle 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_Write" c_th1d_write 
  :: (Ptr RawTH1D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1D_delete" c_th1d_delete 
  :: (Ptr RawTH1D) -> IO ()
foreign import ccall "HROOT.h TH1D_newTH1D" c_th1d_newth1d 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1D)

foreign import ccall "HROOT.h TH1F_Add" c_th1f_add 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_AddBinContent" c_th1f_addbincontent 
  :: (Ptr RawTH1F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_Chi2Test" c_th1f_chi2test 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1F_ComputeIntegral" c_th1f_computeintegral 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_DirectoryAutoAdd" c_th1f_directoryautoadd 
  :: (Ptr RawTH1F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1F_Divide" c_th1f_divide 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_drawCopyTH1" c_th1f_drawcopyth1 
  :: (Ptr RawTH1F) -> CString -> IO (Ptr RawTH1F)
foreign import ccall "HROOT.h TH1F_DrawNormalized" c_th1f_drawnormalized 
  :: (Ptr RawTH1F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_drawPanelTH1" c_th1f_drawpanelth1 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_BufferEmpty" c_th1f_bufferempty 
  :: (Ptr RawTH1F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_evalF" c_th1f_evalf 
  :: (Ptr RawTH1F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_FFT" c_th1f_fft 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_fill1" c_th1f_fill1 
  :: (Ptr RawTH1F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_fill1w" c_th1f_fill1w 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_fillN1" c_th1f_filln1 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_FillRandom" c_th1f_fillrandom 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_FindBin" c_th1f_findbin 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_FindFixBin" c_th1f_findfixbin 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_FindFirstBinAbove" c_th1f_findfirstbinabove 
  :: (Ptr RawTH1F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_FindLastBinAbove" c_th1f_findlastbinabove 
  :: (Ptr RawTH1F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_FitPanelTH1" c_th1f_fitpanelth1 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_getNdivisionA" c_th1f_getndivisiona 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_getAxisColorA" c_th1f_getaxiscolora 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_getLabelColorA" c_th1f_getlabelcolora 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_getLabelFontA" c_th1f_getlabelfonta 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_getLabelOffsetA" c_th1f_getlabeloffseta 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_getLabelSizeA" c_th1f_getlabelsizea 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_getTitleFontA" c_th1f_gettitlefonta 
  :: (Ptr RawTH1F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1F_getTitleOffsetA" c_th1f_gettitleoffseta 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_getTitleSizeA" c_th1f_gettitlesizea 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_getTickLengthA" c_th1f_getticklengtha 
  :: (Ptr RawTH1F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBarOffset" c_th1f_getbaroffset 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBarWidth" c_th1f_getbarwidth 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetContour" c_th1f_getcontour 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetContourLevel" c_th1f_getcontourlevel 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetContourLevelPad" c_th1f_getcontourlevelpad 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBin" c_th1f_getbin 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_GetBinCenter" c_th1f_getbincenter 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent1" c_th1f_getbincontent1 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent2" c_th1f_getbincontent2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinContent3" c_th1f_getbincontent3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError1" c_th1f_getbinerror1 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError2" c_th1f_getbinerror2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinError3" c_th1f_getbinerror3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinLowEdge" c_th1f_getbinlowedge 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetBinWidth" c_th1f_getbinwidth 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetCellContent" c_th1f_getcellcontent 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetCellError" c_th1f_getcellerror 
  :: (Ptr RawTH1F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetEntries" c_th1f_getentries 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetEffectiveEntries" c_th1f_geteffectiveentries 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetFunction" c_th1f_getfunction 
  :: (Ptr RawTH1F) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1F_GetDimension" c_th1f_getdimension 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetKurtosis" c_th1f_getkurtosis 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetLowEdge" c_th1f_getlowedge 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_getMaximumTH1" c_th1f_getmaximumth1 
  :: (Ptr RawTH1F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetMaximumBin" c_th1f_getmaximumbin 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetMaximumStored" c_th1f_getmaximumstored 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_getMinimumTH1" c_th1f_getminimumth1 
  :: (Ptr RawTH1F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetMinimumBin" c_th1f_getminimumbin 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetMinimumStored" c_th1f_getminimumstored 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetMean" c_th1f_getmean 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetMeanError" c_th1f_getmeanerror 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetNbinsX" c_th1f_getnbinsx 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetNbinsY" c_th1f_getnbinsy 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetNbinsZ" c_th1f_getnbinsz 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_getQuantilesTH1" c_th1f_getquantilesth1 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetRandom" c_th1f_getrandom 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetStats" c_th1f_getstats 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_GetSumOfWeights" c_th1f_getsumofweights 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetSumw2" c_th1f_getsumw2 
  :: (Ptr RawTH1F) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1F_GetSumw2N" c_th1f_getsumw2n 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetRMS" c_th1f_getrms 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetRMSError" c_th1f_getrmserror 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_GetSkewness" c_th1f_getskewness 
  :: (Ptr RawTH1F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1F_integral1" c_th1f_integral1 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_interpolate1" c_th1f_interpolate1 
  :: (Ptr RawTH1F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1F_interpolate2" c_th1f_interpolate2 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1F_interpolate3" c_th1f_interpolate3 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1F_KolmogorovTest" c_th1f_kolmogorovtest 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1F_LabelsDeflate" c_th1f_labelsdeflate 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_LabelsInflate" c_th1f_labelsinflate 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_LabelsOption" c_th1f_labelsoption 
  :: (Ptr RawTH1F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_multiflyF" c_th1f_multiflyf 
  :: (Ptr RawTH1F) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_Multiply" c_th1f_multiply 
  :: (Ptr RawTH1F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_PutStats" c_th1f_putstats 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_Rebin" c_th1f_rebin 
  :: (Ptr RawTH1F) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_RebinAxis" c_th1f_rebinaxis 
  :: (Ptr RawTH1F) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1F_Rebuild" c_th1f_rebuild 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_Reset" c_th1f_reset 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_ResetStats" c_th1f_resetstats 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_Scale" c_th1f_scale 
  :: (Ptr RawTH1F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_setAxisColorA" c_th1f_setaxiscolora 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetAxisRange" c_th1f_setaxisrange 
  :: (Ptr RawTH1F) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetBarOffset" c_th1f_setbaroffset 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetBarWidth" c_th1f_setbarwidth 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinContent1" c_th1f_setbincontent1 
  :: (Ptr RawTH1F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinContent2" c_th1f_setbincontent2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinContent3" c_th1f_setbincontent3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinError1" c_th1f_setbinerror1 
  :: (Ptr RawTH1F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinError2" c_th1f_setbinerror2 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBinError3" c_th1f_setbinerror3 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_setBins1" c_th1f_setbins1 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_setBins2" c_th1f_setbins2 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_setBins3" c_th1f_setbins3 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_SetBinsLength" c_th1f_setbinslength 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetBuffer" c_th1f_setbuffer 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetCellContent" c_th1f_setcellcontent 
  :: (Ptr RawTH1F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetContent" c_th1f_setcontent 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_SetContour" c_th1f_setcontour 
  :: (Ptr RawTH1F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_SetContourLevel" c_th1f_setcontourlevel 
  :: (Ptr RawTH1F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetDirectory" c_th1f_setdirectory 
  :: (Ptr RawTH1F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1F_SetEntries" c_th1f_setentries 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetError" c_th1f_seterror 
  :: (Ptr RawTH1F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1F_setLabelColorA" c_th1f_setlabelcolora 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_setLabelSizeA" c_th1f_setlabelsizea 
  :: (Ptr RawTH1F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_setLabelFontA" c_th1f_setlabelfonta 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_setLabelOffsetA" c_th1f_setlabeloffseta 
  :: (Ptr RawTH1F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetMaximum" c_th1f_setmaximum 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetMinimum" c_th1f_setminimum 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetNormFactor" c_th1f_setnormfactor 
  :: (Ptr RawTH1F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1F_SetStats" c_th1f_setstats 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetOption" c_th1f_setoption 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetXTitle" c_th1f_setxtitle 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetYTitle" c_th1f_setytitle 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetZTitle" c_th1f_setztitle 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_ShowBackground" c_th1f_showbackground 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1F_ShowPeaks" c_th1f_showpeaks 
  :: (Ptr RawTH1F) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1F_Smooth" c_th1f_smooth 
  :: (Ptr RawTH1F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_Sumw2" c_th1f_sumw2 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_SetName" c_th1f_setname 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetNameTitle" c_th1f_setnametitle 
  :: (Ptr RawTH1F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetTitle" c_th1f_settitle 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_GetLineColor" c_th1f_getlinecolor 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetLineStyle" c_th1f_getlinestyle 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetLineWidth" c_th1f_getlinewidth 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_ResetAttLine" c_th1f_resetattline 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetLineAttributes" c_th1f_setlineattributes 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_SetLineColor" c_th1f_setlinecolor 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetLineStyle" c_th1f_setlinestyle 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetLineWidth" c_th1f_setlinewidth 
  :: (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_GetMarkerColor" c_th1f_getmarkercolor 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetMarkerStyle" c_th1f_getmarkerstyle 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_GetMarkerSize" c_th1f_getmarkersize 
  :: (Ptr RawTH1F) -> IO CDouble
foreign import ccall "HROOT.h TH1F_ResetAttMarker" c_th1f_resetattmarker 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_SetMarkerAttributes" c_th1f_setmarkerattributes 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_SetMarkerColor" c_th1f_setmarkercolor 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetMarkerStyle" c_th1f_setmarkerstyle 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_SetMarkerSize" c_th1f_setmarkersize 
  :: (Ptr RawTH1F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1F_Draw" c_th1f_draw 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_FindObject" c_th1f_findobject 
  :: (Ptr RawTH1F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1F_GetName" c_th1f_getname 
  :: (Ptr RawTH1F) -> IO CString
foreign import ccall "HROOT.h TH1F_IsA" c_th1f_isa 
  :: (Ptr RawTH1F) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1F_IsFolder" c_th1f_isfolder 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_IsEqual" c_th1f_isequal 
  :: (Ptr RawTH1F) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1F_IsSortable" c_th1f_issortable 
  :: (Ptr RawTH1F) -> IO CInt
foreign import ccall "HROOT.h TH1F_Paint" c_th1f_paint 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_printObj" c_th1f_printobj 
  :: (Ptr RawTH1F) -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_RecursiveRemove" c_th1f_recursiveremove 
  :: (Ptr RawTH1F) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1F_SaveAs" c_th1f_saveas 
  :: (Ptr RawTH1F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1F_UseCurrentStyle" c_th1f_usecurrentstyle 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_Write" c_th1f_write 
  :: (Ptr RawTH1F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1F_delete" c_th1f_delete 
  :: (Ptr RawTH1F) -> IO ()
foreign import ccall "HROOT.h TH1F_newTH1F" c_th1f_newth1f 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH1F)

foreign import ccall "HROOT.h TH1I_Add" c_th1i_add 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_AddBinContent" c_th1i_addbincontent 
  :: (Ptr RawTH1I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_Chi2Test" c_th1i_chi2test 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1I_ComputeIntegral" c_th1i_computeintegral 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_DirectoryAutoAdd" c_th1i_directoryautoadd 
  :: (Ptr RawTH1I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1I_Divide" c_th1i_divide 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_drawCopyTH1" c_th1i_drawcopyth1 
  :: (Ptr RawTH1I) -> CString -> IO (Ptr RawTH1I)
foreign import ccall "HROOT.h TH1I_DrawNormalized" c_th1i_drawnormalized 
  :: (Ptr RawTH1I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_drawPanelTH1" c_th1i_drawpanelth1 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_BufferEmpty" c_th1i_bufferempty 
  :: (Ptr RawTH1I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_evalF" c_th1i_evalf 
  :: (Ptr RawTH1I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_FFT" c_th1i_fft 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_fill1" c_th1i_fill1 
  :: (Ptr RawTH1I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_fill1w" c_th1i_fill1w 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_fillN1" c_th1i_filln1 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_FillRandom" c_th1i_fillrandom 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_FindBin" c_th1i_findbin 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_FindFixBin" c_th1i_findfixbin 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_FindFirstBinAbove" c_th1i_findfirstbinabove 
  :: (Ptr RawTH1I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_FindLastBinAbove" c_th1i_findlastbinabove 
  :: (Ptr RawTH1I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_FitPanelTH1" c_th1i_fitpanelth1 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_getNdivisionA" c_th1i_getndivisiona 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_getAxisColorA" c_th1i_getaxiscolora 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_getLabelColorA" c_th1i_getlabelcolora 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_getLabelFontA" c_th1i_getlabelfonta 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_getLabelOffsetA" c_th1i_getlabeloffseta 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_getLabelSizeA" c_th1i_getlabelsizea 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_getTitleFontA" c_th1i_gettitlefonta 
  :: (Ptr RawTH1I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1I_getTitleOffsetA" c_th1i_gettitleoffseta 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_getTitleSizeA" c_th1i_gettitlesizea 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_getTickLengthA" c_th1i_getticklengtha 
  :: (Ptr RawTH1I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBarOffset" c_th1i_getbaroffset 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBarWidth" c_th1i_getbarwidth 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetContour" c_th1i_getcontour 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetContourLevel" c_th1i_getcontourlevel 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetContourLevelPad" c_th1i_getcontourlevelpad 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBin" c_th1i_getbin 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_GetBinCenter" c_th1i_getbincenter 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent1" c_th1i_getbincontent1 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent2" c_th1i_getbincontent2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinContent3" c_th1i_getbincontent3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError1" c_th1i_getbinerror1 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError2" c_th1i_getbinerror2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinError3" c_th1i_getbinerror3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinLowEdge" c_th1i_getbinlowedge 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetBinWidth" c_th1i_getbinwidth 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetCellContent" c_th1i_getcellcontent 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetCellError" c_th1i_getcellerror 
  :: (Ptr RawTH1I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetEntries" c_th1i_getentries 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetEffectiveEntries" c_th1i_geteffectiveentries 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetFunction" c_th1i_getfunction 
  :: (Ptr RawTH1I) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1I_GetDimension" c_th1i_getdimension 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetKurtosis" c_th1i_getkurtosis 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetLowEdge" c_th1i_getlowedge 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_getMaximumTH1" c_th1i_getmaximumth1 
  :: (Ptr RawTH1I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetMaximumBin" c_th1i_getmaximumbin 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetMaximumStored" c_th1i_getmaximumstored 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_getMinimumTH1" c_th1i_getminimumth1 
  :: (Ptr RawTH1I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetMinimumBin" c_th1i_getminimumbin 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetMinimumStored" c_th1i_getminimumstored 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetMean" c_th1i_getmean 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetMeanError" c_th1i_getmeanerror 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetNbinsX" c_th1i_getnbinsx 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetNbinsY" c_th1i_getnbinsy 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetNbinsZ" c_th1i_getnbinsz 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_getQuantilesTH1" c_th1i_getquantilesth1 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetRandom" c_th1i_getrandom 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetStats" c_th1i_getstats 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_GetSumOfWeights" c_th1i_getsumofweights 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetSumw2" c_th1i_getsumw2 
  :: (Ptr RawTH1I) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1I_GetSumw2N" c_th1i_getsumw2n 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetRMS" c_th1i_getrms 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetRMSError" c_th1i_getrmserror 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_GetSkewness" c_th1i_getskewness 
  :: (Ptr RawTH1I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1I_integral1" c_th1i_integral1 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_interpolate1" c_th1i_interpolate1 
  :: (Ptr RawTH1I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1I_interpolate2" c_th1i_interpolate2 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1I_interpolate3" c_th1i_interpolate3 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1I_KolmogorovTest" c_th1i_kolmogorovtest 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1I_LabelsDeflate" c_th1i_labelsdeflate 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_LabelsInflate" c_th1i_labelsinflate 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_LabelsOption" c_th1i_labelsoption 
  :: (Ptr RawTH1I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_multiflyF" c_th1i_multiflyf 
  :: (Ptr RawTH1I) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_Multiply" c_th1i_multiply 
  :: (Ptr RawTH1I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_PutStats" c_th1i_putstats 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_Rebin" c_th1i_rebin 
  :: (Ptr RawTH1I) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_RebinAxis" c_th1i_rebinaxis 
  :: (Ptr RawTH1I) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1I_Rebuild" c_th1i_rebuild 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_Reset" c_th1i_reset 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_ResetStats" c_th1i_resetstats 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_Scale" c_th1i_scale 
  :: (Ptr RawTH1I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_setAxisColorA" c_th1i_setaxiscolora 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetAxisRange" c_th1i_setaxisrange 
  :: (Ptr RawTH1I) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetBarOffset" c_th1i_setbaroffset 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetBarWidth" c_th1i_setbarwidth 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinContent1" c_th1i_setbincontent1 
  :: (Ptr RawTH1I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinContent2" c_th1i_setbincontent2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinContent3" c_th1i_setbincontent3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinError1" c_th1i_setbinerror1 
  :: (Ptr RawTH1I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinError2" c_th1i_setbinerror2 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBinError3" c_th1i_setbinerror3 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_setBins1" c_th1i_setbins1 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_setBins2" c_th1i_setbins2 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_setBins3" c_th1i_setbins3 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_SetBinsLength" c_th1i_setbinslength 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetBuffer" c_th1i_setbuffer 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetCellContent" c_th1i_setcellcontent 
  :: (Ptr RawTH1I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetContent" c_th1i_setcontent 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_SetContour" c_th1i_setcontour 
  :: (Ptr RawTH1I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_SetContourLevel" c_th1i_setcontourlevel 
  :: (Ptr RawTH1I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetDirectory" c_th1i_setdirectory 
  :: (Ptr RawTH1I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1I_SetEntries" c_th1i_setentries 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetError" c_th1i_seterror 
  :: (Ptr RawTH1I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1I_setLabelColorA" c_th1i_setlabelcolora 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_setLabelSizeA" c_th1i_setlabelsizea 
  :: (Ptr RawTH1I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_setLabelFontA" c_th1i_setlabelfonta 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_setLabelOffsetA" c_th1i_setlabeloffseta 
  :: (Ptr RawTH1I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetMaximum" c_th1i_setmaximum 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetMinimum" c_th1i_setminimum 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetNormFactor" c_th1i_setnormfactor 
  :: (Ptr RawTH1I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1I_SetStats" c_th1i_setstats 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetOption" c_th1i_setoption 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetXTitle" c_th1i_setxtitle 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetYTitle" c_th1i_setytitle 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetZTitle" c_th1i_setztitle 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_ShowBackground" c_th1i_showbackground 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1I_ShowPeaks" c_th1i_showpeaks 
  :: (Ptr RawTH1I) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1I_Smooth" c_th1i_smooth 
  :: (Ptr RawTH1I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_Sumw2" c_th1i_sumw2 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_SetName" c_th1i_setname 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetNameTitle" c_th1i_setnametitle 
  :: (Ptr RawTH1I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetTitle" c_th1i_settitle 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_GetLineColor" c_th1i_getlinecolor 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetLineStyle" c_th1i_getlinestyle 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetLineWidth" c_th1i_getlinewidth 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_ResetAttLine" c_th1i_resetattline 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetLineAttributes" c_th1i_setlineattributes 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_SetLineColor" c_th1i_setlinecolor 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetLineStyle" c_th1i_setlinestyle 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetLineWidth" c_th1i_setlinewidth 
  :: (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_GetMarkerColor" c_th1i_getmarkercolor 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetMarkerStyle" c_th1i_getmarkerstyle 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_GetMarkerSize" c_th1i_getmarkersize 
  :: (Ptr RawTH1I) -> IO CDouble
foreign import ccall "HROOT.h TH1I_ResetAttMarker" c_th1i_resetattmarker 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_SetMarkerAttributes" c_th1i_setmarkerattributes 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_SetMarkerColor" c_th1i_setmarkercolor 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetMarkerStyle" c_th1i_setmarkerstyle 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_SetMarkerSize" c_th1i_setmarkersize 
  :: (Ptr RawTH1I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1I_Draw" c_th1i_draw 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_FindObject" c_th1i_findobject 
  :: (Ptr RawTH1I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1I_GetName" c_th1i_getname 
  :: (Ptr RawTH1I) -> IO CString
foreign import ccall "HROOT.h TH1I_IsA" c_th1i_isa 
  :: (Ptr RawTH1I) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1I_IsFolder" c_th1i_isfolder 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_IsEqual" c_th1i_isequal 
  :: (Ptr RawTH1I) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1I_IsSortable" c_th1i_issortable 
  :: (Ptr RawTH1I) -> IO CInt
foreign import ccall "HROOT.h TH1I_Paint" c_th1i_paint 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_printObj" c_th1i_printobj 
  :: (Ptr RawTH1I) -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_RecursiveRemove" c_th1i_recursiveremove 
  :: (Ptr RawTH1I) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1I_SaveAs" c_th1i_saveas 
  :: (Ptr RawTH1I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1I_UseCurrentStyle" c_th1i_usecurrentstyle 
  :: (Ptr RawTH1I) -> IO ()
foreign import ccall "HROOT.h TH1I_Write" c_th1i_write 
  :: (Ptr RawTH1I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1I_delete" c_th1i_delete 
  :: (Ptr RawTH1I) -> IO ()

foreign import ccall "HROOT.h TH1S_Add" c_th1s_add 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_AddBinContent" c_th1s_addbincontent 
  :: (Ptr RawTH1S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_Chi2Test" c_th1s_chi2test 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH1S_ComputeIntegral" c_th1s_computeintegral 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_DirectoryAutoAdd" c_th1s_directoryautoadd 
  :: (Ptr RawTH1S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1S_Divide" c_th1s_divide 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_drawCopyTH1" c_th1s_drawcopyth1 
  :: (Ptr RawTH1S) -> CString -> IO (Ptr RawTH1S)
foreign import ccall "HROOT.h TH1S_DrawNormalized" c_th1s_drawnormalized 
  :: (Ptr RawTH1S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_drawPanelTH1" c_th1s_drawpanelth1 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_BufferEmpty" c_th1s_bufferempty 
  :: (Ptr RawTH1S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_evalF" c_th1s_evalf 
  :: (Ptr RawTH1S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_FFT" c_th1s_fft 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_fill1" c_th1s_fill1 
  :: (Ptr RawTH1S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_fill1w" c_th1s_fill1w 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_fillN1" c_th1s_filln1 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_FillRandom" c_th1s_fillrandom 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_FindBin" c_th1s_findbin 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_FindFixBin" c_th1s_findfixbin 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_FindFirstBinAbove" c_th1s_findfirstbinabove 
  :: (Ptr RawTH1S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_FindLastBinAbove" c_th1s_findlastbinabove 
  :: (Ptr RawTH1S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_FitPanelTH1" c_th1s_fitpanelth1 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_getNdivisionA" c_th1s_getndivisiona 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_getAxisColorA" c_th1s_getaxiscolora 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_getLabelColorA" c_th1s_getlabelcolora 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_getLabelFontA" c_th1s_getlabelfonta 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_getLabelOffsetA" c_th1s_getlabeloffseta 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_getLabelSizeA" c_th1s_getlabelsizea 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_getTitleFontA" c_th1s_gettitlefonta 
  :: (Ptr RawTH1S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH1S_getTitleOffsetA" c_th1s_gettitleoffseta 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_getTitleSizeA" c_th1s_gettitlesizea 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_getTickLengthA" c_th1s_getticklengtha 
  :: (Ptr RawTH1S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBarOffset" c_th1s_getbaroffset 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBarWidth" c_th1s_getbarwidth 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetContour" c_th1s_getcontour 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetContourLevel" c_th1s_getcontourlevel 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetContourLevelPad" c_th1s_getcontourlevelpad 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBin" c_th1s_getbin 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_GetBinCenter" c_th1s_getbincenter 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent1" c_th1s_getbincontent1 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent2" c_th1s_getbincontent2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinContent3" c_th1s_getbincontent3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError1" c_th1s_getbinerror1 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError2" c_th1s_getbinerror2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinError3" c_th1s_getbinerror3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinLowEdge" c_th1s_getbinlowedge 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetBinWidth" c_th1s_getbinwidth 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetCellContent" c_th1s_getcellcontent 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetCellError" c_th1s_getcellerror 
  :: (Ptr RawTH1S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetEntries" c_th1s_getentries 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetEffectiveEntries" c_th1s_geteffectiveentries 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetFunction" c_th1s_getfunction 
  :: (Ptr RawTH1S) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH1S_GetDimension" c_th1s_getdimension 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetKurtosis" c_th1s_getkurtosis 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetLowEdge" c_th1s_getlowedge 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_getMaximumTH1" c_th1s_getmaximumth1 
  :: (Ptr RawTH1S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetMaximumBin" c_th1s_getmaximumbin 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetMaximumStored" c_th1s_getmaximumstored 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_getMinimumTH1" c_th1s_getminimumth1 
  :: (Ptr RawTH1S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetMinimumBin" c_th1s_getminimumbin 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetMinimumStored" c_th1s_getminimumstored 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetMean" c_th1s_getmean 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetMeanError" c_th1s_getmeanerror 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetNbinsX" c_th1s_getnbinsx 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetNbinsY" c_th1s_getnbinsy 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetNbinsZ" c_th1s_getnbinsz 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_getQuantilesTH1" c_th1s_getquantilesth1 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetRandom" c_th1s_getrandom 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetStats" c_th1s_getstats 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_GetSumOfWeights" c_th1s_getsumofweights 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetSumw2" c_th1s_getsumw2 
  :: (Ptr RawTH1S) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH1S_GetSumw2N" c_th1s_getsumw2n 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetRMS" c_th1s_getrms 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetRMSError" c_th1s_getrmserror 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_GetSkewness" c_th1s_getskewness 
  :: (Ptr RawTH1S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH1S_integral1" c_th1s_integral1 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_interpolate1" c_th1s_interpolate1 
  :: (Ptr RawTH1S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1S_interpolate2" c_th1s_interpolate2 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1S_interpolate3" c_th1s_interpolate3 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH1S_KolmogorovTest" c_th1s_kolmogorovtest 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH1S_LabelsDeflate" c_th1s_labelsdeflate 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_LabelsInflate" c_th1s_labelsinflate 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_LabelsOption" c_th1s_labelsoption 
  :: (Ptr RawTH1S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_multiflyF" c_th1s_multiflyf 
  :: (Ptr RawTH1S) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_Multiply" c_th1s_multiply 
  :: (Ptr RawTH1S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_PutStats" c_th1s_putstats 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_Rebin" c_th1s_rebin 
  :: (Ptr RawTH1S) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_RebinAxis" c_th1s_rebinaxis 
  :: (Ptr RawTH1S) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH1S_Rebuild" c_th1s_rebuild 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_Reset" c_th1s_reset 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_ResetStats" c_th1s_resetstats 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_Scale" c_th1s_scale 
  :: (Ptr RawTH1S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_setAxisColorA" c_th1s_setaxiscolora 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetAxisRange" c_th1s_setaxisrange 
  :: (Ptr RawTH1S) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetBarOffset" c_th1s_setbaroffset 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetBarWidth" c_th1s_setbarwidth 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinContent1" c_th1s_setbincontent1 
  :: (Ptr RawTH1S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinContent2" c_th1s_setbincontent2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinContent3" c_th1s_setbincontent3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinError1" c_th1s_setbinerror1 
  :: (Ptr RawTH1S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinError2" c_th1s_setbinerror2 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBinError3" c_th1s_setbinerror3 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_setBins1" c_th1s_setbins1 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_setBins2" c_th1s_setbins2 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_setBins3" c_th1s_setbins3 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_SetBinsLength" c_th1s_setbinslength 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetBuffer" c_th1s_setbuffer 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetCellContent" c_th1s_setcellcontent 
  :: (Ptr RawTH1S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetContent" c_th1s_setcontent 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_SetContour" c_th1s_setcontour 
  :: (Ptr RawTH1S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_SetContourLevel" c_th1s_setcontourlevel 
  :: (Ptr RawTH1S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetDirectory" c_th1s_setdirectory 
  :: (Ptr RawTH1S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH1S_SetEntries" c_th1s_setentries 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetError" c_th1s_seterror 
  :: (Ptr RawTH1S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH1S_setLabelColorA" c_th1s_setlabelcolora 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_setLabelSizeA" c_th1s_setlabelsizea 
  :: (Ptr RawTH1S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_setLabelFontA" c_th1s_setlabelfonta 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_setLabelOffsetA" c_th1s_setlabeloffseta 
  :: (Ptr RawTH1S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetMaximum" c_th1s_setmaximum 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetMinimum" c_th1s_setminimum 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetNormFactor" c_th1s_setnormfactor 
  :: (Ptr RawTH1S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH1S_SetStats" c_th1s_setstats 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetOption" c_th1s_setoption 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetXTitle" c_th1s_setxtitle 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetYTitle" c_th1s_setytitle 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetZTitle" c_th1s_setztitle 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_ShowBackground" c_th1s_showbackground 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH1S_ShowPeaks" c_th1s_showpeaks 
  :: (Ptr RawTH1S) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH1S_Smooth" c_th1s_smooth 
  :: (Ptr RawTH1S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_Sumw2" c_th1s_sumw2 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_SetName" c_th1s_setname 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetNameTitle" c_th1s_setnametitle 
  :: (Ptr RawTH1S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetTitle" c_th1s_settitle 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_GetLineColor" c_th1s_getlinecolor 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetLineStyle" c_th1s_getlinestyle 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetLineWidth" c_th1s_getlinewidth 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_ResetAttLine" c_th1s_resetattline 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetLineAttributes" c_th1s_setlineattributes 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_SetLineColor" c_th1s_setlinecolor 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetLineStyle" c_th1s_setlinestyle 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetLineWidth" c_th1s_setlinewidth 
  :: (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_GetMarkerColor" c_th1s_getmarkercolor 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetMarkerStyle" c_th1s_getmarkerstyle 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_GetMarkerSize" c_th1s_getmarkersize 
  :: (Ptr RawTH1S) -> IO CDouble
foreign import ccall "HROOT.h TH1S_ResetAttMarker" c_th1s_resetattmarker 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_SetMarkerAttributes" c_th1s_setmarkerattributes 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_SetMarkerColor" c_th1s_setmarkercolor 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetMarkerStyle" c_th1s_setmarkerstyle 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_SetMarkerSize" c_th1s_setmarkersize 
  :: (Ptr RawTH1S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH1S_Draw" c_th1s_draw 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_FindObject" c_th1s_findobject 
  :: (Ptr RawTH1S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH1S_GetName" c_th1s_getname 
  :: (Ptr RawTH1S) -> IO CString
foreign import ccall "HROOT.h TH1S_IsA" c_th1s_isa 
  :: (Ptr RawTH1S) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH1S_IsFolder" c_th1s_isfolder 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_IsEqual" c_th1s_isequal 
  :: (Ptr RawTH1S) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH1S_IsSortable" c_th1s_issortable 
  :: (Ptr RawTH1S) -> IO CInt
foreign import ccall "HROOT.h TH1S_Paint" c_th1s_paint 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_printObj" c_th1s_printobj 
  :: (Ptr RawTH1S) -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_RecursiveRemove" c_th1s_recursiveremove 
  :: (Ptr RawTH1S) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH1S_SaveAs" c_th1s_saveas 
  :: (Ptr RawTH1S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH1S_UseCurrentStyle" c_th1s_usecurrentstyle 
  :: (Ptr RawTH1S) -> IO ()
foreign import ccall "HROOT.h TH1S_Write" c_th1s_write 
  :: (Ptr RawTH1S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH1S_delete" c_th1s_delete 
  :: (Ptr RawTH1S) -> IO ()

foreign import ccall "HROOT.h TH2C_fill2" c_th2c_fill2 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_fill2w" c_th2c_fill2w 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_fillN2" c_th2c_filln2 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_fillRandom2" c_th2c_fillrandom2 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_findFirstBinAbove2" c_th2c_findfirstbinabove2 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_findLastBinAbove2" c_th2c_findlastbinabove2 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_FitSlicesX" c_th2c_fitslicesx 
  :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2C_FitSlicesY" c_th2c_fitslicesy 
  :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2C_getCorrelationFactor2" c_th2c_getcorrelationfactor2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_getCovariance2" c_th2c_getcovariance2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_integral2" c_th2c_integral2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_rebinX2" c_th2c_rebinx2 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2C_rebinY2" c_th2c_rebiny2 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2C_Rebin2D" c_th2c_rebin2d 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2C_SetShowProjectionX" c_th2c_setshowprojectionx 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetShowProjectionY" c_th2c_setshowprojectiony 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_Add" c_th2c_add 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_AddBinContent" c_th2c_addbincontent 
  :: (Ptr RawTH2C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_Chi2Test" c_th2c_chi2test 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2C_ComputeIntegral" c_th2c_computeintegral 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_DirectoryAutoAdd" c_th2c_directoryautoadd 
  :: (Ptr RawTH2C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2C_Divide" c_th2c_divide 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_drawCopyTH1" c_th2c_drawcopyth1 
  :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTH2C)
foreign import ccall "HROOT.h TH2C_DrawNormalized" c_th2c_drawnormalized 
  :: (Ptr RawTH2C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_drawPanelTH1" c_th2c_drawpanelth1 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_BufferEmpty" c_th2c_bufferempty 
  :: (Ptr RawTH2C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_evalF" c_th2c_evalf 
  :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_FFT" c_th2c_fft 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_fill1" c_th2c_fill1 
  :: (Ptr RawTH2C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_fill1w" c_th2c_fill1w 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_fillN1" c_th2c_filln1 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_FillRandom" c_th2c_fillrandom 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_FindBin" c_th2c_findbin 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_FindFixBin" c_th2c_findfixbin 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_FindFirstBinAbove" c_th2c_findfirstbinabove 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_FindLastBinAbove" c_th2c_findlastbinabove 
  :: (Ptr RawTH2C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_FitPanelTH1" c_th2c_fitpanelth1 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_getNdivisionA" c_th2c_getndivisiona 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_getAxisColorA" c_th2c_getaxiscolora 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_getLabelColorA" c_th2c_getlabelcolora 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_getLabelFontA" c_th2c_getlabelfonta 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_getLabelOffsetA" c_th2c_getlabeloffseta 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_getLabelSizeA" c_th2c_getlabelsizea 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_getTitleFontA" c_th2c_gettitlefonta 
  :: (Ptr RawTH2C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2C_getTitleOffsetA" c_th2c_gettitleoffseta 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_getTitleSizeA" c_th2c_gettitlesizea 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_getTickLengthA" c_th2c_getticklengtha 
  :: (Ptr RawTH2C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBarOffset" c_th2c_getbaroffset 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBarWidth" c_th2c_getbarwidth 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetContour" c_th2c_getcontour 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetContourLevel" c_th2c_getcontourlevel 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetContourLevelPad" c_th2c_getcontourlevelpad 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBin" c_th2c_getbin 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_GetBinCenter" c_th2c_getbincenter 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent1" c_th2c_getbincontent1 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent2" c_th2c_getbincontent2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinContent3" c_th2c_getbincontent3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError1" c_th2c_getbinerror1 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError2" c_th2c_getbinerror2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinError3" c_th2c_getbinerror3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinLowEdge" c_th2c_getbinlowedge 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetBinWidth" c_th2c_getbinwidth 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetCellContent" c_th2c_getcellcontent 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetCellError" c_th2c_getcellerror 
  :: (Ptr RawTH2C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetEntries" c_th2c_getentries 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetEffectiveEntries" c_th2c_geteffectiveentries 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetFunction" c_th2c_getfunction 
  :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2C_GetDimension" c_th2c_getdimension 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetKurtosis" c_th2c_getkurtosis 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetLowEdge" c_th2c_getlowedge 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_getMaximumTH1" c_th2c_getmaximumth1 
  :: (Ptr RawTH2C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetMaximumBin" c_th2c_getmaximumbin 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetMaximumStored" c_th2c_getmaximumstored 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_getMinimumTH1" c_th2c_getminimumth1 
  :: (Ptr RawTH2C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetMinimumBin" c_th2c_getminimumbin 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetMinimumStored" c_th2c_getminimumstored 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetMean" c_th2c_getmean 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetMeanError" c_th2c_getmeanerror 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetNbinsX" c_th2c_getnbinsx 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetNbinsY" c_th2c_getnbinsy 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetNbinsZ" c_th2c_getnbinsz 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_getQuantilesTH1" c_th2c_getquantilesth1 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetRandom" c_th2c_getrandom 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetStats" c_th2c_getstats 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_GetSumOfWeights" c_th2c_getsumofweights 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetSumw2" c_th2c_getsumw2 
  :: (Ptr RawTH2C) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2C_GetSumw2N" c_th2c_getsumw2n 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetRMS" c_th2c_getrms 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetRMSError" c_th2c_getrmserror 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_GetSkewness" c_th2c_getskewness 
  :: (Ptr RawTH2C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2C_integral1" c_th2c_integral1 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_interpolate1" c_th2c_interpolate1 
  :: (Ptr RawTH2C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2C_interpolate2" c_th2c_interpolate2 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2C_interpolate3" c_th2c_interpolate3 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2C_KolmogorovTest" c_th2c_kolmogorovtest 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2C_LabelsDeflate" c_th2c_labelsdeflate 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_LabelsInflate" c_th2c_labelsinflate 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_LabelsOption" c_th2c_labelsoption 
  :: (Ptr RawTH2C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_multiflyF" c_th2c_multiflyf 
  :: (Ptr RawTH2C) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_Multiply" c_th2c_multiply 
  :: (Ptr RawTH2C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_PutStats" c_th2c_putstats 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_Rebin" c_th2c_rebin 
  :: (Ptr RawTH2C) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_RebinAxis" c_th2c_rebinaxis 
  :: (Ptr RawTH2C) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2C_Rebuild" c_th2c_rebuild 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_Reset" c_th2c_reset 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_ResetStats" c_th2c_resetstats 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_Scale" c_th2c_scale 
  :: (Ptr RawTH2C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_setAxisColorA" c_th2c_setaxiscolora 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetAxisRange" c_th2c_setaxisrange 
  :: (Ptr RawTH2C) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetBarOffset" c_th2c_setbaroffset 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetBarWidth" c_th2c_setbarwidth 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinContent1" c_th2c_setbincontent1 
  :: (Ptr RawTH2C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinContent2" c_th2c_setbincontent2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinContent3" c_th2c_setbincontent3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinError1" c_th2c_setbinerror1 
  :: (Ptr RawTH2C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinError2" c_th2c_setbinerror2 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBinError3" c_th2c_setbinerror3 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_setBins1" c_th2c_setbins1 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_setBins2" c_th2c_setbins2 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_setBins3" c_th2c_setbins3 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_SetBinsLength" c_th2c_setbinslength 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetBuffer" c_th2c_setbuffer 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetCellContent" c_th2c_setcellcontent 
  :: (Ptr RawTH2C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetContent" c_th2c_setcontent 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_SetContour" c_th2c_setcontour 
  :: (Ptr RawTH2C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_SetContourLevel" c_th2c_setcontourlevel 
  :: (Ptr RawTH2C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetDirectory" c_th2c_setdirectory 
  :: (Ptr RawTH2C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2C_SetEntries" c_th2c_setentries 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetError" c_th2c_seterror 
  :: (Ptr RawTH2C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2C_setLabelColorA" c_th2c_setlabelcolora 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_setLabelSizeA" c_th2c_setlabelsizea 
  :: (Ptr RawTH2C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_setLabelFontA" c_th2c_setlabelfonta 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_setLabelOffsetA" c_th2c_setlabeloffseta 
  :: (Ptr RawTH2C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetMaximum" c_th2c_setmaximum 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetMinimum" c_th2c_setminimum 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetNormFactor" c_th2c_setnormfactor 
  :: (Ptr RawTH2C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2C_SetStats" c_th2c_setstats 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetOption" c_th2c_setoption 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetXTitle" c_th2c_setxtitle 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetYTitle" c_th2c_setytitle 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetZTitle" c_th2c_setztitle 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_ShowBackground" c_th2c_showbackground 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2C_ShowPeaks" c_th2c_showpeaks 
  :: (Ptr RawTH2C) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2C_Smooth" c_th2c_smooth 
  :: (Ptr RawTH2C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_Sumw2" c_th2c_sumw2 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_SetName" c_th2c_setname 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetNameTitle" c_th2c_setnametitle 
  :: (Ptr RawTH2C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetTitle" c_th2c_settitle 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_GetLineColor" c_th2c_getlinecolor 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetLineStyle" c_th2c_getlinestyle 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetLineWidth" c_th2c_getlinewidth 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_ResetAttLine" c_th2c_resetattline 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetLineAttributes" c_th2c_setlineattributes 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_SetLineColor" c_th2c_setlinecolor 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetLineStyle" c_th2c_setlinestyle 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetLineWidth" c_th2c_setlinewidth 
  :: (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_GetMarkerColor" c_th2c_getmarkercolor 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetMarkerStyle" c_th2c_getmarkerstyle 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_GetMarkerSize" c_th2c_getmarkersize 
  :: (Ptr RawTH2C) -> IO CDouble
foreign import ccall "HROOT.h TH2C_ResetAttMarker" c_th2c_resetattmarker 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_SetMarkerAttributes" c_th2c_setmarkerattributes 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_SetMarkerColor" c_th2c_setmarkercolor 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetMarkerStyle" c_th2c_setmarkerstyle 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_SetMarkerSize" c_th2c_setmarkersize 
  :: (Ptr RawTH2C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2C_Draw" c_th2c_draw 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_FindObject" c_th2c_findobject 
  :: (Ptr RawTH2C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2C_GetName" c_th2c_getname 
  :: (Ptr RawTH2C) -> IO CString
foreign import ccall "HROOT.h TH2C_IsA" c_th2c_isa 
  :: (Ptr RawTH2C) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2C_IsFolder" c_th2c_isfolder 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_IsEqual" c_th2c_isequal 
  :: (Ptr RawTH2C) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2C_IsSortable" c_th2c_issortable 
  :: (Ptr RawTH2C) -> IO CInt
foreign import ccall "HROOT.h TH2C_Paint" c_th2c_paint 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_printObj" c_th2c_printobj 
  :: (Ptr RawTH2C) -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_RecursiveRemove" c_th2c_recursiveremove 
  :: (Ptr RawTH2C) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2C_SaveAs" c_th2c_saveas 
  :: (Ptr RawTH2C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2C_UseCurrentStyle" c_th2c_usecurrentstyle 
  :: (Ptr RawTH2C) -> IO ()
foreign import ccall "HROOT.h TH2C_Write" c_th2c_write 
  :: (Ptr RawTH2C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2C_delete" c_th2c_delete 
  :: (Ptr RawTH2C) -> IO ()

foreign import ccall "HROOT.h TH2D_fill2" c_th2d_fill2 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_fill2w" c_th2d_fill2w 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_fillN2" c_th2d_filln2 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_fillRandom2" c_th2d_fillrandom2 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_findFirstBinAbove2" c_th2d_findfirstbinabove2 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_findLastBinAbove2" c_th2d_findlastbinabove2 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_FitSlicesX" c_th2d_fitslicesx 
  :: (Ptr RawTH2D) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2D_FitSlicesY" c_th2d_fitslicesy 
  :: (Ptr RawTH2D) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2D_getCorrelationFactor2" c_th2d_getcorrelationfactor2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_getCovariance2" c_th2d_getcovariance2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_integral2" c_th2d_integral2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_rebinX2" c_th2d_rebinx2 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2D_rebinY2" c_th2d_rebiny2 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2D_Rebin2D" c_th2d_rebin2d 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2D_SetShowProjectionX" c_th2d_setshowprojectionx 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetShowProjectionY" c_th2d_setshowprojectiony 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_Add" c_th2d_add 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_AddBinContent" c_th2d_addbincontent 
  :: (Ptr RawTH2D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_Chi2Test" c_th2d_chi2test 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2D_ComputeIntegral" c_th2d_computeintegral 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_DirectoryAutoAdd" c_th2d_directoryautoadd 
  :: (Ptr RawTH2D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2D_Divide" c_th2d_divide 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_drawCopyTH1" c_th2d_drawcopyth1 
  :: (Ptr RawTH2D) -> CString -> IO (Ptr RawTH2D)
foreign import ccall "HROOT.h TH2D_DrawNormalized" c_th2d_drawnormalized 
  :: (Ptr RawTH2D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_drawPanelTH1" c_th2d_drawpanelth1 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_BufferEmpty" c_th2d_bufferempty 
  :: (Ptr RawTH2D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_evalF" c_th2d_evalf 
  :: (Ptr RawTH2D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_FFT" c_th2d_fft 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_fill1" c_th2d_fill1 
  :: (Ptr RawTH2D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_fill1w" c_th2d_fill1w 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_fillN1" c_th2d_filln1 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_FillRandom" c_th2d_fillrandom 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_FindBin" c_th2d_findbin 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_FindFixBin" c_th2d_findfixbin 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_FindFirstBinAbove" c_th2d_findfirstbinabove 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_FindLastBinAbove" c_th2d_findlastbinabove 
  :: (Ptr RawTH2D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_FitPanelTH1" c_th2d_fitpanelth1 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_getNdivisionA" c_th2d_getndivisiona 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_getAxisColorA" c_th2d_getaxiscolora 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_getLabelColorA" c_th2d_getlabelcolora 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_getLabelFontA" c_th2d_getlabelfonta 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_getLabelOffsetA" c_th2d_getlabeloffseta 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_getLabelSizeA" c_th2d_getlabelsizea 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_getTitleFontA" c_th2d_gettitlefonta 
  :: (Ptr RawTH2D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2D_getTitleOffsetA" c_th2d_gettitleoffseta 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_getTitleSizeA" c_th2d_gettitlesizea 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_getTickLengthA" c_th2d_getticklengtha 
  :: (Ptr RawTH2D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBarOffset" c_th2d_getbaroffset 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBarWidth" c_th2d_getbarwidth 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetContour" c_th2d_getcontour 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetContourLevel" c_th2d_getcontourlevel 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetContourLevelPad" c_th2d_getcontourlevelpad 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBin" c_th2d_getbin 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_GetBinCenter" c_th2d_getbincenter 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent1" c_th2d_getbincontent1 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent2" c_th2d_getbincontent2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinContent3" c_th2d_getbincontent3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError1" c_th2d_getbinerror1 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError2" c_th2d_getbinerror2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinError3" c_th2d_getbinerror3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinLowEdge" c_th2d_getbinlowedge 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetBinWidth" c_th2d_getbinwidth 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetCellContent" c_th2d_getcellcontent 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetCellError" c_th2d_getcellerror 
  :: (Ptr RawTH2D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetEntries" c_th2d_getentries 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetEffectiveEntries" c_th2d_geteffectiveentries 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetFunction" c_th2d_getfunction 
  :: (Ptr RawTH2D) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2D_GetDimension" c_th2d_getdimension 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetKurtosis" c_th2d_getkurtosis 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetLowEdge" c_th2d_getlowedge 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_getMaximumTH1" c_th2d_getmaximumth1 
  :: (Ptr RawTH2D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetMaximumBin" c_th2d_getmaximumbin 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetMaximumStored" c_th2d_getmaximumstored 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_getMinimumTH1" c_th2d_getminimumth1 
  :: (Ptr RawTH2D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetMinimumBin" c_th2d_getminimumbin 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetMinimumStored" c_th2d_getminimumstored 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetMean" c_th2d_getmean 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetMeanError" c_th2d_getmeanerror 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetNbinsX" c_th2d_getnbinsx 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetNbinsY" c_th2d_getnbinsy 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetNbinsZ" c_th2d_getnbinsz 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_getQuantilesTH1" c_th2d_getquantilesth1 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetRandom" c_th2d_getrandom 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetStats" c_th2d_getstats 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_GetSumOfWeights" c_th2d_getsumofweights 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetSumw2" c_th2d_getsumw2 
  :: (Ptr RawTH2D) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2D_GetSumw2N" c_th2d_getsumw2n 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetRMS" c_th2d_getrms 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetRMSError" c_th2d_getrmserror 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_GetSkewness" c_th2d_getskewness 
  :: (Ptr RawTH2D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2D_integral1" c_th2d_integral1 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_interpolate1" c_th2d_interpolate1 
  :: (Ptr RawTH2D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2D_interpolate2" c_th2d_interpolate2 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2D_interpolate3" c_th2d_interpolate3 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2D_KolmogorovTest" c_th2d_kolmogorovtest 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2D_LabelsDeflate" c_th2d_labelsdeflate 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_LabelsInflate" c_th2d_labelsinflate 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_LabelsOption" c_th2d_labelsoption 
  :: (Ptr RawTH2D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_multiflyF" c_th2d_multiflyf 
  :: (Ptr RawTH2D) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_Multiply" c_th2d_multiply 
  :: (Ptr RawTH2D) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_PutStats" c_th2d_putstats 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_Rebin" c_th2d_rebin 
  :: (Ptr RawTH2D) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_RebinAxis" c_th2d_rebinaxis 
  :: (Ptr RawTH2D) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2D_Rebuild" c_th2d_rebuild 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_Reset" c_th2d_reset 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_ResetStats" c_th2d_resetstats 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_Scale" c_th2d_scale 
  :: (Ptr RawTH2D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_setAxisColorA" c_th2d_setaxiscolora 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetAxisRange" c_th2d_setaxisrange 
  :: (Ptr RawTH2D) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetBarOffset" c_th2d_setbaroffset 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetBarWidth" c_th2d_setbarwidth 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinContent1" c_th2d_setbincontent1 
  :: (Ptr RawTH2D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinContent2" c_th2d_setbincontent2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinContent3" c_th2d_setbincontent3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinError1" c_th2d_setbinerror1 
  :: (Ptr RawTH2D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinError2" c_th2d_setbinerror2 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBinError3" c_th2d_setbinerror3 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_setBins1" c_th2d_setbins1 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_setBins2" c_th2d_setbins2 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_setBins3" c_th2d_setbins3 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_SetBinsLength" c_th2d_setbinslength 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetBuffer" c_th2d_setbuffer 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetCellContent" c_th2d_setcellcontent 
  :: (Ptr RawTH2D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetContent" c_th2d_setcontent 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_SetContour" c_th2d_setcontour 
  :: (Ptr RawTH2D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_SetContourLevel" c_th2d_setcontourlevel 
  :: (Ptr RawTH2D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetDirectory" c_th2d_setdirectory 
  :: (Ptr RawTH2D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2D_SetEntries" c_th2d_setentries 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetError" c_th2d_seterror 
  :: (Ptr RawTH2D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2D_setLabelColorA" c_th2d_setlabelcolora 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_setLabelSizeA" c_th2d_setlabelsizea 
  :: (Ptr RawTH2D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_setLabelFontA" c_th2d_setlabelfonta 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_setLabelOffsetA" c_th2d_setlabeloffseta 
  :: (Ptr RawTH2D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetMaximum" c_th2d_setmaximum 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetMinimum" c_th2d_setminimum 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetNormFactor" c_th2d_setnormfactor 
  :: (Ptr RawTH2D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2D_SetStats" c_th2d_setstats 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetOption" c_th2d_setoption 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetXTitle" c_th2d_setxtitle 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetYTitle" c_th2d_setytitle 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetZTitle" c_th2d_setztitle 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_ShowBackground" c_th2d_showbackground 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2D_ShowPeaks" c_th2d_showpeaks 
  :: (Ptr RawTH2D) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2D_Smooth" c_th2d_smooth 
  :: (Ptr RawTH2D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_Sumw2" c_th2d_sumw2 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_SetName" c_th2d_setname 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetNameTitle" c_th2d_setnametitle 
  :: (Ptr RawTH2D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetTitle" c_th2d_settitle 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_GetLineColor" c_th2d_getlinecolor 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetLineStyle" c_th2d_getlinestyle 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetLineWidth" c_th2d_getlinewidth 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_ResetAttLine" c_th2d_resetattline 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetLineAttributes" c_th2d_setlineattributes 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_SetLineColor" c_th2d_setlinecolor 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetLineStyle" c_th2d_setlinestyle 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetLineWidth" c_th2d_setlinewidth 
  :: (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_GetMarkerColor" c_th2d_getmarkercolor 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetMarkerStyle" c_th2d_getmarkerstyle 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_GetMarkerSize" c_th2d_getmarkersize 
  :: (Ptr RawTH2D) -> IO CDouble
foreign import ccall "HROOT.h TH2D_ResetAttMarker" c_th2d_resetattmarker 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_SetMarkerAttributes" c_th2d_setmarkerattributes 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_SetMarkerColor" c_th2d_setmarkercolor 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetMarkerStyle" c_th2d_setmarkerstyle 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_SetMarkerSize" c_th2d_setmarkersize 
  :: (Ptr RawTH2D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2D_Draw" c_th2d_draw 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_FindObject" c_th2d_findobject 
  :: (Ptr RawTH2D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2D_GetName" c_th2d_getname 
  :: (Ptr RawTH2D) -> IO CString
foreign import ccall "HROOT.h TH2D_IsA" c_th2d_isa 
  :: (Ptr RawTH2D) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2D_IsFolder" c_th2d_isfolder 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_IsEqual" c_th2d_isequal 
  :: (Ptr RawTH2D) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2D_IsSortable" c_th2d_issortable 
  :: (Ptr RawTH2D) -> IO CInt
foreign import ccall "HROOT.h TH2D_Paint" c_th2d_paint 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_printObj" c_th2d_printobj 
  :: (Ptr RawTH2D) -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_RecursiveRemove" c_th2d_recursiveremove 
  :: (Ptr RawTH2D) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2D_SaveAs" c_th2d_saveas 
  :: (Ptr RawTH2D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2D_UseCurrentStyle" c_th2d_usecurrentstyle 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_Write" c_th2d_write 
  :: (Ptr RawTH2D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2D_delete" c_th2d_delete 
  :: (Ptr RawTH2D) -> IO ()
foreign import ccall "HROOT.h TH2D_newTH2D" c_th2d_newth2d 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH2D)

foreign import ccall "HROOT.h TH2F_fill2" c_th2f_fill2 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_fill2w" c_th2f_fill2w 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_fillN2" c_th2f_filln2 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_fillRandom2" c_th2f_fillrandom2 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_findFirstBinAbove2" c_th2f_findfirstbinabove2 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_findLastBinAbove2" c_th2f_findlastbinabove2 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_FitSlicesX" c_th2f_fitslicesx 
  :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2F_FitSlicesY" c_th2f_fitslicesy 
  :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2F_getCorrelationFactor2" c_th2f_getcorrelationfactor2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_getCovariance2" c_th2f_getcovariance2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_integral2" c_th2f_integral2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_rebinX2" c_th2f_rebinx2 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2F_rebinY2" c_th2f_rebiny2 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2F_Rebin2D" c_th2f_rebin2d 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2F_SetShowProjectionX" c_th2f_setshowprojectionx 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetShowProjectionY" c_th2f_setshowprojectiony 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_Add" c_th2f_add 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_AddBinContent" c_th2f_addbincontent 
  :: (Ptr RawTH2F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_Chi2Test" c_th2f_chi2test 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2F_ComputeIntegral" c_th2f_computeintegral 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_DirectoryAutoAdd" c_th2f_directoryautoadd 
  :: (Ptr RawTH2F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2F_Divide" c_th2f_divide 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_drawCopyTH1" c_th2f_drawcopyth1 
  :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTH2F)
foreign import ccall "HROOT.h TH2F_DrawNormalized" c_th2f_drawnormalized 
  :: (Ptr RawTH2F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_drawPanelTH1" c_th2f_drawpanelth1 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_BufferEmpty" c_th2f_bufferempty 
  :: (Ptr RawTH2F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_evalF" c_th2f_evalf 
  :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_FFT" c_th2f_fft 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_fill1" c_th2f_fill1 
  :: (Ptr RawTH2F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_fill1w" c_th2f_fill1w 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_fillN1" c_th2f_filln1 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_FillRandom" c_th2f_fillrandom 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_FindBin" c_th2f_findbin 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_FindFixBin" c_th2f_findfixbin 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_FindFirstBinAbove" c_th2f_findfirstbinabove 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_FindLastBinAbove" c_th2f_findlastbinabove 
  :: (Ptr RawTH2F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_FitPanelTH1" c_th2f_fitpanelth1 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_getNdivisionA" c_th2f_getndivisiona 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_getAxisColorA" c_th2f_getaxiscolora 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_getLabelColorA" c_th2f_getlabelcolora 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_getLabelFontA" c_th2f_getlabelfonta 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_getLabelOffsetA" c_th2f_getlabeloffseta 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_getLabelSizeA" c_th2f_getlabelsizea 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_getTitleFontA" c_th2f_gettitlefonta 
  :: (Ptr RawTH2F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2F_getTitleOffsetA" c_th2f_gettitleoffseta 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_getTitleSizeA" c_th2f_gettitlesizea 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_getTickLengthA" c_th2f_getticklengtha 
  :: (Ptr RawTH2F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBarOffset" c_th2f_getbaroffset 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBarWidth" c_th2f_getbarwidth 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetContour" c_th2f_getcontour 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetContourLevel" c_th2f_getcontourlevel 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetContourLevelPad" c_th2f_getcontourlevelpad 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBin" c_th2f_getbin 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_GetBinCenter" c_th2f_getbincenter 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent1" c_th2f_getbincontent1 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent2" c_th2f_getbincontent2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinContent3" c_th2f_getbincontent3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError1" c_th2f_getbinerror1 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError2" c_th2f_getbinerror2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinError3" c_th2f_getbinerror3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinLowEdge" c_th2f_getbinlowedge 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetBinWidth" c_th2f_getbinwidth 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetCellContent" c_th2f_getcellcontent 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetCellError" c_th2f_getcellerror 
  :: (Ptr RawTH2F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetEntries" c_th2f_getentries 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetEffectiveEntries" c_th2f_geteffectiveentries 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetFunction" c_th2f_getfunction 
  :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2F_GetDimension" c_th2f_getdimension 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetKurtosis" c_th2f_getkurtosis 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetLowEdge" c_th2f_getlowedge 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_getMaximumTH1" c_th2f_getmaximumth1 
  :: (Ptr RawTH2F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetMaximumBin" c_th2f_getmaximumbin 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetMaximumStored" c_th2f_getmaximumstored 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_getMinimumTH1" c_th2f_getminimumth1 
  :: (Ptr RawTH2F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetMinimumBin" c_th2f_getminimumbin 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetMinimumStored" c_th2f_getminimumstored 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetMean" c_th2f_getmean 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetMeanError" c_th2f_getmeanerror 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetNbinsX" c_th2f_getnbinsx 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetNbinsY" c_th2f_getnbinsy 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetNbinsZ" c_th2f_getnbinsz 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_getQuantilesTH1" c_th2f_getquantilesth1 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetRandom" c_th2f_getrandom 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetStats" c_th2f_getstats 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_GetSumOfWeights" c_th2f_getsumofweights 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetSumw2" c_th2f_getsumw2 
  :: (Ptr RawTH2F) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2F_GetSumw2N" c_th2f_getsumw2n 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetRMS" c_th2f_getrms 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetRMSError" c_th2f_getrmserror 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_GetSkewness" c_th2f_getskewness 
  :: (Ptr RawTH2F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2F_integral1" c_th2f_integral1 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_interpolate1" c_th2f_interpolate1 
  :: (Ptr RawTH2F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2F_interpolate2" c_th2f_interpolate2 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2F_interpolate3" c_th2f_interpolate3 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2F_KolmogorovTest" c_th2f_kolmogorovtest 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2F_LabelsDeflate" c_th2f_labelsdeflate 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_LabelsInflate" c_th2f_labelsinflate 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_LabelsOption" c_th2f_labelsoption 
  :: (Ptr RawTH2F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_multiflyF" c_th2f_multiflyf 
  :: (Ptr RawTH2F) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_Multiply" c_th2f_multiply 
  :: (Ptr RawTH2F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_PutStats" c_th2f_putstats 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_Rebin" c_th2f_rebin 
  :: (Ptr RawTH2F) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_RebinAxis" c_th2f_rebinaxis 
  :: (Ptr RawTH2F) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2F_Rebuild" c_th2f_rebuild 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_Reset" c_th2f_reset 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_ResetStats" c_th2f_resetstats 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_Scale" c_th2f_scale 
  :: (Ptr RawTH2F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_setAxisColorA" c_th2f_setaxiscolora 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetAxisRange" c_th2f_setaxisrange 
  :: (Ptr RawTH2F) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetBarOffset" c_th2f_setbaroffset 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetBarWidth" c_th2f_setbarwidth 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinContent1" c_th2f_setbincontent1 
  :: (Ptr RawTH2F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinContent2" c_th2f_setbincontent2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinContent3" c_th2f_setbincontent3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinError1" c_th2f_setbinerror1 
  :: (Ptr RawTH2F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinError2" c_th2f_setbinerror2 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBinError3" c_th2f_setbinerror3 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_setBins1" c_th2f_setbins1 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_setBins2" c_th2f_setbins2 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_setBins3" c_th2f_setbins3 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_SetBinsLength" c_th2f_setbinslength 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetBuffer" c_th2f_setbuffer 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetCellContent" c_th2f_setcellcontent 
  :: (Ptr RawTH2F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetContent" c_th2f_setcontent 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_SetContour" c_th2f_setcontour 
  :: (Ptr RawTH2F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_SetContourLevel" c_th2f_setcontourlevel 
  :: (Ptr RawTH2F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetDirectory" c_th2f_setdirectory 
  :: (Ptr RawTH2F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2F_SetEntries" c_th2f_setentries 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetError" c_th2f_seterror 
  :: (Ptr RawTH2F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2F_setLabelColorA" c_th2f_setlabelcolora 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_setLabelSizeA" c_th2f_setlabelsizea 
  :: (Ptr RawTH2F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_setLabelFontA" c_th2f_setlabelfonta 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_setLabelOffsetA" c_th2f_setlabeloffseta 
  :: (Ptr RawTH2F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetMaximum" c_th2f_setmaximum 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetMinimum" c_th2f_setminimum 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetNormFactor" c_th2f_setnormfactor 
  :: (Ptr RawTH2F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2F_SetStats" c_th2f_setstats 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetOption" c_th2f_setoption 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetXTitle" c_th2f_setxtitle 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetYTitle" c_th2f_setytitle 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetZTitle" c_th2f_setztitle 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_ShowBackground" c_th2f_showbackground 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2F_ShowPeaks" c_th2f_showpeaks 
  :: (Ptr RawTH2F) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2F_Smooth" c_th2f_smooth 
  :: (Ptr RawTH2F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_Sumw2" c_th2f_sumw2 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_SetName" c_th2f_setname 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetNameTitle" c_th2f_setnametitle 
  :: (Ptr RawTH2F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetTitle" c_th2f_settitle 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_GetLineColor" c_th2f_getlinecolor 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetLineStyle" c_th2f_getlinestyle 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetLineWidth" c_th2f_getlinewidth 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_ResetAttLine" c_th2f_resetattline 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetLineAttributes" c_th2f_setlineattributes 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_SetLineColor" c_th2f_setlinecolor 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetLineStyle" c_th2f_setlinestyle 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetLineWidth" c_th2f_setlinewidth 
  :: (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_GetMarkerColor" c_th2f_getmarkercolor 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetMarkerStyle" c_th2f_getmarkerstyle 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_GetMarkerSize" c_th2f_getmarkersize 
  :: (Ptr RawTH2F) -> IO CDouble
foreign import ccall "HROOT.h TH2F_ResetAttMarker" c_th2f_resetattmarker 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_SetMarkerAttributes" c_th2f_setmarkerattributes 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_SetMarkerColor" c_th2f_setmarkercolor 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetMarkerStyle" c_th2f_setmarkerstyle 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_SetMarkerSize" c_th2f_setmarkersize 
  :: (Ptr RawTH2F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2F_Draw" c_th2f_draw 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_FindObject" c_th2f_findobject 
  :: (Ptr RawTH2F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2F_GetName" c_th2f_getname 
  :: (Ptr RawTH2F) -> IO CString
foreign import ccall "HROOT.h TH2F_IsA" c_th2f_isa 
  :: (Ptr RawTH2F) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2F_IsFolder" c_th2f_isfolder 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_IsEqual" c_th2f_isequal 
  :: (Ptr RawTH2F) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2F_IsSortable" c_th2f_issortable 
  :: (Ptr RawTH2F) -> IO CInt
foreign import ccall "HROOT.h TH2F_Paint" c_th2f_paint 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_printObj" c_th2f_printobj 
  :: (Ptr RawTH2F) -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_RecursiveRemove" c_th2f_recursiveremove 
  :: (Ptr RawTH2F) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2F_SaveAs" c_th2f_saveas 
  :: (Ptr RawTH2F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2F_UseCurrentStyle" c_th2f_usecurrentstyle 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_Write" c_th2f_write 
  :: (Ptr RawTH2F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2F_delete" c_th2f_delete 
  :: (Ptr RawTH2F) -> IO ()
foreign import ccall "HROOT.h TH2F_newTH2F" c_th2f_newth2f 
  :: CString -> CString -> CInt -> CDouble -> CDouble -> CInt -> CDouble -> CDouble -> IO (Ptr RawTH2F)

foreign import ccall "HROOT.h TH2I_fill2" c_th2i_fill2 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_fill2w" c_th2i_fill2w 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_fillN2" c_th2i_filln2 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_fillRandom2" c_th2i_fillrandom2 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_findFirstBinAbove2" c_th2i_findfirstbinabove2 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_findLastBinAbove2" c_th2i_findlastbinabove2 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_FitSlicesX" c_th2i_fitslicesx 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2I_FitSlicesY" c_th2i_fitslicesy 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2I_getCorrelationFactor2" c_th2i_getcorrelationfactor2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_getCovariance2" c_th2i_getcovariance2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_integral2" c_th2i_integral2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_rebinX2" c_th2i_rebinx2 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2I_rebinY2" c_th2i_rebiny2 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2I_Rebin2D" c_th2i_rebin2d 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2I_SetShowProjectionX" c_th2i_setshowprojectionx 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetShowProjectionY" c_th2i_setshowprojectiony 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_Add" c_th2i_add 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_AddBinContent" c_th2i_addbincontent 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_Chi2Test" c_th2i_chi2test 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2I_ComputeIntegral" c_th2i_computeintegral 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_DirectoryAutoAdd" c_th2i_directoryautoadd 
  :: (Ptr RawTH2I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2I_Divide" c_th2i_divide 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_drawCopyTH1" c_th2i_drawcopyth1 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTH2I)
foreign import ccall "HROOT.h TH2I_DrawNormalized" c_th2i_drawnormalized 
  :: (Ptr RawTH2I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_drawPanelTH1" c_th2i_drawpanelth1 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_BufferEmpty" c_th2i_bufferempty 
  :: (Ptr RawTH2I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_evalF" c_th2i_evalf 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_FFT" c_th2i_fft 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_fill1" c_th2i_fill1 
  :: (Ptr RawTH2I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_fill1w" c_th2i_fill1w 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_fillN1" c_th2i_filln1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_FillRandom" c_th2i_fillrandom 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_FindBin" c_th2i_findbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_FindFixBin" c_th2i_findfixbin 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_FindFirstBinAbove" c_th2i_findfirstbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_FindLastBinAbove" c_th2i_findlastbinabove 
  :: (Ptr RawTH2I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_FitPanelTH1" c_th2i_fitpanelth1 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_getNdivisionA" c_th2i_getndivisiona 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_getAxisColorA" c_th2i_getaxiscolora 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_getLabelColorA" c_th2i_getlabelcolora 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_getLabelFontA" c_th2i_getlabelfonta 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_getLabelOffsetA" c_th2i_getlabeloffseta 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_getLabelSizeA" c_th2i_getlabelsizea 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_getTitleFontA" c_th2i_gettitlefonta 
  :: (Ptr RawTH2I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2I_getTitleOffsetA" c_th2i_gettitleoffseta 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_getTitleSizeA" c_th2i_gettitlesizea 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_getTickLengthA" c_th2i_getticklengtha 
  :: (Ptr RawTH2I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBarOffset" c_th2i_getbaroffset 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBarWidth" c_th2i_getbarwidth 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetContour" c_th2i_getcontour 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetContourLevel" c_th2i_getcontourlevel 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetContourLevelPad" c_th2i_getcontourlevelpad 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBin" c_th2i_getbin 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_GetBinCenter" c_th2i_getbincenter 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent1" c_th2i_getbincontent1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent2" c_th2i_getbincontent2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinContent3" c_th2i_getbincontent3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError1" c_th2i_getbinerror1 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError2" c_th2i_getbinerror2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinError3" c_th2i_getbinerror3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinLowEdge" c_th2i_getbinlowedge 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetBinWidth" c_th2i_getbinwidth 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetCellContent" c_th2i_getcellcontent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetCellError" c_th2i_getcellerror 
  :: (Ptr RawTH2I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetEntries" c_th2i_getentries 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetEffectiveEntries" c_th2i_geteffectiveentries 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetFunction" c_th2i_getfunction 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2I_GetDimension" c_th2i_getdimension 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetKurtosis" c_th2i_getkurtosis 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetLowEdge" c_th2i_getlowedge 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_getMaximumTH1" c_th2i_getmaximumth1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetMaximumBin" c_th2i_getmaximumbin 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetMaximumStored" c_th2i_getmaximumstored 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_getMinimumTH1" c_th2i_getminimumth1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetMinimumBin" c_th2i_getminimumbin 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetMinimumStored" c_th2i_getminimumstored 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetMean" c_th2i_getmean 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetMeanError" c_th2i_getmeanerror 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetNbinsX" c_th2i_getnbinsx 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetNbinsY" c_th2i_getnbinsy 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetNbinsZ" c_th2i_getnbinsz 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_getQuantilesTH1" c_th2i_getquantilesth1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetRandom" c_th2i_getrandom 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetStats" c_th2i_getstats 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_GetSumOfWeights" c_th2i_getsumofweights 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetSumw2" c_th2i_getsumw2 
  :: (Ptr RawTH2I) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2I_GetSumw2N" c_th2i_getsumw2n 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetRMS" c_th2i_getrms 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetRMSError" c_th2i_getrmserror 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_GetSkewness" c_th2i_getskewness 
  :: (Ptr RawTH2I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2I_integral1" c_th2i_integral1 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_interpolate1" c_th2i_interpolate1 
  :: (Ptr RawTH2I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2I_interpolate2" c_th2i_interpolate2 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2I_interpolate3" c_th2i_interpolate3 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2I_KolmogorovTest" c_th2i_kolmogorovtest 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2I_LabelsDeflate" c_th2i_labelsdeflate 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_LabelsInflate" c_th2i_labelsinflate 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_LabelsOption" c_th2i_labelsoption 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_multiflyF" c_th2i_multiflyf 
  :: (Ptr RawTH2I) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_Multiply" c_th2i_multiply 
  :: (Ptr RawTH2I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_PutStats" c_th2i_putstats 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_Rebin" c_th2i_rebin 
  :: (Ptr RawTH2I) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_RebinAxis" c_th2i_rebinaxis 
  :: (Ptr RawTH2I) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2I_Rebuild" c_th2i_rebuild 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_Reset" c_th2i_reset 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_ResetStats" c_th2i_resetstats 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_Scale" c_th2i_scale 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_setAxisColorA" c_th2i_setaxiscolora 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetAxisRange" c_th2i_setaxisrange 
  :: (Ptr RawTH2I) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetBarOffset" c_th2i_setbaroffset 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetBarWidth" c_th2i_setbarwidth 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinContent1" c_th2i_setbincontent1 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinContent2" c_th2i_setbincontent2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinContent3" c_th2i_setbincontent3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinError1" c_th2i_setbinerror1 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinError2" c_th2i_setbinerror2 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBinError3" c_th2i_setbinerror3 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_setBins1" c_th2i_setbins1 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_setBins2" c_th2i_setbins2 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_setBins3" c_th2i_setbins3 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_SetBinsLength" c_th2i_setbinslength 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetBuffer" c_th2i_setbuffer 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetCellContent" c_th2i_setcellcontent 
  :: (Ptr RawTH2I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetContent" c_th2i_setcontent 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_SetContour" c_th2i_setcontour 
  :: (Ptr RawTH2I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_SetContourLevel" c_th2i_setcontourlevel 
  :: (Ptr RawTH2I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetDirectory" c_th2i_setdirectory 
  :: (Ptr RawTH2I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2I_SetEntries" c_th2i_setentries 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetError" c_th2i_seterror 
  :: (Ptr RawTH2I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2I_setLabelColorA" c_th2i_setlabelcolora 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_setLabelSizeA" c_th2i_setlabelsizea 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_setLabelFontA" c_th2i_setlabelfonta 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_setLabelOffsetA" c_th2i_setlabeloffseta 
  :: (Ptr RawTH2I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetMaximum" c_th2i_setmaximum 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetMinimum" c_th2i_setminimum 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetNormFactor" c_th2i_setnormfactor 
  :: (Ptr RawTH2I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2I_SetStats" c_th2i_setstats 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetOption" c_th2i_setoption 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetXTitle" c_th2i_setxtitle 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetYTitle" c_th2i_setytitle 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetZTitle" c_th2i_setztitle 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_ShowBackground" c_th2i_showbackground 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2I_ShowPeaks" c_th2i_showpeaks 
  :: (Ptr RawTH2I) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2I_Smooth" c_th2i_smooth 
  :: (Ptr RawTH2I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_Sumw2" c_th2i_sumw2 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_SetName" c_th2i_setname 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetNameTitle" c_th2i_setnametitle 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetTitle" c_th2i_settitle 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_GetLineColor" c_th2i_getlinecolor 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetLineStyle" c_th2i_getlinestyle 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetLineWidth" c_th2i_getlinewidth 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_ResetAttLine" c_th2i_resetattline 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetLineAttributes" c_th2i_setlineattributes 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_SetLineColor" c_th2i_setlinecolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetLineStyle" c_th2i_setlinestyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetLineWidth" c_th2i_setlinewidth 
  :: (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_GetMarkerColor" c_th2i_getmarkercolor 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetMarkerStyle" c_th2i_getmarkerstyle 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_GetMarkerSize" c_th2i_getmarkersize 
  :: (Ptr RawTH2I) -> IO CDouble
foreign import ccall "HROOT.h TH2I_ResetAttMarker" c_th2i_resetattmarker 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_SetMarkerAttributes" c_th2i_setmarkerattributes 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_SetMarkerColor" c_th2i_setmarkercolor 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetMarkerStyle" c_th2i_setmarkerstyle 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_SetMarkerSize" c_th2i_setmarkersize 
  :: (Ptr RawTH2I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2I_Draw" c_th2i_draw 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_FindObject" c_th2i_findobject 
  :: (Ptr RawTH2I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2I_GetName" c_th2i_getname 
  :: (Ptr RawTH2I) -> IO CString
foreign import ccall "HROOT.h TH2I_IsA" c_th2i_isa 
  :: (Ptr RawTH2I) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2I_IsFolder" c_th2i_isfolder 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_IsEqual" c_th2i_isequal 
  :: (Ptr RawTH2I) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2I_IsSortable" c_th2i_issortable 
  :: (Ptr RawTH2I) -> IO CInt
foreign import ccall "HROOT.h TH2I_Paint" c_th2i_paint 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_printObj" c_th2i_printobj 
  :: (Ptr RawTH2I) -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_RecursiveRemove" c_th2i_recursiveremove 
  :: (Ptr RawTH2I) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2I_SaveAs" c_th2i_saveas 
  :: (Ptr RawTH2I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2I_UseCurrentStyle" c_th2i_usecurrentstyle 
  :: (Ptr RawTH2I) -> IO ()
foreign import ccall "HROOT.h TH2I_Write" c_th2i_write 
  :: (Ptr RawTH2I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2I_delete" c_th2i_delete 
  :: (Ptr RawTH2I) -> IO ()

foreign import ccall "HROOT.h TH2Poly_fill2" c_th2poly_fill2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_fill2w" c_th2poly_fill2w 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_fillN2" c_th2poly_filln2 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_fillRandom2" c_th2poly_fillrandom2 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_findFirstBinAbove2" c_th2poly_findfirstbinabove2 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_findLastBinAbove2" c_th2poly_findlastbinabove2 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FitSlicesX" c_th2poly_fitslicesx 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2Poly_FitSlicesY" c_th2poly_fitslicesy 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2Poly_getCorrelationFactor2" c_th2poly_getcorrelationfactor2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getCovariance2" c_th2poly_getcovariance2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_integral2" c_th2poly_integral2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_rebinX2" c_th2poly_rebinx2 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2Poly_rebinY2" c_th2poly_rebiny2 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2Poly_Rebin2D" c_th2poly_rebin2d 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2Poly_SetShowProjectionX" c_th2poly_setshowprojectionx 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetShowProjectionY" c_th2poly_setshowprojectiony 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_Add" c_th2poly_add 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_AddBinContent" c_th2poly_addbincontent 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_Chi2Test" c_th2poly_chi2test 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_ComputeIntegral" c_th2poly_computeintegral 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_DirectoryAutoAdd" c_th2poly_directoryautoadd 
  :: (Ptr RawTH2Poly) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2Poly_Divide" c_th2poly_divide 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_drawCopyTH1" c_th2poly_drawcopyth1 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTH2Poly)
foreign import ccall "HROOT.h TH2Poly_DrawNormalized" c_th2poly_drawnormalized 
  :: (Ptr RawTH2Poly) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_drawPanelTH1" c_th2poly_drawpanelth1 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_BufferEmpty" c_th2poly_bufferempty 
  :: (Ptr RawTH2Poly) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_evalF" c_th2poly_evalf 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_FFT" c_th2poly_fft 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_fill1" c_th2poly_fill1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_fill1w" c_th2poly_fill1w 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_fillN1" c_th2poly_filln1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_FillRandom" c_th2poly_fillrandom 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_FindBin" c_th2poly_findbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindFixBin" c_th2poly_findfixbin 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindFirstBinAbove" c_th2poly_findfirstbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FindLastBinAbove" c_th2poly_findlastbinabove 
  :: (Ptr RawTH2Poly) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_FitPanelTH1" c_th2poly_fitpanelth1 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_getNdivisionA" c_th2poly_getndivisiona 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_getAxisColorA" c_th2poly_getaxiscolora 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_getLabelColorA" c_th2poly_getlabelcolora 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_getLabelFontA" c_th2poly_getlabelfonta 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_getLabelOffsetA" c_th2poly_getlabeloffseta 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getLabelSizeA" c_th2poly_getlabelsizea 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getTitleFontA" c_th2poly_gettitlefonta 
  :: (Ptr RawTH2Poly) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2Poly_getTitleOffsetA" c_th2poly_gettitleoffseta 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getTitleSizeA" c_th2poly_gettitlesizea 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getTickLengthA" c_th2poly_getticklengtha 
  :: (Ptr RawTH2Poly) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBarOffset" c_th2poly_getbaroffset 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBarWidth" c_th2poly_getbarwidth 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetContour" c_th2poly_getcontour 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetContourLevel" c_th2poly_getcontourlevel 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetContourLevelPad" c_th2poly_getcontourlevelpad 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBin" c_th2poly_getbin 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetBinCenter" c_th2poly_getbincenter 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent1" c_th2poly_getbincontent1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent2" c_th2poly_getbincontent2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinContent3" c_th2poly_getbincontent3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError1" c_th2poly_getbinerror1 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError2" c_th2poly_getbinerror2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinError3" c_th2poly_getbinerror3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinLowEdge" c_th2poly_getbinlowedge 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetBinWidth" c_th2poly_getbinwidth 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetCellContent" c_th2poly_getcellcontent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetCellError" c_th2poly_getcellerror 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetEntries" c_th2poly_getentries 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetEffectiveEntries" c_th2poly_geteffectiveentries 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetFunction" c_th2poly_getfunction 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2Poly_GetDimension" c_th2poly_getdimension 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetKurtosis" c_th2poly_getkurtosis 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetLowEdge" c_th2poly_getlowedge 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_getMaximumTH1" c_th2poly_getmaximumth1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetMaximumBin" c_th2poly_getmaximumbin 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetMaximumStored" c_th2poly_getmaximumstored 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getMinimumTH1" c_th2poly_getminimumth1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetMinimumBin" c_th2poly_getminimumbin 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetMinimumStored" c_th2poly_getminimumstored 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetMean" c_th2poly_getmean 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetMeanError" c_th2poly_getmeanerror 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetNbinsX" c_th2poly_getnbinsx 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetNbinsY" c_th2poly_getnbinsy 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetNbinsZ" c_th2poly_getnbinsz 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_getQuantilesTH1" c_th2poly_getquantilesth1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetRandom" c_th2poly_getrandom 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetStats" c_th2poly_getstats 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_GetSumOfWeights" c_th2poly_getsumofweights 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetSumw2" c_th2poly_getsumw2 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2Poly_GetSumw2N" c_th2poly_getsumw2n 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetRMS" c_th2poly_getrms 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetRMSError" c_th2poly_getrmserror 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_GetSkewness" c_th2poly_getskewness 
  :: (Ptr RawTH2Poly) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_integral1" c_th2poly_integral1 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_interpolate1" c_th2poly_interpolate1 
  :: (Ptr RawTH2Poly) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_interpolate2" c_th2poly_interpolate2 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_interpolate3" c_th2poly_interpolate3 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_KolmogorovTest" c_th2poly_kolmogorovtest 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_LabelsDeflate" c_th2poly_labelsdeflate 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_LabelsInflate" c_th2poly_labelsinflate 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_LabelsOption" c_th2poly_labelsoption 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_multiflyF" c_th2poly_multiflyf 
  :: (Ptr RawTH2Poly) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_Multiply" c_th2poly_multiply 
  :: (Ptr RawTH2Poly) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_PutStats" c_th2poly_putstats 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_Rebin" c_th2poly_rebin 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_RebinAxis" c_th2poly_rebinaxis 
  :: (Ptr RawTH2Poly) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2Poly_Rebuild" c_th2poly_rebuild 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_Reset" c_th2poly_reset 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_ResetStats" c_th2poly_resetstats 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_Scale" c_th2poly_scale 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_setAxisColorA" c_th2poly_setaxiscolora 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetAxisRange" c_th2poly_setaxisrange 
  :: (Ptr RawTH2Poly) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetBarOffset" c_th2poly_setbaroffset 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetBarWidth" c_th2poly_setbarwidth 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinContent1" c_th2poly_setbincontent1 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinContent2" c_th2poly_setbincontent2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinContent3" c_th2poly_setbincontent3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinError1" c_th2poly_setbinerror1 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinError2" c_th2poly_setbinerror2 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBinError3" c_th2poly_setbinerror3 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBins1" c_th2poly_setbins1 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBins2" c_th2poly_setbins2 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_setBins3" c_th2poly_setbins3 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetBinsLength" c_th2poly_setbinslength 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetBuffer" c_th2poly_setbuffer 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetCellContent" c_th2poly_setcellcontent 
  :: (Ptr RawTH2Poly) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetContent" c_th2poly_setcontent 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetContour" c_th2poly_setcontour 
  :: (Ptr RawTH2Poly) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetContourLevel" c_th2poly_setcontourlevel 
  :: (Ptr RawTH2Poly) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetDirectory" c_th2poly_setdirectory 
  :: (Ptr RawTH2Poly) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetEntries" c_th2poly_setentries 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetError" c_th2poly_seterror 
  :: (Ptr RawTH2Poly) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2Poly_setLabelColorA" c_th2poly_setlabelcolora 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_setLabelSizeA" c_th2poly_setlabelsizea 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_setLabelFontA" c_th2poly_setlabelfonta 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_setLabelOffsetA" c_th2poly_setlabeloffseta 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMaximum" c_th2poly_setmaximum 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMinimum" c_th2poly_setminimum 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetNormFactor" c_th2poly_setnormfactor 
  :: (Ptr RawTH2Poly) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetStats" c_th2poly_setstats 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetOption" c_th2poly_setoption 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetXTitle" c_th2poly_setxtitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetYTitle" c_th2poly_setytitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetZTitle" c_th2poly_setztitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_ShowBackground" c_th2poly_showbackground 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2Poly_ShowPeaks" c_th2poly_showpeaks 
  :: (Ptr RawTH2Poly) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2Poly_Smooth" c_th2poly_smooth 
  :: (Ptr RawTH2Poly) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_Sumw2" c_th2poly_sumw2 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetName" c_th2poly_setname 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetNameTitle" c_th2poly_setnametitle 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetTitle" c_th2poly_settitle 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_GetLineColor" c_th2poly_getlinecolor 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetLineStyle" c_th2poly_getlinestyle 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetLineWidth" c_th2poly_getlinewidth 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_ResetAttLine" c_th2poly_resetattline 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetLineAttributes" c_th2poly_setlineattributes 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetLineColor" c_th2poly_setlinecolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetLineStyle" c_th2poly_setlinestyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetLineWidth" c_th2poly_setlinewidth 
  :: (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_GetMarkerColor" c_th2poly_getmarkercolor 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetMarkerStyle" c_th2poly_getmarkerstyle 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_GetMarkerSize" c_th2poly_getmarkersize 
  :: (Ptr RawTH2Poly) -> IO CDouble
foreign import ccall "HROOT.h TH2Poly_ResetAttMarker" c_th2poly_resetattmarker 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMarkerAttributes" c_th2poly_setmarkerattributes 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMarkerColor" c_th2poly_setmarkercolor 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMarkerStyle" c_th2poly_setmarkerstyle 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_SetMarkerSize" c_th2poly_setmarkersize 
  :: (Ptr RawTH2Poly) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2Poly_Draw" c_th2poly_draw 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_FindObject" c_th2poly_findobject 
  :: (Ptr RawTH2Poly) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2Poly_GetName" c_th2poly_getname 
  :: (Ptr RawTH2Poly) -> IO CString
foreign import ccall "HROOT.h TH2Poly_IsA" c_th2poly_isa 
  :: (Ptr RawTH2Poly) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2Poly_IsFolder" c_th2poly_isfolder 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_IsEqual" c_th2poly_isequal 
  :: (Ptr RawTH2Poly) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_IsSortable" c_th2poly_issortable 
  :: (Ptr RawTH2Poly) -> IO CInt
foreign import ccall "HROOT.h TH2Poly_Paint" c_th2poly_paint 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_printObj" c_th2poly_printobj 
  :: (Ptr RawTH2Poly) -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_RecursiveRemove" c_th2poly_recursiveremove 
  :: (Ptr RawTH2Poly) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2Poly_SaveAs" c_th2poly_saveas 
  :: (Ptr RawTH2Poly) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2Poly_UseCurrentStyle" c_th2poly_usecurrentstyle 
  :: (Ptr RawTH2Poly) -> IO ()
foreign import ccall "HROOT.h TH2Poly_Write" c_th2poly_write 
  :: (Ptr RawTH2Poly) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2Poly_delete" c_th2poly_delete 
  :: (Ptr RawTH2Poly) -> IO ()

foreign import ccall "HROOT.h TH2S_fill2" c_th2s_fill2 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_fill2w" c_th2s_fill2w 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_fillN2" c_th2s_filln2 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_fillRandom2" c_th2s_fillrandom2 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_findFirstBinAbove2" c_th2s_findfirstbinabove2 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_findLastBinAbove2" c_th2s_findlastbinabove2 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_FitSlicesX" c_th2s_fitslicesx 
  :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2S_FitSlicesY" c_th2s_fitslicesy 
  :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CString -> (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TH2S_getCorrelationFactor2" c_th2s_getcorrelationfactor2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_getCovariance2" c_th2s_getcovariance2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_integral2" c_th2s_integral2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_rebinX2" c_th2s_rebinx2 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2S_rebinY2" c_th2s_rebiny2 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2S_Rebin2D" c_th2s_rebin2d 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CString -> IO (Ptr RawTH2)
foreign import ccall "HROOT.h TH2S_SetShowProjectionX" c_th2s_setshowprojectionx 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetShowProjectionY" c_th2s_setshowprojectiony 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_Add" c_th2s_add 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_AddBinContent" c_th2s_addbincontent 
  :: (Ptr RawTH2S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_Chi2Test" c_th2s_chi2test 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH2S_ComputeIntegral" c_th2s_computeintegral 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_DirectoryAutoAdd" c_th2s_directoryautoadd 
  :: (Ptr RawTH2S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2S_Divide" c_th2s_divide 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_drawCopyTH1" c_th2s_drawcopyth1 
  :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTH2S)
foreign import ccall "HROOT.h TH2S_DrawNormalized" c_th2s_drawnormalized 
  :: (Ptr RawTH2S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_drawPanelTH1" c_th2s_drawpanelth1 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_BufferEmpty" c_th2s_bufferempty 
  :: (Ptr RawTH2S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_evalF" c_th2s_evalf 
  :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_FFT" c_th2s_fft 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_fill1" c_th2s_fill1 
  :: (Ptr RawTH2S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_fill1w" c_th2s_fill1w 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_fillN1" c_th2s_filln1 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_FillRandom" c_th2s_fillrandom 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_FindBin" c_th2s_findbin 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_FindFixBin" c_th2s_findfixbin 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_FindFirstBinAbove" c_th2s_findfirstbinabove 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_FindLastBinAbove" c_th2s_findlastbinabove 
  :: (Ptr RawTH2S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_FitPanelTH1" c_th2s_fitpanelth1 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_getNdivisionA" c_th2s_getndivisiona 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_getAxisColorA" c_th2s_getaxiscolora 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_getLabelColorA" c_th2s_getlabelcolora 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_getLabelFontA" c_th2s_getlabelfonta 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_getLabelOffsetA" c_th2s_getlabeloffseta 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_getLabelSizeA" c_th2s_getlabelsizea 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_getTitleFontA" c_th2s_gettitlefonta 
  :: (Ptr RawTH2S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH2S_getTitleOffsetA" c_th2s_gettitleoffseta 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_getTitleSizeA" c_th2s_gettitlesizea 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_getTickLengthA" c_th2s_getticklengtha 
  :: (Ptr RawTH2S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBarOffset" c_th2s_getbaroffset 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBarWidth" c_th2s_getbarwidth 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetContour" c_th2s_getcontour 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetContourLevel" c_th2s_getcontourlevel 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetContourLevelPad" c_th2s_getcontourlevelpad 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBin" c_th2s_getbin 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_GetBinCenter" c_th2s_getbincenter 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent1" c_th2s_getbincontent1 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent2" c_th2s_getbincontent2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinContent3" c_th2s_getbincontent3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError1" c_th2s_getbinerror1 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError2" c_th2s_getbinerror2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinError3" c_th2s_getbinerror3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinLowEdge" c_th2s_getbinlowedge 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetBinWidth" c_th2s_getbinwidth 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetCellContent" c_th2s_getcellcontent 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetCellError" c_th2s_getcellerror 
  :: (Ptr RawTH2S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetEntries" c_th2s_getentries 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetEffectiveEntries" c_th2s_geteffectiveentries 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetFunction" c_th2s_getfunction 
  :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH2S_GetDimension" c_th2s_getdimension 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetKurtosis" c_th2s_getkurtosis 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetLowEdge" c_th2s_getlowedge 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_getMaximumTH1" c_th2s_getmaximumth1 
  :: (Ptr RawTH2S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetMaximumBin" c_th2s_getmaximumbin 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetMaximumStored" c_th2s_getmaximumstored 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_getMinimumTH1" c_th2s_getminimumth1 
  :: (Ptr RawTH2S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetMinimumBin" c_th2s_getminimumbin 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetMinimumStored" c_th2s_getminimumstored 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetMean" c_th2s_getmean 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetMeanError" c_th2s_getmeanerror 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetNbinsX" c_th2s_getnbinsx 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetNbinsY" c_th2s_getnbinsy 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetNbinsZ" c_th2s_getnbinsz 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_getQuantilesTH1" c_th2s_getquantilesth1 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetRandom" c_th2s_getrandom 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetStats" c_th2s_getstats 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_GetSumOfWeights" c_th2s_getsumofweights 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetSumw2" c_th2s_getsumw2 
  :: (Ptr RawTH2S) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH2S_GetSumw2N" c_th2s_getsumw2n 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetRMS" c_th2s_getrms 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetRMSError" c_th2s_getrmserror 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_GetSkewness" c_th2s_getskewness 
  :: (Ptr RawTH2S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH2S_integral1" c_th2s_integral1 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_interpolate1" c_th2s_interpolate1 
  :: (Ptr RawTH2S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2S_interpolate2" c_th2s_interpolate2 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2S_interpolate3" c_th2s_interpolate3 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH2S_KolmogorovTest" c_th2s_kolmogorovtest 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH2S_LabelsDeflate" c_th2s_labelsdeflate 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_LabelsInflate" c_th2s_labelsinflate 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_LabelsOption" c_th2s_labelsoption 
  :: (Ptr RawTH2S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_multiflyF" c_th2s_multiflyf 
  :: (Ptr RawTH2S) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_Multiply" c_th2s_multiply 
  :: (Ptr RawTH2S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_PutStats" c_th2s_putstats 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_Rebin" c_th2s_rebin 
  :: (Ptr RawTH2S) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_RebinAxis" c_th2s_rebinaxis 
  :: (Ptr RawTH2S) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH2S_Rebuild" c_th2s_rebuild 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_Reset" c_th2s_reset 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_ResetStats" c_th2s_resetstats 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_Scale" c_th2s_scale 
  :: (Ptr RawTH2S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_setAxisColorA" c_th2s_setaxiscolora 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetAxisRange" c_th2s_setaxisrange 
  :: (Ptr RawTH2S) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetBarOffset" c_th2s_setbaroffset 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetBarWidth" c_th2s_setbarwidth 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinContent1" c_th2s_setbincontent1 
  :: (Ptr RawTH2S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinContent2" c_th2s_setbincontent2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinContent3" c_th2s_setbincontent3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinError1" c_th2s_setbinerror1 
  :: (Ptr RawTH2S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinError2" c_th2s_setbinerror2 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBinError3" c_th2s_setbinerror3 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_setBins1" c_th2s_setbins1 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_setBins2" c_th2s_setbins2 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_setBins3" c_th2s_setbins3 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_SetBinsLength" c_th2s_setbinslength 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetBuffer" c_th2s_setbuffer 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetCellContent" c_th2s_setcellcontent 
  :: (Ptr RawTH2S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetContent" c_th2s_setcontent 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_SetContour" c_th2s_setcontour 
  :: (Ptr RawTH2S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_SetContourLevel" c_th2s_setcontourlevel 
  :: (Ptr RawTH2S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetDirectory" c_th2s_setdirectory 
  :: (Ptr RawTH2S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH2S_SetEntries" c_th2s_setentries 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetError" c_th2s_seterror 
  :: (Ptr RawTH2S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH2S_setLabelColorA" c_th2s_setlabelcolora 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_setLabelSizeA" c_th2s_setlabelsizea 
  :: (Ptr RawTH2S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_setLabelFontA" c_th2s_setlabelfonta 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_setLabelOffsetA" c_th2s_setlabeloffseta 
  :: (Ptr RawTH2S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetMaximum" c_th2s_setmaximum 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetMinimum" c_th2s_setminimum 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetNormFactor" c_th2s_setnormfactor 
  :: (Ptr RawTH2S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH2S_SetStats" c_th2s_setstats 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetOption" c_th2s_setoption 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetXTitle" c_th2s_setxtitle 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetYTitle" c_th2s_setytitle 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetZTitle" c_th2s_setztitle 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_ShowBackground" c_th2s_showbackground 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH2S_ShowPeaks" c_th2s_showpeaks 
  :: (Ptr RawTH2S) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH2S_Smooth" c_th2s_smooth 
  :: (Ptr RawTH2S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_Sumw2" c_th2s_sumw2 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_SetName" c_th2s_setname 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetNameTitle" c_th2s_setnametitle 
  :: (Ptr RawTH2S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetTitle" c_th2s_settitle 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_GetLineColor" c_th2s_getlinecolor 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetLineStyle" c_th2s_getlinestyle 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetLineWidth" c_th2s_getlinewidth 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_ResetAttLine" c_th2s_resetattline 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetLineAttributes" c_th2s_setlineattributes 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_SetLineColor" c_th2s_setlinecolor 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetLineStyle" c_th2s_setlinestyle 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetLineWidth" c_th2s_setlinewidth 
  :: (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_GetMarkerColor" c_th2s_getmarkercolor 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetMarkerStyle" c_th2s_getmarkerstyle 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_GetMarkerSize" c_th2s_getmarkersize 
  :: (Ptr RawTH2S) -> IO CDouble
foreign import ccall "HROOT.h TH2S_ResetAttMarker" c_th2s_resetattmarker 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_SetMarkerAttributes" c_th2s_setmarkerattributes 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_SetMarkerColor" c_th2s_setmarkercolor 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetMarkerStyle" c_th2s_setmarkerstyle 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_SetMarkerSize" c_th2s_setmarkersize 
  :: (Ptr RawTH2S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH2S_Draw" c_th2s_draw 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_FindObject" c_th2s_findobject 
  :: (Ptr RawTH2S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH2S_GetName" c_th2s_getname 
  :: (Ptr RawTH2S) -> IO CString
foreign import ccall "HROOT.h TH2S_IsA" c_th2s_isa 
  :: (Ptr RawTH2S) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH2S_IsFolder" c_th2s_isfolder 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_IsEqual" c_th2s_isequal 
  :: (Ptr RawTH2S) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH2S_IsSortable" c_th2s_issortable 
  :: (Ptr RawTH2S) -> IO CInt
foreign import ccall "HROOT.h TH2S_Paint" c_th2s_paint 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_printObj" c_th2s_printobj 
  :: (Ptr RawTH2S) -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_RecursiveRemove" c_th2s_recursiveremove 
  :: (Ptr RawTH2S) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH2S_SaveAs" c_th2s_saveas 
  :: (Ptr RawTH2S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH2S_UseCurrentStyle" c_th2s_usecurrentstyle 
  :: (Ptr RawTH2S) -> IO ()
foreign import ccall "HROOT.h TH2S_Write" c_th2s_write 
  :: (Ptr RawTH2S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH2S_delete" c_th2s_delete 
  :: (Ptr RawTH2S) -> IO ()

foreign import ccall "HROOT.h TH3C_fill3" c_th3c_fill3 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_fill3w" c_th3c_fill3w 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FitSlicesZ" c_th3c_fitslicesz 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_getCorrelationFactor3" c_th3c_getcorrelationfactor3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_getCovariance3" c_th3c_getcovariance3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_rebinX3" c_th3c_rebinx3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3C_rebinY3" c_th3c_rebiny3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3C_rebinZ3" c_th3c_rebinz3 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3C_Rebin3D" c_th3c_rebin3d 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3C_Add" c_th3c_add 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_AddBinContent" c_th3c_addbincontent 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_Chi2Test" c_th3c_chi2test 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3C_ComputeIntegral" c_th3c_computeintegral 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_DirectoryAutoAdd" c_th3c_directoryautoadd 
  :: (Ptr RawTH3C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3C_Divide" c_th3c_divide 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_drawCopyTH1" c_th3c_drawcopyth1 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTH3C)
foreign import ccall "HROOT.h TH3C_DrawNormalized" c_th3c_drawnormalized 
  :: (Ptr RawTH3C) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_drawPanelTH1" c_th3c_drawpanelth1 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_BufferEmpty" c_th3c_bufferempty 
  :: (Ptr RawTH3C) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_evalF" c_th3c_evalf 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_FFT" c_th3c_fft 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_fill1" c_th3c_fill1 
  :: (Ptr RawTH3C) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_fill1w" c_th3c_fill1w 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_fillN1" c_th3c_filln1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_FillRandom" c_th3c_fillrandom 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_FindBin" c_th3c_findbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FindFixBin" c_th3c_findfixbin 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_FindFirstBinAbove" c_th3c_findfirstbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_FindLastBinAbove" c_th3c_findlastbinabove 
  :: (Ptr RawTH3C) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_FitPanelTH1" c_th3c_fitpanelth1 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_getNdivisionA" c_th3c_getndivisiona 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_getAxisColorA" c_th3c_getaxiscolora 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_getLabelColorA" c_th3c_getlabelcolora 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_getLabelFontA" c_th3c_getlabelfonta 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_getLabelOffsetA" c_th3c_getlabeloffseta 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_getLabelSizeA" c_th3c_getlabelsizea 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_getTitleFontA" c_th3c_gettitlefonta 
  :: (Ptr RawTH3C) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3C_getTitleOffsetA" c_th3c_gettitleoffseta 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_getTitleSizeA" c_th3c_gettitlesizea 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_getTickLengthA" c_th3c_getticklengtha 
  :: (Ptr RawTH3C) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBarOffset" c_th3c_getbaroffset 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBarWidth" c_th3c_getbarwidth 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetContour" c_th3c_getcontour 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetContourLevel" c_th3c_getcontourlevel 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetContourLevelPad" c_th3c_getcontourlevelpad 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBin" c_th3c_getbin 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_GetBinCenter" c_th3c_getbincenter 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent1" c_th3c_getbincontent1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent2" c_th3c_getbincontent2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinContent3" c_th3c_getbincontent3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError1" c_th3c_getbinerror1 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError2" c_th3c_getbinerror2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinError3" c_th3c_getbinerror3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinLowEdge" c_th3c_getbinlowedge 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetBinWidth" c_th3c_getbinwidth 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetCellContent" c_th3c_getcellcontent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetCellError" c_th3c_getcellerror 
  :: (Ptr RawTH3C) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetEntries" c_th3c_getentries 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetEffectiveEntries" c_th3c_geteffectiveentries 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetFunction" c_th3c_getfunction 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3C_GetDimension" c_th3c_getdimension 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetKurtosis" c_th3c_getkurtosis 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetLowEdge" c_th3c_getlowedge 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_getMaximumTH1" c_th3c_getmaximumth1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetMaximumBin" c_th3c_getmaximumbin 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetMaximumStored" c_th3c_getmaximumstored 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_getMinimumTH1" c_th3c_getminimumth1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetMinimumBin" c_th3c_getminimumbin 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetMinimumStored" c_th3c_getminimumstored 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetMean" c_th3c_getmean 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetMeanError" c_th3c_getmeanerror 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetNbinsX" c_th3c_getnbinsx 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetNbinsY" c_th3c_getnbinsy 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetNbinsZ" c_th3c_getnbinsz 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_getQuantilesTH1" c_th3c_getquantilesth1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetRandom" c_th3c_getrandom 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetStats" c_th3c_getstats 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_GetSumOfWeights" c_th3c_getsumofweights 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetSumw2" c_th3c_getsumw2 
  :: (Ptr RawTH3C) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3C_GetSumw2N" c_th3c_getsumw2n 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetRMS" c_th3c_getrms 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetRMSError" c_th3c_getrmserror 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_GetSkewness" c_th3c_getskewness 
  :: (Ptr RawTH3C) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3C_integral1" c_th3c_integral1 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_interpolate1" c_th3c_interpolate1 
  :: (Ptr RawTH3C) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3C_interpolate2" c_th3c_interpolate2 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3C_interpolate3" c_th3c_interpolate3 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3C_KolmogorovTest" c_th3c_kolmogorovtest 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3C_LabelsDeflate" c_th3c_labelsdeflate 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_LabelsInflate" c_th3c_labelsinflate 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_LabelsOption" c_th3c_labelsoption 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_multiflyF" c_th3c_multiflyf 
  :: (Ptr RawTH3C) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_Multiply" c_th3c_multiply 
  :: (Ptr RawTH3C) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_PutStats" c_th3c_putstats 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_Rebin" c_th3c_rebin 
  :: (Ptr RawTH3C) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_RebinAxis" c_th3c_rebinaxis 
  :: (Ptr RawTH3C) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3C_Rebuild" c_th3c_rebuild 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_Reset" c_th3c_reset 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_ResetStats" c_th3c_resetstats 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_Scale" c_th3c_scale 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_setAxisColorA" c_th3c_setaxiscolora 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetAxisRange" c_th3c_setaxisrange 
  :: (Ptr RawTH3C) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetBarOffset" c_th3c_setbaroffset 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetBarWidth" c_th3c_setbarwidth 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinContent1" c_th3c_setbincontent1 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinContent2" c_th3c_setbincontent2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinContent3" c_th3c_setbincontent3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinError1" c_th3c_setbinerror1 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinError2" c_th3c_setbinerror2 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBinError3" c_th3c_setbinerror3 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_setBins1" c_th3c_setbins1 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_setBins2" c_th3c_setbins2 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_setBins3" c_th3c_setbins3 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_SetBinsLength" c_th3c_setbinslength 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetBuffer" c_th3c_setbuffer 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetCellContent" c_th3c_setcellcontent 
  :: (Ptr RawTH3C) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetContent" c_th3c_setcontent 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_SetContour" c_th3c_setcontour 
  :: (Ptr RawTH3C) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_SetContourLevel" c_th3c_setcontourlevel 
  :: (Ptr RawTH3C) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetDirectory" c_th3c_setdirectory 
  :: (Ptr RawTH3C) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3C_SetEntries" c_th3c_setentries 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetError" c_th3c_seterror 
  :: (Ptr RawTH3C) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3C_setLabelColorA" c_th3c_setlabelcolora 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_setLabelSizeA" c_th3c_setlabelsizea 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_setLabelFontA" c_th3c_setlabelfonta 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_setLabelOffsetA" c_th3c_setlabeloffseta 
  :: (Ptr RawTH3C) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetMaximum" c_th3c_setmaximum 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetMinimum" c_th3c_setminimum 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetNormFactor" c_th3c_setnormfactor 
  :: (Ptr RawTH3C) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3C_SetStats" c_th3c_setstats 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetOption" c_th3c_setoption 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetXTitle" c_th3c_setxtitle 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetYTitle" c_th3c_setytitle 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetZTitle" c_th3c_setztitle 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_ShowBackground" c_th3c_showbackground 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3C_ShowPeaks" c_th3c_showpeaks 
  :: (Ptr RawTH3C) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3C_Smooth" c_th3c_smooth 
  :: (Ptr RawTH3C) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_Sumw2" c_th3c_sumw2 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_SetName" c_th3c_setname 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetNameTitle" c_th3c_setnametitle 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetTitle" c_th3c_settitle 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_GetLineColor" c_th3c_getlinecolor 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetLineStyle" c_th3c_getlinestyle 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetLineWidth" c_th3c_getlinewidth 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_ResetAttLine" c_th3c_resetattline 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetLineAttributes" c_th3c_setlineattributes 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_SetLineColor" c_th3c_setlinecolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetLineStyle" c_th3c_setlinestyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetLineWidth" c_th3c_setlinewidth 
  :: (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_GetMarkerColor" c_th3c_getmarkercolor 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetMarkerStyle" c_th3c_getmarkerstyle 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_GetMarkerSize" c_th3c_getmarkersize 
  :: (Ptr RawTH3C) -> IO CDouble
foreign import ccall "HROOT.h TH3C_ResetAttMarker" c_th3c_resetattmarker 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_SetMarkerAttributes" c_th3c_setmarkerattributes 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_SetMarkerColor" c_th3c_setmarkercolor 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetMarkerStyle" c_th3c_setmarkerstyle 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_SetMarkerSize" c_th3c_setmarkersize 
  :: (Ptr RawTH3C) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3C_Draw" c_th3c_draw 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_FindObject" c_th3c_findobject 
  :: (Ptr RawTH3C) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3C_GetName" c_th3c_getname 
  :: (Ptr RawTH3C) -> IO CString
foreign import ccall "HROOT.h TH3C_IsA" c_th3c_isa 
  :: (Ptr RawTH3C) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3C_IsFolder" c_th3c_isfolder 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_IsEqual" c_th3c_isequal 
  :: (Ptr RawTH3C) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3C_IsSortable" c_th3c_issortable 
  :: (Ptr RawTH3C) -> IO CInt
foreign import ccall "HROOT.h TH3C_Paint" c_th3c_paint 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_printObj" c_th3c_printobj 
  :: (Ptr RawTH3C) -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_RecursiveRemove" c_th3c_recursiveremove 
  :: (Ptr RawTH3C) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3C_SaveAs" c_th3c_saveas 
  :: (Ptr RawTH3C) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3C_UseCurrentStyle" c_th3c_usecurrentstyle 
  :: (Ptr RawTH3C) -> IO ()
foreign import ccall "HROOT.h TH3C_Write" c_th3c_write 
  :: (Ptr RawTH3C) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3C_delete" c_th3c_delete 
  :: (Ptr RawTH3C) -> IO ()

foreign import ccall "HROOT.h TH3D_fill3" c_th3d_fill3 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_fill3w" c_th3d_fill3w 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FitSlicesZ" c_th3d_fitslicesz 
  :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_getCorrelationFactor3" c_th3d_getcorrelationfactor3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_getCovariance3" c_th3d_getcovariance3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_rebinX3" c_th3d_rebinx3 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3D_rebinY3" c_th3d_rebiny3 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3D_rebinZ3" c_th3d_rebinz3 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3D_Rebin3D" c_th3d_rebin3d 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3D_Add" c_th3d_add 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_AddBinContent" c_th3d_addbincontent 
  :: (Ptr RawTH3D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_Chi2Test" c_th3d_chi2test 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3D_ComputeIntegral" c_th3d_computeintegral 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_DirectoryAutoAdd" c_th3d_directoryautoadd 
  :: (Ptr RawTH3D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3D_Divide" c_th3d_divide 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_drawCopyTH1" c_th3d_drawcopyth1 
  :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTH3D)
foreign import ccall "HROOT.h TH3D_DrawNormalized" c_th3d_drawnormalized 
  :: (Ptr RawTH3D) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_drawPanelTH1" c_th3d_drawpanelth1 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_BufferEmpty" c_th3d_bufferempty 
  :: (Ptr RawTH3D) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_evalF" c_th3d_evalf 
  :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_FFT" c_th3d_fft 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_fill1" c_th3d_fill1 
  :: (Ptr RawTH3D) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_fill1w" c_th3d_fill1w 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_fillN1" c_th3d_filln1 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_FillRandom" c_th3d_fillrandom 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_FindBin" c_th3d_findbin 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FindFixBin" c_th3d_findfixbin 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_FindFirstBinAbove" c_th3d_findfirstbinabove 
  :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_FindLastBinAbove" c_th3d_findlastbinabove 
  :: (Ptr RawTH3D) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_FitPanelTH1" c_th3d_fitpanelth1 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_getNdivisionA" c_th3d_getndivisiona 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_getAxisColorA" c_th3d_getaxiscolora 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_getLabelColorA" c_th3d_getlabelcolora 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_getLabelFontA" c_th3d_getlabelfonta 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_getLabelOffsetA" c_th3d_getlabeloffseta 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_getLabelSizeA" c_th3d_getlabelsizea 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_getTitleFontA" c_th3d_gettitlefonta 
  :: (Ptr RawTH3D) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3D_getTitleOffsetA" c_th3d_gettitleoffseta 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_getTitleSizeA" c_th3d_gettitlesizea 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_getTickLengthA" c_th3d_getticklengtha 
  :: (Ptr RawTH3D) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBarOffset" c_th3d_getbaroffset 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBarWidth" c_th3d_getbarwidth 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetContour" c_th3d_getcontour 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetContourLevel" c_th3d_getcontourlevel 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetContourLevelPad" c_th3d_getcontourlevelpad 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBin" c_th3d_getbin 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_GetBinCenter" c_th3d_getbincenter 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent1" c_th3d_getbincontent1 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent2" c_th3d_getbincontent2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinContent3" c_th3d_getbincontent3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError1" c_th3d_getbinerror1 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError2" c_th3d_getbinerror2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinError3" c_th3d_getbinerror3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinLowEdge" c_th3d_getbinlowedge 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetBinWidth" c_th3d_getbinwidth 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetCellContent" c_th3d_getcellcontent 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetCellError" c_th3d_getcellerror 
  :: (Ptr RawTH3D) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetEntries" c_th3d_getentries 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetEffectiveEntries" c_th3d_geteffectiveentries 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetFunction" c_th3d_getfunction 
  :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3D_GetDimension" c_th3d_getdimension 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetKurtosis" c_th3d_getkurtosis 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetLowEdge" c_th3d_getlowedge 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_getMaximumTH1" c_th3d_getmaximumth1 
  :: (Ptr RawTH3D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetMaximumBin" c_th3d_getmaximumbin 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetMaximumStored" c_th3d_getmaximumstored 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_getMinimumTH1" c_th3d_getminimumth1 
  :: (Ptr RawTH3D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetMinimumBin" c_th3d_getminimumbin 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetMinimumStored" c_th3d_getminimumstored 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetMean" c_th3d_getmean 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetMeanError" c_th3d_getmeanerror 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetNbinsX" c_th3d_getnbinsx 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetNbinsY" c_th3d_getnbinsy 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetNbinsZ" c_th3d_getnbinsz 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_getQuantilesTH1" c_th3d_getquantilesth1 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetRandom" c_th3d_getrandom 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetStats" c_th3d_getstats 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_GetSumOfWeights" c_th3d_getsumofweights 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetSumw2" c_th3d_getsumw2 
  :: (Ptr RawTH3D) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3D_GetSumw2N" c_th3d_getsumw2n 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetRMS" c_th3d_getrms 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetRMSError" c_th3d_getrmserror 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_GetSkewness" c_th3d_getskewness 
  :: (Ptr RawTH3D) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3D_integral1" c_th3d_integral1 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_interpolate1" c_th3d_interpolate1 
  :: (Ptr RawTH3D) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3D_interpolate2" c_th3d_interpolate2 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3D_interpolate3" c_th3d_interpolate3 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3D_KolmogorovTest" c_th3d_kolmogorovtest 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3D_LabelsDeflate" c_th3d_labelsdeflate 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_LabelsInflate" c_th3d_labelsinflate 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_LabelsOption" c_th3d_labelsoption 
  :: (Ptr RawTH3D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_multiflyF" c_th3d_multiflyf 
  :: (Ptr RawTH3D) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_Multiply" c_th3d_multiply 
  :: (Ptr RawTH3D) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_PutStats" c_th3d_putstats 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_Rebin" c_th3d_rebin 
  :: (Ptr RawTH3D) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_RebinAxis" c_th3d_rebinaxis 
  :: (Ptr RawTH3D) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3D_Rebuild" c_th3d_rebuild 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_Reset" c_th3d_reset 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_ResetStats" c_th3d_resetstats 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_Scale" c_th3d_scale 
  :: (Ptr RawTH3D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_setAxisColorA" c_th3d_setaxiscolora 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetAxisRange" c_th3d_setaxisrange 
  :: (Ptr RawTH3D) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetBarOffset" c_th3d_setbaroffset 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetBarWidth" c_th3d_setbarwidth 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinContent1" c_th3d_setbincontent1 
  :: (Ptr RawTH3D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinContent2" c_th3d_setbincontent2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinContent3" c_th3d_setbincontent3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinError1" c_th3d_setbinerror1 
  :: (Ptr RawTH3D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinError2" c_th3d_setbinerror2 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBinError3" c_th3d_setbinerror3 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_setBins1" c_th3d_setbins1 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_setBins2" c_th3d_setbins2 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_setBins3" c_th3d_setbins3 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_SetBinsLength" c_th3d_setbinslength 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetBuffer" c_th3d_setbuffer 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetCellContent" c_th3d_setcellcontent 
  :: (Ptr RawTH3D) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetContent" c_th3d_setcontent 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_SetContour" c_th3d_setcontour 
  :: (Ptr RawTH3D) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_SetContourLevel" c_th3d_setcontourlevel 
  :: (Ptr RawTH3D) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetDirectory" c_th3d_setdirectory 
  :: (Ptr RawTH3D) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3D_SetEntries" c_th3d_setentries 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetError" c_th3d_seterror 
  :: (Ptr RawTH3D) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3D_setLabelColorA" c_th3d_setlabelcolora 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_setLabelSizeA" c_th3d_setlabelsizea 
  :: (Ptr RawTH3D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_setLabelFontA" c_th3d_setlabelfonta 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_setLabelOffsetA" c_th3d_setlabeloffseta 
  :: (Ptr RawTH3D) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetMaximum" c_th3d_setmaximum 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetMinimum" c_th3d_setminimum 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetNormFactor" c_th3d_setnormfactor 
  :: (Ptr RawTH3D) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3D_SetStats" c_th3d_setstats 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetOption" c_th3d_setoption 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetXTitle" c_th3d_setxtitle 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetYTitle" c_th3d_setytitle 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetZTitle" c_th3d_setztitle 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_ShowBackground" c_th3d_showbackground 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3D_ShowPeaks" c_th3d_showpeaks 
  :: (Ptr RawTH3D) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3D_Smooth" c_th3d_smooth 
  :: (Ptr RawTH3D) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_Sumw2" c_th3d_sumw2 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_SetName" c_th3d_setname 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetNameTitle" c_th3d_setnametitle 
  :: (Ptr RawTH3D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetTitle" c_th3d_settitle 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_GetLineColor" c_th3d_getlinecolor 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetLineStyle" c_th3d_getlinestyle 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetLineWidth" c_th3d_getlinewidth 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_ResetAttLine" c_th3d_resetattline 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetLineAttributes" c_th3d_setlineattributes 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_SetLineColor" c_th3d_setlinecolor 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetLineStyle" c_th3d_setlinestyle 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetLineWidth" c_th3d_setlinewidth 
  :: (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_GetMarkerColor" c_th3d_getmarkercolor 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetMarkerStyle" c_th3d_getmarkerstyle 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_GetMarkerSize" c_th3d_getmarkersize 
  :: (Ptr RawTH3D) -> IO CDouble
foreign import ccall "HROOT.h TH3D_ResetAttMarker" c_th3d_resetattmarker 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_SetMarkerAttributes" c_th3d_setmarkerattributes 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_SetMarkerColor" c_th3d_setmarkercolor 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetMarkerStyle" c_th3d_setmarkerstyle 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_SetMarkerSize" c_th3d_setmarkersize 
  :: (Ptr RawTH3D) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3D_Draw" c_th3d_draw 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_FindObject" c_th3d_findobject 
  :: (Ptr RawTH3D) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3D_GetName" c_th3d_getname 
  :: (Ptr RawTH3D) -> IO CString
foreign import ccall "HROOT.h TH3D_IsA" c_th3d_isa 
  :: (Ptr RawTH3D) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3D_IsFolder" c_th3d_isfolder 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_IsEqual" c_th3d_isequal 
  :: (Ptr RawTH3D) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3D_IsSortable" c_th3d_issortable 
  :: (Ptr RawTH3D) -> IO CInt
foreign import ccall "HROOT.h TH3D_Paint" c_th3d_paint 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_printObj" c_th3d_printobj 
  :: (Ptr RawTH3D) -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_RecursiveRemove" c_th3d_recursiveremove 
  :: (Ptr RawTH3D) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3D_SaveAs" c_th3d_saveas 
  :: (Ptr RawTH3D) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3D_UseCurrentStyle" c_th3d_usecurrentstyle 
  :: (Ptr RawTH3D) -> IO ()
foreign import ccall "HROOT.h TH3D_Write" c_th3d_write 
  :: (Ptr RawTH3D) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3D_delete" c_th3d_delete 
  :: (Ptr RawTH3D) -> IO ()

foreign import ccall "HROOT.h TH3F_fill3" c_th3f_fill3 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_fill3w" c_th3f_fill3w 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FitSlicesZ" c_th3f_fitslicesz 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_getCorrelationFactor3" c_th3f_getcorrelationfactor3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_getCovariance3" c_th3f_getcovariance3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_rebinX3" c_th3f_rebinx3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3F_rebinY3" c_th3f_rebiny3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3F_rebinZ3" c_th3f_rebinz3 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3F_Rebin3D" c_th3f_rebin3d 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3F_Add" c_th3f_add 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_AddBinContent" c_th3f_addbincontent 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_Chi2Test" c_th3f_chi2test 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3F_ComputeIntegral" c_th3f_computeintegral 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_DirectoryAutoAdd" c_th3f_directoryautoadd 
  :: (Ptr RawTH3F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3F_Divide" c_th3f_divide 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_drawCopyTH1" c_th3f_drawcopyth1 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTH3F)
foreign import ccall "HROOT.h TH3F_DrawNormalized" c_th3f_drawnormalized 
  :: (Ptr RawTH3F) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_drawPanelTH1" c_th3f_drawpanelth1 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_BufferEmpty" c_th3f_bufferempty 
  :: (Ptr RawTH3F) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_evalF" c_th3f_evalf 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_FFT" c_th3f_fft 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_fill1" c_th3f_fill1 
  :: (Ptr RawTH3F) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_fill1w" c_th3f_fill1w 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_fillN1" c_th3f_filln1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_FillRandom" c_th3f_fillrandom 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_FindBin" c_th3f_findbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FindFixBin" c_th3f_findfixbin 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_FindFirstBinAbove" c_th3f_findfirstbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_FindLastBinAbove" c_th3f_findlastbinabove 
  :: (Ptr RawTH3F) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_FitPanelTH1" c_th3f_fitpanelth1 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_getNdivisionA" c_th3f_getndivisiona 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_getAxisColorA" c_th3f_getaxiscolora 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_getLabelColorA" c_th3f_getlabelcolora 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_getLabelFontA" c_th3f_getlabelfonta 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_getLabelOffsetA" c_th3f_getlabeloffseta 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_getLabelSizeA" c_th3f_getlabelsizea 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_getTitleFontA" c_th3f_gettitlefonta 
  :: (Ptr RawTH3F) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3F_getTitleOffsetA" c_th3f_gettitleoffseta 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_getTitleSizeA" c_th3f_gettitlesizea 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_getTickLengthA" c_th3f_getticklengtha 
  :: (Ptr RawTH3F) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBarOffset" c_th3f_getbaroffset 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBarWidth" c_th3f_getbarwidth 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetContour" c_th3f_getcontour 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetContourLevel" c_th3f_getcontourlevel 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetContourLevelPad" c_th3f_getcontourlevelpad 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBin" c_th3f_getbin 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_GetBinCenter" c_th3f_getbincenter 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent1" c_th3f_getbincontent1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent2" c_th3f_getbincontent2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinContent3" c_th3f_getbincontent3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError1" c_th3f_getbinerror1 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError2" c_th3f_getbinerror2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinError3" c_th3f_getbinerror3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinLowEdge" c_th3f_getbinlowedge 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetBinWidth" c_th3f_getbinwidth 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetCellContent" c_th3f_getcellcontent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetCellError" c_th3f_getcellerror 
  :: (Ptr RawTH3F) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetEntries" c_th3f_getentries 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetEffectiveEntries" c_th3f_geteffectiveentries 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetFunction" c_th3f_getfunction 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3F_GetDimension" c_th3f_getdimension 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetKurtosis" c_th3f_getkurtosis 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetLowEdge" c_th3f_getlowedge 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_getMaximumTH1" c_th3f_getmaximumth1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetMaximumBin" c_th3f_getmaximumbin 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetMaximumStored" c_th3f_getmaximumstored 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_getMinimumTH1" c_th3f_getminimumth1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetMinimumBin" c_th3f_getminimumbin 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetMinimumStored" c_th3f_getminimumstored 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetMean" c_th3f_getmean 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetMeanError" c_th3f_getmeanerror 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetNbinsX" c_th3f_getnbinsx 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetNbinsY" c_th3f_getnbinsy 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetNbinsZ" c_th3f_getnbinsz 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_getQuantilesTH1" c_th3f_getquantilesth1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetRandom" c_th3f_getrandom 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetStats" c_th3f_getstats 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_GetSumOfWeights" c_th3f_getsumofweights 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetSumw2" c_th3f_getsumw2 
  :: (Ptr RawTH3F) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3F_GetSumw2N" c_th3f_getsumw2n 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetRMS" c_th3f_getrms 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetRMSError" c_th3f_getrmserror 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_GetSkewness" c_th3f_getskewness 
  :: (Ptr RawTH3F) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3F_integral1" c_th3f_integral1 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_interpolate1" c_th3f_interpolate1 
  :: (Ptr RawTH3F) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3F_interpolate2" c_th3f_interpolate2 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3F_interpolate3" c_th3f_interpolate3 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3F_KolmogorovTest" c_th3f_kolmogorovtest 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3F_LabelsDeflate" c_th3f_labelsdeflate 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_LabelsInflate" c_th3f_labelsinflate 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_LabelsOption" c_th3f_labelsoption 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_multiflyF" c_th3f_multiflyf 
  :: (Ptr RawTH3F) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_Multiply" c_th3f_multiply 
  :: (Ptr RawTH3F) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_PutStats" c_th3f_putstats 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_Rebin" c_th3f_rebin 
  :: (Ptr RawTH3F) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_RebinAxis" c_th3f_rebinaxis 
  :: (Ptr RawTH3F) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3F_Rebuild" c_th3f_rebuild 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_Reset" c_th3f_reset 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_ResetStats" c_th3f_resetstats 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_Scale" c_th3f_scale 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_setAxisColorA" c_th3f_setaxiscolora 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetAxisRange" c_th3f_setaxisrange 
  :: (Ptr RawTH3F) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetBarOffset" c_th3f_setbaroffset 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetBarWidth" c_th3f_setbarwidth 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinContent1" c_th3f_setbincontent1 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinContent2" c_th3f_setbincontent2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinContent3" c_th3f_setbincontent3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinError1" c_th3f_setbinerror1 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinError2" c_th3f_setbinerror2 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBinError3" c_th3f_setbinerror3 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_setBins1" c_th3f_setbins1 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_setBins2" c_th3f_setbins2 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_setBins3" c_th3f_setbins3 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_SetBinsLength" c_th3f_setbinslength 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetBuffer" c_th3f_setbuffer 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetCellContent" c_th3f_setcellcontent 
  :: (Ptr RawTH3F) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetContent" c_th3f_setcontent 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_SetContour" c_th3f_setcontour 
  :: (Ptr RawTH3F) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_SetContourLevel" c_th3f_setcontourlevel 
  :: (Ptr RawTH3F) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetDirectory" c_th3f_setdirectory 
  :: (Ptr RawTH3F) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3F_SetEntries" c_th3f_setentries 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetError" c_th3f_seterror 
  :: (Ptr RawTH3F) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3F_setLabelColorA" c_th3f_setlabelcolora 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_setLabelSizeA" c_th3f_setlabelsizea 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_setLabelFontA" c_th3f_setlabelfonta 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_setLabelOffsetA" c_th3f_setlabeloffseta 
  :: (Ptr RawTH3F) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetMaximum" c_th3f_setmaximum 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetMinimum" c_th3f_setminimum 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetNormFactor" c_th3f_setnormfactor 
  :: (Ptr RawTH3F) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3F_SetStats" c_th3f_setstats 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetOption" c_th3f_setoption 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetXTitle" c_th3f_setxtitle 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetYTitle" c_th3f_setytitle 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetZTitle" c_th3f_setztitle 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_ShowBackground" c_th3f_showbackground 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3F_ShowPeaks" c_th3f_showpeaks 
  :: (Ptr RawTH3F) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3F_Smooth" c_th3f_smooth 
  :: (Ptr RawTH3F) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_Sumw2" c_th3f_sumw2 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_SetName" c_th3f_setname 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetNameTitle" c_th3f_setnametitle 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetTitle" c_th3f_settitle 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_GetLineColor" c_th3f_getlinecolor 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetLineStyle" c_th3f_getlinestyle 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetLineWidth" c_th3f_getlinewidth 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_ResetAttLine" c_th3f_resetattline 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetLineAttributes" c_th3f_setlineattributes 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_SetLineColor" c_th3f_setlinecolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetLineStyle" c_th3f_setlinestyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetLineWidth" c_th3f_setlinewidth 
  :: (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_GetMarkerColor" c_th3f_getmarkercolor 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetMarkerStyle" c_th3f_getmarkerstyle 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_GetMarkerSize" c_th3f_getmarkersize 
  :: (Ptr RawTH3F) -> IO CDouble
foreign import ccall "HROOT.h TH3F_ResetAttMarker" c_th3f_resetattmarker 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_SetMarkerAttributes" c_th3f_setmarkerattributes 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_SetMarkerColor" c_th3f_setmarkercolor 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetMarkerStyle" c_th3f_setmarkerstyle 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_SetMarkerSize" c_th3f_setmarkersize 
  :: (Ptr RawTH3F) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3F_Draw" c_th3f_draw 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_FindObject" c_th3f_findobject 
  :: (Ptr RawTH3F) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3F_GetName" c_th3f_getname 
  :: (Ptr RawTH3F) -> IO CString
foreign import ccall "HROOT.h TH3F_IsA" c_th3f_isa 
  :: (Ptr RawTH3F) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3F_IsFolder" c_th3f_isfolder 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_IsEqual" c_th3f_isequal 
  :: (Ptr RawTH3F) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3F_IsSortable" c_th3f_issortable 
  :: (Ptr RawTH3F) -> IO CInt
foreign import ccall "HROOT.h TH3F_Paint" c_th3f_paint 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_printObj" c_th3f_printobj 
  :: (Ptr RawTH3F) -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_RecursiveRemove" c_th3f_recursiveremove 
  :: (Ptr RawTH3F) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3F_SaveAs" c_th3f_saveas 
  :: (Ptr RawTH3F) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3F_UseCurrentStyle" c_th3f_usecurrentstyle 
  :: (Ptr RawTH3F) -> IO ()
foreign import ccall "HROOT.h TH3F_Write" c_th3f_write 
  :: (Ptr RawTH3F) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3F_delete" c_th3f_delete 
  :: (Ptr RawTH3F) -> IO ()

foreign import ccall "HROOT.h TH3I_fill3" c_th3i_fill3 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_fill3w" c_th3i_fill3w 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FitSlicesZ" c_th3i_fitslicesz 
  :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_getCorrelationFactor3" c_th3i_getcorrelationfactor3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_getCovariance3" c_th3i_getcovariance3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_rebinX3" c_th3i_rebinx3 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3I_rebinY3" c_th3i_rebiny3 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3I_rebinZ3" c_th3i_rebinz3 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3I_Rebin3D" c_th3i_rebin3d 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3I_Add" c_th3i_add 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_AddBinContent" c_th3i_addbincontent 
  :: (Ptr RawTH3I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_Chi2Test" c_th3i_chi2test 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3I_ComputeIntegral" c_th3i_computeintegral 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_DirectoryAutoAdd" c_th3i_directoryautoadd 
  :: (Ptr RawTH3I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3I_Divide" c_th3i_divide 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_drawCopyTH1" c_th3i_drawcopyth1 
  :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTH3I)
foreign import ccall "HROOT.h TH3I_DrawNormalized" c_th3i_drawnormalized 
  :: (Ptr RawTH3I) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_drawPanelTH1" c_th3i_drawpanelth1 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_BufferEmpty" c_th3i_bufferempty 
  :: (Ptr RawTH3I) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_evalF" c_th3i_evalf 
  :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_FFT" c_th3i_fft 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_fill1" c_th3i_fill1 
  :: (Ptr RawTH3I) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_fill1w" c_th3i_fill1w 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_fillN1" c_th3i_filln1 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_FillRandom" c_th3i_fillrandom 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_FindBin" c_th3i_findbin 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FindFixBin" c_th3i_findfixbin 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_FindFirstBinAbove" c_th3i_findfirstbinabove 
  :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_FindLastBinAbove" c_th3i_findlastbinabove 
  :: (Ptr RawTH3I) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_FitPanelTH1" c_th3i_fitpanelth1 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_getNdivisionA" c_th3i_getndivisiona 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_getAxisColorA" c_th3i_getaxiscolora 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_getLabelColorA" c_th3i_getlabelcolora 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_getLabelFontA" c_th3i_getlabelfonta 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_getLabelOffsetA" c_th3i_getlabeloffseta 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_getLabelSizeA" c_th3i_getlabelsizea 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_getTitleFontA" c_th3i_gettitlefonta 
  :: (Ptr RawTH3I) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3I_getTitleOffsetA" c_th3i_gettitleoffseta 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_getTitleSizeA" c_th3i_gettitlesizea 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_getTickLengthA" c_th3i_getticklengtha 
  :: (Ptr RawTH3I) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBarOffset" c_th3i_getbaroffset 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBarWidth" c_th3i_getbarwidth 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetContour" c_th3i_getcontour 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetContourLevel" c_th3i_getcontourlevel 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetContourLevelPad" c_th3i_getcontourlevelpad 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBin" c_th3i_getbin 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_GetBinCenter" c_th3i_getbincenter 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent1" c_th3i_getbincontent1 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent2" c_th3i_getbincontent2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinContent3" c_th3i_getbincontent3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError1" c_th3i_getbinerror1 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError2" c_th3i_getbinerror2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinError3" c_th3i_getbinerror3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinLowEdge" c_th3i_getbinlowedge 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetBinWidth" c_th3i_getbinwidth 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetCellContent" c_th3i_getcellcontent 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetCellError" c_th3i_getcellerror 
  :: (Ptr RawTH3I) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetEntries" c_th3i_getentries 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetEffectiveEntries" c_th3i_geteffectiveentries 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetFunction" c_th3i_getfunction 
  :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3I_GetDimension" c_th3i_getdimension 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetKurtosis" c_th3i_getkurtosis 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetLowEdge" c_th3i_getlowedge 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_getMaximumTH1" c_th3i_getmaximumth1 
  :: (Ptr RawTH3I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetMaximumBin" c_th3i_getmaximumbin 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetMaximumStored" c_th3i_getmaximumstored 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_getMinimumTH1" c_th3i_getminimumth1 
  :: (Ptr RawTH3I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetMinimumBin" c_th3i_getminimumbin 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetMinimumStored" c_th3i_getminimumstored 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetMean" c_th3i_getmean 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetMeanError" c_th3i_getmeanerror 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetNbinsX" c_th3i_getnbinsx 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetNbinsY" c_th3i_getnbinsy 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetNbinsZ" c_th3i_getnbinsz 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_getQuantilesTH1" c_th3i_getquantilesth1 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetRandom" c_th3i_getrandom 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetStats" c_th3i_getstats 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_GetSumOfWeights" c_th3i_getsumofweights 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetSumw2" c_th3i_getsumw2 
  :: (Ptr RawTH3I) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3I_GetSumw2N" c_th3i_getsumw2n 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetRMS" c_th3i_getrms 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetRMSError" c_th3i_getrmserror 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_GetSkewness" c_th3i_getskewness 
  :: (Ptr RawTH3I) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3I_integral1" c_th3i_integral1 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_interpolate1" c_th3i_interpolate1 
  :: (Ptr RawTH3I) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3I_interpolate2" c_th3i_interpolate2 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3I_interpolate3" c_th3i_interpolate3 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3I_KolmogorovTest" c_th3i_kolmogorovtest 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3I_LabelsDeflate" c_th3i_labelsdeflate 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_LabelsInflate" c_th3i_labelsinflate 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_LabelsOption" c_th3i_labelsoption 
  :: (Ptr RawTH3I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_multiflyF" c_th3i_multiflyf 
  :: (Ptr RawTH3I) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_Multiply" c_th3i_multiply 
  :: (Ptr RawTH3I) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_PutStats" c_th3i_putstats 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_Rebin" c_th3i_rebin 
  :: (Ptr RawTH3I) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_RebinAxis" c_th3i_rebinaxis 
  :: (Ptr RawTH3I) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3I_Rebuild" c_th3i_rebuild 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_Reset" c_th3i_reset 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_ResetStats" c_th3i_resetstats 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_Scale" c_th3i_scale 
  :: (Ptr RawTH3I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_setAxisColorA" c_th3i_setaxiscolora 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetAxisRange" c_th3i_setaxisrange 
  :: (Ptr RawTH3I) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetBarOffset" c_th3i_setbaroffset 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetBarWidth" c_th3i_setbarwidth 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinContent1" c_th3i_setbincontent1 
  :: (Ptr RawTH3I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinContent2" c_th3i_setbincontent2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinContent3" c_th3i_setbincontent3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinError1" c_th3i_setbinerror1 
  :: (Ptr RawTH3I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinError2" c_th3i_setbinerror2 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBinError3" c_th3i_setbinerror3 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_setBins1" c_th3i_setbins1 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_setBins2" c_th3i_setbins2 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_setBins3" c_th3i_setbins3 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_SetBinsLength" c_th3i_setbinslength 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetBuffer" c_th3i_setbuffer 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetCellContent" c_th3i_setcellcontent 
  :: (Ptr RawTH3I) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetContent" c_th3i_setcontent 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_SetContour" c_th3i_setcontour 
  :: (Ptr RawTH3I) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_SetContourLevel" c_th3i_setcontourlevel 
  :: (Ptr RawTH3I) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetDirectory" c_th3i_setdirectory 
  :: (Ptr RawTH3I) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3I_SetEntries" c_th3i_setentries 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetError" c_th3i_seterror 
  :: (Ptr RawTH3I) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3I_setLabelColorA" c_th3i_setlabelcolora 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_setLabelSizeA" c_th3i_setlabelsizea 
  :: (Ptr RawTH3I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_setLabelFontA" c_th3i_setlabelfonta 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_setLabelOffsetA" c_th3i_setlabeloffseta 
  :: (Ptr RawTH3I) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetMaximum" c_th3i_setmaximum 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetMinimum" c_th3i_setminimum 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetNormFactor" c_th3i_setnormfactor 
  :: (Ptr RawTH3I) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3I_SetStats" c_th3i_setstats 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetOption" c_th3i_setoption 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetXTitle" c_th3i_setxtitle 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetYTitle" c_th3i_setytitle 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetZTitle" c_th3i_setztitle 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_ShowBackground" c_th3i_showbackground 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3I_ShowPeaks" c_th3i_showpeaks 
  :: (Ptr RawTH3I) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3I_Smooth" c_th3i_smooth 
  :: (Ptr RawTH3I) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_Sumw2" c_th3i_sumw2 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_SetName" c_th3i_setname 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetNameTitle" c_th3i_setnametitle 
  :: (Ptr RawTH3I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetTitle" c_th3i_settitle 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_GetLineColor" c_th3i_getlinecolor 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetLineStyle" c_th3i_getlinestyle 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetLineWidth" c_th3i_getlinewidth 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_ResetAttLine" c_th3i_resetattline 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetLineAttributes" c_th3i_setlineattributes 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_SetLineColor" c_th3i_setlinecolor 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetLineStyle" c_th3i_setlinestyle 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetLineWidth" c_th3i_setlinewidth 
  :: (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_GetMarkerColor" c_th3i_getmarkercolor 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetMarkerStyle" c_th3i_getmarkerstyle 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_GetMarkerSize" c_th3i_getmarkersize 
  :: (Ptr RawTH3I) -> IO CDouble
foreign import ccall "HROOT.h TH3I_ResetAttMarker" c_th3i_resetattmarker 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_SetMarkerAttributes" c_th3i_setmarkerattributes 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_SetMarkerColor" c_th3i_setmarkercolor 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetMarkerStyle" c_th3i_setmarkerstyle 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_SetMarkerSize" c_th3i_setmarkersize 
  :: (Ptr RawTH3I) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3I_Draw" c_th3i_draw 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_FindObject" c_th3i_findobject 
  :: (Ptr RawTH3I) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3I_GetName" c_th3i_getname 
  :: (Ptr RawTH3I) -> IO CString
foreign import ccall "HROOT.h TH3I_IsA" c_th3i_isa 
  :: (Ptr RawTH3I) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3I_IsFolder" c_th3i_isfolder 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_IsEqual" c_th3i_isequal 
  :: (Ptr RawTH3I) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3I_IsSortable" c_th3i_issortable 
  :: (Ptr RawTH3I) -> IO CInt
foreign import ccall "HROOT.h TH3I_Paint" c_th3i_paint 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_printObj" c_th3i_printobj 
  :: (Ptr RawTH3I) -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_RecursiveRemove" c_th3i_recursiveremove 
  :: (Ptr RawTH3I) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3I_SaveAs" c_th3i_saveas 
  :: (Ptr RawTH3I) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3I_UseCurrentStyle" c_th3i_usecurrentstyle 
  :: (Ptr RawTH3I) -> IO ()
foreign import ccall "HROOT.h TH3I_Write" c_th3i_write 
  :: (Ptr RawTH3I) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3I_delete" c_th3i_delete 
  :: (Ptr RawTH3I) -> IO ()

foreign import ccall "HROOT.h TH3S_fill3" c_th3s_fill3 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_fill3w" c_th3s_fill3w 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FitSlicesZ" c_th3s_fitslicesz 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CInt -> CInt -> CInt -> CInt -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_getCorrelationFactor3" c_th3s_getcorrelationfactor3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_getCovariance3" c_th3s_getcovariance3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_rebinX3" c_th3s_rebinx3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3S_rebinY3" c_th3s_rebiny3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3S_rebinZ3" c_th3s_rebinz3 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3S_Rebin3D" c_th3s_rebin3d 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CString -> IO (Ptr RawTH3)
foreign import ccall "HROOT.h TH3S_Add" c_th3s_add 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_AddBinContent" c_th3s_addbincontent 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_Chi2Test" c_th3s_chi2test 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> (Ptr CDouble) -> IO CDouble
foreign import ccall "HROOT.h TH3S_ComputeIntegral" c_th3s_computeintegral 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_DirectoryAutoAdd" c_th3s_directoryautoadd 
  :: (Ptr RawTH3S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3S_Divide" c_th3s_divide 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> (Ptr RawTH2) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_drawCopyTH1" c_th3s_drawcopyth1 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTH3S)
foreign import ccall "HROOT.h TH3S_DrawNormalized" c_th3s_drawnormalized 
  :: (Ptr RawTH3S) -> CString -> CDouble -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_drawPanelTH1" c_th3s_drawpanelth1 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_BufferEmpty" c_th3s_bufferempty 
  :: (Ptr RawTH3S) -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_evalF" c_th3s_evalf 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_FFT" c_th3s_fft 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_fill1" c_th3s_fill1 
  :: (Ptr RawTH3S) -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_fill1w" c_th3s_fill1w 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_fillN1" c_th3s_filln1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_FillRandom" c_th3s_fillrandom 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_FindBin" c_th3s_findbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FindFixBin" c_th3s_findfixbin 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_FindFirstBinAbove" c_th3s_findfirstbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_FindLastBinAbove" c_th3s_findlastbinabove 
  :: (Ptr RawTH3S) -> CDouble -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_FitPanelTH1" c_th3s_fitpanelth1 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_getNdivisionA" c_th3s_getndivisiona 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_getAxisColorA" c_th3s_getaxiscolora 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_getLabelColorA" c_th3s_getlabelcolora 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_getLabelFontA" c_th3s_getlabelfonta 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_getLabelOffsetA" c_th3s_getlabeloffseta 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_getLabelSizeA" c_th3s_getlabelsizea 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_getTitleFontA" c_th3s_gettitlefonta 
  :: (Ptr RawTH3S) -> CString -> IO CInt
foreign import ccall "HROOT.h TH3S_getTitleOffsetA" c_th3s_gettitleoffseta 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_getTitleSizeA" c_th3s_gettitlesizea 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_getTickLengthA" c_th3s_getticklengtha 
  :: (Ptr RawTH3S) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBarOffset" c_th3s_getbaroffset 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBarWidth" c_th3s_getbarwidth 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetContour" c_th3s_getcontour 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetContourLevel" c_th3s_getcontourlevel 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetContourLevelPad" c_th3s_getcontourlevelpad 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBin" c_th3s_getbin 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_GetBinCenter" c_th3s_getbincenter 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent1" c_th3s_getbincontent1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent2" c_th3s_getbincontent2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinContent3" c_th3s_getbincontent3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError1" c_th3s_getbinerror1 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError2" c_th3s_getbinerror2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinError3" c_th3s_getbinerror3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinLowEdge" c_th3s_getbinlowedge 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetBinWidth" c_th3s_getbinwidth 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetCellContent" c_th3s_getcellcontent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetCellError" c_th3s_getcellerror 
  :: (Ptr RawTH3S) -> CInt -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetEntries" c_th3s_getentries 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetEffectiveEntries" c_th3s_geteffectiveentries 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetFunction" c_th3s_getfunction 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTF1)
foreign import ccall "HROOT.h TH3S_GetDimension" c_th3s_getdimension 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetKurtosis" c_th3s_getkurtosis 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetLowEdge" c_th3s_getlowedge 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_getMaximumTH1" c_th3s_getmaximumth1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetMaximumBin" c_th3s_getmaximumbin 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetMaximumStored" c_th3s_getmaximumstored 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_getMinimumTH1" c_th3s_getminimumth1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetMinimumBin" c_th3s_getminimumbin 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetMinimumStored" c_th3s_getminimumstored 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetMean" c_th3s_getmean 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetMeanError" c_th3s_getmeanerror 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetNbinsX" c_th3s_getnbinsx 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetNbinsY" c_th3s_getnbinsy 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetNbinsZ" c_th3s_getnbinsz 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_getQuantilesTH1" c_th3s_getquantilesth1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetRandom" c_th3s_getrandom 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetStats" c_th3s_getstats 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_GetSumOfWeights" c_th3s_getsumofweights 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetSumw2" c_th3s_getsumw2 
  :: (Ptr RawTH3S) -> IO (Ptr RawTArrayD)
foreign import ccall "HROOT.h TH3S_GetSumw2N" c_th3s_getsumw2n 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetRMS" c_th3s_getrms 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetRMSError" c_th3s_getrmserror 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_GetSkewness" c_th3s_getskewness 
  :: (Ptr RawTH3S) -> CInt -> IO CDouble
foreign import ccall "HROOT.h TH3S_integral1" c_th3s_integral1 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_interpolate1" c_th3s_interpolate1 
  :: (Ptr RawTH3S) -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3S_interpolate2" c_th3s_interpolate2 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3S_interpolate3" c_th3s_interpolate3 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TH3S_KolmogorovTest" c_th3s_kolmogorovtest 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> CString -> IO CDouble
foreign import ccall "HROOT.h TH3S_LabelsDeflate" c_th3s_labelsdeflate 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_LabelsInflate" c_th3s_labelsinflate 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_LabelsOption" c_th3s_labelsoption 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_multiflyF" c_th3s_multiflyf 
  :: (Ptr RawTH3S) -> (Ptr RawTF1) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_Multiply" c_th3s_multiply 
  :: (Ptr RawTH3S) -> (Ptr RawTH1) -> (Ptr RawTH1) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_PutStats" c_th3s_putstats 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_Rebin" c_th3s_rebin 
  :: (Ptr RawTH3S) -> CInt -> CString -> (Ptr CDouble) -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_RebinAxis" c_th3s_rebinaxis 
  :: (Ptr RawTH3S) -> CDouble -> (Ptr RawTAxis) -> IO ()
foreign import ccall "HROOT.h TH3S_Rebuild" c_th3s_rebuild 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_Reset" c_th3s_reset 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_ResetStats" c_th3s_resetstats 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_Scale" c_th3s_scale 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_setAxisColorA" c_th3s_setaxiscolora 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetAxisRange" c_th3s_setaxisrange 
  :: (Ptr RawTH3S) -> CDouble -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetBarOffset" c_th3s_setbaroffset 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetBarWidth" c_th3s_setbarwidth 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinContent1" c_th3s_setbincontent1 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinContent2" c_th3s_setbincontent2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinContent3" c_th3s_setbincontent3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinError1" c_th3s_setbinerror1 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinError2" c_th3s_setbinerror2 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBinError3" c_th3s_setbinerror3 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_setBins1" c_th3s_setbins1 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_setBins2" c_th3s_setbins2 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_setBins3" c_th3s_setbins3 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_SetBinsLength" c_th3s_setbinslength 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetBuffer" c_th3s_setbuffer 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetCellContent" c_th3s_setcellcontent 
  :: (Ptr RawTH3S) -> CInt -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetContent" c_th3s_setcontent 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_SetContour" c_th3s_setcontour 
  :: (Ptr RawTH3S) -> CInt -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_SetContourLevel" c_th3s_setcontourlevel 
  :: (Ptr RawTH3S) -> CInt -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetDirectory" c_th3s_setdirectory 
  :: (Ptr RawTH3S) -> (Ptr RawTDirectory) -> IO ()
foreign import ccall "HROOT.h TH3S_SetEntries" c_th3s_setentries 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetError" c_th3s_seterror 
  :: (Ptr RawTH3S) -> (Ptr CDouble) -> IO ()
foreign import ccall "HROOT.h TH3S_setLabelColorA" c_th3s_setlabelcolora 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_setLabelSizeA" c_th3s_setlabelsizea 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_setLabelFontA" c_th3s_setlabelfonta 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_setLabelOffsetA" c_th3s_setlabeloffseta 
  :: (Ptr RawTH3S) -> CDouble -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetMaximum" c_th3s_setmaximum 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetMinimum" c_th3s_setminimum 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetNormFactor" c_th3s_setnormfactor 
  :: (Ptr RawTH3S) -> CDouble -> IO ()
foreign import ccall "HROOT.h TH3S_SetStats" c_th3s_setstats 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetOption" c_th3s_setoption 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetXTitle" c_th3s_setxtitle 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetYTitle" c_th3s_setytitle 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetZTitle" c_th3s_setztitle 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_ShowBackground" c_th3s_showbackground 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO (Ptr RawTH1)
foreign import ccall "HROOT.h TH3S_ShowPeaks" c_th3s_showpeaks 
  :: (Ptr RawTH3S) -> CDouble -> CString -> CDouble -> IO CInt
foreign import ccall "HROOT.h TH3S_Smooth" c_th3s_smooth 
  :: (Ptr RawTH3S) -> CInt -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_Sumw2" c_th3s_sumw2 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_SetName" c_th3s_setname 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetNameTitle" c_th3s_setnametitle 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetTitle" c_th3s_settitle 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_GetLineColor" c_th3s_getlinecolor 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetLineStyle" c_th3s_getlinestyle 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetLineWidth" c_th3s_getlinewidth 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_ResetAttLine" c_th3s_resetattline 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetLineAttributes" c_th3s_setlineattributes 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_SetLineColor" c_th3s_setlinecolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetLineStyle" c_th3s_setlinestyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetLineWidth" c_th3s_setlinewidth 
  :: (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_GetMarkerColor" c_th3s_getmarkercolor 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetMarkerStyle" c_th3s_getmarkerstyle 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_GetMarkerSize" c_th3s_getmarkersize 
  :: (Ptr RawTH3S) -> IO CDouble
foreign import ccall "HROOT.h TH3S_ResetAttMarker" c_th3s_resetattmarker 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_SetMarkerAttributes" c_th3s_setmarkerattributes 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_SetMarkerColor" c_th3s_setmarkercolor 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetMarkerStyle" c_th3s_setmarkerstyle 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_SetMarkerSize" c_th3s_setmarkersize 
  :: (Ptr RawTH3S) -> CInt -> IO ()
foreign import ccall "HROOT.h TH3S_Draw" c_th3s_draw 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_FindObject" c_th3s_findobject 
  :: (Ptr RawTH3S) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TH3S_GetName" c_th3s_getname 
  :: (Ptr RawTH3S) -> IO CString
foreign import ccall "HROOT.h TH3S_IsA" c_th3s_isa 
  :: (Ptr RawTH3S) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TH3S_IsFolder" c_th3s_isfolder 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_IsEqual" c_th3s_isequal 
  :: (Ptr RawTH3S) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TH3S_IsSortable" c_th3s_issortable 
  :: (Ptr RawTH3S) -> IO CInt
foreign import ccall "HROOT.h TH3S_Paint" c_th3s_paint 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_printObj" c_th3s_printobj 
  :: (Ptr RawTH3S) -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_RecursiveRemove" c_th3s_recursiveremove 
  :: (Ptr RawTH3S) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TH3S_SaveAs" c_th3s_saveas 
  :: (Ptr RawTH3S) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TH3S_UseCurrentStyle" c_th3s_usecurrentstyle 
  :: (Ptr RawTH3S) -> IO ()
foreign import ccall "HROOT.h TH3S_Write" c_th3s_write 
  :: (Ptr RawTH3S) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TH3S_delete" c_th3s_delete 
  :: (Ptr RawTH3S) -> IO ()

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

foreign import ccall "HROOT.h TVirtualPad_Draw" c_tvirtualpad_draw 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_FindObject" c_tvirtualpad_findobject 
  :: (Ptr RawTVirtualPad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TVirtualPad_GetName" c_tvirtualpad_getname 
  :: (Ptr RawTVirtualPad) -> IO CString
foreign import ccall "HROOT.h TVirtualPad_IsA" c_tvirtualpad_isa 
  :: (Ptr RawTVirtualPad) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TVirtualPad_IsFolder" c_tvirtualpad_isfolder 
  :: (Ptr RawTVirtualPad) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_IsEqual" c_tvirtualpad_isequal 
  :: (Ptr RawTVirtualPad) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_IsSortable" c_tvirtualpad_issortable 
  :: (Ptr RawTVirtualPad) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_Paint" c_tvirtualpad_paint 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_printObj" c_tvirtualpad_printobj 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_RecursiveRemove" c_tvirtualpad_recursiveremove 
  :: (Ptr RawTVirtualPad) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SaveAs" c_tvirtualpad_saveas 
  :: (Ptr RawTVirtualPad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_UseCurrentStyle" c_tvirtualpad_usecurrentstyle 
  :: (Ptr RawTVirtualPad) -> IO ()
foreign import ccall "HROOT.h TVirtualPad_Write" c_tvirtualpad_write 
  :: (Ptr RawTVirtualPad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_GetLineColor" c_tvirtualpad_getlinecolor 
  :: (Ptr RawTVirtualPad) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_GetLineStyle" c_tvirtualpad_getlinestyle 
  :: (Ptr RawTVirtualPad) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_GetLineWidth" c_tvirtualpad_getlinewidth 
  :: (Ptr RawTVirtualPad) -> IO CInt
foreign import ccall "HROOT.h TVirtualPad_ResetAttLine" c_tvirtualpad_resetattline 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetLineAttributes" c_tvirtualpad_setlineattributes 
  :: (Ptr RawTVirtualPad) -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetLineColor" c_tvirtualpad_setlinecolor 
  :: (Ptr RawTVirtualPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetLineStyle" c_tvirtualpad_setlinestyle 
  :: (Ptr RawTVirtualPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetLineWidth" c_tvirtualpad_setlinewidth 
  :: (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_ResetAttPad" c_tvirtualpad_resetattpad 
  :: (Ptr RawTVirtualPad) -> CString -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetBottomMargin" c_tvirtualpad_setbottommargin 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetLeftMargin" c_tvirtualpad_setleftmargin 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetRightMargin" c_tvirtualpad_setrightmargin 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetTopMargin" c_tvirtualpad_settopmargin 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetMargin" c_tvirtualpad_setmargin 
  :: (Ptr RawTVirtualPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetAfile" c_tvirtualpad_setafile 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetXfile" c_tvirtualpad_setxfile 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetYfile" c_tvirtualpad_setyfile 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetAstat" c_tvirtualpad_setastat 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetXstat" c_tvirtualpad_setxstat 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_SetYstat" c_tvirtualpad_setystat 
  :: (Ptr RawTVirtualPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TVirtualPad_delete" c_tvirtualpad_delete 
  :: (Ptr RawTVirtualPad) -> IO ()
foreign import ccall "HROOT.h TVirtualPad_GetFrame" c_tvirtualpad_getframe 
  :: (Ptr RawTVirtualPad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TVirtualPad_Range" c_tvirtualpad_range 
  :: (Ptr RawTVirtualPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOT.h TPad_GetFrame" c_tpad_getframe 
  :: (Ptr RawTPad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TPad_Range" c_tpad_range 
  :: (Ptr RawTPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_Draw" c_tpad_draw 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_FindObject" c_tpad_findobject 
  :: (Ptr RawTPad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TPad_GetName" c_tpad_getname 
  :: (Ptr RawTPad) -> IO CString
foreign import ccall "HROOT.h TPad_IsA" c_tpad_isa 
  :: (Ptr RawTPad) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TPad_IsFolder" c_tpad_isfolder 
  :: (Ptr RawTPad) -> IO CInt
foreign import ccall "HROOT.h TPad_IsEqual" c_tpad_isequal 
  :: (Ptr RawTPad) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TPad_IsSortable" c_tpad_issortable 
  :: (Ptr RawTPad) -> IO CInt
foreign import ccall "HROOT.h TPad_Paint" c_tpad_paint 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_printObj" c_tpad_printobj 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_RecursiveRemove" c_tpad_recursiveremove 
  :: (Ptr RawTPad) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TPad_SaveAs" c_tpad_saveas 
  :: (Ptr RawTPad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TPad_UseCurrentStyle" c_tpad_usecurrentstyle 
  :: (Ptr RawTPad) -> IO ()
foreign import ccall "HROOT.h TPad_Write" c_tpad_write 
  :: (Ptr RawTPad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TPad_GetLineColor" c_tpad_getlinecolor 
  :: (Ptr RawTPad) -> IO CInt
foreign import ccall "HROOT.h TPad_GetLineStyle" c_tpad_getlinestyle 
  :: (Ptr RawTPad) -> IO CInt
foreign import ccall "HROOT.h TPad_GetLineWidth" c_tpad_getlinewidth 
  :: (Ptr RawTPad) -> IO CInt
foreign import ccall "HROOT.h TPad_ResetAttLine" c_tpad_resetattline 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_SetLineAttributes" c_tpad_setlineattributes 
  :: (Ptr RawTPad) -> IO ()
foreign import ccall "HROOT.h TPad_SetLineColor" c_tpad_setlinecolor 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetLineStyle" c_tpad_setlinestyle 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetLineWidth" c_tpad_setlinewidth 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetFillColor" c_tpad_setfillcolor 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_SetFillStyle" c_tpad_setfillstyle 
  :: (Ptr RawTPad) -> CInt -> IO ()
foreign import ccall "HROOT.h TPad_ResetAttPad" c_tpad_resetattpad 
  :: (Ptr RawTPad) -> CString -> IO ()
foreign import ccall "HROOT.h TPad_SetBottomMargin" c_tpad_setbottommargin 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetLeftMargin" c_tpad_setleftmargin 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetRightMargin" c_tpad_setrightmargin 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetTopMargin" c_tpad_settopmargin 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetMargin" c_tpad_setmargin 
  :: (Ptr RawTPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetAfile" c_tpad_setafile 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetXfile" c_tpad_setxfile 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetYfile" c_tpad_setyfile 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetAstat" c_tpad_setastat 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetXstat" c_tpad_setxstat 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_SetYstat" c_tpad_setystat 
  :: (Ptr RawTPad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TPad_delete" c_tpad_delete 
  :: (Ptr RawTPad) -> IO ()

foreign import ccall "HROOT.h TButton_GetTextAlign" c_tbutton_gettextalign 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_GetTextAngle" c_tbutton_gettextangle 
  :: (Ptr RawTButton) -> IO CDouble
foreign import ccall "HROOT.h TButton_GetTextColor" c_tbutton_gettextcolor 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_GetTextFont" c_tbutton_gettextfont 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_GetTextSize" c_tbutton_gettextsize 
  :: (Ptr RawTButton) -> IO CDouble
foreign import ccall "HROOT.h TButton_ResetAttText" c_tbutton_resetatttext 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_SetTextAttributes" c_tbutton_settextattributes 
  :: (Ptr RawTButton) -> IO ()
foreign import ccall "HROOT.h TButton_SetTextAlign" c_tbutton_settextalign 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetTextAngle" c_tbutton_settextangle 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetTextColor" c_tbutton_settextcolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetTextFont" c_tbutton_settextfont 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetTextSize" c_tbutton_settextsize 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetTextSizePixels" c_tbutton_settextsizepixels 
  :: (Ptr RawTButton) -> CInt -> 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_Draw" c_tbutton_draw 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_FindObject" c_tbutton_findobject 
  :: (Ptr RawTButton) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TButton_GetName" c_tbutton_getname 
  :: (Ptr RawTButton) -> IO CString
foreign import ccall "HROOT.h TButton_IsA" c_tbutton_isa 
  :: (Ptr RawTButton) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TButton_IsFolder" c_tbutton_isfolder 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_IsEqual" c_tbutton_isequal 
  :: (Ptr RawTButton) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TButton_IsSortable" c_tbutton_issortable 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_Paint" c_tbutton_paint 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_printObj" c_tbutton_printobj 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_RecursiveRemove" c_tbutton_recursiveremove 
  :: (Ptr RawTButton) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TButton_SaveAs" c_tbutton_saveas 
  :: (Ptr RawTButton) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TButton_UseCurrentStyle" c_tbutton_usecurrentstyle 
  :: (Ptr RawTButton) -> IO ()
foreign import ccall "HROOT.h TButton_Write" c_tbutton_write 
  :: (Ptr RawTButton) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TButton_GetLineColor" c_tbutton_getlinecolor 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_GetLineStyle" c_tbutton_getlinestyle 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_GetLineWidth" c_tbutton_getlinewidth 
  :: (Ptr RawTButton) -> IO CInt
foreign import ccall "HROOT.h TButton_ResetAttLine" c_tbutton_resetattline 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_SetLineAttributes" c_tbutton_setlineattributes 
  :: (Ptr RawTButton) -> IO ()
foreign import ccall "HROOT.h TButton_SetLineColor" c_tbutton_setlinecolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetLineStyle" c_tbutton_setlinestyle 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetLineWidth" c_tbutton_setlinewidth 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetFillColor" c_tbutton_setfillcolor 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_SetFillStyle" c_tbutton_setfillstyle 
  :: (Ptr RawTButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TButton_ResetAttPad" c_tbutton_resetattpad 
  :: (Ptr RawTButton) -> CString -> IO ()
foreign import ccall "HROOT.h TButton_SetBottomMargin" c_tbutton_setbottommargin 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetLeftMargin" c_tbutton_setleftmargin 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetRightMargin" c_tbutton_setrightmargin 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetTopMargin" c_tbutton_settopmargin 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetMargin" c_tbutton_setmargin 
  :: (Ptr RawTButton) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetAfile" c_tbutton_setafile 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetXfile" c_tbutton_setxfile 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetYfile" c_tbutton_setyfile 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetAstat" c_tbutton_setastat 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetXstat" c_tbutton_setxstat 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_SetYstat" c_tbutton_setystat 
  :: (Ptr RawTButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TButton_delete" c_tbutton_delete 
  :: (Ptr RawTButton) -> IO ()

foreign import ccall "HROOT.h TGroupButton_GetTextAlign" c_tgroupbutton_gettextalign 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetTextAngle" c_tgroupbutton_gettextangle 
  :: (Ptr RawTGroupButton) -> IO CDouble
foreign import ccall "HROOT.h TGroupButton_GetTextColor" c_tgroupbutton_gettextcolor 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetTextFont" c_tgroupbutton_gettextfont 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetTextSize" c_tgroupbutton_gettextsize 
  :: (Ptr RawTGroupButton) -> IO CDouble
foreign import ccall "HROOT.h TGroupButton_ResetAttText" c_tgroupbutton_resetatttext 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextAttributes" c_tgroupbutton_settextattributes 
  :: (Ptr RawTGroupButton) -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextAlign" c_tgroupbutton_settextalign 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextAngle" c_tgroupbutton_settextangle 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextColor" c_tgroupbutton_settextcolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextFont" c_tgroupbutton_settextfont 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextSize" c_tgroupbutton_settextsize 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTextSizePixels" c_tgroupbutton_settextsizepixels 
  :: (Ptr RawTGroupButton) -> CInt -> 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_Draw" c_tgroupbutton_draw 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_FindObject" c_tgroupbutton_findobject 
  :: (Ptr RawTGroupButton) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TGroupButton_GetName" c_tgroupbutton_getname 
  :: (Ptr RawTGroupButton) -> IO CString
foreign import ccall "HROOT.h TGroupButton_IsA" c_tgroupbutton_isa 
  :: (Ptr RawTGroupButton) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TGroupButton_IsFolder" c_tgroupbutton_isfolder 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_IsEqual" c_tgroupbutton_isequal 
  :: (Ptr RawTGroupButton) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_IsSortable" c_tgroupbutton_issortable 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_Paint" c_tgroupbutton_paint 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_printObj" c_tgroupbutton_printobj 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_RecursiveRemove" c_tgroupbutton_recursiveremove 
  :: (Ptr RawTGroupButton) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TGroupButton_SaveAs" c_tgroupbutton_saveas 
  :: (Ptr RawTGroupButton) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_UseCurrentStyle" c_tgroupbutton_usecurrentstyle 
  :: (Ptr RawTGroupButton) -> IO ()
foreign import ccall "HROOT.h TGroupButton_Write" c_tgroupbutton_write 
  :: (Ptr RawTGroupButton) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetLineColor" c_tgroupbutton_getlinecolor 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetLineStyle" c_tgroupbutton_getlinestyle 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_GetLineWidth" c_tgroupbutton_getlinewidth 
  :: (Ptr RawTGroupButton) -> IO CInt
foreign import ccall "HROOT.h TGroupButton_ResetAttLine" c_tgroupbutton_resetattline 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetLineAttributes" c_tgroupbutton_setlineattributes 
  :: (Ptr RawTGroupButton) -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetLineColor" c_tgroupbutton_setlinecolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetLineStyle" c_tgroupbutton_setlinestyle 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetLineWidth" c_tgroupbutton_setlinewidth 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetFillColor" c_tgroupbutton_setfillcolor 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetFillStyle" c_tgroupbutton_setfillstyle 
  :: (Ptr RawTGroupButton) -> CInt -> IO ()
foreign import ccall "HROOT.h TGroupButton_ResetAttPad" c_tgroupbutton_resetattpad 
  :: (Ptr RawTGroupButton) -> CString -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetBottomMargin" c_tgroupbutton_setbottommargin 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetLeftMargin" c_tgroupbutton_setleftmargin 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetRightMargin" c_tgroupbutton_setrightmargin 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetTopMargin" c_tgroupbutton_settopmargin 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetMargin" c_tgroupbutton_setmargin 
  :: (Ptr RawTGroupButton) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetAfile" c_tgroupbutton_setafile 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetXfile" c_tgroupbutton_setxfile 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetYfile" c_tgroupbutton_setyfile 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetAstat" c_tgroupbutton_setastat 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetXstat" c_tgroupbutton_setxstat 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_SetYstat" c_tgroupbutton_setystat 
  :: (Ptr RawTGroupButton) -> CDouble -> IO ()
foreign import ccall "HROOT.h TGroupButton_delete" c_tgroupbutton_delete 
  :: (Ptr RawTGroupButton) -> IO ()

foreign import ccall "HROOT.h TCanvas_GetFrame" c_tcanvas_getframe 
  :: (Ptr RawTCanvas) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TCanvas_Range" c_tcanvas_range 
  :: (Ptr RawTCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_Draw" c_tcanvas_draw 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_FindObject" c_tcanvas_findobject 
  :: (Ptr RawTCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCanvas_GetName" c_tcanvas_getname 
  :: (Ptr RawTCanvas) -> IO CString
foreign import ccall "HROOT.h TCanvas_IsA" c_tcanvas_isa 
  :: (Ptr RawTCanvas) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCanvas_IsFolder" c_tcanvas_isfolder 
  :: (Ptr RawTCanvas) -> IO CInt
foreign import ccall "HROOT.h TCanvas_IsEqual" c_tcanvas_isequal 
  :: (Ptr RawTCanvas) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCanvas_IsSortable" c_tcanvas_issortable 
  :: (Ptr RawTCanvas) -> IO CInt
foreign import ccall "HROOT.h TCanvas_Paint" c_tcanvas_paint 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_printObj" c_tcanvas_printobj 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_RecursiveRemove" c_tcanvas_recursiveremove 
  :: (Ptr RawTCanvas) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCanvas_SaveAs" c_tcanvas_saveas 
  :: (Ptr RawTCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_UseCurrentStyle" c_tcanvas_usecurrentstyle 
  :: (Ptr RawTCanvas) -> IO ()
foreign import ccall "HROOT.h TCanvas_Write" c_tcanvas_write 
  :: (Ptr RawTCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCanvas_GetLineColor" c_tcanvas_getlinecolor 
  :: (Ptr RawTCanvas) -> IO CInt
foreign import ccall "HROOT.h TCanvas_GetLineStyle" c_tcanvas_getlinestyle 
  :: (Ptr RawTCanvas) -> IO CInt
foreign import ccall "HROOT.h TCanvas_GetLineWidth" c_tcanvas_getlinewidth 
  :: (Ptr RawTCanvas) -> IO CInt
foreign import ccall "HROOT.h TCanvas_ResetAttLine" c_tcanvas_resetattline 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_SetLineAttributes" c_tcanvas_setlineattributes 
  :: (Ptr RawTCanvas) -> IO ()
foreign import ccall "HROOT.h TCanvas_SetLineColor" c_tcanvas_setlinecolor 
  :: (Ptr RawTCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TCanvas_SetLineStyle" c_tcanvas_setlinestyle 
  :: (Ptr RawTCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TCanvas_SetLineWidth" c_tcanvas_setlinewidth 
  :: (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_ResetAttPad" c_tcanvas_resetattpad 
  :: (Ptr RawTCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TCanvas_SetBottomMargin" c_tcanvas_setbottommargin 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetLeftMargin" c_tcanvas_setleftmargin 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetRightMargin" c_tcanvas_setrightmargin 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetTopMargin" c_tcanvas_settopmargin 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetMargin" c_tcanvas_setmargin 
  :: (Ptr RawTCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetAfile" c_tcanvas_setafile 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetXfile" c_tcanvas_setxfile 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetYfile" c_tcanvas_setyfile 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetAstat" c_tcanvas_setastat 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetXstat" c_tcanvas_setxstat 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_SetYstat" c_tcanvas_setystat 
  :: (Ptr RawTCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TCanvas_delete" c_tcanvas_delete 
  :: (Ptr RawTCanvas) -> IO ()
foreign import ccall "HROOT.h TCanvas_newTCanvas" c_tcanvas_newtcanvas 
  :: CString -> CString -> CInt -> CInt -> IO (Ptr RawTCanvas)

foreign import ccall "HROOT.h TDialogCanvas_GetTextAlign" c_tdialogcanvas_gettextalign 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetTextAngle" c_tdialogcanvas_gettextangle 
  :: (Ptr RawTDialogCanvas) -> IO CDouble
foreign import ccall "HROOT.h TDialogCanvas_GetTextColor" c_tdialogcanvas_gettextcolor 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetTextFont" c_tdialogcanvas_gettextfont 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetTextSize" c_tdialogcanvas_gettextsize 
  :: (Ptr RawTDialogCanvas) -> IO CDouble
foreign import ccall "HROOT.h TDialogCanvas_ResetAttText" c_tdialogcanvas_resetatttext 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextAttributes" c_tdialogcanvas_settextattributes 
  :: (Ptr RawTDialogCanvas) -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextAlign" c_tdialogcanvas_settextalign 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextAngle" c_tdialogcanvas_settextangle 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextColor" c_tdialogcanvas_settextcolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextFont" c_tdialogcanvas_settextfont 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextSize" c_tdialogcanvas_settextsize 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTextSizePixels" c_tdialogcanvas_settextsizepixels 
  :: (Ptr RawTDialogCanvas) -> CInt -> 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_Draw" c_tdialogcanvas_draw 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_FindObject" c_tdialogcanvas_findobject 
  :: (Ptr RawTDialogCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TDialogCanvas_GetName" c_tdialogcanvas_getname 
  :: (Ptr RawTDialogCanvas) -> IO CString
foreign import ccall "HROOT.h TDialogCanvas_IsA" c_tdialogcanvas_isa 
  :: (Ptr RawTDialogCanvas) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TDialogCanvas_IsFolder" c_tdialogcanvas_isfolder 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_IsEqual" c_tdialogcanvas_isequal 
  :: (Ptr RawTDialogCanvas) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_IsSortable" c_tdialogcanvas_issortable 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_Paint" c_tdialogcanvas_paint 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_printObj" c_tdialogcanvas_printobj 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_RecursiveRemove" c_tdialogcanvas_recursiveremove 
  :: (Ptr RawTDialogCanvas) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SaveAs" c_tdialogcanvas_saveas 
  :: (Ptr RawTDialogCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_UseCurrentStyle" c_tdialogcanvas_usecurrentstyle 
  :: (Ptr RawTDialogCanvas) -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_Write" c_tdialogcanvas_write 
  :: (Ptr RawTDialogCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetLineColor" c_tdialogcanvas_getlinecolor 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetLineStyle" c_tdialogcanvas_getlinestyle 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_GetLineWidth" c_tdialogcanvas_getlinewidth 
  :: (Ptr RawTDialogCanvas) -> IO CInt
foreign import ccall "HROOT.h TDialogCanvas_ResetAttLine" c_tdialogcanvas_resetattline 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetLineAttributes" c_tdialogcanvas_setlineattributes 
  :: (Ptr RawTDialogCanvas) -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetLineColor" c_tdialogcanvas_setlinecolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetLineStyle" c_tdialogcanvas_setlinestyle 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetLineWidth" c_tdialogcanvas_setlinewidth 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetFillColor" c_tdialogcanvas_setfillcolor 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetFillStyle" c_tdialogcanvas_setfillstyle 
  :: (Ptr RawTDialogCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_ResetAttPad" c_tdialogcanvas_resetattpad 
  :: (Ptr RawTDialogCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetBottomMargin" c_tdialogcanvas_setbottommargin 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetLeftMargin" c_tdialogcanvas_setleftmargin 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetRightMargin" c_tdialogcanvas_setrightmargin 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetTopMargin" c_tdialogcanvas_settopmargin 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetMargin" c_tdialogcanvas_setmargin 
  :: (Ptr RawTDialogCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetAfile" c_tdialogcanvas_setafile 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetXfile" c_tdialogcanvas_setxfile 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetYfile" c_tdialogcanvas_setyfile 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetAstat" c_tdialogcanvas_setastat 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetXstat" c_tdialogcanvas_setxstat 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_SetYstat" c_tdialogcanvas_setystat 
  :: (Ptr RawTDialogCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TDialogCanvas_delete" c_tdialogcanvas_delete 
  :: (Ptr RawTDialogCanvas) -> IO ()

foreign import ccall "HROOT.h TInspectCanvas_GetTextAlign" c_tinspectcanvas_gettextalign 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetTextAngle" c_tinspectcanvas_gettextangle 
  :: (Ptr RawTInspectCanvas) -> IO CDouble
foreign import ccall "HROOT.h TInspectCanvas_GetTextColor" c_tinspectcanvas_gettextcolor 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetTextFont" c_tinspectcanvas_gettextfont 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetTextSize" c_tinspectcanvas_gettextsize 
  :: (Ptr RawTInspectCanvas) -> IO CDouble
foreign import ccall "HROOT.h TInspectCanvas_ResetAttText" c_tinspectcanvas_resetatttext 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextAttributes" c_tinspectcanvas_settextattributes 
  :: (Ptr RawTInspectCanvas) -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextAlign" c_tinspectcanvas_settextalign 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextAngle" c_tinspectcanvas_settextangle 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextColor" c_tinspectcanvas_settextcolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextFont" c_tinspectcanvas_settextfont 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextSize" c_tinspectcanvas_settextsize 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTextSizePixels" c_tinspectcanvas_settextsizepixels 
  :: (Ptr RawTInspectCanvas) -> CInt -> 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_Draw" c_tinspectcanvas_draw 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_FindObject" c_tinspectcanvas_findobject 
  :: (Ptr RawTInspectCanvas) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TInspectCanvas_GetName" c_tinspectcanvas_getname 
  :: (Ptr RawTInspectCanvas) -> IO CString
foreign import ccall "HROOT.h TInspectCanvas_IsA" c_tinspectcanvas_isa 
  :: (Ptr RawTInspectCanvas) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TInspectCanvas_IsFolder" c_tinspectcanvas_isfolder 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_IsEqual" c_tinspectcanvas_isequal 
  :: (Ptr RawTInspectCanvas) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_IsSortable" c_tinspectcanvas_issortable 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_Paint" c_tinspectcanvas_paint 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_printObj" c_tinspectcanvas_printobj 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_RecursiveRemove" c_tinspectcanvas_recursiveremove 
  :: (Ptr RawTInspectCanvas) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SaveAs" c_tinspectcanvas_saveas 
  :: (Ptr RawTInspectCanvas) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_UseCurrentStyle" c_tinspectcanvas_usecurrentstyle 
  :: (Ptr RawTInspectCanvas) -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_Write" c_tinspectcanvas_write 
  :: (Ptr RawTInspectCanvas) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetLineColor" c_tinspectcanvas_getlinecolor 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetLineStyle" c_tinspectcanvas_getlinestyle 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_GetLineWidth" c_tinspectcanvas_getlinewidth 
  :: (Ptr RawTInspectCanvas) -> IO CInt
foreign import ccall "HROOT.h TInspectCanvas_ResetAttLine" c_tinspectcanvas_resetattline 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetLineAttributes" c_tinspectcanvas_setlineattributes 
  :: (Ptr RawTInspectCanvas) -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetLineColor" c_tinspectcanvas_setlinecolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetLineStyle" c_tinspectcanvas_setlinestyle 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetLineWidth" c_tinspectcanvas_setlinewidth 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetFillColor" c_tinspectcanvas_setfillcolor 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetFillStyle" c_tinspectcanvas_setfillstyle 
  :: (Ptr RawTInspectCanvas) -> CInt -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_ResetAttPad" c_tinspectcanvas_resetattpad 
  :: (Ptr RawTInspectCanvas) -> CString -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetBottomMargin" c_tinspectcanvas_setbottommargin 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetLeftMargin" c_tinspectcanvas_setleftmargin 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetRightMargin" c_tinspectcanvas_setrightmargin 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetTopMargin" c_tinspectcanvas_settopmargin 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetMargin" c_tinspectcanvas_setmargin 
  :: (Ptr RawTInspectCanvas) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetAfile" c_tinspectcanvas_setafile 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetXfile" c_tinspectcanvas_setxfile 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetYfile" c_tinspectcanvas_setyfile 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetAstat" c_tinspectcanvas_setastat 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetXstat" c_tinspectcanvas_setxstat 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_SetYstat" c_tinspectcanvas_setystat 
  :: (Ptr RawTInspectCanvas) -> CDouble -> IO ()
foreign import ccall "HROOT.h TInspectCanvas_delete" c_tinspectcanvas_delete 
  :: (Ptr RawTInspectCanvas) -> IO ()

foreign import ccall "HROOT.h TEvePad_GetFrame" c_tevepad_getframe 
  :: (Ptr RawTEvePad) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TEvePad_Range" c_tevepad_range 
  :: (Ptr RawTEvePad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_Draw" c_tevepad_draw 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_FindObject" c_tevepad_findobject 
  :: (Ptr RawTEvePad) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TEvePad_GetName" c_tevepad_getname 
  :: (Ptr RawTEvePad) -> IO CString
foreign import ccall "HROOT.h TEvePad_IsA" c_tevepad_isa 
  :: (Ptr RawTEvePad) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TEvePad_IsFolder" c_tevepad_isfolder 
  :: (Ptr RawTEvePad) -> IO CInt
foreign import ccall "HROOT.h TEvePad_IsEqual" c_tevepad_isequal 
  :: (Ptr RawTEvePad) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TEvePad_IsSortable" c_tevepad_issortable 
  :: (Ptr RawTEvePad) -> IO CInt
foreign import ccall "HROOT.h TEvePad_Paint" c_tevepad_paint 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_printObj" c_tevepad_printobj 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_RecursiveRemove" c_tevepad_recursiveremove 
  :: (Ptr RawTEvePad) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TEvePad_SaveAs" c_tevepad_saveas 
  :: (Ptr RawTEvePad) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_UseCurrentStyle" c_tevepad_usecurrentstyle 
  :: (Ptr RawTEvePad) -> IO ()
foreign import ccall "HROOT.h TEvePad_Write" c_tevepad_write 
  :: (Ptr RawTEvePad) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TEvePad_GetLineColor" c_tevepad_getlinecolor 
  :: (Ptr RawTEvePad) -> IO CInt
foreign import ccall "HROOT.h TEvePad_GetLineStyle" c_tevepad_getlinestyle 
  :: (Ptr RawTEvePad) -> IO CInt
foreign import ccall "HROOT.h TEvePad_GetLineWidth" c_tevepad_getlinewidth 
  :: (Ptr RawTEvePad) -> IO CInt
foreign import ccall "HROOT.h TEvePad_ResetAttLine" c_tevepad_resetattline 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_SetLineAttributes" c_tevepad_setlineattributes 
  :: (Ptr RawTEvePad) -> IO ()
foreign import ccall "HROOT.h TEvePad_SetLineColor" c_tevepad_setlinecolor 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetLineStyle" c_tevepad_setlinestyle 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetLineWidth" c_tevepad_setlinewidth 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetFillColor" c_tevepad_setfillcolor 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_SetFillStyle" c_tevepad_setfillstyle 
  :: (Ptr RawTEvePad) -> CInt -> IO ()
foreign import ccall "HROOT.h TEvePad_ResetAttPad" c_tevepad_resetattpad 
  :: (Ptr RawTEvePad) -> CString -> IO ()
foreign import ccall "HROOT.h TEvePad_SetBottomMargin" c_tevepad_setbottommargin 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetLeftMargin" c_tevepad_setleftmargin 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetRightMargin" c_tevepad_setrightmargin 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetTopMargin" c_tevepad_settopmargin 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetMargin" c_tevepad_setmargin 
  :: (Ptr RawTEvePad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetAfile" c_tevepad_setafile 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetXfile" c_tevepad_setxfile 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetYfile" c_tevepad_setyfile 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetAstat" c_tevepad_setastat 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetXstat" c_tevepad_setxstat 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_SetYstat" c_tevepad_setystat 
  :: (Ptr RawTEvePad) -> CDouble -> IO ()
foreign import ccall "HROOT.h TEvePad_delete" c_tevepad_delete 
  :: (Ptr RawTEvePad) -> IO ()

foreign import ccall "HROOT.h TSlider_GetFrame" c_tslider_getframe 
  :: (Ptr RawTSlider) -> IO (Ptr RawTFrame)
foreign import ccall "HROOT.h TSlider_Range" c_tslider_range 
  :: (Ptr RawTSlider) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_Draw" c_tslider_draw 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_FindObject" c_tslider_findobject 
  :: (Ptr RawTSlider) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSlider_GetName" c_tslider_getname 
  :: (Ptr RawTSlider) -> IO CString
foreign import ccall "HROOT.h TSlider_IsA" c_tslider_isa 
  :: (Ptr RawTSlider) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TSlider_IsFolder" c_tslider_isfolder 
  :: (Ptr RawTSlider) -> IO CInt
foreign import ccall "HROOT.h TSlider_IsEqual" c_tslider_isequal 
  :: (Ptr RawTSlider) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TSlider_IsSortable" c_tslider_issortable 
  :: (Ptr RawTSlider) -> IO CInt
foreign import ccall "HROOT.h TSlider_Paint" c_tslider_paint 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_printObj" c_tslider_printobj 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_RecursiveRemove" c_tslider_recursiveremove 
  :: (Ptr RawTSlider) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TSlider_SaveAs" c_tslider_saveas 
  :: (Ptr RawTSlider) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_UseCurrentStyle" c_tslider_usecurrentstyle 
  :: (Ptr RawTSlider) -> IO ()
foreign import ccall "HROOT.h TSlider_Write" c_tslider_write 
  :: (Ptr RawTSlider) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSlider_GetLineColor" c_tslider_getlinecolor 
  :: (Ptr RawTSlider) -> IO CInt
foreign import ccall "HROOT.h TSlider_GetLineStyle" c_tslider_getlinestyle 
  :: (Ptr RawTSlider) -> IO CInt
foreign import ccall "HROOT.h TSlider_GetLineWidth" c_tslider_getlinewidth 
  :: (Ptr RawTSlider) -> IO CInt
foreign import ccall "HROOT.h TSlider_ResetAttLine" c_tslider_resetattline 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_SetLineAttributes" c_tslider_setlineattributes 
  :: (Ptr RawTSlider) -> IO ()
foreign import ccall "HROOT.h TSlider_SetLineColor" c_tslider_setlinecolor 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetLineStyle" c_tslider_setlinestyle 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetLineWidth" c_tslider_setlinewidth 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetFillColor" c_tslider_setfillcolor 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_SetFillStyle" c_tslider_setfillstyle 
  :: (Ptr RawTSlider) -> CInt -> IO ()
foreign import ccall "HROOT.h TSlider_ResetAttPad" c_tslider_resetattpad 
  :: (Ptr RawTSlider) -> CString -> IO ()
foreign import ccall "HROOT.h TSlider_SetBottomMargin" c_tslider_setbottommargin 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetLeftMargin" c_tslider_setleftmargin 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetRightMargin" c_tslider_setrightmargin 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetTopMargin" c_tslider_settopmargin 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetMargin" c_tslider_setmargin 
  :: (Ptr RawTSlider) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetAfile" c_tslider_setafile 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetXfile" c_tslider_setxfile 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetYfile" c_tslider_setyfile 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetAstat" c_tslider_setastat 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetXstat" c_tslider_setxstat 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_SetYstat" c_tslider_setystat 
  :: (Ptr RawTSlider) -> CDouble -> IO ()
foreign import ccall "HROOT.h TSlider_delete" c_tslider_delete 
  :: (Ptr RawTSlider) -> IO ()

foreign import ccall "HROOT.h TApplication_Draw" c_tapplication_draw 
  :: (Ptr RawTApplication) -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_FindObject" c_tapplication_findobject 
  :: (Ptr RawTApplication) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TApplication_GetName" c_tapplication_getname 
  :: (Ptr RawTApplication) -> IO CString
foreign import ccall "HROOT.h TApplication_IsA" c_tapplication_isa 
  :: (Ptr RawTApplication) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TApplication_IsFolder" c_tapplication_isfolder 
  :: (Ptr RawTApplication) -> IO CInt
foreign import ccall "HROOT.h TApplication_IsEqual" c_tapplication_isequal 
  :: (Ptr RawTApplication) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TApplication_IsSortable" c_tapplication_issortable 
  :: (Ptr RawTApplication) -> IO CInt
foreign import ccall "HROOT.h TApplication_Paint" c_tapplication_paint 
  :: (Ptr RawTApplication) -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_printObj" c_tapplication_printobj 
  :: (Ptr RawTApplication) -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_RecursiveRemove" c_tapplication_recursiveremove 
  :: (Ptr RawTApplication) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TApplication_SaveAs" c_tapplication_saveas 
  :: (Ptr RawTApplication) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TApplication_UseCurrentStyle" c_tapplication_usecurrentstyle 
  :: (Ptr RawTApplication) -> IO ()
foreign import ccall "HROOT.h TApplication_Write" c_tapplication_write 
  :: (Ptr RawTApplication) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TApplication_delete" c_tapplication_delete 
  :: (Ptr RawTApplication) -> IO ()
foreign import ccall "HROOT.h TApplication_newTApplication" c_tapplication_newtapplication 
  :: CString -> (Ptr CInt) -> (Ptr (CString)) -> IO (Ptr RawTApplication)
foreign import ccall "HROOT.h TApplication_Run" c_tapplication_run 
  :: (Ptr RawTApplication) -> CInt -> IO ()

foreign import ccall "HROOT.h TRint_Run" c_trint_run 
  :: (Ptr RawTRint) -> CInt -> IO ()
foreign import ccall "HROOT.h TRint_Draw" c_trint_draw 
  :: (Ptr RawTRint) -> CString -> IO ()
foreign import ccall "HROOT.h TRint_FindObject" c_trint_findobject 
  :: (Ptr RawTRint) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TRint_GetName" c_trint_getname 
  :: (Ptr RawTRint) -> IO CString
foreign import ccall "HROOT.h TRint_IsA" c_trint_isa 
  :: (Ptr RawTRint) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TRint_IsFolder" c_trint_isfolder 
  :: (Ptr RawTRint) -> IO CInt
foreign import ccall "HROOT.h TRint_IsEqual" c_trint_isequal 
  :: (Ptr RawTRint) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TRint_IsSortable" c_trint_issortable 
  :: (Ptr RawTRint) -> IO CInt
foreign import ccall "HROOT.h TRint_Paint" c_trint_paint 
  :: (Ptr RawTRint) -> CString -> IO ()
foreign import ccall "HROOT.h TRint_printObj" c_trint_printobj 
  :: (Ptr RawTRint) -> CString -> IO ()
foreign import ccall "HROOT.h TRint_RecursiveRemove" c_trint_recursiveremove 
  :: (Ptr RawTRint) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TRint_SaveAs" c_trint_saveas 
  :: (Ptr RawTRint) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TRint_UseCurrentStyle" c_trint_usecurrentstyle 
  :: (Ptr RawTRint) -> IO ()
foreign import ccall "HROOT.h TRint_Write" c_trint_write 
  :: (Ptr RawTRint) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TRint_delete" c_trint_delete 
  :: (Ptr RawTRint) -> IO ()
foreign import ccall "HROOT.h TRint_newTRint" c_trint_newtrint 
  :: CString -> (Ptr CInt) -> (Ptr (CString)) -> IO (Ptr RawTRint)

foreign import ccall "HROOT.h TRandom_SetName" c_trandom_setname 
  :: (Ptr RawTRandom) -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_SetNameTitle" c_trandom_setnametitle 
  :: (Ptr RawTRandom) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_SetTitle" c_trandom_settitle 
  :: (Ptr RawTRandom) -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_Draw" c_trandom_draw 
  :: (Ptr RawTRandom) -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_FindObject" c_trandom_findobject 
  :: (Ptr RawTRandom) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TRandom_GetName" c_trandom_getname 
  :: (Ptr RawTRandom) -> IO CString
foreign import ccall "HROOT.h TRandom_IsA" c_trandom_isa 
  :: (Ptr RawTRandom) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TRandom_IsFolder" c_trandom_isfolder 
  :: (Ptr RawTRandom) -> IO CInt
foreign import ccall "HROOT.h TRandom_IsEqual" c_trandom_isequal 
  :: (Ptr RawTRandom) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TRandom_IsSortable" c_trandom_issortable 
  :: (Ptr RawTRandom) -> IO CInt
foreign import ccall "HROOT.h TRandom_Paint" c_trandom_paint 
  :: (Ptr RawTRandom) -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_printObj" c_trandom_printobj 
  :: (Ptr RawTRandom) -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_RecursiveRemove" c_trandom_recursiveremove 
  :: (Ptr RawTRandom) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TRandom_SaveAs" c_trandom_saveas 
  :: (Ptr RawTRandom) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TRandom_UseCurrentStyle" c_trandom_usecurrentstyle 
  :: (Ptr RawTRandom) -> IO ()
foreign import ccall "HROOT.h TRandom_Write" c_trandom_write 
  :: (Ptr RawTRandom) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TRandom_delete" c_trandom_delete 
  :: (Ptr RawTRandom) -> IO ()
foreign import ccall "HROOT.h TRandom_newTRandom" c_trandom_newtrandom 
  :: CInt -> IO (Ptr RawTRandom)
foreign import ccall "HROOT.h TRandom_Gaus" c_trandom_gaus 
  :: (Ptr RawTRandom) -> CDouble -> CDouble -> IO CDouble
foreign import ccall "HROOT.h TRandom_Uniform" c_trandom_uniform 
  :: (Ptr RawTRandom) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOT.h TCollection_Draw" c_tcollection_draw 
  :: (Ptr RawTCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TCollection_FindObject" c_tcollection_findobject 
  :: (Ptr RawTCollection) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TCollection_GetName" c_tcollection_getname 
  :: (Ptr RawTCollection) -> IO CString
foreign import ccall "HROOT.h TCollection_IsA" c_tcollection_isa 
  :: (Ptr RawTCollection) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TCollection_IsFolder" c_tcollection_isfolder 
  :: (Ptr RawTCollection) -> IO CInt
foreign import ccall "HROOT.h TCollection_IsEqual" c_tcollection_isequal 
  :: (Ptr RawTCollection) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TCollection_IsSortable" c_tcollection_issortable 
  :: (Ptr RawTCollection) -> IO CInt
foreign import ccall "HROOT.h TCollection_Paint" c_tcollection_paint 
  :: (Ptr RawTCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TCollection_printObj" c_tcollection_printobj 
  :: (Ptr RawTCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TCollection_RecursiveRemove" c_tcollection_recursiveremove 
  :: (Ptr RawTCollection) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TCollection_SaveAs" c_tcollection_saveas 
  :: (Ptr RawTCollection) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TCollection_UseCurrentStyle" c_tcollection_usecurrentstyle 
  :: (Ptr RawTCollection) -> IO ()
foreign import ccall "HROOT.h TCollection_Write" c_tcollection_write 
  :: (Ptr RawTCollection) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TCollection_delete" c_tcollection_delete 
  :: (Ptr RawTCollection) -> IO ()

foreign import ccall "HROOT.h TSeqCollection_Draw" c_tseqcollection_draw 
  :: (Ptr RawTSeqCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TSeqCollection_FindObject" c_tseqcollection_findobject 
  :: (Ptr RawTSeqCollection) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TSeqCollection_GetName" c_tseqcollection_getname 
  :: (Ptr RawTSeqCollection) -> IO CString
foreign import ccall "HROOT.h TSeqCollection_IsA" c_tseqcollection_isa 
  :: (Ptr RawTSeqCollection) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TSeqCollection_IsFolder" c_tseqcollection_isfolder 
  :: (Ptr RawTSeqCollection) -> IO CInt
foreign import ccall "HROOT.h TSeqCollection_IsEqual" c_tseqcollection_isequal 
  :: (Ptr RawTSeqCollection) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TSeqCollection_IsSortable" c_tseqcollection_issortable 
  :: (Ptr RawTSeqCollection) -> IO CInt
foreign import ccall "HROOT.h TSeqCollection_Paint" c_tseqcollection_paint 
  :: (Ptr RawTSeqCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TSeqCollection_printObj" c_tseqcollection_printobj 
  :: (Ptr RawTSeqCollection) -> CString -> IO ()
foreign import ccall "HROOT.h TSeqCollection_RecursiveRemove" c_tseqcollection_recursiveremove 
  :: (Ptr RawTSeqCollection) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TSeqCollection_SaveAs" c_tseqcollection_saveas 
  :: (Ptr RawTSeqCollection) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TSeqCollection_UseCurrentStyle" c_tseqcollection_usecurrentstyle 
  :: (Ptr RawTSeqCollection) -> IO ()
foreign import ccall "HROOT.h TSeqCollection_Write" c_tseqcollection_write 
  :: (Ptr RawTSeqCollection) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TSeqCollection_delete" c_tseqcollection_delete 
  :: (Ptr RawTSeqCollection) -> IO ()

foreign import ccall "HROOT.h TObjArray_Draw" c_tobjarray_draw 
  :: (Ptr RawTObjArray) -> CString -> IO ()
foreign import ccall "HROOT.h TObjArray_FindObject" c_tobjarray_findobject 
  :: (Ptr RawTObjArray) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TObjArray_GetName" c_tobjarray_getname 
  :: (Ptr RawTObjArray) -> IO CString
foreign import ccall "HROOT.h TObjArray_IsA" c_tobjarray_isa 
  :: (Ptr RawTObjArray) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TObjArray_IsFolder" c_tobjarray_isfolder 
  :: (Ptr RawTObjArray) -> IO CInt
foreign import ccall "HROOT.h TObjArray_IsEqual" c_tobjarray_isequal 
  :: (Ptr RawTObjArray) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TObjArray_IsSortable" c_tobjarray_issortable 
  :: (Ptr RawTObjArray) -> IO CInt
foreign import ccall "HROOT.h TObjArray_Paint" c_tobjarray_paint 
  :: (Ptr RawTObjArray) -> CString -> IO ()
foreign import ccall "HROOT.h TObjArray_printObj" c_tobjarray_printobj 
  :: (Ptr RawTObjArray) -> CString -> IO ()
foreign import ccall "HROOT.h TObjArray_RecursiveRemove" c_tobjarray_recursiveremove 
  :: (Ptr RawTObjArray) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TObjArray_SaveAs" c_tobjarray_saveas 
  :: (Ptr RawTObjArray) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TObjArray_UseCurrentStyle" c_tobjarray_usecurrentstyle 
  :: (Ptr RawTObjArray) -> IO ()
foreign import ccall "HROOT.h TObjArray_Write" c_tobjarray_write 
  :: (Ptr RawTObjArray) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TObjArray_delete" c_tobjarray_delete 
  :: (Ptr RawTObjArray) -> IO ()

foreign import ccall "HROOT.h TList_Draw" c_tlist_draw 
  :: (Ptr RawTList) -> CString -> IO ()
foreign import ccall "HROOT.h TList_FindObject" c_tlist_findobject 
  :: (Ptr RawTList) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TList_GetName" c_tlist_getname 
  :: (Ptr RawTList) -> IO CString
foreign import ccall "HROOT.h TList_IsA" c_tlist_isa 
  :: (Ptr RawTList) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TList_IsFolder" c_tlist_isfolder 
  :: (Ptr RawTList) -> IO CInt
foreign import ccall "HROOT.h TList_IsEqual" c_tlist_isequal 
  :: (Ptr RawTList) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TList_IsSortable" c_tlist_issortable 
  :: (Ptr RawTList) -> IO CInt
foreign import ccall "HROOT.h TList_Paint" c_tlist_paint 
  :: (Ptr RawTList) -> CString -> IO ()
foreign import ccall "HROOT.h TList_printObj" c_tlist_printobj 
  :: (Ptr RawTList) -> CString -> IO ()
foreign import ccall "HROOT.h TList_RecursiveRemove" c_tlist_recursiveremove 
  :: (Ptr RawTList) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TList_SaveAs" c_tlist_saveas 
  :: (Ptr RawTList) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TList_UseCurrentStyle" c_tlist_usecurrentstyle 
  :: (Ptr RawTList) -> IO ()
foreign import ccall "HROOT.h TList_Write" c_tlist_write 
  :: (Ptr RawTList) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TList_delete" c_tlist_delete 
  :: (Ptr RawTList) -> IO ()

foreign import ccall "HROOT.h TKey_SetName" c_tkey_setname 
  :: (Ptr RawTKey) -> CString -> IO ()
foreign import ccall "HROOT.h TKey_SetNameTitle" c_tkey_setnametitle 
  :: (Ptr RawTKey) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TKey_SetTitle" c_tkey_settitle 
  :: (Ptr RawTKey) -> CString -> IO ()
foreign import ccall "HROOT.h TKey_Draw" c_tkey_draw 
  :: (Ptr RawTKey) -> CString -> IO ()
foreign import ccall "HROOT.h TKey_FindObject" c_tkey_findobject 
  :: (Ptr RawTKey) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOT.h TKey_GetName" c_tkey_getname 
  :: (Ptr RawTKey) -> IO CString
foreign import ccall "HROOT.h TKey_IsA" c_tkey_isa 
  :: (Ptr RawTKey) -> IO (Ptr RawTClass)
foreign import ccall "HROOT.h TKey_IsFolder" c_tkey_isfolder 
  :: (Ptr RawTKey) -> IO CInt
foreign import ccall "HROOT.h TKey_IsEqual" c_tkey_isequal 
  :: (Ptr RawTKey) -> (Ptr RawTObject) -> IO CInt
foreign import ccall "HROOT.h TKey_IsSortable" c_tkey_issortable 
  :: (Ptr RawTKey) -> IO CInt
foreign import ccall "HROOT.h TKey_Paint" c_tkey_paint 
  :: (Ptr RawTKey) -> CString -> IO ()
foreign import ccall "HROOT.h TKey_printObj" c_tkey_printobj 
  :: (Ptr RawTKey) -> CString -> IO ()
foreign import ccall "HROOT.h TKey_RecursiveRemove" c_tkey_recursiveremove 
  :: (Ptr RawTKey) -> (Ptr RawTObject) -> IO ()
foreign import ccall "HROOT.h TKey_SaveAs" c_tkey_saveas 
  :: (Ptr RawTKey) -> CString -> CString -> IO ()
foreign import ccall "HROOT.h TKey_UseCurrentStyle" c_tkey_usecurrentstyle 
  :: (Ptr RawTKey) -> IO ()
foreign import ccall "HROOT.h TKey_Write" c_tkey_write 
  :: (Ptr RawTKey) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOT.h TKey_delete" c_tkey_delete 
  :: (Ptr RawTKey) -> IO ()
foreign import ccall "HROOT.h TKey_newTKey" c_tkey_newtkey 
  :: CString -> CString -> (Ptr RawTClass) -> CInt -> (Ptr RawTDirectory) -> IO (Ptr RawTKey)

foreign import ccall "HROOT.h TDatime_delete" c_tdatime_delete 
  :: (Ptr RawTDatime) -> IO ()
foreign import ccall "HROOT.h TDatime_newTDatime" c_tdatime_newtdatime 
  :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO (Ptr RawTDatime)
foreign import ccall "HROOT.h TDatime_Convert" c_tdatime_convert 
  :: (Ptr RawTDatime) -> CInt -> IO CUInt