Re: [Haskell] Paper: The essence of dataflow programming

2005-09-26 Thread Einar Karttunen
On 26.09 01:01, David Menendez wrote:
 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

We add some nice combinators:


(-) :: Comonad co = (co a - co b) - (co b - co c) - co a - co c
a - b = b . a
infixr -

(--) :: Comonad co = (co a - co b) - (b - co b - co c) - co a - co c
a -- b = \co - let x = a co in b (counit x) x
infixr --

coreturn v = cobind (const v)


And define the simple state comonad:


data StateC st a = StateC (st - a) st

instance Comonad (StateC st) where
  counit (StateC f v) = f v
  cobind fun (StateC f v) = StateC (\v - fun (StateC f v)) v

get :: StateC st a - StateC st st
get (StateC _ st) = StateC id st

set :: st - StateC st a - StateC st a
set new (StateC fun _) = StateC fun new

modify :: (c - c) - StateC c a - StateC c a
modify mutator (StateC fun st) = StateC fun $ mutator st

runStateC fun v0 = let StateC a b = fun (StateC id v0) in (a b,b)


Now we can write comonadic code like monadic code:

foobar = get -- \x - coreturn (3*x)

test3 = get -- \x -
set 15  -
foobar  -- \y -
set x   -
coreturn (show y)


This looks very much like monadic code written with  and =.

A general Functor instance is easy (but non-haskell98):


instance Comonad w = Functor w where
  fmap f = cobind (f . counit)


- Einar Karttunen
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Paper: The essence of dataflow programming

2005-09-26 Thread Tarmo Uustalu

Dear Dave,

Thanks for the nice propaganda!

A few comments regarding the points you made in your message.

Ineffeciency of fibo-like programs: Your observations are true. But this is a 
comonadic interpreter analogous to the cbv monadic interpreter. One can also 
define an analogue to the cbn monadic interpreter. This is better than the 
cbv version on the n first Fibonacci numbers but worse on the nth number 
alone...

Zippers: Yes, of course! Streams are an infinite linear datastructure, but you 
can also do trees (eg decorated parse trees of a CFG). Such trees with a 
distinguished position are of course the zipper datatype and this is a comonad 
as well. And similarly to the comonadic approach to the semantics of dataflow 
languages one can give a comonadic structure eg to attribute grammar 
specifications (either purely synthesized attribute grammars or general 
attribute grammars). We've developed these ideas in a paper that was presented 
at TFP, see

http://www.cs.ioc.ee/~tarmo/papers/tfp05.pdf

(this is the symposium version, the full version is in preparation.)

To present the comonadic semantics of attribute grammar specifications neatly, 
one needs either GADTs or dependent types.

Best wishes,

Tarmo U


___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Paper: The essence of dataflow programming

2005-09-25 Thread David Menendez
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 

[Haskell] Paper: The essence of dataflow programming

2005-09-21 Thread Tarmo Uustalu

Dear Haskell subscribers,

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).

The paper will not be presented at TFP/ICFP/GPCE in Tallinn. A
trimmed-down version will appear in Proc. of APLAS 2005. The full 
text has been submitted.

Best wishes,

Tarmo Uustalu, Varmo Vene




___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell