| Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2024 Albert Krewinkel | 
|---|---|
| License | MIT | 
| Maintainer | Albert Krewinkel <tarleb@hslua.org> | 
| Stability | beta | 
| Portability | non-portable (depends on GHC) | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
HsLua.Core
Contents
- Run Lua computations
- 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
- Debug interface
- Haskell userdata values
- Error handling
- Package
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
Synopsis
- run :: LuaE e a -> IO a
- runWith :: State -> LuaE e a -> IO a
- runEither :: Exception e => LuaE e a -> IO (Either e a)
- data GCManagedState
- newGCManagedState :: IO GCManagedState
- closeGCManagedState :: GCManagedState -> IO ()
- withGCManagedState :: GCManagedState -> LuaE e a -> IO a
- newtype LuaE e a = Lua {- unLua :: ReaderT LuaEnvironment IO a
 
- type Lua a = LuaE Exception a
- unsafeRunWith :: State -> LuaE e a -> IO a
- liftIO :: MonadIO m => IO a -> m a
- state :: LuaE e State
- newtype LuaEnvironment = LuaEnvironment {- luaEnvState :: State
 
- type CFunction = FunPtr PreCFunction
- type PreCFunction = State -> IO NumResults
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype StackIndex = StackIndex {}
- nthTop :: CInt -> StackIndex
- nthBottom :: CInt -> StackIndex
- nth :: CInt -> StackIndex
- top :: StackIndex
- newtype NumArgs = NumArgs {- fromNumArgs :: CInt
 
- newtype NumResults = NumResults {}
- newtype Name = Name {}
- multret :: NumResults
- registryindex :: StackIndex
- upvalueindex :: StackIndex -> StackIndex
- newtype State = State (Ptr ())
- newstate :: IO State
- close :: State -> IO ()
- absindex :: StackIndex -> LuaE e StackIndex
- gettop :: LuaE e StackIndex
- settop :: StackIndex -> LuaE e ()
- pushvalue :: StackIndex -> LuaE e ()
- copy :: StackIndex -> StackIndex -> LuaE e ()
- insert :: StackIndex -> LuaE e ()
- rotate :: StackIndex -> Int -> LuaE e ()
- pop :: Int -> LuaE e ()
- remove :: StackIndex -> LuaE e ()
- replace :: StackIndex -> LuaE e ()
- checkstack :: Int -> LuaE e Bool
- data Type
- ltype :: StackIndex -> LuaE e Type
- typename :: Type -> LuaE e ByteString
- isboolean :: StackIndex -> LuaE e Bool
- iscfunction :: StackIndex -> LuaE e Bool
- isfunction :: StackIndex -> LuaE e Bool
- isinteger :: StackIndex -> LuaE e Bool
- islightuserdata :: StackIndex -> LuaE e Bool
- isnil :: StackIndex -> LuaE e Bool
- isnone :: StackIndex -> LuaE e Bool
- isnoneornil :: StackIndex -> LuaE e Bool
- isnumber :: StackIndex -> LuaE e Bool
- isstring :: StackIndex -> LuaE e Bool
- istable :: StackIndex -> LuaE e Bool
- isthread :: StackIndex -> LuaE e Bool
- isuserdata :: StackIndex -> LuaE e Bool
- toboolean :: StackIndex -> LuaE e Bool
- tocfunction :: StackIndex -> LuaE e (Maybe CFunction)
- tointeger :: StackIndex -> LuaE e (Maybe Integer)
- tonumber :: StackIndex -> LuaE e (Maybe Number)
- topointer :: StackIndex -> LuaE e (Ptr ())
- tostring :: StackIndex -> LuaE e (Maybe ByteString)
- tothread :: StackIndex -> LuaE e (Maybe State)
- touserdata :: StackIndex -> LuaE e (Maybe (Ptr a))
- rawlen :: StackIndex -> LuaE e Int
- data RelationalOperator
- compare :: LuaError e => StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
- equal :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool
- lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool
- rawequal :: StackIndex -> StackIndex -> LuaE e Bool
- pushboolean :: Bool -> LuaE e ()
- pushcfunction :: CFunction -> LuaE e ()
- pushcclosure :: CFunction -> NumArgs -> LuaE e ()
- pushinteger :: Integer -> LuaE e ()
- pushlightuserdata :: Ptr a -> LuaE e ()
- pushnil :: LuaE e ()
- pushnumber :: Number -> LuaE e ()
- pushstring :: ByteString -> LuaE e ()
- pushthread :: LuaE e Bool
- getglobal :: LuaError e => Name -> LuaE e Type
- gettable :: LuaError e => StackIndex -> LuaE e Type
- getfield :: LuaError e => StackIndex -> Name -> LuaE e Type
- rawget :: LuaError e => StackIndex -> LuaE e Type
- rawgeti :: LuaError e => StackIndex -> Integer -> LuaE e Type
- createtable :: Int -> Int -> LuaE e ()
- newtable :: LuaE e ()
- newuserdatauv :: Int -> Int -> LuaE e (Ptr ())
- getmetatable :: StackIndex -> LuaE e Bool
- getiuservalue :: StackIndex -> Int -> LuaE e Type
- setglobal :: LuaError e => Name -> LuaE e ()
- settable :: LuaError e => StackIndex -> LuaE e ()
- setfield :: LuaError e => StackIndex -> Name -> LuaE e ()
- rawset :: LuaError e => StackIndex -> LuaE e ()
- rawseti :: LuaError e => StackIndex -> Integer -> LuaE e ()
- setmetatable :: StackIndex -> LuaE e ()
- setiuservalue :: StackIndex -> Int -> LuaE e Bool
- call :: LuaError e => NumArgs -> NumResults -> LuaE e ()
- pcall :: NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
- load :: Reader -> Ptr () -> Name -> LuaE e Status
- loadbuffer :: ByteString -> Name -> LuaE e Status
- loadfile :: Maybe FilePath -> LuaE e Status
- loadstring :: ByteString -> LuaE e Status
- data Status
- status :: LuaE e Status
- data GCControl
- gc :: GCControl -> LuaE e Int
- next :: LuaError e => StackIndex -> LuaE e Bool
- error :: LuaE e NumResults
- concat :: LuaError e => NumArgs -> LuaE e ()
- pushglobaltable :: LuaE e ()
- register :: LuaError e => Name -> CFunction -> LuaE e ()
- setwarnf :: WarnFunction -> Ptr () -> LuaE e ()
- openbase :: LuaError e => LuaE e ()
- opendebug :: LuaError e => LuaE e ()
- openio :: LuaError e => LuaE e ()
- openlibs :: LuaE e ()
- openmath :: LuaError e => LuaE e ()
- openpackage :: LuaError e => LuaE e ()
- openos :: LuaError e => LuaE e ()
- openstring :: LuaError e => LuaE e ()
- opentable :: LuaError e => LuaE e ()
- checkstack' :: LuaError e => Int -> String -> LuaE e ()
- dostring :: ByteString -> LuaE e Status
- dofile :: Maybe FilePath -> LuaE e Status
- getmetafield :: StackIndex -> Name -> LuaE e Type
- getmetatable' :: Name -> LuaE e Type
- getsubtable :: LuaError e => StackIndex -> Name -> LuaE e Bool
- newmetatable :: Name -> LuaE e Bool
- requiref :: LuaError e => Name -> CFunction -> Bool -> LuaE e ()
- tostring' :: LuaError e => StackIndex -> LuaE e ByteString
- traceback :: State -> Maybe ByteString -> Int -> LuaE e ()
- where' :: Int -> LuaE e ()
- data Reference
- ref :: StackIndex -> LuaE e Reference
- getref :: LuaError e => StackIndex -> Reference -> LuaE e Type
- unref :: StackIndex -> Reference -> LuaE e ()
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
- noref :: Int
- refnil :: Int
- loaded :: Name
- preload :: Name
- pcallTrace :: NumArgs -> NumResults -> LuaE e Status
- callTrace :: LuaError e => NumArgs -> NumResults -> LuaE e ()
- dofileTrace :: Maybe FilePath -> LuaE e Status
- dostringTrace :: ByteString -> LuaE e Status
- setwarnf' :: LuaError e => (ByteString -> LuaE e ()) -> LuaE e ()
- getupvalue :: StackIndex -> Int -> LuaE e (Maybe Name)
- setupvalue :: StackIndex -> Int -> LuaE e (Maybe Name)
- newhsuserdatauv :: a -> Int -> LuaE e ()
- newudmetatable :: Name -> LuaE e Bool
- fromuserdata :: forall a e. StackIndex -> Name -> LuaE e (Maybe a)
- putuserdata :: StackIndex -> Name -> a -> LuaE e Bool
- type HaskellFunction e = LuaE e NumResults
- pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e ()
- pushPreCFunction :: PreCFunction -> LuaE e ()
- class Exception e => LuaError e where- popException :: LuaE e e
- pushException :: e -> LuaE e ()
- luaException :: String -> e
 
- newtype Exception = Exception {}
- try :: Exception e => LuaE e a -> LuaE e (Either e a)
- failLua :: LuaError e => String -> LuaE e a
- throwErrorAsException :: LuaError e => LuaE e a
- throwTypeMismatchError :: LuaError e => ByteString -> StackIndex -> LuaE e a
- changeErrorType :: forall old new a. LuaE old a -> LuaE new a
- popErrorMessage :: State -> IO ByteString
- pushTypeMismatchError :: ByteString -> StackIndex -> LuaE e ()
- requirehs :: LuaError e => Name -> (Name -> LuaE e ()) -> LuaE e ()
- preloadhs :: LuaError e => Name -> LuaE e NumResults -> LuaE e ()
Run Lua computations
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 #
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) #
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.
data GCManagedState #
Wrapper of a Lua state whose lifetime is managed by the Haskell garbage collector and has a finalizer attached. This means that the state does not have to be closed explicitly, but will be closed automatically when the value is garbage collected in Haskell.
newGCManagedState :: IO GCManagedState #
Creates a new Lua state that is under the control of the Haskell garbage collector.
closeGCManagedState :: GCManagedState -> IO () #
Closes the Lua state and runs all finalizers associated with it. The state _may not_ be used after it has been closed.
withGCManagedState :: GCManagedState -> LuaE e a -> IO a #
Runs a Lua action with a state that's managed by GC.
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
Constructors
| Lua | |
| Fields 
 | |
Instances
| MonadReader LuaEnvironment (LuaE e) # | |
| 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 # | |
| MonadIO (LuaE e) # | |
| Defined in HsLua.Core.Types | |
| MonadCatch (LuaE e) # | |
| Defined in HsLua.Core.Types | |
| MonadMask (LuaE e) # | |
| Defined in HsLua.Core.Types Methods mask :: HasCallStack => ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b # uninterruptibleMask :: HasCallStack => ((forall a. LuaE e a -> LuaE e a) -> LuaE e b) -> LuaE e b # generalBracket :: HasCallStack => LuaE e a -> (a -> ExitCase b -> LuaE e c) -> (a -> LuaE e b) -> LuaE e (b, c) # | |
| MonadThrow (LuaE e) # | |
| Defined in HsLua.Core.Types Methods throwM :: (HasCallStack, Exception e0) => e0 -> LuaE e a # | |
| LuaError e => Alternative (LuaE e) # | |
| Applicative (LuaE e) # | |
| Functor (LuaE e) # | |
| Monad (LuaE e) # | |
| LuaError e => MonadFail (LuaE e) # | |
| Defined in HsLua.Core.Error | |
type Lua a = LuaE Exception a #
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 #
Run the given operation, but crash if any Haskell exceptions occur.
This function is identical to runWith; it exists for backwards
 compatibility.
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO monad.
 This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
 (i.e. IO is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO () and IO ()
Luckily, we know of a function that takes an IO a(m a): liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
newtype LuaEnvironment #
Environment in which Lua computations are evaluated.
Constructors
| LuaEnvironment | |
| Fields 
 | |
Instances
| MonadReader LuaEnvironment (LuaE e) # | |
| 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_gettoplua_gettop
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.
The type of integers in Lua.
By default this type is Int64LUA_INT_TYPE in luaconf.h.)
See lua_Integer.
Instances
| Bounded Integer | |
| Enum Integer | |
| Num Integer | |
| Read Integer | |
| Integral Integer | |
| Defined in Lua.Types | |
| Real Integer | |
| Defined in Lua.Types Methods toRational :: Integer -> Rational # | |
| Show Integer | |
| Eq Integer | |
| Ord Integer | |
The type of floats in Lua.
By default this type is DoubleLUA_FLOAT_TYPE in
 luaconf.h.)
See lua_Number.
Instances
| Floating Number | |
| RealFloat Number | |
| Defined in Lua.Types Methods 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 # | |
| Num Number | |
| Read Number | |
| Fractional Number | |
| Real Number | |
| Defined in Lua.Types Methods toRational :: Number -> Rational # | |
| RealFrac Number | |
| Show Number | |
| Eq Number | |
| Ord Number | |
Stack index
newtype StackIndex #
A stack index
Constructors
| StackIndex | |
| Fields | |
Instances
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
The number of arguments consumed curing a function call.
Constructors
| NumArgs | |
| Fields 
 | |
newtype NumResults #
The number of results returned by a function call.
Constructors
| NumResults | |
| Fields | |
Instances
| Num NumResults | |
| Defined in Lua.Types Methods (+) :: NumResults -> NumResults -> NumResults # (-) :: NumResults -> NumResults -> NumResults # (*) :: NumResults -> NumResults -> NumResults # negate :: NumResults -> NumResults # abs :: NumResults -> NumResults # signum :: NumResults -> NumResults # fromInteger :: Integer -> NumResults # | |
| Show NumResults | |
| Defined in Lua.Types Methods showsPrec :: Int -> NumResults -> ShowS # show :: NumResults -> String # showList :: [NumResults] -> ShowS # | |
| Eq NumResults | |
| Defined in Lua.Types | |
| Ord NumResults | |
| Defined in Lua.Types Methods compare :: NumResults -> NumResults -> Ordering # (<) :: NumResults -> NumResults -> Bool # (<=) :: NumResults -> NumResults -> Bool # (>) :: NumResults -> NumResults -> Bool # (>=) :: NumResults -> NumResults -> Bool # max :: NumResults -> NumResults -> NumResults # min :: NumResults -> NumResults -> NumResults # | |
Table fields
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 | |
Lua API
Constants and pseudo-indices
multret :: NumResults #
Option for multiple returns in pcall
Pseudo stack index of the Lua registry.
upvalueindex :: StackIndex -> StackIndex #
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
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 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.
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 #
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 #
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 () #
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 () #
Pushes a copy of the element at the given index onto the stack.
Wraps lua_pushvalue.
copy :: StackIndex -> StackIndex -> LuaE e () #
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 () #
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.
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.
remove :: StackIndex -> LuaE e () #
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 () #
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 #
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
Enumeration used as type tag. See lua_type.
Constructors
| 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 | 
ltype :: StackIndex -> LuaE e Type #
typename :: Type -> LuaE e ByteString #
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 #
Returns True if the value at the given index is a boolean, and
 False otherwise.
Wraps lua_isboolean.
iscfunction :: StackIndex -> LuaE e Bool #
Returns True if the value at the given index is a C function, and
 False otherwise.
Wraps lua_iscfunction.
isfunction :: StackIndex -> LuaE e Bool #
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 #
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 #
Returns True if the value at the given index is a light userdata,
 and False otherwise.
Wraps lua_islightuserdata.
isnil :: StackIndex -> LuaE e Bool #
isnone :: StackIndex -> LuaE e Bool #
Returns True if the given index is not valid, and False
 otherwise.
Wraps lua_isnone.
isnoneornil :: StackIndex -> LuaE e Bool #
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 #
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 #
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 #
Returns True if the value at the given index is a table, and
 False otherwise.
Wraps lua_istable.
isthread :: StackIndex -> LuaE e Bool #
Returns True if the value at the given index is a thread, and
 False otherwise.
Wraps lua_isthread.
isuserdata :: StackIndex -> LuaE e Bool #
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 #
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
Wraps lua_toboolean.
tocfunction :: StackIndex -> LuaE e (Maybe CFunction) #
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) #
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) #
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 ()) #
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) #
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) #
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)) #
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 #
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 #
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 | 
Instances
| Show RelationalOperator # | |
| Defined in HsLua.Core.Types Methods showsPrec :: Int -> RelationalOperator -> ShowS # show :: RelationalOperator -> String # showList :: [RelationalOperator] -> ShowS # | |
| Eq RelationalOperator # | |
| Defined in HsLua.Core.Types Methods (==) :: RelationalOperator -> RelationalOperator -> Bool # (/=) :: RelationalOperator -> RelationalOperator -> Bool # | |
| Ord RelationalOperator # | |
| Defined in HsLua.Core.Types Methods compare :: RelationalOperator -> RelationalOperator -> Ordering # (<) :: RelationalOperator -> RelationalOperator -> Bool # (<=) :: RelationalOperator -> RelationalOperator -> Bool # (>) :: RelationalOperator -> RelationalOperator -> Bool # (>=) :: RelationalOperator -> RelationalOperator -> Bool # max :: RelationalOperator -> RelationalOperator -> RelationalOperator # min :: RelationalOperator -> RelationalOperator -> RelationalOperator # | |
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.
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
lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool #
Tests whether the object under the first index is smaller than that
 under the second. Uses compare
