keera-hails-reactivevalues-0.1.2.1: Haskell on Rails - Reactive Values

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.ReactiveValue

Contents

Description

Reactive Values are typed mutable variables with a change notification mechanism.

They are defined by providing a way to read the value, a way to change it, and a way to install an event listener when the value has changed.

RVs are pruposely defined in an abstract way, as a type class. GUI toolkits, for instance, can use existing event-handling installing mechanisms to enclose widget attributes as Reactive Values, without the need for an extra layer.

RVs are complemented with Relation-building functions, which enable pairing RVs during execution so that they are kept in sync for the duration of the program.

This module only defines RVs and operations on them. For connections to existing backends (GUIs, devices, files, network, FRP), see https://github.com/keera-studios/keera-hails

Synopsis

Reactive values: common interface for all RVs

class ReactiveValueRead a b m | a -> b, a -> m where Source

Readable reactive values

Methods

reactiveValueOnCanRead :: a -> m () -> m () Source

reactiveValueRead :: a -> m b Source

class ReactiveValueWrite a b m | a -> b, a -> m where Source

Writable reactive values

Methods

reactiveValueWrite :: a -> b -> m () Source

class (ReactiveValueRead a b m, ReactiveValueWrite a b m) => ReactiveValueReadWrite a b m Source

Read-write reactive values

Reactive rules (data dependency/passing building combinators)

(=:>) :: Monad m => (ReactiveValueRead a b m, ReactiveValueWrite c b m) => a -> c -> m () infix 9 Source

Priorities so that we can write them infix without parenthesising

Left to right RV synchronisation function. If the value on the left changes, the one on the right is updated accordingly.

(<:=) :: Monad m => (ReactiveValueRead a b m, ReactiveValueWrite c b m) => c -> a -> m () infix 9 Source

Right-to-left RV synchronisation function. If the value on the right changes, the one on the left is updated accordingly.

(=:=) :: Monad m => (ReactiveValueReadWrite a b m, ReactiveValueReadWrite c b m) => a -> c -> m () infix 9 Source

Bidirectional synchronisation. When either value changes, the other is updated accordingly.

Purely functional implementation of RVs.

Setters, getters and notifiers

type FieldGetter m a = m a Source

type FieldSetter m a = a -> m () Source

type FieldNotifier m a = m () -> m () Source

Concrete types implementing the above interface

Activatable reactive values (producing units)

Creating RVs based on other RVs

Lifting onto readable values

initRW :: Monad m => a -> ReactiveFieldRead m a Source

TODO: Bad name. Should be eliminated or extended with a setter.

Lifting onto readable values

liftR :: (Monad m, ReactiveValueRead a b m) => (b -> c) -> a -> ReactiveFieldRead m c Source

Lift a transformation onto a RV. Note that this creates a new RV, it does not modify the existing RV.

(<^>) :: (Monad m, ReactiveValueRead a b m) => (b -> c) -> a -> ReactiveFieldRead m c Source

Shorter name for liftR

liftR2 :: (Monad m, ReactiveValueRead a b m, ReactiveValueRead c d m) => (b -> d -> e) -> a -> c -> ReactiveFieldRead m e Source

Lift a transformation onto two RVs. Note that this creates a new RV, it does not modify the existing RVs. When either RV changes, the new one triggers a change.

liftR3 :: (Monad m, ReactiveValueRead a b m, ReactiveValueRead c d m, ReactiveValueRead e f m) => (b -> d -> f -> g) -> a -> c -> e -> ReactiveFieldRead m g Source

Lift a transformation onto three RVs. Note that this creates a new RV, it does not modify the existing RVs. When either RV changes, the new one triggers a change.

liftMR :: (Monad m, ReactiveValueRead a b m) => (b -> m c) -> a -> ReactiveFieldRead m c Source

Lift a parameterised monadic transformation onto an RV.

Same as lifting join . f?

Lifting onto writeable values

constW :: (Monad m, ReactiveValueWrite v a m) => a -> v -> ReactiveFieldWrite m b Source

Create a constant writable RV.

liftW :: (Monad m, ReactiveValueWrite a b m) => (c -> b) -> a -> ReactiveFieldWrite m c Source

Lift a transformation onto an RV. This creates a new RV, it does not actually modify the old RV (when this one is written to, so will be the old one, but both will keep existing somewhat independently).

