lua-2.2.1: Lua, an embeddable scripting language
Copyright© 2021-2022 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb+hslua@zeitkraut.de>
Stabilitybeta
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Lua

Description

Extend Haskell programs with a Lua interpreter.

This package provides the basic building blocks to integrate Lua into a Haskell program. The library is kept very close to the C Lua API, and users familiar with the C API should have no problem using it.

However, there are important differences of which users must be aware: The method for error signaling used in Lua, based on setjmp and longjmp, is incompatible with the Haskell FFI. All errors must be handled at language boundaries, as failure to do so will lead to unrecoverable crashes. C API functions that can throw Lua errors are still exported, but non-error throwing hslua_ versions are provided as safer alternatives. . The hslua ersatz functions have worse performance than the original versions, but should be fast enough for most use cases.

The Haskell FFI requires all C function that can call back into Haskell to be imported safely. Some of the Lua functions may, directly or indirectly, call a Haskell function, so they are always imported with the safe keyword.

Many API functions can trigger garbage collection. This will lead to problems if Haskell functions are used as part of finalizers (i.e., __gc metamethods). Haskell in finalizers is not supported by default, but can be enabled by unsetting the allow-unsafe-gc flag.

Synopsis

Run Lua operations

withNewState :: (State -> IO a) -> IO a Source #

Runs operations on a new Lua State. The state is created when the function is called and closed on return. The state, and all pointers to values within it, must not be used after the function returns.

Example

Run a small Lua operation (prints the major version of Lua).

withNewState $ \l -> do
  luaL_openlibs l
  withCString "print" (lua_getglobal l)
  withCString "_VERSION" (lua_getglobal l)
  lua_pcall l (NumArgs 1) (NumResults 1) (StackIndex 0)

Since: 2.0.0

Types

newtype State 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

State (Ptr ()) 

Instances

Instances details
Eq State Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Generic State Source # 
Instance details

Defined in Lua.Types

Associated Types

type Rep State :: Type -> Type #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

type Rep State Source # 
Instance details

Defined in Lua.Types

type Rep State = D1 ('MetaData "State" "Lua.Types" "lua-2.2.1-KlU5RPNhml0CgrTmPpae4U" 'True) (C1 ('MetaCons "State" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr ()))))

type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar)) Source #

The reader function used by load. Every time it needs another piece of the chunk, lua_load calls the reader, passing along its data parameter. The reader must return a pointer to a block of memory with a new piece of the chunk and set size to the block size. The block must exist until the reader function is called again. To signal the end of the chunk, the reader must return NULL or set size to zero. The reader function may return pieces of any size greater than zero.

See lua_Reader.

Base Lua types

type CFunction = FunPtr PreCFunction 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, lua_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 lua_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.

type PreCFunction = State -> IO NumResults Source #

Type of Haskell functions that can be turned into C functions.

This is the same as a dereferenced CFunction.

newtype Integer 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.

Constructors

Integer Int64 

Instances

Instances details
Bounded Integer Source # 
Instance details

Defined in Lua.Types

Enum Integer Source # 
Instance details

Defined in Lua.Types

Eq Integer Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Integral Integer Source # 
Instance details

Defined in Lua.Types

Num Integer Source # 
Instance details

Defined in Lua.Types

Ord Integer Source # 
Instance details

Defined in Lua.Types

Read Integer Source # 
Instance details

Defined in Lua.Types

Real Integer Source # 
Instance details

Defined in Lua.Types

Show Integer Source # 
Instance details

Defined in Lua.Types

newtype Number 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.

Constructors

Number Double 

Instances

Instances details
Eq Number Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Floating Number Source # 
Instance details

Defined in Lua.Types

Fractional Number Source # 
Instance details

Defined in Lua.Types

Num Number Source # 
Instance details

Defined in Lua.Types

Ord Number Source # 
Instance details

Defined in Lua.Types

Read Number Source # 
Instance details

Defined in Lua.Types

Real Number Source # 
Instance details

Defined in Lua.Types

RealFloat Number Source # 
Instance details

Defined in Lua.Types

RealFrac Number Source # 
Instance details

Defined in Lua.Types

Methods

properFraction :: Integral b => Number -> (b, Number) #

truncate :: Integral b => Number -> b #

round :: Integral b => Number -> b #

ceiling :: Integral b => Number -> b #

floor :: Integral b => Number -> b #

Show Number Source # 
Instance details

Defined in Lua.Types

Booleans

newtype LuaBool Source #

Boolean value returned by a Lua C API function. This is a CInt and should be interpreted as False iff the value is 0, True otherwise.

Constructors

LuaBool CInt 

Instances

Instances details
Eq LuaBool Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Show LuaBool Source # 
Instance details

Defined in Lua.Types

Storable LuaBool Source # 
Instance details

Defined in Lua.Types

pattern TRUE :: LuaBool Source #

Value which Lua usually uses as True.

pattern FALSE :: LuaBool Source #

Value which Lua usually uses as False.

Stack indices

newtype StackIndex Source #

A stack index

Constructors

StackIndex 

Fields

Instances

Instances details
Enum StackIndex Source # 
Instance details

Defined in Lua.Types

Eq StackIndex Source # 
Instance details

