hsqml-0.3.5.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 Source #

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

Minimal complete definition

marshaller

Associated Types

type MarshalMode t c d Source #

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 Source #

Yields the Marshaller for the type t.

Instances

Marshal () Source # 

Associated Types

type MarshalMode () c d :: * Source #

Methods

marshaller :: MarshallerFor () Source #

Marshal AnyObjRef Source # 

Associated Types

type MarshalMode AnyObjRef c d :: * Source #

Methods

marshaller :: MarshallerFor AnyObjRef Source #

Marshal Ignored Source # 

Associated Types

type MarshalMode Ignored c d :: * Source #

Methods

marshaller :: MarshallerFor Ignored Source #

Marshal OpenGLDelegate Source # 

Associated Types

type MarshalMode OpenGLDelegate c d :: * Source #

Methods

marshaller :: MarshallerFor OpenGLDelegate Source #

Typeable * tt => Marshal (ObjRef tt) Source # 

Associated Types

type MarshalMode (ObjRef tt) c d :: * Source #

Methods

marshaller :: MarshallerFor (ObjRef tt) Source #

type family ModeBidi c Source #

MarshalMode for non-object types with bidirectional marshalling.

type family ModeTo c Source #

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

type family ModeObjBidi a c Source #

MarshalMode for object types with bidirectional marshalling.

type family ModeObjTo a c Source #

MarshalMode for object types with to-only marshalling.

data Yes Source #

Type value indicating a capability is supported.

type CanGetFrom t = MarshalMode t ICanGetFrom () Source #

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

type CanPassTo t = MarshalMode t ICanPassTo () Source #

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

type CanReturnTo t = MarshalMode t ICanReturnTo () Source #

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

type IsObjType t = MarshalMode t IIsObjType () Source #

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

type GetObjType t = MarshalMode t IGetObjType () Source #

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

data Marshaller t u v w x y Source #

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 Source #

Represents an argument whose value is ignored.

Constructors

Ignored 

Instances

Marshal Ignored Source # 

Associated Types

type MarshalMode Ignored c d :: * Source #

Methods

marshaller :: MarshallerFor Ignored Source #

type MarshalMode Ignored c d Source # 

Custom Marshallers

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

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 Source #

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 Source #

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 Source #

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 Source #

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 Source #

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

Orphan instances

Marshal Bool Source # 

Associated Types

type MarshalMode Bool c d :: * Source #

Methods

marshaller :: MarshallerFor Bool Source #

Marshal Double Source # 

Associated Types

type MarshalMode Double c d :: * Source #

Methods

marshaller :: MarshallerFor Double Source #

Marshal Int Source # 

Associated Types

type MarshalMode Int c d :: * Source #

Methods

marshaller :: MarshallerFor Int Source #

Marshal Int32 Source # 

Associated Types

type MarshalMode Int32 c d :: * Source #

Methods

marshaller :: MarshallerFor Int32 Source #

Marshal Text Source # 

Associated Types

type MarshalMode Text c d :: * Source #

Methods

marshaller :: MarshallerFor Text Source #

Marshal a => Marshal [a] Source # 

Associated Types

type MarshalMode [a] c d :: * Source #

Methods

marshaller :: MarshallerFor [a] Source #

Marshal a => Marshal (Maybe a) Source # 

Associated Types

type MarshalMode (Maybe a) c d :: * Source #

Methods

marshaller :: MarshallerFor (Maybe a) Source #