[Haskell-cafe] Annotations in abstract syntax tree

j.romildo at gmail.com j.romildo at gmail.com
Fri Apr 27 14:46:02 CEST 2012


On Fri, Apr 27, 2012 at 08:39:23AM -0300, romildo at malaquias.DHCP-GERAL wrote:
> On Thu, Apr 26, 2012 at 10:21:36AM +0200, José Pedro Magalhães wrote:
> > Hi Romildo,
> > 
> > If I understand correctly, you now want to add annotations to
> > mutually-recursive datatypes. The annotations package supports that.
> > Section 8 of our paper [1] gives an example of how to do that, and also
> > Chapter 6 of Martijn's MSc thesis [2].
> > 
> > Let me know if these references do not answer your question.
> 
> I am reading Martijn's MSc thesis and trying some code he presents. In
> secton 5.1 he presents catamorphisms over fixed points.
> 
> The code I am trying is attached.
> 
> When evaluating the expression
> 
>     cata exprEval (runExpr (1+2*3))
> 
> I am getting the following error:
> 
>     No instance for (Functor ExprF)
>       arising from a use of `cata'
>     Possible fix: add an instance declaration for (Functor ExprF)
>     In the expression: cata exprEval (runExpr (1 + 2 * 3))
>     In an equation for `it': it = cata exprEval (runExpr (1 + 2 * 3))
> 
> How should an instance of (Functor ExprF) be defined? It is not shown in
> the thesis.
[...] 
> type Id = String
> 
> data Op = Add | Sub | Mul | Div
>           deriving (Show)
> 
> data ExprF r = Num Double
>              | Var Id
>              | Bin Op r r
>                deriving (Show)

I could write the (Functor ExprF) instance:

  instance Functor ExprF where
    fmap f expr = case expr of
                    Num n -> Num n
                    Var v -> Var v
                    Bin op x y -> Bin op (f x) (f y)

Romildo



More information about the Haskell-Cafe mailing list