Defined in Lua.Types

Num StackIndex Source # 
Instance details

Defined in Lua.Types

Ord StackIndex Source # 
Instance details

Defined in Lua.Types

Show StackIndex Source # 
Instance details

Defined in Lua.Types

pattern LUA_REGISTRYINDEX :: StackIndex Source #

Stack index of the Lua registry.

Function calling

newtype NumArgs Source #

The number of arguments consumed curing a function call.

Constructors

NumArgs 

Fields

Instances

Instances details
Eq NumArgs Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Num NumArgs Source # 
Instance details

Defined in Lua.Types

Ord NumArgs Source # 
Instance details

Defined in Lua.Types

Show NumArgs Source # 
Instance details

Defined in Lua.Types

newtype NumResults Source #

The number of results returned by a function call.

Constructors

NumResults 

Fields

pattern LUA_MULTRET :: NumResults Source #

Option for multiple returns in lua_pcall.

Basic types

newtype TypeCode Source #

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

Constructors

TypeCode 

Fields

Instances

Instances details
Eq TypeCode Source # 
Instance details

Defined in Lua.Types

Ord TypeCode Source # 
Instance details

Defined in Lua.Types

Show TypeCode Source # 
Instance details

Defined in Lua.Types

pattern LUA_TNONE :: TypeCode Source #

Non-valid stack index

pattern LUA_TNIL :: TypeCode Source #

Type of Lua's nil value

pattern LUA_TBOOLEAN :: TypeCode Source #

Type of Lua booleans

pattern LUA_TLIGHTUSERDATA :: TypeCode Source #

Type of light userdata

pattern LUA_TNUMBER :: TypeCode Source #

Type of Lua numbers. See Number

pattern LUA_TSTRING :: TypeCode Source #

Type of Lua string values

pattern LUA_TTABLE :: TypeCode Source #

Type of Lua tables

pattern LUA_TFUNCTION :: TypeCode Source #

Type of functions, either normal or CFunction

pattern LUA_TUSERDATA :: TypeCode Source #

Type of full user data

pattern LUA_TTHREAD :: TypeCode Source #

Type of Lua threads

Relational operator codes

newtype OPCode Source #

Relational operator code.

Constructors

OPCode CInt 

Instances

Instances details
Eq OPCode Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Show OPCode Source # 
Instance details

Defined in Lua.Types

Storable OPCode Source # 
Instance details

Defined in Lua.Types

pattern LUA_OPEQ :: OPCode Source #

Compares for equality (==)

pattern LUA_OPLT :: OPCode Source #

Compares for less than (<)

pattern LUA_OPLE :: OPCode Source #

Compares for less or equal (<=)

Codes for arithmetic operations

pattern LUA_OPADD :: ArithOPCode Source #

Performs addition (+).

pattern LUA_OPSUB :: ArithOPCode Source #

Performs subtraction (-)

pattern LUA_OPMUL :: ArithOPCode Source #

Performs multiplication (*)

pattern LUA_OPDIV :: ArithOPCode Source #

Performs float division (/)

pattern LUA_OPIDIV :: ArithOPCode Source #

Performs floor division (//)

pattern LUA_OPMOD :: ArithOPCode Source #

Performs modulo (%)

pattern LUA_OPPOW :: ArithOPCode Source #

Performs exponentiation (^)

pattern LUA_OPUNM :: ArithOPCode Source #

Performs mathematical negation (unary -)

pattern LUA_OPBNOT :: ArithOPCode Source #

Performs bitwise NOT (~)

pattern LUA_OPBAND :: ArithOPCode Source #

Performs bitwise AND (&)

pattern LUA_OPBOR :: ArithOPCode Source #

Performs bitwise OR (|)

pattern LUA_OPBXOR :: ArithOPCode Source #

Performs bitwise exclusive OR (~)

pattern LUA_OPSHL :: ArithOPCode Source #

Performs left shift (<<)

pattern LUA_OPSHR :: ArithOPCode Source #

Performs right shift (>>)

Status codes

newtype StatusCode Source #

Integer code used to signal the status of a thread or computation.

Constructors

StatusCode CInt 

Instances

Instances details
Eq StatusCode Source # 
Instance details

Defined in Lua.Types

Show StatusCode Source # 
Instance details

Defined in Lua.Types

Storable StatusCode Source # 
Instance details

Defined in Lua.Types

pattern LUA_OK :: StatusCode Source #

Success.

pattern LUA_YIELD :: StatusCode Source #

Yielding / suspended coroutine.

pattern LUA_ERRRUN :: StatusCode Source #

A runtime error.

pattern LUA_ERRSYNTAX :: StatusCode Source #

A syntax error.

pattern LUA_ERRMEM :: StatusCode Source #

Memory allocation error. For such errors, Lua does not call the message handler.

pattern LUA_ERRERR :: StatusCode Source #

Error while running the message handler.

pattern LUA_ERRFILE :: StatusCode Source #

File related error (e.g., the file cannot be opened or read).

Stack index helpers

nthTop :: CInt -> StackIndex Source #

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

Since: 2.0.0

nthBottom :: CInt -> StackIndex Source #

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

Since: 2.0.0

nth :: CInt -> StackIndex Source #

Alias for nthTop.

Since: 2.0.0

top :: StackIndex Source #

Index of the topmost stack element.

Since: 2.0.0

Functions

State manipulation

lua_close :: State -> 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. In 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.

https://www.lua.org/manual/5.4/manual.html#lua_close

lua_newthread :: State -> IO State Source #

Creates a new thread, pushes it on the stack, and returns a State that represents this new thread. The new thread returned by this function shares with the original thread its global environment, but has an independent execution stack.

There is no explicit function to close or to destroy a thread. Threads are subject to garbage collection, like any Lua object.

https://www.lua.org/manual/5.4/manual.html#lua_newthread

lua_version :: State -> IO (Ptr Number) Source #

Returns the address of the version number (a C static variable) stored in the Lua core. When called with a valid State, returns the address of the version used to create that state. When called with NULL, returns the address of the version running the call.

https://www.lua.org/manual/5.4/manual.html#lua_version

Basic stack manipulation

lua_absindex Source #

Arguments

:: State 
-> StackIndex

idx

-> IO StackIndex 

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

https://www.lua.org/manual/5.4/manual.html#lua_absindex

lua_gettop :: State -> IO 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).

