Copyright | © 2021-2022 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | beta |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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 safe
ly. 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
- withNewState :: (State -> IO a) -> IO a
- newtype State = State (Ptr ())
- type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar))
- type CFunction = FunPtr PreCFunction
- type PreCFunction = State -> IO NumResults
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype LuaBool = LuaBool CInt
- pattern TRUE :: LuaBool
- pattern FALSE :: LuaBool
- newtype StackIndex = StackIndex {}
- pattern LUA_REGISTRYINDEX :: StackIndex
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {}
- pattern LUA_MULTRET :: NumResults
- newtype TypeCode = TypeCode {
- fromTypeCode :: CInt
- pattern LUA_TNONE :: TypeCode
- pattern LUA_TNIL :: TypeCode
- pattern LUA_TBOOLEAN :: TypeCode
- pattern LUA_TLIGHTUSERDATA :: TypeCode
- pattern LUA_TNUMBER :: TypeCode
- pattern LUA_TSTRING :: TypeCode
- pattern LUA_TTABLE :: TypeCode
- pattern LUA_TFUNCTION :: TypeCode
- pattern LUA_TUSERDATA :: TypeCode
- pattern LUA_TTHREAD :: TypeCode
- newtype OPCode = OPCode CInt
- pattern LUA_OPEQ :: OPCode
- pattern LUA_OPLT :: OPCode
- pattern LUA_OPLE :: OPCode
- pattern LUA_OPADD :: ArithOPCode
- pattern LUA_OPSUB :: ArithOPCode
- pattern LUA_OPMUL :: ArithOPCode
- pattern LUA_OPDIV :: ArithOPCode
- pattern LUA_OPIDIV :: ArithOPCode
- pattern LUA_OPMOD :: ArithOPCode
- pattern LUA_OPPOW :: ArithOPCode
- pattern LUA_OPUNM :: ArithOPCode
- pattern LUA_OPBNOT :: ArithOPCode
- pattern LUA_OPBAND :: ArithOPCode
- pattern LUA_OPBOR :: ArithOPCode
- pattern LUA_OPBXOR :: ArithOPCode
- pattern LUA_OPSHL :: ArithOPCode
- pattern LUA_OPSHR :: ArithOPCode
- newtype StatusCode = StatusCode CInt
- pattern LUA_OK :: StatusCode
- pattern LUA_YIELD :: StatusCode
- pattern LUA_ERRRUN :: StatusCode
- pattern LUA_ERRSYNTAX :: StatusCode
- pattern LUA_ERRMEM :: StatusCode
- pattern LUA_ERRGCMM :: StatusCode
- pattern LUA_ERRERR :: StatusCode
- pattern LUA_ERRFILE :: StatusCode
- nthTop :: CInt -> StackIndex
- nthBottom :: CInt -> StackIndex
- nth :: CInt -> StackIndex
- top :: StackIndex
- lua_close :: State -> IO ()
- lua_newthread :: State -> IO State
- lua_version :: State -> IO (Ptr Number)
- lua_absindex :: State -> StackIndex -> IO StackIndex
- lua_gettop :: State -> IO StackIndex
- lua_settop :: State -> StackIndex -> IO ()
- lua_pushvalue :: State -> StackIndex -> IO ()
- lua_pop :: State -> CInt -> IO ()
- lua_copy :: State -> StackIndex -> StackIndex -> IO ()
- lua_remove :: State -> StackIndex -> IO ()
- lua_insert :: State -> StackIndex -> IO ()
- lua_replace :: State -> StackIndex -> IO ()
- lua_rotate :: State -> StackIndex -> CInt -> IO ()
- lua_checkstack :: State -> CInt -> IO LuaBool
- lua_isnil :: State -> StackIndex -> IO LuaBool
- lua_isboolean :: State -> StackIndex -> IO LuaBool
- lua_isnumber :: State -> StackIndex -> IO LuaBool
- lua_isinteger :: State -> StackIndex -> IO LuaBool
- lua_isstring :: State -> StackIndex -> IO LuaBool
- lua_isfunction :: State -> StackIndex -> IO LuaBool
- lua_istable :: State -> StackIndex -> IO LuaBool
- lua_iscfunction :: State -> StackIndex -> IO LuaBool
- lua_isuserdata :: State -> StackIndex -> IO LuaBool
- lua_islightuserdata :: State -> StackIndex -> IO LuaBool
- lua_isthread :: State -> StackIndex -> IO LuaBool
- lua_isnone :: State -> StackIndex -> IO LuaBool
- lua_isnoneornil :: State -> StackIndex -> IO LuaBool
- lua_type :: State -> StackIndex -> IO TypeCode
- lua_typename :: State -> TypeCode -> IO CString
- lua_rawequal :: State -> StackIndex -> StackIndex -> IO LuaBool
- lua_toboolean :: State -> StackIndex -> IO LuaBool
- lua_tocfunction :: State -> StackIndex -> IO CFunction
- lua_tointegerx :: State -> StackIndex -> Ptr LuaBool -> IO Integer
- lua_tonumberx :: State -> StackIndex -> Ptr LuaBool -> IO Number
- lua_tolstring :: State -> StackIndex -> Ptr CSize -> IO (Ptr CChar)
- lua_topointer :: State -> StackIndex -> IO (Ptr ())
- lua_tothread :: State -> StackIndex -> IO State
- lua_touserdata :: State -> StackIndex -> IO (Ptr a)
- lua_rawlen :: State -> StackIndex -> IO CSize
- lua_pushnil :: State -> IO ()
- lua_pushnumber :: State -> Number -> IO ()
- lua_pushinteger :: State -> Integer -> IO ()
- lua_pushlstring :: State -> Ptr CChar -> CSize -> IO ()
- lua_pushstring :: State -> CString -> IO CString
- lua_pushcclosure :: State -> CFunction -> NumArgs -> IO ()
- lua_pushcfunction :: State -> CFunction -> IO ()
- lua_pushboolean :: State -> LuaBool -> IO ()
- lua_pushlightuserdata :: State -> Ptr a -> IO ()
- lua_pushthread :: State -> IO CInt
- lua_rawget :: State -> StackIndex -> IO TypeCode
- lua_rawgeti :: State -> StackIndex -> Integer -> IO TypeCode
- lua_createtable :: State -> CInt -> CInt -> IO ()
- lua_newuserdata :: State -> CSize -> IO (Ptr ())
- lua_getmetatable :: State -> StackIndex -> IO LuaBool
- lua_getuservalue :: State -> StackIndex -> IO TypeCode
- lua_getglobal :: State -> CString -> IO TypeCode
- lua_gettable :: State -> StackIndex -> IO TypeCode
- lua_rawset :: State -> StackIndex -> IO ()
- lua_rawseti :: State -> StackIndex -> Integer -> IO ()
- lua_setmetatable :: State -> StackIndex -> IO ()
- lua_setuservalue :: State -> StackIndex -> IO ()
- lua_setglobal :: State -> CString -> IO ()
- lua_settable :: State -> StackIndex -> IO ()
- lua_stringtonumber :: State -> CString -> IO CSize
- lua_arith :: State -> ArithOPCode -> IO ()
- lua_concat :: State -> CInt -> IO ()
- lua_next :: State -> StackIndex -> IO LuaBool
- lua_pcall :: State -> NumArgs -> NumResults -> StackIndex -> IO StatusCode
- lua_load :: State -> Reader -> Ptr () -> CString -> CString -> IO StatusCode
- lua_status :: State -> IO StatusCode
- lua_gc :: State -> GCCode -> CInt -> IO CInt
- newtype GCCode = GCCode CInt
- pattern LUA_GCSTOP :: GCCode
- pattern LUA_GCRESTART :: GCCode
- pattern LUA_GCCOLLECT :: GCCode
- pattern LUA_GCCOUNT :: GCCode
- pattern LUA_GCCOUNTB :: GCCode
- pattern LUA_GCSTEP :: GCCode
- pattern LUA_GCSETPAUSE :: GCCode
- pattern LUA_GCSETSTEPMUL :: GCCode
- pattern LUA_GCISRUNNING :: GCCode
- lua_pushglobaltable :: State -> IO ()
- luaL_getmetafield :: State -> StackIndex -> CString -> IO TypeCode
- luaL_getmetatable :: State -> CString -> IO TypeCode
- luaL_loadbuffer :: State -> Ptr CChar -> CSize -> CString -> IO StatusCode
- luaL_openlibs :: State -> IO ()
- luaL_newmetatable :: State -> CString -> IO LuaBool
- luaL_ref :: State -> StackIndex -> IO CInt
- luaL_testudata :: State -> StackIndex -> CString -> IO (Ptr ())
- luaL_traceback :: State -> State -> CString -> CInt -> IO ()
- luaL_unref :: State -> StackIndex -> CInt -> IO ()
- loadedTableRegistryField :: String
- preloadTableRegistryField :: String
- data Reference
- pattern LUA_REFNIL :: CInt
- pattern LUA_NOREF :: CInt
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
- hsluaL_newstate :: IO State
- hsluaL_tolstring :: State -> StackIndex -> Ptr CSize -> IO (Ptr CChar)
- hsluaL_requiref :: State -> Ptr CChar -> CFunction -> LuaBool -> Ptr StatusCode -> IO ()
- hslua_gettable :: State -> StackIndex -> Ptr StatusCode -> IO TypeCode
- hslua_getglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO TypeCode
- hslua_settable :: State -> StackIndex -> Ptr StatusCode -> IO ()
- hslua_setglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO ()
- hslua_error :: State -> IO NumResults
- hslua_next :: State -> StackIndex -> Ptr StatusCode -> IO LuaBool
- hslua_concat :: State -> NumArgs -> Ptr StatusCode -> IO ()
- hslua_arith :: State -> ArithOPCode -> Ptr StatusCode -> IO ()
- hslua_compare :: State -> StackIndex -> StackIndex -> OPCode -> Ptr StatusCode -> IO LuaBool
- luaopen_base :: CFunction
- luaopen_table :: CFunction
- luaopen_io :: CFunction
- luaopen_os :: CFunction
- luaopen_string :: CFunction
- luaopen_math :: CFunction
- luaopen_debug :: CFunction
- luaopen_package :: CFunction
- hslua_pushhsfunction :: State -> PreCFunction -> IO ()
Run Lua operations
withNewState :: (State -> IO a) -> IO a Source #
Runs operations on a new Lua
. 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.State
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
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.
type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar)) Source #
The reader function used by
.
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 load
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,
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.lua_gettop
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
.
The type of integers in Lua.
By default this type is
, but that can be changed to
different values in Lua. (See Int64
LUA_INT_TYPE
in luaconf.h
.)
See lua_Integer.
Instances
Bounded Integer Source # | |
Enum Integer Source # | |
Eq Integer Source # | |
Integral Integer Source # | |
Defined in Lua.Types | |
Num Integer Source # | |
Ord Integer Source # | |
Read Integer Source # | |
Real Integer Source # | |
Defined in Lua.Types toRational :: Integer -> Rational # | |
Show Integer Source # | |
The type of floats in Lua.
By default this type is
, but that can be changed in Lua to
a single float or a long double. (See Double
LUA_FLOAT_TYPE
in
luaconf.h
.)
See lua_Number.
Instances
Eq Number Source # | |
Floating Number Source # | |
Fractional Number Source # | |
Num Number Source # | |
Ord Number Source # | |
Read Number Source # | |
Real Number Source # | |
Defined in Lua.Types toRational :: Number -> Rational # | |
RealFloat Number Source # | |
Defined in Lua.Types floatRadix :: Number -> Integer # floatDigits :: Number -> Int # floatRange :: Number -> (Int, Int) # decodeFloat :: Number -> (Integer, Int) # encodeFloat :: Integer -> Int -> Number # significand :: Number -> Number # scaleFloat :: Int -> Number -> Number # isInfinite :: Number -> Bool # isDenormalized :: Number -> Bool # isNegativeZero :: Number -> Bool # | |
RealFrac Number Source # | |
Show Number Source # | |
Booleans
Boolean value returned by a Lua C API function. This is a
and should be interpreted as CInt
iff the value is False
0
,
otherwise.True
Instances
Eq LuaBool Source # | |
Show LuaBool Source # | |
Storable LuaBool Source # | |
Stack indices
newtype StackIndex Source #
A stack index
Instances
pattern LUA_REGISTRYINDEX :: StackIndex Source #
Stack index of the Lua registry.
Function calling
The number of arguments consumed curing a function call.
newtype NumResults Source #
The number of results returned by a function call.
Instances
Eq NumResults Source # | |
Defined in Lua.Types (==) :: NumResults -> NumResults -> Bool # (/=) :: NumResults -> NumResults -> Bool # | |
Num NumResults Source # | |
Defined in Lua.Types (+) :: NumResults -> NumResults -> NumResults # (-) :: NumResults -> NumResults -> NumResults # (*) :: NumResults -> NumResults -> NumResults # negate :: NumResults -> NumResults # abs :: NumResults -> NumResults # signum :: NumResults -> NumResults # fromInteger :: Integer -> NumResults # | |
Ord NumResults Source # | |
Defined in Lua.Types compare :: NumResults -> NumResults -> Ordering # (<) :: NumResults -> NumResults -> Bool # (<=) :: NumResults -> NumResults -> Bool # (>) :: NumResults -> NumResults -> Bool # (>=) :: NumResults -> NumResults -> Bool # max :: NumResults -> NumResults -> NumResults # min :: NumResults -> NumResults -> NumResults # | |
Show NumResults Source # | |
Defined in Lua.Types showsPrec :: Int -> NumResults -> ShowS # show :: NumResults -> String # showList :: [NumResults] -> ShowS # |
pattern LUA_MULTRET :: NumResults Source #
Option for multiple returns in
.lua_pcall
Basic types
Integer code used to encode the type of a Lua 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
Relational operator code.
Instances
Eq OPCode Source # | |
Show OPCode Source # | |
Storable OPCode Source # | |
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.
Instances
Eq StatusCode Source # | |
Defined in Lua.Types (==) :: StatusCode -> StatusCode -> Bool # (/=) :: StatusCode -> StatusCode -> Bool # | |
Show StatusCode Source # | |
Defined in Lua.Types showsPrec :: Int -> StatusCode -> ShowS # show :: StatusCode -> String # showList :: [StatusCode] -> ShowS # | |
Storable StatusCode Source # | |
Defined in Lua.Types sizeOf :: StatusCode -> Int # alignment :: StatusCode -> Int # peekElemOff :: Ptr StatusCode -> Int -> IO StatusCode # pokeElemOff :: Ptr StatusCode -> Int -> StatusCode -> IO () # peekByteOff :: Ptr b -> Int -> IO StatusCode # pokeByteOff :: Ptr b -> Int -> StatusCode -> IO () # peek :: Ptr StatusCode -> IO StatusCode # poke :: Ptr StatusCode -> StatusCode -> IO () # |
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_ERRGCMM :: StatusCode Source #
Error while running a __gc
metamethod. For such errors, Lua does
not call the message handler (as this kind of error typically has no
relation with the function being called).
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
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.
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.
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.
Basic stack manipulation
:: 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).
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).
:: 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.
lua_pushvalue :: State -> StackIndex -> IO () Source #
Pushes a copy of the element at the given index onto the stack.
Pops n
elements from the stack.
:: 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.
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.
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.
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.
:: 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.
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.
Access functions (stack → Haskell)
lua_isboolean :: State -> StackIndex -> IO LuaBool Source #
lua_isnumber :: State -> StackIndex -> IO LuaBool Source #
lua_isinteger :: State -> StackIndex -> IO LuaBool Source #
lua_isstring :: State -> StackIndex -> IO LuaBool Source #
lua_isfunction :: State -> StackIndex -> IO LuaBool Source #
lua_istable :: State -> StackIndex -> IO LuaBool Source #
lua_iscfunction :: State -> StackIndex -> IO LuaBool Source #
lua_isuserdata :: State -> StackIndex -> IO LuaBool Source #
lua_islightuserdata :: State -> StackIndex -> IO LuaBool Source #
Returns
if the value at the given index is a
light userdata, and TRUE
otherwise.FALSE
https://www.lua.org/manual/5.3/manual.html#lua_islightuserdata
lua_isthread :: State -> StackIndex -> IO LuaBool Source #
lua_isnone :: State -> StackIndex -> IO LuaBool Source #
lua_isnoneornil :: State -> StackIndex -> IO LuaBool Source #
lua_type :: State -> StackIndex -> IO TypeCode Source #
Returns the type of the value in the given valid index, or
for a non-valid (but acceptable) index.LUA_TNONE
Returns the name of the type encoded by the value tp
, which must
be one the values returned by
.lua_type
:: 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.
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
to test the value's type.)lua_isboolean
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
.
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.3 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.
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.
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.
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
. Different
objects will give different pointers. There is no way to convert the
pointer back to its original value.nullPtr
Typically this function is used only for hashing and debug information.
lua_tothread :: State -> StackIndex -> IO State Source #
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
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.
Push functions (Haskell → stack)
lua_pushnil :: State -> IO () Source #
Pushes a nil value onto the stack.
lua_pushnumber :: State -> Number -> IO () Source #
Pushes a float with the given value onto the stack.
lua_pushinteger :: State -> Integer -> IO () Source #
Pushes an integer with with the given value onto the stack.
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.
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.
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.3/manual.html#lua_pushcclosure.
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.3/manual.html#lua_pushcfunction.
lua_pushboolean :: State -> LuaBool -> IO () Source #
Pushes a boolean value with the given value onto the stack.
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.3/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.
Get functions (Lua → stack)
lua_rawget :: State -> StackIndex -> IO TypeCode Source #
Similar to
, but does a raw access (i.e., without
metamethods).lua_gettable
:: 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.
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
.
lua_newuserdata :: State -> CSize -> IO (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.
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.3/manual.html#lua_getmetatable.
lua_getuservalue :: State -> StackIndex -> IO TypeCode Source #
Pushes onto the stack the Lua value associated with the full userdata at the given index.
Returns the type of the pushed value.
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
ersatz function instead. Likewise, the
metamethod may not call a Haskell function unless the library was
compiled without hslua_getglobal
allow-unsafe-gc
.
:: 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
ersatz function instead. Likewise, the
metamethod may not call a Haskell function unless the library was
compiled without hslua_gettable
allow-unsafe-gc
.
Set functions (stack → Lua)
lua_rawset :: State -> StackIndex -> IO () Source #
Similar to
, but does a raw assignment (i.e.,
without metamethods).lua_settable
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.
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.3/manual.html#lua_setmetatable.
lua_setuservalue :: State -> StackIndex -> IO () Source #
Pops a value from the stack and sets it as the new value associated to the full userdata at the given index.
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
ersatz function instead. Likewise,
the global metamethod may not call a Haskell function unless the
library was compiled without hslua_setglobal
allow-unsafe-gc
.
:: 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
ersatz function instead. Likewise, the
metamethod may not call a Haskell function unless the library was
compiled without hslua_settable
allow-unsafe-gc
.
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.3/manual.html#lua_stringtonumber.
Misc (unsafe)
:: 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
ersatz function instead. Likewise, the metamethod
may not call a Haskell function unless the library was compiled
without hslua_arith
allow-unsafe-gc
.
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
ersatz function instead.hslua_concat
:: 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
ersatz function instead.hslua_next
Load and run Lua code
:: 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
. 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.LUA_MULTRET
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
, since by then
the stack has unwound.lua_pcall
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:
: no errors;LUA_OK
: syntax error during pre-compilation;LUA_ERRSYNTAX
: memory allocation error;LUA_ERRMEM
: error while running aLUA_ERRGCMM
__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
). The data argument is an opaque
value passed to the reader function.Reader
The chunkname
argument gives a name to the chunk, which is used for
error messages and in debug information (see
§4.9).
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.
Coroutine functions
lua_status :: State -> IO StatusCode Source #
Returns the status of this Lua thread.
The status can be
for a normal thread, an
error value if the thread finished the execution of a LUA_OK
lua_resume
with an error, or
if the thread is
suspended.LUA_YIELD
You can only call functions in threads with status
. You can resume threads with status
LUA_OK
(to start a new coroutine) or
LUA_OK
(to resume a coroutine).LUA_YIELD
Garbage-collection
Controls the garbage collector.
See the Lua docs at https://www.lua.org/manual/5.3/manual.html#lua_gc.
Garbage-collection options.
Instances
Eq GCCode Source # | |
Show GCCode Source # | |
Storable GCCode Source # | |
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).
Miscellaneous functions
lua_pushglobaltable :: State -> IO () Source #
Pushes the global environment onto the stack.
https://www.lua.org/manual/5.3/manual.html#lua_pushglobaltable
The Auxiliary Library
:: 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
) (nil if there is no
metatable associated with that name). Returns the type of the pushed
value.luaL_newmetatable
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.
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.
:: 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
frees a
reference and its associated object.luaL_unref
If the object at the top of the stack is nil, luaL_ref
returns the
constant
. The constant
LUA_REFNIL
is guaranteed to be different
from any reference returned by LUA_NOREF
luaL_ref
.
:: State | l |
-> StackIndex | arg |
-> CString | tname |
-> IO (Ptr ()) |
Checks whether the function argument arg
is a userdata of the
type tname
(see
) and returns the userdata
address (see luaL_newmetatable
). Returns lua_touserdata
NULL
if the
test fails.
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.
:: State | |
-> StackIndex | t |
-> CInt | ref |
-> IO () |
Releases reference ref
from the table at index t
(see
). The entry is removed from the table, so that the
referred object can be collected. The reference luaL_ref
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
Reference to a stored value.
pattern LUA_REFNIL :: CInt Source #
Value signaling that no reference was created.
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.
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
, but prevents
unrecoverable program crashes by calling that function through
lua_gettable
. Takes an additional status code pointer
that is set to the status returned by lua_pcall
lua_pcall
.
hslua_getglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO TypeCode Source #
Behaves like
, but prevents
unrecoverable program crashes by calling that function through
lua_getglobal
. Takes an additional status code pointer
that is set to the status returned by lua_pcall
lua_pcall
.
Set functions (stack → Lua)
hslua_settable :: State -> StackIndex -> Ptr StatusCode -> IO () Source #
Behaves like
, but prevents
unrecoverable program crashes by calling that function through
lua_settable
. Takes an additional status code pointer
that is set to the status returned by lua_pcall
lua_pcall
.
hslua_setglobal :: State -> CString -> CSize -> Ptr StatusCode -> IO () Source #
Behaves like
, but prevents
unrecoverable program crashes by calling that function through
lua_setglobal
. Takes an additional status code pointer
that is set to the status returned by lua_pcall
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.
:: 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
.
:: 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:
LUA_OPEQ
: compares for equality (==)LUA_OPLT
: compares for less than (<)LUA_OPLE
: compares for less or equal (<=)
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)