rhine-0.5.0.0: Functional Reactive Programming with type-level clocks

Safe HaskellNone
LanguageHaskell2010

FRP.Rhine.Clock.Realtime.Event

Description

This module provides two things:

  • Clocks that tick whenever events arrive on a Chan, and useful utilities.
  • Primitives to emit events.

Note that _events work across multiple clocks_, i.e. it is possible (and encouraged) to emit events from signals on a different clock than the event clock. This is in line with the Rhine philosophy that _event sources are clocks_.

Events even work well across separate threads, and constitute the recommended way of communication between threads in Rhine.

A simple example using events and threads can be found in rhine-examples.

Synopsis

Documentation

data EventClock event Source #

A clock that ticks whenever an event is emitted. It is not yet bound to a specific channel, since ideally, the correct channel is created automatically by runEventChanT. If you want to create the channel manually and bind the clock to it, use eventClockOn.

Constructors

EventClock 
Instances
Semigroup (EventClock event) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Event

Methods

(<>) :: EventClock event -> EventClock event -> EventClock event #

sconcat :: NonEmpty (EventClock event) -> EventClock event #

stimes :: Integral b => b -> EventClock event -> EventClock event #

MonadIO m => Clock (EventChanT event m) (EventClock event) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Event

Associated Types

type Time (EventClock event) :: * Source #

type Tag (EventClock event) :: * Source #

Methods

initClock :: EventClock event -> RunningClockInit (EventChanT event m) (Time (EventClock event)) (Tag (EventClock event)) Source #

type Time (EventClock event) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Event

type Time (EventClock event) = UTCTime
type Tag (EventClock event) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Event

type Tag (EventClock event) = event

type EventChanT event m = ReaderT (Chan event) m Source #

A monad transformer in which events can be emitted onto a Chan.

withChan :: Chan event -> EventChanT event m a -> m a Source #

Escape the EventChanT layer by explicitly providing a channel over which events are sent. Often this is not needed, and runEventChanT can be used instead.

runEventChanT :: MonadIO m => EventChanT event m a -> m a Source #

Create a channel across which events can be communicated, and subsequently execute all event effects on this channel.

Ideally, this action is run _outside_ of flow, e.g. runEventChanT $ flow myRhine. This way, exactly one channel is created.

Caution: Don't use this with liftMSFPurer, since it would create a new channel every tick. Instead, create one chan :: Chan c, e.g. with newChan, and then use withChanS.

withChanS :: Monad m => Chan event -> ClSF (EventChanT event m) cl a b -> ClSF m cl a b Source #

Remove ("run") an EventChanT layer from the monad stack by passing it explicitly the channel over which events are sent.

This is usually only needed if you can't use runEventChanT to create the channel. Typically, create a chan :: Chan c in your main program before the main loop (e.g. flow) would be run, then, by using this function, pass the channel to every behaviour or ClSF that wants to emit events, and, by using eventClockOn, to every clock that should tick on the event.

emit :: MonadIO m => event -> EventChanT event m () Source #

Emit a single event. This causes every EventClock on the same monad to tick immediately.

Be cautious when emitting events from a signal clocked by an EventClock. Nothing prevents you from emitting more events than are handled, causing the event buffer to grow indefinitely.

emitS :: MonadIO m => ClSF (EventChanT event m) cl event () Source #

Emit an event on every tick.

emitSMaybe :: MonadIO m => ClSF (EventChanT event m) cl (Maybe event) () Source #

Emit an event whenever the input value is Just event.

emit' :: (NFData event, MonadIO m) => event -> EventChanT event m () Source #

Like emit, but completely evaluates the event before emitting it.

emitS' :: (NFData event, MonadIO m) => ClSF (EventChanT event m) cl event () Source #

Like emitS, but completely evaluates the event before emitting it.

emitSMaybe' :: (NFData event, MonadIO m) => ClSF (EventChanT event m) cl (Maybe event) () Source #

Like emitSMaybe, but completely evaluates the event before emitting it.

eventClockOn :: MonadIO m => Chan event -> HoistClock (EventChanT event m) m (EventClock event) Source #

Create an event clock that is bound to a specific event channel. This is usually only useful if you can't apply runEventChanT to the main loop (see withChanS).

concurrentlyWithEvents :: (Time cl1 ~ Time cl2, Clock (EventChanT event IO) cl1, Clock (EventChanT event IO) cl2) => Schedule (EventChanT event IO) cl1 cl2 Source #

Given two clocks with an EventChanT layer directly atop the IO monad, you can schedule them using concurrent GHC threads, and share the event channel.

Typical use cases:

  • Different subevent selection clocks (implemented i.e. with Select) on top of the same main event source.
  • An event clock and other event-unaware clocks in the IO monad, which are lifted using liftClock.

newChan :: IO (Chan a) #

Build and returns a new instance of Chan.