[Haskell-cafe] Data Flow Programming in FP

David Menendez dave at zednenem.com
Wed Jun 22 04:07:04 CEST 2011


On Tue, Jun 21, 2011 at 12:14 PM, Edward Kmett <ekmett at gmail.com> wrote:
> The essence of data flow programming describes how you can use comonads to
> model the semantics of dataflow languages.
>
> One of the best stops from there is probably, Dave Menendez's response on
> the Haskell mailing list back in 2005 summarized how one can move from
> building a semantics for dataflow programming using comonads to actually
> implementing dataflow programming directly using comonads. This is useful if
> you don't want to write a dataflow language compiler or interpreter, but
> instead just want to write some dataflow code in the middle of your program
> as an embedded domain-specific language.
>
> http://www.haskell.org/pipermail/haskell/2005-September/016502.html

Comonads are useful for describing dataflow operations and for making
simple implementations, but they can have serious performance problems
if your goal is to obtain intermediate results. Still, it's useful to
see what sorts of things are possible with comonads and how they
translate into other, more efficient implementations.

I should also note a few errors in my 2005 e-mail:

1. CoKleisli arrows are *not* an instance of ArrowApply, as they do
not satisfy the composition law. That is, app . arr ((h .) *** id) /=
h . app

2. Defining ArrowLoop does not require a zip operation. You can define
the instance like so:

instance Comonad c => ArrowLoop (Cokleisli c) where
    loop f = C $ fst . f'
        where
        f' = unC f . coextend (extract &&& snd . f')

This incidentally, was inspired by a more recent definition of cfix,

cfix :: Comonad f => (f (a,b) -> b) -> f a -> b
cfix f = f . coextend (\c -> (extract c, cfix f c))

(Exercise: define the cfix in my 2005 email in terms of this one, and
vice versa.)

3. You don't need cfix to write recursive comonadic code. For example,
pos (which is initially one and then increments), can be defined using
cfix:

pos :: History a -> Int
pos = cfix (\ctx -> 1 + 0 `fby` fmap snd ctx)

but it can also be defined using Haskell's recursion:

pos ctx = 1 + 0 `fby` pos ctx

4. Auto is not less powerful than Hist. In fact, any arrow in Hist can
be converted to Auto, and vice-versa. Similarly, Auto forms a monad in
the same way Hist does.

--
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>



More information about the Haskell-Cafe mailing list