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

-- module HROOT.Class.FFI where

module HROOT.Graf.TSPHE.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Graf.TSPHE.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 20 "src/HROOT/Graf/TSPHE/FFI.hsc" #-}

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetName" c_tsphe_setname 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetNameTitle" c_tsphe_setnametitle 
  :: (Ptr RawTSPHE) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetTitle" c_tsphe_settitle 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_GetLineColor" c_tsphe_getlinecolor 
  :: (Ptr RawTSPHE) -> IO CInt

foreign import ccall "HROOTGrafTSPHE.h TSPHE_GetLineStyle" c_tsphe_getlinestyle 
  :: (Ptr RawTSPHE) -> IO CInt

foreign import ccall "HROOTGrafTSPHE.h TSPHE_GetLineWidth" c_tsphe_getlinewidth 
  :: (Ptr RawTSPHE) -> IO CInt

foreign import ccall "HROOTGrafTSPHE.h TSPHE_ResetAttLine" c_tsphe_resetattline 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetLineAttributes" c_tsphe_setlineattributes 
  :: (Ptr RawTSPHE) -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetLineColor" c_tsphe_setlinecolor 
  :: (Ptr RawTSPHE) -> CInt -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetLineStyle" c_tsphe_setlinestyle 
  :: (Ptr RawTSPHE) -> CInt -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetLineWidth" c_tsphe_setlinewidth 
  :: (Ptr RawTSPHE) -> CInt -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetFillColor" c_tsphe_setfillcolor 
  :: (Ptr RawTSPHE) -> CInt -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SetFillStyle" c_tsphe_setfillstyle 
  :: (Ptr RawTSPHE) -> CInt -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_Draw" c_tsphe_draw 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_FindObject" c_tsphe_findobject 
  :: (Ptr RawTSPHE) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTGrafTSPHE.h TSPHE_GetName" c_tsphe_getname 
  :: (Ptr RawTSPHE) -> IO CString

foreign import ccall "HROOTGrafTSPHE.h TSPHE_IsA" c_tsphe_isa 
  :: (Ptr RawTSPHE) -> IO (Ptr RawTClass)

foreign import ccall "HROOTGrafTSPHE.h TSPHE_Paint" c_tsphe_paint 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_printObj" c_tsphe_printobj 
  :: (Ptr RawTSPHE) -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_SaveAs" c_tsphe_saveas 
  :: (Ptr RawTSPHE) -> CString -> CString -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_Write" c_tsphe_write 
  :: (Ptr RawTSPHE) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTGrafTSPHE.h TSPHE_delete" c_tsphe_delete 
  :: (Ptr RawTSPHE) -> IO ()

foreign import ccall "HROOTGrafTSPHE.h TSPHE_newTSPHE" c_tsphe_newtsphe 
  :: CString -> CString -> CString -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTSPHE)