euphoria-0.8.0.0: Dynamic network FRP with events and continuous values

Safe HaskellNone
LanguageHaskell98

FRP.Euphoria.Event

Contents

Description

Event/discrete layer constructed on top of Elerea. The API is largely inspired by reactive-banana.

Synopsis

Events

data Event a Source #

Event a represents a stream of events whose occurrences carry a value of a. The event can have zero, one or more occurrences in a single network step.

Two event occurrences are said to be simultaneous iff they are within the same step. Simultaneous occurrences are ordered within a single event stream, but not across different event streams.

Instances

Functor Event Source # 

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

Apply Signal Event Source # 

Methods

(<@>) :: Signal (a -> b) -> Event a -> Event b Source #

(<@) :: Signal a -> Event b -> Event a Source #

Monoid (Event a) Source #

Event streams can be merged together. In case of simultaneous occurrences, occurrences from the left stream comes first.

Methods

mempty :: Event a #

mappend :: Event a -> Event a -> Event a #

mconcat :: [Event a] -> Event a #

SignalSet (Event a) Source # 
EasyApply (Signal (a -> b)) (Event a) (Event b) Source # 

Methods

(<~~>) :: Signal (a -> b) -> Event a -> Event b Source #

Creation

externalEvent :: (MonadSignalGen g, MonadIO m, MonadIO m') => m (g (Event a), a -> m' ()) Source #

Create an event that can be triggered as an IO action.

eachStep :: Signal a -> Event a Source #

eachStep sig is an event that occurs every step, having the same value as sig.

onCreation :: MonadSignalGen m => a -> m (Event a) Source #

onCreation x creates an event that occurs only once, immediately on creation.

signalToEvent :: Signal [a] -> Event a Source #

The inverse of eventToSignal.

Sampling

apply :: Signal (a -> b) -> Event a -> Event b Source #

Transform an event stream using a time-varying transformation function.

There is also an infix form <@>.

eventToSignal :: Event a -> Signal [a] Source #

eventToSignal evt is a signal whose value is the list of current occurrences of evt.

State accumulation

With these functions, any input event occurrence will affect the output immediately, without any delays.

stepperS :: MonadSignalGen m => a -> Event a -> m (Signal a) Source #

stepperS initial evt returns a signal whose value is the last occurrence of evt, or initial if there has been none.

accumS :: MonadSignalGen m => a -> Event (a -> a) -> m (Signal a) Source #

The basic construct to build a stateful signal. accumS initial evt returns a signal whose value is originally initial. For each occurrence of evt the value of the signal gets updated using the function.

Example:

If we have an event stream of numbers, (nums :: Event Int), then we can make a signal that remembers the sum of the numbers seen so far, as follows:

accumS 0 $ (+) <$> nums

accumSIO :: MonadSignalGen m => a -> Event (a -> IO a) -> m (Signal a) Source #

accumS with side-effecting updates.

accumE :: MonadSignalGen m => a -> Event (a -> a) -> m (Event a) Source #

accumE initial evt maintains an internal state just like accumS. It returns an event which occurs every time an update happens. The resulting event, once created, will have the same number of occurrences as evt each step.

accumEM :: MonadSignalGen m => s -> Event (s -> SignalGen s) -> m (Event s) Source #

Monadic version of accumE.

scanAccumE :: MonadSignalGen m => s -> Event (s -> (s, a)) -> m (Event a) Source #

A useful special case of accumE.

scanAccumEM :: MonadSignalGen m => s -> Event (s -> SignalGen (s, a)) -> m (Event a) Source #

A useful special case of accumEM.

Filtering and other list-like operations

filterE :: (a -> Bool) -> Event a -> Event a Source #

Filter an event stream.

justE :: Event (Maybe a) -> Event a Source #

Remove occurrences that are Nothing.

mapMaybeE :: (a -> Maybe b) -> Event a -> Event b Source #

Like mapMaybe over events.

flattenE :: Event [a] -> Event a Source #

Converts an event stream of lists into a stream of their elements. All elements of a list become simultaneous occurrences.

expandE :: Event a -> Event [a] Source #

Expand simultaneous events (if any)

withPrevE :: MonadSignalGen m => a -> Event a -> m (Event (a, a)) Source #

withPrevE initial evt is an Event which occurs every time evt occurs. Each occurrence carries a pair, whose first element is the value of the current occurrence of evt, and whose second element is the value of the previous occurrence of evt, or initial if there has been none.

dropE :: MonadSignalGen m => Int -> Event a -> m (Event a) Source #

dropE n evt returns an event, which behaves similarly to evt except that its first n occurrences are dropped.

