hslua-1.1.0: Bindings to Lua, an embeddable scripting language
Copyright© 2007–2012 Gracjan Polak
2012–2016 Ömer Sinan Ağacan
2017-2020 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb+hslua@zeitkraut.de>
Stabilitybeta
Portabilitynon-portable (depends on GHC)
Safe HaskellNone
LanguageHaskell2010

Foreign.Lua.Core.Types

Contents

Description

The core Lua types, including mappings of Lua types to Haskell.

Synopsis

Documentation

newtype Lua a #

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

Instances details
Monad Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(>>=) :: Lua a -> (a -> Lua b) -> Lua b

(>>) :: Lua a -> Lua b -> Lua b

return :: a -> Lua a

Functor Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

fmap :: (a -> b) -> Lua a -> Lua b

(<$) :: a -> Lua b -> Lua a

Applicative Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

pure :: a -> Lua a

(<*>) :: Lua (a -> b) -> Lua a -> Lua b

liftA2 :: (a -> b -> c) -> Lua a -> Lua b -> Lua c

(*>) :: Lua a -> Lua b -> Lua b

(<*) :: Lua a -> Lua b -> Lua a

MonadCatch Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

catch :: Exception e => Lua a -> (e -> Lua a) -> Lua a

MonadMask Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

mask :: ((forall a. Lua a -> Lua a) -> Lua b) -> Lua b

uninterruptibleMask :: ((forall a. Lua a -> Lua a) -> Lua b) -> Lua b

generalBracket :: Lua a -> (a -> ExitCase b -> Lua c) -> (a -> Lua b) -> Lua (b, c)

MonadThrow Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

throwM :: Exception e => e -> Lua a

MonadIO Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

liftIO :: IO a -> Lua a #

Alternative Lua 
Instance details

Defined in Foreign.Lua.Core.Error

Methods

empty :: Lua a

(<|>) :: Lua a -> Lua a -> Lua a

some :: Lua a -> Lua [a]

many :: Lua a -> Lua [a]

ToHaskellFunction HaskellFunction # 
Instance details

Defined in Foreign.Lua.FunctionCalling

MonadReader LuaEnvironment Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

Peekable a => LuaCallFunc (Lua a) # 
Instance details

Defined in Foreign.Lua.FunctionCalling

Methods

callFunc' :: String -> Lua () -> NumArgs -> Lua a #

Pushable a => ToHaskellFunction (Lua a) # 
Instance details

Defined in Foreign.Lua.FunctionCalling

Methods

toHsFun :: StackIndex -> Lua a -> Lua NumResults #

data LuaEnvironment #

Environment in which Lua computations are evaluated.

Constructors

LuaEnvironment 

Fields

Instances

Instances details
MonadReader LuaEnvironment Lua # 
Instance details

Defined in Foreign.Lua.Core.Types

data ErrorConversion #

Define the ways in which exceptions and errors are handled.

Constructors

ErrorConversion 

Fields

errorConversion :: Lua ErrorConversion #

Get the error-to-exception function.

newtype State #

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.

Constructors

State (Ptr ()) 

Instances

Instances details
Eq State # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: State -> State -> Bool

(/=) :: State -> State -> Bool

Generic State # 
Instance details

Defined in Foreign.Lua.Core.Types

Associated Types

type Rep State :: Type -> Type

Methods

from :: State -> Rep State x

to :: Rep State x -> State

Pushable CFunction # 
Instance details

Defined in Foreign.Lua.Types.Pushable

Methods

push :: CFunction -> Lua () #

Peekable CFunction # 
Instance details

Defined in Foreign.Lua.Types.Peekable

Peekable State # 
Instance details

Defined in Foreign.Lua.Types.Peekable

Methods

peek :: StackIndex -> Lua State #

type Rep State # 
Instance details

Defined in Foreign.Lua.Core.Types

