[Haskell] Paper: The essence of dataflow programming

David Menendez zednenem at psualum.com
Mon Sep 26 01:01:56 EDT 2005


Tarmo Uustalu writes:

| We would like to announce our new paper
| 
| The essence of dataflow programming
| 
| http://cs.ioc.ee/~tarmo/papers/essence.pdf
| 
| which describes a novel comonadic foundation of dataflow computing,
| incl. semantics of dataflow languages a la Lucid or Lustre. The
| central point is that comonads structure the context-dependence in
| dataflow paradigms in much the same way as monads organize
| effects. The paper was specifically written for functional
| programmers (as opposed to semanticists).

This is really cool!

For those who haven't read the above paper yet, it describes how to
structure an interpreter for a dataflow language using comonads, similar
to the way you can structure an interpreter for an impure language using
monads. Inspired, I've tried my hand at implementing some of the example
dataflow functions directly in Haskell. 

This message is literate Haskell code. It uses the arrow syntax in a few
places; these are just examples, so you may comment them out if you do
not have a recent-enough GHCi or an arrow syntax preprocessor.

> {-# OPTIONS -farrows #-}
> module Dataflow where
> import Prelude hiding (sum)
> import Control.Arrow

FIrst, a class for comonads:

> class Functor d => Comonad d where
>     extract :: d a -> a
>     coextend :: (d a -> b) -> d a -> d b

(In the paper, these are "counit" and "cobind".)

We'll also define the injection combinator from Kieburtz's paper[1]:

> (.>>) :: Functor d => d a -> b -> d b
> d .>> a = fmap (const a) d

As a simple example, the environment comonad:

> instance Functor ((,) e) where
>     fmap f (e,a) = (e, f a)
> 
> instance Comonad ((,) e) where
>     extract (e,a) = a
>     coextend f d@(e,a) = (e, f d)

This is closely related to the reader monad (in fact they are adjoint).

Given a comonad d, we can also create an arrow Cokleisli d:

> newtype Cokleisli d a b = Cokleisli { runCokleisli :: d a -> b }
>
> instance Comonad d => Arrow (Cokleisli d) where
>     arr f = Cokleisli (f . extract)
>     
>     Cokleisli f >>> Cokleisli g = Cokleisli (g . coextend f)
>     
>     first (Cokleisli f) = Cokleisli $ 
>                              \d -> (f (fmap fst d), snd (extract d))

Here is something I did not expect to find: you can *apply* cokleisli
arrows.

> instance Comonad d => ArrowApply (Cokleisli d) where
>     app = Cokleisli $ 
>              \d -> runCokleisli (fst (extract d)) (fmap snd d)
>
> instance Comonad d => ArrowChoice (Cokleisli d) where
>     left = leftApp

Now, I haven't proven that this implementation of app satisfies the
relevant laws, but assuming it does, it raises some questions. Most of
the papers dealing with arrows state that instances of ArrowApply are
equivalent to monads, but cokleisli arrows allow you to do dataflow
programming, which cannot be done with monads. That may or may not be a
contradiction.

One point to consider is that the type "Cokleisli d a b" (or "d a -> b")
is isomorphic to "Reader (d a) b" (or "d a -> b"), and "Reader (d a)" is
a monad.

Thus:

> instance Functor (Cokleisli d a) where
>     fmap f (Cokleisli k) = Cokleisli (f . k)
>    
> instance Monad (Cokleisli d a) where
>     return a = Cokleisli (const a)
>     
>     Cokleisli k >>= f = Cokleisli $ \d -> runCokleisli (f (k d)) d

I don't know whether this is significant or useful.


To describe synchronous dataflow languages (where values can depend on
the past, but not the future), Uustalu and Vene employ the non-empty
list comonad, which I will call History.

> data History a = First a | History a :> a
> infixl 4 :>
> 
> runHistory :: (History a -> b) -> [a] -> [b]
> runHistory f []     = []
> runHistory f (a:as) = run (First a) as
>     where
>     run az []     = [f az]
>     run az (a:as) = f az : run (az :> a) as
> 
> instance Functor History where
>     fmap f (First a) = First (f a)
>     fmap f (as :> a) = fmap f as :> f a
> 
> instance Comonad History where
>     extract (First a) = a
>     extract (as :> a) = a
>     
>     coextend f d@(First a) = First (f d)
>     coextend f d@(as :> a) = coextend f as :> f d

We'll also need a combinator "fby", which is short for "followed by". In
a dataflow language, you might write:

    pos = 0 fby (pos + 1)

Which means that pos is initially zero, and its next value is always the
current value plus one. The fby combinator is easy to define,

> fby :: a -> History a -> a
> a0 `fby` First a = a0
> a0 `fby` (az :> a) = extract az

but defining pos requires recursion.

Thanks to Yampa[2], we know how this sort of thing looks when written in
arrow notation:

> type Hist = Cokleisli History
> 
> posA :: Hist a Integer
> posA = proc _ -> do
>         rec
>             x <- delay 0 -< x + 1
>         returnA -< x

We can define 'delay' using 'fby'.

> delay :: a -> Hist a a
> delay a0 = Cokleisli $ \d -> a0 `fby` d

Now we just need a instance for ArrowLoop. This was tricky, but I
eventually managed to reverse-engineer the ArrowLoop instance for
Kleisli arrows and come up with a counterpart.

I rely on two combinators. The first, czip, is from the paper and
expresses the ability to merge two comonadic values.

> class Comonad d => ComonadZip d where
>     czip :: d a -> d b -> d (a,b)
> 
> instance ComonadZip History where
>     czip (First a) (First b) = First (a,b)
>     czip (as :> a) (First b) = First (a,b)
>     czip (First a) (bs :> b) = First (a,b)
>     czip (as :> a) (bs :> b) = czip as bs :> (a,b)

The second, cfix, corresponds to mfix.

> cfix :: Comonad d => d (d a -> a) -> a
> cfix d = extract d (coextend cfix d)

Interestingly enough, cfix, unlike mfix, is defined for all comonads.

Finally, ArrowLoop:

> instance ComonadZip d => ArrowLoop (Cokleisli d) where
>     loop (Cokleisli f) = Cokleisli (fst . cfix . coextend f')
>         where
>         f' da db = f (czip da (fmap snd db))

Assuming, again, that this satisfies the appropriate laws, it suggests
that ComonadZip is in some way dual to MonadFix.

Now, a quick function for running History arrows:

> runHist :: Hist a b -> [a] -> [b]
> runHist = runHistory . runCokleisli

and presto:

    *Dataflow> runHist posA [(),(),()]
    [0,1,2]

Having defined pos as an arrow, can we define it using the comonad
combinators directly? Yes, but it doesn't look as pretty:

> pos :: History a -> Int
> pos d = cfix $ d .>> \dpos -> 0 `fby` fmap (+1) dpos

Using (.>>), we inject a function into the comonad, giving us a value of
the necessary type for cfix.

This is noisy, but you can see the similiarities to the original code,

    pos = 0 fby (pos + 1)

Fortunately, the arrow notation lets us work in a more intuitive fashion
without having to define a comonadic counterpart to the mdo syntax.

Here are some other examples from the paper.

> -- sum x = x + (0 fby sum x)
> 
> sumA :: Num a => Hist a a
> sumA = proc x -> do
>     rec
>         prev_sum <- delay 0 -< sum
>         let sum = x + prev_sum
>     returnA -< sum
>
> sum :: Num a => History a -> a
> sum dx = extract dx + 0 `fby` coextend sum dx
> 
> -- diff x = x - 0 fby x
> 
> diffA :: Num a => Hist a a
> diffA = proc x -> do
>     prev_x <- delay 0 -< x
>     returnA -< x - prev_x
>     
> diff :: Num a => History a -> a
> diff dx = extract dx - 0 `fby` dx
> 
> -- ini x = x fby ini x
>
> ini :: History a -> a
> ini x = extract x `fby` coextend ini x
> 
> iniA :: Hist a a
> iniA = proc x -> do
>     rec i <- delay x -<< i
>     returnA -< i
>
> -- fibo = 0 fby (fibo + (1 fby fibo))
>
> fibo :: Num b => History a -> b
> fibo d = cfix $ d .>> \dfibo ->
>     0 `fby` coextend (\dfibo -> extract dfibo + 1 `fby` dfibo) dfibo
>
> fiboA :: Num b => Hist a b
> fiboA = proc _ -> do
>     rec
>         fib <- delay 0 -< next_fib
>         next_fib <- delay 1 -< fib + next_fib
>     returnA -< fib

Note that the versions written with straight comonads are sometimes
simpler than those written using arrow syntax. In particular, iniA
involves arrow recursion and arrow application, while ini gets by with
regular recursion and application.


While the Fibonacci series examples work, they are extremely
inefficient. As it happens, it is possible to write O(n) versions:

> fibo' :: Num b => History a -> b
> fibo' d = fst $ cfix $
>         d .>> \dfibo -> (0,1) `fby` fmap (\(x,x') -> (x',x+x')) dfibo
> 
> fiboA' :: Num b => Hist a b
> fiboA' = proc _ -> do
>     rec (fib, next_fib) <- delay (0,1) -< (next_fib, fib + next_fib)
>     returnA -< fib

I initially thought the problem with fiboA was the double use of delay,
but this code--essentially a hand translation of fiboA into raw arrow
combinators--is also O(n).

> fiboA'' :: Num b => Hist a b
> fiboA'' = loop $ 
>     second ((arr snd >>> delay 0) &&& (arr (uncurry (+)) >>> delay 1))
>     >>> arr (\(_,d) -> (fst d,d))

I'm not sure why fiboA'' works so much better than fiboA.

To clarify, fibo' and its relatives are O(n) for calculating the nth
Fibonacci number *only*. If you want to find the first n Fibonacci
numbers, then they are O(n^2). This is because each calculation occurs
separately. Consider the signature of sum:

    sum :: Num a => History a -> a

The use of fby makes it seem like sum is using past calculations, but in
fact there can be no communication from one invocation of sum to the
next. Thus, sum is O(n), but "coextend sum" is O(n^2).


There are other arrows with better performance. Consider the automaton
arrow[3]:

    newtype Auto a b = Auto (a -> (b, Auto a b))

This is an instance of Arrow, ArrowChoice, and ArrowLoop. It supports a
delay operation, just like the History comonad and its relatives. Its
versions of posA, sumA, and fiboA are O(n). To gain that performance, it
gives up power: Auto is not an instance of ArrowApply, meaning iniA has
to be defined as a primitive.


I don't have any conclusion, except to say that it's great to see some
examples of comonads in action. I had heard comonads described as
encapsulating context-dependence, much as monads encapsulate effects,
but I never had a good sense of what that meant before now.

Actually, the context-dependence angle also suggests a connection to
zippers[4]. I guess that's my next project.


[1] <http://citeseer.ist.psu.edu/kieburtz99codata.html>
[2] <http://haskell.org/yampa/>
[3] <http://haskell.org/arrows/arrows/Control.Arrow.Transformer.
Automaton.html>
[4] <http://haskell.org/hawiki/TheZipper>
-- 
David Menendez <zednenem at psualum.com> <http://www.eyrie.org/~zednenem/>


More information about the Haskell mailing list