functional-arrow-0.0: Combinators that allow for a more functional/monadic style of Arrow programming

Control.Arrow.Monad

Description

This module is an attempt to simplify the use of arrow combinators. If I have f :: arrow a b, then subsequent arrows can only access the b, but often I also want to access the a. Thus I often write

 f &&& arr id :: arrow a (b,a)  .

If I repeat this, it yields

 g &&& arr id <<< f &&& arr id :: arrow a (c,(b,a))
 h &&& arr id <<< g &&& arr id <<< f &&& arr id :: arrow a (d,(c,(b,a)))  .

However accessing the particular inputs of type d, c, b from within h and g is cumbersome. Thus I wrote a little support for this style of arrow programming. First I use HList instead of nested pairs. Using type level Peano numbers and reverse HList index access I can use the same expression (say listen x) in both g and h although in both contexts they refer to different HLists. E.g. g expects the b input at the HList head, whereas h gets it one position later.

Synopsis

Documentation

(>>>=) :: (Arrow arrow, HLength list n) => arrow list a -> (n -> arrow (HCons a list) b) -> arrow list bSource

This bind-like operator allows you to a share an interim arrow result between various following arrow inputs.

Instead of

 mix <<<  id &&& delay  <<< lowpass

you can write

 (\x -> HL.hCons x HL.hNil) ^>>
 ((HL.hHead ^>> lowpass) >>>= \x ->
      mix <<<  listen x &&& (delay <<< listen x))

(=<<<) :: (Arrow arrow, HLength list n) => (n -> arrow (HCons a list) b) -> arrow list a -> arrow list bSource

class (HNat x, HNat y, HNat z) => HAdd x y z | x y -> z, x z -> ySource

Instances

HNat x => HAdd HZero x x 
HAdd x y z => HAdd (HSucc x) y (HSucc z) 

listen :: (Arrow arrow, HLength list len, HAdd n m len, HLookupByHNat m list a) => n -> arrow list aSource