hslua-packaging-2.3.0: Utilities to build Lua modules.
Copyright© 2020-2023 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb@hslua.org>
Safe HaskellSafe-Inferred
LanguageHaskell2010

HsLua.Packaging.UDType

Description

This module provides types and functions to use Haskell values as userdata objects in Lua. These objects wrap a Haskell value and provide methods and properties to interact with the Haskell value.

The terminology in this module refers to the userdata values as /UD objects, and to their type as UD type/.

Synopsis

Documentation

type DocumentedType e a = UDType e (DocumentedFunction e) a Source #

Type definitions containing documented functions.

type DocumentedTypeWithList e a itemtype = UDTypeWithList e (DocumentedFunction e) a itemtype Source #

A userdata type, capturing the behavior of Lua objects that wrap Haskell values. The type name must be unique; once the type has been used to push or retrieve a value, the behavior can no longer be modified through this type.

deftype Source #

Arguments

:: LuaError e 
=> Name

type name

-> [(Operation, DocumentedFunction e)]

operations

-> [Member e (DocumentedFunction e) a]

methods

-> DocumentedType e a 

Defines a new type, defining the behavior of objects in Lua. Note that the type name must be unique.

deftype' Source #

Arguments

:: LuaError e 
=> Name

type name

-> [(Operation, DocumentedFunction e)]

operations

-> [Member e (DocumentedFunction e) a]

methods

-> Maybe (ListSpec e a itemtype)

list access

-> DocumentedTypeWithList e a itemtype 

Defines a new type that could also be treated as a list; defines the behavior of objects in Lua. Note that the type name must be unique.

method :: DocumentedFunction e -> Member e (DocumentedFunction e) a Source #

Use a documented function as an object method.

property #

Arguments

:: LuaError e 
=> Name

property name

-> Text

property description

-> (Pusher e b, a -> b)

how to get the property value

-> (Peeker e b, a -> b -> a)

how to set a new property value

-> Member e fn a 

Declares a new read- and writable property.

property' #

Arguments

:: LuaError e 
=> Name

property name

-> TypeSpec

property type

-> Text

property description

-> (Pusher e b, a -> b)

how to get the property value

-> (Peeker e b, a -> b -> a)

how to set a new property value

-> Member e fn a 

Declares a new read- and writable typed property.

possibleProperty #

Arguments

:: LuaError e 
=> Name

property name

-> Text

property description

-> (Pusher e b, a -> Possible b)

how to get the property value

-> (Peeker e b, a -> b -> Possible a)

how to set a new property value

-> Member e fn a 

Declares a new read- and writable property which is not always available.

possibleProperty' #

Arguments

:: LuaError e 
=> Name

property name

-> TypeSpec

type of the property value

-> Text

property description

-> (Pusher e b, a -> Possible b)

how to get the property value

-> (Peeker e b, a -> b -> Possible a)

how to set a new property value

-> Member e fn a 

Declares a new read- and writable property which is not always available.

readonly #

Arguments

:: Name

property name

-> Text

property description

-> (Pusher e b, a -> b)

how to get the property value

-> Member e fn a 

Creates a read-only object property. Attempts to set the value will cause an error.

readonly' #

Arguments

:: Name

property name

-> TypeSpec

property type

-> Text

property description

-> (Pusher e b, a -> b)

how to get the property value

-> Member e fn a 

Creates a read-only object property. Attempts to set the value will cause an error.

alias #

Arguments

:: AliasIndex

property alias

-> Text

description

-> [AliasIndex]

sequence of nested properties

-> Member e fn a 

Define an alias for another, possibly nested, property.

operation Source #

Arguments

:: Operation

the kind of operation

-> DocumentedFunction e

function used to perform the operation

-> (Operation, DocumentedFunction e) 

Declares a new object operation from a documented function.

peekUD :: LuaError e => DocumentedTypeWithList e a itemtype -> Peeker e a Source #

Retrieves a userdata value of the given type.

pushUD :: LuaError e => DocumentedTypeWithList e a itemtype -> a -> LuaE e () Source #

Pushes a userdata value of the given type.

initType :: LuaError e => DocumentedTypeWithList e a itemtype -> LuaE e Name Source #

Ensures that the type has been fully initialized, i.e., that all metatables have been created and stored in the registry. Returns the name of the initialized type.

udparam Source #

Arguments

:: LuaError e 
=> DocumentedTypeWithList e a itemtype

