| Stability | experimental |
|---|---|
| Maintainer | conal@conal.net |
FRP.Reactive.Reactive
Contents
Description
Simple reactive values. Adds some extra functionality on top of FRP.Reactive.PrimReactive
- module FRP.Reactive.PrimReactive
- type ImpBounds t = Improving (AddBounds t)
- exactNB :: ImpBounds t -> t
- type TimeT = Double
- type ITime = ImpBounds TimeT
- type Future = FutureG ITime
- traceF :: Functor f => (a -> String) -> f a -> f a
- type Event = EventG ITime
- withTimeE :: Ord t => EventG (ImpBounds t) d -> EventG (ImpBounds t) (d, t)
- withTimeE_ :: Ord t => EventG (ImpBounds t) d -> EventG (ImpBounds t) t
- atTime :: TimeT -> Event ()
- atTimes :: [TimeT] -> Event ()
- listE :: [(TimeT, a)] -> Event a
- zipE :: (Ord t, Bounded t) => (c, d) -> (EventG t c, EventG t d) -> EventG t (c, d)
- scanlE :: (Ord t, Bounded t) => (a -> b -> a) -> a -> EventG t b -> EventG t a
- monoidE :: (Ord t, Bounded t, Monoid o) => EventG t o -> EventG t o
- firstRestE :: (Ord t, Bounded t) => EventG t a -> (a, EventG t a)
- firstE :: (Ord t, Bounded t) => EventG t a -> a
- restE :: (Ord t, Bounded t) => EventG t a -> EventG t a
- remainderR :: (Ord t, Bounded t) => EventG t a -> ReactiveG t (EventG t a)
- snapRemainderE :: (Ord t, Bounded t) => EventG t b -> EventG t a -> EventG t (a, EventG t b)
- onceRestE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, EventG t a)
- withPrevE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, a)
- withPrevEWith :: (Ord t, Bounded t) => (a -> a -> b) -> EventG t a -> EventG t b
- withNextE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, a)
- withNextEWith :: (Ord t, Bounded t) => (a -> a -> b) -> EventG t a -> EventG t b
- mealy :: (Ord t, Bounded t) => s -> (s -> s) -> EventG t b -> EventG t (b, s)
- mealy_ :: (Ord t, Bounded t) => s -> (s -> s) -> EventG t b -> EventG t s
- countE :: (Ord t, Bounded t, Num n) => EventG t b -> EventG t (b, n)
- countE_ :: (Ord t, Bounded t, Num n) => EventG t b -> EventG t n
- diffE :: (Ord t, Bounded t, AffineSpace a) => EventG t a -> EventG t (Diff a)
- type Reactive = ReactiveG ITime
- snapshot_ :: (Ord t, Bounded t) => ReactiveG t b -> EventG t a -> EventG t b
- snapshot :: (Ord t, Bounded t) => ReactiveG t b -> EventG t a -> EventG t (a, b)
- whenE :: (Ord t, Bounded t) => EventG t a -> ReactiveG t Bool -> EventG t a
- scanlR :: (Ord t, Bounded t) => (a -> b -> a) -> a -> EventG t b -> ReactiveG t a
- monoidR :: (Ord t, Bounded t, Monoid a) => EventG t a -> ReactiveG t a
- eitherE :: (Ord t, Bounded t) => EventG t a -> EventG t b -> EventG t (Either a b)
- maybeR :: (Ord t, Bounded t) => EventG t a -> EventG t b -> ReactiveG t (Maybe a)
- flipFlop :: (Ord t, Bounded t) => EventG t a -> EventG t b -> ReactiveG t Bool
- countR :: (Ord t, Bounded t, Num n) => EventG t a -> ReactiveG t n
- splitE :: (Ord t, Bounded t) => EventG t b -> EventG t a -> EventG t (a, EventG t b)
- switchE :: (Ord t, Bounded t) => EventG t (EventG t a) -> EventG t a
- integral :: forall v t. (VectorSpace v, AffineSpace t, Scalar v ~ Diff t) => t -> Event t -> Reactive v -> Reactive v
- sumR :: (Ord t, Bounded t) => AdditiveGroup v => EventG t v -> ReactiveG t v
- exact :: Improving a -> a
- batch :: TestBatch
Documentation
module FRP.Reactive.PrimReactive
Event
withTimeE :: Ord t => EventG (ImpBounds t) d -> EventG (ImpBounds t) (d, t)Source
Access occurrence times in an event. See withTimeGE for more
general notions of time.
withTimeE :: Event a -> Event (a, TimeT)
withTimeE_ :: Ord t => EventG (ImpBounds t) d -> EventG (ImpBounds t) tSource
Access occurrence times in an event. Discard the rest. See also
withTimeE.
withTimeE_ :: Event a -> Event TimeT
listE :: [(TimeT, a)] -> Event aSource
Convert a temporally monotonic list of timed values to an event. See also
the generalization listEG
scanlE :: (Ord t, Bounded t) => (a -> b -> a) -> a -> EventG t b -> EventG t aSource
Like scanl for events.
firstE :: (Ord t, Bounded t) => EventG t a -> aSource
Extract the first occurrence value of an event. See also
firstRestE and restE.
restE :: (Ord t, Bounded t) => EventG t a -> EventG t aSource
Extract the remainder an event, after its first occurrence. See also
firstRestE and firstE.
remainderR :: (Ord t, Bounded t) => EventG t a -> ReactiveG t (EventG t a)Source
Remaining part of an event. See also withRestE.
snapRemainderE :: (Ord t, Bounded t) => EventG t b -> EventG t a -> EventG t (a, EventG t b)Source
Tack remainders a second event onto values of a first event. Occurs when the first event occurs.
onceRestE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, EventG t a)Source
Convert an event into a single-occurrence event, whose occurrence contains the remainder.
withPrevE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, a)Source
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)
withPrevEWith :: (Ord t, Bounded t) => (a -> a -> b) -> EventG t a -> EventG t bSource
Same as withPrevE, but allow a function to combine the values.
Provided for convenience.
withNextE :: (Ord t, Bounded t) => EventG t a -> EventG t (a, a)Source
Pair each event value with the next one one. The second result is the next one.
withNextEWith :: (Ord t, Bounded t) => (a -> a -> b) -> EventG t a -> EventG t bSource
Same as withNextE, but allow a function to combine the values.
Provided for convenience.
mealy :: (Ord t, Bounded t) => s -> (s -> s) -> EventG t b -> EventG t (b, s)Source
Mealy-style state machine, given initial value and transition
function. Carries along event data. See also mealy_.
mealy_ :: (Ord t, Bounded t) => s -> (s -> s) -> EventG t b -> EventG t sSource
Mealy-style state machine, given initial value and transition
function. Forgetful version of mealy.
countE :: (Ord t, Bounded t, Num n) => EventG t b -> EventG t (b, n)Source
Count occurrences of an event, remembering the occurrence values.
See also countE_.
countE_ :: (Ord t, Bounded t, Num n) => EventG t b -> EventG t nSource
Count occurrences of an event, forgetting the occurrence values. See
also countE.
diffE :: (Ord t, Bounded t, AffineSpace a) => EventG t a -> EventG t (Diff a)Source
Difference of successive event occurrences. See withPrevE for a
trick to supply an initial previous value.
Reactive values
snapshot_ :: (Ord t, Bounded t) => ReactiveG t b -> EventG t a -> EventG t bSource
Like snapshot but discarding event data (often a is '()').
snapshot :: (Ord t, Bounded t) => ReactiveG t b -> EventG t a -> EventG t (a, b)Source
Snapshot a reactive value whenever an event occurs.
whenE :: (Ord t, Bounded t) => EventG t a -> ReactiveG t Bool -> EventG t aSource
Filter an event according to whether a reactive boolean is true.
eitherE :: (Ord t, Bounded t) => EventG t a -> EventG t b -> EventG t (Either a b)Source
Combine two events into one.
flipFlop :: (Ord t, Bounded t) => EventG t a -> EventG t b -> ReactiveG t BoolSource
Flip-flopping reactive value. Turns true when ea occurs and false
when eb occurs.
countR :: (Ord t, Bounded t, Num n) => EventG t a -> ReactiveG t nSource
Count occurrences of an event. See also countE.
splitE :: (Ord t, Bounded t) => EventG t b -> EventG t a -> EventG t (a, EventG t b)Source
Partition an event into segments.
switchE :: (Ord t, Bounded t) => EventG t (EventG t a) -> EventG t aSource
Switch from one event to another, as they occur. (Doesn't merge, as
join does.)
integral :: forall v t. (VectorSpace v, AffineSpace t, Scalar v ~ Diff t) => t -> Event t -> Reactive v -> Reactive vSource
Euler integral.