Copyright | © 2021-2022 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Safe Haskell | None |
Language | Haskell2010 |
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
- type UDType e fn a = UDTypeWithList e fn a Void
- data UDTypeWithList e fn a itemtype = UDTypeWithList {
- udName :: Name
- udOperations :: [(Operation, fn)]
- udProperties :: Map Name (Property e a)
- udMethods :: Map Name fn
- udAliases :: Map AliasIndex Alias
- udListSpec :: Maybe (ListSpec e a itemtype)
- udFnPusher :: fn -> LuaE e ()
- deftypeGeneric :: Pusher e fn -> Name -> [(Operation, fn)] -> [Member e fn a] -> UDType e fn a
- deftypeGeneric' :: Pusher e fn -> Name -> [(Operation, fn)] -> [Member e fn a] -> Maybe (ListSpec e a itemtype) -> UDTypeWithList e fn a itemtype
- methodGeneric :: Name -> fn -> Member e fn a
- property :: LuaError e => Name -> Text -> (Pusher e b, a -> b) -> (Peeker e b, a -> b -> a) -> Member e fn a
- possibleProperty :: LuaError e => Name -> Text -> (Pusher e b, a -> Possible b) -> (Peeker e b, a -> b -> Possible a) -> Member e fn a
- readonly :: Name -> Text -> (Pusher e b, a -> b) -> Member e fn a
- alias :: AliasIndex -> Text -> [AliasIndex] -> Member e fn a
- peekUD :: LuaError e => UDTypeWithList e fn a itemtype -> Peeker e a
- pushUD :: LuaError e => UDTypeWithList e fn a itemtype -> a -> LuaE e ()
- data Member e fn a
- data Property e a
- data Operation
- type ListSpec e a itemtype = ((Pusher e itemtype, a -> [itemtype]), (Peeker e itemtype, a -> [itemtype] -> a))
- data Possible a
- type Alias = [AliasIndex]
- data AliasIndex
Documentation
type UDType e fn a = UDTypeWithList e fn a Void 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.
data UDTypeWithList e fn 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.
This type includes methods to define how the object should behave as
a read-only list of type itemtype
.
UDTypeWithList | |
|
:: Pusher e fn | function pusher |
-> Name | type name |
-> [(Operation, fn)] | operations |
-> [Member e fn a] | methods |
-> UDType e fn a |
Defines a new type, defining the behavior of objects in Lua. Note that the type name must be unique.
:: Pusher e fn | function pusher |
-> Name | type name |
-> [(Operation, fn)] | operations |
-> [Member e fn a] | methods |
-> Maybe (ListSpec e a itemtype) | list access |
-> UDTypeWithList e fn 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.
methodGeneric :: Name -> fn -> Member e fn a Source #
Use a documented function as an object method.
:: 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.
:: 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.
:: 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.
:: AliasIndex | property alias |
-> Text | description |
-> [AliasIndex] | sequence of nested properties |
-> Member e fn a |
Define an alias for another, possibly nested, property.
peekUD :: LuaError e => UDTypeWithList e fn a itemtype -> Peeker e a Source #
Retrieves a userdata value of the given type.
pushUD :: LuaError e => UDTypeWithList e fn a itemtype -> a -> LuaE e () Source #
Pushes a userdata value of the given type.
Helper types for building
Lua metadata operation types.
Add | the addition ( |
Sub | the subtraction ( |
Mul | the multiplication ( |
Div | the division ( |
Mod | the modulo ( |
Pow | the exponentiation ( |
Unm | the negation (unary |
Idiv | the floor division ( |
Band | the bitwise AND ( |
Bor | the bitwise OR ( |
Bxor | the bitwise exclusive OR (binary |
Bnot | the bitwise NOT (unary |
Shl | the bitwise left shift ( |
Shr | the bitwise right shift ( |
Concat | the concatenation ( |
Len | the length ( |
Eq | the equal ( |
Lt | the less than ( |
Le | the less equal ( |
Index | The indexing access operation |
Newindex | The indexing assignment |
Call | The call operation |
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. |
type ListSpec e a itemtype = ((Pusher e itemtype, a -> [itemtype]), (Peeker e itemtype, a -> [itemtype] -> a)) Source #
Pair of pairs, describing how a type can be used as a Lua list. The first pair describes how to push the list items, and how the list is extracted from the type; the second pair contains a method to retrieve list items, and defines how the list is used to create an updated value.
A property or method which may be available in some instances but not in others.
type Alias = [AliasIndex] Source #
Alias for a different property of this or of a nested object.
data AliasIndex Source #
Index types allowed in aliases (strings and integers)
Instances
Eq AliasIndex Source # | |
Defined in HsLua.ObjectOrientation (==) :: AliasIndex -> AliasIndex -> Bool # (/=) :: AliasIndex -> AliasIndex -> Bool # | |
Ord AliasIndex Source # | |
Defined in HsLua.ObjectOrientation compare :: AliasIndex -> AliasIndex -> Ordering # (<) :: AliasIndex -> AliasIndex -> Bool # (<=) :: AliasIndex -> AliasIndex -> Bool # (>) :: AliasIndex -> AliasIndex -> Bool # (>=) :: AliasIndex -> AliasIndex -> Bool # max :: AliasIndex -> AliasIndex -> AliasIndex # min :: AliasIndex -> AliasIndex -> AliasIndex # | |
IsString AliasIndex Source # | |
Defined in HsLua.ObjectOrientation fromString :: String -> AliasIndex # |