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

foreign import ccall interruptible "HROOTIOTFile.h TFile_Append"
               c_tfile_append :: Ptr RawTFile -> Ptr RawTObject -> CBool -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_addD"
               c_tfile_addd :: Ptr RawTFile -> Ptr RawTObject -> CBool -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_AppendKey"
               c_tfile_appendkey :: Ptr RawTFile -> Ptr RawTKey -> IO CInt

foreign import ccall interruptible "HROOTIOTFile.h TFile_Close"
               c_tfile_close :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_Get"
               c_tfile_get :: Ptr RawTFile -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTIOTFile.h TFile_cd_TDirectory" c_tfile_cd_tdirectory ::
               Ptr RawTFile -> CString -> IO CBool

foreign import ccall interruptible "HROOTIOTFile.h TFile_SetName"
               c_tfile_setname :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible
               "HROOTIOTFile.h TFile_SetNameTitle" c_tfile_setnametitle ::
               Ptr RawTFile -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_SetTitle"
               c_tfile_settitle :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_Clear"
               c_tfile_clear :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_Draw"
               c_tfile_draw :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible
               "HROOTIOTFile.h TFile_FindObject" c_tfile_findobject ::
               Ptr RawTFile -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible "HROOTIOTFile.h TFile_GetName"
               c_tfile_getname :: Ptr RawTFile -> IO CString

foreign import ccall interruptible "HROOTIOTFile.h TFile_IsA"
               c_tfile_isa :: Ptr RawTFile -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTIOTFile.h TFile_Paint"
               c_tfile_paint :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_printObj"
               c_tfile_printobj :: Ptr RawTFile -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_SaveAs"
               c_tfile_saveas :: Ptr RawTFile -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_Write"
               c_tfile_write :: Ptr RawTFile -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible "HROOTIOTFile.h TFile_Write_"
               c_tfile_write_ :: Ptr RawTFile -> IO CInt

foreign import ccall interruptible "HROOTIOTFile.h TFile_delete"
               c_tfile_delete :: Ptr RawTFile -> IO ()

foreign import ccall interruptible "HROOTIOTFile.h TFile_newTFile"
               c_tfile_newtfile ::
               CString -> CString -> CString -> CInt -> IO (Ptr RawTFile)