{-# LINE 1 "src/HROOT/Core/TSeqCollection/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Core.TSeqCollection.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Core.TSeqCollection.RawType
import HROOT.Core.TSeqCollection.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_Clear"
               c_tseqcollection_clear :: Ptr RawTSeqCollection -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_Draw"
               c_tseqcollection_draw :: Ptr RawTSeqCollection -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_FindObject"
               c_tseqcollection_findobject ::
               Ptr RawTSeqCollection -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_GetName"
               c_tseqcollection_getname :: Ptr RawTSeqCollection -> IO CString

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_IsA" c_tseqcollection_isa
               :: Ptr RawTSeqCollection -> IO (Ptr RawTClass)

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_Paint"
               c_tseqcollection_paint :: Ptr RawTSeqCollection -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_printObj"
               c_tseqcollection_printobj ::
               Ptr RawTSeqCollection -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_SaveAs"
               c_tseqcollection_saveas ::
               Ptr RawTSeqCollection -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_Write"
               c_tseqcollection_write ::
               Ptr RawTSeqCollection -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_Write_"
               c_tseqcollection_write_ :: Ptr RawTSeqCollection -> IO CInt

foreign import ccall interruptible
               "HROOTCoreTSeqCollection.h TSeqCollection_delete"
               c_tseqcollection_delete :: Ptr RawTSeqCollection -> IO ()