[Template-haskell] Reification of local names

Kamil Skalski nazgul at omega.pl
Tue Jun 22 11:47:24 EDT 2004


Tuesday 22 June 2004 15:36, Simon Peyton-Jones wrote:
> | > One idea: add (Maybe Type) fields to many TH syntax forms, where the
> | > type checker can record types.  That's simple and direct.
> |
> | This is actually the way how we implemented it in Nemerle. Our syntax
>
> trees
>
> | has elements like E_typed { body : Typedtree.Expr } in Parsetree.Expr
>
> or
>
> | T_typed { body : Typedtree.Type } in Parsetree.Type, so we can store
>
> typed
>
> | parts in our ASTs.
> | Our quotations support this with
> | <[  $(e : typed) ]>  where `e' is a variable holding typed tree of
>
> expression
>
> | We can also build typed trees for types with quotation like
> | <[ ttype: int ]>
>
> Interesting ... but I'm afraid I don't understand what these notations
> mean.

This corresponds strongly to way how we perform translation in compiler - 
parser gives us parsetree (tree composed of Parsetree.Expr, Parsetree.Type, 
Parsetree.Pattern, etc.), macros are mainly of type
Parsetree.Expr -> Parsetree.Expr
and later we transform parsetree to typed tree (which are separate, 
unambiguated versions of Parsetree structures)

But sometimes our macros perform task, which compiler should do - they type 
parts of given parsetree, geting Typedtree as a result. In order to not loose 
informations (type variables restrictions, etc.) obtained, we must return 
those Typedtree parts embedded in Parsetree. So we created additional element 
of Parsetree, namely Parsetree.E_typed.

Our quotations are similar to TH, they are equivalent to creating AST by hand, 
so
<[ x ]> is equivalent to Parsetree.E_ref (Name ("x"))
and we can of course splice values into quotations

<[ f ($e) ]> is equivalent to 
Parsetree.E_call (Parsetree.E_ref (Name ("f")), e)

we also support other kinds of splices
<[ $(x : int) ]> is Parsetree.E_literal (L_int (x))

so following this design, 
<[ $(te : typed) ]> is Parsetree.E_typed (te)
where E_typed (of type Parsetree.Expr) holds variable of type Typedtree.Type

>
> Suppose you want to build a data structure from the original
> constructors, by hand as it were.  (Which Template Haskell certainly
> allows you to do.)  You don't want to supply all the types!  If pattern
> match over this structure, you aren't going to see types.  So the types
> must somehow be optional.  I don't want to have two completely
> different, but similar, data structures, one with types and one without.
> Hence the 'Maybe' part.  Is that what you have?

As I understand, you have the same datastructure for Typedtree and Parsetree, 
so adding to all its elements field optionally holding real type of given 
object seems to be a good idea.

And coming back to < ttype: int ]> it is equivalent to
Parsetree.T_typed (ty_type (typingcontext, Parsetree.T_app (Name ("int"))))

ty_type is compiler's procedure performing translation Parsetree.Type -> 
Typedtree.Type, so here we again create special element of parsetree holding 
typed tree. 

This way we can for example check if parameter supplied to macro is of type 
int of bool - great feature for generating different code according to type 
of object.
So my point is, that having ability to operate on AST enriched by typing 
information, being able to ask compiler about some local typing information 
is great and useful (according to our practical expiriences).

Kamil Skalski


More information about the template-haskell mailing list