hsqml-0.3.3.0: Haskell binding for Qt Quick

Safe HaskellNone
LanguageHaskell2010

Graphics.QML.Objects

Contents

Description

Facilities for defining new object types which can be marshalled between Haskell and QML.

Synopsis

Object References

data ObjRef tt

Represents an instance of the QML class which wraps the type tt.

Instances

Typeable * tt => Marshal (ObjRef tt) 
type MarshalMode (ObjRef tt) c d = ModeObjBidi tt c 

newObject :: forall tt. Class tt -> tt -> IO (ObjRef tt)

Creates a QML object given a Class and a Haskell value of type tt.

newObjectDC :: forall tt. DefaultClass tt => tt -> IO (ObjRef tt)

Creates a QML object given a Haskell value of type tt which has a DefaultClass instance.

fromObjRef :: ObjRef tt -> tt

Returns the associated value of the underlying Haskell type tt from an instance of the QML class which wraps it.

Dynamic Object References

data AnyObjRef

Represents an instance of a QML class which wraps an arbitrary Haskell type. Unlike ObjRef, an AnyObjRef only carries the type of its Haskell value dynamically and does not encode it into the static type.

Instances

anyObjRef :: ObjRef tt -> AnyObjRef

Upcasts an ObjRef into an AnyObjRef.

fromAnyObjRef :: Typeable tt => AnyObjRef -> Maybe (ObjRef tt)

Attempts to downcast an AnyObjRef into an ObjRef with the specific underlying Haskell type tt.

Class Definition

data Class tt

Represents a QML class which wraps the type tt.

newClass :: forall tt. Typeable tt => [Member tt] -> IO (Class tt)

Creates a new QML class for the type tt.

class Typeable tt => DefaultClass tt where

The class DefaultClass specifies a standard class definition for the type tt.

Methods

classMembers :: [Member tt]

List of default class members.

data Member tt

Represents a named member of the QML class which wraps type tt.

Methods

defMethod :: forall tt ms. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, MethodSuffix ms) => String -> (tt -> ms) -> Member (GetObjType tt)

Defines a named method using a function f in the IO monad.

The first argument to f receives the "this" object and hence must match the type of the class on which the method is being defined. Subsequently, there may be zero or more parameter arguments followed by an optional return argument in the IO monad.

defMethod' :: forall obj ms. (Typeable obj, MethodSuffix ms) => String -> (ObjRef obj -> ms) -> Member obj

Alias of defMethod which is less polymorphic to reduce the need for type signatures.

class MethodSuffix a

Supports marshalling Haskell functions with an arbitrary number of arguments.

Minimal complete definition

mkMethodFunc, mkMethodTypes

Instances

(Marshal a, (~) * (CanReturnTo a) Yes) => MethodSuffix (IO a) 
(Marshal a, (~) * (CanGetFrom a) Yes, MethodSuffix b) => MethodSuffix (a -> b) 

Signals

defSignal :: forall obj skv. SignalKeyValue skv => String -> skv -> Member obj

Defines a named signal. The signal is identified in subsequent calls to fireSignal using a SignalKeyValue. This can be either i) type-based using Proxy sk where sk is an instance of the SignalKeyClass class or ii) value-based using a SignalKey value creating using newSignalKey.

defSignalNamedParams :: forall obj skv. SignalKeyValue skv => String -> skv -> ParamNames (SignalParamNames (SignalValueParams skv)) -> Member obj

Defines a named signal with named parameters. This is otherwise identical to defSignal, but allows QML code to reference signal parameters by-name in addition to by-position.

fireSignal :: forall tt skv. (Marshal tt, CanPassTo tt ~ Yes, IsObjType tt ~ Yes, SignalKeyValue skv) => skv -> tt -> SignalValueParams skv

Fires a signal defined on an object instance. The signal is identified using either a type- or value-based signal key, as described in the documentation for defSignal. The first argument is the signal key, the second is the object, and the remaining arguments, if any, are the arguments to the signal as specified by the signal key.

If this function is called using a signal key which doesn't match a signal defined on the supplied object, it will silently do nothing.

This function is safe to call from any thread. Any attached signal handlers will be executed asynchronously on the event loop thread.

data SignalKey p

Values of the type SignalKey identify distinct signals by value. The type parameter p specifies the signal's signature.

newSignalKey :: SignalSuffix p => IO (SignalKey p)

Creates a new SignalKey.

class SignalSuffix (SignalParams sk) => SignalKeyClass sk

Instances of the SignalKeyClass class identify distinct signals by type. The associated SignalParams type specifies the signal's signature.

Associated Types

type SignalParams sk

class AnonParams (SignalParamNames ss) => SignalSuffix ss

Supports marshalling an arbitrary number of arguments into a QML signal.

Minimal complete definition

mkSignalArgs, mkSignalTypes

Instances

SignalSuffix (IO ()) 
(Marshal a, (~) * (CanPassTo a) Yes, SignalSuffix b) => SignalSuffix (a -> b) 

Properties

defPropertyConst :: forall tt tr. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, Marshal tr, CanReturnTo tr ~ Yes) => String -> (tt -> IO tr) -> Member (GetObjType tt)

Defines a named constant property using an accessor function in the IO monad.

defPropertyRO :: forall tt tr. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, Marshal tr, CanReturnTo tr ~ Yes) => String -> (tt -> IO tr) -> Member (GetObjType tt)

Defines a named read-only property using an accessor function in the IO monad.

defPropertySigRO :: forall tt tr skv. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, Marshal tr, CanReturnTo tr ~ Yes, SignalKeyValue skv) => String -> skv -> (tt -> IO tr) -> Member (GetObjType tt)

Defines a named read-only property with an associated signal.

defPropertyRW :: forall tt tr. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, Marshal tr, CanReturnTo tr ~ Yes, CanGetFrom tr ~ Yes) => String -> (tt -> IO tr) -> (tt -> tr -> IO ()) -> Member (GetObjType tt)

Defines a named read-write property using a pair of accessor and mutator functions in the IO monad.

defPropertySigRW :: forall tt tr skv. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, Marshal tr, CanReturnTo tr ~ Yes, CanGetFrom tr ~ Yes, SignalKeyValue skv) => String -> skv -> (tt -> IO tr) -> (tt -> tr -> IO ()) -> Member (GetObjType tt)

Defines a named read-write property with an associated signal.

defPropertyConst' :: forall obj tr. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes) => String -> (ObjRef obj -> IO tr) -> Member obj

Alias of defPropertyConst which is less polymorphic to reduce the need for type signatures.

defPropertyRO' :: forall obj tr. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes) => String -> (ObjRef obj -> IO tr) -> Member obj

Alias of defPropertyRO which is less polymorphic to reduce the need for type signatures.

defPropertySigRO' :: forall obj tr skv. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes, SignalKeyValue skv) => String -> skv -> (ObjRef obj -> IO tr) -> Member obj

Alias of defPropertySigRO which is less polymorphic to reduce the need for type signatures.

defPropertyRW' :: forall obj tr. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes, CanGetFrom tr ~ Yes) => String -> (ObjRef obj -> IO tr) -> (ObjRef obj -> tr -> IO ()) -> Member obj

Alias of defPropertyRW which is less polymorphic to reduce the need for type signatures.

defPropertySigRW' :: forall obj tr skv. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes, CanGetFrom tr ~ Yes, SignalKeyValue skv) => String -> skv -> (ObjRef obj -> IO tr) -> (ObjRef obj -> tr -> IO ()) -> Member obj

Alias of defPropertySigRW which is less polymorphic to reduce the need for type signatures.