Portability | portable, ffi |
---|---|
Stability | alpha |
Maintainer | [email protected] |
Safe Haskell | Safe-Inferred |
Scripting.Lua
Contents
Description
A Haskell wrapper library for a scripting language Lua.
See http://www.lua.org/
for more details.
This module is intended to be imported qualified
, eg.
import qualified Scripting.Lua as Lua
This way we use Haskell module hierarchy to make Lua names shorter.
Haskell functions are named after Lua functions, but the lua_
or
luaL_
prefix.
Lua types are mapped to Haskell types as in the following table:
int (stack index) Int lua_Integer LuaInteger lua_Number LuaNumber int (bool result) Bool const char * (string) String void * Ptr () lua_State * LuaState
Most functions are one-to-one mappings. Rare special cases are clearly marked in this document.
Minmal sample embedding:
import qualified Scripting.Lua as Lua
main = do l <- Lua.newstate Lua.openlibs l Lua.callproc l "print" "Hello from Lua" Lua.close l
- newtype LuaState = LuaState (Ptr ())
- type LuaCFunction = LuaState -> IO CInt
- type LuaInteger = CPtrdiff
- type LuaNumber = CDouble
- class LuaImport a where
- luaimport' :: Int -> a -> LuaCFunction
- luaimportargerror :: Int -> String -> a -> LuaCFunction
- data GCCONTROL
- = GCSTOP
- | GCRESTART
- | GCCOLLECT
- | GCCOUNT
- | GCCOUNTB
- | GCSTEP
- | GCSETPAUSE
- | GCSETSTEPMUL
- data LTYPE
- multret :: Int
- registryindex :: Int
- environindex :: Int
- globalsindex :: Int
- atpanic :: LuaState -> FunPtr LuaCFunction -> IO (FunPtr LuaCFunction)
- call :: LuaState -> Int -> Int -> IO Int
- checkstack :: LuaState -> Int -> IO Bool
- close :: LuaState -> IO ()
- concat :: LuaState -> Int -> IO ()
- cpcall :: LuaState -> FunPtr LuaCFunction -> Ptr a -> IO Int
- createtable :: LuaState -> Int -> Int -> IO ()
- dump :: LuaState -> IO String
- equal :: LuaState -> Int -> Int -> IO Bool
- gc :: LuaState -> GCCONTROL -> Int -> IO Int
- getfenv :: LuaState -> Int -> IO ()
- getfield :: LuaState -> Int -> String -> IO ()
- getglobal :: LuaState -> String -> IO ()
- getmetatable :: LuaState -> Int -> IO Bool
- gettable :: LuaState -> Int -> IO ()
- gettop :: LuaState -> IO Int
- getupvalue :: LuaState -> Int -> Int -> IO String
- insert :: LuaState -> Int -> IO ()
- isboolean :: LuaState -> Int -> IO Bool
- iscfunction :: LuaState -> Int -> IO Bool
- isfunction :: LuaState -> Int -> IO Bool
- islightuserdata :: LuaState -> Int -> IO Bool
- isnil :: LuaState -> Int -> IO Bool
- isnumber :: LuaState -> Int -> IO Bool
- isstring :: LuaState -> Int -> IO Bool
- istable :: LuaState -> Int -> IO Bool
- isthread :: LuaState -> Int -> IO Bool
- isuserdata :: LuaState -> Int -> IO Bool
- lessthan :: LuaState -> Int -> Int -> IO Bool
- newstate :: IO LuaState
- newtable :: LuaState -> IO ()
- newthread :: LuaState -> IO LuaState
- newuserdata :: LuaState -> Int -> IO (Ptr ())
- next :: LuaState -> Int -> IO Bool
- objlen :: LuaState -> Int -> IO Int
- pcall :: LuaState -> Int -> Int -> Int -> IO Int
- pop :: LuaState -> Int -> IO ()
- pushboolean :: LuaState -> Bool -> IO ()
- pushcclosure :: LuaState -> FunPtr LuaCFunction -> Int -> IO ()
- pushcfunction :: LuaState -> FunPtr LuaCFunction -> IO ()
- pushinteger :: LuaState -> LuaInteger -> IO ()
- pushlightuserdata :: LuaState -> Ptr a -> IO ()
- pushnil :: LuaState -> IO ()
- pushnumber :: LuaState -> LuaNumber -> IO ()
- pushstring :: LuaState -> String -> 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 ()
- register :: LuaState -> String -> FunPtr LuaCFunction -> IO ()
- remove :: LuaState -> Int -> IO ()
- replace :: LuaState -> Int -> IO ()
- resume :: LuaState -> Int -> IO Int
- setfenv :: LuaState -> Int -> IO Int
- setfield :: LuaState -> Int -> String -> IO ()
- setglobal :: LuaState -> String -> IO ()
- setmetatable :: LuaState -> Int -> IO ()
- settable :: LuaState -> Int -> IO ()
- settop :: LuaState -> Int -> IO ()
- setupvalue :: LuaState -> Int -> Int -> IO String
- status :: LuaState -> IO Int
- toboolean :: LuaState -> Int -> IO Bool
- tocfunction :: LuaState -> Int -> IO (FunPtr LuaCFunction)
- tointeger :: LuaState -> Int -> IO LuaInteger
- tonumber :: LuaState -> Int -> IO CDouble
- topointer :: LuaState -> Int -> IO (Ptr ())
- tostring :: LuaState -> Int -> IO String
- tothread :: LuaState -> Int -> IO LuaState
- touserdata :: LuaState -> Int -> IO (Ptr a)
- ltype :: LuaState -> Int -> IO LTYPE
- typename :: LuaState -> LTYPE -> IO String
- upvalueindex :: Int -> Int
- xmove :: LuaState -> LuaState -> Int -> IO ()
- yield :: LuaState -> Int -> IO Int
- openlibs :: LuaState -> IO ()
- loadfile :: LuaState -> String -> IO Int
- loadstring :: LuaState -> String -> String -> IO Int
- newmetatable :: LuaState -> String -> IO Int
- argerror :: LuaState -> Int -> String -> IO CInt
- class StackValue a where
- callproc :: LuaCallProc a => LuaState -> String -> a
- callfunc :: LuaCallFunc a => LuaState -> String -> a
- getglobal2 :: LuaState -> String -> IO ()
- newcfunction :: LuaImport a => a -> IO (FunPtr LuaCFunction)
- freecfunction :: FunPtr LuaCFunction -> IO ()
- luaimport :: LuaImport a => a -> LuaCFunction
- pushhsfunction :: LuaImport a => LuaState -> a -> IO ()
- registerhsfunction :: LuaImport a => LuaState -> String -> a -> IO ()
Basic Lua types
Wrapper for lua_State *
. See lua_State
in Lua Reference Manual.
Instances
type LuaCFunction = LuaState -> IO CIntSource
Wrapper for lua_CFunction
. See lua_CFunction
in Lua Reference Manual.
type LuaInteger = CPtrdiffSource
Wrapper for lua_Integer
. See lua_Integer
in Lua Reference Manual.
HsLua uses C ptrdiff_t
as lua_Integer
.
type LuaNumber = CDoubleSource
Wrapper for lua_Number
. See lua_Number
in Lua Reference Manual.
HsLua uses C double
as lua_Integer
.
Methods
luaimport' :: Int -> a -> LuaCFunctionSource
luaimportargerror :: Int -> String -> a -> LuaCFunctionSource
Instances
StackValue a => LuaImport (IO a) | |
(StackValue a, LuaImport b) => LuaImport (a -> b) |
Constants and enumerations
Enumeration used by gc
function.
Constructors
GCSTOP | |
GCRESTART | |
GCCOLLECT | |
GCCOUNT | |
GCCOUNTB | |
GCSTEP | |
GCSETPAUSE | |
GCSETSTEPMUL |
Enumeration used as type tag. See lua_type
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.
lua_* functions
atpanic :: LuaState -> FunPtr LuaCFunction -> IO (FunPtr LuaCFunction)Source
See lua_atpanic
in Lua Reference Manual.
call :: LuaState -> Int -> Int -> IO IntSource
See lua_call
and lua_call
in Lua Reference Manual. This is
a wrapper over lua_pcall
, as lua_call
is unsafe in controlled environment
like Haskell VM.
cpcall :: LuaState -> FunPtr LuaCFunction -> Ptr a -> IO IntSource
See lua_cpcall
in Lua Reference Manual.
gc :: LuaState -> GCCONTROL -> Int -> IO IntSource
See lua_error
in Lua Reference Manual.
error :: LuaState -> IO Int
error l = liftM fromIntegral (c_lua_error l)
See lua_gc
in Lua Reference Manual.
pushboolean :: LuaState -> Bool -> IO ()Source
See lua_pushboolean
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.
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 -> String -> IO ()Source
See lua_pushstring
in Lua Reference Manual.
pushthread :: LuaState -> IO BoolSource
See lua_pushthread
in Lua Reference Manual.
register :: LuaState -> String -> FunPtr LuaCFunction -> IO ()Source
See lua_register
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.
upvalueindex :: Int -> IntSource
See lua_upvalueindex
in Lua Reference Manual.
luaL_* functions
loadstring :: LuaState -> String -> String -> IO IntSource
See luaL_loadstring
in Lua Reference Manual.
argerror :: LuaState -> Int -> String -> IO CIntSource
See luaL_argerror
in Lua Reference Manual. Contrary to the
manual, Haskell function does return with value less than zero.
Haskell extensions
class StackValue a whereSource
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
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.
Lua type id code of the vaule expected. Parameter is unused.
callproc :: LuaCallProc a => LuaState -> String -> aSource
Call a Lua procedure. Use as:
callproc l "proc" "abc" (1::Int) (5.0::Double)
callfunc :: LuaCallFunc a => LuaState -> String -> aSource
Call a Lua function. Use as:
Just v <- callfunc l "proc" "abc" (1::Int) (5.0::Double)
getglobal2 :: LuaState -> String -> IO ()Source
Like getglobal
, but knows about packages. e. g.
getglobal l "math.sin"
returns correct result
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
.
freecfunction :: FunPtr LuaCFunction -> IO ()Source
Free function pointer created with newcfunction
.
luaimport :: LuaImport a => a -> LuaCFunctionSource
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.
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.