hslua-0.9.5: 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
PortabilityCPP, ForeignFunctionInterface
Safe HaskellNone
LanguageHaskell98

Foreign.Lua.Api

Contents

Description

Monadic functions which operate within the Lua type.

The functions in this module are mostly just thin wrappers around the respective C functions. However, C function which can throw an error are wrapped such that the error is converted into a LuaException. Memory allocation errors, however, are not caught and will cause the host program to terminate.

Synopsis

Lua API types

type CFunction = FunPtr (LuaState -> IO NumResults) Source #

Type for C functions.

In order to communicate properly with Lua, a C function must use the following protocol, which defines the way parameters and results are passed: a C function receives its arguments from Lua in its stack in direct order (the first argument is pushed first). So, when the function starts, gettop returns the number of arguments received by the function. The first argument (if any) is at index 1 and its last argument is at index gettop. To return values to Lua, a C function just pushes them onto the stack, in direct order (the first result is pushed first), and returns the number of results. Any other value in the stack below the results will be properly discarded by Lua. Like a Lua function, a C function called by Lua can also return many results.

See lua_CFunction.

data LuaInteger Source #

The type of integers in Lua.

By default this type is Int64, but that can be changed to different values in lua. (See LUA_INT_TYPE in luaconf.h.)

See lua_Integer.

Instances

Enum LuaInteger Source # 
Eq LuaInteger Source # 
Integral LuaInteger Source # 
Num LuaInteger Source # 
Ord LuaInteger Source # 
Real LuaInteger Source # 
Show LuaInteger Source # 
FromLuaStack LuaInteger Source # 
ToLuaStack LuaInteger Source # 

Methods

push :: LuaInteger -> Lua () Source #

data LuaNumber Source #

The type of floats in Lua.

By default this type is Double, but that can be changed in Lua to a single float or a long double. (See LUA_FLOAT_TYPE in luaconf.h.)

See lua_Number.

Instances

Eq LuaNumber Source # 
Floating LuaNumber Source # 
Fractional LuaNumber Source # 
Num LuaNumber Source # 
Ord LuaNumber Source # 
Real LuaNumber Source # 
RealFloat LuaNumber Source # 
RealFrac LuaNumber Source # 
Show LuaNumber Source # 
FromLuaStack LuaNumber Source # 
ToLuaStack LuaNumber Source # 

Methods

push :: LuaNumber -> Lua () Source #

nthFromBottom :: CInt -> StackIndex Source #

Stack index of the nth element from the bottom of the stack.

nthFromTop :: CInt -> StackIndex Source #

Stack index of the nth element from the top of the stack.

stackTop :: StackIndex Source #

Top of the stack

stackBottom :: StackIndex Source #

Bottom of the stack

newtype NumArgs Source #

The number of arguments expected a function.

Constructors

NumArgs 

Fields

Lua API

Constants and pseudo-indices

multret :: NumResults Source #

Alias for C constant LUA_MULTRET. See lua_call.

registryindex :: StackIndex Source #

Alias for C constant LUA_REGISTRYINDEX. See Lua registry.

noref :: Int Source #

Value signaling that no reference was found.

refnil :: Int Source #

Value signaling that no reference was created.

upvalueindex :: StackIndex -> StackIndex Source #

Returns the pseudo-index that represents the i-th upvalue of the running function (see §4.4 of the Lua 5.3 reference manual).

See also: lua_upvalueindex.

State manipulation

newtype LuaState Source #

An opaque structure that points to a thread and indirectly (through the thread) to the whole state of a Lua interpreter. The Lua library is fully reentrant: it has no global variables. All information about a state is accessible through this structure.

Synonym for lua_State *. See lua_State.

Constructors

LuaState (Ptr ()) 

newstate :: IO LuaState Source #

Creates a new Lua state. It calls lua_newstate with an allocator based on the standard C realloc function and then sets a panic function (see §4.6 of the Lua 5.3 Reference Manual) that prints an error message to the standard error output in case of fatal errors.

See also: luaL_newstate.

close :: LuaState -> IO () Source #

Destroys all objects in the given Lua state (calling the corresponding garbage-collection metamethods, if any) and frees all dynamic memory used by this state. On several platforms, you may not need to call this function, because all resources are naturally released when the host program ends. On the other hand, long-running programs that create multiple states, such as daemons or web servers, will probably need to close states as soon as they are not needed.

This is a wrapper function of lua_close.

Basic stack manipulation

absindex :: StackIndex -> Lua StackIndex Source #

Converts the acceptable index idx into an equivalent absolute index (that is, one that does not depend on the stack top).

gettop :: Lua StackIndex Source #

Returns the index of the top element in the stack. Because indices start at 1, this result is equal to the number of elements in the stack (and so 0 means an empty stack).

See also: lua_gettop.

settop :: StackIndex -> Lua () Source #

Accepts any index, or 0, and sets the stack top to this index. If the new top is larger than the old one, then the new elements are filled with nil. If index is 0, then all stack elements are removed.

See also: lua_settop.

pushvalue :: StackIndex -> Lua () Source #

Pushes a copy of the element at the given index onto the stack.

See lua_pushvalue.

copy :: StackIndex -> StackIndex -> Lua () Source #

Copies the element at index fromidx into the valid index toidx, replacing the value at that position. Values at other positions are not affected.

See also lua_copy in the lua manual.

insert :: StackIndex -> Lua () Source #

Moves the top element into the given valid index, shifting up the elements above this index to open space. This function cannot be called with a pseudo-index, because a pseudo-index is not an actual stack position.

See also: lua_insert.

pop :: StackIndex -> Lua () Source #

Pops n elements from the stack.

See also: lua_pop.

remove :: StackIndex -> Lua () Source #

Removes the element at the given valid index, shifting down the elements above this index to fill the gap. This function cannot be called with a pseudo-index, because a pseudo-index is not an actual stack position.

See lua_remove.

replace :: StackIndex -> Lua () Source #

Moves the top element into the given valid index without shifting any element (therefore replacing the value at that given index), and then pops the top element.

See lua_replace.

checkstack :: Int -> Lua Bool Source #

Ensures that the stack has space for at least n extra slots (that is, that you can safely push up to n values into it). It returns false if it cannot fulfill the request, either because it would cause the stack to be larger than a fixed maximum size (typically at least several thousand elements) or because it cannot allocate memory for the extra space. This function never shrinks the stack; if the stack already has space for the extra slots, it is left unchanged.

This is a wrapper function of lua_checkstack.

types and type checks

data Type Source #

Enumeration used as type tag. See lua_type.

Constructors

TypeNone

non-valid stack index

TypeNil

type of lua's nil value

TypeBoolean

type of lua booleans

TypeLightUserdata

type of light userdata

TypeNumber

type of lua numbers. See LuaNumber

TypeString

type of lua string values

TypeTable

type of lua tables

TypeFunction

type of functions, either normal or CFunction

TypeUserdata

type of full user data

TypeThread

type of lua threads

Instances

Bounded Type Source # 
Enum Type Source # 

Methods

succ :: Type -> Type #

pred :: Type -> Type #

toEnum :: Int -> Type #

fromEnum :: Type -> Int #

enumFrom :: Type -> [Type] #

enumFromThen :: Type -> Type -> [Type] #

enumFromTo :: Type -> Type -> [Type] #

enumFromThenTo :: Type -> Type -> Type -> [Type] #

Eq Type Source # 

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Ord Type Source # 

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

(>=) :: Type -> Type -> Bool #

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

newtype TypeCode Source #

Integer code used to encode the type of a lua value.

Constructors

TypeCode 

Fields

fromType :: Type -> TypeCode Source #

Convert a lua Type to a type code which can be passed to the C API.

toType :: TypeCode -> Type Source #

Convert numerical code to lua type.

typename :: Type -> Lua String Source #

Returns the name of the type encoded by the value tp, which must be one the values returned by ltype.

See also: lua_typename.

isboolean :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a boolean, and False otherwise.

See also: lua_isboolean.

iscfunction :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a C function, and False otherwise.

See also: lua_iscfunction.

isfunction :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a function (either C or Lua), and False otherwise.

See also: lua_isfunction.

islightuserdata :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a light userdata, and False otherwise.

See also: -- lua_islightuserdata.

isnil :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is nil, and False otherwise.

See also: lua_isnil.

isnone :: StackIndex -> Lua Bool Source #

Returns True if the given index is not valid, and False otherwise.

See also: lua_isnone.

isnoneornil :: StackIndex -> Lua Bool Source #

Returns True if the given index is not valid or if the value at the given index is nil, and False otherwise.

See also: lua_isnoneornil.

isnumber :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a number or a string convertible to a number, and False otherwise.

