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

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Append"
               c_troot_append :: Ptr RawTROOT -> Ptr RawTObject -> CBool -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_addD"
               c_troot_addd :: Ptr RawTROOT -> Ptr RawTObject -> CBool -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_AppendKey" c_troot_appendkey ::
               Ptr RawTROOT -> Ptr RawTKey -> IO CInt

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Close"
               c_troot_close :: Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Get"
               c_troot_get :: Ptr RawTROOT -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_cd_TDirectory" c_troot_cd_tdirectory ::
               Ptr RawTROOT -> CString -> IO CBool

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_SetName"
               c_troot_setname :: Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_SetNameTitle" c_troot_setnametitle ::
               Ptr RawTROOT -> CString -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_SetTitle" c_troot_settitle ::
               Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Clear"
               c_troot_clear :: Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Draw"
               c_troot_draw :: Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_FindObject" c_troot_findobject ::
               Ptr RawTROOT -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_GetName"
               c_troot_getname :: Ptr RawTROOT -> IO CString

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_IsA"
               c_troot_isa :: Ptr RawTROOT -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Paint"
               c_troot_paint :: Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_printObj" c_troot_printobj ::
               Ptr RawTROOT -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_SaveAs"
               c_troot_saveas :: Ptr RawTROOT -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Write"
               c_troot_write :: Ptr RawTROOT -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_Write_"
               c_troot_write_ :: Ptr RawTROOT -> IO CInt

foreign import ccall interruptible "HROOTCoreTROOT.h TROOT_delete"
               c_troot_delete :: Ptr RawTROOT -> IO ()

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_tROOT_GetGlobal" c_troot_troot_getglobal ::
               Ptr RawTROOT -> CString -> CBool -> IO (Ptr RawTGlobal)

foreign import ccall interruptible
               "HROOTCoreTROOT.h TROOT_tROOT_Initialized"
               c_troot_troot_initialized :: IO CBool