hslua-0.5.0: A Lua language interpreter embedding in Haskell

Safe HaskellNone
LanguageHaskell98

Scripting.Lua

Contents

Synopsis

Documentation

data LuaState Source #

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.

type LuaNumber = Double Source #

Synonym for lua_Number. See lua_Number in Lua Reference Manual.

data LTYPE Source #

Enumeration used as type tag. See lua_type.

multret :: Int Source #

Alias for C constant LUA_MULTRET. See lua_call.

pop :: LuaState -> Int -> IO () Source #

See lua_pop.

strlen :: LuaState -> Int -> IO Int Source #

Deprecated: Use objlen instead.

Compatibility alias for objlen

tolist :: StackValue a => LuaState -> Int -> IO (Maybe [a]) Source #

Try to convert Lua array at given index to Haskell list.

registryindex :: Int Source #

Alias for C constant LUA_REGISTRYINDEX. See Lua registry.

environindex :: Int Source #

Alias for C constant LUA_ENVIRONINDEX. See pseudo-indices.

globalsindex :: Int Source #

Alias for C constant LUA_GLOBALSINDEX. See pseudo-indices.

newstate :: IO LuaState Source #

See lua_newstate and luaL_newstate.

call :: LuaState -> Int -> Int -> IO () Source #

See lua_call and lua_call.

lerror :: LuaState -> IO Int Source #

This is a convenience function to implement error propagation convention described in Error handling in hslua. hslua doesn't implement lua_error function from Lua C API because it's never safe to use. (see Error handling in hslua for details)

pushlist :: StackValue a => LuaState -> [a] -> IO () Source #

Push a list to Lua stack as a Lua array.

argerror :: LuaState -> Int -> String -> IO CInt Source #

See luaL_argerror. Contrary to the manual, Haskell function does return with value less than zero.

unref :: LuaState -> Int -> Int -> IO () Source #

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 nil
  • Ptr () pushes light user data, peek checks for lightuserdata or userdata
  • See "A note about integer functions" for integer functions.

Minimal complete definition

push, peek, valuetype

Methods

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.

Instances

StackValue Bool Source # 
StackValue Int Source # 
StackValue () Source # 

Methods

push :: LuaState -> () -> IO () Source #

peek :: LuaState -> Int -> IO (Maybe ()) Source #

valuetype :: () -> LTYPE Source #

StackValue ByteString Source # 
StackValue LuaNumber Source # 
StackValue LuaInteger Source # 
StackValue LuaState Source # 
StackValue a => StackValue [a] Source # 

Methods

push :: LuaState -> [a] -> IO () Source #

peek :: LuaState -> Int -> IO (Maybe [a]) Source #

valuetype :: [a] -> LTYPE Source #

StackValue (Ptr a) Source # 

Methods

push :: LuaState -> Ptr a -> IO () Source #

peek :: LuaState -> Int -> IO (Maybe (Ptr a)) Source #

valuetype :: Ptr a -> LTYPE Source #

StackValue (FunPtr LuaCFunction) Source # 

maybepeek :: l -> n -> (l -> n -> IO Bool) -> (l -> n -> IO r) -> IO (Maybe r) Source #

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 #

Minimal complete definition

luaimport', luaimportargerror

Instances

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 #

Minimal complete definition

callproc'

Methods

callproc' :: LuaState -> String -> IO () -> Int -> a Source #

Instances

LuaCallProc (IO t) Source # 

Methods

callproc' :: LuaState -> String -> IO () -> Int -> IO t Source #

(StackValue t, LuaCallProc b) => LuaCallProc (t -> b) Source # 

Methods

callproc' :: LuaState -> String -> IO () -> Int -> t -> b Source #

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 #

Minimal complete definition

callfunc'

Methods

callfunc' :: LuaState -> String -> IO () -> Int -> a Source #

Instances

StackValue t => LuaCallFunc (IO t) Source # 

Methods

callfunc' :: LuaState -> String -> IO () -> Int -> IO t Source #

(StackValue t, LuaCallFunc b) => LuaCallFunc (t -> b) Source # 

Methods

callfunc' :: LuaState -> String -> IO () -> Int -> t -> b Source #

callfunc :: LuaCallFunc a => LuaState -> String -> a Source #

Call a Lua function. Use as:

Just v <- callfunc l "proc" "abc" (1::Int) (5.0::Double)

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 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 longjmps 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 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 LuaNumbers before storing them in Lua stack/heap, and getter functions like tointeger convert them back to LuaIntegers.

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.