https://www.lua.org/manual/5.4/manual.html#lua_gettop

lua_settop Source #

Arguments

:: State 
-> StackIndex

index

-> IO () 

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.

https://www.lua.org/manual/5.4/manual.html#lua_settop

lua_pushvalue :: State -> StackIndex -> IO () Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_pushvalue

lua_pop Source #

Arguments

:: State 
-> CInt

n

-> IO () 

lua_copy Source #

Arguments

:: State 
-> StackIndex

fromidx

-> StackIndex

toidx

-> IO () 

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

https://www.lua.org/manual/5.4/manual.html#lua_copy

lua_remove :: State -> StackIndex -> IO () 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.

https://www.lua.org/manual/5.4/manual.html#lua_remove

lua_insert :: State -> StackIndex -> IO () 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.

https://www.lua.org/manual/5.4/manual.html#lua_insert

lua_replace :: State -> StackIndex -> IO () 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.

https://www.lua.org/manual/5.4/manual.html#lua_replace

lua_rotate Source #

Arguments

:: State 
-> StackIndex

idx

-> CInt

n

-> IO () 

Rotates the stack elements between the valid index idx and the top of the stack. The elements are rotated n positions in the direction of the top, for a positive n, or -n positions in the direction of the bottom, for a negative n. The absolute value of n must not be greater than the size of the slice being rotated. This function cannot be called with a pseudo-index, because a pseudo-index is not an actual stack position.

https://www.lua.org/manual/5.4/manual.html#lua_rotate

lua_checkstack Source #

Arguments

:: State 
-> CInt

n

-> IO LuaBool 

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.

https://www.lua.org/manual/5.4/manual.html#lua_checkstack

Access functions (stack → Haskell)

lua_isnil :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is nil, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_isnil

lua_isboolean :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is a boolean, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_isboolean

lua_isnumber :: State -> StackIndex -> IO LuaBool Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_isnumber

lua_isinteger :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is an integer (that is, the value is a number and is represented as an integer), and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_isinteger

lua_isstring :: State -> StackIndex -> IO LuaBool 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.

https://www.lua.org/manual/5.4/manual.html#lua_isstring

lua_isfunction :: State -> StackIndex -> IO LuaBool Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_isfunction

lua_istable :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is a table, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_istable

lua_iscfunction :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is a C function, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_iscfunction

lua_isuserdata :: State -> StackIndex -> IO LuaBool Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_isuserdata

lua_islightuserdata :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is a light userdata, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_islightuserdata

lua_isthread :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the value at the given index is a thread, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_isthread

lua_isnone :: State -> StackIndex -> IO LuaBool Source #

Returns TRUE if the given index is not valid, and FALSE otherwise.

https://www.lua.org/manual/5.4/manual.html#lua_isnone

lua_isnoneornil :: State -> StackIndex -> IO LuaBool Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_isnoneornil

lua_type :: State -> StackIndex -> IO TypeCode Source #

Returns the type of the value in the given valid index, or LUA_TNONE for a non-valid (but acceptable) index.

https://www.lua.org/manual/5.4/manual.html#lua_type

lua_typename Source #

Arguments

:: State 
-> TypeCode

tp

-> IO CString 

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

https://www.lua.org/manual/5.4/manual.html#lua_typename

lua_rawequal Source #

Arguments

:: State 
-> StackIndex

idx1

-> StackIndex

idx2

-> IO LuaBool 

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.

https://www.lua.org/manual/5.4/manual.html#lua_rawequal

lua_toboolean :: State -> StackIndex -> IO LuaBool 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 lua_isboolean to test the value's type.)

https://www.lua.org/manual/5.4/manual.html#lua_toboolean

lua_tocfunction :: State -> StackIndex -> IO CFunction Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_tocfunction

lua_tointegerx Source #

Arguments

:: State 
-> StackIndex

index

-> Ptr LuaBool

isnum

-> IO Integer 

Converts the Lua value at the given acceptable index to the signed integral type 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.4 Reference Manual); otherwise, lua_tointegerx returns 0.

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