rawequal :: StackIndex -> StackIndex -> LuaE e Bool #
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 () #
Pushes a boolean value with the given value onto the stack.
This functions wraps lua_pushboolean.
pushcfunction :: CFunction -> LuaE e () #
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 .
 lua_pushcfunction.pushcclosure 0
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 () #
Pushes an integer with with the given value onto the stack.
Wraps lua_pushinteger.
pushlightuserdata :: Ptr a -> LuaE e () #
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.
Pushes a nil value onto the stack.
Wraps lua_pushnil.
pushnumber :: Number -> LuaE e () #
Pushes a float with the given value onto the stack.
Wraps lua_pushnumber.
pushstring :: ByteString -> LuaE e () #
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 #
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 #
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 #
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 #
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 #
Similar to gettable
Wraps lua_rawget.
rawgeti :: LuaError e => StackIndex -> Integer -> LuaE e Type #
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 () #
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.
Creates a new empty table and pushes it onto the stack. It is
 equivalent to createtable 0 0.
See also: lua_newtable.
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 #
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.
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)
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 () #
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 () #
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 () #
Similar to settable
Wraps lua_rawset.
rawseti :: LuaError e => StackIndex -> Integer -> LuaE e () #
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 () #
Pops a table from the stack and sets it as the new metatable for the value at the given index.
Wraps lua_setmetatable.
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 () #
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 #
Calls a function in protected mode.
Both nargs and nresults have the same meaning as in callpcall behaves exactly like
 callpcall catches it, pushes
 a single value on the stack (the error message), and returns the
 error code. Like callpcall 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
