Ah, I found the attachment on your other email.
I didn't get any attachments from you, but haskell-cafe might filter them out (I'm not sure).
But, the usual derived instances for Show should work fine for your expression and annotation types.
For the Fix type you can use:
instance (Show (f (Fix f))) => Show (Fix f) where
show (Fix a) = show "Fix " ++ show a
hmmm, but you'll probably need:
{-# LANGUAGE FlexibleContexts, UndecidableInstances #-}
- Job2010/7/19 José Romildo Malaquias <j.romildo@gmail.com>
On Mon, Jul 19, 2010 at 01:51:57PM -0400, Job Vranish wrote:After a quick read at Martijn blog article I've written the attached
> 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.
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.romildo@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?