reflex-0.6.2.3: Higher-order Functional Reactive Programming

Safe HaskellSafe
LanguageHaskell98

Reflex.PerformEvent.Class

Description

This module defines PerformEvent and TriggerEvent, which mediate the interaction between a Reflex-based program and the external side-effecting actions such as IO.

Synopsis

Documentation

class (Reflex t, Monad (Performable m), Monad m) => PerformEvent t m | m -> t where Source #

PerformEvent represents actions that can trigger other actions based on Events.

Associated Types

type Performable m :: * -> * Source #

The type of action to be triggered; this is often not the same type as the triggering action.

Methods

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

Perform the action contained in the given Event whenever the Event fires. Return the result in another Event. Note that the output Event will generally occur later than the input Event, since most Performable actions cannot be performed during Event propagation.

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

Like performEvent, but do not return the result. May have slightly better performance.

Instances
PerformEvent t m => PerformEvent t (ReaderT r m) Source # 
Instance details

Defined in Reflex.PerformEvent.Class

Associated Types

type Performable (ReaderT r m) :: Type -> Type Source #

Methods

performEvent :: Event t (Performable (ReaderT r m) a) -> ReaderT r m (Event t a) Source #

performEvent_ :: Event t (Performable (ReaderT r m) ()) -> ReaderT r m () Source #

PerformEvent t m => PerformEvent t (TriggerEventT t m) Source # 
Instance details

Defined in Reflex.TriggerEvent.Base

Associated Types

type Performable (TriggerEventT t m) :: Type -> Type Source #

PerformEvent t m => PerformEvent t (PostBuildT t m) Source # 
Instance details

Defined in Reflex.PostBuild.Base

Associated Types

type Performable (PostBuildT t m) :: Type -> Type Source #

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

Defined in Reflex.PerformEvent.Base

Associated Types

type Performable (PerformEventT t m) :: Type -> Type Source #

PerformEvent t m => PerformEvent t (EventWriterT t w m) Source # 
Instance details

Defined in Reflex.EventWriter.Base

Associated Types

type Performable (EventWriterT t w m) :: Type -> Type Source #

PerformEvent t m => PerformEvent t (QueryT t q m) Source # 
Instance details

Defined in Reflex.Query.Base

Associated Types

type Performable (QueryT t q m) :: Type -> Type Source #

Methods

performEvent :: Event t (Performable (QueryT t q m) a) -> QueryT t q m (Event t a) Source #

performEvent_ :: Event t (Performable (QueryT t q m) ()) -> QueryT t q m () Source #

PerformEvent t m => PerformEvent t (DynamicWriterT t w m) Source # 
Instance details

Defined in Reflex.DynamicWriter.Base

Associated Types

type Performable (DynamicWriterT t w m) :: Type -> Type Source #

PerformEvent t m => PerformEvent t (BehaviorWriterT t w m) Source # 
Instance details

Defined in Reflex.BehaviorWriter.Base

Associated Types

type Performable (BehaviorWriterT t w m) :: Type -> Type Source #

PerformEvent t m => PerformEvent t (RequesterT t request response m) Source # 
Instance details

Defined in Reflex.Requester.Base

Associated Types

type Performable (RequesterT t request response m) :: Type -> Type Source #

Methods

performEvent :: Event t (Performable (RequesterT t request response m) a) -> RequesterT t request response m (Event t a) Source #

performEvent_ :: Event t (Performable (RequesterT t request response m) ()) -> RequesterT t request response m () Source #

PerformEvent t m => PerformEvent (ProfiledTimeline t) (ProfiledM m) Source # 
Instance details

Defined in Reflex.Profiled

Associated Types

type Performable (ProfiledM m) :: Type -> Type Source #

performEventAsync :: (TriggerEvent t m, PerformEvent t m) => Event t ((a -> IO ()) -> Performable m ()) -> m (Event t a) Source #

Like performEvent, but the resulting Event occurs only when the callback (a -> IO ()) is called, not when the included action finishes.

NOTE: Despite the name, performEventAsync does not run its action in a separate thread - although the action is free to invoke forkIO and then call the callback whenever it is ready. This will work properly, even in GHCJS (which fully implements concurrency even though JavaScript does not have built in concurrency).