If isnum is not NULL, its referent is assigned a boolean value that indicates whether the operation succeeded.

https://www.lua.org/manual/5.4/manual.html#lua_tointegerx

lua_tonumberx Source #

Arguments

:: State 
-> StackIndex

index

-> Ptr LuaBool

isnum

-> IO Number 

Converts the Lua value at the given index to the C type lua_Number (see lua_Number). The Lua value must be a number or a string convertible to a number (see §3.4.3); otherwise, lua_tonumberx returns 0.

If isnum is not NULL, its referent is assigned a boolean value that indicates whether the operation succeeded.

https://www.lua.org/manual/5.4/manual.html#lua_tonumberx

lua_tolstring Source #

Arguments

:: State 
-> StackIndex

index

-> Ptr CSize

len

-> IO (Ptr CChar) 

Converts the Lua value at the given index to a C string. If len is not NULL, it sets the referent with the string length. The Lua value must be a string or a number; otherwise, the function returns NULL. If the value is a number, then lua_tolstring also changes the actual value in the stack to a string. (This change confuses lua_next when lua_tolstring is applied to keys during a table traversal.)

lua_tolstring returns a pointer to a string inside the Lua state. This string always has a zero ('0') after its last character (as in C), but can contain other zeros in its body.

Because Lua has garbage collection, there is no guarantee that the pointer returned by lua_tolstring will be valid after the corresponding Lua value is removed from the stack.

https://www.lua.org/manual/5.4/manual.html#lua_tolstring

lua_topointer :: State -> StackIndex -> IO (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 nullPtr. 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.

https://www.lua.org/manual/5.4/manual.html#lua_topointer

lua_tothread :: State -> StackIndex -> IO State Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_tothread

lua_touserdata :: State -> StackIndex -> IO (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 nullPtr.

https://www.lua.org/manual/5.4/manual.html#lua_touserdata

lua_rawlen :: State -> StackIndex -> IO CSize 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.

https://www.lua.org/manual/5.4/manual.html#lua_rawlen.

Push functions (Haskell → stack)

lua_pushnumber :: State -> Number -> IO () Source #

Pushes a float with the given value onto the stack.

https://www.lua.org/manual/5.4/manual.html#lua_pushnumber.

lua_pushinteger :: State -> Integer -> IO () Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_pushinteger.

lua_pushlstring Source #

Arguments

:: State 
-> Ptr CChar

s

-> CSize

len

-> IO () 

Pushes the string pointed to by s with size len 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. The string can contain any binary data, including embedded zeros.

Returns a pointer to the internal copy of the string.

https://www.lua.org/manual/5.4/manual.html#lua_pushlstring.

lua_pushstring Source #

Arguments

:: State 
-> CString

s

-> IO CString 

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.

Returns a pointer to the internal copy of the string.

If s is NULL, pushes nil and returns NULL.

lua_pushcclosure Source #

Arguments

:: State 
-> CFunction

fn

-> NumArgs

n

-> IO () 

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.

https://www.lua.org/manual/5.4/manual.html#lua_pushcclosure.

lua_pushcfunction Source #

Arguments

:: State 
-> CFunction

fn

-> IO () 

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).

https://www.lua.org/manual/5.4/manual.html#lua_pushcfunction.

lua_pushboolean :: State -> LuaBool -> IO () Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_pushboolean.

lua_pushlightuserdata :: State -> Ptr a -> IO () 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.

https://www.lua.org/manual/5.4/manual.html#lua_pushlightuserdata.

lua_pushthread :: State -> IO CInt Source #

Pushes the current thread onto the stack. Returns 1 iff this thread is the main thread of its state.

https://www.lua.org/manual/5.4/manual.html#lua_pushthread.

Get functions (Lua → stack)

lua_rawget :: State -> StackIndex -> IO TypeCode Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_rawget.

lua_rawgeti Source #

Arguments

:: State 
-> StackIndex 
-> Integer

n

-> IO TypeCode 

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.

https://www.lua.org/manual/5.4/manual.html#lua_rawgeti.

lua_createtable Source #

Arguments

:: State 
-> CInt

narr

-> CInt

nrec

-> IO () 

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.

https://www.lua.org/manual/5.4/manual.html#lua_createtable.

lua_newuserdatauv Source #

Arguments

:: State 
-> CSize

size

-> CInt

nuvalue

-> IO (Ptr ()) 

This function creates and pushes on the stack a new full userdata, with nuvalue associated Lua values, called user values, plus an associated block of raw memory with size bytes. (The user values can be set and read with the functions lua_setiuservalue and lua_getiuservalue.)

The function returns the address of the block of memory. Lua ensures that this address is valid as long as the corresponding userdata is alive (see §2.5). Moreover, if the userdata is marked for finalization (see §2.5.3), its address is valid at least until the call to its finalizer.

https://www.lua.org/manual/5.4/manual.html#lua_newuserdatauv.

lua_getmetatable :: State -> StackIndex -> IO LuaBool Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_getmetatable.

lua_getiuservalue Source #

Arguments

:: State 
-> StackIndex

index

-> CInt

n

-> IO TypeCode 

Pushes onto the stack the n-th user value associated with the full userdata at the given index and returns the type of the pushed value.

If the userdata does not have that value, pushes nil and returns LUA_TNONE.

https://www.lua.org/manual/5.4/manual.html#lua_getiuservalue

lua_getglobal Source #

Arguments

:: State 
-> CString

name

-> IO TypeCode 

Warning: This is an unsafe function, errors will lead to a program crash;consider using hslua_getglobal instead.

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

WARNING: lua_getglobal is unsafe in Haskell: if the call to a metamethod triggers an error, then that error cannot be handled and will lead to an unrecoverable program crash. Consider using the hslua_getglobal ersatz function instead. Likewise, the metamethod may not call a Haskell function unless the library was compiled without allow-unsafe-gc.

https://www.lua.org/manual/5.4/manual.html#lua_getglobal.

lua_gettable Source #

Arguments

:: State 
-> StackIndex

index

-> IO TypeCode 

Warning: This is an unsafe function, errors will lead to a program crash;consider using hslua_gettable instead.

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).

Returns the type of the pushed value.

WARNING: lua_gettable is unsafe in Haskell: if the call to a metamethod triggers an error, then that error cannot be handled and will lead to an unrecoverable program crash. Consider using the hslua_gettable ersatz function instead. Likewise, the metamethod may not call a Haskell function unless the library was compiled without allow-unsafe-gc.

https://www.lua.org/manual/5.4/manual.html#lua_gettable.

Set functions (stack → Lua)

lua_rawset :: State -> StackIndex -> IO () Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_rawset.

lua_rawseti :: State -> StackIndex -> Integer -> IO () 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.

https://www.lua.org/manual/5.4/manual.html#lua_rawseti.

lua_setmetatable :: State -> StackIndex -> IO () Source #

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

https://www.lua.org/manual/5.4/manual.html#lua_setmetatable.

lua_setiuservalue Source #

Arguments

:: State 
-> StackIndex

index

-> CInt

n

-> IO LuaBool 

Pops a value from the stack and sets it as the new n-th user value associated to the full userdata at the given index. Returns 0 if the userdata does not have that value.

https://www.lua.org/manual/5.4/manual.html#lua_setiuservalue

lua_setglobal Source #

Arguments

:: State 
-> CString

name

-> IO () 

Warning: This is an unsafe function, errors will lead to a program crash;consider using hslua_getglobal instead.

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

WARNING: lua_setglobal is unsafe in Haskell: if the call to a metamethod triggers an error, then that error cannot be handled and will lead to an unrecoverable program crash. Consider using the hslua_setglobal ersatz function instead. Likewise, the global metamethod may not call a Haskell function unless the library was compiled without allow-unsafe-gc.

https://www.lua.org/manual/5.4/manual.html#lua_setglobal.

lua_settable Source #

Arguments

:: State 
-> StackIndex

index

-> IO () 

Warning: This is an unsafe function, errors will lead to a program crash;consider using hslua_settable instead.

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).

WARNING: lua_settable is unsafe in Haskell: if the call to a metamethod triggers an error, then that error cannot be handled and will lead to an unrecoverable program crash. Consider using the hslua_settable ersatz function instead. Likewise, the metamethod may not call a Haskell function unless the library was compiled without allow-unsafe-gc.

https://www.lua.org/manual/5.4/manual.html#lua_settable

Misc (safe)

lua_stringtonumber :: State -> CString -> IO CSize Source #

Converts the zero-terminated string s to a number, pushes that number into the stack, and returns the total size of the string, that is, its length plus one. The conversion can result in an integer or a float, according to the lexical conventions of Lua (see §3.1). The string may have leading and trailing spaces and a sign. If the string is not a valid numeral, returns 0 and pushes nothing. (Note that the result can be used as a boolean, true if the conversion succeeds.)

https://www.lua.org/manual/5.4/manual.html#lua_stringtonumber.

Misc (unsafe)

lua_arith Source #

Arguments

:: State 
-> ArithOPCode

op

-> IO () 

Warning: This is an unsafe function, errors will lead to a program crash;consider using hslua_arith instead.

Performs an arithmetic or bitwise operation over the two values (or one, in the case of negations) at the top of the stack, with the value at the top being the second operand, pops these values, and pushes the result of the operation. The function follows the semantics of the corresponding Lua operator (that is, it may call metamethods).

The value of op must be one of the following constants:

  • LUA_OPADD: performs addition (+)
  • LUA_OPSUB: performs subtraction (-)
  • LUA_OPMUL: performs multiplication (*)
  • LUA_OPDIV: performs float division (/)
  • LUA_OPIDIV: performs floor division (//)
  • LUA_OPMOD: performs modulo (%)
  • LUA_OPPOW: performs exponentiation (^)
  • LUA_OPUNM: performs mathematical negation (unary -)
  • LUA_OPBNOT: performs bitwise NOT (~)
  • LUA_OPBAND: performs bitwise AND (&)
  • LUA_OPBOR: performs bitwise OR (|)
  • LUA_OPBXOR: performs bitwise exclusive OR (~)
  • LUA_OPSHL: performs left shift (<<)
  • LUA_OPSHR: performs right shift (>>)

WARNING: lua_arith is unsafe in Haskell: if the call to a metamethod triggers an error, then that error cannot be handled and will lead to an unrecoverable program crash. Consider using the hslua_arith ersatz function instead. Likewise, the metamethod may not call a Haskell function unless the library was compiled without allow-unsafe-gc.

https://www.lua.org/manual/5.4/manual.html#lua_arith.

lua_concat Source #

Arguments

:: State 
-> CInt

n

-> IO () 

Warning: This is an unsafe function, it will cause a program crash ifa metamethod throws an error.Consider using hslua_concat instead.

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).

WARNING: lua_concat is unsafe in Haskell: This function will cause an unrecoverable crash an error if any of the concatenated values causes an error when executing a metamethod. Consider using the hslua_concat ersatz function instead.

lua_next Source #

Arguments

:: State 
-> StackIndex

index

-> IO LuaBool 

Warning: This is an unsafe function, it will cause a program crash ifthe given key is neither nil nor present in the table.Consider using hslua_next instead.

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 lua_next returns FALSE (and pushes nothing).

A typical traversal looks like this:

-- table is in the stack at index 't'
lua_pushnil l    -- first key
let loop = lua_next l t >>= \case
      FALSE -> return ()
      _ -> do
        lua_type l (-2) >>= lua_typename l >>= peekCString >>= putStrLn
        lua_type l (-1) >>= lua_typename l >>= peekCString >>= putStrLn
        -- removes 'value'; keeps 'key' for next iteration
        lua_pop l 1
        loop
loop

While traversing a table, do not call lua_tolstring directly on a key, unless you know that the key is actually a string. Recall that lua_tolstring may change the value at the given index; this confuses the next call to lua_next.

See function next for the caveats of modifying the table during its traversal.

WARNING: lua_next is unsafe in Haskell: This function will cause an unrecoverable crash an error if the given key is neither nil nor present in the table. Consider using the hslua_next ersatz function instead.

Load and run Lua code

lua_pcall Source #

Arguments

:: State 
-> NumArgs

nargs

-> NumResults

nresults

-> StackIndex

msgh

-> IO StatusCode 

Calls a function in protected mode.

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 lua_pcall; 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 LUA_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.

If there is any error, lua_pcall catches it, pushes a single value on the stack (the error message), and returns the error code. lua_pcall always removes the function and its arguments from the stack.

If msgh is 0, then the error object returned on the stack is exactly the original error object. Otherwise, msgh 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 lua_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 lua_pcall, since by then the stack has unwound.

https://www.lua.org/manual/5.4/manual.html#lua_pcall.

lua_load Source #

Arguments

:: State 
-> Reader

reader

-> Ptr ()

data

-> CString

chunkname

-> CString

mode

-> IO StatusCode 

Loads a Lua chunk (without running it). If there are no errors, lua_load pushes the compiled chunk as a Lua function on top of the stack. Otherwise, it pushes an error message.

The return values of lua_load are:

  • LUA_OK: no errors;
  • LUA_ERRSYNTAX: syntax error during pre-compilation;
  • LUA_ERRMEM: memory allocation error;
  • LUA_ERRGCMM: error while running a __gc metamethod. (This error has no relation with the chunk being loaded. It is generated by the garbage collector.)

This function only loads a chunk; it does not run it.

lua_load automatically detects whether the chunk is text or binary, and loads it accordingly (see program luac).

The lua_load function uses a user-supplied reader function to read the chunk (see Reader). The data argument is an opaque value passed to the reader function.

The chunkname argument gives a name to the chunk, which is used for error messages and in debug information (see §4.7).

lua_load automatically detects whether the chunk is text or binary and loads it accordingly (see program luac). The string mode works as in function load, with the addition that a NULL value is equivalent to the string "bt".

lua_load uses the stack internally, so the reader function must always leave the stack unmodified when returning.

https://www.lua.org/manual/5.4/manual.html#lua_load.

Coroutine functions

lua_status :: State -> IO StatusCode Source #

Returns the status of this Lua thread.

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

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

https://www.lua.org/manual/5.4/manual.html#lua_status.

Garbage-collection

lua_gc Source #

Arguments

:: State 
-> GCCode

what

-> CInt

data1

-> CInt

data2

-> CInt

data3

-> IO CInt 

Controls the garbage collector.

See the Lua docs at https://www.lua.org/manual/5.4/manual.html#lua_gc. Unused dataN values should be set to 0, but can be anything.

newtype GCCode Source #

Garbage-collection options.

Constructors

GCCode CInt 

Instances

Instances details
Eq GCCode Source # 
Instance details

Defined in Lua.Types

Methods

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

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

Show GCCode Source # 
Instance details

Defined in Lua.Types

Storable GCCode Source # 
Instance details

Defined in Lua.Types

pattern LUA_GCSTOP :: GCCode Source #

Stops the garbage collector.

pattern LUA_GCRESTART :: GCCode Source #

Restarts the garbage collector.

pattern LUA_GCCOLLECT :: GCCode Source #

Performs a full garbage-collection cycle.

pattern LUA_GCCOUNT :: GCCode Source #

Returns the current amount of memory (in Kbytes) in use by Lua.

