hslua-core-2.2.1: Bindings to Lua, an embeddable scripting language
Copyright© 2007–2012 Gracjan Polak;
© 2012–2016 Ömer Sinan Ağacan;
© 2017-2022 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb+hslua@zeitkraut.de>
Stabilitybeta
Portabilitynon-portable (depends on GHC)
Safe HaskellNone
LanguageHaskell2010

HsLua.Core

Description

Core Lua API. This module provides thin wrappers around the respective functions of the Lua C API. C functions which can throw an error are wrapped such that the error is converted into an Exception. However, memory allocation errors are not caught and will cause the host program to terminate.

Synopsis

Run Lua computations

run :: LuaE e a -> IO a Source #

Run Lua computation using the default HsLua state as starting point. Exceptions are masked, thus avoiding some issues when using multiple threads. All exceptions are passed through; error handling is the responsibility of the caller.

runWith :: State -> LuaE e a -> IO a Source #

Run Lua computation with the given Lua state. Exception handling is left to the caller; resulting exceptions are left unhandled.

runEither :: Exception e => LuaE e a -> IO (Either e a) Source #

Run the given Lua computation; exceptions raised in Haskell code are caught, but other exceptions (user exceptions raised in Haskell, unchecked type errors, etc.) are passed through.

Lua Computations

newtype LuaE e a Source #

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.

Constructors

Lua 

Instances

