module HROOT.Graf.TShape.FFI where
import Foreign.C
import Foreign.Ptr
import HROOT.Graf.TShape.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType
foreign import ccall "HROOTGrafTShape.h TShape_SetName" c_tshape_setname
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetNameTitle" c_tshape_setnametitle
:: (Ptr RawTShape) -> CString -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetTitle" c_tshape_settitle
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_GetLineColor" c_tshape_getlinecolor
:: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOTGrafTShape.h TShape_GetLineStyle" c_tshape_getlinestyle
:: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOTGrafTShape.h TShape_GetLineWidth" c_tshape_getlinewidth
:: (Ptr RawTShape) -> IO CInt
foreign import ccall "HROOTGrafTShape.h TShape_ResetAttLine" c_tshape_resetattline
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetLineAttributes" c_tshape_setlineattributes
:: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetLineColor" c_tshape_setlinecolor
:: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetLineStyle" c_tshape_setlinestyle
:: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetLineWidth" c_tshape_setlinewidth
:: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetFillColor" c_tshape_setfillcolor
:: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SetFillStyle" c_tshape_setfillstyle
:: (Ptr RawTShape) -> CInt -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_Draw" c_tshape_draw
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_FindObject" c_tshape_findobject
:: (Ptr RawTShape) -> CString -> IO (Ptr RawTObject)
foreign import ccall "HROOTGrafTShape.h TShape_GetName" c_tshape_getname
:: (Ptr RawTShape) -> IO CString
foreign import ccall "HROOTGrafTShape.h TShape_IsA" c_tshape_isa
:: (Ptr RawTShape) -> IO (Ptr RawTClass)
foreign import ccall "HROOTGrafTShape.h TShape_Paint" c_tshape_paint
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_printObj" c_tshape_printobj
:: (Ptr RawTShape) -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_SaveAs" c_tshape_saveas
:: (Ptr RawTShape) -> CString -> CString -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_Write" c_tshape_write
:: (Ptr RawTShape) -> CString -> CInt -> CInt -> IO CInt
foreign import ccall "HROOTGrafTShape.h TShape_delete" c_tshape_delete
:: (Ptr RawTShape) -> IO ()
foreign import ccall "HROOTGrafTShape.h TShape_newTShape" c_tshape_newtshape
:: CString -> CString -> CString -> IO (Ptr RawTShape)