Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2021 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | beta |
Portability | non-portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell2010 |
The core Lua types, including mappings of Lua types to Haskell.
This module has mostly been moved to
and
currently re-exports that module. This module might be removed in
the future.Types
Synopsis
- newtype LuaE e a = Lua {
- unLua :: ReaderT LuaEnvironment IO a
- newtype LuaEnvironment = LuaEnvironment {
- luaEnvState :: State
- newtype State = State (Ptr ())
- type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar))
- liftLua :: (State -> IO a) -> LuaE e a
- liftLua1 :: (State -> a -> IO b) -> a -> LuaE e b
- state :: LuaE e State
- runWith :: State -> LuaE e a -> IO a
- unsafeRunWith :: State -> LuaE e a -> IO a
- data GCControl
- toGCcode :: GCControl -> GCCode
- toGCdata :: GCControl -> CInt
- data Type
- fromType :: Type -> TypeCode
- toType :: TypeCode -> Type
- liftIO :: MonadIO m => IO a -> m a
- type CFunction = FunPtr PreCFunction
- type PreCFunction = State -> IO NumResults
- type HaskellFunction e = LuaE e NumResults
- newtype LuaBool = LuaBool CInt
- fromLuaBool :: LuaBool -> Bool
- toLuaBool :: Bool -> LuaBool
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype StackIndex = StackIndex {}
- registryindex :: StackIndex
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {}
- multret :: NumResults
- data RelationalOperator
- fromRelationalOperator :: RelationalOperator -> OPCode
- data Status
- toStatus :: StatusCode -> Status
- data Reference
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
- noref :: Int
- refnil :: Int
- nthTop :: CInt -> StackIndex
- nthBottom :: CInt -> StackIndex
- nth :: CInt -> StackIndex
- top :: StackIndex
- newtype Name = Name {}
Documentation
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
Lua | |
|
Instances
MonadReader LuaEnvironment (LuaE e) Source # | |
Defined in HsLua.Core.Types ask :: LuaE e LuaEnvironment # local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a # reader :: (LuaEnvironment -> a) -> LuaE e a # | |
Monad (LuaE e) Source # | |
Functor (LuaE e) Source # | |
LuaError e => MonadFail (LuaE e) Source # | |
Defined in HsLua.Core.Error | |
Applicative (LuaE e) Source # | |
MonadIO (LuaE e) Source # | |
Defined in HsLua.Core.Types | |
LuaError e => Alternative (LuaE e) Source # | |
MonadThrow (LuaE e) Source # | |
Defined in HsLua.Core.Types | |
MonadCatch (LuaE e) Source # | |
MonadMask (LuaE e) Source # | |
newtype LuaEnvironment Source #
Environment in which Lua computations are evaluated.
LuaEnvironment | |
|
Instances
MonadReader LuaEnvironment (LuaE e) Source # | |
Defined in HsLua.Core.Types ask :: LuaE e LuaEnvironment # local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a # reader :: (LuaEnvironment -> a) -> LuaE e a # |
An opaque structure that points to a thread and indirectly (through the thread) to the whole state of a Lua interpreter. The Lua library is fully reentrant: it has no global variables. All information about a state is accessible through this structure.
Synonym for lua_State *
. See
lua_State.
type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar)) #
The reader function used by
.
Every time it needs another piece of the chunk, lua_load calls the
reader, passing along its data parameter. The reader must return a
pointer to a block of memory with a new piece of the chunk and set
size to the block size. The block must exist until the reader
function is called again. To signal the end of the chunk, the reader
must return load
NULL
or set size to zero. The reader function may
return pieces of any size greater than zero.
See lua_Reader.
liftLua :: (State -> IO a) -> LuaE e a Source #
Turn a function of typ Lua.State -> IO a
into a monadic Lua
operation.
liftLua1 :: (State -> a -> IO b) -> a -> LuaE e b Source #
Turn a function of typ Lua.State -> a -> IO b
into a monadic Lua
operation.
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.
unsafeRunWith :: State -> LuaE e a -> IO a Source #
Run the given operation, but crash if any Haskell exceptions occur.
Commands to control the garbage collector.
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 | performs an incremental step of garbage collection. |
GCSetPause CInt | sets data as the new value for the pause of the collector (see <https://www.lua.org/manual/5.3/manual.html#2.5 §2.5> of the Lua reference manual) and returns the previous value of the pause. |
GCSetStepMul CInt | sets data as the new value for the step multiplier of the collector (see <https://www.lua.org/manual/5.3/manual.html#2.5 §2.5> of the Lua reference manual) and returns the previous value of the step multiplier. |
GCIsRunning | returns a boolean that tells whether the collector is running (i.e., not stopped). |
Enumeration used as type tag. See lua_type.
TypeNone | non-valid stack index |
TypeNil | type of Lua's |
TypeBoolean | type of Lua booleans |
TypeLightUserdata | type of light userdata |
TypeNumber | type of Lua numbers. See |
TypeString | type of Lua string values |
TypeTable | type of Lua tables |
TypeFunction | type of functions, either normal or |
TypeUserdata | type of full user data |
TypeThread | type of Lua threads |
fromType :: Type -> TypeCode Source #
Convert a Lua Type
to a type code which can be passed to the C
API.
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,
returns the
number of arguments received by the function. The first argument (if
any) is at index 1 and its last argument is at index
lua_gettop
. To return values to Lua, a C
function just pushes them onto the stack, in direct order (the first
result is pushed first), and returns the number of results. Any other
value in the stack below the results will be properly discarded by
Lua. Like a Lua function, a C function called by Lua can also return
many results.lua_gettop
See lua_CFunction.
type PreCFunction = State -> IO NumResults #
Type of Haskell functions that can be turned into C functions.
This is the same as a dereferenced CFunction
.
type HaskellFunction e = LuaE e NumResults Source #
Haskell function that can be called from Lua.
The HsLua equivallent of a PreCFunction
.
Boolean value returned by a Lua C API function. This is a
and should be interpreted as CInt
iff the value is False
0
,
otherwise.True
Instances
The type of integers in Lua.
By default this type is
, but that can be changed to
different values in lua. (See Int64
LUA_INT_TYPE
in luaconf.h
.)
See lua_Integer.
Instances
Bounded Integer | |
Enum Integer | |
Eq Integer | |
Integral Integer | |
Defined in Lua.Types | |
Num Integer | |
Ord Integer | |
Real Integer | |
Defined in Lua.Types toRational :: Integer -> Rational # | |
Show Integer | |
The type of floats in Lua.
By default this type is
, but that can be changed in Lua to
a single float or a long double. (See Double
LUA_FLOAT_TYPE
in
luaconf.h
.)
See lua_Number.
Instances
Eq Number | |
Floating Number | |
Fractional Number | |
Num Number | |
Ord Number | |
Real Number | |
Defined in Lua.Types toRational :: Number -> Rational # | |
RealFloat Number | |
Defined in Lua.Types floatRadix :: Number -> Integer # floatDigits :: Number -> Int # floatRange :: Number -> (Int, Int) # decodeFloat :: Number -> (Integer, Int) # encodeFloat :: Integer -> Int -> Number # significand :: Number -> Number # scaleFloat :: Int -> Number -> Number # isInfinite :: Number -> Bool # isDenormalized :: Number -> Bool # isNegativeZero :: Number -> Bool # | |
RealFrac Number | |
Show Number | |
newtype StackIndex #
A stack index
Instances
registryindex :: StackIndex Source #
Pseudo stack index of the Lua registry.
The number of arguments consumed curing a function call.
newtype NumResults #
The number of results returned by a function call.
Instances
Eq NumResults | |
Defined in Lua.Types (==) :: NumResults -> NumResults -> Bool # (/=) :: NumResults -> NumResults -> Bool # | |
Num NumResults | |
Defined in Lua.Types (+) :: NumResults -> NumResults -> NumResults # (-) :: NumResults -> NumResults -> NumResults # (*) :: NumResults -> NumResults -> NumResults # negate :: NumResults -> NumResults # abs :: NumResults -> NumResults # signum :: NumResults -> NumResults # fromInteger :: Integer -> NumResults # | |
Ord NumResults | |
Defined in Lua.Types compare :: NumResults -> NumResults -> Ordering # (<) :: NumResults -> NumResults -> Bool # (<=) :: NumResults -> NumResults -> Bool # (>) :: NumResults -> NumResults -> Bool # (>=) :: NumResults -> NumResults -> Bool # max :: NumResults -> NumResults -> NumResults # min :: NumResults -> NumResults -> NumResults # | |
Show NumResults | |
Defined in Lua.Types showsPrec :: Int -> NumResults -> ShowS # show :: NumResults -> String # showList :: [NumResults] -> ShowS # |
multret :: NumResults Source #
Option for multiple returns in
.pcall
data RelationalOperator Source #
Lua comparison operations.
EQ | Correponds to Lua's equality (==) operator. |
LT | Correponds to Lua's strictly-lesser-than (<) operator |
LE | Correponds to Lua's lesser-or-equal (<=) operator |
Instances
Eq RelationalOperator Source # | |
Defined in HsLua.Core.Types (==) :: RelationalOperator -> RelationalOperator -> Bool # (/=) :: RelationalOperator -> RelationalOperator -> Bool # | |
Ord RelationalOperator Source # | |
Defined in HsLua.Core.Types compare :: RelationalOperator -> RelationalOperator -> Ordering # (<) :: RelationalOperator -> RelationalOperator -> Bool # (<=) :: RelationalOperator -> RelationalOperator -> Bool # (>) :: RelationalOperator -> RelationalOperator -> Bool # (>=) :: RelationalOperator -> RelationalOperator -> Bool # max :: RelationalOperator -> RelationalOperator -> RelationalOperator # min :: RelationalOperator -> RelationalOperator -> RelationalOperator # | |
Show RelationalOperator Source # | |
Defined in HsLua.Core.Types showsPrec :: Int -> RelationalOperator -> ShowS # show :: RelationalOperator -> String # showList :: [RelationalOperator] -> ShowS # |
fromRelationalOperator :: RelationalOperator -> OPCode Source #
Convert relation operator to its C representation.
Lua status values.
References
Reference to a stored value.
fromReference :: Reference -> CInt #
Convert a reference to its C representation.
toReference :: CInt -> Reference #
Create a reference from its C representation.
Stack index helpers
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
Table field names
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.