Instances details
MonadReader LuaEnvironment (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

ask :: LuaE e LuaEnvironment #

local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a #

reader :: (LuaEnvironment -> a) -> LuaE e a #

Monad (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

(>>=) :: LuaE e a -> (a -> LuaE e b) -> LuaE e b #

(>>) :: LuaE e a -> LuaE e b -> LuaE e b #

return :: a -> LuaE e a #

Functor (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

fmap :: (a -> b) -> LuaE e a -> LuaE e b #

(<$) :: a -> LuaE e b -> LuaE e a #

LuaError e => MonadFail (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Error

Methods

fail :: String -> LuaE e a #

Applicative (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

pure :: a -> LuaE e a #

(<*>) :: LuaE e (a -> b) -> LuaE e a -> LuaE e b #

liftA2 :: (a -> b -> c) -> LuaE e a -> LuaE e b -> LuaE e c #

(*>) :: LuaE e a -> LuaE e b -> LuaE e b #

(<*) :: LuaE e a -> LuaE e b -> LuaE e a #

MonadIO (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

liftIO :: IO a -> LuaE e a #

LuaError e => Alternative (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Error

Methods

empty :: LuaE e a #

(<|>) :: LuaE e a -> LuaE e a -> LuaE e a #

some :: LuaE e a -> LuaE e [a] #

many :: LuaE e a -> LuaE e [a] #

MonadThrow (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

throwM :: Exception e0 => e0 -> LuaE e a #

MonadCatch (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

catch :: Exception e0 => LuaE e a -> (e0 -> LuaE e a) -> LuaE e a #

MonadMask (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

mask :: ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b #

uninterruptibleMask :: ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b #

generalBracket :: LuaE e a -> (a -> ExitCase b -> LuaE e c) -> (a -> LuaE e b) -> LuaE e (b, c) #

type Lua a = LuaE Exception a Source #

A Lua operation.

This type is suitable for most users. It uses a default exception for error handling. Users who need more control over error handling can use LuaE with a custom error type instead.

unsafeRunWith :: State -> LuaE e a -> IO a Source #

Run the given operation, but crash if any Haskell exceptions occur.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

state :: LuaE e State Source #

Get the Lua state of this Lua computation.

newtype LuaEnvironment Source #

Environment in which Lua computations are evaluated.

Constructors

LuaEnvironment 

Fields

Instances

Instances details
MonadReader LuaEnvironment (LuaE e) Source # 
Instance details

Defined in HsLua.Core.Types

Methods

ask :: LuaE e LuaEnvironment #

local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a #

reader :: (LuaEnvironment -> a) -> LuaE e a #

Lua API types

type CFunction = FunPtr PreCFunction #

Type for C functions.

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

See lua_CFunction.

type PreCFunction = State -> IO NumResults #

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

This is the same as a dereferenced CFunction.

newtype Integer #

The type of integers in Lua.

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

See lua_Integer.

Constructors

Integer Int64 

Instances

Instances details
Bounded Integer 
Instance details

Defined in Lua.Types

Enum Integer 
Instance details

Defined in Lua.Types

Eq Integer 
Instance details

Defined in Lua.Types

Methods

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

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

Integral Integer 
Instance details

Defined in Lua.Types

Num Integer 
Instance details

Defined in Lua.Types

Ord Integer 
Instance details

Defined in Lua.Types

Read Integer 
Instance details

Defined in Lua.Types

Real Integer 
Instance details

Defined in Lua.Types

Show Integer 
Instance details

Defined in Lua.Types

newtype Number #

The type of floats in Lua.

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

See lua_Number.

Constructors

Number Double 

Instances

Instances details
Eq Number 
Instance details

Defined in Lua.Types

Methods

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

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

Floating Number 
Instance details

Defined in Lua.Types

Fractional Number 
Instance details

Defined in Lua.Types

Num Number 
Instance details

Defined in Lua.Types

Ord Number 
Instance details

Defined in Lua.Types

Read Number 
Instance details

Defined in Lua.Types

Real Number 
Instance details

Defined in Lua.Types

RealFloat Number 
Instance details

Defined in Lua.Types

RealFrac Number 
Instance details

Defined in Lua.Types

Methods

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

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

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

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

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

Show Number 
Instance details

Defined in Lua.Types

Stack index

newtype StackIndex #

A stack index

Constructors

StackIndex 

Fields

nthTop :: CInt -> StackIndex #

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

Since: lua-2.0.0

nthBottom :: CInt -> StackIndex #

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

Since: lua-2.0.0

nth :: CInt -> StackIndex #

Alias for nthTop.

Since: lua-2.0.0

top :: StackIndex #

Index of the topmost stack element.

Since: lua-2.0.0

Number of arguments and return values

newtype NumArgs #

The number of arguments consumed curing a function call.

Constructors

NumArgs 

Fields

Instances

Instances details
Eq NumArgs 
Instance details

Defined in Lua.Types

Methods

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

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

Num NumArgs 
Instance details

Defined in Lua.Types

Ord NumArgs 
Instance details

Defined in Lua.Types

Show NumArgs 
Instance details

Defined in Lua.Types

newtype NumResults #

The number of results returned by a function call.

Constructors

NumResults 

Fields

Table fields

newtype Name Source #

Name of a function, table field, or chunk; the name must be valid UTF-8 and may not contain any nul characters.

Implementation note: this is a newtype instead of a simple type Name = ByteString alias so we can define a UTF-8 based IsString instance. Non-ASCII users would have a bad time otherwise.

Constructors

Name 

Fields

Instances

Instances details
Eq Name Source # 
Instance details

Defined in HsLua.Core.Types

Methods

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

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

Ord Name Source # 
Instance details

Defined in HsLua.Core.Types

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in HsLua.Core.Types

Methods

fromString :: String -> Name #

Semigroup Name Source # 
Instance details

Defined in HsLua.Core.Types

Methods

(<>) :: Name -> Name -> Name #

sconcat :: NonEmpty Name -> Name #

stimes :: Integral b => b -> Name -> Name #

Lua API

Constants and pseudo-indices

multret :: NumResults Source #

Option for multiple returns in pcall.

registryindex :: StackIndex Source #

Pseudo stack index of the Lua registry.

upvalueindex :: StackIndex -> StackIndex Source #

Returns the pseudo-index that represents the i-th upvalue of the running function (see <https://www.lua.org/manual/5.4/manual.html#4.2 §4.2> of the Lua 5.4 reference manual).

See also: lua_upvalueindex.

State manipulation

newtype State #

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

Synonym for lua_State *. See lua_State.

Constructors

State (Ptr ()) 

Instances

Instances details
Eq State 
Instance details

Defined in Lua.Types

Methods

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

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

Generic State 
Instance details

Defined in Lua.Types

Associated Types

type Rep State :: Type -> Type #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

type Rep State 
Instance details

Defined in Lua.Types

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

newstate :: IO State Source #

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

Wraps hsluaL_newstate. 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.

Same as lua_close.

Basic stack manipulation

absindex :: StackIndex -> LuaE e StackIndex Source #

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

Wraps lua_absindex.

gettop :: LuaE e 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).

Wraps lua_gettop.

settop :: StackIndex -> LuaE e () 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.

Wraps lua_settop.

pushvalue :: StackIndex -> LuaE e () Source #

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

Wraps lua_pushvalue.

copy :: StackIndex -> StackIndex -> LuaE e () 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.

Wraps lua_copy.

insert :: StackIndex -> LuaE e () 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.

Wraps lua_insert.

rotate Source #

Arguments

:: StackIndex
idx
-> Int
n
-> LuaE e () 

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

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

pop :: Int -> LuaE e () Source #

Pops n elements from the stack.

See also: lua_pop.

remove :: StackIndex -> LuaE e () 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.

Wraps lua_remove.

replace :: StackIndex -> LuaE e () 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.

Wraps lua_replace.

checkstack :: Int -> LuaE e 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.

Wraps lua_checkstack.

types and type checks

data Type Source #

Enumeration used as type tag. See lua_type.

Constructors

TypeNone

non-valid stack index

TypeNil

type of Lua's nil value

TypeBoolean

type of Lua booleans

TypeLightUserdata

type of light userdata

TypeNumber

type of Lua numbers. See Number

TypeString

type of Lua string values

TypeTable

type of Lua tables

TypeFunction

type of functions, either normal or CFunction

TypeUserdata

type of full user data

TypeThread

type of Lua threads

Instances

Instances details
Bounded Type Source # 
Instance details

Defined in HsLua.Core.Types

Enum Type Source # 
Instance details

Defined in HsLua.Core.Types

Methods

succ :: Type -> Type #

pred :: Type -> Type #

toEnum :: Int -> Type #

fromEnum :: Type -> Int #

enumFrom :: Type -> [Type] #

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

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

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

Eq Type Source # 
Instance details

Defined in HsLua.Core.Types

Methods

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

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

Ord Type Source # 
Instance details

Defined in HsLua.Core.Types

Methods

compare :: Type -> Type -> Ordering #

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

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

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

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 
Instance details

Defined in HsLua.Core.Types

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

ltype :: StackIndex -> LuaE e Type Source #

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

This function wraps lua_type.

typename :: Type -> LuaE e ByteString Source #

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

Wraps lua_typename.

isboolean :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isboolean.

iscfunction :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_iscfunction.

isfunction :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isfunction.

isinteger :: StackIndex -> LuaE e 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.

Wraps lua_isinteger.

islightuserdata :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_islightuserdata.

isnil :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isnil.

isnone :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isnone.

isnoneornil :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isnoneornil.

isnumber :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isnumber.

isstring :: StackIndex -> LuaE e 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.

Wraps lua_isstring.

istable :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_istable.

isthread :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isthread.

isuserdata :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_isuserdata.

access functions (stack → Haskell)

toboolean :: StackIndex -> LuaE e Bool Source #

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

Wraps lua_toboolean.

tocfunction :: StackIndex -> LuaE e (Maybe CFunction) Source #

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

Wraps lua_tocfunction.

tointeger :: StackIndex -> LuaE e (Maybe Integer) Source #

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, tointeger returns Nothing.

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

Wraps lua_tointegerx. See also: lua_tointeger.

tonumber :: StackIndex -> LuaE e (Maybe Number) Source #

Converts the Lua value at the given index to a Number. The Lua value must be a number or a string convertible to a number; otherwise, tonumber returns Nothing.

Wraps lua_tonumberx. See also lua_tonumber.

topointer :: StackIndex -> LuaE e (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.

Wraps lua_topointer.

tostring :: StackIndex -> LuaE e (Maybe ByteString) Source #

Converts the Lua value at the given index to a ByteString. The Lua value must be a string or a number; otherwise, the function returns Nothing. If the value is a number, then tostring also changes the actual value in the stack to a string. (This change confuses next when tostring is applied to keys during a table traversal.)

Wraps lua_tolstring.

tothread :: StackIndex -> LuaE e (Maybe State) Source #

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

Wraps lua_tothread.

touserdata :: StackIndex -> LuaE e (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..

Wraps lua_touserdata.

rawlen :: StackIndex -> LuaE e 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.

Wraps lua_rawlen.

Comparison and arithmetic functions

data RelationalOperator Source #

Lua comparison operations.

Constructors

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

compare Source #

Arguments

:: LuaError e 
=> StackIndex

idx1

-> StackIndex

idx2

-> RelationalOperator 
-> LuaE e Bool 

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 RelationalOperator:

EQ: compares for equality (==) LT: compares for less than (<) LE: compares for less or equal (<=)

Wraps hslua_compare. See also lua_compare.

equal Source #

Arguments

:: LuaError e 
=> StackIndex

index1

-> StackIndex

index2

-> LuaE e Bool 

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

lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool Source #

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

rawequal :: StackIndex -> StackIndex -> LuaE e 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.

Wraps lua_rawequal.

push functions (Haskell → stack)

pushboolean :: Bool -> LuaE e () Source #

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

This functions wraps lua_pushboolean.

pushcfunction :: CFunction -> LuaE e () 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)

Same as flip pushcclosure 0. lua_pushcfunction.

pushcclosure Source #

Arguments

:: CFunction 
-> NumArgs

n

-> LuaE e () 

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 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. pushcclosure also pops these values from the stack.

The maximum value for n is 255.

Wraps lua_pushcclosure.

pushinteger :: Integer -> LuaE e () Source #

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

Wraps lua_pushinteger.

pushlightuserdata :: Ptr a -> LuaE e () Source #

Pushes a light userdata onto the stack.

Userdata represent C values in Lua. A light userdata represents a pointer, a Ptr a (i.e., void* in C). 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.

Wraps lua_pushlightuserdata.

pushnil :: LuaE e () Source #

Pushes a nil value onto the stack.

Wraps lua_pushnil.

pushnumber :: Number -> LuaE e () Source #

Pushes a float with the given value onto the stack.

Wraps lua_pushnumber.

pushstring :: ByteString -> LuaE e () Source #

Pushes the 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.

Wraps lua_pushlstring.

pushthread :: LuaE e Bool Source #

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

Wraps lua_pushthread.

get functions (Lua → stack)

getglobal :: LuaError e => Name -> LuaE e Type Source #

Pushes onto the stack the value of the global name.

Errors on the Lua side are propagated.

Wraps hslua_getglobal.

gettable :: LuaError e => StackIndex -> LuaE e Type 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.

Wraps hslua_gettable. See also: lua_gettable.

getfield :: LuaError e => StackIndex -> Name -> LuaE e Type 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 propagated.

See also lua_getfield.

rawget :: LuaError e => StackIndex -> LuaE e Type Source #

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

Wraps lua_rawget.

rawgeti :: LuaError e => StackIndex -> Integer -> LuaE e Type 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.

Wraps lua_rawgeti.

createtable :: Int -> Int -> LuaE e () 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.

Wraps lua_createtable.

newtable :: LuaE e () Source #

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

See also: lua_newtable.

newuserdatauv Source #

Arguments

:: Int

size

-> Int

nuvalue

-> LuaE e (Ptr ()) 

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

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

This function wraps lua_newuserdatauv.

getmetatable :: StackIndex -> LuaE e 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.

Wraps lua_getmetatable.

getiuservalue Source #

Arguments

:: StackIndex

index

-> Int

n

-> LuaE e Type 

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.

Wraps lua_getiuservalue.

set functions (stack → Lua)

setglobal Source #

Arguments

:: LuaError e 
=> Name

name

-> LuaE e () 

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

Wraps hslua_setglobal. See also: lua_setglobal.

settable :: LuaError e => StackIndex -> LuaE e () 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.4 Reference Manual).

Errors on the Lua side are caught and rethrown.

Wraps hslua_settable.

setfield :: LuaError e => StackIndex -> Name -> LuaE e () 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.4 Reference Manual).

Errors on the Lua side are caught and rethrown as a Exception.

See also: lua_setfield.

rawset :: LuaError e => StackIndex -> LuaE e () Source #

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

Wraps lua_rawset.

rawseti :: LuaError e => StackIndex -> Integer -> LuaE e () 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.

Wraps lua_rawseti.

setmetatable :: StackIndex -> LuaE e () Source #

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

Wraps lua_setmetatable.

setiuservalue Source #

Arguments

:: StackIndex

index

-> Int

n

-> LuaE e Bool 

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.

Wraps lua_setiuservalue.

load and call functions (load and run Lua code)

call :: LuaError e => NumArgs -> NumResults -> LuaE e () 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 is propagated as exception of type e.

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 -> LuaE e Status Source #

Calls a function in protected mode.

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

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

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

This function wraps lua_pcall.

load :: Reader -> Ptr () -> Name -> LuaE e Status Source #

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

The return values of load are:

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

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

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

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

The chunkname argument gives a name to the chunk, which is used for error messages and in debug information (see §4.7). Note that the chunkname is used as a C string, so it may not contain null-bytes.

This is a wrapper of lua_load.

loadbuffer Source #

Arguments

:: ByteString

Program to load

-> Name

chunk name

-> LuaE e 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.

Wraps luaL_loadbuffer.

loadfile Source #

Arguments

:: FilePath

filename

-> LuaE e Status 

Loads a file as a Lua chunk. This function uses lua_load (see load) to load the chunk in the file named filename. The first line in the file is ignored if it starts with a #.

The string mode works as in function load.

This function returns the same results as load, but it has an extra error code ErrFile for file-related errors (e.g., it cannot open or read the file).

As load, this function only loads the chunk; it does not run it.

See luaL_loadfile.

loadstring :: ByteString -> LuaE e 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 load, this function only loads the chunk; it does not run it.

See luaL_loadstring.

Coroutine functions

data Status Source #

Lua status values.

Constructors

OK

success

Yield

yielding / suspended coroutine

ErrRun

a runtime rror

ErrSyntax

syntax error during precompilation

ErrMem

memory allocation (out-of-memory) error.

ErrErr

error while running the message handler.

ErrFile

opening or reading a file failed.

Instances

Instances details
Eq Status Source # 
Instance details

Defined in HsLua.Core.Types

Methods

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

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

Show Status Source # 
Instance details

Defined in HsLua.Core.Types

status :: LuaE e Status Source #

Returns the status of this Lua thread.

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

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

Wraps lua_status.

garbage-collection function and options

data GCControl Source #

Commands to control the garbage collector.

Constructors

GCStop

stops the garbage collector.

GCRestart

restarts the garbage collector

GCCollect

performs a full garbage-collection cycle.

GCCount

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

GCCountb

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

GCStep CInt

performs an incremental step of garbage collection, corresponding to the allocation of stepsize Kbytes.

GCInc CInt CInt CInt

Changes the collector to incremental mode with the given parameters (see <https://www.lua.org/manual/5.4/manual.html#2.5.1 §2.5.1>). Returns the previous mode (LUA_GCGEN or LUA_GCINC). Parameters: pause, stepmul, and stepsize.

GCGen CInt CInt

Changes the collector to generational mode with the given parameters (see <https://www.lua.org/manual/5.4/manual.html#2.5.2 §2.5.2>). Returns the previous mode (LUA_GCGEN or LUA_GCINC).

GCIsRunning

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

Instances

Instances details
Eq GCControl Source # 
Instance details

Defined in HsLua.Core.Types

Ord GCControl Source # 
Instance details

Defined in HsLua.Core.Types

Show GCControl Source # 
Instance details

Defined in HsLua.Core.Types

gc :: GCControl -> LuaE e Int Source #

Controls the garbage collector.

This function performs several tasks, according to the given control command. See the documentation for GCControl.

Wraps lua_gc.

miscellaneous and helper functions

next :: LuaError e => StackIndex -> LuaE e Bool Source #

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

Errors on the Lua side are caught and rethrown as a Exception.

This function wraps hslua_next. See also: lua_next.

error :: LuaE e NumResults Source #

Signals to Lua that an error has occurred and that the error object is at the top of the stack.

concat :: LuaError e => NumArgs -> LuaE e () 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).

Wraps hslua_concat. See also lua_concat.

pushglobaltable :: LuaE e () Source #

Pushes the global environment onto the stack.

Wraps lua_pushglobaltable.

register :: LuaError e => Name -> CFunction -> LuaE e () Source #

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

Behaves like "lua_register".

loading libraries

openbase :: LuaError e => LuaE e () Source #

Pushes Lua's base library onto the stack.

This function pushes and and calls luaopen_base.

opendebug :: LuaError e => LuaE e () Source #

Pushes Lua's debug library onto the stack.

This function pushes and and calls luaopen_io.

openio :: LuaError e => LuaE e () Source #

Pushes Lua's io library onto the stack.

This function pushes and and calls luaopen_io.

openlibs :: LuaE e () Source #

Opens all standard Lua libraries into the current state and sets each library name as a global value.

This function wraps luaL_openlibs.

openmath :: LuaError e => LuaE e () Source #

Pushes Lua's math library onto the stack.

This function pushes and and calls luaopen_math.

openpackage :: LuaError e => LuaE e () Source #

Pushes Lua's package library onto the stack.

This function pushes and and calls luaopen_package.

openos :: LuaError e => LuaE e () Source #

Pushes Lua's os library onto the stack.

This function pushes and and calls luaopen_os.

openstring :: LuaError e => LuaE e () Source #

Pushes Lua's string library onto the stack.

This function pushes and and calls luaopen_string.

opentable :: LuaError e => LuaE e () Source #

Pushes Lua's table library onto the stack.

This function pushes and and calls luaopen_table.

Auxiliary library

checkstack' Source #

Arguments

:: LuaError e 
=> Int

sz (requested additional size)

-> String

msg

-> LuaE e () 

Grows the stack size to top + sz elements, raising an error if the stack cannot grow to that size. msg is an additional text to go into the error message (or the empty string for no additional text).

dostring :: ByteString -> LuaE e Status Source #

Loads and runs the given string.

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

dofile :: FilePath -> LuaE e Status Source #

Loads and runs the given file. Note that the filepath is interpreted by Lua, not Haskell. The resulting chunk is named using the UTF8 encoded filepath.

getmetafield Source #

Arguments

:: StackIndex

obj

-> Name

e

-> LuaE e 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.

Wraps luaL_getmetafield.

getmetatable' Source #

Arguments

:: Name

tname

-> LuaE e Type 

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.

Wraps luaL_getmetatable.

getsubtable Source #

Arguments

:: LuaError e 
=> StackIndex

idx

-> Name

fname

-> LuaE e Bool 

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 :: Name -> LuaE e 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.

Wraps luaL_newmetatable.

requiref Source #

Arguments

:: LuaError e 
=> Name

modname

-> CFunction

openf

-> Bool

glb

-> LuaE e () 

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.

See requirehs for a version intended to be used with Haskell actions.

tostring' :: forall e. LuaError e => StackIndex -> LuaE e ByteString Source #

Converts any Lua value at the given index to a ByteString in a reasonable format. The resulting string is pushed onto the stack and also returned by the function.

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.

Wraps hsluaL_tolstring.

traceback :: State -> Maybe ByteString -> Int -> LuaE e () Source #

Creates and pushes a traceback of the stack L1. If a message is given it is appended at the beginning of the traceback. The level parameter tells at which level to start the traceback.

Wraps luaL_traceback.

where' Source #

Arguments

:: Int

lvl

-> LuaE e () 

Pushes onto the stack a string identifying the current position of the control at level lvl in the call stack. Typically this string has the following format:

chunkname:currentline:

Level 0 is the running function, level 1 is the function that called the running function, etc.

This function is used to build a prefix for error messages.

References

data Reference #

Reference to a stored value.

Constructors

Reference CInt

Reference to a stored value

RefNil

Reference to a nil value

Instances

Instances details
Eq Reference 
Instance details

Defined in Lua.Auxiliary

Show Reference 
Instance details

Defined in Lua.Auxiliary

ref :: StackIndex -> LuaE e 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 unref frees a reference and its associated object.

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

Wraps luaL_ref.

getref :: LuaError e => StackIndex -> Reference -> LuaE e Type Source #

Push referenced value from the table at the given index.

unref Source #

Arguments

:: StackIndex

idx

-> Reference

ref

-> LuaE e () 

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

Wraps luaL_unref. See also: luaL_unref.

fromReference :: Reference -> CInt #

Convert a reference to its C representation.

toReference :: CInt -> Reference #

Create a reference from its C representation.

noref :: Int Source #

Value signaling that no reference was found.

refnil :: Int Source #

Value signaling that no reference was created.

Registry fields

loaded :: Name Source #

Key to the registry field that holds the table of loaded modules.

preload :: Name Source #

Key to the registry field that holds the table of loader functions.

Running with tracebacks

pcallTrace :: NumArgs -> NumResults -> LuaE e Status Source #

Like pcall, but sets an appropriate message handler function, thereby adding a stack traceback if an error occurs.

callTrace :: LuaError e => NumArgs -> NumResults -> LuaE e () Source #

Like call, but adds a traceback if an error occurs.

dofileTrace :: FilePath -> LuaE e Status Source #

Run the given file as a Lua program, while also adding a traceback to the error message if an error occurs.

Haskell userdata values

Push arbitrary Haskell values to the Lua stack.

newhsuserdatauv :: forall a e. a -> Int -> LuaE e () Source #

Creates a new userdata wrapping the given Haskell object. The userdata is pushed to the top of the stack.

newudmetatable :: Name -> LuaE e Bool Source #

Creates and registers a new metatable for a userdata-wrapped Haskell value; checks whether a metatable of that name has been registered yet and uses the registered table if possible.

Using a metatable created by this functions ensures that the pointer to the Haskell value will be freed when the userdata object is garbage collected in Lua.

The name may not contain a nul character.

fromuserdata Source #

Arguments

:: forall a e. StackIndex

stack index of userdata

-> Name

expected name of userdata object

-> LuaE e (Maybe a) 

Retrieves a Haskell object from userdata at the given index. The userdata must have the given name.

putuserdata Source #

Arguments

:: forall a e. StackIndex

index

-> Name

name

-> a

new value

-> LuaE e Bool 

Replaces the Haskell value contained in the userdata value at index. Checks that the userdata is of type name and returns True on success, or False otherwise.

Haskell functions and closures

type HaskellFunction e = LuaE e NumResults Source #

Haskell function that can be called from Lua. The HsLua equivallent of a PreCFunction.

pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e () Source #

Pushes Haskell function as a callable userdata. All values created will be garbage collected. The function should behave similar to a CFunction.

Error conditions should be indicated by raising a catchable exception or by returning the result of error.

Example:

mod23 :: Lua NumResults
mod23 = do
  mn <- tointeger (nthBottom 1)
  case mn of
    Nothing -> pushstring "expected an integer" *> error
    Just n  -> pushinteger (n `mod` 23)
pushHaskellFunction mod23
setglobal "mod23"

pushPreCFunction :: PreCFunction -> LuaE e () Source #

Converts a pre C function to a Lua function and pushes it to the stack.

Pre C functions collect parameters from the stack and return a CInt that represents number of return values left on the stack. See CFunction for more info.

Error handling

class Exception e => LuaError e where Source #

Any type that you wish to use for error handling in HsLua must be an instance of the LuaError class.

Methods

popException :: LuaE e e Source #

Converts the error at the top of the stack into an exception and pops the error off the stack.

This function is expected to produce a valid result for any Lua value; neither a Haskell exception nor a Lua error may result when this is called.

pushException :: e -> LuaE e () Source #

Pushes an exception to the top of the Lua stack. The pushed Lua object is used as an error object, and it is recommended that calling tostring() on the object produces an informative message.

luaException :: String -> e Source #

Creates a new exception with the given message.

newtype Exception Source #

Default Lua error type. Exceptions raised by Lua-related operations.

Constructors

Exception 

try :: Exception e => LuaE e a -> LuaE e (Either e a) Source #

Return either the result of a Lua computation or, if an exception was thrown, the error.

failLua :: forall e a. LuaError e => String -> LuaE e a Source #

Raises an exception in the Lua monad.

throwErrorAsException :: LuaError e => LuaE e a Source #

Converts a Lua error at the top of the stack into a Haskell exception and throws it.

throwTypeMismatchError :: forall e a. LuaError e => ByteString -> StackIndex -> LuaE e a Source #

Raises an exception that's appropriate when the type of a Lua object at the given index did not match the expected type. The name or description of the expected type is taken as an argument.

changeErrorType :: forall old new a. LuaE old a -> LuaE new a Source #

Change the error type of a computation.

Helpers

popErrorMessage :: State -> IO ByteString Source #

Retrieve and pop the top object as an error message. This is very similar to tostring', but ensures that we don't recurse if getting the message failed.

This helpful as a "last resort" method when implementing popException.

pushTypeMismatchError Source #

Arguments

:: ByteString

name or description of expected type

-> StackIndex

stack index of mismatching object

-> LuaE e () 

Creates an error to notify about a Lua type mismatch and pushes it to the stack.

Package

requirehs Source #

Arguments

:: LuaError e 
=> Name

modname

-> (Name -> LuaE e ())

openf

-> LuaE e () 

Load a module, defined by a Haskell action, under the given name.

Similar to luaL_requiref: 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.

Leaves a copy of the module on the stack.

preloadhs :: LuaError e => Name -> LuaE e NumResults -> LuaE e () Source #

Registers a preloading function. Takes an module name and the Lua operation which produces the package.