hslua-0.4.1: 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 in Lua Reference Manual.

multret :: Int Source

See LUA_MULTRET in Lua Reference Manual.

settop :: LuaState -> Int -> IO () Source

See lua_settop in Lua Reference Manual.

createtable :: LuaState -> Int -> Int -> IO () Source

See lua_createtable in Lua Reference Manual.

objlen :: LuaState -> Int -> IO Int Source

See lua_objlen in Lua Reference Manual.

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

See lua_pop in Lua Reference Manual.

newtable :: LuaState -> IO () Source

See lua_newtable in Lua Reference Manual.

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.

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

See lua_strlen in Lua Reference Manual.

ltype :: LuaState -> Int -> IO LTYPE Source

See lua_type in Lua Reference Manual.

isfunction :: LuaState -> Int -> IO Bool Source

See lua_isfunction in Lua Reference Manual.

istable :: LuaState -> Int -> IO Bool Source

See lua_istable 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.

isnil :: LuaState -> Int -> IO Bool Source

See lua_isnil in Lua Reference Manual.

isboolean :: LuaState -> Int -> IO Bool Source

See lua_isboolean in Lua Reference Manual.

isthread :: LuaState -> Int -> IO Bool Source

See lua_isthread in Lua Reference Manual.

isnone :: LuaState -> Int -> IO Bool Source

See lua_none in Lua Reference Manual.

isnoneornil :: LuaState -> Int -> IO Bool Source

See lua_noneornil in Lua Reference Manual.

registryindex :: Int Source

See LUA_REGISTRYINDEX in Lua Reference Manual.

environindex :: Int Source

See LUA_ENVIRONINDEX in Lua Reference Manual.

globalsindex :: Int Source

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.

tostring :: LuaState -> Int -> IO ByteString Source

See lua_tostring in Lua Reference Manual.

tothread :: LuaState -> Int -> IO LuaState Source

See lua_tothread in Lua Reference Manual.

touserdata :: LuaState -> Int -> IO (Ptr a) Source

See lua_touserdata in Lua Reference Manual.

typename :: LuaState -> LTYPE -> IO String Source

See lua_typename in Lua Reference Manual.

xmove :: LuaState -> LuaState -> Int -> IO () Source

See lua_xmove in Lua Reference Manual.

yield :: LuaState -> Int -> IO Int Source

See lua_yield in Lua Reference Manual.

checkstack :: LuaState -> Int -> IO Bool Source

See lua_checkstack in Lua Reference Manual.

newstate :: IO LuaState Source

See lua_newstate and luaL_newstate in Lua Reference Manual.

close :: LuaState -> IO () Source

See lua_close in Lua Reference Manual.

concat :: LuaState -> Int -> IO () Source

See lua_concat in Lua Reference Manual.

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

See lua_call and lua_call in Lua Reference Manual.

pcall :: LuaState -> Int -> Int -> Int -> IO Int Source

See lua_pcall in Lua Reference Manual.

cpcall :: LuaState -> FunPtr LuaCFunction -> Ptr a -> IO Int Source

See lua_cpcall in Lua Reference Manual.

getfield :: LuaState -> Int -> String -> IO () Source

See lua_getfield in Lua Reference Manual.

setfield :: LuaState -> Int -> String -> IO () Source

See lua_setfield in Lua Reference Manual.

getglobal :: LuaState -> String -> IO () Source

See lua_getglobal in Lua Reference Manual.

setglobal :: LuaState -> String -> IO () Source

See lua_setglobal in Lua Reference Manual.

openlibs :: LuaState -> IO () Source

See luaL_openlibs in Lua Reference Manual.

dump :: LuaState -> IO String Source

See lua_dump in Lua Reference Manual.

equal :: LuaState -> Int -> Int -> IO Bool Source

See lua_equal 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)

gc :: LuaState -> GCCONTROL -> Int -> IO Int Source

See lua_gc in Lua Reference Manual.

getfenv :: LuaState -> Int -> IO () Source

See lua_getfenv in Lua Reference Manual.

getmetatable :: LuaState -> Int -> IO Bool Source

