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

-- module HROOT.Class.FFI where

module HROOT.Core.TSeqCollection.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Core.TSeqCollection.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType


{-# LINE 20 "src/HROOT/Core/TSeqCollection/FFI.hsc" #-}

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

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

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

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

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

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

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

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

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