Copyright | © 2007–2012 Gracjan Polak 2012–2016 Ömer Sinan Ağacan 2017-2019 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | beta |
Portability | non-portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell2010 |
- Lua Computations
- Lua API types
- Lua API
- Constants and pseudo-indices
- State manipulation
- Basic stack manipulation
- types and type checks
- access functions (stack → Haskell)
- Comparison and arithmetic functions
- push functions (Haskell → stack)
- get functions (Lua → stack)
- set functions (stack → Lua)
- load and call functions (load and run Lua code)
- Coroutine functions
- garbage-collection function and options
- miscellaneous and helper functions
- loading libraries
- Auxiliary library
- Error handling
Core Lua API. This module provides thin wrappers around the respective functions
of the Lua C API. C function which can throw an error are wrapped such that the
error is converted into an
. However, memory allocation errors are
not caught and will cause the host program to terminate.Exception
Synopsis
- newtype Lua a = Lua {}
- runWith :: State -> Lua a -> IO a
- liftIO :: MonadIO m => IO a -> m a
- state :: Lua State
- type CFunction = FunPtr (State -> IO NumResults)
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype StackIndex = StackIndex {}
- nthFromBottom :: CInt -> StackIndex
- nthFromTop :: CInt -> StackIndex
- stackTop :: StackIndex
- stackBottom :: StackIndex
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {}
- multret :: NumResults
- registryindex :: StackIndex
- upvalueindex :: StackIndex -> StackIndex
- newtype State = State (Ptr ())
- newstate :: IO State
- close :: State -> IO ()
- absindex :: StackIndex -> Lua StackIndex
- gettop :: Lua StackIndex
- settop :: StackIndex -> Lua ()
- pushvalue :: StackIndex -> Lua ()
- copy :: StackIndex -> StackIndex -> Lua ()
- insert :: StackIndex -> Lua ()
- pop :: StackIndex -> Lua ()
- remove :: StackIndex -> Lua ()
- replace :: StackIndex -> Lua ()
- checkstack :: Int -> Lua Bool
- data Type
- newtype TypeCode = TypeCode {
- fromTypeCode :: CInt
- fromType :: Type -> TypeCode
- toType :: TypeCode -> Type
- ltype :: StackIndex -> Lua Type
- typename :: Type -> Lua String
- isboolean :: StackIndex -> Lua Bool
- iscfunction :: StackIndex -> Lua Bool
- isfunction :: StackIndex -> Lua Bool
- isinteger :: StackIndex -> Lua Bool
- islightuserdata :: StackIndex -> Lua Bool
- isnil :: StackIndex -> Lua Bool
- isnone :: StackIndex -> Lua Bool
- isnoneornil :: StackIndex -> Lua Bool
- isnumber :: StackIndex -> Lua Bool
- isstring :: StackIndex -> Lua Bool
- istable :: StackIndex -> Lua Bool
- isthread :: StackIndex -> Lua Bool
- isuserdata :: StackIndex -> Lua Bool
- toboolean :: StackIndex -> Lua Bool
- tocfunction :: StackIndex -> Lua (Maybe CFunction)
- tointeger :: StackIndex -> Lua (Maybe Integer)
- tonumber :: StackIndex -> Lua (Maybe Number)
- topointer :: StackIndex -> Lua (Ptr ())
- tostring :: StackIndex -> Lua (Maybe ByteString)
- tothread :: StackIndex -> Lua (Maybe State)
- touserdata :: StackIndex -> Lua (Maybe (Ptr a))
- rawlen :: StackIndex -> Lua Int
- data RelationalOperator
- fromRelationalOperator :: RelationalOperator -> CInt
- compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
- equal :: StackIndex -> StackIndex -> Lua Bool
- lessthan :: StackIndex -> StackIndex -> Lua Bool
- rawequal :: StackIndex -> StackIndex -> Lua Bool
- pushboolean :: Bool -> Lua ()
- pushcfunction :: CFunction -> Lua ()
- pushcclosure :: CFunction -> NumArgs -> Lua ()
- pushinteger :: Integer -> Lua ()
- pushlightuserdata :: Ptr a -> Lua ()
- pushnil :: Lua ()
- pushnumber :: Number -> Lua ()
- pushstring :: ByteString -> Lua ()
- pushthread :: Lua Bool
- getglobal :: String -> Lua ()
- gettable :: StackIndex -> Lua ()
- getfield :: StackIndex -> String -> Lua ()
- rawget :: StackIndex -> Lua ()
- rawgeti :: StackIndex -> Integer -> Lua ()
- createtable :: Int -> Int -> Lua ()
- newtable :: Lua ()
- newuserdata :: Int -> Lua (Ptr ())
- getmetatable :: StackIndex -> Lua Bool
- setglobal :: String -> Lua ()
- settable :: StackIndex -> Lua ()
- setfield :: StackIndex -> String -> Lua ()
- rawset :: StackIndex -> Lua ()
- rawseti :: StackIndex -> Integer -> Lua ()
- setmetatable :: StackIndex -> Lua ()
- call :: NumArgs -> NumResults -> Lua ()
- pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
- load :: Reader -> Ptr () -> ByteString -> Lua Status
- loadbuffer :: ByteString -> String -> Lua Status
- loadfile :: FilePath -> Lua Status
- loadstring :: ByteString -> Lua Status
- data Status
- toStatus :: StatusCode -> Status
- status :: Lua Status
- data GCCONTROL
- gc :: GCCONTROL -> Int -> Lua Int
- next :: StackIndex -> Lua Bool
- error :: Lua NumResults
- concat :: NumArgs -> Lua ()
- pushglobaltable :: Lua ()
- register :: String -> CFunction -> Lua ()
- openbase :: Lua ()
- opendebug :: Lua ()
- openio :: Lua ()
- openlibs :: Lua ()
- openmath :: Lua ()
- openpackage :: Lua ()
- openos :: Lua ()
- openstring :: Lua ()
- opentable :: Lua ()
- dostring :: ByteString -> Lua Status
- dofile :: FilePath -> Lua Status
- getmetafield :: StackIndex -> String -> Lua Type
- getmetatable' :: String -> Lua Type
- getsubtable :: StackIndex -> String -> Lua Bool
- newmetatable :: String -> Lua Bool
- tostring' :: StackIndex -> Lua ByteString
- traceback :: State -> Maybe String -> Int -> Lua ()
- data Reference
- ref :: StackIndex -> Lua Reference
- getref :: StackIndex -> Reference -> Lua ()
- unref :: StackIndex -> Reference -> Lua ()
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
- noref :: Int
- refnil :: Int
- loadedTableRegistryField :: String
- preloadTableRegistryField :: String
- newtype Exception = Exception {}
- throwException :: String -> Lua a
- catchException :: Lua a -> (Exception -> Lua a) -> Lua a
- withExceptionMessage :: (String -> String) -> Lua a -> Lua a
- try :: Lua a -> Lua (Either Exception a)
- throwTopMessage :: Lua a
Lua Computations
A Lua computation. This is the base type used to run Lua programs of any
kind. The Lua state is handled automatically, but can be retrieved via
.state
Instances
Monad Lua Source # | |
Functor Lua Source # | |
Applicative Lua Source # | |
MonadIO Lua Source # | |
Defined in Foreign.Lua.Core.Types | |
Alternative Lua Source # | |
MonadThrow Lua Source # | |
Defined in Foreign.Lua.Core.Types | |
MonadCatch Lua Source # | |
MonadMask Lua Source # | |
ToHaskellFunction HaskellFunction Source # | |
Defined in Foreign.Lua.FunctionCalling toHsFun :: StackIndex -> HaskellFunction -> Lua NumResults Source # | |
MonadReader State Lua Source # | |
Peekable a => LuaCallFunc (Lua a) Source # | |
Pushable a => ToHaskellFunction (Lua a) Source # | |
Defined in Foreign.Lua.FunctionCalling toHsFun :: StackIndex -> Lua a -> Lua NumResults Source # |
runWith :: State -> Lua a -> IO a Source #
Run lua computation with custom lua state. Errors are left unhandled, the caller of this function is responsible to catch lua errors.
Lua API types
type CFunction = FunPtr (State -> IO NumResults) Source #
Type for C functions.
In order to communicate properly with Lua, a C function must use the
following protocol, which defines the way parameters and results are passed:
a C function receives its arguments from Lua in its stack in direct order
(the first argument is pushed first). So, when the function starts,
returns the number of arguments received by the function. The
first argument (if any) is at index 1 and its last argument is at index
gettop
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.
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 Foreign.Lua.Core.Types | |
Num Integer Source # | |
Ord Integer Source # | |
Real Integer Source # | |
Defined in Foreign.Lua.Core.Types toRational :: Integer -> Rational # | |
Show Integer Source # | |
Pushable Integer Source # | |
Peekable Integer Source # | |
Defined in Foreign.Lua.Types.Peekable |
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 # | |
Real Number Source # | |
Defined in Foreign.Lua.Core.Types toRational :: Number -> Rational # | |
RealFloat Number Source # | |
Defined in Foreign.Lua.Core.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 # | |
Pushable Number Source # | |
Peekable Number Source # | |
Defined in Foreign.Lua.Types.Peekable |
Stack index
newtype StackIndex Source #
A stack index
Instances
nthFromBottom :: CInt -> StackIndex Source #
Stack index of the nth element from the bottom of the stack.
nthFromTop :: CInt -> StackIndex Source #
Stack index of the nth element from the top of the stack.
stackTop :: StackIndex Source #
Top of the stack
stackBottom :: StackIndex Source #
Bottom of the stack
Number of arguments and return values
The number of arguments expected a function.
newtype NumResults Source #
The number of results returned by a function call.
Instances
Lua API
Constants and pseudo-indices
multret :: NumResults Source #
Alias for C constant LUA_MULTRET
. See
lua_call.
registryindex :: StackIndex Source #
Alias for C constant LUA_REGISTRYINDEX
. See
Lua registry.
upvalueindex :: StackIndex -> StackIndex Source #
Returns the pseudo-index that represents the i
-th upvalue of the running
function (see §4.4 of the
Lua 5.3 reference manual).
See also: lua_upvalueindex.
State manipulation
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.
Creates a new Lua state. It calls
with an allocator based
on the standard C lua_newstate
realloc
function and then sets a panic function (see
§4.6 of the Lua 5.3
Reference Manual) that prints an error message to the standard error output
in case of fatal errors.
See also: luaL_newstate.
close :: 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. On several platforms, you may not need to call this function, because all resources are naturally released when the host program ends. On the other hand, long-running programs that create multiple states, such as daemons or web servers, will probably need to close states as soon as they are not needed.
This is a wrapper function of lua_close.
Basic stack manipulation
absindex :: StackIndex -> Lua StackIndex Source #
Converts the acceptable index idx
into an equivalent absolute index (that
is, one that does not depend on the stack top).
gettop :: Lua StackIndex Source #
Returns the index of the top element in the stack. Because indices start at 1, this result is equal to the number of elements in the stack (and so 0 means an empty stack).
See also: lua_gettop.
settop :: StackIndex -> Lua () Source #
Accepts any index, or 0, and sets the stack top to this index. If the new top is larger than the old one, then the new elements are filled with nil. If index is 0, then all stack elements are removed.
See also: lua_settop.
pushvalue :: StackIndex -> Lua () Source #
Pushes a copy of the element at the given index onto the stack.
See lua_pushvalue.
copy :: StackIndex -> StackIndex -> Lua () Source #
Copies the element at index fromidx
into the valid index toidx
,
replacing the value at that position. Values at other positions are not
affected.
See also lua_copy in the lua manual.
insert :: StackIndex -> Lua () Source #
Moves the top element into the given valid index, shifting up the elements above this index to open space. This function cannot be called with a pseudo-index, because a pseudo-index is not an actual stack position.
See also: lua_insert.
remove :: StackIndex -> Lua () Source #
Removes the element at the given valid index, shifting down the elements above this index to fill the gap. This function cannot be called with a pseudo-index, because a pseudo-index is not an actual stack position.
See lua_remove.
replace :: StackIndex -> Lua () Source #
Moves the top element into the given valid index without shifting any element (therefore replacing the value at that given index), and then pops the top element.
See lua_replace.
checkstack :: Int -> Lua Bool Source #
Ensures that the stack has space for at least n
extra slots (that is,
that you can safely push up to n
values into it). It returns false if it
cannot fulfill the request, either because it would cause the stack to be
larger than a fixed maximum size (typically at least several thousand
elements) or because it cannot allocate memory for the extra space. This
function never shrinks the stack; if the stack already has space for the
extra slots, it is left unchanged.
This is a wrapper function of lua_checkstack.
types and type checks
Enumeration used as type tag. See lua_type.
TypeNone | non-valid stack index |
TypeNil | type of lua's |
TypeBoolean | type of lua booleans |
TypeLightUserdata | type of light userdata |
TypeNumber | type of lua numbers. See |
TypeString | type of lua string values |
TypeTable | type of lua tables |
TypeFunction | type of functions, either normal or |
TypeUserdata | type of full user data |
TypeThread | type of lua threads |
Integer code used to encode the type of a lua value.
fromType :: Type -> TypeCode Source #
Convert a lua Type to a type code which can be passed to the C API.
typename :: Type -> Lua String Source #
Returns the name of the type encoded by the value tp
, which must be one
the values returned by
.ltype
See also: lua_typename.
isboolean :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a boolean, and False
otherwise.
See also: lua_isboolean.
iscfunction :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a C function, and False
otherwise.
See also: lua_iscfunction.
isfunction :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a function (either C or
Lua), and False
otherwise.
See also: lua_isfunction.
isinteger :: StackIndex -> Lua Bool 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.
islightuserdata :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a light userdata, and
False
otherwise.
See also: <https://www.lua.org/manual/5.3/manual.html#lua_islightuserdata lua_islightuserdata>.
isnil :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is nil
, and False
otherwise.
See also: lua_isnil.
isnone :: StackIndex -> Lua Bool Source #
Returns True
if the given index is not valid, and False
otherwise.
See also: lua_isnone.
isnoneornil :: StackIndex -> Lua Bool Source #
Returns True
if the given index is not valid or if the value at the given
index is nil
, and False
otherwise.
See also: lua_isnoneornil.
isnumber :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a number or a string
convertible to a number, and False
otherwise.
See also: lua_isnumber.
isstring :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a string or a number
(which is always convertible to a string), and False
otherwise.
See also: lua_isstring.
istable :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a table, and False
otherwise.
See also: lua_istable.
isthread :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a thread, and False
otherwise.
See also: lua_isthread.
isuserdata :: StackIndex -> Lua Bool Source #
Returns True
if the value at the given index is a userdata (either full
or light), and False
otherwise.
See also: lua_isuserdata.
access functions (stack → Haskell)
toboolean :: StackIndex -> Lua Bool Source #
Converts the Lua value at the given index to a haskell boolean value. Like
all tests in Lua, toboolean
returns True
for any Lua value different from
false
and nil
; otherwise it returns False
. (If you want to accept only
actual boolean values, use
to test the value's type.)isboolean
See also: lua_toboolean.
tocfunction :: StackIndex -> Lua (Maybe CFunction) Source #
Converts a value at the given index to a C function. That value must be a C
function; otherwise, returns Nothing
.
See also: lua_tocfunction.
tointeger :: StackIndex -> Lua (Maybe Integer) Source #
Converts the Lua value at the given acceptable index to the signed integral
type
. 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_Integer
tointeger
returns Nothing
.
If the number is not an integer, it is truncated in some non-specified way.
See also: lua_tointeger.
tonumber :: StackIndex -> Lua (Maybe Number) Source #
Converts the Lua value at the given index to the C type lua_Number. The Lua
value must be a number or a string convertible to a number; otherwise,
tonumber
returns
.Nothing
See lua_tonumber.
topointer :: StackIndex -> Lua (Ptr ()) Source #
Converts the value at the given index to a generic C pointer (void*). The
value can be a userdata, a table, a thread, or a function; otherwise,
lua_topointer returns 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.
See also: lua_topointer.
tostring :: StackIndex -> Lua (Maybe ByteString) Source #
Converts the Lua value at the given index to a
. The Lua
value must be a string or a number; otherwise, the function returns
ByteString
. If the value is a number, then Nothing
also changes the
actual value in the stack to a string. (This change confuses tostring
when
next
is applied to keys during a table traversal.)tostring
See lua_tolstring.
tothread :: StackIndex -> Lua (Maybe State) Source #
Converts the value at the given index to a Lua thread (represented as
lua_State*). This value must be a thread; otherwise, the function returns
Nothing
.
See also: lua_tothread.
touserdata :: StackIndex -> Lua (Maybe (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 Nothing
..
See also: lua_touserdata.
rawlen :: StackIndex -> Lua Int Source #
Returns the raw "length" of the value at the given index: for strings, this
is the string length; for tables, this is the result of the length operator
(#
) with no metamethods; for userdata, this is the size of the block of
memory allocated for the userdata; for other values, it is 0.
See also: lua_rawlen.
Comparison and arithmetic functions
data RelationalOperator Source #
Lua comparison operations.
EQ | Correponds to lua's equality (==) operator. |
LT | Correponds to lua's strictly-lesser-than (<) operator |
LE | Correponds to lua's lesser-or-equal (<=) operator |
Instances
Eq RelationalOperator Source # | |
Defined in Foreign.Lua.Core.Types (==) :: RelationalOperator -> RelationalOperator -> Bool # (/=) :: RelationalOperator -> RelationalOperator -> Bool # | |
Ord RelationalOperator Source # | |
Defined in Foreign.Lua.Core.Types compare :: RelationalOperator -> RelationalOperator -> Ordering # (<) :: RelationalOperator -> RelationalOperator -> Bool # (<=) :: RelationalOperator -> RelationalOperator -> Bool # (>) :: RelationalOperator -> RelationalOperator -> Bool # (>=) :: RelationalOperator -> RelationalOperator -> Bool # max :: RelationalOperator -> RelationalOperator -> RelationalOperator # min :: RelationalOperator -> RelationalOperator -> RelationalOperator # | |
Show RelationalOperator Source # | |
Defined in Foreign.Lua.Core.Types showsPrec :: Int -> RelationalOperator -> ShowS # show :: RelationalOperator -> String # showList :: [RelationalOperator] -> ShowS # |
fromRelationalOperator :: RelationalOperator -> CInt Source #
Convert relation operator to its C representation.
compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool Source #
Compares two Lua values. Returns True
if the value at index idx1
satisfies op
when compared with the value at index idx2
, following the
semantics of the corresponding Lua operator (that is, it may call
metamethods). Otherwise returns False
. Also returns False
if any of the
indices is not valid.
The value of op must be of type
:LuaComparerOp
OpEQ: compares for equality (==) OpLT: compares for less than (<) OpLE: compares for less or equal (<=)
This is a wrapper function of lua_compare.
equal :: StackIndex -> StackIndex -> Lua Bool Source #
Returns True
if the two values in acceptable indices index1 and index2
are equal, following the semantics of the Lua ==
operator (that is, may
call metamethods). Otherwise returns False. Also returns False if any of the
indices is non valid. Uses
internally.compare
lessthan :: StackIndex -> StackIndex -> Lua Bool Source #
Tests whether the object under the first index is smaller than that under
the second. Uses
internally.compare
rawequal :: StackIndex -> StackIndex -> Lua Bool Source #
Returns True
if the two values in indices idx1
and idx2
are
primitively equal (that is, without calling the __eq
metamethod). Otherwise
returns False
. Also returns False
if any of the indices are not valid.
See also: lua_rawequal.
push functions (Haskell → stack)
pushboolean :: Bool -> Lua () Source #
Pushes a boolean value with the given value onto the stack.
See also: lua_pushboolean.
pushcfunction :: CFunction -> Lua () Source #
Pushes a C function onto the stack. This function receives a pointer to a C function and pushes onto the stack a Lua value of type function that, when called, invokes the corresponding C function.
Any function to be callable by Lua must follow the correct protocol to
receive its parameters and return its results (see
)CFunction
See also: lua_pushcfunction.
pushcclosure :: CFunction -> NumArgs -> Lua () Source #
Pushes a new C closure onto the stack.
When a C function is created, it is possible to associate some values with
it, thus creating a C closure (see
§3.4); these values are then
accessible to the function whenever it is called. To associate values with a
C function, first these values should be pushed onto the stack (when there
are multiple values, the first value is pushed first). Then lua_pushcclosure
is called to create and push the C function onto the stack, with the argument
n
telling how many values should be associated with the function.
lua_pushcclosure also pops these values from the stack.
The maximum value for n
is 255.
See also: lua_pushcclosure.
pushinteger :: Integer -> Lua () Source #
Pushes an integer with with the given value onto the stack.
See also: lua_pushinteger.
pushlightuserdata :: Ptr a -> Lua () Source #
Pushes a light userdata onto the stack.
Userdata represent C values in Lua. A light userdata represents a pointer, a
Ptr ()
(i.e., void*
in C lingo). It is a value (like a number): you do
not create it, it has no individual metatable, and it is not collected (as it
was never created). A light userdata is equal to "any" light userdata with
the same C address.
See also: lua_pushlightuserdata.
Pushes a nil value onto the stack.
See lua_pushnil.
pushnumber :: Number -> Lua () Source #
Pushes a float with the given value onto the stack.
See lua_pushnumber.
pushstring :: ByteString -> Lua () Source #
Pushes the zero-terminated string pointed to by s onto the stack. Lua makes (or reuses) an internal copy of the given string, so the memory at s can be freed or reused immediately after the function returns.
See also: <https://www.lua.org/manual/5.3/manual.html#lua_pushstring lua_pushstring>.
pushthread :: Lua Bool Source #
Pushes the current thread onto the stack. Returns True
if this thread is
the main thread of its state, False
otherwise.
See also: lua_pushthread.
get functions (Lua → stack)
getglobal :: String -> Lua () Source #
Pushes onto the stack the value of the global name
.
Errors on the Lua side are caught and rethrown as
.Exception
Wrapper of lua_getglobal.
gettable :: StackIndex -> Lua () Source #
Pushes onto the stack the value t[k]
, where t
is the value at the given
index and k
is the value at the top of the stack.
This function pops the key from the stack, pushing the resulting value in its place. As in Lua, this function may trigger a metamethod for the "index" event (see §2.4 of lua's manual).
Errors on the Lua side are caught and rethrown as
.Exception
See also: lua_gettable.
getfield :: StackIndex -> String -> Lua () Source #
Pushes onto the stack the value t[k]
, where t
is the value at the given
stack index. As in Lua, this function may trigger a metamethod for the
"index" event (see §2.4 of
lua's manual).
Errors on the Lua side are caught and rethrown as
.Exception
See also: lua_getfield.
rawget :: StackIndex -> Lua () Source #
Similar to
, but does a raw access (i.e., without metamethods).gettable
See also: lua_rawget.
rawgeti :: StackIndex -> Integer -> Lua () Source #
Pushes onto the stack the value t[n]
, where t
is the table at the given
index. The access is raw, that is, it does not invoke the __index
metamethod.
See also: lua_rawgeti.
createtable :: Int -> Int -> Lua () Source #
Creates a new empty table and pushes it onto the stack. Parameter narr is a hint for how many elements the table will have as a sequence; parameter nrec is a hint for how many other elements the table will have. Lua may use these hints to preallocate memory for the new table. This preallocation is useful for performance when you know in advance how many elements the table will have. Otherwise you can use the function lua_newtable.
This is a wrapper for function lua_createtable.
Creates a new empty table and pushes it onto the stack. It is equivalent to
createtable 0 0
.
See also: lua_newtable.
newuserdata :: Int -> Lua (Ptr ()) Source #
This function allocates a new block of memory with the given size, pushes onto the stack a new full userdata with the block address, and returns this address. The host program can freely use this memory.
See also: lua_newuserdata.
getmetatable :: StackIndex -> Lua Bool Source #
If the value at the given index has a metatable, the function pushes that
metatable onto the stack and returns True
. Otherwise, the function returns
False
and pushes nothing on the stack.
See also: lua_getmetatable.
set functions (stack → Lua)
setglobal :: String -> Lua () Source #
Pops a value from the stack and sets it as the new value of global name
.
Errors on the Lua side are caught and rethrown as a
.Exception
See also: lua_setglobal.
settable :: StackIndex -> Lua () Source #
Does the equivalent to t[k] = v
, where t
is the value at the given
index, v
is the value at the top of the stack, and k
is the value just
below the top.
This function pops both the key and the value from the stack. As in Lua, this function may trigger a metamethod for the "newindex" event (see §2.4 of the Lua 5.3 Reference Manual).
Errors on the Lua side are caught and rethrown as a
.Exception
See also: lua_settable.
setfield :: StackIndex -> String -> Lua () Source #
Does the equivalent to t[k] = v
, where t
is the value at the given
index and v
is the value at the top of the stack.
This function pops the value from the stack. As in Lua, this function may trigger a metamethod for the "newindex" event (see §2.4 of the Lua 5.3 Reference Manual).
Errors on the Lua side are caught and rethrown as a
.Exception
See also: lua_setfield.
rawset :: StackIndex -> Lua () Source #
Similar to
, but does a raw assignment (i.e., without
metamethods).settable
See also: lua_rawset.
rawseti :: StackIndex -> Integer -> Lua () Source #
Does the equivalent of t[i] = v
, where t
is the table at the given
index and v
is the value at the top of the stack.
This function pops the value from the stack. The assignment is raw, that is,
it does not invoke the __newindex
metamethod.
See also: lua_rawseti.
setmetatable :: StackIndex -> Lua () Source #
Pops a table from the stack and sets it as the new metatable for the value at the given index.
See also: <https://www.lua.org/manual/5.3/manual.html#lua_setmetatable lua_setmetatable>.
load and call functions (load and run Lua code)
call :: NumArgs -> NumResults -> Lua () Source #
Calls a function.
To call a function you must use the following protocol: first, the function
to be called is pushed onto the stack; then, the arguments to the function
are pushed in direct order; that is, the first argument is pushed first.
Finally you call call
; nargs
is the number of arguments that you pushed
onto the stack. All arguments and the function value are popped from the
stack when the function is called. The function results are pushed onto the
stack when the function returns. The number of results is adjusted to
nresults
, unless nresults
is multret
. In this case, all results from
the function are pushed. Lua takes care that the returned values fit into the
stack space. The function results are pushed onto the stack in direct order
(the first result is pushed first), so that after the call the last result is
on the top of the stack.
Any error inside the called function cause a
to be thrown.Exception
The following example shows how the host program can do the equivalent to this Lua code:
a = f("how", t.x, 14)
Here it is in Haskell (assuming the OverloadedStrings language extension):
getglobal "f" -- function to be called pushstring "how" -- 1st argument getglobal "t" -- table to be indexed getfield (-1) "x" -- push result of t.x (2nd arg) remove (-2) -- remove 't' from the stack pushinteger 14 -- 3rd argument call 3 1 -- call 'f' with 3 arguments and 1 result setglobal "a" -- set global 'a'
Note that the code above is "balanced": at its end, the stack is back to its original configuration. This is considered good programming practice.
See lua_call.
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status Source #
Calls a function in protected mode.
Both nargs
and nresults
have the same meaning as in
. If there
are no errors during the call, call
pcall
behaves exactly like
.
However, if there is any error, call
pcall
catches it, pushes a single value on
the stack (the error message), and returns the error code. Like
,
call
pcall
always removes the function and its arguments from the stack.
If msgh
is Nothing
, then the error object returned on the stack is
exactly the original error object. Otherwise, when msgh
is Just idx
, the
stack index idx
is the location of a message handler. (This index cannot be
a pseudo-index.) In case of runtime errors, this function will be called with
the error object and its return value will be the object returned on the
stack by
.pcall
Typically, the message handler is used to add more debug information to the
error object, such as a stack traceback. Such information cannot be gathered
after the return of
, since by then the stack has unwound.pcall
See lua_pcall.
load :: Reader -> Ptr () -> ByteString -> Lua Status Source #
Loads a Lua chunk (without running it). If there are no errors,
pushes the compiled chunk as a Lua function on top of the stack. Otherwise,
it pushes an error message.load
The return values of
are:load
: no errors;OK
: syntax error during pre-compilation;ErrSyntax
: memory allocation error;ErrMem
: error while running aErrGcmm
__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.
load
automatically detects whether the chunk is text or binary, and loads
it accordingly (see program luac).
The
function uses a user-supplied reader function to read the chunk
(see load
). 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). Note that the
chunkname
is used as a C string, so it may not contain null-bytes.
:: ByteString | Program to load |
-> String | chunk name |
-> Lua Status |
Loads a ByteString as a Lua chunk.
This function returns the same results as
. load
name
is the chunk name,
used for debug information and error messages. Note that name
is used as a
C string, so it may not contain null-bytes.
See luaL_loadbuffer.
Loads a file as a Lua chunk. This function uses lua_load
(see
)
to load the chunk in the file named filename. The first line in the file is
ignored if it starts with a load
#
.
The string mode works as in function
.load
This function returns the same results as
, but it has an extra error
code load
for file-related errors (e.g., it cannot open or read the
file).ErrFile
As
, this function only loads the chunk; it does not run it.load
Note that the file is opened by Haskell, not Lua.
See luaL_loadfile.
loadstring :: ByteString -> Lua Status Source #
Loads a string as a Lua chunk. This function uses lua_load
to load the
chunk in the given ByteString. The given string may not contain any NUL
characters.
This function returns the same results as lua_load
(see
).load
Also as
, this function only loads the chunk; it does not run it.load
See luaL_loadstring.
Coroutine functions
Lua status values.
toStatus :: StatusCode -> Status Source #
Convert C integer constant to
.LuaStatus
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 OK
with an error, or lua_resume
if
the thread is suspended.Yield
You can only call functions in threads with status
. You can resume
threads with status OK
(to start a new coroutine) or OK
(to
resume a coroutine).Yield
See also: lua_status.
garbage-collection function and options
Enumeration used by gc
function.
Instances
Enum GCCONTROL Source # | |
Defined in Foreign.Lua.Core.Types succ :: GCCONTROL -> GCCONTROL # pred :: GCCONTROL -> GCCONTROL # fromEnum :: GCCONTROL -> Int # enumFrom :: GCCONTROL -> [GCCONTROL] # enumFromThen :: GCCONTROL -> GCCONTROL -> [GCCONTROL] # enumFromTo :: GCCONTROL -> GCCONTROL -> [GCCONTROL] # enumFromThenTo :: GCCONTROL -> GCCONTROL -> GCCONTROL -> [GCCONTROL] # | |
Eq GCCONTROL Source # | |
Ord GCCONTROL Source # | |
Defined in Foreign.Lua.Core.Types | |
Show GCCONTROL Source # | |
gc :: GCCONTROL -> Int -> Lua Int Source #
Controls the garbage collector.
This function performs several tasks, according to the value of the parameter what:
: stops the garbage collector.GCSTOP
: restarts the garbage collector.GCRESTART
: performs a full garbage-collection cycle.GCCOLLECT
: returns the current amount of memory (in Kbytes) in use by Lua.GCCOUNT
: returns the remainder of dividing the current amount of bytes of memory in use by Lua by 1024.GCCOUNTB
: performs an incremental step of garbage collection. The step "size" is controlled by data (larger values mean more steps) in a non-specified way. If you want to control the step size you must experimentally tune the value of data. The function returns 1 if the step finished a garbage-collection cycle.GCSTEP
'GCSETPAUSE
': sets data as the new value for the pause of the collector (see §2.10). The function returns the previous value of the pause.
: sets data as the new value for the step multiplier of the collector (see §2.10). The function returns the previous value of the step multiplier.GCSETSTEPMUL
See lua_gc.
miscellaneous and helper functions
error :: Lua NumResults Source #
This is a convenience function to implement error propagation convention
described in Error handling in hslua. hslua doesn't implement
lua_error
function from Lua C API because it's never safe to use. (see
Error handling in hslua for details)
concat :: NumArgs -> Lua () Source #
Concatenates the n
values at the top of the stack, pops them, and leaves
the result at the top. If n
is 1, the result is the single value on the
stack (that is, the function does nothing); if n
is 0, the result is the
empty string. Concatenation is performed following the usual semantics of Lua
(see §3.4.6 of the lua
manual).
This is a wrapper function of lua_concat.
pushglobaltable :: Lua () Source #
register :: String -> CFunction -> Lua () Source #
Sets the C function f
as the new value of global name
.
See lua_register.
loading libraries
Pushes Lua's base library onto the stack.
See luaopen_base.
Pushes Lua's debug library onto the stack.
See also: luaopen_debug.
Pushes Lua's io library onto the stack.
See also: luaopen_io.
Opens all standard Lua libraries into the current state and sets each library name as a global value.
See also: luaL_openlibs.
Pushes Lua's math library onto the stack.
See also: luaopen_math.
openpackage :: Lua () Source #
Pushes Lua's package library onto the stack.
See also: luaopen_package.
Pushes Lua's os library onto the stack.
See also: luaopen_os.
openstring :: Lua () Source #
Pushes Lua's string library onto the stack.
See also: luaopen_string.
Pushes Lua's table library onto the stack.
See also: luaopen_table.
Auxiliary library
dostring :: ByteString -> Lua Status Source #
Loads and runs the given string.
Returns
on success, or an error if either loading of the string or
calling of the thunk failed.OK
dofile :: FilePath -> Lua Status Source #
Loads and runs the given file. Note that the filepath is interpreted by Haskell, not Lua. The resulting chunk is named using the UTF8 encoded filepath.
:: StackIndex | obj |
-> String | e |
-> Lua Type |
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 TypeNil.
Pushes onto the stack the metatable associated with name tname
in the
registry (see newmetatable
) (nil
if there is no metatable associated
with that name). Returns the type of the pushed value.
getsubtable :: StackIndex -> String -> Lua Bool Source #
Ensures that the value t[fname]
, where t
is the value at index idx
,
is a table, and pushes that table onto the stack. Returns True if it finds a
previous table there and False if it creates a new table.
newmetatable :: String -> Lua Bool Source #
If the registry already has the key tname, returns False
. Otherwise,
creates a new table to be used as a metatable for userdata, adds to this new
table the pair __name = tname
, adds to the registry the pair [tname] = new
table
, and returns True
. (The entry __name
is used by some
error-reporting functions.)
In both cases pushes onto the stack the final value associated with tname
in
the registry.
The value of tname
is used as a C string and hence must not contain null
bytes.
See also: luaL_newmetatable.
tostring' :: StackIndex -> Lua ByteString Source #
Converts any Lua value at the given index to a
in a
reasonable format. The resulting string is pushed onto the stack and also
returned by the function.ByteString
If the value has a metatable with a __tostring
field, then tolstring'
calls the corresponding metamethod with the value as argument, and uses the
result of the call as its result.
traceback :: State -> Maybe String -> Int -> Lua () Source #
Creates and pushes a traceback of the stack L1. If a message is given it appended at the beginning of the traceback. The level parameter tells at which level to start the traceback.
References
ref :: StackIndex -> Lua Reference Source #
Creates and returns a reference, in the table at index t
, for the object
at the top of the stack (and pops the object).
A reference is a unique integer key. As long as you do not manually add
integer keys into table t
, ref
ensures the uniqueness of the key it
returns. You can retrieve an object referred by reference r
by calling
rawgeti t r
. Function
frees a reference and its associated
object.unref
If the object at the top of the stack is nil,
returns the constant
ref
. The constant refnil
is guaranteed to be different from any
reference returned by noref
.ref
See also: luaL_ref.
getref :: StackIndex -> Reference -> Lua () Source #
Push referenced value from the table at the given index.
:: StackIndex | idx |
-> Reference | ref |
-> Lua () |
Releases reference
from the table at index ref
idx
(see
). 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.ref
See also: luaL_unref.
fromReference :: Reference -> CInt Source #
Convert a reference to its C representation.
toReference :: CInt -> Reference Source #
Create a reference from its C representation.
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.
Error handling
Exceptions raised by Lua-related operations.
Instances
Eq Exception Source # | |
Show Exception Source # | |
Exception Exception Source # | |
Defined in Foreign.Lua.Core.Error toException :: Exception -> SomeException # fromException :: SomeException -> Maybe Exception # displayException :: Exception -> String # |
withExceptionMessage :: (String -> String) -> Lua a -> Lua a Source #
Catch Lua
, alter the message and rethrow.Exception
try :: Lua a -> Lua (Either Exception a) Source #
Return either the result of a Lua computation or, if an exception was thrown, the error.
throwTopMessage :: Lua a Source #
Convert the object at the top of the stack into a string and throw it as
an
.Exception