reflex-gi-gtk-0.2.0.0: Helper functions to use reflex with gi-gtk
CopyrightSven Bartscher 2020
LicenseMPL-2.0
Maintainersven.bartscher@weltraumschlangen.de
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Reflex.GI.Gtk.Host

Description

This module provides the top-level entry-point for running reactive GTK applications, namely runReflexGtk.

Synopsis

Documentation

runReflexGtk Source #

Arguments

:: Application

The application to run the GTK mainloop on.

-> Maybe [String]

The arguments to provide to applicationRun

-> (forall x. HasSpiderTimeline x => ReflexGtk x ())

The user-provided monadic action to set up your reactive network.

-> IO Int32

The exit code as returned by applicationRun

The top-level entry point for reactive GTK applications.

You have to provide an existing Application which will run the GTK application. applicationRun should not be called on the Application manually, as this function expects to start the mainloop by itself. However, apart from that, you may use the Application as you wish, for example by setting appropriate ApplicationFlags, binding to its signals, assigning Windows to it or changing its attributes.

type ReflexGtk x = ReflexGtkT (SpiderTimeline x) (SpiderHost x) Source #

This is the monad that reactive GTK code is run in. Notably this type implements MonadReflexGtk when run with runReflexGtk.

data ReflexGtkT (t :: *) (m :: k) a Source #

A monad providing an implementation for MonadReflexGtk given a suitable reflex host (such as SpiderHost) as a base monad.

Your probably want to look at ReflexGtk, as it is the only specialization of this type that can be executed using runReflexGtk.

Instances

Instances details
(ReflexHost t, NotReady t (PerformEventT t m)) => NotReady t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

notReadyUntil :: Event t a -> ReflexGtkT t m () #

notReady :: ReflexGtkT t m () #

(ReflexHost t, Ref m ~ Ref IO) => PerformEvent t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Associated Types

type Performable (ReflexGtkT t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (ReflexGtkT t m) a) -> ReflexGtkT t m (Event t a) #

performEvent_ :: Event t (Performable (ReflexGtkT t m) ()) -> ReflexGtkT t m () #

(ReflexHost t, MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO) => TriggerEvent t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

newTriggerEvent :: ReflexGtkT t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: ReflexGtkT t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> ReflexGtkT t m (Event t a) #

ReflexHost t => PostBuild t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

getPostBuild :: ReflexGtkT t m (Event t ()) #

(ReflexHost t, PrimMonad (HostFrame t), MonadHold t m, Ref m ~ Ref IO) => Adjustable t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

runWithReplace :: ReflexGtkT t m a -> Event t (ReflexGtkT t m b) -> ReflexGtkT t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> ReflexGtkT t m v') -> IntMap v -> Event t (PatchIntMap v) -> ReflexGtkT t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> ReflexGtkT t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> ReflexGtkT t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> ReflexGtkT t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> ReflexGtkT t m (DMap k v', Event t (PatchDMapWithMove k v')) #

(ReflexHost t, MonadIO (HostFrame t), MonadRef (HostFrame t), Ref (HostFrame t) ~ Ref IO) => MonadGtkSource t (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

eventFromSignalWith :: (GObject object, SignalInfo info) => Registerer object info -> FireAsync -> object -> SignalProxy object info -> ((a -> IO ()) -> HaskellCallbackType info) -> ReflexGtkT t m (Event t a) Source #

ReflexHost t => MonadSample (t :: Type) (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

sample :: Behavior t a -> ReflexGtkT t m a #

(ReflexHost t, MonadHold t m) => MonadHold (t :: Type) (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

hold :: a -> Event t a -> ReflexGtkT t m (Behavior t a) #

holdDyn :: a -> Event t a -> ReflexGtkT t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> ReflexGtkT t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> ReflexGtkT t m (Dynamic t a) #

headE :: Event t a -> ReflexGtkT t m (Event t a) #

now :: ReflexGtkT t m (Event t ()) #

ReflexHost t => Monad (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

(>>=) :: ReflexGtkT t m a -> (a -> ReflexGtkT t m b) -> ReflexGtkT t m b #

(>>) :: ReflexGtkT t m a -> ReflexGtkT t m b -> ReflexGtkT t m b #

return :: a -> ReflexGtkT t m a #

ReflexHost t => Functor (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

fmap :: (a -> b) -> ReflexGtkT t m a -> ReflexGtkT t m b #

(<$) :: a -> ReflexGtkT t m b -> ReflexGtkT t m a #

ReflexHost t => MonadFix (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

mfix :: (a -> ReflexGtkT t m a) -> ReflexGtkT t m a #

ReflexHost t => Applicative (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

pure :: a -> ReflexGtkT t m a #

(<*>) :: ReflexGtkT t m (a -> b) -> ReflexGtkT t m a -> ReflexGtkT t m b #

liftA2 :: (a -> b -> c) -> ReflexGtkT t m a -> ReflexGtkT t m b -> ReflexGtkT t m c #

(*>) :: ReflexGtkT t m a -> ReflexGtkT t m b -> ReflexGtkT t m b #

(<*) :: ReflexGtkT t m a -> ReflexGtkT t m b -> ReflexGtkT t m a #

(ReflexHost t, MonadIO (HostFrame t)) => MonadIO (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

liftIO :: IO a -> ReflexGtkT t m a #

(MonadRef (HostFrame t), ReflexHost t) => MonadRef (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Associated Types

type Ref (ReflexGtkT t m) :: Type -> Type #

Methods

newRef :: a -> ReflexGtkT t m (Ref (ReflexGtkT t m) a) #

readRef :: Ref (ReflexGtkT t m) a -> ReflexGtkT t m a #

writeRef :: Ref (ReflexGtkT t m) a -> a -> ReflexGtkT t m () #

modifyRef :: Ref (ReflexGtkT t m) a -> (a -> a) -> ReflexGtkT t m () #

modifyRef' :: Ref (ReflexGtkT t m) a -> (a -> a) -> ReflexGtkT t m () #

(ReflexHost t, MonadIO (HostFrame t)) => MonadRunGtk (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

Methods

runGtk :: IO a -> ReflexGtkT t m a Source #

runGtk_ :: IO a -> ReflexGtkT t m () Source #

runGtkPromise :: IO a -> ReflexGtkT t m (ReflexGtkT t m a) Source #

type Ref (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host

type Ref (ReflexGtkT t m)
type Performable (ReflexGtkT t m) Source # 
Instance details

Defined in Reflex.GI.Gtk.Host