camlp4: support polymorphic recursion and bootstrap

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10410 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Nicolas Pouillard 2010-05-17 13:44:14 +00:00
parent cc123f5ea7
commit 17a6330d29
2 changed files with 6 additions and 0 deletions

View File

@ -764,6 +764,8 @@ module Make (Ast : Sig.Camlp4Ast) = struct
match x with
[ <:binding< $x$ and $y$ >> ->
binding x (binding y acc)
| <:binding@_loc< $p$ = ($e$ : ! $vs$ . $ty$) >> ->
[(patt <:patt< ($p$ : ! $vs$ . $ty$ ) >>, expr e) :: acc]
| <:binding< $p$ = $e$ >> -> [(patt p, expr e) :: acc]
| <:binding<>> -> acc
| _ -> assert False ]

View File

@ -14325,6 +14325,10 @@ module Struct =
and binding x acc =
match x with
| Ast.BiAnd (_, x, y) -> binding x (binding y acc)
| Ast.BiEq (_loc, p,
(Ast.ExTyc (_, e, (Ast.TyPol (_, vs, ty))))) ->
((patt (Ast.PaTyc (_loc, p, Ast.TyPol (_loc, vs, ty)))),
(expr e)) :: acc
| Ast.BiEq (_, p, e) -> ((patt p), (expr e)) :: acc
| Ast.BiNil _ -> acc
| _ -> assert false