Skip to content

Commit

Permalink
camlp4: bootstrap
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10405 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
np committed May 17, 2010
1 parent 432bb22 commit cc123f5
Showing 1 changed file with 19 additions and 32 deletions.
51 changes: 19 additions & 32 deletions camlp4/boot/camlp4boot.ml
Expand Up @@ -2895,33 +2895,13 @@ Very old (no more supported) syntax:\n\
((fun () ->
(None,
[ (None, (Some Camlp4.Sig.Grammar.RightA),
[ ([ Gram.Skeyword ":>";
Gram.Snterm
(Gram.Entry.obj (ctyp : 'ctyp Gram.Entry.t));
Gram.Skeyword "=";
Gram.Snterm
(Gram.Entry.obj (expr : 'expr Gram.Entry.t)) ],
(Gram.Action.mk
(fun (e : 'expr) _ (t : 'ctyp) _
(_loc : Gram.Loc.t) ->
(Ast.ExCoe (_loc, e, Ast.TyNil _loc, t) :
'fun_binding))));
([ Gram.Skeyword ":";
Gram.Snterm
(Gram.Entry.obj (ctyp : 'ctyp Gram.Entry.t));
Gram.Skeyword "=";
Gram.Snterm
(Gram.Entry.obj (expr : 'expr Gram.Entry.t)) ],
(Gram.Action.mk
(fun (e : 'expr) _ (t : 'ctyp) _
(_loc : Gram.Loc.t) ->
(Ast.ExTyc (_loc, e, t) : 'fun_binding))));
([ Gram.Skeyword "=";
Gram.Snterm
(Gram.Entry.obj (expr : 'expr Gram.Entry.t)) ],
[ ([ Gram.Snterm
(Gram.Entry.obj
(cvalue_binding :
'cvalue_binding Gram.Entry.t)) ],
(Gram.Action.mk
(fun (e : 'expr) _ (_loc : Gram.Loc.t) ->
(e : 'fun_binding))));
(fun (bi : 'cvalue_binding) (_loc : Gram.Loc.t)
-> (bi : 'fun_binding))));
([ Gram.Snterm
(Gram.Entry.obj
(labeled_ipatt :
Expand Down Expand Up @@ -5918,26 +5898,33 @@ Very old (no more supported) syntax:\n\
'cvalue_binding))));
([ Gram.Skeyword ":";
Gram.Snterm
(Gram.Entry.obj (ctyp : 'ctyp Gram.Entry.t));
(Gram.Entry.obj
(poly_type : 'poly_type Gram.Entry.t));
Gram.Skeyword ":>";
Gram.Snterm
(Gram.Entry.obj (ctyp : 'ctyp Gram.Entry.t));
Gram.Skeyword "=";
Gram.Snterm
(Gram.Entry.obj (expr : 'expr Gram.Entry.t)) ],
(Gram.Action.mk
(fun (e : 'expr) _ (t2 : 'ctyp) _ (t : 'ctyp) _
(_loc : Gram.Loc.t) ->
(Ast.ExCoe (_loc, e, t, t2) :
(fun (e : 'expr) _ (t2 : 'ctyp) _
(t : 'poly_type) _ (_loc : Gram.Loc.t) ->
(match t with
| Ast.TyPol (_, _, _) ->
raise
(Stream.Error
"unexpected polytype here")
| _ -> Ast.ExCoe (_loc, e, t, t2) :
'cvalue_binding))));
([ Gram.Skeyword ":";
Gram.Snterm
(Gram.Entry.obj (ctyp : 'ctyp Gram.Entry.t));
(Gram.Entry.obj
(poly_type : 'poly_type Gram.Entry.t));
Gram.Skeyword "=";
Gram.Snterm
(Gram.Entry.obj (expr : 'expr Gram.Entry.t)) ],
(Gram.Action.mk
(fun (e : 'expr) _ (t : 'ctyp) _
(fun (e : 'expr) _ (t : 'poly_type) _
(_loc : Gram.Loc.t) ->
(Ast.ExTyc (_loc, e, t) : 'cvalue_binding))));
([ Gram.Skeyword "=";
Expand Down

0 comments on commit cc123f5

Please sign in to comment.