git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4268 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Daniel de Rauglaudre 2002-01-19 03:35:26 +00:00
parent d007c8e431
commit 16f6e8b9ed
13 changed files with 424 additions and 307 deletions

View File

@ -277,7 +277,7 @@
((list (Sexpr _ sel1) :: sel2)
(let* ((lbs (List.map let_binding_se sel1))
(e (progn_se loc sel2)))
<:expr< let $rec:r$ $list:lbs$ in $e$ >>))
<:expr< let $opt:r$ $list:lbs$ in $e$ >>))
((list se :: _) (error se "let_binding"))
((_) (error_loc loc "let_binding")))))
((Sexpr loc (list (Satom _ Alid "let*") :: sel))

View File

@ -272,7 +272,7 @@ and expr_se =
[ [Sexpr _ sel1 :: sel2] ->
let lbs = List.map let_binding_se sel1 in
let e = progn_se loc sel2 in
<:expr< let $rec:r$ $list:lbs$ in $e$ >>
<:expr< let $opt:r$ $list:lbs$ in $e$ >>
| [se :: _] -> error se "let_binding"
| _ -> error_loc loc "let_binding" ]
| Sexpr loc [Satom _ Alid "let*" :: sel] ->

View File

@ -428,7 +428,7 @@ EXTEND
<:str_item< type $list:tdl$ >>
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
x = expr ->
let e = <:expr< let $rec:o2b r$ $list:l$ in $x$ >> in
let e = <:expr< let $opt:o2b r$ $list:l$ in $x$ >> in
<:str_item< $exp:e$ >>
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and" ->
match l with
@ -512,7 +512,7 @@ EXTEND
| "expr1"
[ "let"; o = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
x = expr LEVEL "top" ->
<:expr< let $rec:o2b o$ $list:l$ in $x$ >>
<:expr< let $opt:o2b o$ $list:l$ in $x$ >>
| "let"; "module"; m = UIDENT; mb = module_binding; "in";
e = expr LEVEL "top" ->
<:expr< let module $m$ = $mb$ in $e$ >>

View File

@ -923,7 +923,7 @@ EXTEND
<:str_item< type $list:tdl$ >>
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
x = expr ->
let e = <:expr< let $rec:o2b r$ $list:l$ in $x$ >> in
let e = <:expr< let $opt:o2b r$ $list:l$ in $x$ >> in
<:str_item< $exp:e$ >>
| "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and" ->
match l with
@ -1006,7 +1006,7 @@ EXTEND
| "expr1"
[ "let"; o = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
x = expr LEVEL "top" ->
<:expr< let $rec:o2b o$ $list:l$ in $x$ >>
<:expr< let $opt:o2b o$ $list:l$ in $x$ >>
| "let"; "module"; m = UIDENT; mb = module_binding; "in";
e = expr LEVEL "top" ->
<:expr< let module $m$ = $mb$ in $e$ >>
@ -1782,8 +1782,8 @@ value rec subst v e =
| <:expr< $chr:_$ >> -> e
| <:expr< $str:_$ >> -> e
| <:expr< $_$ . $_$ >> -> e
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
| _ -> raise Not_found ]

View File

@ -93,8 +93,8 @@ value rec subst v e =
| <:expr< $chr:_$ >> -> e
| <:expr< $str:_$ >> -> e
| <:expr< $_$ . $_$ >> -> e
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
| _ -> raise Not_found ]

View File

@ -36,7 +36,7 @@ EXTEND
[ [e] -> e
| _ -> <:expr< do { $list:el$ } >> ]
in
[<:expr< let $rec:o2b o$ $list:l$ in $e$ >>]
[<:expr< let $opt:o2b o$ $list:l$ in $e$ >>]
| e = expr; ";"; el = SELF ->
let e = let loc = MLast.loc_of_expr e in <:expr< ($e$ : unit) >> in
[e :: el]

View File

@ -1028,7 +1028,7 @@ pr_expr.pr_levels :=
{pr_label = "expr1"; pr_box _ x = HOVbox x;
pr_rules =
extfun Extfun.empty with
[ <:expr< let $rec:r$ $p1$ = $e1$ in $e$ >> ->
[ <:expr< let $opt:r$ $p1$ = $e1$ in $e$ >> ->
fun curr next dg k ->
let r = if r then [: `S LR "rec" :] else [: :] in
if dg <> ";" then
@ -1049,7 +1049,7 @@ pr_expr.pr_levels :=
[: `S LR "in" :];
`expr e "" [: :] :];
`HVbox [: `S LR "end"; k :] :] :]
| <:expr< let $rec:r$ $list:pel$ in $e$ >> ->
| <:expr< let $opt:r$ $list:pel$ in $e$ >> ->
fun curr next dg k ->
let r = if r then [: `S LR "rec" :] else [: :] in
if dg <> ";" then
@ -1530,7 +1530,7 @@ pr_expr.pr_levels :=
<:expr< fun [ $list:_$ ] >> | <:expr< match $_$ with [ $list:_$ ] >> |
<:expr< if $_$ then $_$ else $_$ >> |
<:expr< try $_$ with [ $list:_$ ] >> |
<:expr< let $rec:_$ $list:_$ in $_$ >> |
<:expr< let $opt:_$ $list:_$ in $_$ >> |
<:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> |
<:expr< while $_$ do { $list:_$ } >> | <:expr< ($list: _$) >> |
<:expr< $_$ . $_$ >> | <:expr< $_$ . ( $_$ ) >> |

View File

@ -454,7 +454,7 @@ and let_binding b (p, e) k =
and let_binding0 b e k =
let (pl, e) = expr_fun_args e in
match e with
[ <:expr< let $rec:r$ $lid:f$ = fun [ $list:pel$ ] in $e$ >>
[ <:expr< let $opt:r$ $lid:f$ = fun [ $list:pel$ ] in $e$ >>
when
let rec call_f =
fun
@ -509,7 +509,7 @@ value field_expr (lab, e) k = HVbox [: `label lab; `S LR "="; `expr e k :];
value rec sequence_loop =
fun
[ [<:expr< let $rec:r$ $list:pel$ in $e$ >>] ->
[ [<:expr< let $opt:r$ $list:pel$ in $e$ >>] ->
let el =
match e with
[ <:expr< do { $list:el$ } >> -> el
@ -519,7 +519,7 @@ value rec sequence_loop =
[: listwbws (fun b (p, e) k -> let_binding b (p, e) k)
[: `S LR "let"; r :] (S LR "and") pel [: `S RO ";" :];
sequence_loop el :]
| [(<:expr< let $rec:_$ $list:_$ in $_$ >> as e) :: el] ->
| [(<:expr< let $opt:_$ $list:_$ in $_$ >> as e) :: el] ->
[: `HVbox [: `S LO "("; `expr e [: `S RO ")"; `S RO ";" :] :];
sequence_loop el :]
| [e] -> [: `expr e [: :] :]
@ -537,7 +537,7 @@ value sequence b1 b2 b3 el k =
value rec let_sequence e =
match e with
[ <:expr< do { $list:el$ } >> -> Some el
| <:expr< let $rec:_$ $list:_$ in $e1$ >> ->
| <:expr< let $opt:_$ $list:_$ in $e1$ >> ->
match let_sequence e1 with
[ Some _ -> Some [e]
| None -> None ]
@ -1028,7 +1028,7 @@ pr_expr.pr_levels :=
[{pr_label = "top"; pr_box e x = LocInfo (MLast.loc_of_expr e) (HOVbox x);
pr_rules =
extfun Extfun.empty with
[ <:expr< let $rec:r$ $p1$ = $e1$ in $e$ >> ->
[ <:expr< let $opt:r$ $p1$ = $e1$ in $e$ >> ->
fun curr next _ k ->
let r = flag "rec" r in
[: `Vbox
@ -1036,7 +1036,7 @@ pr_expr.pr_levels :=
`let_binding [: `S LR "let"; r :] (p1, e1)
[: `S LR "in" :];
`expr e k :] :]
| <:expr< let $rec:r$ $list:pel$ in $e$ >> ->
| <:expr< let $opt:r$ $list:pel$ in $e$ >> ->
fun curr next _ k ->
let r = flag "rec" r in
[: `Vbox
@ -1392,7 +1392,7 @@ pr_expr.pr_levels :=
<:expr< if $_$ then $_$ else $_$ >> | <:expr< do { $list:_$ } >> |
<:expr< for $_$ = $_$ $to:_$ $_$ do { $list:_$ } >> |
<:expr< while $_$ do { $list:_$ } >> |
<:expr< let $rec:_$ $list:_$ in $_$ >> | MLast.ExNew _ _ as e ->
<:expr< let $opt:_$ $list:_$ in $_$ >> | MLast.ExNew _ _ as e ->
fun curr next _ k ->
[: `S LO "("; `expr e [: `HVbox [: `S RO ")"; k :] :] :]
| e -> fun curr next _ k -> [: `next e "" k :] ]}];

View File

@ -263,9 +263,9 @@ EXTEND
;
expr:
[ "top" RIGHTA
[ "let"; o = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
[ "let"; r = OPT "rec"; l = LIST1 let_binding SEP "and"; "in";
x = SELF ->
<:expr< let $rec:o2b o$ $list:l$ in $x$ >>
<:expr< let $opt:o2b r$ $list:l$ in $x$ >>
| "let"; "module"; m = UIDENT; mb = module_binding; "in"; e = SELF ->
<:expr< let module $m$ = $mb$ in $e$ >>
| "fun"; "["; l = LIST0 match_case SEP "|"; "]" ->
@ -286,19 +286,19 @@ EXTEND
[ [e] -> e
| _ -> <:expr< do { $list:seq$ } >> ]
| "for"; i = LIDENT; "="; e1 = SELF; df = direction_flag; e2 = SELF;
"do"; "{"; el = sequence; "}" ->
<:expr< for $i$ = $e1$ $to:df$ $e2$ do { $list:el$ } >>
| "while"; e = SELF; "do"; "{"; el = sequence; "}" ->
<:expr< while $e$ do { $list:el$ } >> ]
"do"; "{"; seq = sequence; "}" ->
<:expr< for $i$ = $e1$ $to:df$ $e2$ do { $list:seq$ } >>
| "while"; e = SELF; "do"; "{"; seq = sequence; "}" ->
<:expr< while $e$ do { $list:seq$ } >> ]
| "where"
[ e = SELF; "where"; rf = OPT "rec"; lb = let_binding ->
<:expr< let $rec:o2b rf$ $list:[lb]$ in $e$ >> ]
<:expr< let $opt:o2b rf$ $list:[lb]$ in $e$ >> ]
| ":=" NONA
[ e1 = SELF; ":="; e2 = SELF; dummy -> <:expr< $e1$ := $e2$ >> ]
| "||" RIGHTA
[ e1 = SELF; f = "||"; e2 = SELF -> <:expr< $lid:f$ $e1$ $e2$ >> ]
[ e1 = SELF; "||"; e2 = SELF -> <:expr< $e1$ || $e2$ >> ]
| "&&" RIGHTA
[ e1 = SELF; f = "&&"; e2 = SELF -> <:expr< $lid:f$ $e1$ $e2$ >> ]
[ e1 = SELF; "&&"; e2 = SELF -> <:expr< $e1$ && $e2$ >> ]
| "<" LEFTA
[ e1 = SELF; "<"; e2 = SELF -> <:expr< $e1$ < $e2$ >>
| e1 = SELF; ">"; e2 = SELF -> <:expr< $e1$ > $e2$ >>
@ -405,7 +405,7 @@ EXTEND
[ [e] -> e
| _ -> <:expr< do { $list:el$ } >> ]
in
[ <:expr< let $rec:o2b o$ $list:l$ in $e$ >>]
[ <:expr< let $opt:o2b o$ $list:l$ in $e$ >>]
| e = expr; ";"; el = SELF -> [e :: el]
| e = expr; ";" -> [e]
| e = expr -> [e] ] ]

View File

@ -91,8 +91,8 @@ value rec subst v e =
| <:expr< $chr:_$ >> -> e
| <:expr< $str:_$ >> -> e
| <:expr< $_$ . $_$ >> -> e
| <:expr< let $rec:rf$ $list:pel$ in $e$ >> ->
<:expr< let $rec:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< let $opt:rf$ $list:pel$ in $e$ >> ->
<:expr< let $opt:rf$ $list:List.map (subst_pe v) pel$ in $subst v e$ >>
| <:expr< $e1$ $e2$ >> -> <:expr< $subst v e1$ $subst v e2$ >>
| <:expr< ( $list:el$ ) >> -> <:expr< ( $list:List.map (subst v) el$ ) >>
| _ -> raise Not_found ]

View File

@ -154,7 +154,6 @@ EXTEND
| "#"; n = lident; dp = dir_param -> Node "StDir" [Loc; n; dp]
| e = expr -> Node "StExp" [Loc; e] ] ]
;
rebind_exn:
[ [ "="; sl = mod_ident -> sl
| -> List [] ] ]
@ -168,8 +167,7 @@ EXTEND
| "="; me = module_expr -> me ] ]
;
module_type:
[ [ "functor"; "("; i = a_UIDENT; ":"; t = SELF; ")"; "->";
mt = SELF ->
[ [ "functor"; "("; i = a_UIDENT; ":"; t = SELF; ")"; "->"; mt = SELF ->
Node "MtFun" [Loc; i; t; mt] ]
| [ mt = SELF; "with"; wcl = SLIST1 with_constr SEP "and" ->
Node "MtWit" [Loc; mt; wcl] ]
@ -177,32 +175,35 @@ EXTEND
Node "MtSig" [Loc; sg] ]
| [ m1 = SELF; m2 = SELF -> Node "MtApp" [Loc; m1; m2] ]
| [ m1 = SELF; "."; m2 = SELF -> Node "MtAcc" [Loc; m1; m2] ]
| [ i = UIDENT -> Node "MtUid" [Loc; Str i]
| i = LIDENT -> Node "MtLid" [Loc; Str i]
| a = anti_uid -> Node "MtUid" [Loc; a]
| a = anti_lid -> Node "MtLid" [Loc; a]
| a = anti_ -> a
| [ a = a_module_type -> a
| i = a_UIDENT -> Node "MtUid" [Loc; i]
| i = a_LIDENT -> Node "MtLid" [Loc; i]
| "("; mt = SELF; ")" -> mt ] ]
;
sig_item:
[ [ "declare"; st = SLIST0 [ s = sig_item; ";" -> s ]; "end" ->
[ "top"
[ a = a_sig_item -> a
| "declare"; st = SLIST0 [ s = sig_item; ";" -> s ]; "end" ->
Node "SgDcl" [Loc; st]
| "exception"; ctl = constructor_declaration ->
match ctl with
[ Tuple [Loc; c; tl] -> Node "SgExc" [Loc; c; tl]
| _ -> match () with [] ]
| "external"; i = lident; ":"; t = ctyp; "="; p = SLIST1 string ->
Node "SgExt" [Loc; i; t; p]
let (_, c, tl) =
match ctl with
[ Tuple [xx1; xx2; xx3] -> (xx1, xx2, xx3)
| _ -> match () with [] ]
in
Node "SgExc" [Loc; c; tl]
| "external"; i = a_LIDENT; ":"; t = ctyp; "="; pd = SLIST1 a_STRING ->
Node "SgExt" [Loc; i; t; pd]
| "include"; mt = module_type -> Node "SgInc" [Loc; mt]
| "module"; i = a_UIDENT; mt = module_declaration ->
Node "SgMod" [Loc; i; mt]
| "module"; "type"; i = a_UIDENT; "="; mt = module_type ->
Node "SgMty" [Loc; i; mt]
| "open"; m = mod_ident -> Node "SgOpn" [Loc; m]
| "type"; l = SLIST1 type_declaration SEP "and" -> Node "SgTyp" [Loc; l]
| "value"; i = lident; ":"; t = ctyp -> Node "SgVal" [Loc; i; t]
| "#"; n = lident; dp = dir_param -> Node "SgDir" [Loc; n; dp]
| a = anti_ -> a ] ]
| "open"; i = mod_ident -> Node "SgOpn" [Loc; i]
| "type"; tdl = SLIST1 type_declaration SEP "and" ->
Node "SgTyp" [Loc; tdl]
| "value"; i = a_LIDENT; ":"; t = ctyp -> Node "SgVal" [Loc; i; t]
| "#"; n = lident; dp = dir_param -> Node "SgDir" [Loc; n; dp] ] ]
;
module_declaration:
[ RIGHTA
@ -211,8 +212,8 @@ EXTEND
Node "MtFun" [Loc; i; t; mt] ] ]
;
with_constr:
[ [ "type"; i = mod_ident; tp = SLIST0 type_parameter; "="; t = ctyp ->
Node "WcTyp" [Loc; i; tp; t]
[ [ "type"; i = mod_ident; tpl = SLIST0 type_parameter; "="; t = ctyp ->
Node "WcTyp" [Loc; i; tpl; t]
| "module"; i = mod_ident; "="; mt = module_type ->
Node "WcMod" [Loc; i; mt] ] ]
;
@ -223,53 +224,80 @@ EXTEND
;
expr:
[ "top" RIGHTA
[ "let"; r = rec_flag; l = SLIST1 let_binding SEP "and"; "in";
[ "let"; r = SOPT "rec"; l = SLIST1 let_binding SEP "and"; "in";
x = SELF ->
Node "ExLet" [Loc; r; l; x]
| "let"; "module"; m = a_UIDENT; mb = module_binding; "in";
x = SELF ->
Node "ExLmd" [Loc; m; mb; x]
Node "ExLet" [Loc; o2b r; l; x]
| "let"; "module"; m = a_UIDENT; mb = module_binding; "in"; e = SELF ->
Node "ExLmd" [Loc; m; mb; e]
| "fun"; "["; l = SLIST0 match_case SEP "|"; "]" ->
Node "ExFun" [Loc; l]
| "fun"; p = ipatt; e = fun_def ->
Node "ExFun" [Loc; List [Tuple [p; Option None; e]]]
| "match"; e = SELF; "with"; "["; l = SLIST0 match_case SEP "|"; "]" ->
Node "ExMat" [Loc; e; l]
| "match"; x = SELF; "with"; p = ipatt; "->"; e = SELF ->
Node "ExMat" [Loc; x; List [Tuple [p; Option None; e]]]
| "match"; e = SELF; "with"; p1 = ipatt; "->"; e1 = SELF ->
Node "ExMat" [Loc; e; List [Tuple [p1; Option None; e1]]]
| "try"; e = SELF; "with"; "["; l = SLIST0 match_case SEP "|"; "]" ->
Node "ExTry" [Loc; e; l]
| "try"; x = SELF; "with"; p = ipatt; "->"; e = SELF ->
Node "ExTry" [Loc; x; List [Tuple [p; Option None; e]]]
| "try"; e = SELF; "with"; p1 = ipatt; "->"; e1 = SELF ->
Node "ExTry" [Loc; e; List [Tuple [p1; Option None; e1]]]
| "if"; e1 = SELF; "then"; e2 = SELF; "else"; e3 = SELF ->
Node "ExIfe" [Loc; e1; e2; e3]
| "do"; "{"; seq = SLIST0 expr SEP ";"; "}" -> Node "ExSeq" [Loc; seq]
| "for"; i = lident; "="; e1 = SELF; df = direction_flag; e2 = SELF;
"do"; "{"; seq = SLIST0 [ e = expr; ";" -> e ]; "}" ->
| "do"; "{"; seq = sequence; "}" -> Node "ExSeq" [Loc; seq]
| "for"; i = a_LIDENT; "="; e1 = SELF; df = direction_flag; e2 = SELF;
"do"; "{"; seq = sequence; "}" ->
Node "ExFor" [Loc; i; e1; e2; df; seq]
| "while"; e = SELF; "do"; "{"; seq = SLIST0 [ e = expr; ";" -> e ];
"}" ->
| "while"; e = SELF; "do"; "{"; seq = sequence; "}" ->
Node "ExWhi" [Loc; e; seq] ]
| NONA
| "where"
[ e = SELF; "where";
rf =
[ a = anti_opt -> a | o = OPT [ x = "rec" -> Str x ] -> Option o ];
lb = let_binding ->
Node "ExLet" [Loc; o2b rf; List [lb]; e] ]
| ":=" NONA
[ e1 = SELF; ":="; e2 = SELF; dummy -> Node "ExAss" [Loc; e1; e2] ]
| RIGHTA
[ e1 = SELF; f = "||"; e2 = SELF ->
| "||" RIGHTA
[ e1 = SELF; "||"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
| RIGHTA
[ e1 = SELF; f = "&&"; e2 = SELF ->
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "||"]; e1]; e2] ]
| "&&" RIGHTA
[ e1 = SELF; "&&"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
| LEFTA
[ e1 = SELF; f = [ "<" | ">" | "<=" | ">=" | "=" | "<>" | "==" | "!=" ];
e2 = SELF ->
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "&&"]; e1]; e2] ]
| "<" LEFTA
[ e1 = SELF; "<"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
| RIGHTA
[ e1 = SELF; f = [ "^" | "@" ]; e2 = SELF ->
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "<"]; e1]; e2]
| e1 = SELF; ">"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
| LEFTA
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str ">"]; e1]; e2]
| e1 = SELF; "<="; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "<="]; e1]; e2]
| e1 = SELF; ">="; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str ">="]; e1]; e2]
| e1 = SELF; "="; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "="]; e1]; e2]
| e1 = SELF; "<>"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "<>"]; e1]; e2]
| e1 = SELF; "=="; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "=="]; e1]; e2]
| e1 = SELF; "!="; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "!="]; e1]; e2] ]
| "^" RIGHTA
[ e1 = SELF; "^"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "^"]; e1]; e2]
| e1 = SELF; "@"; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str "@"]; e1]; e2] ]
| "+" LEFTA
[ e1 = SELF; f = [ "+" | "-" | "+." | "-." ]; e2 = SELF ->
Node "ExApp"
[Loc; Node "ExApp" [Loc; Node "ExLid" [Loc; Str f]; e1]; e2] ]
@ -344,7 +372,7 @@ EXTEND
[ [ "do"; seq = SLIST0 [ e = expr; ";" -> e ]; "return"; e = SELF ->
let _ = warning_seq () in
Node "ExSeq" [Loc; Append seq e]
| "for"; i = lident; "="; e1 = SELF; df = direction_flag; e2 = SELF;
| "for"; i = a_LIDENT; "="; e1 = SELF; df = direction_flag; e2 = SELF;
"do"; seq = SLIST0 [ e = expr; ";" -> e ]; "done" ->
let _ = warning_seq () in
Node "ExFor" [Loc; i; e1; e2; df; seq]
@ -356,6 +384,9 @@ EXTEND
dummy:
[ [ -> () ] ]
;
sequence:
[ [ seq = SLIST0 expr SEP ";" -> seq ] ]
;
let_binding:
[ [ p = ipatt; e = fun_binding -> Tuple [p; e] ] ]
;
@ -563,10 +594,6 @@ EXTEND
| "downto" -> Bool False
| a = anti_to -> a ] ]
;
string:
[ [ s = STRING -> Str s
| a = anti_ -> a ] ]
;
rec_flag:
[ [ a = anti_rec -> a
| "rec" -> Bool True
@ -595,6 +622,14 @@ EXTEND
[ [ a = ANTIQUOT "str_item" -> antiquot "str_item" loc a
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
;
a_module_type:
[ [ a = ANTIQUOT "module_type" -> antiquot "module_type" loc a
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
;
a_sig_item:
[ [ a = ANTIQUOT "sig_item" -> antiquot "sig_item" loc a
| a = ANTIQUOT "" -> antiquot "" loc a ] ]
;
a_UIDENT:
[ [ a = ANTIQUOT "uid" -> antiquot "uid" loc a
| a = ANTIQUOT "" -> antiquot "" loc a

View File

@ -630,8 +630,8 @@ Grammar.extend
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
Gramext.Stoken ("", "}")],
Gramext.action
(fun _ (el : 'sequence) _ _ (e : 'expr) _ (loc : int * int) ->
(MLast.ExWhi (loc, e, el) : 'expr));
(fun _ (seq : 'sequence) _ _ (e : 'expr) _ (loc : int * int) ->
(MLast.ExWhi (loc, e, seq) : 'expr));
[Gramext.Stoken ("", "for"); Gramext.Stoken ("LIDENT", "");
Gramext.Stoken ("", "="); Gramext.Sself;
Gramext.Snterm
@ -642,9 +642,9 @@ Grammar.extend
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
Gramext.Stoken ("", "}")],
Gramext.action
(fun _ (el : 'sequence) _ _ (e2 : 'expr) (df : 'direction_flag)
(fun _ (seq : 'sequence) _ _ (e2 : 'expr) (df : 'direction_flag)
(e1 : 'expr) _ (i : string) _ (loc : int * int) ->
(MLast.ExFor (loc, i, e1, e2, df, el) : 'expr));
(MLast.ExFor (loc, i, e1, e2, df, seq) : 'expr));
[Gramext.Stoken ("", "do"); Gramext.Stoken ("", "{");
Gramext.Snterm
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
@ -726,9 +726,9 @@ Grammar.extend
Gramext.Stoken ("", "and"));
Gramext.Stoken ("", "in"); Gramext.Sself],
Gramext.action
(fun (x : 'expr) _ (l : 'let_binding list) (o : string option) _
(fun (x : 'expr) _ (l : 'let_binding list) (r : string option) _
(loc : int * int) ->
(MLast.ExLet (loc, o2b o, l, x) : 'expr))];
(MLast.ExLet (loc, o2b r, l, x) : 'expr))];
Some "where", None,
[[Gramext.Sself; Gramext.Stoken ("", "where");
Gramext.Sopt (Gramext.Stoken ("", "rec"));
@ -747,16 +747,16 @@ Grammar.extend
Some "||", Some Gramext.RightA,
[[Gramext.Sself; Gramext.Stoken ("", "||"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : string) (e1 : 'expr) (loc : int * int) ->
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(MLast.ExApp
(loc, MLast.ExApp (loc, MLast.ExLid (loc, f), e1), e2) :
(loc, MLast.ExApp (loc, MLast.ExLid (loc, "||"), e1), e2) :
'expr))];
Some "&&", Some Gramext.RightA,
[[Gramext.Sself; Gramext.Stoken ("", "&&"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : string) (e1 : 'expr) (loc : int * int) ->
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(MLast.ExApp
(loc, MLast.ExApp (loc, MLast.ExLid (loc, f), e1), e2) :
(loc, MLast.ExApp (loc, MLast.ExLid (loc, "&&"), e1), e2) :
'expr))];
Some "<", Some Gramext.LeftA,
[[Gramext.Sself; Gramext.Stoken ("", "!="); Gramext.Sself],

View File

@ -142,6 +142,7 @@ Grammar.extend
and dir_param : 'dir_param Grammar.Entry.e =
grammar_entry_create "dir_param"
and dummy : 'dummy Grammar.Entry.e = grammar_entry_create "dummy"
and sequence : 'sequence Grammar.Entry.e = grammar_entry_create "sequence"
and let_binding : 'let_binding Grammar.Entry.e =
grammar_entry_create "let_binding"
and fun_binding : 'fun_binding Grammar.Entry.e =
@ -178,7 +179,6 @@ Grammar.extend
grammar_entry_create "mod_ident"
and direction_flag : 'direction_flag Grammar.Entry.e =
grammar_entry_create "direction_flag"
and string : 'string Grammar.Entry.e = grammar_entry_create "string"
and rec_flag : 'rec_flag Grammar.Entry.e = grammar_entry_create "rec_flag"
and as_opt : 'as_opt Grammar.Entry.e = grammar_entry_create "as_opt"
and when_opt : 'when_opt Grammar.Entry.e = grammar_entry_create "when_opt"
@ -188,6 +188,10 @@ Grammar.extend
grammar_entry_create "a_module_expr"
and a_str_item : 'a_str_item Grammar.Entry.e =
grammar_entry_create "a_str_item"
and a_module_type : 'a_module_type Grammar.Entry.e =
grammar_entry_create "a_module_type"
and a_sig_item : 'a_sig_item Grammar.Entry.e =
grammar_entry_create "a_sig_item"
and a_UIDENT : 'a_UIDENT Grammar.Entry.e = grammar_entry_create "a_UIDENT"
and a_LIDENT : 'a_LIDENT Grammar.Entry.e = grammar_entry_create "a_LIDENT"
and a_STRING : 'a_STRING Grammar.Entry.e = grammar_entry_create "a_STRING"
@ -568,32 +572,24 @@ Grammar.extend
Gramext.action
(fun _ (mt : 'module_type) _ (loc : int * int) ->
(mt : 'module_type));
[Gramext.Snterm (Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_) (loc : int * int) -> (a : 'module_type));
[Gramext.Snterm
(Grammar.Entry.obj (anti_lid : 'anti_lid Grammar.Entry.e))],
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_lid) (loc : int * int) ->
(Node ("MtLid", [Loc; a]) : 'module_type));
(fun (i : 'a_LIDENT) (loc : int * int) ->
(Node ("MtLid", [Loc; i]) : 'module_type));
[Gramext.Snterm
(Grammar.Entry.obj (anti_uid : 'anti_uid Grammar.Entry.e))],
(Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_uid) (loc : int * int) ->
(Node ("MtUid", [Loc; a]) : 'module_type));
[Gramext.Stoken ("LIDENT", "")],
(fun (i : 'a_UIDENT) (loc : int * int) ->
(Node ("MtUid", [Loc; i]) : 'module_type));
[Gramext.Snterm
(Grammar.Entry.obj
(a_module_type : 'a_module_type Grammar.Entry.e))],
Gramext.action
(fun (i : string) (loc : int * int) ->
(Node ("MtLid", [Loc; Str i]) : 'module_type));
[Gramext.Stoken ("UIDENT", "")],
Gramext.action
(fun (i : string) (loc : int * int) ->
(Node ("MtUid", [Loc; Str i]) : 'module_type))]];
(fun (a : 'a_module_type) (loc : int * int) -> (a : 'module_type))]];
Grammar.Entry.obj (sig_item : 'sig_item Grammar.Entry.e), None,
[None, None,
[[Gramext.Snterm (Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e))],
Gramext.action (fun (a : 'anti_) (loc : int * int) -> (a : 'sig_item));
[Gramext.Stoken ("", "#");
[Some "top", None,
[[Gramext.Stoken ("", "#");
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
Gramext.Snterm
(Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e))],
@ -601,11 +597,12 @@ Grammar.extend
(fun (dp : 'dir_param) (n : 'lident) _ (loc : int * int) ->
(Node ("SgDir", [Loc; n; dp]) : 'sig_item));
[Gramext.Stoken ("", "value");
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
Gramext.Snterm
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e));
Gramext.Stoken ("", ":");
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e))],
Gramext.action
(fun (t : 'ctyp) _ (i : 'lident) _ (loc : int * int) ->
(fun (t : 'ctyp) _ (i : 'a_LIDENT) _ (loc : int * int) ->
(Node ("SgVal", [Loc; i; t]) : 'sig_item));
[Gramext.Stoken ("", "type");
Gramext.srules
@ -622,14 +619,14 @@ Grammar.extend
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))]],
Gramext.action
(fun (l : ast) _ (loc : int * int) ->
(Node ("SgTyp", [Loc; l]) : 'sig_item));
(fun (tdl : ast) _ (loc : int * int) ->
(Node ("SgTyp", [Loc; tdl]) : 'sig_item));
[Gramext.Stoken ("", "open");
Gramext.Snterm
(Grammar.Entry.obj (mod_ident : 'mod_ident Grammar.Entry.e))],
Gramext.action
(fun (m : 'mod_ident) _ (loc : int * int) ->
(Node ("SgOpn", [Loc; m]) : 'sig_item));
(fun (i : 'mod_ident) _ (loc : int * int) ->
(Node ("SgOpn", [Loc; i]) : 'sig_item));
[Gramext.Stoken ("", "module"); Gramext.Stoken ("", "type");
Gramext.Snterm
(Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e));
@ -655,23 +652,24 @@ Grammar.extend
(fun (mt : 'module_type) _ (loc : int * int) ->
(Node ("SgInc", [Loc; mt]) : 'sig_item));
[Gramext.Stoken ("", "external");
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
Gramext.Snterm
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e));
Gramext.Stoken ("", ":");
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e));
Gramext.Stoken ("", "=");
Gramext.srules
[[Gramext.Slist1
(Gramext.Snterm
(Grammar.Entry.obj (string : 'string Grammar.Entry.e)))],
(Grammar.Entry.obj (a_STRING : 'a_STRING Grammar.Entry.e)))],
Gramext.action
(fun (l : 'string list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'a_STRING list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))]],
Gramext.action
(fun (p : ast) _ (t : 'ctyp) _ (i : 'lident) _ (loc : int * int) ->
(Node ("SgExt", [Loc; i; t; p]) : 'sig_item));
(fun (pd : ast) _ (t : 'ctyp) _ (i : 'a_LIDENT) _ (loc : int * int) ->
(Node ("SgExt", [Loc; i; t; pd]) : 'sig_item));
[Gramext.Stoken ("", "exception");
Gramext.Snterm
(Grammar.Entry.obj
@ -679,11 +677,14 @@ Grammar.extend
'constructor_declaration Grammar.Entry.e))],
Gramext.action
(fun (ctl : 'constructor_declaration) _ (loc : int * int) ->
(match ctl with
Tuple [Loc; c; tl] -> Node ("SgExc", [Loc; c; tl])
| _ ->
match () with
_ -> raise (Match_failure ("q_MLast.ml", 6691, 6707)) :
(let (_, c, tl) =
match ctl with
Tuple [xx1; xx2; xx3] -> xx1, xx2, xx3
| _ ->
match () with
_ -> raise (Match_failure ("q_MLast.ml", 6660, 6676))
in
Node ("SgExc", [Loc; c; tl]) :
'sig_item));
[Gramext.Stoken ("", "declare");
Gramext.srules
@ -705,7 +706,11 @@ Grammar.extend
Gramext.Stoken ("", "end")],
Gramext.action
(fun _ (st : ast) _ (loc : int * int) ->
(Node ("SgDcl", [Loc; st]) : 'sig_item))]];
(Node ("SgDcl", [Loc; st]) : 'sig_item));
[Gramext.Snterm
(Grammar.Entry.obj (a_sig_item : 'a_sig_item Grammar.Entry.e))],
Gramext.action
(fun (a : 'a_sig_item) (loc : int * int) -> (a : 'sig_item))]];
Grammar.Entry.obj
(module_declaration : 'module_declaration Grammar.Entry.e),
None,
@ -756,8 +761,8 @@ Grammar.extend
Gramext.Stoken ("", "=");
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e))],
Gramext.action
(fun (t : 'ctyp) _ (tp : ast) (i : 'mod_ident) _ (loc : int * int) ->
(Node ("WcTyp", [Loc; i; tp; t]) : 'with_constr))]];
(fun (t : 'ctyp) _ (tpl : ast) (i : 'mod_ident) _ (loc : int * int) ->
(Node ("WcTyp", [Loc; i; tpl; t]) : 'with_constr))]];
Grammar.Entry.obj (dir_param : 'dir_param Grammar.Entry.e), None,
[None, None,
[[],
@ -773,65 +778,33 @@ Grammar.extend
[Some "top", Some Gramext.RightA,
[[Gramext.Stoken ("", "while"); Gramext.Sself; Gramext.Stoken ("", "do");
Gramext.Stoken ("", "{");
Gramext.srules
[[Gramext.Slist0
(Gramext.srules
[[Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__6))])],
Gramext.action
(fun (l : 'e__6 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
Gramext.Snterm
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
Gramext.Stoken ("", "}")],
Gramext.action
(fun _ (seq : ast) _ _ (e : 'expr) _ (loc : int * int) ->
(fun _ (seq : 'sequence) _ _ (e : 'expr) _ (loc : int * int) ->
(Node ("ExWhi", [Loc; e; seq]) : 'expr));
[Gramext.Stoken ("", "for");
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
Gramext.Snterm
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e));
Gramext.Stoken ("", "="); Gramext.Sself;
Gramext.Snterm
(Grammar.Entry.obj
(direction_flag : 'direction_flag Grammar.Entry.e));
Gramext.Sself; Gramext.Stoken ("", "do"); Gramext.Stoken ("", "{");
Gramext.srules
[[Gramext.Slist0
(Gramext.srules
[[Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__5))])],
Gramext.action
(fun (l : 'e__5 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
Gramext.Snterm
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
Gramext.Stoken ("", "}")],
Gramext.action
(fun _ (seq : ast) _ _ (e2 : 'expr) (df : 'direction_flag)
(e1 : 'expr) _ (i : 'lident) _ (loc : int * int) ->
(fun _ (seq : 'sequence) _ _ (e2 : 'expr) (df : 'direction_flag)
(e1 : 'expr) _ (i : 'a_LIDENT) _ (loc : int * int) ->
(Node ("ExFor", [Loc; i; e1; e2; df; seq]) : 'expr));
[Gramext.Stoken ("", "do"); Gramext.Stoken ("", "{");
Gramext.srules
[[Gramext.Slist0sep
(Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e)),
Gramext.Stoken ("", ";"))],
Gramext.action
(fun (l : 'expr list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
Gramext.Snterm
(Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e));
Gramext.Stoken ("", "}")],
Gramext.action
(fun _ (seq : ast) _ _ (loc : int * int) ->
(fun _ (seq : 'sequence) _ _ (loc : int * int) ->
(Node ("ExSeq", [Loc; seq]) : 'expr));
[Gramext.Stoken ("", "if"); Gramext.Sself; Gramext.Stoken ("", "then");
Gramext.Sself; Gramext.Stoken ("", "else"); Gramext.Sself],
@ -842,8 +815,8 @@ Grammar.extend
Gramext.Snterm (Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e));
Gramext.Stoken ("", "->"); Gramext.Sself],
Gramext.action
(fun (e : 'expr) _ (p : 'ipatt) _ (x : 'expr) _ (loc : int * int) ->
(Node ("ExTry", [Loc; x; List [Tuple [p; Option None; e]]]) :
(fun (e1 : 'expr) _ (p1 : 'ipatt) _ (e : 'expr) _ (loc : int * int) ->
(Node ("ExTry", [Loc; e; List [Tuple [p1; Option None; e1]]]) :
'expr));
[Gramext.Stoken ("", "try"); Gramext.Sself; Gramext.Stoken ("", "with");
Gramext.Stoken ("", "[");
@ -869,8 +842,8 @@ Grammar.extend
Gramext.Snterm (Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e));
Gramext.Stoken ("", "->"); Gramext.Sself],
Gramext.action
(fun (e : 'expr) _ (p : 'ipatt) _ (x : 'expr) _ (loc : int * int) ->
(Node ("ExMat", [Loc; x; List [Tuple [p; Option None; e]]]) :
(fun (e1 : 'expr) _ (p1 : 'ipatt) _ (e : 'expr) _ (loc : int * int) ->
(Node ("ExMat", [Loc; e; List [Tuple [p1; Option None; e1]]]) :
'expr));
[Gramext.Stoken ("", "match"); Gramext.Sself;
Gramext.Stoken ("", "with"); Gramext.Stoken ("", "[");
@ -924,12 +897,22 @@ Grammar.extend
(module_binding : 'module_binding Grammar.Entry.e));
Gramext.Stoken ("", "in"); Gramext.Sself],
Gramext.action
(fun (x : 'expr) _ (mb : 'module_binding) (m : 'a_UIDENT) _ _
(fun (e : 'expr) _ (mb : 'module_binding) (m : 'a_UIDENT) _ _
(loc : int * int) ->
(Node ("ExLmd", [Loc; m; mb; x]) : 'expr));
(Node ("ExLmd", [Loc; m; mb; e]) : 'expr));
[Gramext.Stoken ("", "let");
Gramext.Snterm
(Grammar.Entry.obj (rec_flag : 'rec_flag Grammar.Entry.e));
Gramext.srules
[[Gramext.Sopt
(Gramext.srules
[[Gramext.Stoken ("", "rec")],
Gramext.action
(fun (x : string) (loc : int * int) -> (Str x : 'ast))])],
Gramext.action
(fun (o : ast option) (loc : int * int) -> (Option o : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_opt : 'anti_opt Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_opt) (loc : int * int) -> (a : 'anti))];
Gramext.srules
[[Gramext.Slist1sep
(Gramext.Snterm
@ -945,50 +928,156 @@ Grammar.extend
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))];
Gramext.Stoken ("", "in"); Gramext.Sself],
Gramext.action
(fun (x : 'expr) _ (l : ast) (r : 'rec_flag) _ (loc : int * int) ->
(Node ("ExLet", [Loc; r; l; x]) : 'expr))];
None, Some Gramext.NonA,
(fun (x : 'expr) _ (l : ast) (r : ast) _ (loc : int * int) ->
(Node ("ExLet", [Loc; o2b r; l; x]) : 'expr))];
Some "where", None,
[[Gramext.Sself; Gramext.Stoken ("", "where");
Gramext.srules
[[Gramext.Sopt
(Gramext.srules
[[Gramext.Stoken ("", "rec")],
Gramext.action
(fun (x : string) (loc : int * int) -> (Str x : 'e__5))])],
Gramext.action
(fun (o : 'e__5 option) (loc : int * int) -> (Option o : 'e__6));
[Gramext.Snterm
(Grammar.Entry.obj (anti_opt : 'anti_opt Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_opt) (loc : int * int) -> (a : 'e__6))];
Gramext.Snterm
(Grammar.Entry.obj (let_binding : 'let_binding Grammar.Entry.e))],
Gramext.action
(fun (lb : 'let_binding) (rf : 'e__6) _ (e : 'expr)
(loc : int * int) ->
(Node ("ExLet", [Loc; o2b rf; List [lb]; e]) : 'expr))];
Some ":=", Some Gramext.NonA,
[[Gramext.Sself; Gramext.Stoken ("", ":="); Gramext.Sself;
Gramext.Snterm (Grammar.Entry.obj (dummy : 'dummy Grammar.Entry.e))],
Gramext.action
(fun _ (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node ("ExAss", [Loc; e1; e2]) : 'expr))];
None, Some Gramext.RightA,
Some "||", Some Gramext.RightA,
[[Gramext.Sself; Gramext.Stoken ("", "||"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : string) (e1 : 'expr) (loc : int * int) ->
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "||"]); e1]);
e2]) :
'expr))];
None, Some Gramext.RightA,
Some "&&", Some Gramext.RightA,
[[Gramext.Sself; Gramext.Stoken ("", "&&"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : string) (e1 : 'expr) (loc : int * int) ->
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "&&"]); e1]);
e2]) :
'expr))];
None, Some Gramext.LeftA,
Some "<", Some Gramext.LeftA,
[[Gramext.Sself; Gramext.Stoken ("", "!="); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "!="]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "=="); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "=="]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "<>"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "<>"]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "="); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "="]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", ">="); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str ">="]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "<="); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "<="]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", ">"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str ">"]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "<"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "<"]); e1]);
e2]) :
'expr))];
Some "^", Some Gramext.RightA,
[[Gramext.Sself; Gramext.Stoken ("", "@"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "@"]); e1]);
e2]) :
'expr));
[Gramext.Sself; Gramext.Stoken ("", "^"); Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) _ (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc;
Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str "^"]); e1]);
e2]) :
'expr))];
Some "+", Some Gramext.LeftA,
[[Gramext.Sself;
Gramext.srules
[[Gramext.Stoken ("", "!=")],
[[Gramext.Stoken ("", "-.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", "==")],
[Gramext.Stoken ("", "+.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", "<>")],
[Gramext.Stoken ("", "-")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", "=")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", ">=")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", "<=")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", ">")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7));
[Gramext.Stoken ("", "<")],
[Gramext.Stoken ("", "+")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__7))];
Gramext.Sself],
Gramext.action
@ -998,12 +1087,24 @@ Grammar.extend
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
e2]) :
'expr))];
None, Some Gramext.RightA,
None, Some Gramext.LeftA,
[[Gramext.Sself;
Gramext.srules
[[Gramext.Stoken ("", "@")],
[[Gramext.Stoken ("", "mod")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "^")],
[Gramext.Stoken ("", "lxor")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "lor")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "land")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "/.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "*.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "/")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8));
[Gramext.Stoken ("", "*")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__8))];
Gramext.Sself],
Gramext.action
@ -1013,16 +1114,16 @@ Grammar.extend
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
e2]) :
'expr))];
None, Some Gramext.LeftA,
None, Some Gramext.RightA,
[[Gramext.Sself;
Gramext.srules
[[Gramext.Stoken ("", "-.")],
[[Gramext.Stoken ("", "lsr")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
[Gramext.Stoken ("", "+.")],
[Gramext.Stoken ("", "lsl")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
[Gramext.Stoken ("", "-")],
[Gramext.Stoken ("", "asr")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9));
[Gramext.Stoken ("", "+")],
[Gramext.Stoken ("", "**")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__9))];
Gramext.Sself],
Gramext.action
@ -1032,64 +1133,16 @@ Grammar.extend
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
e2]) :
'expr))];
None, Some Gramext.LeftA,
[[Gramext.Sself;
Gramext.srules
[[Gramext.Stoken ("", "mod")],
Some "unary minus", Some Gramext.NonA,
[[Gramext.srules
[[Gramext.Stoken ("", "-.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "lxor")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "lor")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "land")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "/.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "*.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "/")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__10));
[Gramext.Stoken ("", "*")],
[Gramext.Stoken ("", "-")],
Gramext.action
(fun (x : string) (loc : int * int) -> (x : 'e__10))];
Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : 'e__10) (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
e2]) :
'expr))];
None, Some Gramext.RightA,
[[Gramext.Sself;
Gramext.srules
[[Gramext.Stoken ("", "lsr")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__11));
[Gramext.Stoken ("", "lsl")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__11));
[Gramext.Stoken ("", "asr")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__11));
[Gramext.Stoken ("", "**")],
Gramext.action
(fun (x : string) (loc : int * int) -> (x : 'e__11))];
Gramext.Sself],
Gramext.action
(fun (e2 : 'expr) (f : 'e__11) (e1 : 'expr) (loc : int * int) ->
(Node
("ExApp",
[Loc; Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e1]);
e2]) :
'expr))];
Some "unary minus", Some Gramext.NonA,
[[Gramext.srules
[[Gramext.Stoken ("", "-.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__12));
[Gramext.Stoken ("", "-")],
Gramext.action
(fun (x : string) (loc : int * int) -> (x : 'e__12))];
Gramext.Sself],
Gramext.action
(fun (e : 'expr) (f : 'e__12) (loc : int * int) ->
(fun (e : 'expr) (f : 'e__10) (loc : int * int) ->
(mkumin f e : 'expr))];
Some "apply", Some Gramext.LeftA,
[[Gramext.Sself; Gramext.Sself],
@ -1155,13 +1208,13 @@ Grammar.extend
None, Some Gramext.NonA,
[[Gramext.srules
[[Gramext.Stoken ("", "~-.")],
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__13));
Gramext.action (fun (x : string) (loc : int * int) -> (x : 'e__11));
[Gramext.Stoken ("", "~-")],
Gramext.action
(fun (x : string) (loc : int * int) -> (x : 'e__13))];
(fun (x : string) (loc : int * int) -> (x : 'e__11))];
Gramext.Sself],
Gramext.action
(fun (e : 'expr) (f : 'e__13) (loc : int * int) ->
(fun (e : 'expr) (f : 'e__11) (loc : int * int) ->
(Node ("ExApp", [Loc; Node ("ExLid", [Loc; Str f]); e]) : 'expr))];
Some "simple", None,
[[Gramext.Stoken ("", "("); Gramext.Sself; Gramext.Stoken ("", ")")],
@ -1262,10 +1315,10 @@ Grammar.extend
Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
Gramext.action
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__14))]);
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__12))]);
Gramext.Stoken ("", "]")],
Gramext.action
(fun _ (last : 'e__14 option) (el : 'expr list) _ (loc : int * int) ->
(fun _ (last : 'e__12 option) (el : 'expr list) _ (loc : int * int) ->
(mklistexp last el : 'expr));
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
Gramext.action
@ -1355,9 +1408,9 @@ Grammar.extend
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__17))])],
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__15))])],
Gramext.action
(fun (l : 'e__17 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__15 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -1367,7 +1420,8 @@ Grammar.extend
(fun _ (seq : ast) _ (e : 'expr) _ (loc : int * int) ->
(let _ = warning_seq () in Node ("ExWhi", [Loc; e; seq]) : 'expr));
[Gramext.Stoken ("", "for");
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
Gramext.Snterm
(Grammar.Entry.obj (a_LIDENT : 'a_LIDENT Grammar.Entry.e));
Gramext.Stoken ("", "="); Gramext.Sself;
Gramext.Snterm
(Grammar.Entry.obj
@ -1380,9 +1434,9 @@ Grammar.extend
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__16))])],
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__14))])],
Gramext.action
(fun (l : 'e__16 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__14 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -1390,7 +1444,7 @@ Grammar.extend
Gramext.Stoken ("", "done")],
Gramext.action
(fun _ (seq : ast) _ (e2 : 'expr) (df : 'direction_flag) (e1 : 'expr)
_ (i : 'lident) _ (loc : int * int) ->
_ (i : 'a_LIDENT) _ (loc : int * int) ->
(let _ = warning_seq () in
Node ("ExFor", [Loc; i; e1; e2; df; seq]) :
'expr));
@ -1402,9 +1456,9 @@ Grammar.extend
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__15))])],
(fun _ (e : 'expr) (loc : int * int) -> (e : 'e__13))])],
Gramext.action
(fun (l : 'e__15 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__13 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -1417,6 +1471,21 @@ Grammar.extend
Grammar.Entry.obj (dummy : 'dummy Grammar.Entry.e), None,
[None, None,
[[], Gramext.action (fun (loc : int * int) -> (() : 'dummy))]];
Grammar.Entry.obj (sequence : 'sequence Grammar.Entry.e), None,
[None, None,
[[Gramext.srules
[[Gramext.Slist0sep
(Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e)),
Gramext.Stoken ("", ";"))],
Gramext.action
(fun (l : 'expr list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
(fun (a : 'anti_list) (loc : int * int) -> (a : 'anti))]],
Gramext.action
(fun (seq : ast) (loc : int * int) -> (seq : 'sequence))]];
Grammar.Entry.obj (let_binding : 'let_binding Grammar.Entry.e), None,
[None, None,
[[Gramext.Snterm (Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e));
@ -1546,10 +1615,10 @@ Grammar.extend
Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
Gramext.action
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__19))]);
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__17))]);
Gramext.Stoken ("", ")")],
Gramext.action
(fun _ (e : 'e__19 option) (t : 'ctyp) _ (p : 'patt) _ _ (i : 'lident)
(fun _ (e : 'e__17 option) (t : 'ctyp) _ (p : 'patt) _ _ (i : 'lident)
_ (loc : int * int) ->
(let p = Node ("PaTyc", [Loc; p; t]) in
Node ("PaOlb", [Loc; i; p; Option e]) :
@ -1563,10 +1632,10 @@ Grammar.extend
Gramext.Snterm
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
Gramext.action
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__18))]);
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__16))]);
Gramext.Stoken ("", ")")],
Gramext.action
(fun _ (e : 'e__18 option) (p : 'patt) _ _ (i : 'lident) _
(fun _ (e : 'e__16 option) (p : 'patt) _ _ (i : 'lident) _
(loc : int * int) ->
(Node ("PaOlb", [Loc; i; p; Option e]) : 'patt));
[Gramext.Stoken ("", "~");
@ -1668,10 +1737,10 @@ Grammar.extend
Gramext.Snterm
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
Gramext.action
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__20))]);
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__18))]);
Gramext.Stoken ("", "]")],
Gramext.action
(fun _ (last : 'e__20 option) (pl : 'patt list) _ (loc : int * int) ->
(fun _ (last : 'e__18 option) (pl : 'patt list) _ (loc : int * int) ->
(mklistpat last pl : 'patt));
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
Gramext.action
@ -2268,13 +2337,6 @@ Grammar.extend
[Gramext.Stoken ("", "to")],
Gramext.action
(fun _ (loc : int * int) -> (Bool true : 'direction_flag))]];
Grammar.Entry.obj (string : 'string Grammar.Entry.e), None,
[None, None,
[[Gramext.Snterm (Grammar.Entry.obj (anti_ : 'anti_ Grammar.Entry.e))],
Gramext.action (fun (a : 'anti_) (loc : int * int) -> (a : 'string));
[Gramext.Stoken ("STRING", "")],
Gramext.action
(fun (s : string) (loc : int * int) -> (Str s : 'string))]];
Grammar.Entry.obj (rec_flag : 'rec_flag Grammar.Entry.e), None,
[None, None,
[[], Gramext.action (fun (loc : int * int) -> (Bool false : 'rec_flag));
@ -2337,6 +2399,26 @@ Grammar.extend
Gramext.action
(fun (a : string) (loc : int * int) ->
(antiquot "str_item" loc a : 'a_str_item))]];
Grammar.Entry.obj (a_module_type : 'a_module_type Grammar.Entry.e), None,
[None, None,
[[Gramext.Stoken ("ANTIQUOT", "")],
Gramext.action
(fun (a : string) (loc : int * int) ->
(antiquot "" loc a : 'a_module_type));
[Gramext.Stoken ("ANTIQUOT", "module_type")],
Gramext.action
(fun (a : string) (loc : int * int) ->
(antiquot "module_type" loc a : 'a_module_type))]];
Grammar.Entry.obj (a_sig_item : 'a_sig_item Grammar.Entry.e), None,
[None, None,
[[Gramext.Stoken ("ANTIQUOT", "")],
Gramext.action
(fun (a : string) (loc : int * int) ->
(antiquot "" loc a : 'a_sig_item));
[Gramext.Stoken ("ANTIQUOT", "sig_item")],
Gramext.action
(fun (a : string) (loc : int * int) ->
(antiquot "sig_item" loc a : 'a_sig_item))]];
Grammar.Entry.obj (a_UIDENT : 'a_UIDENT Grammar.Entry.e), None,
[None, None,
[[Gramext.Stoken ("UIDENT", "")],
@ -2727,9 +2809,9 @@ Grammar.extend
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (cf : 'class_str_item) (loc : int * int) ->
(cf : 'e__21))])],
(cf : 'e__19))])],
Gramext.action
(fun (l : 'e__21 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__19 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -2825,9 +2907,9 @@ Grammar.extend
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (s : 'class_str_item) (loc : int * int) ->
(s : 'e__22))])],
(s : 'e__20))])],
Gramext.action
(fun (l : 'e__22 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__20 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -2901,9 +2983,9 @@ Grammar.extend
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (csf : 'class_sig_item) (loc : int * int) ->
(csf : 'e__23))])],
(csf : 'e__21))])],
Gramext.action
(fun (l : 'e__23 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__21 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action
@ -3024,9 +3106,9 @@ Grammar.extend
Gramext.Stoken ("", ";")],
Gramext.action
(fun _ (s : 'class_sig_item) (loc : int * int) ->
(s : 'e__24))])],
(s : 'e__22))])],
Gramext.action
(fun (l : 'e__24 list) (loc : int * int) -> (List l : 'anti));
(fun (l : 'e__22 list) (loc : int * int) -> (List l : 'anti));
[Gramext.Snterm
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
Gramext.action