expected type

-> Text

parameter name

-> Text

parameter description

-> Parameter e a 

Defines a function parameter that takes the given type.

udresult Source #

Arguments

:: LuaError e 
=> DocumentedTypeWithList e a itemtype

result type

-> Text

result description

-> FunctionResults e a 

Defines a function result of the given type.

udDocs :: UDTypeWithList e fn a itemtype -> TypeDocs #

Returns documentation for this type.

udTypeSpec :: UDTypeWithList e fn a itemtype -> TypeSpec #

Type specifier for a UDType

Helper types for building

data Member e fn a #

A type member, either a method or a variable.

data Operation #

Lua metadata operation types.

Constructors

Add

the addition (+) operation. If any operand for an addition is not a number (nor a string coercible to a number), Lua will try to call a metamethod. First, Lua will check the first operand (even if it is valid). If that operand does not define a metamethod for __add, then Lua will check the second operand. If Lua can find a metamethod, it calls the metamethod with the two operands as arguments, and the result of the call (adjusted to one value) is the result of the operation. Otherwise, it raises an error.

Sub

the subtraction (-) operation. Behavior similar to the addition operation.

Mul

the multiplication (*) operation. Behavior similar to the addition operation.

Div

the division (/) operation. Behavior similar to the addition operation.

Mod

the modulo (%) operation. Behavior similar to the addition operation.

Pow

the exponentiation (^) operation. Behavior similar to the addition operation.

Unm

the negation (unary -) operation. Behavior similar to the addition operation.

Idiv

the floor division (//) operation. Behavior similar to the addition operation.

Band

the bitwise AND (&) operation. Behavior similar to the addition operation, except that Lua will try a metamethod if any operand is neither an integer nor a value coercible to an integer (see §3.4.3).

Bor

the bitwise OR (|) operation. Behavior similar to the bitwise AND operation.

Bxor

the bitwise exclusive OR (binary ~) operation. Behavior similar to the bitwise AND operation.

Bnot

the bitwise NOT (unary ~) operation. Behavior similar to the bitwise AND operation.

Shl

the bitwise left shift (<<) operation. Behavior similar to the bitwise AND operation.

Shr

the bitwise right shift (>>) operation. Behavior similar to the bitwise AND operation.

Concat

the concatenation (..) operation. Behavior similar to the addition operation, except that Lua will try a metamethod if any operand is neither a string nor a number (which is always coercible to a string).

Len

the length (#) operation. If the object is not a string, Lua will try its metamethod. If there is a metamethod, Lua calls it with the object as argument, and the result of the call (always adjusted to one value) is the result of the operation. If there is no metamethod but the object is a table, then Lua uses the table length operation (see §3.4.7). Otherwise, Lua raises an error.

Eq

the equal (==) operation. Behavior similar to the addition operation, except that Lua will try a metamethod only when the values being compared are either both tables or both full userdata and they are not primitively equal. The result of the call is always converted to a boolean.

Lt

the less than (<) operation. Behavior similar to the addition operation, except that Lua will try a metamethod only when the values being compared are neither both numbers nor both strings. The result of the call is always converted to a boolean.

Le

the less equal (<=) operation. Unlike other operations, the less-equal operation can use two different events. First, Lua looks for the __le metamethod in both operands, like in the less than operation. If it cannot find such a metamethod, then it will try the __lt metamethod, assuming that a <= b is equivalent to not (b < a). As with the other comparison operators, the result is always a boolean. (This use of the __lt event can be removed in future versions; it is also slower than a real __le metamethod.)

Index

The indexing access operation table[key]. This event happens when table is not a table or when key is not present in table. The metamethod is looked up in table.

Newindex

The indexing assignment table[key] = value. Like the index event, this event happens when table is not a table or when key is not present in table. The metamethod is looked up in table.

Call

The call operation func(args). This event happens when Lua tries to call a non-function value (that is, func is not a function). The metamethod is looked up in func. If present, the metamethod is called with func as its first argument, followed by the arguments of the original call (args). All results of the call are the result of the operation. (This is the only metamethod that allows multiple results.)

Tostring

The operation used to create a string representation of the object.

Pairs

the operation of iterating over the object's key-value pairs.

CustomOperation Name

a custom operation, with the metamethod name as parameter.

data Property e a #

A read- and writable property on a UD object.

data Possible a #

A property or method which may be available in some instances but not in others.

Constructors

Actual a 
Absent