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 |
The core Lua types, including mappings of Lua types to Haskell.
Synopsis
- newtype State = State (Ptr ())
- type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar))
- newtype TypeCode = TypeCode {
- fromTypeCode :: CInt
- type CFunction = FunPtr PreCFunction
- type PreCFunction = State -> IO NumResults
- type WarnFunction = FunPtr (Ptr () -> CString -> LuaBool -> IO ())
- type PreWarnFunction = Ptr () -> CString -> LuaBool -> IO ()
- newtype LuaBool = LuaBool CInt
- newtype Integer = Integer Int64
- newtype Number = Number Double
- newtype StackIndex = StackIndex {}
- newtype NumArgs = NumArgs {
- fromNumArgs :: CInt
- newtype NumResults = NumResults {}
- newtype OPCode = OPCode CInt
- newtype ArithOPCode = ArithOPCode CInt
- newtype StatusCode = StatusCode CInt
- newtype GCCode = GCCode CInt
Documentation
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.
Integer code used to encode the type of a Lua value.
type CFunction = FunPtr PreCFunction 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
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 Source #
Type of Haskell functions that can be turned into C functions.
This is the same as a dereferenced CFunction
.
type WarnFunction = FunPtr (Ptr () -> CString -> LuaBool -> IO ()) Source #
The type of warning functions, called by Lua to emit warnings. The
first parameter is an opaque pointer set by lua_setwarnf
. The
second parameter is the warning message. The third parameter is a
boolean that indicates whether the message is to be continued by the
message in the next call.
See warn for more details about warnings.
type PreWarnFunction = Ptr () -> CString -> LuaBool -> IO () Source #
Type of Haskell functions that can be turned into a WarnFunction.
This is the same as a dereferenced WarnFunction
.
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
Storable LuaBool Source # | |
Show LuaBool Source # | |
Eq 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 # | |
Num Integer Source # | |
Read Integer Source # | |
Integral Integer Source # | |
Defined in Lua.Types | |
Real Integer Source # | |
Defined in Lua.Types toRational :: Integer -> Rational # | |
Show Integer Source # | |
Eq Integer Source # | |
Ord Integer Source # | |
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
Floating Number Source # | |
RealFloat Number Source # | |
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 # | |
Num Number Source # | |
Read Number Source # | |
Fractional Number Source # | |
Real Number Source # | |
Defined in Lua.Types toRational :: Number -> Rational # | |
RealFrac Number Source # | |
Show Number Source # | |
Eq Number Source # | |
Ord Number Source # | |
newtype StackIndex Source #
A stack index
Instances
The number of arguments consumed curing a function call.
newtype NumResults Source #
The number of results returned by a function call.
Instances
Num NumResults Source # | |
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 # | |
Show NumResults Source # | |
Defined in Lua.Types showsPrec :: Int -> NumResults -> ShowS # show :: NumResults -> String # showList :: [NumResults] -> ShowS # | |
Eq NumResults Source # | |
Defined in Lua.Types (==) :: NumResults -> NumResults -> Bool # (/=) :: NumResults -> NumResults -> Bool # | |
Ord NumResults Source # | |
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 # |
Relational operator code.
Instances
Storable OPCode Source # | |
Show OPCode Source # | |
Eq OPCode Source # | |
newtype ArithOPCode Source #
Arithmetic operator code.
Instances
Storable ArithOPCode Source # | |
Defined in Lua.Types sizeOf :: ArithOPCode -> Int # alignment :: ArithOPCode -> Int # peekElemOff :: Ptr ArithOPCode -> Int -> IO ArithOPCode # pokeElemOff :: Ptr ArithOPCode -> Int -> ArithOPCode -> IO () # peekByteOff :: Ptr b -> Int -> IO ArithOPCode # pokeByteOff :: Ptr b -> Int -> ArithOPCode -> IO () # peek :: Ptr ArithOPCode -> IO ArithOPCode # poke :: Ptr ArithOPCode -> ArithOPCode -> IO () # | |
Show ArithOPCode Source # | |
Defined in Lua.Types showsPrec :: Int -> ArithOPCode -> ShowS # show :: ArithOPCode -> String # showList :: [ArithOPCode] -> ShowS # | |
Eq ArithOPCode Source # | |
Defined in Lua.Types (==) :: ArithOPCode -> ArithOPCode -> Bool # (/=) :: ArithOPCode -> ArithOPCode -> Bool # |
newtype StatusCode Source #
Integer code used to signal the status of a thread or computation.
Instances
Storable StatusCode Source # | |
Defined in Lua.Types sizeOf :: StatusCode -> Int # alignment :: StatusCode -> Int # peekElemOff :: Ptr StatusCode -> Int -> IO StatusCode # pokeElemOff :: Ptr StatusCode -> Int -> StatusCode -> IO () # peekByteOff :: Ptr b -> Int -> IO StatusCode # pokeByteOff :: Ptr b -> Int -> StatusCode -> IO () # peek :: Ptr StatusCode -> IO StatusCode # poke :: Ptr StatusCode -> StatusCode -> IO () # | |
Show StatusCode Source # | |
Defined in Lua.Types showsPrec :: Int -> StatusCode -> ShowS # show :: StatusCode -> String # showList :: [StatusCode] -> ShowS # | |
Eq StatusCode Source # | |
Defined in Lua.Types (==) :: StatusCode -> StatusCode -> Bool # (/=) :: StatusCode -> StatusCode -> Bool # |
Garbage-Collection
Garbage-collection options.
Instances
Storable GCCode Source # | |
Show GCCode Source # | |
Eq GCCode Source # | |