hslua-0.7.0: A Lua language interpreter embedding in Haskell

Copyright© 2007–2012 Gracjan Polak
2012–2016 Ömer Sinan Ağacan
2017 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb+hslua@zeitkraut.de>
Stabilitybeta
PortabilityFlexibleInstances, ForeignFunctionInterface, ScopedTypeVariables
Safe HaskellNone
LanguageHaskell98

Foreign.Lua

Contents

Description

Bindings, functions, and utilities enabling the integration of a lua interpreter into a haskell project.

Synopsis

Documentation

newtype Lua a Source #

Lua computation

Constructors

Lua 

Fields

Instances

Monad Lua Source # 

Methods

(>>=) :: Lua a -> (a -> Lua b) -> Lua b #

(>>) :: Lua a -> Lua b -> Lua b #

return :: a -> Lua a #

fail :: String -> Lua a #

Functor Lua Source # 

Methods

fmap :: (a -> b) -> Lua a -> Lua b #

(<$) :: a -> Lua b -> Lua a #

Applicative Lua Source # 

Methods

pure :: a -> Lua a #

(<*>) :: Lua (a -> b) -> Lua a -> Lua b #

(*>) :: Lua a -> Lua b -> Lua b #

(<*) :: Lua a -> Lua b -> Lua a #

MonadIO Lua Source # 

Methods

liftIO :: IO a -> Lua a #

MonadThrow Lua Source # 

Methods

throwM :: Exception e => e -> Lua a #

MonadCatch Lua Source # 

Methods

catch :: Exception e => Lua a -> (e -> Lua a) -> Lua a #

ToHaskellFunction HaskellFunction Source # 
MonadReader LuaState Lua Source # 

Methods

ask :: Lua LuaState #

local :: (LuaState -> LuaState) -> Lua a -> Lua a #

reader :: (LuaState -> a) -> Lua a #

FromLuaStack a => LuaCallFunc (Lua a) Source # 

Methods

callFunc' :: String -> Lua () -> NumArgs -> Lua a Source #

ToLuaStack a => ToHaskellFunction (Lua a) Source # 

luaState :: Lua LuaState Source #

Get the lua state of this lua computation.

runLuaWith :: LuaState -> Lua a -> IO a Source #

Run lua computation with custom lua state. Errors are left unhandled, the caller of this function is responsible to catch lua errors.

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

Receiving values from Lua stack (Lua → Haskell)

class FromLuaStack a where Source #

A value that can be read from the Lua stack.

Minimal complete definition

peek

Methods

peek :: StackIndex -> Lua a Source #

Check if at index n there is a convertible Lua value and if so return it. Throws a LuaException otherwise.

Instances

FromLuaStack Bool Source # 
FromLuaStack Int Source # 

Methods

peek :: StackIndex -> Lua Int Source #

FromLuaStack () Source # 

Methods

peek :: StackIndex -> Lua () Source #

FromLuaStack ByteString Source # 
FromLuaStack Text Source # 
FromLuaStack LuaNumber Source # 
FromLuaStack LuaInteger Source # 
FromLuaStack CFunction Source # 
FromLuaStack LuaState Source # 
FromLuaStack [Char] Source # 

Methods

peek :: StackIndex -> Lua [Char] Source #

FromLuaStack a => FromLuaStack [a] Source # 

Methods

peek :: StackIndex -> Lua [a] Source #

FromLuaStack (Ptr a) Source # 

Methods

peek :: StackIndex -> Lua (Ptr a) Source #

(FromLuaStack a, FromLuaStack b) => FromLuaStack (a, b) Source # 

Methods

peek :: StackIndex -> Lua (a, b) Source #

(Ord a, FromLuaStack a, FromLuaStack b) => FromLuaStack (Map a b) Source # 

Methods

peek :: StackIndex -> Lua (Map a b) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c) => FromLuaStack (a, b, c) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c, FromLuaStack d) => FromLuaStack (a, b, c, d) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c, d) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c, FromLuaStack d, FromLuaStack e) => FromLuaStack (a, b, c, d, e) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c, d, e) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c, FromLuaStack d, FromLuaStack e, FromLuaStack f) => FromLuaStack (a, b, c, d, e, f) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c, d, e, f) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c, FromLuaStack d, FromLuaStack e, FromLuaStack f, FromLuaStack g) => FromLuaStack (a, b, c, d, e, f, g) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c, d, e, f, g) Source #

(FromLuaStack a, FromLuaStack b, FromLuaStack c, FromLuaStack d, FromLuaStack e, FromLuaStack f, FromLuaStack g, FromLuaStack h) => FromLuaStack (a, b, c, d, e, f, g, h) Source # 

Methods

peek :: StackIndex -> Lua (a, b, c, d, e, f, g, h) Source #

peekEither :: FromLuaStack a => StackIndex -> Lua (Either String a) Source #

Try to convert the value at the given stack index to a haskell value. Returns Left with an error message on failure.

toList :: FromLuaStack a => StackIndex -> Lua [a] Source #

Read a table into a list

pairsFromTable :: (FromLuaStack a, FromLuaStack b) => StackIndex -> Lua [(a, b)] Source #

Read a table into a list of pairs.

Pushing values to Lua stack (Haskell → Lua)

class ToLuaStack a where Source #

A value that can be pushed to the Lua stack.

Minimal complete definition

push

Methods

push :: a -> Lua () Source #

Pushes a value onto Lua stack, casting it into meaningfully nearest Lua type.

