Copyright | © 2007–2012 Gracjan Polak 2012–2016 Ömer Sinan Ağacan 2017-2020 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.
Synopsis
- newtype Lua a = Lua {
- unLua :: ReaderT LuaEnvironment IO a
- data LuaEnvironment = LuaEnvironment {}
- data ErrorConversion = ErrorConversion {
- errorToException :: forall a. State -> IO a
- addContextToException :: forall a. String -> Lua a -> Lua a
- alternative :: forall a. Lua a -> Lua a -> Lua a
- exceptionToError :: Lua NumResults -> Lua NumResults
- errorConversion :: Lua ErrorConversion
- newtype State = State (Ptr ())
- type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar))
- liftLua :: (State -> IO a) -> Lua a
- liftLua1 :: (State -> a -> IO b) -> a -> Lua b
- state :: Lua State
- runWithConverter :: ErrorConversion -> State -> Lua a -> IO a
- unsafeRunWith :: State -> Lua a -> IO a
- unsafeErrorConversion :: ErrorConversion
- data GCCONTROL
- data Type
- newtype TypeCode = TypeCode {
- fromTypeCode :: CInt
- fromType :: Type -> TypeCode
- toType :: TypeCode -> Type
- liftIO :: MonadIO m => IO a -> m a
- type CFunction = FunPtr (State -> IO NumResults)
- newtype LuaBool = LuaBool CInt
- false :: LuaBool
- true :: LuaBool
- fromLuaBool :: LuaBool -> Bool
- toLuaBool :: Bool -> LuaBool
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype StackIndex = StackIndex {}
- nthFromBottom :: CInt -> StackIndex
- nthFromTop :: CInt -> StackIndex
- stackTop :: StackIndex
- stackBottom :: StackIndex
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {}
- data RelationalOperator
- fromRelationalOperator :: RelationalOperator -> CInt
- data Status
- newtype StatusCode = StatusCode CInt
- toStatus :: StatusCode -> Status
- data Reference
- fromReference :: Reference -> CInt
- toReference :: CInt -> Reference
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
Monad Lua Source # | |
Functor Lua Source # | |
Applicative Lua Source # | |
MonadIO Lua Source # | |
Defined in Foreign.Lua.Core.Types | |
Alternative Lua Source # | |
MonadThrow Lua Source # | |
Defined in Foreign.Lua.Core.Types | |
MonadCatch Lua Source # | |
MonadMask Lua Source # | |
ToHaskellFunction HaskellFunction Source # | |
Defined in Foreign.Lua.FunctionCalling toHsFun :: StackIndex -> HaskellFunction -> Lua NumResults Source # | |
MonadReader LuaEnvironment Lua Source # | |
Defined in Foreign.Lua.Core.Types ask :: Lua LuaEnvironment # local :: (LuaEnvironment -> LuaEnvironment) -> Lua a -> Lua a # reader :: (LuaEnvironment -> a) -> Lua a # | |
Peekable a => LuaCallFunc (Lua a) Source # | |
Pushable a => ToHaskellFunction (Lua a) Source # | |
Defined in Foreign.Lua.FunctionCalling toHsFun :: StackIndex -> Lua a -> Lua NumResults Source # |
data LuaEnvironment Source #
Environment in which Lua computations are evaluated.
LuaEnvironment | |
|
Instances
MonadReader LuaEnvironment Lua Source # | |
Defined in Foreign.Lua.Core.Types ask :: Lua LuaEnvironment # local :: (LuaEnvironment -> LuaEnvironment) -> Lua a -> Lua a # reader :: (LuaEnvironment -> a) -> Lua a # |
data ErrorConversion Source #
Define the ways in which exceptions and errors are handled.
ErrorConversion | |
|
errorConversion :: Lua ErrorConversion Source #
Get the error-to-exception function.
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)) Source #
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) -> Lua a Source #
Turn a function of typ Lua.State -> IO a
into a monadic Lua operation.
liftLua1 :: (State -> a -> IO b) -> a -> Lua b Source #
Turn a function of typ Lua.State -> a -> IO b
into a monadic Lua operation.
runWithConverter :: ErrorConversion -> State -> Lua a -> IO a Source #
Run Lua computation with the given Lua state and error-to-exception converter. Any resulting exceptions are left unhandled.
unsafeRunWith :: State -> Lua a -> IO a Source #
Run the given operation, but crash if any Haskell exceptions occur.
unsafeErrorConversion :: ErrorConversion Source #
Unsafe
; no proper error handling is attempted,
any error leads to a crash.ErrorConversion
Enumeration used by gc
function.
Instances
Enum GCCONTROL Source # | |
Defined in Foreign.Lua.Core.Types succ :: GCCONTROL -> GCCONTROL # pred :: GCCONTROL -> GCCONTROL # fromEnum :: GCCONTROL -> Int # enumFrom :: GCCONTROL -> [GCCONTROL] # enumFromThen :: GCCONTROL -> GCCONTROL -> [GCCONTROL] # enumFromTo :: GCCONTROL -> GCCONTROL -> [GCCONTROL] # enumFromThenTo :: GCCONTROL -> GCCONTROL -> GCCONTROL -> [GCCONTROL] # | |
Eq GCCONTROL Source # | |
Ord GCCONTROL Source # | |
Defined in Foreign.Lua.Core.Types | |
Show GCCONTROL Source # | |
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 |
Integer code used to encode the type of a lua value.
fromType :: Type -> TypeCode Source #
Convert a lua Type to a type code which can be passed to the C API.
type CFunction = FunPtr (State -> IO NumResults) Source #
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
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.gettop
See lua_CFunction.
Boolean value returned by a Lua C API function. This is a
and
interpreted as CInt
iff the value is False
0
,
otherwise.True
Instances
Eq LuaBool Source # | |
Show LuaBool Source # | |
Storable LuaBool Source # | |
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 Source # | |
Enum Integer Source # | |
Eq Integer Source # | |
Integral Integer Source # | |
Defined in Foreign.Lua.Core.Types | |
Num Integer Source # | |
Ord Integer Source # | |
Real Integer Source # | |
Defined in Foreign.Lua.Core.Types toRational :: Integer -> Rational # | |
Show Integer Source # | |
Pushable Integer Source # | |
Peekable Integer Source # | |
Defined in Foreign.Lua.Types.Peekable |
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 Source # | |
Floating Number Source # | |
Fractional Number Source # | |
Num Number Source # | |
Ord Number Source # | |
Real Number Source # | |
Defined in Foreign.Lua.Core.Types toRational :: Number -> Rational # | |
RealFloat Number Source # | |
Defined in Foreign.Lua.Core.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 Source # | |
Show Number Source # | |
Pushable Number Source # | |
Peekable Number Source # | |
Defined in Foreign.Lua.Types.Peekable |
newtype StackIndex Source #
A stack index
Instances
nthFromBottom :: CInt -> StackIndex Source #
Stack index of the nth element from the bottom of the stack.
nthFromTop :: CInt -> StackIndex Source #
Stack index of the nth element from the top of the stack.
stackTop :: StackIndex Source #
Top of the stack
stackBottom :: StackIndex Source #
Bottom of the stack
The number of arguments expected a function.
newtype NumResults Source #
The number of results returned by a function call.
Instances
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 Foreign.Lua.Core.Types (==) :: RelationalOperator -> RelationalOperator -> Bool # (/=) :: RelationalOperator -> RelationalOperator -> Bool # | |
Ord RelationalOperator Source # | |
Defined in Foreign.Lua.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 Foreign.Lua.Core.Types showsPrec :: Int -> RelationalOperator -> ShowS # show :: RelationalOperator -> String # showList :: [RelationalOperator] -> ShowS # |
fromRelationalOperator :: RelationalOperator -> CInt Source #
Convert relation operator to its C representation.
Lua status values.
newtype StatusCode Source #
Integer code used to signal the status of a thread or computation.
See
.Status
Instances
Eq StatusCode Source # | |
Defined in Foreign.Lua.Core.Types (==) :: StatusCode -> StatusCode -> Bool # (/=) :: StatusCode -> StatusCode -> Bool # |
References
fromReference :: Reference -> CInt Source #
Convert a reference to its C representation.
toReference :: CInt -> Reference Source #
Create a reference from its C representation.