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

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.ReactiveValue

Contents

Description

This is a more general, cleaner interface that allows Model to Model synchronization and view to view.

It is meant to replace Hails.MVC.Controller.Reactive as soon as we do not need to provide an undefined value for the function reactiveValueOnCanRead.

Synopsis

Reactive values: common interface

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

Readable reactive values

Methods

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

reactiveValueRead :: a -> m b Source

class ReactiveValueWrite a b 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

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

Right-to-left

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

Bidirectional

Purely functional implementation

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

Lifting onto readable values

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

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

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

Lifting onto writeable values

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

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

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

Lift monadic operations

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

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

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

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.

Conditionals

Category theoretic definitions

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

Temporary: will be moved to Keera Hails' Reactive Values library.