dropWhileE :: MonadSignalGen m => (a -> Bool) -> Event a -> m (Event a) Source #

dropWhileE p evt returns an event, which behaves similarly to evt except that all its occurrences before the first one that satisfies p are dropped.

takeE :: MonadSignalGen m => Int -> Event a -> m (Event a) Source #

Take the first n occurrences of the event and discard the rest. It drops the reference to the original event after the first n occurrences are seen.

takeWhileE :: MonadSignalGen m => (a -> Bool) -> Event a -> m (Event a) Source #

Take the first occurrences satisfying the predicate and discard the rest. It drops the reference to the original event after the first non-satisfying occurrence is seen.

partitionEithersE :: MonadSignalGen m => Event (Either a b) -> m (Event a, Event b) Source #

Split a stream of Eithers into two, based on tags. This needs to be in SignalGen in order to memoise the intermediate result.

leftE :: Event (Either e a) -> Event e Source #

Keep occurrences which are Left.

rightE :: Event (Either e a) -> Event a Source #

Keep occurrences which are Right.

groupByE :: MonadSignalGen m => (a -> a -> Bool) -> Event a -> m (Event (Event a)) Source #

groupByE eqv evt creates a stream of event streams, each corresponding to a span of consecutive occurrences of equivalent elements in the original stream. Equivalence is tested using eqv.

groupWithInitialByE :: MonadSignalGen m => (a -> a -> Bool) -> Event a -> m (Event (a, Event a)) Source #

groupWithInitialByE eqv evt creates a stream of event streams, each corresponding to a span of consecutive occurrences of equivalent elements in the original stream. Equivalence is tested using eqv. In addition, each outer event occurrence contains the first occurrence of its inner event.

groupE :: (Eq a, MonadSignalGen m) => Event a -> m (Event (Event a)) Source #

Same as groupByE (==)

groupWithInitialE :: (Eq a, MonadSignalGen m) => Event a -> m (Event (a, Event a)) Source #

Same as groupWithInitialByE (==)

splitOnE :: MonadSignalGen m => Event () -> Event a -> m (Event [a]) Source #

For each Event () received, emit all a in a list since the last Event () was received. In the case of simultaneous a and '()' in a step, the a are included in the emitted list.

differentE :: (Eq a, MonadSignalGen m) => Event a -> m (Event a) Source #

Filter events to only those which are different than the previous event.

Other event operations

delayE :: MonadSignalGen m => Event a -> m (Event a) Source #

delayE evt creates an event whose occurrences are same as the occurrences of evt in the previous step.

dropStepE :: MonadSignalGen m => Event a -> m (Event a) Source #

Drops all events in this network step

mapEIO :: MonadSignalGen m => (t -> IO a) -> Event t -> m (Event a) Source #

Like mapM over events.

memoE :: MonadSignalGen m => Event a -> m (Event a) Source #

Memoization of events. See the doc for memo.

joinEventSignal :: Signal (Event a) -> Event a Source #

An event whose occurrences come from different event stream each step.

generatorE :: MonadSignalGen m => Event (SignalGen a) -> m (Event a) Source #

generatorE evt creates a subnetwork every time evt occurs.

Discrete signals

data Discrete a Source #

Discrete a is much like Signal a, but the user can get notified every time the value may have changed. See changesD.

Instances

Monad Discrete Source # 

Methods

(>>=) :: Discrete a -> (a -> Discrete b) -> Discrete b #

(>>) :: Discrete a -> Discrete b -> Discrete b #

return :: a -> Discrete a #

fail :: String -> Discrete a #

Functor Discrete Source # 

Methods

fmap :: (a -> b) -> Discrete a -> Discrete b #

(<$) :: a -> Discrete b -> Discrete a #

Applicative Discrete Source # 

Methods

pure :: a -> Discrete a #

(<*>) :: Discrete (a -> b) -> Discrete a -> Discrete b #

(*>) :: Discrete a -> Discrete b -> Discrete b #

(<*) :: Discrete a -> Discrete b -> Discrete a #

SignalSet (Discrete a) Source # 
EasyApply (Maybe (a -> b)) (Discrete a) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Maybe (a -> b) -> Discrete a -> Discrete (Maybe b) Source #

EasyApply (Discrete (a -> b)) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (Discrete (a -> b)) (Discrete a) (Discrete b) Source # 

Methods

(<~~>) :: Discrete (a -> b) -> Discrete a -> Discrete b Source #

EasyApply (Discrete (Maybe (a -> b))) (Discrete a) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (Maybe (a -> b)) -> Discrete a -> Discrete (Maybe b) Source #

EasyApply (Discrete (Maybe (a -> b))) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (Maybe (a -> b)) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (a -> b) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (a -> b) (Discrete a) (Discrete b) Source # 

