Copyright | (c) Atze van der Ploeg 2015 |
---|---|
License | BSD-style |
Maintainer | atzeus@gmail.org |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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)
- data BehaviorEnd x a = Until {}
- combineUntil :: (a -> b -> b) -> BehaviorEnd a x -> Behavior b -> Behavior b
- (.:) :: BehaviorEnd a x -> Behavior [a] -> Behavior [a]
- parList :: EvStream (BehaviorEnd b ()) -> Behavior (Behavior [b])
- till :: Swap b (BehaviorEnd x) => Behavior x -> b (Event a) -> (b :. BehaviorEnd x) a
- newtype (f :. g) x = Close {
- open :: f (g x)
- class (Monad f, Monad g) => Swap f g where
- swap :: g (f a) -> f (g a)
- liftLeft :: (Monad f, Monad g) => f x -> (f :. g) x
- liftRight :: Monad f => g x -> (f :. g) x
Until
data BehaviorEnd x a Source
(Monad b, Plan b) => Swap b (BehaviorEnd x) Source | |
Monad (BehaviorEnd x) Source | |
Functor (BehaviorEnd x) Source | |
Applicative (BehaviorEnd x) Source |
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
Composition of functors.
class (Monad f, Monad g) => Swap f g where Source
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