Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2023 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb@hslua.org> |
Stability | beta |
Portability | non-portable (depends on GHC) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
HsLua.Core.Types
Description
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, 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 Source # local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a Source # reader :: (LuaEnvironment -> a) -> LuaE e a Source # | |
LuaError e => MonadFail (LuaE e) Source # | |
MonadIO (LuaE e) Source # | |
LuaError e => Alternative (LuaE e) Source # | |
Applicative (LuaE e) Source # | |
Functor (LuaE e) Source # | |
Monad (LuaE e) Source # | |
MonadCatch (LuaE e) Source # | |
MonadMask (LuaE e) Source # | |
Defined in HsLua.Core.Types | |
MonadThrow (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 Source # local :: (LuaEnvironment -> LuaEnvironment) -> LuaE e a -> LuaE e a Source # reader :: (LuaEnvironment -> a) -> LuaE e a Source # |
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.
This function is identical to runWith
; it exists for backwards
compatibility.
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 Source # | |
Eq GCControl Source # | |
Ord GCControl Source # | |
Defined in HsLua.Core.Types |
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 |
Instances
Bounded Type Source # | |
Enum Type Source # | |
Read Type Source # | |
Show Type Source # | |
Eq Type Source # | |
Ord Type Source # | |
fromType :: Type -> TypeCode Source #
Convert a Lua Type
to a type code which can be passed to the C
API.
liftIO :: MonadIO m => IO a -> m a Source #
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
, we would have ended up with this error: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
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
type CFunction = FunPtr PreCFunction #
type PreCFunction = State -> IO NumResults #
type HaskellFunction e = LuaE e NumResults Source #
Haskell function that can be called from Lua.
The HsLua equivallent of a PreCFunction
.
Instances
Storable LuaBool | |
Defined in Lua.Types Methods sizeOf :: LuaBool -> Int Source # alignment :: LuaBool -> Int Source # peekElemOff :: Ptr LuaBool -> Int -> IO LuaBool Source # pokeElemOff :: Ptr LuaBool -> Int -> LuaBool -> IO () Source # peekByteOff :: Ptr b -> Int -> IO LuaBool Source # pokeByteOff :: Ptr b -> Int -> LuaBool -> IO () Source # | |
Show LuaBool | |
Eq LuaBool | |
Instances
Bounded Integer | |
Enum Integer | |
Defined in Lua.Types Methods succ :: Integer -> Integer Source # pred :: Integer -> Integer Source # toEnum :: Int -> Integer Source # fromEnum :: Integer -> Int Source # enumFrom :: Integer -> [Integer] Source # enumFromThen :: Integer -> Integer -> [Integer] Source # enumFromTo :: Integer -> Integer -> [Integer] Source # enumFromThenTo :: Integer -> Integer -> Integer -> [Integer] Source # | |
Num Integer | |
Defined in Lua.Types | |
Read Integer | |
Integral Integer | |
Defined in Lua.Types Methods quot :: Integer -> Integer -> Integer Source # rem :: Integer -> Integer -> Integer Source # div :: Integer -> Integer -> Integer Source # mod :: Integer -> Integer -> Integer Source # quotRem :: Integer -> Integer -> (Integer, Integer) Source # | |
Real Integer | |
Show Integer | |
Eq Integer | |
Ord Integer | |
Instances
newtype StackIndex #
Constructors
StackIndex | |
Fields |
Instances
registryindex :: StackIndex Source #
Pseudo stack index of the Lua registry.
Constructors
NumArgs | |
Fields
|
Instances
Num NumArgs | |
Defined in Lua.Types | |
Show NumArgs | |
Eq NumArgs | |
Ord NumArgs | |
newtype NumResults #
Constructors
NumResults | |
Fields |
Instances
Num NumResults | |
Defined in Lua.Types Methods (+) :: NumResults -> NumResults -> NumResults Source # (-) :: NumResults -> NumResults -> NumResults Source # (*) :: NumResults -> NumResults -> NumResults Source # negate :: NumResults -> NumResults Source # abs :: NumResults -> NumResults Source # signum :: NumResults -> NumResults Source # fromInteger :: Integer -> NumResults Source # | |
Show NumResults | |
Eq NumResults | |
Defined in Lua.Types Methods (==) :: NumResults -> NumResults -> Bool Source # (/=) :: NumResults -> NumResults -> Bool Source # | |
Ord NumResults | |
Defined in Lua.Types Methods compare :: NumResults -> NumResults -> Ordering Source # (<) :: NumResults -> NumResults -> Bool Source # (<=) :: NumResults -> NumResults -> Bool Source # (>) :: NumResults -> NumResults -> Bool Source # (>=) :: NumResults -> NumResults -> Bool Source # max :: NumResults -> NumResults -> NumResults Source # min :: NumResults -> NumResults -> NumResults Source # |
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
Show RelationalOperator Source # | |
Defined in HsLua.Core.Types | |
Eq RelationalOperator Source # | |
Defined in HsLua.Core.Types Methods (==) :: RelationalOperator -> RelationalOperator -> Bool Source # (/=) :: RelationalOperator -> RelationalOperator -> Bool Source # | |
Ord RelationalOperator Source # | |
Defined in HsLua.Core.Types Methods compare :: RelationalOperator -> RelationalOperator -> Ordering Source # (<) :: RelationalOperator -> RelationalOperator -> Bool Source # (<=) :: RelationalOperator -> RelationalOperator -> Bool Source # (>) :: RelationalOperator -> RelationalOperator -> Bool Source # (>=) :: RelationalOperator -> RelationalOperator -> Bool Source # max :: RelationalOperator -> RelationalOperator -> RelationalOperator Source # min :: RelationalOperator -> RelationalOperator -> RelationalOperator Source # |
fromRelationalOperator :: RelationalOperator -> OPCode Source #
Convert relation operator to its C representation.
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. |
References
fromReference :: Reference -> CInt #
toReference :: CInt -> Reference #
Stack index helpers
nthTop :: CInt -> StackIndex #
nthBottom :: CInt -> StackIndex #
nth :: CInt -> StackIndex #
top :: StackIndex #
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 |