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.


Cheers,
Pedro

[1] http://www.dreixel.net/research/pdf/gss.pdf
[2] http://martijn.van.steenbergen.nl/projects/Selections.pdf

On Thu, Apr 26, 2012 at 10:07, <j.romildo@gmail.com> wrote:
Hello.

I need to annotate abstract syntax tree with additional information in a
compiler.

Using the Annotations package[1] I have written the following small
program:

 import Annotations.F.Annotated
 import Annotations.F.Fixpoints

 data ExprF r
   = Num Double
   | Var String
   | Add r r
   | Sub r r
   | Mul r r
   | Div r r
   deriving (Eq,Show)

 type BareExpr = Fix ExprF

 e :: BareExpr
 e = In (Mul (In (Num 5))
             (In (Add (In (Var "x"))
                      (In (Num 8)))))


 type ValExpr = Fix (Ann Double ExprF)

 type Memory = [(String,Double)]

 eval :: Memory -> BareExpr -> ValExpr
 eval _ (In (Num x))   = In (Ann x (Num x))
 eval m (In (Var x))   = let y = case lookup x m of
                                   Just k -> k
                                   Nothing -> 0
                         in In (Ann y (Var x))
 eval m (In (Add x y)) = op m (+) Add x y
 eval m (In (Sub x y)) = op m (-) Sub x y
 eval m (In (Mul x y)) = op m (*) Mul x y
 eval m (In (Div x y)) = op m (/) Div x y

 op m f k x y = let x'@(In (Ann v1 _)) = eval m x
                    y'@(In (Ann v2 _)) = eval m y
                in In (Ann (f v1 v2) (k x' y'))


With these definitions we can represent simple arithmetic expressions
and we can also evaluate them, annotating each node in the abstract
syntax tree with its corresponding value.

Now I want to add statements to this toy language. One statement may be
a print statement containing an expression whose value is to be printed,
an assign statement containing an identifier and an expression, or a
compound statement containing two statements to be executed in sequence.

How the data types for statements can be defined?

How a function to execute an statement anotating its node with the
corresponding state (memory plus output) after its execution can be
defined?

Without annotations the type of statements could be:

 data Stm
   = PrintStm Expr
   | AssignStm String Expr
   | CompoundStm Stm Stm

How to enable annotations in this case? Note that Stm uses both Expr and Stm.


[1]  http://hackage.haskell.org/package/Annotations


Romildo

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe