frpnow-0.15: Principled practical FRP

Copyright(c) Atze van der Ploeg 2015
LicenseBSD-style
Maintaineratzeus@gmail.org
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Control.FRPNow.BehaviorEnd

Contents

Description

The until abstraction, and related definitions.

A value of type BehaviorEnd is a behavior and an ending event. This also forms a monad, such that we can write

do a1 `Until` e1
   b1 `Until` e2

for behaviors consisting of multiple phases. This concept is similar to "Monadic FRP" (Haskell symposium 2013, van der Ploeg) and the Task monad abstraction (Lambda in motion: Controlling robots with haskell, Peterson, Hudak and Elliot, PADL 1999)

Synopsis

Until

data BehaviorEnd x a Source

Constructors

Until 

Fields

behavior :: Behavior x
 
end :: Event a
 

combineUntil :: (a -> b -> b) -> BehaviorEnd a x -> Behavior b -> Behavior b Source

Combine the behavior of the Until and the other behavior until the with the given function until the end event happens.

(.:) :: BehaviorEnd a x -> Behavior [a] -> Behavior [a] Source

Add the values in the behavior of the Until to the front of the list until the end event happsens.

parList :: EvStream (BehaviorEnd b ()) -> Behavior (Behavior [b]) Source

Given an eventstream that spawns behaviors with an end, returns a behavior with list of the values of currently active behavior ends.

Derived monads

The monad for Until is a bit restrictive, because we cannot sample other behaviors in this monad. For this reason we also define a monad for (Behavior :. Until x), where :. is functor composition, which can sample other monads. This relies on the swap construction from "Composing monads", Mark Jones and Luc Duponcheel.

till :: Swap b (BehaviorEnd x) => Behavior x -> b (Event a) -> (b :. BehaviorEnd x) a Source

Like Until, but the event can now be generated by a behavior (Behavior (Event a)) or even (Now (Event a)).

Name is not "until" to prevent a clash with until.

newtype (f :. g) x Source

Composition of functors.

Constructors

Close 

Fields

open :: f (g x)
 

Instances

Swap f g => Monad ((:.) f g) 
(Functor a, Functor b) => Functor ((:.) a b) 
(Applicative b, Applicative e) => Applicative ((:.) b e) 
(Swap b e, Sample b) => Sample ((:.) b e) 

class (Monad f, Monad g) => Swap f g where Source

Methods

swap :: g (f a) -> f (g a) Source

Swap the composition of two monads. Laws (from Composing Monads, Jones and Duponcheel)

swap . fmap (fmap f) == fmap (fmap f) . swap
swap . return        == fmap unit
swap . fmap return   == return
prod . fmap dorp     == dorp . prod 
           where prod = fmap join . swap
                 dorp = join . fmap swap

Instances

Plan b => Swap b Event 
(Monad b, Plan b) => Swap b (BehaviorEnd x) 

liftLeft :: (Monad f, Monad g) => f x -> (f :. g) x Source

Lift a value from the left monad into the composite monad.

liftRight :: Monad f => g x -> (f :. g) x Source

Lift a value from the right monad into the composite monad.