hsqml-0.3.2.1: Haskell binding for Qt Quick

Safe HaskellNone
LanguageHaskell2010

Graphics.QML.Marshal

Contents

Description

Type classs and instances for marshalling values between Haskell and QML.

Synopsis

Marshalling Type-class

class Marshal t where

The class Marshal allows Haskell values to be marshalled to and from the QML environment.

Associated Types

type MarshalMode t c d

The MarshalMode associated type family specifies the marshalling capabilities offered by the instance. c indicates the capability being queried. d is dummy parameter which allows certain instances to type check.

Methods

marshaller :: MarshallerFor t

Yields the Marshaller for the type t.

type family ModeBidi c

MarshalMode for non-object types with bidirectional marshalling.

type family ModeFrom c

MarshalMode for non-object types with from-only marshalling.

type family ModeTo c

MarshalMode for non-object types with to-only marshalling.

type family ModeRetVoid c

MarshalMode for void in method returns.

type family ModeObjBidi a c

MarshalMode for object types with bidirectional marshalling.

type family ModeObjFrom a c

MarshalMode for object types with from-only marshalling.

type family ModeObjTo a c

MarshalMode for object types with to-only marshalling.

Instances

data Yes

Type value indicating a capability is supported.

type CanGetFrom t = MarshalMode t ICanGetFrom ()

Type function equal to Yes if the marshallable type t supports being received from QML.

data ICanGetFrom

Type index into MarshalMode for querying if the mode supports receiving values from QML.

type CanPassTo t = MarshalMode t ICanPassTo ()

Type function equal to Yes if the marshallable type t supports being passed to QML.

data ICanPassTo

Type index into MarshalMode for querying if the mode supports passing values to QML.

type CanReturnTo t = MarshalMode t ICanReturnTo ()

Type function equal to Yes if the marshallable type t supports being returned to QML.

data ICanReturnTo

Type index into MarshalMode for querying if the mode supports returning values to QML.

type IsObjType t = MarshalMode t IIsObjType ()

Type function equal to Yes if the marshallable type t is an object.

data IIsObjType

Type index into MarshalMode for querying if the mode supports an object type.

type GetObjType t = MarshalMode t IGetObjType ()

Type function which returns the type encapsulated by the object handles used by the marshallable type t.

data IGetObjType

Type index into MarshalMode for querying the type encapsulated by the mode's object handles.

data Marshaller t u v w x y

Encapsulates the functionality to needed to implement an instance of Marshal so that such instances can be defined without access to implementation details.

Data Types

data Ignored

Represents an argument whose value is ignored.

Constructors

Ignored 

Instances

Custom Marshallers

bidiMarshallerIO :: forall a b. (Marshal a, CanGetFrom a ~ Yes, CanPassTo a ~ Yes) => (a -> IO b) -> (b -> IO a) -> BidiMarshaller a b

Provides a bidirectional Marshaller which allows you to define an instance of Marshal for your own type b in terms of another marshallable type a. Type b should have a MarshalMode of ModeObjBidi or ModeBidi depending on whether a was an object type or not.

bidiMarshaller :: forall a b. (Marshal a, CanGetFrom a ~ Yes, CanPassTo a ~ Yes) => (a -> b) -> (b -> a) -> BidiMarshaller a b

Variant of bidiMarshallerIO where the conversion functions between types a and b do not live in the IO monad.

fromMarshallerIO :: forall a b. (Marshal a, CanGetFrom a ~ Yes) => (a -> IO b) -> FromMarshaller a b

Provides a "from" Marshaller which allows you to define an instance of Marshal for your own type b in terms of another marshallable type a. Type b should have a MarshalMode of ModeObjFrom or ModeFrom depending on whether a was an object type or not.

fromMarshaller :: forall a b. (Marshal a, CanGetFrom a ~ Yes) => (a -> b) -> FromMarshaller a b

Variant of fromMarshallerIO where the conversion function between types a and b does not live in the IO monad.

toMarshallerIO :: forall a b. (Marshal a, CanPassTo a ~ Yes) => (b -> IO a) -> ToMarshaller a b

Provides a "to" Marshaller which allows you to define an instance of Marshal for your own type b in terms of another marshallable type a. Type b should have a MarshalMode of ModeObjTo or ModeTo depending on whether a was an object type or not.

toMarshaller :: forall a b. (Marshal a, CanPassTo a ~ Yes) => (b -> a) -> ToMarshaller a b

Variant of toMarshallerIO where the conversion function between types a and b does not live in the IO monad.