{-# LANGUAGE CPP #-} {-| Module : Foreign.Lua.Core.RawBindings Copyright : © 2007–2012 Gracjan Polak, 2012–2016 Ömer Sinan Ağacan, 2017-2020 Albert Krewinkel License : MIT Maintainer : Albert Krewinkel Stability : beta Portability : ForeignFunctionInterface Haskell bindings to lua C API functions. -} module Foreign.Lua.Core.RawBindings where import Foreign.C import Foreign.Lua.Core.Error (Failable (Failable)) import Foreign.Lua.Core.Types as Lua import Foreign.Ptr ##ifdef ALLOW_UNSAFE_GC ##define SAFTY unsafe ##else ##define SAFTY safe ##endif -- TODO: lua_getallocf, lua_setallocf -- TODO: Debugger functions -- Some of the Lua functions may call a Haskell function, and trigger -- garbage collection, rescheduling etc. This means we must declare these -- functions as 'safe'. -------------------------------------------------------------------------------- -- * State manipulation -- lua_newstate is currently not supported. -- | See foreign import ccall "lua.h lua_close" lua_close :: Lua.State -> IO () -- lua_newthread is currently not supported. -------------------------------------------------------------------------------- -- * Basic stack manipulation -- | See foreign import ccall unsafe "lua.h lua_absindex" lua_absindex :: Lua.State -> StackIndex -> IO StackIndex -- | See foreign import ccall unsafe "lua.h lua_gettop" lua_gettop :: Lua.State -> IO StackIndex -- | See foreign import ccall SAFTY "lua.h lua_settop" lua_settop :: Lua.State -> StackIndex -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushvalue" lua_pushvalue :: Lua.State -> StackIndex -> IO () -- | See foreign import ccall SAFTY "lua.h lua_copy" lua_copy :: Lua.State -> StackIndex -> StackIndex -> IO () -- | See foreign import capi SAFTY "lua.h lua_remove" lua_remove :: Lua.State -> StackIndex -> IO () -- | See foreign import capi SAFTY "lua.h lua_insert" lua_insert :: Lua.State -> StackIndex -> IO () -- | See foreign import capi SAFTY "lua.h lua_replace" lua_replace :: Lua.State -> StackIndex -> IO () -- | See foreign import capi SAFTY "lua.h lua_checkstack" lua_checkstack :: Lua.State -> CInt -> IO LuaBool -- lua_xmove is currently not supported. -------------------------------------------------------------------------------- -- * Stack access functions -- | See foreign import ccall SAFTY "lua.h lua_isnumber" lua_isnumber :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_isinteger" lua_isinteger :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_isstring" lua_isstring :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_iscfunction" lua_iscfunction :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_isuserdata" lua_isuserdata :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_type" lua_type :: Lua.State -> StackIndex -> IO TypeCode -- | See foreign import ccall SAFTY "lua.h lua_typename" lua_typename :: Lua.State -> TypeCode -> IO CString -- lua_compare is unsafe (might cause a longjmp), use hslua_compare instead. -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_compare" hslua_compare :: Lua.State -> StackIndex -> StackIndex -> CInt -> IO (Failable LuaBool) -- | See foreign import ccall SAFTY "lua.h lua_rawequal" lua_rawequal :: Lua.State -> StackIndex -> StackIndex -> IO LuaBool -- -- Type coercion -- -- | See foreign import capi SAFTY "lua.h lua_toboolean" lua_toboolean :: Lua.State -> StackIndex -> IO LuaBool -- | See foreign import ccall SAFTY "lua.h lua_tocfunction" lua_tocfunction :: Lua.State -> StackIndex -> IO CFunction -- | See foreign import ccall SAFTY "lua.h lua_tointegerx" lua_tointegerx :: Lua.State -> StackIndex -> Ptr LuaBool -> IO Lua.Integer -- | See foreign import ccall SAFTY "lua.h lua_tonumberx" lua_tonumberx :: Lua.State -> StackIndex -> Ptr LuaBool -> IO Lua.Number -- | See foreign import ccall SAFTY "lua.h lua_tolstring" lua_tolstring :: Lua.State -> StackIndex -> Ptr CSize -> IO (Ptr CChar) -- | See foreign import ccall SAFTY "lua.h lua_topointer" lua_topointer :: Lua.State -> StackIndex -> IO (Ptr ()) -- | See foreign import ccall SAFTY "lua.h lua_tothread" lua_tothread :: Lua.State -> StackIndex -> IO Lua.State -- | See foreign import ccall SAFTY "lua.h lua_touserdata" lua_touserdata :: Lua.State -> StackIndex -> IO (Ptr a) -- -- Object size -- -- | See foreign import ccall SAFTY "lua.h lua_rawlen" lua_rawlen :: Lua.State -> StackIndex -> IO CSize -------------------------------------------------------------------------------- -- * Push functions -- | See foreign import ccall SAFTY "lua.h lua_pushnil" lua_pushnil :: Lua.State -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushnumber" lua_pushnumber :: Lua.State -> Lua.Number -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushinteger" lua_pushinteger :: Lua.State -> Lua.Integer -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushlstring" lua_pushlstring :: Lua.State -> Ptr CChar -> CSize -> IO () -- lua_pushstring is currently not supported. It's difficult to use in a haskell -- context. -- | See foreign import ccall SAFTY "lua.h lua_pushcclosure" lua_pushcclosure :: Lua.State -> CFunction -> NumArgs -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushboolean" lua_pushboolean :: Lua.State -> LuaBool -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushlightuserdata" lua_pushlightuserdata :: Lua.State -> Ptr a -> IO () -- | See foreign import ccall SAFTY "lua.h lua_pushthread" lua_pushthread :: Lua.State -> IO CInt -------------------------------------------------------------------------------- -- * Get functions -- + lua_gettable is unsafe, use hslua_gettable instead. -- + lua_getglobal is unsafe, use hslua_getglobal instead. -- + lua_getfield is unsafe, we build something equivallent using pushlstring and -- gettable. -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_gettable" hslua_gettable :: Lua.State -> StackIndex -> IO (Failable ()) -- | See foreign import ccall SAFTY "lua.h lua_rawget" lua_rawget :: Lua.State -> StackIndex -> IO () -- | See foreign import ccall SAFTY "lua.h lua_rawgeti" lua_rawgeti :: Lua.State -> StackIndex -> Lua.Integer -> IO () -- | See foreign import ccall SAFTY "lua.h lua_createtable" lua_createtable :: Lua.State -> CInt -> CInt -> IO () -- | See foreign import ccall SAFTY "lua.h lua_newuserdata" lua_newuserdata :: Lua.State -> CSize -> IO (Ptr ()) -- | See foreign import ccall SAFTY "lua.h lua_getmetatable" lua_getmetatable :: Lua.State -> StackIndex -> IO LuaBool -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_getglobal" hslua_getglobal :: Lua.State -> CString -> CSize -> IO (Failable ()) -------------------------------------------------------------------------------- -- * Set functions -- lua_settable is unsafe, use hslua_settable instead. -- lua_setfield is unsafe, use hslua_setfield instead. -- lua_setglobal is unsafe, use hslua_setglobal instead. -- lua_setfenv (5.1 only) is not supported. -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_settable" hslua_settable :: Lua.State -> StackIndex -> IO (Failable ()) -- | See foreign import ccall SAFTY "lua.h lua_rawset" lua_rawset :: Lua.State -> StackIndex -> IO () -- | See foreign import ccall SAFTY "lua.h lua_rawseti" lua_rawseti :: Lua.State -> StackIndex -> Lua.Integer -> IO () -- | See foreign import ccall SAFTY "lua.h lua_setmetatable" lua_setmetatable :: Lua.State -> StackIndex -> IO () -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_setglobal" hslua_setglobal :: Lua.State -> CString -> CSize -> IO (Failable ()) -------------------------------------------------------------------------------- -- * \'load\' and \'call\' functions (load and run Lua code) -- lua_call is inherently unsafe, we do not support it. -- | See foreign import capi "lua.h lua_pcall" lua_pcall :: Lua.State -> NumArgs -> NumResults -> StackIndex -> IO StatusCode -- | See foreign import ccall safe "lua.h lua_load" lua_load :: Lua.State -> Lua.Reader -> Ptr () -> CString -> CString -> IO StatusCode -- currently unsupported: -- lua_dump ------------------------------------------------------------------------------ -- * Coroutine functions -- lua_yield / lua_yieldk and lua_resume are currently not supported. -- | See foreign import ccall unsafe "lua.h lua_status" lua_status :: Lua.State -> IO StatusCode ------------------------------------------------------------------------------ -- * Garbage-collection functions and options -- | See foreign import ccall "lua.h lua_gc" lua_gc :: Lua.State -> CInt -> CInt -> IO CInt ------------------------------------------------------------------------------ -- * Miscellaneous functions -- lua_error is unsafe, use hslua_error instead. -- lua_next is unsafe, use hslua_next instead. -- lua_concat is unsafe (may trigger a longjmp), use hslua_concat instead. -- | Replacement for ; it uses the HsLua error signaling convention instead of raw -- @longjmp@. foreign import ccall "error-conversion.h hslua_error" hslua_error :: Lua.State -> IO NumResults -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_next" hslua_next :: Lua.State -> StackIndex -> IO (Failable LuaBool) -- | Wrapper around which catches any @longjmp@s. foreign import ccall "error-conversion.h hslua_concat" hslua_concat :: Lua.State -> NumArgs -> IO (Failable ()) -- | See foreign import capi unsafe "lua.h lua_pushglobaltable" lua_pushglobaltable :: Lua.State -> IO () ------------------------------------------------------------------------------ -- * Lua Libraries -- | See foreign import ccall unsafe "lualib.h luaL_openlibs" luaL_openlibs :: Lua.State -> IO () -- | Point to function opening the base library. foreign import ccall unsafe "lualib.h &luaopen_base" lua_open_base_ptr :: CFunction -- | Point to function opening the table library. foreign import ccall unsafe "lualib.h &luaopen_table" lua_open_table_ptr :: CFunction -- | Point to function opening the io library. foreign import ccall unsafe "lualib.h &luaopen_io" lua_open_io_ptr :: CFunction -- | Point to function opening the os library. foreign import ccall unsafe "lualib.h &luaopen_os" lua_open_os_ptr :: CFunction -- | Point to function opening the string library. foreign import ccall unsafe "lualib.h &luaopen_string" lua_open_string_ptr :: CFunction -- | Point to function opening the math library. foreign import ccall unsafe "lualib.h &luaopen_math" lua_open_math_ptr :: CFunction -- | Point to function opening the debug library. foreign import ccall unsafe "lualib.h &luaopen_debug" lua_open_debug_ptr :: CFunction -- | Point to function opening the package library. foreign import ccall unsafe "lualib.h &luaopen_package" lua_open_package_ptr :: CFunction