Methods

(<~~>) :: (a -> b) -> Discrete a -> Discrete b Source #

Sampling Discretes

Signals can be sampled using apply or equivalently <@>. However, currently there are no corresponding functions for Discrete due to implementation difficulty. To sample a Discrete, you need to first convert it into a Signal using discreteToSignal.

Accumulation

stepperD :: MonadSignalGen m => a -> Event a -> m (Discrete a) Source #

Like stepperS, but creates a Discrete.

stepperMaybeD :: MonadSignalGen m => Event a -> m (Discrete (Maybe a)) Source #

Use Nothing to supply the initial value, and wrap the returned type in Maybe.

justD :: MonadSignalGen m => a -> Discrete (Maybe a) -> m (Discrete a) Source #

Given an initial value, filter out the Nothings.

accumD :: MonadSignalGen m => a -> Event (a -> a) -> m (Discrete a) Source #

Like accumS, but creates a Discrete.

Conversion into events

eachStepD :: MonadSignalGen m => Discrete a -> m (Event a) Source #

Discrete version of eachStep.

changesD :: Discrete a -> Event a Source #

changesD dis is an event that occurs when the value of dis may have changed. It never occurs more than once a step.

preservesD :: MonadSignalGen m => Discrete a -> m (Event a) Source #

Like changesD, but uses the current value in the Discrete even if it is not new.

Other discrete operations

snapshotD :: MonadSignalGen m => Discrete a -> m a Source #

snapshotD dis returns the current value of dis.

memoD :: MonadSignalGen m => Discrete a -> m (Discrete a) Source #

Memoization of discretes. See the doc for memo.

delayD :: MonadSignalGen m => a -> Discrete a -> m (Discrete a) Source #

Like delayS.

generatorD :: MonadSignalGen m => Discrete (SignalGen a) -> m (Discrete a) Source #

Like generatorS. A subnetwork is only created when the value of the discrete may have changed.

minimizeChanges :: (MonadSignalGen m, Eq a) => Discrete a -> m (Discrete a) Source #

minimizeChanges dis creates a Discrete whose value is same as dis. The resulting discrete is considered changed only if it is really changed.

discreteToSignal :: MonadSignalGen m => Discrete a -> m (Signal a) Source #

Converts a Discrete to an equivalent Signal.

freezeD :: MonadSignalGen m => Event () -> Discrete a -> m (Discrete a) Source #

freezeD fixEvent dis returns a discrete whose value is same as dis before fixEvent is activated first. Its value gets fixed once an occurrence of fixEvent is seen.

signalToDiscrete :: Signal a -> Discrete a Source #

Convert a Signal to an equivalent Discrete. The resulting discrete is always considered to 'possibly have changed'.

Signals

Application operators

class (Functor f, Functor g) => Apply f g where Source #

A generalization of Applicative where the lhs and the rhs can have different container types.

Minimal complete definition

(<@>)

Methods

(<@>) :: f (a -> b) -> g a -> g b infixl 4 Source #

(<@) :: f a -> g b -> g a infixl 4 Source #

Instances

Apply Signal Event Source # 

Methods

(<@>) :: Signal (a -> b) -> Event a -> Event b Source #

(<@) :: Signal a -> Event b -> Event a Source #

Convenience combinators for working with 'Discrete a' and 'Discrete (Maybe a)' in applicative style. You can choose the right one by representing what's on the left and right side of the operator with the following rules:

  • '-' is for Discrete a
  • '?' is for Discrete (Maybe a)

(<$?>) :: (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) infixl 4 Source #

(<?*?>) :: Discrete (Maybe (a -> b)) -> Discrete (Maybe a) -> Discrete (Maybe b) infixl 4 Source #

(<-*?>) :: Discrete (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) infixl 4 Source #

(<?*->) :: Discrete (Maybe (a -> b)) -> Discrete a -> Discrete (Maybe b) infixl 4 Source #

class EasyApply a b c | a b -> c where Source #

When using applicative style and mixing (Discrete a) and (Discrete (Maybe a)), EasyApply's <~~> will attempt to choose the right combinator. This is an experimental idea, and may be more trouble than it's worth in practice.

GHC will fail to find instances under various circumstances, such as when when anonymous functions are applied to tuples, so you will have to fall back to using explicit combinators.

Minimal complete definition

(<~~>)

Methods

(<~~>) :: a -> b -> c infixl 4 Source #

Instances

EasyApply (Maybe (a -> b)) (Discrete a) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Maybe (a -> b) -> Discrete a -> Discrete (Maybe b) Source #