liftW2 :: (Monad m, ReactiveValueWrite a b m, ReactiveValueWrite d e m) => (c -> (b, e)) -> a -> d -> ReactiveFieldWrite m c Source

Lift a transformation onto two RVs. This creates a new RV, it does not actually modify the old RVs (when this one is written to, so will be the old ones, but both will keep existing somewhat independently).

(&&&) :: (Monad m, ReactiveValueWrite a b m, ReactiveValueWrite c b m) => a -> c -> ReactiveFieldWrite m b Source

Binary writable replicator.

r1 &&& r2 = liftW2 (x -> (x,x)) r1 r2

liftMW :: (Monad m, ReactiveValueWrite a b m) => (c -> m b) -> a -> ReactiveFieldWrite m c Source

Lift a parameterised monadic transformation onto an RV.

readOnly :: ReactiveValueRead r a m => r -> ReactiveFieldRead m a Source

Make a RW RV read only

writeOnly :: ReactiveValueWrite r a m => r -> ReactiveFieldWrite m a Source

Make a RW RV write only

Lift monadic actions/sinks (setters) and sources (getters)

Lifting (sink) computations into writable RVs.

wrapMW :: (a -> m ()) -> ReactiveFieldWrite m a Source

Wrap a monadic computation in a writable reactive value.

wrapDo :: m () -> ReactiveFieldWrite m a Source

Wrap a monadic computation in a writable reactive value. It discards the written value and executes the operation.

Note: Because the value is discarded, the resulting RV is polymorphic in the value that may be written to it. Using wrapDo_ may save you some extra type signatures.

wrapDo_ :: m () -> ReactiveFieldWrite m () Source

Wrap a monadic computation in a writable reactive value of type unit. It discards the written value and executes the operation.

Lifting (source) computations into readable RVs.

wrapMR :: m a -> (m () -> m ()) -> ReactiveFieldRead m a Source

Wrap an reading operation and an notification installer in a readable reactive value.

wrapMRPassive :: Monad m => m a -> ReactiveFieldRead m a Source

Wrap an reading operation into an RV. Because there is no way to detect changes, the resulting RV is passive (does not push updates).

eventR :: Monad m => (m () -> m ()) -> ReactiveFieldRead m () Source

Wrap event-handler installers in RVs

Lifting onto read-write values

Bijections

newtype BijectiveFunc a b Source

Constructors

BijectiveFunc 

Fields

unBijectiveFunc :: (a -> b, b -> a)
 

bijection :: (a -> b, b -> a) -> BijectiveFunc a b Source

direct :: BijectiveFunc a b -> a -> b Source

inverse :: BijectiveFunc a b -> b -> a Source

involution :: (a -> a) -> Involution a Source

Actual lifting

Modifying reactive values (applying modification transformations)

modRW :: (Monad m, ReactiveValueReadWrite a b m) => (b -> c -> b) -> a -> ReactiveFieldWrite m c Source

Lifting modification functions

reactiveValueModify :: (Monad m, ReactiveValueReadWrite a b m) => a -> (b -> b) -> m () Source

Merging

lMerge :: (Monad m, ReactiveValueRead a v m, ReactiveValueRead b v m) => a -> b -> ReactiveFieldRead m v Source

Left merge (give priority to the value on the left)

rMerge :: (Monad m, ReactiveValueRead a v m, ReactiveValueRead b v m) => a -> b -> ReactiveFieldRead m v Source

Right merge (give priority to the value on the left)

Deactivating reactive values

passivelyR :: (Monad m, ReactiveValueRead a b m) => a -> ReactiveFieldRead m b Source

Turning an active RV into a passive one (does not propagate changes) Note that this does not really affect the RV itself, only produces a new RV that will not propagate changes. So, if used in a reactive relation, values will not get propagated when they change. It is useful in combination with lifts, to achieve things similar to Yampa's tagging, but this might be more general.

governingR :: (ReactiveValueRead a b m, ReactiveValueRead c d m) => a -> c -> ReactiveFieldRead m d Source

A form of binary readable lifting that passifies the second RV but reads exclusively from it.

governingR r1 r2 = rMerge r1 (passively r2)

Conditionals

guardRO' :: (Monad m, ReactiveValueRead c a m) => c -> (a -> Bool) -> ReactiveFieldRead m a Source