See also: lua_isnumber.

isstring :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a string or a number (which is always convertible to a string), and False otherwise.

See also: lua_isstring.

istable :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a table, and False otherwise.

See also: lua_istable.

isthread :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a thread, and False otherwise.

See also: lua_isthread.

isuserdata :: StackIndex -> Lua Bool Source #

Returns True if the value at the given index is a userdata (either full or light), and False otherwise.

See also: lua_isuserdata.

access functions (stack → Haskell)

toboolean :: StackIndex -> Lua Bool Source #

Converts the Lua value at the given index to a haskell boolean value. Like all tests in Lua, toboolean returns True for any Lua value different from false and nil; otherwise it returns False. (If you want to accept only actual boolean values, use isboolean to test the value's type.)

See also: lua_toboolean.

tocfunction :: StackIndex -> Lua CFunction Source #

Converts a value at the given index to a C function. That value must be a C function; otherwise, returns NULL.

See also: lua_tocfunction.

tointeger :: StackIndex -> Lua LuaInteger Source #

Converts the Lua value at the given acceptable index to the signed integral type lua_Integer. The Lua value must be an integer, a number or a string convertible to an integer (see §3.4.3 of the Lua 5.3 Reference Manual); otherwise, tointeger returns 0.

If the number is not an integer, it is truncated in some non-specified way.

See also: lua_tointeger.

tointegerx :: StackIndex -> Lua (Maybe LuaInteger) Source #

Like tointeger, but returns Nothing if the conversion failed

tonumber :: StackIndex -> Lua LuaNumber Source #

Converts the Lua value at the given index to the C type lua_Number. The Lua value must be a number or a string convertible to a number; otherwise, tonumber returns 0.

See lua_tonumber.

tonumberx :: StackIndex -> Lua (Maybe LuaNumber) Source #

Like tonumber, but returns Nothing if the conversion failed

topointer :: StackIndex -> Lua (Ptr ()) Source #

Converts the value at the given index to a generic C pointer (void*). The value can be a userdata, a table, a thread, or a function; otherwise, lua_topointer returns NULL. Different objects will give different pointers. There is no way to convert the pointer back to its original value.

Typically this function is used only for hashing and debug information.

See also: lua_topointer.

tothread :: StackIndex -> Lua LuaState Source #

Converts the value at the given index to a Lua thread (represented as lua_State*). This value must be a thread; otherwise, the function returns NULL.

See also: lua_tothread.

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

If the value at the given index is a full userdata, returns its block address. If the value is a light userdata, returns its pointer. Otherwise, returns NULL.

See also: lua_touserdata.

objlen :: StackIndex -> Lua Int Source #

Deprecated: Use rawlen instead.

Obsolete alias for rawlen.

rawlen :: StackIndex -> Lua Int Source #

Returns the raw "length" of the value at the given index: for strings, this is the string length; for tables, this is the result of the length operator (#) with no metamethods; for userdata, this is the size of the block of memory allocated for the userdata; for other values, it is 0.

See also: lua_rawlen.

strlen :: StackIndex -> Lua Int Source #

Deprecated: Use rawlen instead.

Compatibility alias for rawlen

Comparison and arithmetic functions

fromRelationalOperator :: RelationalOperator -> CInt Source #

Convert relation operator to its C representation.

compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool Source #

Compares two Lua values. Returns True if the value at index idx1 satisfies op when compared with the value at index idx2, following the semantics of the corresponding Lua operator (that is, it may call metamethods). Otherwise returns False. Also returns False if any of the indices is not valid.

The value of op must be of type LuaComparerOp:

OpEQ: compares for equality (==) OpLT: compares for less than (<) OpLE: compares for less or equal (<=)

This is a wrapper function of lua_compare.

equal :: StackIndex -> StackIndex -> Lua Bool Source #

Returns True if the two values in acceptable indices index1 and index2 are equal, following the semantics of the Lua == operator (that is, may call metamethods). Otherwise returns False. Also returns False if any of the indices is non valid. Uses compare internally.

lessthan :: StackIndex -> StackIndex -> Lua Bool Source #

Tests whether the object under the first index is smaller than that under the second. Uses compare internally.

rawequal :: StackIndex -> StackIndex -> Lua Bool Source #

Returns True if the two values in indices idx1 and idx2 are primitively equal (that is, without calling the __eq metamethod). Otherwise returns False. Also returns False if any of the indices are not valid.

See also: lua_rawequal.

push functions (Haskell → stack)

pushboolean :: Bool -> Lua () Source #

Pushes a boolean value with the given value onto the stack.

See also: lua_pushboolean.

pushcfunction :: CFunction -> Lua () Source #

Pushes a C function onto the stack. This function receives a pointer to a C function and pushes onto the stack a Lua value of type function that, when called, invokes the corresponding C function.

Any function to be callable by Lua must follow the correct protocol to receive its parameters and return its results (see CFunction)

See also: lua_pushcfunction.

pushcclosure :: CFunction -> Int -> Lua () Source #

Pushes a new C closure onto the stack.

When a C function is created, it is possible to associate some values with it, thus creating a C closure (see §3.4); these values are then accessible to the function whenever it is called. To associate values with a C function, first these values should be pushed onto the stack (when there are multiple values, the first value is pushed first). Then lua_pushcclosure is called to create and push the C function onto the stack, with the argument n telling how many values should be associated with the function. lua_pushcclosure also pops these values from the stack.

The maximum value for n is 255.

See also: lua_pushcclosure.

pushinteger :: LuaInteger -> Lua () Source #

Pushes an integer with with the given value onto the stack.

See also: lua_pushinteger.

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

Pushes a light userdata onto the stack.

Userdata represent C values in Lua. A light userdata represents a pointer, a Ptr () (i.e., void* in C lingo). It is a value (like a number): you do not create it, it has no individual metatable, and it is not collected (as it was never created). A light userdata is equal to "any" light userdata with the same C address.

See also: lua_pushlightuserdata.

pushnil :: Lua () Source #

Pushes a nil value onto the stack.

See lua_pushnil.

pushnumber :: LuaNumber -> Lua () Source #

Pushes a float with the given value onto the stack.

See lua_pushnumber.

pushstring :: ByteString -> Lua () Source #

Pushes the zero-terminated string pointed to by s onto the stack. Lua makes (or reuses) an internal copy of the given string, so the memory at s can be freed or reused immediately after the function returns.

See also: -- lua_pushstring.

pushthread :: Lua Bool Source #

Pushes the current thread onto the stack. Returns True if this thread is the main thread of its state, False otherwise.

See also: lua_pushthread.

get functions (Lua → stack)

getglobal :: String -> Lua () Source #

Pushes onto the stack the value of the global name. Returns the type of that value.

Wrapper of lua_getglobal.

gettable :: StackIndex -> Lua () Source #

Pushes onto the stack the value t[k], where t is the value at the given index and k is the value at the top of the stack.

This function pops the key from the stack, pushing the resulting value in its place. As in Lua, this function may trigger a metamethod for the "index" event (see §2.4 of lua's manual).

See also: lua_gettable.

getfield :: StackIndex -> String -> Lua () Source #

Pushes onto the stack the value t[k], where t is the value at the given stack index. As in Lua, this function may trigger a metamethod for the "index" event (see §2.4 of lua's manual).

Returns the type of the pushed value.

See also: lua_getfield.

rawget :: StackIndex -> Lua () Source #

Similar to gettable, but does a raw access (i.e., without metamethods).

See also: lua_rawget.

rawgeti :: StackIndex -> Int -> Lua () Source #

Pushes onto the stack the value t[n], where t is the table at the given index. The access is raw, that is, it does not invoke the __index metamethod.

See also: lua_rawgeti.

createtable :: Int -> Int -> Lua () Source #

Creates a new empty table and pushes it onto the stack. Parameter narr is a hint for how many elements the table will have as a sequence; parameter nrec is a hint for how many other elements the table will have. Lua may use these hints to preallocate memory for the new table. This preallocation is useful for performance when you know in advance how many elements the table will have. Otherwise you can use the function lua_newtable.

This is a wrapper for function lua_createtable.

newtable :: Lua () Source #

Creates a new empty table and pushes it onto the stack. It is equivalent to createtable 0 0.

See also: lua_newtable.

newuserdata :: Int -> Lua (Ptr ()) Source #

This function allocates a new block of memory with the given size, pushes onto the stack a new full userdata with the block address, and returns this address. The host program can freely use this memory.

See also: lua_newuserdata.

getmetatable :: StackIndex -> Lua Bool Source #

If the value at the given index has a metatable, the function pushes that metatable onto the stack and returns True. Otherwise, the function returns False and pushes nothing on the stack.

See also: lua_getmetatable.

set functions (stack → Lua)

setglobal :: String -> Lua () Source #

Pops a value from the stack and sets it as the new value of global name.

See also: lua_setglobal.

settable :: StackIndex -> Lua () Source #

Does the equivalent to t[k] = v, where t is the value at the given index, v is the value at the top of the stack, and k is the value just below the top.

This function pops both the key and the value from the stack. As in Lua, this function may trigger a metamethod for the "newindex" event (see §2.4 of the Lua 5.3 Reference Manual).

See also: lua_settable.

setfield :: StackIndex -> String -> Lua () Source #

Does the equivalent to t[k] = v, where t is the value at the given index and v is the value at the top of the stack.

This function pops the value from the stack. As in Lua, this function may trigger a metamethod for the "newindex" event (see §2.4 of the Lua 5.3 Reference Manual).

See also: lua_setfield.

rawset :: StackIndex -> Lua () Source #

Similar to settable, but does a raw assignment (i.e., without metamethods).

See also: lua_rawset.

rawseti :: StackIndex -> Int -> Lua () Source #

Does the equivalent of t[i] = v, where t is the table at the given index and v is the value at the top of the stack.

This function pops the value from the stack. The assignment is raw, that is, it does not invoke the __newindex metamethod.

See also: lua_rawseti.

setmetatable :: StackIndex -> Lua () Source #

Pops a table from the stack and sets it as the new metatable for the value at the given index.

See also: -- lua_setmetatable.

load and call functions (load and run Lua code)

call :: NumArgs -> NumResults -> Lua () Source #

Calls a function.

To call a function you must use the following protocol: first, the function to be called is pushed onto the stack; then, the arguments to the function are pushed in direct order; that is, the first argument is pushed first. Finally you call call; nargs is the number of arguments that you pushed onto the stack. All arguments and the function value are popped from the stack when the function is called. The function results are pushed onto the stack when the function returns. The number of results is adjusted to nresults, unless nresults is multret. In this case, all results from the function are pushed. Lua takes care that the returned values fit into the stack space. The function results are pushed onto the stack in direct order (the first result is pushed first), so that after the call the last result is on the top of the stack.

Any error inside the called function cause a LuaException to be thrown.

The following example shows how the host program can do the equivalent to this Lua code:

a = f("how", t.x, 14)

Here it is in Haskell (assuming the OverloadedStrings language extension):

getglobal "f"         -- function to be called
pushstring  "how"     -- 1st argument
getglobal "t"         -- table to be indexed
getfield (-1) "x"     -- push result of t.x (2nd arg)
remove (-2)           -- remove 't' from the stack
pushinteger 14        -- 3rd argument
call 3 1              -- call 'f' with 3 arguments and 1 result
setglobal "a"         -- set global 'a'

Note that the code above is "balanced": at its end, the stack is back to its original configuration. This is considered good programming practice.

See lua_call.

pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status Source #

Calls a function in protected mode.

Both nargs and nresults have the same meaning as in call. If there are no errors during the call, pcall behaves exactly like call. However, if there is any error, pcall catches it, pushes a single value on the stack (the error message), and returns the error code. Like call, pcall always removes the function and its arguments from the stack.

If msgh is Nothing, then the error object returned on the stack is exactly the original error object. Otherwise, when msgh is Just idx, the stack index idx is the location of a message handler. (This index cannot be a pseudo-index.) In case of runtime errors, this function will be called with the error object and its return value will be the object returned on the stack by pcall.

Typically, the message handler is used to add more debug information to the error object, such as a stack traceback. Such information cannot be gathered after the return of pcall, since by then the stack has unwound.

See lua_pcall.

Coroutine functions

data Status Source #

Lua status values.

Constructors

OK

success

Yield

yielding / suspended coroutine

ErrRun

a runtime rror

ErrSyntax

syntax error during precompilation

ErrMem

memory allocation (out-of-memory) error.

ErrErr

error while running the message handler.

ErrGcmm

error while running a __gc metamethod.

ErrFile

opening or reading a file failed.

Instances

toStatus :: StatusCode -> Status Source #

Convert C integer constant to LuaStatus.

status :: Lua Status Source #

Returns the status of this Lua thread.

The status can be OK for a normal thread, an error value if the thread finished the execution of a lua_resume with an error, or Yield if the thread is suspended.

You can only call functions in threads with status OK. You can resume threads with status OK (to start a new coroutine) or Yield (to resume a coroutine).

See also: lua_status.

garbage-collection function and options

gc :: GCCONTROL -> Int -> Lua Int Source #

Controls the garbage collector.

This function performs several tasks, according to the value of the parameter what:

  • GCSTOP: stops the garbage collector.
  • GCRESTART: restarts the garbage collector.
  • GCCOLLECT: performs a full garbage-collection cycle.
  • GCCOUNT: returns the current amount of memory (in Kbytes) in use by Lua.
  • GCCOUNTB: returns the remainder of dividing the current amount of bytes of memory in use by Lua by 1024.
  • GCSTEP: performs an incremental step of garbage collection. The step "size" is controlled by data (larger values mean more steps) in a non-specified way. If you want to control the step size you must experimentally tune the value of data. The function returns 1 if the step finished a garbage-collection cycle.
  • 'GCSETPAUSE': sets data as the new value for the pause of the collector (see §2.10). The function returns the previous value of the pause.
  • GCSETSTEPMUL: sets data as the new value for the step multiplier of the collector (see §2.10). The function returns the previous value of the step multiplier.

See lua_gc.

miscellaneous and helper functions

next :: StackIndex -> Lua Bool Source #

Pops a key from the stack, and pushes a key–value pair from the table at the given index (the "next" pair after the given key). If there are no more elements in the table, then next returns False (and pushes nothing).

See also: lua_next.

lerror :: Lua 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)

concat :: NumArgs -> Lua () Source #

Concatenates the n values at the top of the stack, pops them, and leaves the result at the top. If n is 1, the result is the single value on the stack (that is, the function does nothing); if n is 0, the result is the empty string. Concatenation is performed following the usual semantics of Lua (see §3.4.6 of the lua manual).

This is a wrapper function of lua_concat.

register :: String -> CFunction -> Lua () Source #

Sets the C function f as the new value of global name.

See lua_register.

loading libraries

openbase :: Lua () Source #

Opens all standard Lua libraries into the current state.

| See luaopen_base.

opendebug :: Lua () Source #

Opens Lua's debug library into the current state.

See also: luaopen_debug.

openio :: Lua () Source #

Opens Lua's io library into the current state.

See also: luaopen_io.

openlibs :: Lua () Source #

Opens all standard Lua libraries into the current state.

See also: luaL_openlibs.

openmath :: Lua () Source #

Opens Lua's math library into the current state.

See also: luaopen_math.

openpackage :: Lua () Source #

Opens Lua's package library into the current state.

See also: luaopen_package.

openos :: Lua () Source #

Opens Lua's os library into the current state.

See also: luaopen_os.

openstring :: Lua () Source #

Opens Lua's string library into the current state.

See also: luaopen_string.

opentable :: Lua () Source #

Opens Lua's table library into the current state.

See also: luaopen_table.

Auxiliary library

dostring :: String -> Lua Status Source #

Loads and runs the given string.

Returns OK on success, or an error if either loading of the string or calling of the thunk failed.

dofile :: FilePath -> Lua Status Source #

Loads and runs the given file.

newmetatable :: String -> Lua Bool Source #

If the registry already has the key tname, returns False. Otherwise, creates a new table to be used as a metatable for userdata, adds to this new table the pair __name = tname, adds to the registry the pair [tname] = new table, and returns True. (The entry __name is used by some error-reporting functions.)

In both cases pushes onto the stack the final value associated with tname in the registry.

See also: luaL_newmetatable.

ref :: StackIndex -> Lua Int Source #

Creates and returns a reference, in the table at index t, for the object at the top of the stack (and pops the object).

A reference is a unique integer key. As long as you do not manually add integer keys into table t, ref ensures the uniqueness of the key it returns. You can retrieve an object referred by reference r by calling rawgeti t r. Function unref frees a reference and its associated object.

If the object at the top of the stack is nil, ref returns the constant refnil. The constant noref is guaranteed to be different from any reference returned by ref.

See also: luaL_ref.

unref :: StackIndex -> Int -> Lua () Source #

Releases reference ref from the table at index idx (see ref). The entry is removed from the table, so that the referred object can be collected. The reference ref is also freed to be used again.

See also: luaL_unref.

Helper functions

wrapHaskellFunction :: Lua () Source #

Convert a Haskell function userdata object into a CFuntion. The userdata object must be at the top of the stack. Errors signaled via lerror are converted to lua errors.