hslua-typing-0.1.1: Type specifiers for Lua.
Copyright© 2023-2024 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb@hslua.org>
Safe HaskellSafe-Inferred
LanguageHaskell2010

HsLua.Typing

Description

The module provides Haskell types and values that can be used to describe and declare the types of Lua values.

Synopsis

Documentation

data TypeSpec Source #

Type specification for Lua values.

Constructors

BasicType Type

Built-in type

NamedType Name

A type that's been given a name.

SeqType TypeSpec

Sequence of the given type.

SumType [TypeSpec]

Union type; a sum type.

RecType (Map Name TypeSpec)

Record type (type product).

FunType [TypeSpec] [TypeSpec]

Function type.

AnyType

Unconstrained type.

Instances

Instances details
IsString TypeSpec Source #

For backwards compatibility and convenience, strings can be used as TypeSpec values.

Instance details

Defined in HsLua.Typing

Generic TypeSpec Source # 
Instance details

Defined in HsLua.Typing

Associated Types

type Rep TypeSpec :: Type -> Type #

Methods

from :: TypeSpec -> Rep TypeSpec x #

to :: Rep TypeSpec x -> TypeSpec #

Show TypeSpec Source # 
Instance details

Defined in HsLua.Typing

Eq TypeSpec Source # 
Instance details

Defined in HsLua.Typing

Ord TypeSpec Source # 
Instance details

Defined in HsLua.Typing

type Rep TypeSpec Source # 
Instance details

Defined in HsLua.Typing

data TypeDocs Source #

Documented custom type.

Instances

Instances details
Generic TypeDocs Source # 
Instance details

Defined in HsLua.Typing

Associated Types

type Rep TypeDocs :: Type -> Type #

Methods

from :: TypeDocs -> Rep TypeDocs x #

to :: Rep TypeDocs x -> TypeDocs #

Show TypeDocs Source # 
Instance details

Defined in HsLua.Typing

Eq TypeDocs Source # 
Instance details

Defined in HsLua.Typing

Ord TypeDocs Source # 
Instance details

Defined in HsLua.Typing

type Rep TypeDocs Source # 
Instance details

Defined in HsLua.Typing

type Rep TypeDocs = D1 ('MetaData "TypeDocs" "HsLua.Typing" "hslua-typing-0.1.1-LiVjbUc2V3DIMCvCaKVrW5" 'False) (C1 ('MetaCons "TypeDocs" 'PrefixI 'True) (S1 ('MetaSel ('Just "typeDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "typeSpec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeSpec) :*: S1 ('MetaSel ('Just "typeRegistry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)))))

(#|#) :: TypeSpec -> TypeSpec -> TypeSpec Source #

Returns the sum of two type specifiers, declaring that a Lua value can have either type.

typeSpecToString :: TypeSpec -> String Source #

Generate a string representation of the type specifier.

typeSpecFromString :: String -> TypeSpec Source #

Creates a TypeSpec value from a string.

The implementation currently handles basic types, sequences, and alternatives. A string that cannot be parsed is returned as a Named type with the full string as the name.

Types

anyType :: TypeSpec Source #

Unconstraint type; any Lua value.

voidType :: TypeSpec Source #

A type for which there cannot be any value.

Built-in types

booleanType :: TypeSpec Source #

The built-in boolean Lua type.

functionType :: TypeSpec Source #

The built-in function Lua type.

integerType :: TypeSpec Source #

A Lua integer type.

lightUserdataType :: TypeSpec Source #

The built-in light userdata Lua type.

nilType :: TypeSpec Source #

The built-in nil Lua type.

numberType :: TypeSpec Source #

The built-in number Lua type.

stringType :: TypeSpec Source #

The built-in string Lua type.

tableType :: TypeSpec Source #

The built-in table Lua type.

threadType :: TypeSpec Source #

The built-in thread Lua type.

userdataType :: TypeSpec Source #

The built-in userdata Lua type.

Type constructors

recType :: [(Name, TypeSpec)] -> TypeSpec Source #

Creates a record type.

seqType :: TypeSpec -> TypeSpec Source #

Creates a sequence type.

Marshalling

pushTypeSpec :: LuaError e => TypeSpec -> LuaE e () Source #

Pushes a table representation of a TypeSpec to the stack.

peekTypeSpec :: LuaError e => Peeker e TypeSpec Source #

Retrieves a TypeSpec from a table on the stack.

pushTypeDoc :: LuaError e => Pusher e TypeDocs Source #

Pushes documentation for a custom type.

peekTypeDoc :: LuaError e => Peeker e TypeDocs Source #

Retrieves a custom type specifier.