|
FRP.Reactive.Reactive | Stability | experimental | Maintainer | conal@conal.net |
|
|
|
|
|
Description |
Simple reactive values. Adds some extra functionality on top of
FRP.Reactive.PrimReactive
|
|
Synopsis |
|
module FRP.Reactive.PrimReactive | | type TimeT = Double | | type ITime = Improving TimeT | | type Future = FutureG ITime | | traceF :: Functor f => (a -> String) -> f a -> f a | | type Event = EventG ITime | | withTimeE :: Ord t => EventG (Improving t) d -> EventG (Improving t) (d, t) | | withTimeE_ :: Ord t => EventG (Improving t) d -> EventG (Improving t) t | | atTime :: TimeT -> Event () | | atTimes :: [TimeT] -> Event () | | listE :: [(TimeT, a)] -> Event a | | zipE :: Ord t => (c, d) -> (EventG t c, EventG t d) -> EventG t (c, d) | | scanlE :: Ord t => (a -> b -> a) -> a -> EventG t b -> EventG t a | | monoidE :: (Ord t, Monoid o) => EventG t o -> EventG t o | | firstRestE :: Ord t => EventG t a -> (a, EventG t a) | | firstE :: Ord t => EventG t a -> a | | restE :: Ord t => EventG t a -> EventG t a | | remainderR :: Ord t => EventG t a -> ReactiveG t (EventG t a) | | snapRemainderE :: Ord t => EventG t b -> EventG t a -> EventG t (a, EventG t b) | | onceRestE :: Ord t => EventG t a -> EventG t (a, EventG t a) | | withPrevE :: Ord t => EventG t a -> EventG t (a, a) | | withPrevEWith :: Ord t => (a -> a -> b) -> EventG t a -> EventG t b | | withNextE :: Ord t => EventG t a -> EventG t (a, a) | | withNextEWith :: Ord t => (a -> a -> b) -> EventG t a -> EventG t b | | mealy :: Ord t => s -> (s -> s) -> EventG t b -> EventG t (b, s) | | mealy_ :: Ord t => s -> (s -> s) -> EventG t b -> EventG t s | | countE :: (Ord t, Num n) => EventG t b -> EventG t (b, n) | | countE_ :: (Ord t, Num n) => EventG t b -> EventG t n | | diffE :: (Ord t, Num n) => EventG t n -> EventG t n | | type Reactive = ReactiveG ITime | | snapshot_ :: Ord t => ReactiveG t b -> EventG t a -> EventG t b | | snapshot :: Ord t => ReactiveG t b -> EventG t a -> EventG t (a, b) | | whenE :: Ord t => EventG t a -> ReactiveG t Bool -> EventG t a | | scanlR :: Ord t => (a -> b -> a) -> a -> EventG t b -> ReactiveG t a | | monoidR :: (Ord t, Monoid a) => EventG t a -> ReactiveG t a | | eitherE :: Ord t => EventG t a -> EventG t b -> EventG t (Either a b) | | maybeR :: Ord t => EventG t a -> EventG t b -> ReactiveG t (Maybe a) | | flipFlop :: Ord t => EventG t a -> EventG t b -> ReactiveG t Bool | | countR :: (Ord t, Num n) => EventG t a -> ReactiveG t n | | splitE :: Ord t => EventG t b -> EventG t a -> EventG t (a, EventG t b) | | switchE :: Ord t => EventG t (EventG t a) -> EventG t a | | integral :: forall v t. (VectorSpace v, t ~ Scalar v, Num t) => t -> Event t -> Reactive v -> Reactive v | | sumR :: Ord t => AdditiveGroup v => EventG t v -> ReactiveG t v | | exact :: Improving a -> a | | batch :: TestBatch |
|
|
Documentation |
|
module FRP.Reactive.PrimReactive |
|
|
The type of finite time values.
|
|
|
Improving doubles, as used for time values in Event, Reactive,
and ReactiveB.
|
|
|
Type of future values. Specializes FutureG.
|
|
|
Trace the elements of a functor type.
|
|
Event
|
|
|
Events, specialized to improving doubles for time
|
|
|
Access occurrence times in an event. See withTimeGE for more
general notions of time.
withTimeE :: Event a -> Event (a, TimeT)
|
|
|
Access occurrence times in an event. Discard the rest. See also
withTimeE.
withTimeE_ :: Event a -> Event TimeT
|
|
|
Single-occurrence event at given time. See atTimes and atTimeG.
|
|
|
Event occuring at given times. See also atTime and atTimeG.
|
|
|
Convert a temporally monotonic list of timed values to an event. See also
the generalization listEG
|
|
|
Generate a pair-valued event, given a pair of initial values and a
pair of events. See also pair on Reactive. Not quite a zip,
because of the initial pair required.
|
|
|
Like scanl for events.
|
|
|
Accumulate values from a monoid-typed event. Specialization of
scanlE, using mappend and mempty.
|
|
|
Decompose an event into its first occurrence value and a remainder
event. See also firstE and restE.
|
|
|
Extract the first occurrence value of an event. See also
firstRestE and restE.
|
|
|
Extract the remainder an event, after its first occurrence. See also
firstRestE and firstE.
|
|
|
Remaining part of an event. See also withRestE.
|
|
|
Tack remainders a second event onto values of a first event. Occurs
when the first event occurs.
|
|
|
Convert an event into a single-occurrence event, whose occurrence
contains the remainder.
|
|
|
Pair each event value with the previous one. The second result is
the old one. Nothing will come out for the first occurrence of e,
but if you have an initial value a, you can do withPrevE (pure a
mappend e).
|
|
|
Same as withPrevE, but allow a function to combine the values.
Provided for convenience.
|
|
|
Pair each event value with the next one one. The second result is
the next one.
|
|
|
Same as withNextE, but allow a function to combine the values.
Provided for convenience.
|
|
|
Mealy-style state machine, given initial value and transition
function. Carries along event data. See also mealy_.
|
|
|
Mealy-style state machine, given initial value and transition
function. Forgetful version of mealy.
|
|
|
Count occurrences of an event, remembering the occurrence values.
See also countE_.
|
|
|
Count occurrences of an event, forgetting the occurrence values. See
also countE.
|
|
|
Difference of successive event occurrences. See withPrevE for a
trick to supply an initial previous value.
|
|
Reactive values
|
|
|
Reactive values, specialized to improving doubles for time
|
|
|
Like snapshot but discarding event data (often a is '()').
|
|
|
Snapshot a reactive value whenever an event occurs.
|
|
|
Filter an event according to whether a reactive boolean is true.
|
|
|
Like scanl for reactive values. See also scanlE.
|
|
|
Accumulate values from a monoid-valued event. Specialization of
scanlE, using mappend and mempty. See also monoidE.
|
|
|
Combine two events into one.
|
|
|
Start out blank (Nothing), latching onto each new a, and blanking
on each b. If you just want to latch and not blank, then use
mempty for lose.
|
|
|
Flip-flopping reactive value. Turns true when ea occurs and false
when eb occurs.
|
|
|
Count occurrences of an event. See also countE.
|
|
|
Partition an event into segments.
|
|
|
Switch from one event to another, as they occur. (Doesn't merge, as
join does.)
|
|
|
Euler integral.
|
|
|
|
Re-export
|
|
|
|
Tests
|
|
|
|
Produced by Haddock version 2.4.2 |