
Dear Haskellers, I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor. [1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass: -- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ... -- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ... -- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count' Then we can compute the average in a single pass like runHylo avg' treeAnamorphism seed My experiments together with the example are available at https://github .com/ppetr/recursion-attributes I wonder, is there an existing library that expresses this idea? Best regards, Petr Pudlak

* Petr P
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor.
...
My experiments together with the example are available at https://github .com/ppetr/recursion-attributes
Very nice! This can be generalized to arbitrary arrows: {-# LANGUAGE ExistentialQuantification #-} import Prelude hiding (id) import Control.Arrow import Control.Applicative import Control.Category data F from to b c = forall d . F (from b d) (to d c) instance (Arrow from, Arrow to) => Functor (F from to b) where fmap f x = pure f <*> x instance (Arrow from, Arrow to) => Applicative (F from to b) where pure x = F (arr $ const x) id F from1 to1 <*> F from2 to2 = F (from1 &&& from2) (to1 *** to2 >>> arr (uncurry id)) Now your construction is a special case where 'from' is the category of f-algebras and 'to' is the usual (->) category. I wonder what's a categorical interpretation of F itself. Roman

Roman, this is interesting. Is this arrow generalization in some library
already? And does it have a name?
Best regards,
Petr Pudlak
2013/1/27 Roman Cheplyaka
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact,
* Petr P
[2013-01-26 23:03:51+0100] they form an applicative functor.
...
My experiments together with the example are available at https://github .com/ppetr/recursion-attributes
Very nice! This can be generalized to arbitrary arrows:
{-# LANGUAGE ExistentialQuantification #-}
import Prelude hiding (id) import Control.Arrow import Control.Applicative import Control.Category
data F from to b c = forall d . F (from b d) (to d c)
instance (Arrow from, Arrow to) => Functor (F from to b) where fmap f x = pure f <*> x
instance (Arrow from, Arrow to) => Applicative (F from to b) where pure x = F (arr $ const x) id F from1 to1 <*> F from2 to2 = F (from1 &&& from2) (to1 *** to2 >>> arr (uncurry id))
Now your construction is a special case where 'from' is the category of f-algebras and 'to' is the usual (->) category.
I wonder what's a categorical interpretation of F itself.
Roman

On Sun, Jan 27, 2013 at 12:20:25AM +0000, Roman Cheplyaka wrote:
Very nice! This can be generalized to arbitrary arrows:
{-# LANGUAGE ExistentialQuantification #-}
import Prelude hiding (id) import Control.Arrow import Control.Applicative import Control.Category
data F from to b c = forall d . F (from b d) (to d c)
instance (Arrow from, Arrow to) => Functor (F from to b) where fmap f x = pure f <*> x
instance (Arrow from, Arrow to) => Applicative (F from to b) where pure x = F (arr $ const x) id F from1 to1 <*> F from2 to2 = F (from1 &&& from2) (to1 *** to2 >>> arr (uncurry id))
You only require that from b is Applicative, so that in turn can be generalized: data F g to c = forall d . F (g d) (to d c) instance (Applicative g, Arrow to) => Functor (F g to) where fmap f x = pure f <*> x instance (Applicative g, Arrow to) => Applicative (F g to) where pure x = F (pure x) id F from1 to1 <*> F from2 to2 = F ((,) <$> from1 <*> from2) (to1 *** to2 >>> arr (uncurry id))
I wonder what's a categorical interpretation of F itself.
It's a variety of left Kan extension (cf section 5 of "Constructing Applicative Functors" at MPC'2012).

Hi Petr,
Congratulations -- you've just implemented a Moore machine! [1]
I posted something very much like this just last year [2]. It's a very
common pattern in Haskell, forming the basis of coroutines and
iteratees and many other things.
Edward Kmett includes it in his machines package [3]. His variation,
like mine, hides the state inside a closure, removing the need for
existentials. pipes 2.0 contains one implemented as a free monad [4].
[1] http://en.wikipedia.org/wiki/Moore_machine
[2] http://hackage.haskell.org/packages/archive/machines/0.2.3/doc/html/Data-Mac...
[3] http://www.haskell.org/pipermail/haskell-cafe/2012-May/101460.html
[4] http://hackage.haskell.org/packages/archive/pipes/2.0.0/doc/html/Control-Pip...
Chris
On Sun, Jan 27, 2013 at 11:03 AM, Petr P
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor.
[1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler
To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass:
-- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ...
-- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ...
-- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count'
Then we can compute the average in a single pass like
runHylo avg' treeAnamorphism seed
My experiments together with the example are available at https://github.com/ppetr/recursion-attributes
I wonder, is there an existing library that expresses this idea?
Best regards, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Chris,
While the two things solve similar problems and have other similarities,
they are still quite different.
It's hard to call Petr's type a machine — there's no dynamics in it. It's
just a pair of an f-algebra and finalizer. Values of your type return
themselves — it is exactly this recursion that makes them "machines".
And the problem solved are different. Catamorphisms are not the same as
folds in the sense of Data.Foldable. Folds get elements one at a time,
while a catamorphism sees the structure of the tree.
For instance, it is possible to write an evaluator for an expression AST
using catamorphisms, but not using Moore machines[*], because you won't
know what the operations are.
[*] without linearizing the tree beforehand
Roman
* Chris Wong
Hi Petr,
Congratulations -- you've just implemented a Moore machine! [1]
I posted something very much like this just last year [2]. It's a very common pattern in Haskell, forming the basis of coroutines and iteratees and many other things.
Edward Kmett includes it in his machines package [3]. His variation, like mine, hides the state inside a closure, removing the need for existentials. pipes 2.0 contains one implemented as a free monad [4].
[1] http://en.wikipedia.org/wiki/Moore_machine [2] http://hackage.haskell.org/packages/archive/machines/0.2.3/doc/html/Data-Mac... [3] http://www.haskell.org/pipermail/haskell-cafe/2012-May/101460.html [4] http://hackage.haskell.org/packages/archive/pipes/2.0.0/doc/html/Control-Pip...
Chris
On Sun, Jan 27, 2013 at 11:03 AM, Petr P
wrote: Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor.
[1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler
To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass:
-- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ...
-- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ...
-- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count'
Then we can compute the average in a single pass like
runHylo avg' treeAnamorphism seed
My experiments together with the example are available at https://github.com/ppetr/recursion-attributes
I wonder, is there an existing library that expresses this idea?
Best regards, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Chris,
thanks for insightful links. At the first glance, I think the main
difference is that machines and iteratees process streams of data, while
catamorphisms work on general recursive data structures. (I used "count" +
"sum" in the example, which could lead to the impression that it's list
oriented.)
However, it seems to me that there is some connection between
cata/anamorphisms and free (co)monads generated by a functor. I'm just
guessing - perhaps using such a monad in a monadic pipe would lead to a
similar result?
BTW, while it seems that using existentials in by Cata data type is
natural, I'd like to know if I could do it without them. If you have any
ideas, please let me know.
Best regards,
Petr
PS: Is there actually anything left that ekmett hasn't implemented?
2013/1/27 Chris Wong
Hi Petr,
Congratulations -- you've just implemented a Moore machine! [1]
I posted something very much like this just last year [2]. It's a very common pattern in Haskell, forming the basis of coroutines and iteratees and many other things.
Edward Kmett includes it in his machines package [3]. His variation, like mine, hides the state inside a closure, removing the need for existentials. pipes 2.0 contains one implemented as a free monad [4].
[1] http://en.wikipedia.org/wiki/Moore_machine [2] http://hackage.haskell.org/packages/archive/machines/0.2.3/doc/html/Data-Mac... [3] http://www.haskell.org/pipermail/haskell-cafe/2012-May/101460.html [4] http://hackage.haskell.org/packages/archive/pipes/2.0.0/doc/html/Control-Pip...
Chris
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact,
On Sun, Jan 27, 2013 at 11:03 AM, Petr P
wrote: they form an applicative functor.
[1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler
To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass:
-- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ...
-- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ...
-- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count'
Then we can compute the average in a single pass like
runHylo avg' treeAnamorphism seed
My experiments together with the example are available at https://github.com/ppetr/recursion-attributes
I wonder, is there an existing library that expresses this idea?
Best regards, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You have applied the so-called banana-split theorem, as described e.g. in http://www.cs.ox.ac.uk/jeremy.gibbons/publications/acmmpc-calcfp.pdf
Indeed you are right in noticing the correspondence between AG's and catamorphims; actually I see AG's as a domain specific language for constructing algebras.
Since we believe in embedded domain specific languages we have developed a library for constructing attribute grammars in Haskell, which is described in our ICFP paper:
@inproceedings{1596586,
Address = {New York, NY, USA},
Author = {Viera, Marcos and Swierstra, S. Doaitse and Swierstra, Wouter},
Booktitle = {ICFP '09: Proceedings of the 14th ACM SIGPLAN international conference on Functional programming},
Date-Added = {2009-10-05 22:06:26 +0200},
Date-Modified = {2009-10-05 22:06:26 +0200},
Doi = {http://doi.acm.org/10.1145/1596550.1596586},
Isbn = {978-1-60558-332-7},
Location = {Edinburgh, Scotland},
Pages = {245--256},
Publisher = {ACM},
Title = {Attribute grammars fly first-class: how to do aspect oriented programming in Haskell},
Year = {2009}}
where you will find the problem you are solving done using the library.
On March 8 2013 Marcos Viera hopes to defend his Ph.D. thesis at Utrecht University. His thesis contains the progress we have made in this area in recent years. You can find it at the bottom op the page; amongst others you can use the UUAGC nowadays to generate this code form uuagc input.
http://www.cs.uu.nl/wiki/bin/view/Center/PhDs
Doaitse Swierstra
On Jan 26, 2013, at 23:03 , Petr P
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor.
[1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler
To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass:
-- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ...
-- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ...
-- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count'
Then we can compute the average in a single pass like
runHylo avg' treeAnamorphism seed
My experiments together with the example are available at https://github.com/ppetr/recursion-attributes
I wonder, is there an existing library that expresses this idea?
Best regards, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Patrick Bahr does something very similar in Modular Tree Automata [1], also noting the relation to attribute grammars. It's implemented in the compdata package [2]. [1] Patrick Bahr, Modular Tree Automata (MPC 2012), http://dx.doi.org/10.1007/978-3-642-31113-0_14 [2] http://hackage.haskell.org/package/compdata / Emil 2013-01-26 23:03, Petr P skrev:
Dear Haskellers,
I read some stuff about attribute grammars recently [1] and how UUAGC [2] can be used for code generation. I felt like this should be possible inside Haskell too so I did some experiments and I realized that indeed catamorphisms can be represented in such a way that they can be combined together and all run in a single pass over a data structure. In fact, they form an applicative functor.
[1] http://www.haskell.org/haskellwiki/Attribute_grammar [2] Utrecht University Attribute Grammar Compiler
To give an example, let's say we want to compute the average value of a binary tree. If we compute a sum first and then count the elements, the whole tree is retained in memory (and moreover, deforestation won't happen). So it's desirable to compute both values at once during a single pass:
-- Count nodes in a tree. count' :: (Num i) => CataBase (BinTree a) i count' = ...
-- Sums all nodes in a tree. sum' :: (Num n) => CataBase (BinTree n) n sum' = ...
-- Computes the average value of a tree. avg' :: (Fractional b) => CataBase (BinTree b) b avg' = (/) <$> sum' <*> count'
Then we can compute the average in a single pass like
runHylo avg' treeAnamorphism seed
My experiments together with the example are available at https://github.com/ppetr/recursion-attributes
I wonder, is there an existing library that expresses this idea?
Best regards, Petr Pudlak
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Chris Wong
-
Doaitse Swierstra
-
Emil Axelsson
-
Petr P
-
Roman Cheplyaka
-
Ross Paterson