EasyApply (Signal (a -> b)) (Event a) (Event b) Source # 

Methods

(<~~>) :: Signal (a -> b) -> Event a -> Event b Source #

EasyApply (Discrete (a -> b)) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (Discrete (a -> b)) (Discrete a) (Discrete b) Source # 

Methods

(<~~>) :: Discrete (a -> b) -> Discrete a -> Discrete b Source #

EasyApply (Discrete (Maybe (a -> b))) (Discrete a) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (Maybe (a -> b)) -> Discrete a -> Discrete (Maybe b) Source #

EasyApply (Discrete (Maybe (a -> b))) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: Discrete (Maybe (a -> b)) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (a -> b) (Discrete (Maybe a)) (Discrete (Maybe b)) Source # 

Methods

(<~~>) :: (a -> b) -> Discrete (Maybe a) -> Discrete (Maybe b) Source #

EasyApply (a -> b) (Discrete a) (Discrete b) Source # 

Methods

(<~~>) :: (a -> b) -> Discrete a -> Discrete b Source #

Switching

switchD :: (SignalSet s, MonadSignalGen m) => Discrete s -> m s Source #

switchD dis creates some signal-like thing whose value is same as the thing dis currently contains.

switchDE :: MonadSignalGen m => Discrete (Event a) -> m (Event a) Source #

switchDE selects the current Event stream contained in a Discrete

See switchD for a more general function.

switchDS :: MonadSignalGen m => Discrete (Signal a) -> m (Signal a) Source #

switchDS selects current Signal a of a Discrete.

See switchD for a more general function.

generatorD' :: (MonadSignalGen m, SignalSet s) => Discrete (SignalGen s) -> m s Source #

Executes a dynamic SignalGen in a convenient way.

generatorD' dis = generatorD dis >>= switchD

class SignalSet a where Source #

A class of signal-like types.

Minimal complete definition

basicSwitchD, memoizeSignalSet

Methods

basicSwitchD :: MonadSignalGen m => Discrete a -> m a Source #

Create a dynamically switched a. The returned value doesn't need to be properly memoized. The user should call switchD instead.

memoizeSignalSet :: MonadSignalGen m => a -> m a Source #

Memoize a signal set.

Instances

SignalSet (Signal a) Source # 
SignalSet (Discrete a) Source # 
SignalSet (Event a) Source # 
Monoid a => SignalSet (Update a) Source # 
(SignalSet a, SignalSet b) => SignalSet (a, b) Source # 

Methods

basicSwitchD :: MonadSignalGen m => Discrete (a, b) -> m (a, b) Source #

memoizeSignalSet :: MonadSignalGen m => (a, b) -> m (a, b) Source #

SignalSet (Collection k a) Source # 
(SignalSet a, SignalSet b, SignalSet c) => SignalSet (a, b, c) Source # 

Methods

basicSwitchD :: MonadSignalGen m => Discrete (a, b, c) -> m (a, b, c) Source #

memoizeSignalSet :: MonadSignalGen m => (a, b, c) -> m (a, b, c) Source #

(SignalSet a, SignalSet b, SignalSet c, SignalSet d) => SignalSet (a, b, c, d) Source # 

Methods

basicSwitchD :: MonadSignalGen m => Discrete (a, b, c, d) -> m (a, b, c, d) Source #

memoizeSignalSet :: MonadSignalGen m => (a, b, c, d) -> m (a, b, c, d) Source #

(SignalSet a, SignalSet b, SignalSet c, SignalSet d, SignalSet e) => SignalSet (a, b, c, d, e) Source # 

Methods

basicSwitchD :: MonadSignalGen m => Discrete (a, b, c, d, e) -> m (a, b, c, d, e) Source #

memoizeSignalSet :: MonadSignalGen m => (a, b, c, d, e) -> m (a, b, c, d, e) Source #

Evaluation control

forceD :: MonadSignalGen m => Discrete a -> m (Discrete a) Source #

Forces the value in a Discrete.

forceE :: MonadSignalGen m => Event a -> m (Event a) Source #

Like forceD, but for Event.

rnfD :: (NFData a, MonadSignalGen m) => Discrete a -> m (Discrete a) Source #

Completely evaluates the value in a Discrete.

rnfE :: (NFData a, MonadSignalGen m) => Event a -> m (Event a) Source #

Like rnfD, but for Event.

Debugging

Side-effecting trace functions

traceSignalT :: Show b => String -> (a -> b) -> Signal a -> Signal a Source #

traceEventT :: Show b => String -> (a -> b) -> Event a -> Event a Source #

traceDiscreteT :: Show b => String -> (a -> b) -> Discrete a -> Discrete a Source #

Testing