Copyright | © 2021-2024 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <[email protected]> |
Safe Haskell | None |
Language | Haskell2010 |
HsLua.ObjectOrientation.Generic
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
- data UDTypeGeneric e fn a = UDType {
- udName :: Name
- udOperations :: [(Operation, fn)]
- udProperties :: Map Name (Property e a)
- udMethods :: Map Name fn
- udAliases :: Map AliasIndex Alias
- udHooks :: UDTypeHooks e fn a
- udFnPusher :: fn -> LuaE e ()
- deftypeGeneric' :: Pusher e fn -> Name -> [(Operation, fn)] -> [Member e fn a] -> UDTypeHooks e fn a -> UDTypeGeneric e fn a
- 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
- property' :: LuaError e => Name -> TypeSpec -> 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
- possibleProperty' :: LuaError e => Name -> TypeSpec -> 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
- readonly' :: Name -> TypeSpec -> Text -> (Pusher e b, a -> b) -> Member e fn a
- alias :: AliasIndex -> Text -> [AliasIndex] -> Member e fn a
- data UDTypeHooks e fn a = UDTypeHooks {
- hookUservalues :: Int
- hookMetatableSetup :: LuaE e ()
- hookPeekUD :: a -> StackIndex -> Peek e a
- hookPushUD :: a -> LuaE e ()
- emptyHooks :: UDTypeHooks e fn a
- peekUDGeneric :: LuaError e => UDTypeGeneric e fn a -> Peeker e a
- pushUDGeneric :: LuaError e => UDTypeGeneric e fn a -> a -> LuaE e ()
- initType :: LuaError e => UDTypeGeneric e fn a -> LuaE e Name
- udDocs :: UDTypeGeneric e fn a -> TypeDocs
- udTypeSpec :: UDTypeGeneric e fn a -> TypeSpec
- data Member e fn a
- data Property e a = Property {
- propertyGet :: a -> LuaE e NumResults
- propertySet :: Maybe (StackIndex -> a -> LuaE e a)
- propertyDescription :: Text
- propertyType :: TypeSpec
- data Operation
- data Possible a
- type Alias = [AliasIndex]
- data AliasIndex
Documentation
data UDTypeGeneric e fn a 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
.
Constructors
UDType | |
Fields
|
Defining types
Arguments
:: Pusher e fn | function pusher |
-> Name | type name |
-> [(Operation, fn)] | operations |
-> [Member e fn a] | methods |
-> UDTypeHooks e fn a | behavior modifying hooks |
-> UDTypeGeneric e fn a |
Defines a new "Lua type" and sets the behavior of the Lua object instances. It's possible to pass custom type extensions, which modify the default object behavior. Furthermore, the function pusher parameter controls how functions are marshaled to Lua.
Note that the type name must be unique.
Methods
methodGeneric :: Name -> fn -> Member e fn a Source #
Use a documented function as an object method.
Properties
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.
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.
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.
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.
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.
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.
Aliases
Arguments
:: AliasIndex | property alias |
-> Text | description |
-> [AliasIndex] | sequence of nested properties |
-> Member e fn a |
Define an alias for another, possibly nested, property.
Type extension
data UDTypeHooks e fn a Source #
Extensions for userdata types.
Constructors
UDTypeHooks | |
Fields
|
emptyHooks :: UDTypeHooks e fn a Source #
No extension.
Marshaling
peekUDGeneric :: LuaError e => UDTypeGeneric e fn a -> Peeker e a Source #
Retrieves a userdata value of the given type.
Arguments
:: LuaError e | |
=> UDTypeGeneric e fn a | userdata type |
-> a | value to push |
-> LuaE e () |
Pushes a userdata value of the given type.
initType :: LuaError e => UDTypeGeneric e fn a -> 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.
Type docs
udDocs :: UDTypeGeneric e fn a -> TypeDocs Source #
Returns documentation for this type.
udTypeSpec :: UDTypeGeneric e fn a -> TypeSpec Source #
Type specifier for a UDType
Helper types for building
A read- and writable property on a UD object.
Constructors
Property | |
Fields
|
Lua metadata operation types.
Constructors
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. |
Instances
Show Operation Source # | |
Eq Operation Source # | |
Ord Operation Source # | |
Defined in HsLua.ObjectOrientation.Operation |
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)
Constructors
StringIndex Name | |
IntegerIndex Integer |
Instances
IsString AliasIndex Source # | |
Defined in HsLua.ObjectOrientation.Generic Methods fromString :: String -> AliasIndex # | |
Eq AliasIndex Source # | |
Defined in HsLua.ObjectOrientation.Generic | |
Ord AliasIndex Source # | |
Defined in HsLua.ObjectOrientation.Generic Methods compare :: AliasIndex -> AliasIndex -> Ordering # (<) :: AliasIndex -> AliasIndex -> Bool # (<=) :: AliasIndex -> AliasIndex -> Bool # (>) :: AliasIndex -> AliasIndex -> Bool # (>=) :: AliasIndex -> AliasIndex -> Bool # max :: AliasIndex -> AliasIndex -> AliasIndex # min :: AliasIndex -> AliasIndex -> AliasIndex # |