type Rep State = D1 ('MetaData "State" "Foreign.Lua.Core.Types" "hslua-1.1.0-4JmH6d3JbRqDpFMeZ2axlL" 'True) (C1 ('MetaCons "State" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr ()))))

type Reader = FunPtr (State -> Ptr () -> Ptr CSize -> IO (Ptr CChar)) #

The reader function used by lua_load. 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 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 #

Turn a function of typ Lua.State -> IO a into a monadic Lua operation.

liftLua1 :: (State -> a -> IO b) -> a -> Lua b #

Turn a function of typ Lua.State -> a -> IO b into a monadic Lua operation.

state :: Lua State #

Get the Lua state of this Lua computation.

runWithConverter :: ErrorConversion -> State -> Lua a -> IO a #

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 #

Run the given operation, but crash if any Haskell exceptions occur.

unsafeErrorConversion :: ErrorConversion #

Unsafe ErrorConversion; no proper error handling is attempted, any error leads to a crash.

data GCCONTROL #

Enumeration used by gc function.

Instances

Instances details
Enum GCCONTROL # 
Instance details

Defined in Foreign.Lua.Core.Types

Eq GCCONTROL # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: GCCONTROL -> GCCONTROL -> Bool

(/=) :: GCCONTROL -> GCCONTROL -> Bool

Ord GCCONTROL # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: GCCONTROL -> GCCONTROL -> Ordering

(<) :: GCCONTROL -> GCCONTROL -> Bool

(<=) :: GCCONTROL -> GCCONTROL -> Bool

(>) :: GCCONTROL -> GCCONTROL -> Bool

(>=) :: GCCONTROL -> GCCONTROL -> Bool

max :: GCCONTROL -> GCCONTROL -> GCCONTROL

min :: GCCONTROL -> GCCONTROL -> GCCONTROL

Show GCCONTROL # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> GCCONTROL -> ShowS

show :: GCCONTROL -> String

showList :: [GCCONTROL] -> ShowS

data Type #

Enumeration used as type tag. See lua_type.

Constructors

TypeNone

non-valid stack index

TypeNil

type of lua's nil value

TypeBoolean

type of lua booleans

TypeLightUserdata

type of light userdata

TypeNumber

type of lua numbers. See Number

TypeString

type of lua string values

TypeTable

type of lua tables

TypeFunction

type of functions, either normal or CFunction

TypeUserdata

type of full user data

TypeThread

type of lua threads

Instances

Instances details
Bounded Type # 
Instance details

Defined in Foreign.Lua.Core.Types

Enum Type # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

succ :: Type -> Type

pred :: Type -> Type

toEnum :: Int -> Type

fromEnum :: Type -> Int

enumFrom :: Type -> [Type]

enumFromThen :: Type -> Type -> [Type]

enumFromTo :: Type -> Type -> [Type]

enumFromThenTo :: Type -> Type -> Type -> [Type]

Eq Type # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: Type -> Type -> Bool

(/=) :: Type -> Type -> Bool

Ord Type # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: Type -> Type -> Ordering

(<) :: Type -> Type -> Bool

(<=) :: Type -> Type -> Bool

(>) :: Type -> Type -> Bool

(>=) :: Type -> Type -> Bool

max :: Type -> Type -> Type

min :: Type -> Type -> Type

Show Type # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> Type -> ShowS

show :: Type -> String

showList :: [Type] -> ShowS

newtype TypeCode #

Integer code used to encode the type of a lua value.

Constructors

TypeCode 

Fields

Instances

Instances details
Eq TypeCode # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: TypeCode -> TypeCode -> Bool

(/=) :: TypeCode -> TypeCode -> Bool

Ord TypeCode # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: TypeCode -> TypeCode -> Ordering

(<) :: TypeCode -> TypeCode -> Bool

(<=) :: TypeCode -> TypeCode -> Bool

(>) :: TypeCode -> TypeCode -> Bool

(>=) :: TypeCode -> TypeCode -> Bool

max :: TypeCode -> TypeCode -> TypeCode

min :: TypeCode -> TypeCode -> TypeCode

Show TypeCode # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> TypeCode -> ShowS

show :: TypeCode -> String

showList :: [TypeCode] -> ShowS

fromType :: Type -> TypeCode #

Convert a lua Type to a type code which can be passed to the C API.

toType :: TypeCode -> Type #

Convert numerical code to lua type.

liftIO :: MonadIO m => IO a -> m a #

type CFunction = FunPtr (State -> IO NumResults) #

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, gettop 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.

See lua_CFunction.

newtype LuaBool #

Boolean value returned by a Lua C API function. This is a CInt and interpreted as False iff the value is 0, True otherwise.

Constructors

LuaBool CInt 

Instances

Instances details
Eq LuaBool # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: LuaBool -> LuaBool -> Bool

(/=) :: LuaBool -> LuaBool -> Bool

Show LuaBool # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> LuaBool -> ShowS

show :: LuaBool -> String

showList :: [LuaBool] -> ShowS

Storable LuaBool # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

sizeOf :: LuaBool -> Int

alignment :: LuaBool -> Int

peekElemOff :: Ptr LuaBool -> Int -> IO LuaBool

pokeElemOff :: Ptr LuaBool -> Int -> LuaBool -> IO ()

peekByteOff :: Ptr b -> Int -> IO LuaBool

pokeByteOff :: Ptr b -> Int -> LuaBool -> IO ()

peek :: Ptr LuaBool -> IO LuaBool

poke :: Ptr LuaBool -> LuaBool -> IO ()

false :: LuaBool #

Lua representation of the value interpreted as false.

true :: LuaBool #

Generic Lua representation of a value interpreted as being true.

fromLuaBool :: LuaBool -> Bool #

Convert a LuaBool to a Haskell Bool.

toLuaBool :: Bool -> LuaBool #

Convert a Haskell Bool to a LuaBool.

newtype Integer #

The type of integers in Lua.

By default this type is Int64, but that can be changed to different values in lua. (See LUA_INT_TYPE in luaconf.h.)

See lua_Integer.

Constructors

Integer Int64 

Instances

Instances details
Bounded Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Enum Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Eq Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: Integer -> Integer -> Bool

(/=) :: Integer -> Integer -> Bool

Integral Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Num Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Ord Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: Integer -> Integer -> Ordering

(<) :: Integer -> Integer -> Bool

(<=) :: Integer -> Integer -> Bool

(>) :: Integer -> Integer -> Bool

(>=) :: Integer -> Integer -> Bool

max :: Integer -> Integer -> Integer

min :: Integer -> Integer -> Integer

Real Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

toRational :: Integer -> Rational

Show Integer # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> Integer -> ShowS

show :: Integer -> String

showList :: [Integer] -> ShowS

Pushable Integer # 
Instance details

Defined in Foreign.Lua.Types.Pushable

Methods

push :: Integer -> Lua () #

Peekable Integer # 
Instance details

Defined in Foreign.Lua.Types.Peekable

Methods

peek :: StackIndex -> Lua Integer #

newtype Number #

The type of floats in Lua.

By default this type is Double, but that can be changed in Lua to a single float or a long double. (See LUA_FLOAT_TYPE in luaconf.h.)

See lua_Number.

Constructors

Number Double 

Instances

Instances details
Eq Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: Number -> Number -> Bool

(/=) :: Number -> Number -> Bool

Floating Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Fractional Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(/) :: Number -> Number -> Number

recip :: Number -> Number

fromRational :: Rational -> Number

Num Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Ord Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: Number -> Number -> Ordering

(<) :: Number -> Number -> Bool

(<=) :: Number -> Number -> Bool

(>) :: Number -> Number -> Bool

(>=) :: Number -> Number -> Bool

max :: Number -> Number -> Number

min :: Number -> Number -> Number

Real Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

toRational :: Number -> Rational

RealFloat Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

floatRadix :: Number -> Integer

floatDigits :: Number -> Int

floatRange :: Number -> (Int, Int)

decodeFloat :: Number -> (Integer, Int)

encodeFloat :: Integer -> Int -> Number

exponent :: Number -> Int

significand :: Number -> Number

scaleFloat :: Int -> Number -> Number

isNaN :: Number -> Bool

isInfinite :: Number -> Bool

isDenormalized :: Number -> Bool

isNegativeZero :: Number -> Bool

isIEEE :: Number -> Bool

atan2 :: Number -> Number -> Number

RealFrac Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

properFraction :: Integral b => Number -> (b, Number)

truncate :: Integral b => Number -> b

round :: Integral b => Number -> b

ceiling :: Integral b => Number -> b

floor :: Integral b => Number -> b

Show Number # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> Number -> ShowS

show :: Number -> String

showList :: [Number] -> ShowS

Pushable Number # 
Instance details

Defined in Foreign.Lua.Types.Pushable

Methods

push :: Number -> Lua () #

Peekable Number # 
Instance details

Defined in Foreign.Lua.Types.Peekable

Methods

peek :: StackIndex -> Lua Number #

newtype StackIndex #

A stack index

Constructors

StackIndex 

Fields

Instances

Instances details
Enum StackIndex # 
Instance details

Defined in Foreign.Lua.Core.Types

Eq StackIndex # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: StackIndex -> StackIndex -> Bool

(/=) :: StackIndex -> StackIndex -> Bool

Num StackIndex # 
Instance details

Defined in Foreign.Lua.Core.Types

Ord StackIndex # 
Instance details

Defined in Foreign.Lua.Core.Types

Show StackIndex # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> StackIndex -> ShowS

show :: StackIndex -> String

showList :: [StackIndex] -> ShowS

nthFromBottom :: CInt -> StackIndex #

Stack index of the nth element from the bottom of the stack.

nthFromTop :: CInt -> StackIndex #

Stack index of the nth element from the top of the stack.

stackTop :: StackIndex #

Top of the stack

stackBottom :: StackIndex #

Bottom of the stack

newtype NumArgs #

The number of arguments expected a function.

Constructors

NumArgs 

Fields

Instances

Instances details
Eq NumArgs # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: NumArgs -> NumArgs -> Bool

(/=) :: NumArgs -> NumArgs -> Bool

Num NumArgs # 
Instance details

Defined in Foreign.Lua.Core.Types

Ord NumArgs # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

compare :: NumArgs -> NumArgs -> Ordering

(<) :: NumArgs -> NumArgs -> Bool

(<=) :: NumArgs -> NumArgs -> Bool

(>) :: NumArgs -> NumArgs -> Bool

(>=) :: NumArgs -> NumArgs -> Bool

max :: NumArgs -> NumArgs -> NumArgs

min :: NumArgs -> NumArgs -> NumArgs

Show NumArgs # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> NumArgs -> ShowS

show :: NumArgs -> String

showList :: [NumArgs] -> ShowS

newtype NumResults #

The number of results returned by a function call.

Constructors

NumResults 

Fields

Instances

Instances details
Eq NumResults # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: NumResults -> NumResults -> Bool

(/=) :: NumResults -> NumResults -> Bool

Num NumResults # 
Instance details

Defined in Foreign.Lua.Core.Types

Ord NumResults # 
Instance details

Defined in Foreign.Lua.Core.Types

Show NumResults # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> NumResults -> ShowS

show :: NumResults -> String

showList :: [NumResults] -> ShowS

Pushable CFunction # 
Instance details

Defined in Foreign.Lua.Types.Pushable

Methods

push :: CFunction -> Lua () #

Peekable CFunction # 
Instance details

Defined in Foreign.Lua.Types.Peekable

ToHaskellFunction HaskellFunction # 
Instance details

Defined in Foreign.Lua.FunctionCalling

data RelationalOperator #

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

fromRelationalOperator :: RelationalOperator -> CInt #

Convert relation operator to its C representation.

data Status #

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.

ErrGcmm

error while running a __gc metamethod.

ErrFile

opening or reading a file failed.

Instances

Instances details
Eq Status # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: Status -> Status -> Bool

(/=) :: Status -> Status -> Bool

Show Status # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> Status -> ShowS

show :: Status -> String

showList :: [Status] -> ShowS

newtype StatusCode #

Integer code used to signal the status of a thread or computation. See Status.

Constructors

StatusCode CInt 

Instances

Instances details
Eq StatusCode # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: StatusCode -> StatusCode -> Bool

(/=) :: StatusCode -> StatusCode -> Bool

toStatus :: StatusCode -> Status #

Convert C integer constant to LuaStatus.

References

data Reference #

Reference to a stored value.

Constructors

Reference CInt

Reference to a stored value

RefNil

Reference to a nil value

Instances

Instances details
Eq Reference # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

(==) :: Reference -> Reference -> Bool

(/=) :: Reference -> Reference -> Bool

Show Reference # 
Instance details

Defined in Foreign.Lua.Core.Types

Methods

showsPrec :: Int -> Reference -> ShowS

show :: Reference -> String

showList :: [Reference] -> ShowS

fromReference :: Reference -> CInt #

Convert a reference to its C representation.

toReference :: CInt -> Reference #

Create a reference from its C representation.