pattern LUA_GCCOUNTB :: GCCode Source #

Returns the remainder of dividing the current amount of bytes of memory in use by Lua by 1024.

pattern LUA_GCSTEP :: GCCode Source #

Performs an incremental step of garbage collection.

pattern LUA_GCSETPAUSE :: GCCode Source #

Sets data as the new value for the pause of the collector (see §2.5) and returns the previous value of the pause.

pattern LUA_GCSETSTEPMUL :: GCCode Source #

Sets data as the new value for the step multiplier of the collector (see §2.5) and returns the previous value of the step multiplier.

pattern LUA_GCISRUNNING :: GCCode Source #

Returns a boolean that tells whether the collector is running (i.e., not stopped).

pattern LUA_GCGEN :: GCCode Source #

Changes the collector to generational mode.

pattern LUA_GCINC :: GCCode Source #

Changes the collector to incremental mode.

Warning-related functions

lua_warning Source #

Arguments

:: State 
-> CString

message

-> LuaBool

tocont

-> IO () 

Emits a warning with the given message. A message in a call with tocont true should be continued in another call to this function.

See warn for more details about warnings.

https://www.lua.org/manual/5.4/manual.html#lua_warning

lua_setwarnf Source #

Arguments

:: State 
-> WarnFunction

f

-> Ptr ()

ud

-> IO () 

Sets the warning function to be used by Lua to emit warnings (see WarnFunction). The ud parameter sets the value ud passed to the warning function.

type WarnFunction = FunPtr (Ptr () -> CString -> LuaBool -> IO ()) Source #

The type of warning functions, called by Lua to emit warnings. The first parameter is an opaque pointer set by lua_setwarnf. The second parameter is the warning message. The third parameter is a boolean that indicates whether the message is to be continued by the message in the next call.

See warn for more details about warnings.

Miscellaneous functions

The Auxiliary Library

luaL_getmetafield Source #

Arguments

:: State 
-> StackIndex

obj

-> CString

e

-> IO TypeCode 

Pushes onto the stack the field e from the metatable of the object at index obj and returns the type of the pushed value. If the object does not have a metatable, or if the metatable does not have this field, pushes nothing and returns LUA_TNIL.

luaL_getmetatable :: State -> CString -> IO TypeCode Source #

Pushes onto the stack the metatable associated with name tname in the registry (see luaL_newmetatable) (nil if there is no metatable associated with that name). Returns the type of the pushed value.

luaL_loadbuffer Source #

Arguments

:: State 
-> Ptr CChar

buff

-> CSize

sz

-> CString

name

-> IO StatusCode 

Loads a buffer as a Lua chunk. This function uses lua_load to load the chunk in the buffer pointed to by buff with size sz.

This function returns the same results as lua_load. name is the chunk name, used for debug information and error messages.

luaL_openlibs :: State -> IO () Source #

Opens all standard Lua libraries into the given state.

https://www.lua.org/manual/5.4/manual.html#luaL_openlibs

luaL_newmetatable Source #

Arguments

:: State 
-> CString

tname

-> IO LuaBool 

