Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module provides the interface for hosting Reflex
engines. This
should only be necessary if you're writing a binding or some other library
that provides a core event loop.
Synopsis
- class (Reflex t, MonadReflexCreateTrigger t (HostFrame t), MonadSample t (HostFrame t), MonadHold t (HostFrame t), MonadFix (HostFrame t), MonadSubscribeEvent t (HostFrame t)) => ReflexHost t where
- type EventTrigger t :: * -> *
- type EventHandle t :: * -> *
- type HostFrame t :: * -> *
- class (Reflex t, Monad m) => MonadSubscribeEvent t m | m -> t where
- subscribeEvent :: Event t a -> m (EventHandle t a)
- class (ReflexHost t, Applicative m, Monad m) => MonadReadEvent t m | m -> t where
- readEvent :: EventHandle t a -> m (Maybe (m a))
- class (Applicative m, Monad m) => MonadReflexCreateTrigger t m | m -> t where
- newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> m (Event t a)
- newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> m (EventSelector t k)
- class (ReflexHost t, MonadReflexCreateTrigger t m, MonadSubscribeEvent t m, MonadReadEvent t (ReadPhase m), MonadSample t (ReadPhase m), MonadHold t (ReadPhase m)) => MonadReflexHost t m | m -> t where
- type ReadPhase m :: * -> *
- fireEventsAndRead :: [DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a
- runHostFrame :: HostFrame t a -> m a
- fireEvents :: MonadReflexHost t m => [DSum (EventTrigger t) Identity] -> m ()
- newEventWithTriggerRef :: (MonadReflexCreateTrigger t m, MonadRef m, Ref m ~ Ref IO) => m (Event t a, Ref m (Maybe (EventTrigger t a)))
- fireEventRef :: (MonadReflexHost t m, MonadRef m, Ref m ~ Ref IO) => Ref m (Maybe (EventTrigger t a)) -> a -> m ()
- fireEventRefAndRead :: (MonadReflexHost t m, MonadRef m, Ref m ~ Ref IO) => Ref m (Maybe (EventTrigger t a)) -> a -> EventHandle t b -> m (Maybe b)
Documentation
class (Reflex t, MonadReflexCreateTrigger t (HostFrame t), MonadSample t (HostFrame t), MonadHold t (HostFrame t), MonadFix (HostFrame t), MonadSubscribeEvent t (HostFrame t)) => ReflexHost t Source #
Framework implementation support class for the reflex implementation
represented by t
.
type EventTrigger t :: * -> * Source #
type EventHandle t :: * -> * Source #
Instances
HasSpiderTimeline x => ReflexHost (SpiderTimeline x) Source # | |
Defined in Reflex.Spider.Internal type EventTrigger (SpiderTimeline x) :: Type -> Type Source # type EventHandle (SpiderTimeline x) :: Type -> Type Source # | |
ReflexHost t => ReflexHost (ProfiledTimeline t) Source # | |
Defined in Reflex.Profiled type EventTrigger (ProfiledTimeline t) :: Type -> Type Source # type EventHandle (ProfiledTimeline t) :: Type -> Type Source # type HostFrame (ProfiledTimeline t) :: Type -> Type Source # |
class (Reflex t, Monad m) => MonadSubscribeEvent t m | m -> t where Source #
Monad in which Events can be subscribed
. This forces all underlying
event sources to be initialized, so that the event will fire whenever it
ought to. Events must be subscribed before they are read using readEvent
subscribeEvent :: Event t a -> m (EventHandle t a) Source #
Subscribe to an event and set it up if needed.
This function will create a new EventHandle
from an Event
. This handle
may then be used via readEvent
in the read callback of
fireEventsAndRead
.
If the event wasn't subscribed to before (either manually or through a
dependent event or behavior) then this function will cause the event and
all dependencies of this event to be set up. For example, if the event was
created by newEventWithTrigger
, then it's callback will be executed.
It's safe to call this function multiple times.
Instances
class (ReflexHost t, Applicative m, Monad m) => MonadReadEvent t m | m -> t where Source #
Monad that allows to read events' values.
readEvent :: EventHandle t a -> m (Maybe (m a)) Source #
Read the value of an Event
from an EventHandle
(created by calling
subscribeEvent
).
After event propagation is done, all events can be in two states: either
they are firing with some value or they are not firing. In the former
case, this function returns Just act
, where act
in an action to read
the current value of the event. In the latter case, the function returns
Nothing
.
This function is normally used in the calllback for fireEventsAndRead
.
Instances
HasSpiderTimeline x => MonadReadEvent (SpiderTimeline x) (ReadPhase x) Source # | |
Defined in Reflex.Spider.Internal readEvent :: EventHandle (SpiderTimeline x) a -> ReadPhase x (Maybe (ReadPhase x a)) Source # | |
MonadReadEvent t m => MonadReadEvent (ProfiledTimeline t) (ProfiledM m) Source # | |
Defined in Reflex.Profiled readEvent :: EventHandle (ProfiledTimeline t) a -> ProfiledM m (Maybe (ProfiledM m a)) Source # |
class (Applicative m, Monad m) => MonadReflexCreateTrigger t m | m -> t where Source #
A monad where new events feed from external sources can be created.
newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> m (Event t a) Source #
Creates a root Event
(one that is not based on any other event).
When a subscriber first subscribes to an event (building another event that depends on the subscription) the given callback function is run and passed a trigger. The callback function can then set up the event source in IO. After this is done, the callback function must return an accompanying teardown action.
Any time between setup and teardown the trigger can be used to fire the
event, by passing it to fireEventsAndRead
.
Note: An event may be set up multiple times. So after the teardown action is executed, the event may still be set up again in the future.
newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> m (EventSelector t k) Source #
Instances
class (ReflexHost t, MonadReflexCreateTrigger t m, MonadSubscribeEvent t m, MonadReadEvent t (ReadPhase m), MonadSample t (ReadPhase m), MonadHold t (ReadPhase m)) => MonadReflexHost t m | m -> t where Source #
MonadReflexHost
designates monads that can run reflex frames.
fireEventsAndRead :: [DSum (EventTrigger t) Identity] -> ReadPhase m a -> m a Source #
Propagate some events firings and read the values of events afterwards.
This function will create a new frame to fire the given events. It will then update all dependent events and behaviors. After that is done, the given callback is executed which allows to read the final values of events and check whether they have fired in this frame or not.
All events that are given are fired at the same time.
This function is typically used in the main loop of a reflex framework implementation. The main loop waits for external events to happen (such as keyboard input or a mouse click) and then fires the corresponding events using this function. The read callback can be used to read output events and perform a corresponding response action to the external event.
runHostFrame :: HostFrame t a -> m a Source #
Run a frame without any events firing.
This function should be used when you want to use sample
and hold
when
no events are currently firing. Using this function in that case can
improve performance, since the implementation can assume that no events are
firing when sample
or hold
are called.
This function is commonly used to set up the basic event network when the application starts up.
Instances
fireEvents :: MonadReflexHost t m => [DSum (EventTrigger t) Identity] -> m () Source #
Like fireEventsAndRead
, but without reading any events.
newEventWithTriggerRef :: (MonadReflexCreateTrigger t m, MonadRef m, Ref m ~ Ref IO) => m (Event t a, Ref m (Maybe (EventTrigger t a))) Source #
Create a new event and store its trigger in an IORef
while it's active.
An event is only active between the set up (when it's first subscribed to)
and the teardown phases (when noboby is subscribing the event anymore). This
function returns an Event and an IORef
. As long as the event is active, the
IORef
will contain Just
the event trigger to trigger this event. When the
event is not active, the IORef
will contain Nothing
. This allows event
sources to be more efficient, since they don't need to produce events when
nobody is listening.
fireEventRef :: (MonadReflexHost t m, MonadRef m, Ref m ~ Ref IO) => Ref m (Maybe (EventTrigger t a)) -> a -> m () Source #
Fire the given trigger if it is not Nothing
.
fireEventRefAndRead :: (MonadReflexHost t m, MonadRef m, Ref m ~ Ref IO) => Ref m (Maybe (EventTrigger t a)) -> a -> EventHandle t b -> m (Maybe b) Source #
Fire the given trigger if it is not Nothing
, and read from the given
EventHandle
.