| Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2022 Albert Krewinkel | 
|---|---|
| License | MIT | 
| Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> | 
| Stability | beta | 
| Portability | non-portable (depends on GHC) | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
HsLua.Core.Types
Description
The core Lua types, including mappings of Lua types to Haskell.
This module has mostly been moved to 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, CInt, 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
Constructors
| Lua | |
| Fields 
 | |
Instances
| MonadReader LuaEnvironment (LuaE e) Source # | |
| 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 # | |
| 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.
Constructors
| LuaEnvironment | |
| Fields 
 | |
Instances
| MonadReader LuaEnvironment (LuaE e) Source # | |
| 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 # | |
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 loadNULL 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.
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
| Eq GCControl Source # | |
| Ord GCControl Source # | |
| Show GCControl Source # | |
toGCdata :: GCControl -> (CInt, CInt, CInt) Source #
Returns the data value associated with a GCControl command.
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 | 
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, 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.
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 CIntFalse0, True
Instances
| Eq LuaBool | |
| Show LuaBool | |
| Storable LuaBool | |
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 | |
| Eq Integer | |
| Integral Integer | |
| Defined in Lua.Types | |
| Num Integer | |
| Ord Integer | |
| Read Integer | |
| Real Integer | |
| Defined in Lua.Types Methods toRational :: Integer -> Rational # | |
| Show Integer | |
The type of floats in Lua.
By default this type is DoubleLUA_FLOAT_TYPE in
 luaconf.h.)
See lua_Number.
Instances
| Eq Number | |
| Floating Number | |
| Fractional Number | |
| Num Number | |
| Ord Number | |
| Read Number | |
| Real Number | |
| Defined in Lua.Types Methods toRational :: Number -> Rational # | |
| 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 # | |
| RealFrac Number | |
| Show Number | |
newtype StackIndex #
A stack index
Constructors
| StackIndex | |
| Fields | |
Instances
registryindex :: StackIndex Source #
Pseudo stack index of the Lua registry.
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
| Eq NumResults | |
| Defined in Lua.Types | |
| 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 # | |
| 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 # | |
| Show NumResults | |
| Defined in Lua.Types Methods 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.
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
| Eq RelationalOperator Source # | |
| Defined in HsLua.Core.Types Methods (==) :: RelationalOperator -> RelationalOperator -> Bool # (/=) :: RelationalOperator -> RelationalOperator -> Bool # | |
| Ord RelationalOperator Source # | |
| 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 # | |
| Show RelationalOperator Source # | |
| Defined in HsLua.Core.Types Methods 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.
Constructors
| Name | |
| Fields | |