[Haskell-cafe] catamorphisms and attribute grammars

Roman Cheplyaka roma at ro-che.info
Sun Jan 27 08:49:01 CET 2013


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 <chrisyco+haskell-cafe at gmail.com> [2013-01-27 20:20:07+1300]
> 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-Machine-Moore.html
> [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-Pipe-Common.html
> 
> Chris
> 
> On Sun, Jan 27, 2013 at 11:03 AM, Petr P <petr.mvd at gmail.com> 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 at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list