-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Haskell binding for Qt Quick -- -- A Haskell binding for Qt Quick, a cross-platform framework for -- creating graphical user interfaces. For further information on -- installing and using this library, please see the project's web site. @package hsqml @version 0.3.5.1 -- | Debug Options module Graphics.QML.Debug -- | Sets the global debug log level. At level zero, no logging information -- will be printed. Higher levels will increase debug verbosity. setDebugLogLevel :: Int -> IO () -- | Type classs and instances for marshalling values between Haskell and -- QML. module Graphics.QML.Marshal -- | The class Marshal allows Haskell values to be marshalled to and -- from the QML environment. class Marshal t where { type family MarshalMode t c d; } -- | Yields the Marshaller for the type t. marshaller :: Marshal t => MarshallerFor t -- | MarshalMode for non-object types with bidirectional -- marshalling. -- | MarshalMode for non-object types with from-only marshalling. -- | MarshalMode for non-object types with to-only marshalling. -- | MarshalMode for void in method returns. -- | MarshalMode for object types with bidirectional marshalling. -- | MarshalMode for object types with from-only marshalling. -- | MarshalMode for object types with to-only marshalling. -- | Type value indicating a capability is supported. data Yes -- | Type function equal to Yes if the marshallable type t -- supports being received from QML. type CanGetFrom t = MarshalMode t ICanGetFrom () -- | Type index into MarshalMode for querying if the mode supports -- receiving values from QML. data ICanGetFrom -- | Type function equal to Yes if the marshallable type t -- supports being passed to QML. type CanPassTo t = MarshalMode t ICanPassTo () -- | Type index into MarshalMode for querying if the mode supports -- passing values to QML. data ICanPassTo -- | Type function equal to Yes if the marshallable type t -- supports being returned to QML. type CanReturnTo t = MarshalMode t ICanReturnTo () -- | Type index into MarshalMode for querying if the mode supports -- returning values to QML. data ICanReturnTo -- | Type function equal to Yes if the marshallable type t -- is an object. type IsObjType t = MarshalMode t IIsObjType () -- | Type index into MarshalMode for querying if the mode supports -- an object type. data IIsObjType -- | Type function which returns the type encapsulated by the object -- handles used by the marshallable type t. type GetObjType t = MarshalMode t IGetObjType () -- | Type index into MarshalMode for querying the type encapsulated -- by the mode's object handles. data IGetObjType -- | Encapsulates the functionality to needed to implement an instance of -- Marshal so that such instances can be defined without access to -- implementation details. data Marshaller t u v w x y -- | Represents an argument whose value is ignored. data Ignored Ignored :: Ignored -- | 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. bidiMarshallerIO :: forall a b. (Marshal a, CanGetFrom a ~ Yes, CanPassTo a ~ Yes) => (a -> IO b) -> (b -> IO a) -> BidiMarshaller a b -- | Variant of bidiMarshallerIO where the conversion functions -- between types a and b do not live in the IO monad. bidiMarshaller :: forall a b. (Marshal a, CanGetFrom a ~ Yes, CanPassTo a ~ Yes) => (a -> b) -> (b -> a) -> BidiMarshaller 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. fromMarshallerIO :: forall a b. (Marshal a, CanGetFrom a ~ Yes) => (a -> IO b) -> FromMarshaller a b -- | Variant of fromMarshallerIO where the conversion function -- between types a and b does not live in the IO monad. fromMarshaller :: forall a b. (Marshal a, CanGetFrom a ~ Yes) => (a -> b) -> FromMarshaller 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. toMarshallerIO :: forall a b. (Marshal a, CanPassTo a ~ Yes) => (b -> IO a) -> ToMarshaller a b -- | Variant of toMarshallerIO where the conversion function between -- types a and b does not live in the IO monad. toMarshaller :: forall a b. (Marshal a, CanPassTo a ~ Yes) => (b -> a) -> ToMarshaller a b instance Graphics.QML.Internal.Marshal.Marshal Graphics.QML.Marshal.Ignored instance Graphics.QML.Internal.Marshal.Marshal GHC.Types.Bool instance Graphics.QML.Internal.Marshal.Marshal GHC.Int.Int32 instance Graphics.QML.Internal.Marshal.Marshal GHC.Types.Int instance Graphics.QML.Internal.Marshal.Marshal GHC.Types.Double instance Graphics.QML.Internal.Marshal.Marshal Data.Text.Internal.Text instance Graphics.QML.Internal.Marshal.Marshal a => Graphics.QML.Internal.Marshal.Marshal (GHC.Base.Maybe a) instance Graphics.QML.Internal.Marshal.Marshal a => Graphics.QML.Internal.Marshal.Marshal [a] -- | Facility for drawing OpenGL graphics into the QML scenegraph. -- -- To use this facility, you must place a HaskellCanvas item -- into your QML scene. This item can be imported from the -- HsQML.Canvas 1.0 module using an import statement in -- your QML script. It has several properties which can be set from QML: -- -- -- -- The HsQML.Canvas 1.0 module also contains another type of -- item called OpenGLConextControl which can be used to -- configure the OpenGL context used by your windows. When placed inside -- a QML window, it has several properties which when read return the -- current state of that window's OpenGL context, and when written to -- cause the window's context to be reconfigured with a request for the -- supplied setting. Note that as reconfiguring the context may cause a -- visible window to dis- and re-appear, it's recommended to supply the -- desired settings at startup or otherwise before the corresponding -- window is made visible. Available properties are as below: -- -- module Graphics.QML.Canvas -- | Delegate for painting OpenGL graphics. data OpenGLDelegate -- | Creates a new OpenGLDelegate from setup, paint, and cleanup -- functions. newOpenGLDelegate :: (Marshal m, CanGetFrom m ~ Yes) => (OpenGLSetup -> IO i) -> (OpenGLPaint i m -> IO ()) -> (i -> IO ()) -> IO OpenGLDelegate -- | Represents the type of an OpenGL context. data OpenGLType -- | Desktop OpenGL context. OpenGLDesktop :: OpenGLType -- | OpenGL ES context. OpenGLES :: OpenGLType -- | Encapsulates parameters for OpenGL setup. data OpenGLSetup -- | Type of OpenGL context. openGLType :: OpenGLSetup -> OpenGLType -- | Major version number of OpenGL context. openGLMajor :: OpenGLSetup -> Int -- | Minor version number of OpenGL context. openGLMinor :: OpenGLSetup -> Int -- | Encapsulates parameters for OpenGL paint. data OpenGLPaint s m -- | Specialised version of OpenGLPaint with no model. type OpenGLPaint' s = OpenGLPaint s Ignored -- | Gets the setup state. setupData :: OpenGLPaint s m -> s -- | Gets the active model. modelData :: OpenGLPaint s m -> m -- | Pointer to a 4 by 4 matrix which transform coordinates in the range -- (-1, -1) to (1, 1) on to the target rectangle in the scene. matrixPtr :: OpenGLPaint s m -> Ptr CFloat -- | Width of the canvas item in its local coordinate system. itemWidth :: OpenGLPaint s m -> Float -- | Height of the canvas item in its local coordinate system. itemHeight :: OpenGLPaint s m -> Float instance GHC.Show.Show Graphics.QML.Canvas.OpenGLType instance GHC.Classes.Eq Graphics.QML.Canvas.OpenGLType instance Graphics.QML.Internal.Marshal.Marshal Graphics.QML.Canvas.OpenGLDelegate -- | Facility for working with Qt data models. -- -- This module is a placeholder for the ability to freely define QML -- classes which implement the QAbstractItemModel interface and -- functions to interact with those models. This is not currently -- supported, but the functionality will be available in a future -- release. -- -- HsQML does currently provide one mechanism for creating a Qt data -- model, the AutoListModel item. This item implements the -- QAbstractItemModel interface and provides a QML-side solution -- for generating a stateful Qt data model from a succession of -- JavaScript arrays. -- -- The advantage of this over using the arrays directly is that, when the -- array changes, the AutoListModel can generate item add, -- remove, and change events based on the differences between the old and -- new arrays. An simple array binding, on the other hand, causes the -- entire model to be reset so that views lose their state, cannot -- animate changes, etc. -- -- To use this facility, you must assign an AutoListModel item -- to the model property of a QML view such as a -- Repeater item. In turn, the source property of the -- AutoListModel must then be bound to an expression yielding -- the arrays you want to use. The AutoListModel can be imported -- from the HsQML.Model 1.0 module using an import -- statement in your QML script and it has several properties which can -- be set from QML as described below: -- -- module Graphics.QML.Model -- | Parameter Name Lists module Graphics.QML.Objects.ParamNames -- | Represents a list of parameter names. The number of names in the list -- is statically encoded using the length of the function type held in -- the type parameter a. data ParamNames a -- | Coverts a ParamNames list to an ordinary list of strings. paramNames :: ParamNames a -> [String] -- | An empty ParamNames list. noNames :: ParamNames () -- | Produces a ParamNames list with a single name. fstName :: String -> ParamNames (String -> ()) -- | Adds one parameter name to a ParamNames list. plusName :: ParamNames a -> String -> ParamNames (String -> a) -- | Polymorphically produces ParamNames lists of any length filled -- with blank parameter names. anonParams :: (AnonParams a) => ParamNames a -- | Helper class for generating anonymous parameter lists. class AnonParams a instance Graphics.QML.Objects.ParamNames.AnonParams b => Graphics.QML.Objects.ParamNames.AnonParams (GHC.Base.String -> b) instance Graphics.QML.Objects.ParamNames.AnonParams () instance GHC.Show.Show (Graphics.QML.Objects.ParamNames.ParamNames a) -- | Facilities for defining new object types which can be marshalled -- between Haskell and QML. module Graphics.QML.Objects -- | Represents an instance of the QML class which wraps the type -- tt. data ObjRef tt -- | Creates a QML object given a Class and a Haskell value of type -- tt. newObject :: forall tt. Class tt -> tt -> IO (ObjRef tt) -- | Creates a QML object given a Haskell value of type tt which -- has a DefaultClass instance. newObjectDC :: forall tt. (DefaultClass tt) => tt -> IO (ObjRef tt) -- | Returns the associated value of the underlying Haskell type -- tt from an instance of the QML class which wraps it. fromObjRef :: ObjRef tt -> tt -- | 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. data AnyObjRef -- | Upcasts an ObjRef into an AnyObjRef. anyObjRef :: ObjRef tt -> AnyObjRef -- | Attempts to downcast an AnyObjRef into an ObjRef with -- the specific underlying Haskell type tt. fromAnyObjRef :: (Typeable tt) => AnyObjRef -> Maybe (ObjRef tt) -- | Represents a QML class which wraps the type tt. data Class tt -- | Creates a new QML class for the type tt. newClass :: forall tt. (Typeable tt) => [Member tt] -> IO (Class tt) -- | The class DefaultClass specifies a standard class definition -- for the type tt. class (Typeable tt) => DefaultClass tt -- | List of default class members. classMembers :: DefaultClass tt => [Member tt] -- | Represents a named member of the QML class which wraps type -- tt. data Member 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 tt ms. (Marshal tt, CanGetFrom tt ~ Yes, IsObjType tt ~ Yes, MethodSuffix ms) => String -> (tt -> ms) -> Member (GetObjType tt) -- | Alias of defMethod which is less polymorphic to reduce the need -- for type signatures. defMethod' :: forall obj ms. (Typeable obj, MethodSuffix ms) => String -> (ObjRef obj -> ms) -> Member obj -- | Supports marshalling Haskell functions with an arbitrary number of -- arguments. class MethodSuffix a -- | 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. defSignal :: forall obj skv. (SignalKeyValue skv) => String -> 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. defSignalNamedParams :: forall obj skv. (SignalKeyValue skv) => String -> skv -> ParamNames (SignalParamNames (SignalValueParams skv)) -> Member obj -- | 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. fireSignal :: forall tt skv. (Marshal tt, CanPassTo tt ~ Yes, IsObjType tt ~ Yes, SignalKeyValue skv) => skv -> tt -> SignalValueParams skv -- | Values of the type SignalKey identify distinct signals by -- value. The type parameter p specifies the signal's signature. data SignalKey p -- | Creates a new SignalKey. newSignalKey :: (SignalSuffix p) => IO (SignalKey p) -- | Instances of the SignalKeyClass class identify distinct signals -- by type. The associated SignalParams type specifies the -- signal's signature. class (SignalSuffix (SignalParams sk)) => SignalKeyClass sk where { type family SignalParams sk; } -- | Supports marshalling an arbitrary number of arguments into a QML -- signal. class (AnonParams (SignalParamNames ss)) => SignalSuffix ss -- | Defines a named constant property using an accessor function in the IO -- monad. 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 read-only 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 with an associated signal. 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-write property using a pair of accessor and -- mutator functions in the IO monad. 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 with an associated signal. 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) -- | Alias of defPropertyConst which is less polymorphic to reduce -- the need for type signatures. defPropertyConst' :: 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. defPropertyRO' :: forall obj tr. (Typeable obj, Marshal tr, CanReturnTo tr ~ Yes) => String -> (ObjRef obj -> IO tr) -> Member obj -- | Alias of defPropertySigRO 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 defPropertyRW 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 defPropertySigRW 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 instance (Graphics.QML.Objects.SignalKeyClass sk, Data.Typeable.Internal.Typeable sk) => Graphics.QML.Objects.SignalKeyValue (Data.Proxy.Proxy sk) instance Graphics.QML.Objects.SignalSuffix p => Graphics.QML.Objects.SignalKeyValue (Graphics.QML.Objects.SignalKey p) instance (Graphics.QML.Internal.Marshal.Marshal a, Graphics.QML.Internal.Marshal.CanPassTo a ~ Graphics.QML.Internal.Marshal.Yes, Graphics.QML.Objects.SignalSuffix b) => Graphics.QML.Objects.SignalSuffix (a -> b) instance Graphics.QML.Objects.SignalSuffix (GHC.Types.IO ()) instance Graphics.QML.Objects.IsVoidIO b => Graphics.QML.Objects.IsVoidIO (a -> b) instance Graphics.QML.Objects.IsVoidIO Graphics.QML.Objects.VoidIO instance Graphics.QML.Objects.MethodSuffix Graphics.QML.Objects.VoidIO instance (Graphics.QML.Internal.Marshal.Marshal a, Graphics.QML.Internal.Marshal.CanGetFrom a ~ Graphics.QML.Internal.Marshal.Yes, Graphics.QML.Objects.MethodSuffix b) => Graphics.QML.Objects.MethodSuffix (a -> b) instance (Graphics.QML.Internal.Marshal.Marshal a, Graphics.QML.Internal.Marshal.CanReturnTo a ~ Graphics.QML.Internal.Marshal.Yes) => Graphics.QML.Objects.MethodSuffix (GHC.Types.IO a) -- | Functions for starting QML engines, displaying content in a window. module Graphics.QML.Engine -- | Holds parameters for configuring a QML runtime engine. data EngineConfig EngineConfig :: DocumentPath -> Maybe AnyObjRef -> [FilePath] -> [FilePath] -> EngineConfig -- | Path to the first QML document to be loaded. [initialDocument] :: EngineConfig -> DocumentPath -- | Context Object made available to QML script code. [contextObject] :: EngineConfig -> Maybe AnyObjRef -- | Additional search paths for QML modules [importPaths] :: EngineConfig -> [FilePath] -- | Additional search paths for QML native plugins [pluginPaths] :: EngineConfig -> [FilePath] -- | Default engine configuration. Loads "main.qml" from the -- current working directory into a visible window with no context -- object. defaultEngineConfig :: EngineConfig -- | Represents a QML engine. data Engine -- | Starts a new QML engine using the supplied configuration and blocks -- until the engine has terminated. runEngine :: EngineConfig -> RunQML () -- | Starts a new QML engine using the supplied configuration. The 'with' -- function is executed once the engine has been started and after it -- returns this function blocks until the engine has terminated. runEngineWith :: EngineConfig -> (Engine -> RunQML a) -> RunQML a -- | Starts a new QML engine using the supplied configuration and returns -- immediately without blocking. runEngineAsync :: EngineConfig -> RunQML Engine -- | Conveniance function that both runs the event loop and starts a new -- QML engine. It blocks keeping the event loop running until the engine -- has terminated. runEngineLoop :: EngineConfig -> IO () -- | Waits for the specified Engine to terminate. joinEngine :: Engine -> IO () -- | Kills the specified Engine asynchronously. killEngine :: Engine -> IO () -- | Wrapper around the IO monad for running actions which depend on the Qt -- event loop. data RunQML a -- | This function enters the Qt event loop and executes the supplied -- function in the RunQML monad on a new unbound thread. The event -- loop will continue to run until all functions in the RunQML -- monad have completed. This includes both the RunQML function -- launched by this call and any launched asynchronously via -- requireEventLoop. When the event loop exits, all engines will -- be terminated. -- -- It's recommended that applications run the event loop on their -- primordial thread as some platforms mandate this. Once the event loop -- has finished, it can be started again, but only on the same operating -- system thread as before. If the event loop fails to start then an -- EventLoopException will be thrown. -- -- If the event loop is entered for the first time then the currently set -- runtime command line arguments will be passed to Qt. Hence, while -- calling back to the supplied function, attempts to read the runtime -- command line arguments using the System.Environment module will only -- return those arguments not already consumed by Qt (per -- getQtArgs). runEventLoop :: RunQML a -> IO a -- | Enters the Qt event loop in the same manner as runEventLoop, -- but does not perform any processing related to command line arguments. runEventLoopNoArgs :: RunQML a -> IO a -- | Executes a function in the RunQML monad asynchronously to the -- event loop. Callers must apply their own sychronisation to ensure that -- the event loop is currently running when this function is called, -- otherwise an EventLoopException will be thrown. The event loop -- will not exit until the supplied function has completed. requireEventLoop :: RunQML a -> IO a -- | Sets the program name and command line arguments used by Qt and -- returns True if successful. This must be called before the first time -- the Qt event loop is entered otherwise it will have no effect and -- return False. By default Qt receives no arguments and the program name -- is set to HsQML. setQtArgs :: String -> [String] -> IO Bool -- | Gets the program name and any command line arguments remaining from an -- earlier call to setQtArgs once Qt has removed any it -- understands, leaving only application specific arguments. getQtArgs :: RunQML (String, [String]) -- | Represents a Qt application flag. data QtFlag -- | Enables resource sharing between OpenGL contexts. This must be set in -- order to use QtWebEngine. QtShareOpenGLContexts :: QtFlag -- | Sets or clears one of the application flags used by Qt and returns -- True if successful. If the flag or flag value is not supported then it -- will return False. Setting flags once the Qt event loop is entered is -- unsupported and will also cause this function to return False. setQtFlag :: QtFlag -> Bool -> IO Bool -- | Gets the state of one of the application flags used by Qt. getQtFlag :: QtFlag -> RunQML Bool -- | Shuts down and frees resources used by the Qt framework, preventing -- further use of the event loop. The framework is initialised when -- runEventLoop is first called and remains initialised afterwards -- so that the event loop can be reentered if desired (e.g. when using -- GHCi). Once shut down, the framework cannot be reinitialised. -- -- It is recommended that you call this function at the end of your -- program as this library will try, but cannot guarantee in all -- configurations to be able to shut it down for you. Failing to shutdown -- the framework has been known to intermittently cause crashes on -- process exit on some platforms. -- -- This function must be called from the event loop thread and the event -- loop must not be running at the time otherwise an -- EventLoopException will be thrown. shutdownQt :: IO () -- | Exception type used to report errors pertaining to the event loop. data EventLoopException -- | Path to a QML document file. data DocumentPath -- | Converts a local file path into a DocumentPath. fileDocument :: FilePath -> DocumentPath -- | Converts a URI string into a DocumentPath. uriDocument :: String -> DocumentPath instance GHC.Show.Show Graphics.QML.Engine.EventLoopException instance GHC.Show.Show Graphics.QML.Engine.QtFlag instance GHC.Base.Monad Graphics.QML.Engine.RunQML instance GHC.Base.Applicative Graphics.QML.Engine.RunQML instance GHC.Base.Functor Graphics.QML.Engine.RunQML instance GHC.Exception.Exception Graphics.QML.Engine.EventLoopException instance Control.Monad.IO.Class.MonadIO Graphics.QML.Engine.RunQML -- | Facilities for working with weak references, finalisers, and factory -- pools. module Graphics.QML.Objects.Weak -- | Represents a weak reference to a QML object which wraps the type -- tt. -- -- Unlike ordinary strong references, a weak reference does not prevent -- the QML garbage collector from collecting the underlying object. Weak -- references can be used to monitor the life cycles of QML objects. data WeakObjRef tt -- | Converts a strong ObjRef into a WeakObjRef. toWeakObjRef :: ObjRef tt -> IO (WeakObjRef tt) -- | Converts a WeakObjRef into a strong ObjRef. -- -- If the underlying QML object has already been collected then the -- resulting ObjRef can be used to reincarnate it. fromWeakObjRef :: WeakObjRef tt -> IO (ObjRef tt) -- | Represents an object finaliser function for QML objects which wrap the -- type tt. data ObjFinaliser tt -- | Create a new object finaliser from a finaliser function. -- -- Note that at the time the finaliser is called the runtime will have -- already comitted to collecting the underlying QML object. The -- ObjRef passed into the finaliser can be used to reincarnate the -- object, but this QML object will have a distinct identity to the -- original. newObjFinaliser :: (ObjRef tt -> IO ()) -> IO (ObjFinaliser tt) -- | Adds an object finaliser to an QML object. -- -- The finaliser will be called no more than once for each time it was -- added to an object. The timing of finaliser execution is subject to -- the combined behaviour of the Haskell and QML garbage collectors. All -- outstanding finalisers will be run when the QML engine is terminated -- provided that the program does not prematurely exit. addObjFinaliser :: ObjFinaliser tt -> ObjRef tt -> IO () -- | Represents an object factory which maintains a one-to-one mapping -- between values of type tt and QML object instances. -- -- ObjRefs manufactured by the pool are cached using the wrapped -- type tt as the lookup key in an ordered map. The pool uses -- weak references to automatically purge objects which no longer have -- any strong references leading to them from either Haskell or QML code. data FactoryPool tt -- | Creates a new FactoryPool using the supplied factory function. newFactoryPool :: (Ord tt) => (tt -> IO (ObjRef tt)) -> IO (FactoryPool tt) -- | Return the pool's canonical QML object for a value of tt, -- either by creating it or looking it up in the pool's cache of objects. getPoolObject :: (Ord tt) => FactoryPool tt -> tt -> IO (ObjRef tt) -- | This module imports the entire package, except Debug. module Graphics.QML