Forgot the attachment.

Romildo
--- Begin Message ---
On Mon, Jul 19, 2010 at 01:51:57PM -0400, Job Vranish wrote:
> Martijn van Steenbergen has a good blog post that describes the method I
> generally use:
> http://martijn.van.steenbergen.nl/journal/2010/06/24/generically-adding-position-information-to-a-datatype/
> 
> In his example he annotates the expression tree with position information,
> but you can use the same method to add type annotations, or whatever you
> want.

After a quick read at Martijn blog article I've written the attached
test program, which works.

But I am not succeeding in deriving Show for the data types. Any help?

Romildo

> 2010/7/19 José Romildo Malaquias <j.romi...@gmail.com>
> 
> > Hello.
> >
> > In his book "Modern Compilder Implementation in ML", Appel presents a
> > compiler project for the Tiger programming language where type checking
> > and intermediate code generation are intrinsically coupled.
> >
> > There is a function
> >
> >  transExp :: Absyn.Exp -> (Tree.Exp,Types.Type)
> >
> > that do semantic analysis, translating an expression to the Tree
> > intermediate representation language and also do type checking,
> > calculating the type of the expression.
> >
> > Maybe the compiler can be made more didatic if these phases are separate
> > phases of compilation.
> >
> > The type checker would annotate the abstract syntax tree (ast) with type
> > annotations, that could be used later by the translater to intermediate
> > representation.
> >
> > In an imperative language probably each relevant ast node would have a
> > field for the type annotation, and the type checker would assign the
> > type of the node to this field after computing it.
> >
> > I am writing here to ask suggestions on how to annotate an ast with
> > types (or any other information that would be relevant in a compiler
> > phase) in Haskell.
> >
> > As an example, consider the simplified ast types:
> >
> >  data Exp
> >    = IntExp Integer
> >    | VarExp Symbol
> >    | AssignExp Symbol Exp
> >    | IfExp Exp Exp (Maybe Exp)
> >    | CallExp Symbol [Exp]
> >    | LetExp [Dec] Exp
> >
> >  data Dec
> >     = TypeDec Symbol Ty
> >     | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
> >     | VarDec Symbol (Maybe Symbol) Exp
> >
> > Expressions can have type annotations, but declarations can not.
> >
> > Comments?

--- End Message ---
module Main where

newtype Fix f = In { out :: f (Fix f) }

newtype AnnFix x f = AnnFix { runAnnFix :: (x, f (AnnFix x f)) }

data ExpF r
  = Num Integer
  | Add r r
  | Mul r r
  | If r r r

type BareExp = Fix ExpF

eval :: BareExp -> Integer
eval (In (Num i)) = i
eval (In (Add x y)) = eval x + eval y
eval (In (Mul x y)) = eval x * eval y
eval (In (If t x y)) | eval t == 0 = eval y
                     | otherwise = eval x

e = In (Add (In (Num 7)) (In (Num 8)))

type Pos = Int

type PosExp = AnnFix Pos ExpF

aEval (AnnFix (_, e)) =
  case e of
    Num i -> i
    Add x y -> aEval x + aEval y
    Mul x y -> aEval x * aEval y
    If t x y | aEval t == 0 -> aEval y
             | otherwise -> aEval x

ae = AnnFix (3, Add (AnnFix (1, Num 7)) (AnnFix (5, Num 8)))

main = do print (eval e)
          print (aEval ae)
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to