See lua_getmetatable in Lua Reference Manual.

gettable :: LuaState -> Int -> IO () Source

See lua_gettable in Lua Reference Manual.

gettop :: LuaState -> IO Int Source

See lua_gettop in Lua Reference Manual.

insert :: LuaState -> Int -> IO () Source

See lua_insert in Lua Reference Manual.

iscfunction :: LuaState -> Int -> IO Bool Source

See lua_iscfunction in Lua Reference Manual.

isnumber :: LuaState -> Int -> IO Bool Source

See lua_isnumber in Lua Reference Manual.

isstring :: LuaState -> Int -> IO Bool Source

See lua_isstring in Lua Reference Manual.

isuserdata :: LuaState -> Int -> IO Bool Source

See lua_isuserdata in Lua Reference Manual.

lessthan :: LuaState -> Int -> Int -> IO Bool Source

See lua_lessthan in Lua Reference Manual.

loadfile :: LuaState -> String -> IO Int Source

See luaL_loadfile in Lua Reference Manual.

loadstring :: LuaState -> String -> String -> IO Int Source

See luaL_loadstring in Lua Reference Manual.

newthread :: LuaState -> IO LuaState Source

See lua_newthread in Lua Reference Manual.

newuserdata :: LuaState -> Int -> IO (Ptr ()) Source

See lua_newuserdata in Lua Reference Manual.

next :: LuaState -> Int -> IO Bool Source

See lua_next 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.

pushnil :: LuaState -> IO () Source

See lua_pushnil 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.

pushvalue :: LuaState -> Int -> IO () Source

See lua_pushvalue in Lua Reference Manual.

rawequal :: LuaState -> Int -> Int -> IO Bool Source

See lua_rawequal in Lua Reference Manual.

rawget :: LuaState -> Int -> IO () Source

See lua_rawget in Lua Reference Manual.

rawgeti :: LuaState -> Int -> Int -> IO () Source

See lua_rawgeti in Lua Reference Manual.

rawset :: LuaState -> Int -> IO () Source

See lua_rawset in Lua Reference Manual.

rawseti :: LuaState -> Int -> Int -> IO () Source

See lua_rawseti in Lua Reference Manual.

remove :: LuaState -> Int -> IO () Source

See lua_remove in Lua Reference Manual.

replace :: LuaState -> Int -> IO () Source

See lua_replace in Lua Reference Manual.

resume :: LuaState -> Int -> IO Int Source

See lua_resume in Lua Reference Manual.

setfenv :: LuaState -> Int -> IO Int Source

See lua_setfenv in Lua Reference Manual.

setmetatable :: LuaState -> Int -> IO () Source

See lua_setmetatable in Lua Reference Manual.

settable :: LuaState -> Int -> IO () Source

See lua_settable in Lua Reference Manual.

status :: LuaState -> IO Int Source

See lua_status in Lua Reference Manual.

toboolean :: LuaState -> Int -> IO Bool Source

See lua_toboolean in Lua Reference Manual.

tocfunction :: LuaState -> Int -> IO (FunPtr LuaCFunction) Source

See lua_tocfunction in Lua Reference Manual.

tointeger :: LuaState -> Int -> IO LuaInteger Source

See lua_tointeger in Lua Reference Manual.

tonumber :: LuaState -> Int -> IO LuaNumber Source

See lua_tonumber in Lua Reference Manual.

topointer :: LuaState -> Int -> IO (Ptr ()) Source

See lua_topointer in Lua Reference Manual.

register :: LuaState -> String -> FunPtr LuaCFunction -> IO () Source

See lua_register in Lua Reference Manual.

newmetatable :: LuaState -> String -> IO Int Source

See luaL_newmetatable 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.

ref :: LuaState -> Int -> IO Int Source

See luaL_ref in Lua Reference Manual.

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

See luaL_unref in Lua Reference Manual.

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.

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.

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

Instances

StackValue a => LuaImport (IO a) 
(StackValue a, LuaImport b) => LuaImport (a -> b) 

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

Methods

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

Instances

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

Methods

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

Instances

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](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 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](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 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.