Safe Haskell | None |
---|---|
Language | Haskell98 |
- data LuaState
- type LuaCFunction = LuaState -> IO CInt
- type LuaInteger = Int64
- type LuaNumber = Double
- data LTYPE
- data GCCONTROL
- multret :: Int
- settop :: LuaState -> Int -> IO ()
- createtable :: LuaState -> Int -> Int -> IO ()
- objlen :: LuaState -> Int -> IO Int
- pop :: LuaState -> Int -> IO ()
- newtable :: LuaState -> IO ()
- pushcclosure :: LuaState -> FunPtr LuaCFunction -> Int -> IO ()
- pushcfunction :: LuaState -> FunPtr LuaCFunction -> IO ()
- strlen :: LuaState -> Int -> IO Int
- ltype :: LuaState -> Int -> IO LTYPE
- isfunction :: LuaState -> Int -> IO Bool
- istable :: LuaState -> Int -> IO Bool
- tolist :: StackValue a => LuaState -> Int -> IO (Maybe [a])
- islightuserdata :: LuaState -> Int -> IO Bool
- isnil :: LuaState -> Int -> IO Bool
- isboolean :: LuaState -> Int -> IO Bool
- isthread :: LuaState -> Int -> IO Bool
- isnone :: LuaState -> Int -> IO Bool
- isnoneornil :: LuaState -> Int -> IO Bool
- registryindex :: Int
- environindex :: Int
- globalsindex :: Int
- upvalueindex :: Int -> Int
- atpanic :: LuaState -> FunPtr LuaCFunction -> IO (FunPtr LuaCFunction)
- tostring :: LuaState -> Int -> IO ByteString
- tothread :: LuaState -> Int -> IO LuaState
- touserdata :: LuaState -> Int -> IO (Ptr a)
- typename :: LuaState -> LTYPE -> IO String
- xmove :: LuaState -> LuaState -> Int -> IO ()
- yield :: LuaState -> Int -> IO Int
- checkstack :: LuaState -> Int -> IO Bool
- newstate :: IO LuaState
- close :: LuaState -> IO ()
- concat :: LuaState -> Int -> IO ()
- call :: LuaState -> Int -> Int -> IO ()
- pcall :: LuaState -> Int -> Int -> Int -> IO Int
- cpcall :: LuaState -> FunPtr LuaCFunction -> Ptr a -> IO Int
- getfield :: LuaState -> Int -> String -> IO ()
- setfield :: LuaState -> Int -> String -> IO ()
- getglobal :: LuaState -> String -> IO ()
- setglobal :: LuaState -> String -> IO ()
- openlibs :: LuaState -> IO ()
- mkStringWriter :: LuaWriter -> IO (FunPtr LuaWriter)
- dump :: LuaState -> IO String
- equal :: LuaState -> Int -> Int -> IO Bool
- lerror :: LuaState -> IO Int
- gc :: LuaState -> GCCONTROL -> Int -> IO Int
- getfenv :: LuaState -> Int -> IO ()
- getmetatable :: LuaState -> Int -> IO Bool
- gettable :: LuaState -> Int -> IO ()
- gettop :: LuaState -> IO Int
- insert :: LuaState -> Int -> IO ()
- iscfunction :: LuaState -> Int -> IO Bool
- isnumber :: LuaState -> Int -> IO Bool
- isstring :: LuaState -> Int -> IO Bool
- isuserdata :: LuaState -> Int -> IO Bool
- lessthan :: LuaState -> Int -> Int -> IO Bool
- loadfile :: LuaState -> String -> IO Int
- mkStringReader :: LuaReader -> IO (FunPtr LuaReader)
- loadstring :: LuaState -> String -> String -> IO Int
- newthread :: LuaState -> IO LuaState
- newuserdata :: LuaState -> Int -> IO (Ptr ())
- next :: LuaState -> Int -> IO Bool
- pushboolean :: LuaState -> Bool -> IO ()
- pushinteger :: LuaState -> LuaInteger -> IO ()
- pushlightuserdata :: LuaState -> Ptr a -> IO ()
- pushnil :: LuaState -> IO ()
- pushnumber :: LuaState -> LuaNumber -> IO ()
- pushstring :: LuaState -> ByteString -> IO ()
- pushlist :: StackValue a => LuaState -> [a] -> IO ()
- pushthread :: LuaState -> IO Bool
- pushvalue :: LuaState -> Int -> IO ()
- rawequal :: LuaState -> Int -> Int -> IO Bool
- rawget :: LuaState -> Int -> IO ()
- rawgeti :: LuaState -> Int -> Int -> IO ()
- rawset :: LuaState -> Int -> IO ()
- rawseti :: LuaState -> Int -> Int -> IO ()
- remove :: LuaState -> Int -> IO ()
- replace :: LuaState -> Int -> IO ()
- resume :: LuaState -> Int -> IO Int
- setfenv :: LuaState -> Int -> IO Int
- setmetatable :: LuaState -> Int -> IO ()
- settable :: LuaState -> Int -> IO ()
- status :: LuaState -> IO Int
- toboolean :: LuaState -> Int -> IO Bool
- tocfunction :: LuaState -> Int -> IO (FunPtr LuaCFunction)
- tointeger :: LuaState -> Int -> IO LuaInteger
- tonumber :: LuaState -> Int -> IO LuaNumber
- topointer :: LuaState -> Int -> IO (Ptr ())
- register :: LuaState -> String -> FunPtr LuaCFunction -> IO ()
- newmetatable :: LuaState -> String -> IO Int
- argerror :: LuaState -> Int -> String -> IO CInt
- ref :: LuaState -> Int -> IO Int
- unref :: LuaState -> Int -> Int -> IO ()
- class StackValue a where
- maybepeek :: l -> n -> (l -> n -> IO Bool) -> (l -> n -> IO r) -> IO (Maybe r)
- getglobal2 :: LuaState -> String -> IO ()
- typenameindex :: LuaState -> Int -> IO String
- class LuaImport a where
- luaimport' :: Int -> a -> LuaCFunction
- luaimportargerror :: Int -> String -> a -> LuaCFunction
- mkWrapper :: LuaCFunction -> IO (FunPtr LuaCFunction)
- newcfunction :: LuaImport a => a -> IO (FunPtr LuaCFunction)
- luaimport :: LuaImport a => a -> LuaCFunction
- freecfunction :: FunPtr LuaCFunction -> IO ()
- class LuaCallProc a where
- callproc :: LuaCallProc a => LuaState -> String -> a
- class LuaCallFunc a where
- callfunc :: LuaCallFunc a => LuaState -> String -> a
- hsmethod__gc_addr :: FunPtr LuaCFunction
- hsmethod__call_addr :: FunPtr LuaCFunction
- hsmethod__gc :: LuaState -> IO CInt
- hsmethod__call :: LuaState -> IO CInt
- pushhsfunction :: LuaImport a => LuaState -> a -> IO ()
- pushrawhsfunction :: LuaState -> LuaCFunction -> IO ()
- registerhsfunction :: LuaImport a => LuaState -> String -> a -> IO ()
- registerrawhsfunction :: LuaState -> String -> (LuaState -> IO CInt) -> IO ()
Documentation
Synonym for lua_State *
. See lua_State
in Lua Reference Manual.
type LuaCFunction = LuaState -> IO CInt Source
Synonym for lua_CFunction
. See lua_CFunction
in Lua Reference Manual.
type LuaInteger = Int64 Source
Synonym for lua_Integer
. See lua_Integer
in Lua Reference Manual.
Enumeration used as type tag. See lua_type
in Lua Reference Manual.
Enumeration used by gc
function.
pushcclosure :: LuaState -> FunPtr LuaCFunction -> Int -> IO () Source
See lua_pushcclosure
in Lua Reference Manual.
pushcfunction :: LuaState -> FunPtr LuaCFunction -> IO () Source
See lua_pushcfunction
in Lua Reference Manual.
tolist :: StackValue a => LuaState -> Int -> IO (Maybe [a]) Source
Try to convert Lua array at given index to Haskell list.
islightuserdata :: LuaState -> Int -> IO Bool Source
See lua_islightuserdata
in Lua Reference Manual.
See LUA_REGISTRYINDEX
in Lua Reference Manual.
See LUA_ENVIRONINDEX
in Lua Reference Manual.
See LUA_GLOBALSINDEX
in Lua Reference Manual.
upvalueindex :: Int -> Int Source
See lua_upvalueindex
in Lua Reference Manual.
atpanic :: LuaState -> FunPtr LuaCFunction -> IO (FunPtr LuaCFunction) Source
See lua_atpanic
in Lua Reference Manual.
cpcall :: LuaState -> FunPtr LuaCFunction -> Ptr a -> IO Int Source
See lua_cpcall
in Lua Reference Manual.
lerror :: LuaState -> IO Int Source
This is a convenience function to implement error propagation convention
described in [Error handling in hslua](#g:1). hslua doesn't implement
lua_error
function from Lua C API because it's never safe to use. (see
[Error handling in hslua](#g:1) for details)
loadstring :: LuaState -> String -> String -> IO Int Source
See luaL_loadstring
in Lua Reference Manual.
pushboolean :: LuaState -> Bool -> IO () Source
See lua_pushboolean
in Lua Reference Manual.
pushinteger :: LuaState -> LuaInteger -> IO () Source
See lua_pushinteger
in Lua Reference Manual.
pushlightuserdata :: LuaState -> Ptr a -> IO () Source
See lua_pushlightuserdata
in Lua Reference Manual.
pushnumber :: LuaState -> LuaNumber -> IO () Source
See lua_pushnumber
in Lua Reference Manual.
pushstring :: LuaState -> ByteString -> IO () Source
See lua_pushstring
in Lua Reference Manual.
pushlist :: StackValue a => LuaState -> [a] -> IO () Source
Push a list to Lua stack as a Lua array.
pushthread :: LuaState -> IO Bool Source
See lua_pushthread
in Lua Reference Manual.
setmetatable :: LuaState -> Int -> IO () Source
See lua_setmetatable
in Lua Reference Manual.
tocfunction :: LuaState -> Int -> IO (FunPtr LuaCFunction) Source
See lua_tocfunction
in Lua Reference Manual.
register :: LuaState -> String -> FunPtr LuaCFunction -> IO () Source
See lua_register
in Lua Reference Manual.
argerror :: LuaState -> Int -> String -> IO CInt Source
See luaL_argerror
in Lua Reference Manual. Contrary to the
manual, Haskell function does return with value less than zero.
class StackValue a where Source
A value that can be pushed and poped from the Lua stack. All instances are natural, except following:
LuaState
push ignores its argument, pushes current state()
push ignores its argument, just pushes nilPtr ()
pushes light user data, peek checks for lightuserdata or userdata- See "A note about integer functions" for integer functions.
push :: LuaState -> a -> IO () Source
Pushes a value onto Lua stack, casting it into meaningfully nearest Lua type.
peek :: LuaState -> Int -> IO (Maybe a) Source
Check if at index n
there is a convertible Lua value and if so return it
wrapped in Just
. Return Nothing
otherwise.
valuetype :: a -> LTYPE Source
Lua type id code of the vaule expected. Parameter is unused.
getglobal2 :: LuaState -> String -> IO () Source
Like getglobal
, but knows about packages. e. g.
getglobal l "math.sin"
returns correct result
class LuaImport a where Source
luaimport' :: Int -> a -> LuaCFunction Source
luaimportargerror :: Int -> String -> a -> LuaCFunction Source
StackValue a => LuaImport (IO a) | |
(StackValue a, LuaImport b) => LuaImport (a -> b) |
mkWrapper :: LuaCFunction -> IO (FunPtr LuaCFunction) Source
newcfunction :: LuaImport a => a -> IO (FunPtr LuaCFunction) Source
Create new foreign Lua function. Function created can be called
by Lua engine. Remeber to free the pointer with freecfunction
.
luaimport :: LuaImport a => a -> LuaCFunction Source
Convert a Haskell function to Lua function. Any Haskell function can be converted provided that:
- all arguments are instances of StackValue
- return type is IO t, where t is an instance of StackValue
Any Haskell exception will be converted to a string and returned as Lua error.
freecfunction :: FunPtr LuaCFunction -> IO () Source
Free function pointer created with newcfunction
.
class LuaCallProc a where Source
LuaCallProc (IO t) | |
(StackValue t, LuaCallProc b) => LuaCallProc (t -> b) |
callproc :: LuaCallProc a => LuaState -> String -> a Source
Call a Lua procedure. Use as:
callproc l "proc" "abc" (1::Int) (5.0::Double)
class LuaCallFunc a where Source
StackValue t => LuaCallFunc (IO t) | |
(StackValue t, LuaCallFunc b) => LuaCallFunc (t -> b) |
callfunc :: LuaCallFunc a => LuaState -> String -> a Source
Call a Lua function. Use as:
Just v <- callfunc l "proc" "abc" (1::Int) (5.0::Double)
hsmethod__gc :: LuaState -> IO CInt Source
hsmethod__call :: LuaState -> IO CInt Source
pushhsfunction :: LuaImport a => LuaState -> a -> IO () Source
Pushes Haskell function converted to a Lua function. All values created will be garbage collected. Use as:
Lua.pushhsfunction l myfun Lua.setglobal l "myfun"
You are not allowed to use lua_error
anywhere, but
use an error code of (-1) to the same effect. Push
error message as the sole return value.
pushrawhsfunction :: LuaState -> LuaCFunction -> IO () Source
Pushes _raw_ Haskell function converted to a Lua function.
Raw Haskell functions collect parameters from the stack and return
a CInt
that represents number of return values left in the stack.
registerhsfunction :: LuaImport a => LuaState -> String -> a -> IO () Source
Imports a Haskell function and registers it at global name.
registerrawhsfunction :: LuaState -> String -> (LuaState -> IO CInt) -> IO () Source
Imports a raw Haskell function and registers it at global name.
Error handling in hslua
Error handling in hslua is tricky, because we can call Haskell from Lua which calls Lua again etc. (or the other way around, e.g. Lua loads Haskell program compiled as a dynamic library, see [this blog post](http:/osa1.netposts/2015-01-16-haskell-so-lua.html) as an example)
At each language boundary we should check for errors and propagate them properly to the next level in stack.
Let's say we have this call stack: (stack grows upwards)
Haskell function Lua function Haskell program
and we want to report an error in top-most Haskell function. We can't use
lua_error
from Lua C API, because it uses longjmp
, which means it skips
layers of abstractions, including Haskell RTS. There's no way to prevent this
longjmp
. lua_pcall
sets the jump target, but even with lua_pcall
it's
not safe. Consider this call stack:
Haskell function which calls `lua_error` Lua function, uses pcall Haskell program
This program jumps to Lua function, skipping Haskell RTS code that would run
before Haskell function returns. For this reason we can use
lua_pcall
(pcall
) only for catching errors from Lua, and even in that case
we need to make sure there are no Haskell calls between error-throwing Lua
call and our pcall
call.
To be able to catch errors from Haskell functions in Lua, we need to find a
convention. Currently hslua does this: lerror
has same type as Lua's
lua_error
, but instead of calling real lua_error
, it's returning two
values: A special value _HASKELLERR
and error message as a string.
Using this, we can write a function to catch errors from Haskell like this:
function catch_haskell(ret, err_msg) if ret == _HASKELLERR then print("Error caught from Haskell land: " .. err_msg) return end return ret end
(_HASKELLERR
is created by newstate
)
(Type errors in Haskell functions are also handled using this convention. E.g. if you pass a Lua value with wrong type to a Haskell function, error will be reported in this way)
At this point our call stack is like this:
Lua function (Haskell function returned with error, which we caught) Haskell program
If we further want to propagate the error message to Haskell program, we
we can just use standard error
function and use pcall
in Haskell side.
Note that if we use error
in Lua side and forget to use pcall
in calling
Haskell function, we start skipping layers of abstractions and we get a
segfault in the best case.
This use of error
in Lua side and pcall
in Haskell side is safe, as
long as there are no Haskell-Lua interactions going on between those two
calls. (e.g. we can only remove one layer from our stack, otherwise it's
unsafe)
The reason it's safe is because lua_pcall
C function is calling the Lua
function using Lua C API, and when called Lua function calls error
it
longjmp
s to lua_pcall
C function, without skipping any layers of
abstraction. lua_pcall
then returns to Haskell.
As an example program that does error propagations between Haskell and Lua(in both ways), see [this example](https:/github.comosa1hsluatreemasterexamples/err_prop) from hslua repository.
NOTE: If you're loading a hslua program compiled to a dynamic library from a
Lua program, you need to define _HASKELLERR = {}
manually, after creating
the Lua state.
A note about integer functions
Lua didn't have integers until Lua 5.3, and the version supported by hslua
is Lua 5.1. In Lua 5.1 and 5.2, integer functions like pushinteger
convert
integers to LuaNumber
s before storing them in Lua stack/heap, and getter
functions like tointeger
convert them back to LuaInteger
s.
This means that you can lose some information during the conversion. For example:
main = do l <- newstate let val = maxBound :: LuaInteger pushinteger l val i3 <- tointeger l 1 putStrLn $ show val ++ " - " ++ show i3
Prints 9223372036854775807 - -9223372036854775808
.