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

foreign import ccall interruptible "HROOTCoreTKey.h TKey_SetName"
               c_tkey_setname :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTKey.h TKey_SetNameTitle" c_tkey_setnametitle ::
               Ptr RawTKey -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_SetTitle"
               c_tkey_settitle :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_Clear"
               c_tkey_clear :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_Draw"
               c_tkey_draw :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTKey.h TKey_FindObject" c_tkey_findobject ::
               Ptr RawTKey -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible "HROOTCoreTKey.h TKey_GetName"
               c_tkey_getname :: Ptr RawTKey -> IO CString

foreign import ccall interruptible "HROOTCoreTKey.h TKey_IsA"
               c_tkey_isa :: Ptr RawTKey -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTCoreTKey.h TKey_Paint"
               c_tkey_paint :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_printObj"
               c_tkey_printobj :: Ptr RawTKey -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_SaveAs"
               c_tkey_saveas :: Ptr RawTKey -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_Write"
               c_tkey_write :: Ptr RawTKey -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible "HROOTCoreTKey.h TKey_Write_"
               c_tkey_write_ :: Ptr RawTKey -> IO CInt

foreign import ccall interruptible "HROOTCoreTKey.h TKey_delete"
               c_tkey_delete :: Ptr RawTKey -> IO ()

foreign import ccall interruptible "HROOTCoreTKey.h TKey_newTKey"
               c_tkey_newtkey ::
               CString ->
                 CString ->
                   Ptr RawTClass -> CInt -> Ptr RawTDirectory -> IO (Ptr RawTKey)