| Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2022 Albert Krewinkel | 
|---|---|
| License | MIT | 
| Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> | 
| Stability | beta | 
| Portability | ForeignFunctionInterface, CPP | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Lua.Primary
Description
Haskell bindings to Lua C API functions.
The exposed functions correspond closely to the respective C Lua API
functions. However, C API functions which can throw Lua errors are not
exported directly, as any errors would crash the program. Non-error
throwing hslua_ versions are provided instead. The hslua ersatz
functions have worse performance than the original.
Some of the Lua functions may, directly or indirectly, call a Haskell
function, and trigger garbage collection, rescheduling etc. These
functions are always imported safely (i.e., with the safe keyword).
However, all function can trigger garbage collection. If that can lead
to problems, then the package should be configured without flag
allow-unsafe-gc.
Synopsis
- lua_absindex :: State -> StackIndex -> IO StackIndex
- lua_arith :: State -> ArithOPCode -> IO ()
- lua_checkstack :: State -> CInt -> IO LuaBool
- lua_close :: State -> IO ()
- lua_close_ptr :: FunPtr (Ptr () -> IO ())
- lua_concat :: State -> CInt -> IO ()
- lua_copy :: State -> StackIndex -> StackIndex -> IO ()
- lua_createtable :: State -> CInt -> CInt -> IO ()
- lua_gc :: State -> GCCode -> CInt -> CInt -> CInt -> IO CInt
- lua_getglobal :: State -> CString -> IO TypeCode
- lua_getmetatable :: State -> StackIndex -> IO LuaBool
- lua_gettable :: State -> StackIndex -> IO TypeCode
- lua_gettop :: State -> IO StackIndex
- lua_getiuservalue :: State -> StackIndex -> CInt -> IO TypeCode
- lua_insert :: State -> StackIndex -> IO ()
- lua_isboolean :: State -> StackIndex -> IO LuaBool
- lua_iscfunction :: State -> StackIndex -> IO LuaBool
- lua_isfunction :: State -> StackIndex -> IO LuaBool
- lua_isinteger :: State -> StackIndex -> IO LuaBool
- lua_islightuserdata :: State -> StackIndex -> IO LuaBool
- lua_isnil :: State -> StackIndex -> IO LuaBool
- lua_isnone :: State -> StackIndex -> IO LuaBool
- lua_isnoneornil :: State -> StackIndex -> IO LuaBool
- lua_isnumber :: State -> StackIndex -> IO LuaBool
- lua_isstring :: State -> StackIndex -> IO LuaBool
- lua_istable :: State -> StackIndex -> IO LuaBool
- lua_isthread :: State -> StackIndex -> IO LuaBool
- lua_isuserdata :: State -> StackIndex -> IO LuaBool
- lua_load :: State -> Reader -> Ptr () -> CString -> CString -> IO StatusCode
- lua_newthread :: State -> IO State
- lua_newuserdatauv :: State -> CSize -> CInt -> IO (Ptr ())
- lua_next :: State -> StackIndex -> IO LuaBool
- lua_pcall :: State -> NumArgs -> NumResults -> StackIndex -> IO StatusCode
- lua_pop :: State -> CInt -> IO ()
- lua_pushboolean :: State -> LuaBool -> IO ()
- lua_pushcclosure :: State -> CFunction -> NumArgs -> IO ()
- lua_pushcfunction :: State -> CFunction -> IO ()
- lua_pushglobaltable :: State -> IO ()
- lua_pushinteger :: State -> Integer -> IO ()
- lua_pushlightuserdata :: State -> Ptr a -> IO ()
- lua_pushlstring :: State -> Ptr CChar -> CSize -> IO ()
- lua_pushnil :: State -> IO ()
- lua_pushnumber :: State -> Number -> IO ()
- lua_pushstring :: State -> CString -> IO CString
- lua_pushthread :: State -> IO CInt
- lua_pushvalue :: State -> StackIndex -> IO ()
- lua_rawequal :: State -> StackIndex -> StackIndex -> IO LuaBool
- lua_rawget :: State -> StackIndex -> IO TypeCode
- lua_rawgeti :: State -> StackIndex -> Integer -> IO TypeCode
- lua_rawlen :: State -> StackIndex -> IO CSize
- lua_rawset :: State -> StackIndex -> IO ()
- lua_rawseti :: State -> StackIndex -> Integer -> IO ()
- lua_remove :: State -> StackIndex -> IO ()
- lua_replace :: State -> StackIndex -> IO ()
- lua_rotate :: State -> StackIndex -> CInt -> IO ()
- lua_setglobal :: State -> CString -> IO ()
- lua_setmetatable :: State -> StackIndex -> IO ()
- lua_settable :: State -> StackIndex -> IO ()
- lua_settop :: State -> StackIndex -> IO ()
- lua_setiuservalue :: State -> StackIndex -> CInt -> IO LuaBool
- lua_setwarnf :: State -> WarnFunction -> Ptr () -> IO ()
- lua_status :: State -> IO StatusCode
- lua_stringtonumber :: State -> CString -> IO CSize
- lua_toboolean :: State -> StackIndex -> IO LuaBool
- lua_tocfunction :: State -> StackIndex -> IO CFunction
- lua_tointegerx :: State -> StackIndex -> Ptr LuaBool -> IO Integer
- lua_tolstring :: State -> StackIndex -> Ptr CSize -> IO (Ptr CChar)
- lua_tonumberx :: State -> StackIndex -> Ptr LuaBool -> IO Number
- lua_topointer :: State -> StackIndex -> IO (Ptr ())
- lua_tothread :: State -> StackIndex -> IO State
- lua_touserdata :: State -> StackIndex -> IO (Ptr a)
- lua_type :: State -> StackIndex -> IO TypeCode
- lua_typename :: State -> TypeCode -> IO CString
- lua_version :: State -> IO (Ptr Number)
- lua_warning :: State -> CString -> LuaBool -> IO ()
- module Lua.Ersatz.Functions
- module Lua.Ersatz.Auxiliary
Documentation
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).
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_arithallow-unsafe-gc.
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.
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_close_ptr :: FunPtr (Ptr () -> IO ()) Source #
Function pointer to function lua_close; intended to be used with
 newForeignPtr.
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
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.
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.
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.
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_getglobalallow-unsafe-gc.
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.
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_gettableallow-unsafe-gc.
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).
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_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_isboolean :: State -> StackIndex -> IO LuaBool Source #
lua_iscfunction :: State -> StackIndex -> IO LuaBool Source #
lua_isfunction :: State -> StackIndex -> IO LuaBool Source #
lua_isinteger :: State -> StackIndex -> IO LuaBool Source #
lua_islightuserdata :: State -> StackIndex -> IO LuaBool Source #
Returns TRUEFALSE
https://www.lua.org/manual/5.4/manual.html#lua_islightuserdata
lua_isnone :: State -> StackIndex -> IO LuaBool Source #
lua_isnoneornil :: State -> StackIndex -> IO LuaBool Source #
lua_isnumber :: State -> StackIndex -> IO LuaBool Source #
lua_isstring :: State -> StackIndex -> IO LuaBool Source #
lua_istable :: State -> StackIndex -> IO LuaBool Source #
lua_isthread :: State -> StackIndex -> IO LuaBool Source #
lua_isuserdata :: State -> StackIndex -> IO LuaBool Source #
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
- LUA_ERRSYNTAX
- LUA_ERRMEM
- LUA_ERRGCMM- __gcmetamethod. (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 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.
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.
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.
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
loopWhile 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
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
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
Pops n elements from the stack.
lua_pushboolean :: State -> LuaBool -> IO () Source #
Pushes a boolean value with the given value onto the stack.
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.
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_pushglobaltable :: State -> IO () Source #
Pushes the global environment onto the stack.
https://www.lua.org/manual/5.4/manual.html#lua_pushglobaltable
lua_pushinteger :: State -> Integer -> IO () Source #
Pushes an integer with 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.4/manual.html#lua_pushlightuserdata.
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.
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.
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_pushthread :: State -> IO CInt Source #
Pushes the current thread onto the stack. Returns 1 iff this
 thread is the main thread of its state.
lua_pushvalue :: State -> StackIndex -> IO () Source #
Pushes a copy of the element at the given index onto the stack.
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.
lua_rawget :: State -> StackIndex -> IO TypeCode Source #
Similar to lua_gettable
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.
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.
lua_rawset :: State -> StackIndex -> IO () Source #
Similar to 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_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_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.
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.
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_setglobalallow-unsafe-gc.
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.
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_settableallow-unsafe-gc.
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.
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
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.
lua_status :: State -> IO StatusCode Source #
Returns the status of this Lua thread.
The status can be LUA_OKlua_resume
 with an error, or LUA_YIELD
You can only call functions in threads with status
 LUA_OKLUA_OKLUA_YIELD
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.
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
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.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.
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.
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.
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
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_type :: State -> StackIndex -> IO TypeCode Source #
Returns the type of the value in the given valid index, or
 LUA_TNONE
Returns the name of the type encoded by the value tp, which must
 be one the values returned by lua_type
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.
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.
module Lua.Ersatz.Functions
module Lua.Ersatz.Auxiliary