If the registry already has the key tname, returns 0. 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 1. (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.

luaL_ref Source #

Arguments

:: State 
-> StackIndex

t

-> IO CInt 

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, luaL_ref ensures the uniqueness of the key it returns. You can retrieve an object referred by reference r by calling lua_rawgeti l t r. Function luaL_unref frees a reference and its associated object.

If the object at the top of the stack is nil, luaL_ref returns the constant LUA_REFNIL. The constant LUA_NOREF is guaranteed to be different from any reference returned by luaL_ref.

luaL_testudata Source #

Arguments

:: State

l

-> StackIndex

arg

-> CString

tname

-> IO (Ptr ()) 

Checks whether the function argument arg is a userdata of the type tname (see luaL_newmetatable) and returns the userdata address (see lua_touserdata). Returns NULL if the test fails.

https://www.lua.org/manual/5.4/manual.html#luaL_testudata

luaL_traceback Source #

Arguments

:: State

l

-> State

l1

-> CString

msg

-> CInt

level

-> IO () 

Creates and pushes a traceback of the stack l1. If msg is not NULL it is appended at the beginning of the traceback. The level parameter tells at which level to start the traceback.

luaL_unref Source #

Arguments

:: State 
-> StackIndex

t

-> CInt

ref

-> IO () 

Releases reference ref from the table at index t (see luaL_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.

Registry fields

loadedTableRegistryField :: String Source #

Key, in the registry, for table of loaded modules.

preloadTableRegistryField :: String Source #

Key, in the registry, for table of preloaded loaders.

References

data Reference Source #

Reference to a stored value.

Constructors

Reference CInt

Reference to a stored value

RefNil

Reference to a nil value

Instances

Instances details
Eq Reference Source # 
Instance details

Defined in Lua.Auxiliary

Show Reference Source # 
Instance details

Defined in Lua.Auxiliary

pattern LUA_REFNIL :: CInt Source #

Value signaling that no reference was created.

pattern LUA_NOREF :: CInt Source #

Value signaling that no reference was found.

fromReference :: Reference -> CInt Source #

Convert a reference to its C representation.

toReference :: CInt -> Reference Source #

Create a reference from its C representation.

Ersatz functions

hsluaL_newstate :: IO State Source #

Creates a new Lua state and set extra registry values for error bookkeeping.

hsluaL_tolstring :: State -> StackIndex -> Ptr CSize -> IO (Ptr CChar) Source #

Converts object to string, respecting any metamethods; returns NULL if an error occurs.

hsluaL_requiref Source #

Arguments

:: State 
-> Ptr CChar

modname

-> CFunction

openf

-> LuaBool

glb

-> Ptr StatusCode 
-> IO () 

If modname is not already present in package.loaded. calls function openf with string modname as an argument and sets the call result in package.loaded[modname], as if that function has been called through require.

If glb is true, also stores the module into global modname.

Leaves a copy of the module on the stack.

Get functions (Lua → stack)

hslua_gettable :: State -> StackIndex -> Ptr StatusCode -> IO TypeCode Source #

Behaves like lua_gettable, but prevents unrecoverable program crashes by calling that function through lua_pcall. Takes an additional status code pointer that is set to the status returned by lua_pcall.

hslua_getglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO TypeCode Source #

Behaves like lua_getglobal, but prevents unrecoverable program crashes by calling that function through lua_pcall. Takes an additional status code pointer that is set to the status returned by lua_pcall.

Set functions (stack → Lua)

hslua_settable :: State -> StackIndex -> Ptr StatusCode -> IO () Source #

Behaves like lua_settable, but prevents unrecoverable program crashes by calling that function through lua_pcall. Takes an additional status code pointer that is set to the status returned by lua_pcall.

hslua_setglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO () Source #

Behaves like lua_setglobal, but prevents unrecoverable program crashes by calling that function through lua_pcall. Takes an additional status code pointer that is set to the status returned by lua_pcall.

Misc

hslua_error :: State -> IO NumResults Source #

Replacement for lua_error; it uses the HsLua error signaling convention instead of raw Lua errors.

hslua_next :: State -> StackIndex -> Ptr StatusCode -> IO LuaBool Source #

Wrapper around lua_next which catches any Lua errors.

hslua_concat :: State -> NumArgs -> Ptr StatusCode -> IO () Source #

Wrapper around lua_concat which catches any Lua errors.

hslua_arith Source #

Arguments

:: State 
-> ArithOPCode

op

-> Ptr StatusCode 
-> IO () 

Performs an arithmetic or bitwise operation over the two values (or one, in the case of negations) at the top of the stack, with the value at the top being the second operand, pops these values, and pushes the result of the operation. The function follows the semantics of the corresponding Lua operator (that is, it may call metamethods).

The value of op must be one of the following constants:

  • LUA_OPADD: performs addition (+)
  • LUA_OPSUB: performs subtraction (-)
  • LUA_OPMUL: performs multiplication (*)
  • LUA_OPDIV: performs float division (/)
  • LUA_OPIDIV: performs floor division (//)
  • LUA_OPMOD: performs modulo (%)
  • LUA_OPPOW: performs exponentiation (^)
  • LUA_OPUNM: performs mathematical negation (unary -)
  • LUA_OPBNOT: performs bitwise NOT (~)
  • LUA_OPBAND: performs bitwise AND (&)
  • LUA_OPBOR: performs bitwise OR (|)
  • LUA_OPBXOR: performs bitwise exclusive OR (~)
  • LUA_OPSHL: performs left shift (<<)
  • LUA_OPSHR: performs right shift (>>)

This function wraps lua_arith and takes an additional parameter status; if it is not NULL, then the return value is set to the status after calling lua_arith.

hslua_compare Source #

Arguments

:: State 
-> StackIndex

index 1

-> StackIndex

index 2

-> OPCode

operator

-> Ptr StatusCode

status

-> IO LuaBool 

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

The value of op must be one of the following constants:

This function wraps lua_compare and takes an additional parameter status; if it is not NULL, then the return value is set to the status after calling lua_compare.

Standard Lua libraries

luaopen_base :: CFunction Source #

Pointer to function opening the base library.

luaopen_table :: CFunction Source #

Pointer to function opening the table library.

luaopen_io :: CFunction Source #

Pointer to function opening the io library.

luaopen_os :: CFunction Source #

Pointer to function opening the os library.

luaopen_string :: CFunction Source #

Pointer to function opening the string library.

luaopen_math :: CFunction Source #

Pointer to function opening the math library.

luaopen_debug :: CFunction Source #

Pointer to function opening the debug library.

luaopen_package :: CFunction Source #

Pointer to function opening the package library.

Push Haskell functions

hslua_pushhsfunction :: State -> PreCFunction -> IO () Source #

Pushes a Haskell operation as a Lua function. The Haskell operation is expected to follow the custom error protocol, i.e., it must signal errors with hslua_error.

Example

Export the function to calculate triangular numbers.

let triangular :: PreCFunction
    triangular l' = do
      n <- lua_tointegerx l' (nthBottom 1) nullPtr
      lua_pushinteger l' (sum [1..n])
      return (NumResults 1)

hslua_newhsfunction l triangular
withCString "triangular" (lua_setglobal l)