This function wraps lua_pcall.
load :: Reader -> Ptr () -> Name -> LuaE e Status #
Loads a Lua chunk (without running it). If there are no errors,
 load
The return values of load
- OK
- ErrSyntax
- ErrMem
- ErrGcmm- __gcmetamethod. (This error has no relation with the chunk being loaded. It is generated by the garbage collector.)
This function only loads a chunk; it does not run it.
load automatically detects whether the chunk is text or binary, and
 loads it accordingly (see program luac).
The loadReader
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.
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 loadname 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.
Loads a file as a Lua chunk. This function uses lua_load (see
 loadfilename. If
 filename is Nothing, then it loads from the standard input. 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 loadErrFile
As load
See luaL_loadfile.
loadstring :: ByteString -> LuaE e Status #
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
See luaL_loadstring.
Coroutine functions
Lua status values.
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
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
  | 
| 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
 ( | 
| 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
 ( | 
| GCIsRunning | returns a boolean that tells whether the collector is running (i.e., not stopped). | 
Instances
| Show GCControl # | |
| Eq GCControl # | |
| Ord GCControl # | |
miscellaneous and helper functions
next :: LuaError e => StackIndex -> LuaE e Bool #
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 #
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 () #
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 () #
Pushes the global environment onto the stack.
Wraps lua_pushglobaltable.
register :: LuaError e => Name -> CFunction -> LuaE e () #
Sets the C function f as the new value of global name.
Behaves like "lua_register".
Arguments
| :: WarnFunction | f | 
| -> Ptr () | ud | 
| -> LuaE e () | 
Sets the warning function to be used by Lua to emit warnings (see
 WarnFunction). The ud parameter sets the value ud passed to the
 warning function.
loading libraries
openbase :: LuaError e => LuaE e () #
Pushes Lua's base library onto the stack.
This function pushes and and calls luaopen_base.
opendebug :: LuaError e => LuaE e () #
Pushes Lua's debug library onto the stack.
This function pushes and and calls luaopen_io.
openio :: LuaError e => LuaE e () #
Pushes Lua's io library onto the stack.
This function pushes and and calls luaopen_io.
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 () #
Pushes Lua's math library onto the stack.
This function pushes and and calls luaopen_math.
openpackage :: LuaError e => LuaE e () #
Pushes Lua's package library onto the stack.
This function pushes and and calls luaopen_package.
openos :: LuaError e => LuaE e () #
Pushes Lua's os library onto the stack.
This function pushes and and calls luaopen_os.
openstring :: LuaError e => LuaE e () #
Pushes Lua's string library onto the stack.
This function pushes and and calls luaopen_string.
opentable :: LuaError e => LuaE e () #
Pushes Lua's table library onto the stack.
This function pushes and and calls luaopen_table.
Auxiliary library
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 #
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 :: Maybe FilePath -> LuaE e Status #
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.
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.
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.
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 #
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.
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' :: LuaError e => StackIndex -> LuaE e ByteString #
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 () #
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.
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
Reference to a stored value.
ref :: StackIndex -> LuaE e Reference #
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
If the object at the top of the stack is nil, refrefnilnorefref
Wraps luaL_ref.
getref :: LuaError e => StackIndex -> Reference -> LuaE e Type #
Push referenced value from the table at the given index.
Arguments
| :: StackIndex | idx | 
| -> Reference | ref | 
| -> LuaE e () | 
Releases reference refidx (see
 refref
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.
Registry fields
Running with tracebacks
pcallTrace :: NumArgs -> NumResults -> LuaE e Status #
Like pcall
callTrace :: LuaError e => NumArgs -> NumResults -> LuaE e () #
Like call
dofileTrace :: Maybe FilePath -> LuaE e Status #
Run the given file as a Lua program, while also adding a traceback to the error message if an error occurs.
dostringTrace :: ByteString -> LuaE e Status #
Warnings
setwarnf' :: LuaError e => (ByteString -> LuaE e ()) -> LuaE e () #
Sets a warning function. This is a simplified version of
 lua_setwarnf. The given function is called with the concatenated
 warning components as the single argument.
Control messages are handled internally and are not passed on the
 warning hook. As with the default warning function, the control
 messages @on and @off can switch error reporting to stderr on
 and off. The given Haskell function will be called in either case,
 even when the error is not written to stderr.
Wraps hsluaL_setwarnf.
Debug interface
Arguments
| :: StackIndex | funcindex | 
| -> Int | n | 
| -> LuaE e (Maybe Name) | 
Gets information about the n-th upvalue of the closure at index
 funcindex. It pushes the upvalue's value onto the stack and returns
 its name. Returns Nothing (and pushes nothing) when the index n
 is greater than the number of upvalues.
See debug.getupvalue for more information about upvalues.
[0, +(0|1), -]
Wraps lua_getupvalue.
Arguments
| :: StackIndex | funcindex | 
| -> Int | n | 
| -> LuaE e (Maybe Name) | 
Sets the value of a closure’s upvalue. It assigns the value on the top of the stack to the upvalue and returns its name. It also pops the value from the stack.
Returns Nothing (and pops nothing) when the index n is greater
 than the number of upvalues.
Parameters funcindex and n are as in the function getupvalue.
[-(0|1), +0, -]
Wraps lua_setupvalue.
Haskell userdata values
Push arbitrary Haskell values to the Lua stack.
Creates a new userdata wrapping the given Haskell object. The userdata is pushed to the top of the stack.
newudmetatable :: Name -> LuaE e Bool #
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.
Returns True if a new metatable was created, and False otherwise.
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.
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.
Arguments
| :: StackIndex | index | 
| -> Name | name | 
| -> a | new value | 
| -> LuaE e Bool | 
Haskell functions and closures
type HaskellFunction e = LuaE e NumResults #
Haskell function that can be called from Lua.
 The HsLua equivallent of a PreCFunction.
pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e () #
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 () #
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 #
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 #
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 () #
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 #
Creates a new exception with the given message.
Instances
| LuaError Exception # | |
| Defined in HsLua.Core.Error Methods popException :: LuaE Exception Exception # pushException :: Exception -> LuaE Exception () # luaException :: String -> Exception # | |
Default Lua error type. Exceptions raised by Lua-related operations.
Constructors
| Exception | |
| Fields | |
Instances
| Exception Exception # | |
| Defined in HsLua.Core.Error Methods toException :: Exception -> SomeException # fromException :: SomeException -> Maybe Exception # displayException :: Exception -> String # backtraceDesired :: Exception -> Bool # | |
| Show Exception # | |
| Eq Exception # | |
| LuaError Exception # | |
| Defined in HsLua.Core.Error Methods popException :: LuaE Exception Exception # pushException :: Exception -> LuaE Exception () # luaException :: String -> Exception # | |
try :: Exception e => LuaE e a -> LuaE e (Either e a) #
Return either the result of a Lua computation or, if an exception was thrown, the error.
throwErrorAsException :: LuaError e => LuaE e a #
Converts a Lua error at the top of the stack into a Haskell exception and throws it.
throwTypeMismatchError :: LuaError e => ByteString -> StackIndex -> LuaE e a #
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 #
Change the error type of a computation.
Helpers
popErrorMessage :: State -> IO ByteString #
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.
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
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.