Instances

ToLuaStack Bool Source # 

Methods

push :: Bool -> Lua () Source #

ToLuaStack Int Source # 

Methods

push :: Int -> Lua () Source #

ToLuaStack () Source # 

Methods

push :: () -> Lua () Source #

ToLuaStack ByteString Source # 

Methods

push :: ByteString -> Lua () Source #

ToLuaStack Text Source # 

Methods

push :: Text -> Lua () Source #

ToLuaStack LuaNumber Source # 

Methods

push :: LuaNumber -> Lua () Source #

ToLuaStack LuaInteger Source # 

Methods

push :: LuaInteger -> Lua () Source #

ToLuaStack CFunction Source # 

Methods

push :: CFunction -> Lua () Source #

ToLuaStack [Char] Source # 

Methods

push :: [Char] -> Lua () Source #

ToLuaStack a => ToLuaStack [a] Source # 

Methods

push :: [a] -> Lua () Source #

ToLuaStack (Ptr a) Source # 

Methods

push :: Ptr a -> Lua () Source #

(ToLuaStack a, ToLuaStack b) => ToLuaStack (a, b) Source # 

Methods

push :: (a, b) -> Lua () Source #

(ToLuaStack a, ToLuaStack b) => ToLuaStack (Map a b) Source # 

Methods

push :: Map a b -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c) => ToLuaStack (a, b, c) Source # 

Methods

push :: (a, b, c) -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d) => ToLuaStack (a, b, c, d) Source # 

Methods

push :: (a, b, c, d) -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d, ToLuaStack e) => ToLuaStack (a, b, c, d, e) Source # 

Methods

push :: (a, b, c, d, e) -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d, ToLuaStack e, ToLuaStack f) => ToLuaStack (a, b, c, d, e, f) Source # 

Methods

push :: (a, b, c, d, e, f) -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d, ToLuaStack e, ToLuaStack f, ToLuaStack g) => ToLuaStack (a, b, c, d, e, f, g) Source # 

Methods

push :: (a, b, c, d, e, f, g) -> Lua () Source #

(ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d, ToLuaStack e, ToLuaStack f, ToLuaStack g, ToLuaStack h) => ToLuaStack (a, b, c, d, e, f, g, h) Source # 

Methods

push :: (a, b, c, d, e, f, g, h) -> Lua () Source #

pushList :: ToLuaStack a => [a] -> Lua () Source #

Push list as numerically indexed table.

Calling Functions

type PreCFunction = LuaState -> IO NumResults Source #

Type of raw haskell functions that can be made into CFunctions.

type HaskellFunction = Lua NumResults Source #

Haskell function that can be called from Lua.

callFunc :: LuaCallFunc a => String -> a Source #

Call a Lua function. Use as:

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

newCFunction :: ToHaskellFunction a => a -> Lua CFunction Source #

Create new foreign Lua function. Function created can be called by Lua engine. Remeber to free the pointer with freecfunction.

freeCFunction :: CFunction -> Lua () Source #

Free function pointer created with newcfunction.

pushHaskellFunction :: ToHaskellFunction a => a -> Lua () Source #

Pushes Haskell function converted to a Lua function. All values created will be garbage collected. Use as:

pushHaskellFunction myfun
setglobal "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.

registerHaskellFunction :: ToHaskellFunction a => String -> a -> Lua () Source #

Imports a Haskell function and registers it at global name.

Utility functions

runLua :: Lua a -> IO a Source #

Run lua computation using the default HsLua state as starting point. Raised exceptions are passed through; error handling is the responsibility of the caller.

runLuaEither :: Lua a -> IO (Either LuaException a) Source #

Run the given Lua computation; exceptions raised in haskell code are caught, but other exceptions (user exceptions raised in haskell, unchecked type errors, etc.) are passed through.

getglobal' :: String -> Lua () Source #

Like getglobal, but knows about packages. e. g.

getglobal' l "math.sin"

returns correct result

API

Error handling in hslua

We are trying to keep error handling on the haskell side very simple and intuitive. However, when combined with error handling on the Lua side, it get's tricky: We can call Haskell from Lua which calls Lua again etc. At each language boundary we should check for errors and propagate them properly to the next level in stack. Hslua does this for you when returning from Lua to Haskell, but care must be taken when passing errors back into Lua.

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 the top-most Haskell function. We can't use lua_error from the Lua C API, because it uses longjmp, which means it skips layers of abstractions, including the 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 the wrong type to a Haskell function, the 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 on the Lua side and forget to use pcall in the calling Haskell function, we would be starting to skip layers of abstractions and would get a segfault in the best case. That's why hslua wraps all API functions that can potentially fail in custom C functions. Those functions behave idential to the functions they wrap, but catch all errors and return error codes instead. Using error within Lua should hence be safe.

However, the raw C API bindings in RawBindings don't provide these guarantees. Even an apparently harmless operations like accessing a field via lua_getfield can call a meta method and trigger a longjmp, causing the host program to crash.

The pcall function is not wrapped in additional C code but still safe. The reason it's safe is because the lua_pcall C function is calling the Lua function using Lua C API, and when the called Lua function calls error it longjmps to lua_pcall C function, without skipping any layers of abstraction. lua_pcall then returns to Haskell.

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.

throwLuaError :: String -> Lua a Source #

Raise a LuaException containing the given error message.

tryLua :: Lua a -> Lua (Either LuaException a) Source #

Return either the result of a Lua computation or, if an exception was thrown, the error.