git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3874 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
5f1ae5e132
commit
83a6451e45
|
@ -5,7 +5,8 @@ Camlp4 Version 3.03
|
||||||
named "True" of "False" (capitalized, i.e. not like the booleans), it
|
named "True" of "False" (capitalized, i.e. not like the booleans), it
|
||||||
did not work.
|
did not work.
|
||||||
- [04 Oct 01] Fixed some revised and quotation syntaxes in objects classes
|
- [04 Oct 01] Fixed some revised and quotation syntaxes in objects classes
|
||||||
and types (cleaner). Cleaned up also several parts of the parsers.
|
and types (cleaner). Cleaned up also several parts of the parsers. Completed
|
||||||
|
missing cases.
|
||||||
- [02 Oct 01] In revised syntax, the warning for using old syntax for
|
- [02 Oct 01] In revised syntax, the warning for using old syntax for
|
||||||
sequences is now by default. To remove it, the option -no-warn-seq
|
sequences is now by default. To remove it, the option -no-warn-seq
|
||||||
of camlp4r has been added. Option -warn-seq has been removed.
|
of camlp4r has been added. Option -warn-seq has been removed.
|
||||||
|
|
|
@ -628,8 +628,14 @@ and str_item s l =
|
||||||
l]
|
l]
|
||||||
| StDcl loc sl -> List.fold_right str_item sl l
|
| StDcl loc sl -> List.fold_right str_item sl l
|
||||||
| StDir loc _ _ -> l
|
| StDir loc _ _ -> l
|
||||||
| StExc loc n tl ->
|
| StExc loc n tl sl ->
|
||||||
[mkstr loc (Pstr_exception n (List.map ctyp tl)) :: l]
|
let si =
|
||||||
|
match (tl, sl) with
|
||||||
|
[ (tl, []) -> Pstr_exception n (List.map ctyp tl)
|
||||||
|
| ([], sl) -> Pstr_exn_rebind n (long_id_of_string_list loc sl)
|
||||||
|
| _ -> error loc "bad exception declaration" ]
|
||||||
|
in
|
||||||
|
[mkstr loc si :: l]
|
||||||
| StExp loc e -> [mkstr loc (Pstr_eval (expr e)) :: l]
|
| StExp loc e -> [mkstr loc (Pstr_eval (expr e)) :: l]
|
||||||
| StExt loc n t p ->
|
| StExt loc n t p ->
|
||||||
[mkstr loc (Pstr_primitive n (mkvalue_desc t p)) :: l]
|
[mkstr loc (Pstr_primitive n (mkvalue_desc t p)) :: l]
|
||||||
|
|
|
@ -138,7 +138,7 @@ and str_item =
|
||||||
| StClt of loc and list (class_infos class_type)
|
| StClt of loc and list (class_infos class_type)
|
||||||
| StDcl of loc and list str_item
|
| StDcl of loc and list str_item
|
||||||
| StDir of loc and string and option expr
|
| StDir of loc and string and option expr
|
||||||
| StExc of loc and string and list ctyp
|
| StExc of loc and string and list ctyp and list string
|
||||||
| StExp of loc and expr
|
| StExp of loc and expr
|
||||||
| StExt of loc and string and ctyp and list string
|
| StExt of loc and string and ctyp and list string
|
||||||
| StInc of loc and module_expr
|
| StInc of loc and module_expr
|
||||||
|
|
|
@ -206,7 +206,7 @@ and str_item floc sh =
|
||||||
StClt (floc loc) (List.map (class_infos class_type floc sh) x1)
|
StClt (floc loc) (List.map (class_infos class_type floc sh) x1)
|
||||||
| StDcl loc x1 -> StDcl (floc loc) (List.map self x1)
|
| StDcl loc x1 -> StDcl (floc loc) (List.map self x1)
|
||||||
| StDir loc x1 x2 -> StDir (floc loc) x1 x2
|
| StDir loc x1 x2 -> StDir (floc loc) x1 x2
|
||||||
| StExc loc x1 x2 -> StExc (floc loc) x1 (List.map (ctyp floc sh) x2)
|
| StExc loc x1 x2 x3 -> StExc (floc loc) x1 (List.map (ctyp floc sh) x2) x3
|
||||||
| StExp loc x1 -> StExp (floc loc) (expr floc sh x1)
|
| StExp loc x1 -> StExp (floc loc) (expr floc sh x1)
|
||||||
| StExt loc x1 x2 x3 -> StExt (floc loc) x1 (ctyp floc sh x2) x3
|
| StExt loc x1 x2 x3 -> StExt (floc loc) x1 (ctyp floc sh x2) x3
|
||||||
| StInc loc x1 -> StInc (floc loc) (module_expr floc sh x1)
|
| StInc loc x1 -> StInc (floc loc) (module_expr floc sh x1)
|
||||||
|
|
|
@ -372,8 +372,8 @@ EXTEND
|
||||||
;
|
;
|
||||||
str_item:
|
str_item:
|
||||||
[ "top"
|
[ "top"
|
||||||
[ "exception"; (c, tl) = constructor_declaration ->
|
[ "exception"; (c, tl) = constructor_declaration; b = rebind_exn ->
|
||||||
<:str_item< exception $c$ of $list:tl$ >>
|
<:str_item< exception $c$ of $list:tl$ = $b$ >>
|
||||||
| "external"; i = LIDENT; ":"; t = ctyp; "="; pd = LIST1 STRING ->
|
| "external"; i = LIDENT; ":"; t = ctyp; "="; pd = LIST1 STRING ->
|
||||||
<:str_item< external $i$ : $t$ = $list:pd$ >>
|
<:str_item< external $i$ : $t$ = $list:pd$ >>
|
||||||
| "external"; "("; i = operator_rparen; ":"; t = ctyp; "=";
|
| "external"; "("; i = operator_rparen; ":"; t = ctyp; "=";
|
||||||
|
@ -399,6 +399,10 @@ EXTEND
|
||||||
<:str_item< let module $m$ = $mb$ in $e$ >>
|
<:str_item< let module $m$ = $mb$ in $e$ >>
|
||||||
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
||||||
;
|
;
|
||||||
|
rebind_exn:
|
||||||
|
[ [ "="; sl = mod_ident -> sl
|
||||||
|
| -> [] ] ]
|
||||||
|
;
|
||||||
module_binding:
|
module_binding:
|
||||||
[ RIGHTA
|
[ RIGHTA
|
||||||
[ "("; m = UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
|
[ "("; m = UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
|
||||||
|
@ -1118,20 +1122,30 @@ EXTEND
|
||||||
| "#"; t = mod_ident -> <:patt< # $list:t$ >> ] ]
|
| "#"; t = mod_ident -> <:patt< # $list:t$ >> ] ]
|
||||||
;
|
;
|
||||||
labeled_patt:
|
labeled_patt:
|
||||||
[ [ i = TILDEIDENTCOLON; p = patt LEVEL "simple" -> <:patt< ~ $i$ : $p$ >>
|
[ [ i = TILDEIDENTCOLON; p = patt LEVEL "simple" ->
|
||||||
| i = TILDEIDENT -> <:patt< ~ $i$ >>
|
<:patt< ~ $i$ : $p$ >>
|
||||||
| i = QUESTIONIDENTCOLON; j = LIDENT -> <:patt< ? $i$ : $lid:j$ >>
|
| i = TILDEIDENT ->
|
||||||
| i = QUESTIONIDENTCOLON; "("; lp = let_pattern; "="; e = expr; ")" ->
|
<:patt< ~ $i$ >>
|
||||||
<:patt< ? $i$ : ( $lp$ = $e$ ) >>
|
| "~"; "("; i = LIDENT; ":"; t = ctyp; ")" ->
|
||||||
| i = QUESTIONIDENT -> <:patt< ? $i$ : $lid:i$ >>
|
<:patt< ~ $i$ : ($lid:i$ : $t$) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; j = LIDENT ->
|
||||||
|
<:patt< ? $i$ : ($lid:j$) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; "("; p = patt; "="; e = expr; ")" ->
|
||||||
|
<:patt< ? $i$ : ( $p$ = $e$ ) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; "("; p = patt; ":"; t = ctyp; ")" ->
|
||||||
|
<:patt< ? $i$ : ( $p$ : $t$ ) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; "("; p = patt; ":"; t = ctyp; "=";
|
||||||
|
e = expr; ")" ->
|
||||||
|
<:patt< ? $i$ : ( $p$ : $t$ = $e$ ) >>
|
||||||
|
| i = QUESTIONIDENT -> <:patt< ? $i$ : ($lid:i$) >>
|
||||||
| "?"; "("; i = LIDENT; "="; e = expr; ")" ->
|
| "?"; "("; i = LIDENT; "="; e = expr; ")" ->
|
||||||
<:patt< ? $i$ : ( $lid:i$ = $e$ ) >>
|
<:patt< ? $i$ : ( $lid:i$ = $e$ ) >>
|
||||||
| "?"; "("; i = LIDENT; ":"; t = ctyp; "="; e = expr; ")" ->
|
| "?"; "("; i = LIDENT; ":"; t = ctyp; "="; e = expr; ")" ->
|
||||||
<:patt< ? $i$ : ( ($lid:i$ : $t$) = $e$ ) >> ] ]
|
<:patt< ? $i$ : ( $lid:i$ : $t$ = $e$ ) >>
|
||||||
;
|
| "?"; "("; i = LIDENT; ")" ->
|
||||||
let_pattern:
|
<:patt< ? $i$ >>
|
||||||
[ [ p = patt -> p
|
| "?"; "("; i = LIDENT; ":"; t = ctyp; ")" ->
|
||||||
| p = patt; ":"; t = ctyp -> <:patt< ($p$ : $t$) >> ] ]
|
<:patt< ? $i$ : ( $lid:i$ : $t$ ) >> ] ]
|
||||||
;
|
;
|
||||||
class_type:
|
class_type:
|
||||||
[ [ i = LIDENT; ":"; t = ctyp LEVEL "ctyp1"; "->"; ct = SELF ->
|
[ [ i = LIDENT; ":"; t = ctyp LEVEL "ctyp1"; "->"; ct = SELF ->
|
||||||
|
|
|
@ -1677,11 +1677,11 @@ EXTEND
|
||||||
labeled_patt:
|
labeled_patt:
|
||||||
[ [ i = LABEL; p = patt LEVEL "simple" -> <:patt< ~ $i$ : $p$ >>
|
[ [ i = LABEL; p = patt LEVEL "simple" -> <:patt< ~ $i$ : $p$ >>
|
||||||
| i = ELABEL -> <:patt< ~ $i$ >>
|
| i = ELABEL -> <:patt< ~ $i$ >>
|
||||||
| "?"; i = LABEL; j = LIDENT -> <:patt< ? $i$ : $lid:j$ >>
|
| "?"; i = LABEL; j = LIDENT -> <:patt< ? $i$ : ($lid:j$) >>
|
||||||
| "?"; "("; i = LABEL; j = LIDENT; ")" -> <:patt< ? $i$ : $lid:j$ >>
|
| "?"; "("; i = LABEL; j = LIDENT; ")" -> <:patt< ? $i$ : ($lid:j$) >>
|
||||||
| "?"; "("; i = LABEL; j = LIDENT; "="; e = expr; ")" ->
|
| "?"; "("; i = LABEL; j = LIDENT; "="; e = expr; ")" ->
|
||||||
<:patt< ? $i$ : ( $lid:j$ = $e$ ) >>
|
<:patt< ? $i$ : ( $lid:j$ = $e$ ) >>
|
||||||
| "?"; i = ELABEL -> <:patt< ? $i$ : $lid:i$ >>
|
| "?"; i = ELABEL -> <:patt< ? $i$ : ($lid:i$) >>
|
||||||
| "?"; "("; i = ELABEL; "="; e = expr; ")" ->
|
| "?"; "("; i = ELABEL; "="; e = expr; ")" ->
|
||||||
<:patt< ? $i$ : ( $lid:i$ = $e$ ) >> ] ]
|
<:patt< ? $i$ : ( $lid:i$ = $e$ ) >> ] ]
|
||||||
;
|
;
|
||||||
|
|
|
@ -172,7 +172,7 @@ and str_item =
|
||||||
[ StCls _ cil -> list (fun ci -> class_expr ci.ciExp) cil
|
[ StCls _ cil -> list (fun ci -> class_expr ci.ciExp) cil
|
||||||
| StDcl _ sil -> list str_item sil
|
| StDcl _ sil -> list str_item sil
|
||||||
| StDir _ _ _ -> ()
|
| StDir _ _ _ -> ()
|
||||||
| StExc _ _ tl -> list ctyp tl
|
| StExc _ _ tl _ -> list ctyp tl
|
||||||
| StExp _ e -> expr e
|
| StExp _ e -> expr e
|
||||||
| StExt _ _ t _ -> ctyp t
|
| StExt _ _ t _ -> ctyp t
|
||||||
| StMod _ _ me -> module_expr me
|
| StMod _ _ me -> module_expr me
|
||||||
|
|
|
@ -393,7 +393,7 @@ value rec is_irrefut_patt =
|
||||||
List.for_all (fun (_, p) -> is_irrefut_patt p) fpl
|
List.for_all (fun (_, p) -> is_irrefut_patt p) fpl
|
||||||
| <:patt< ($p$ : $_$) >> -> is_irrefut_patt p
|
| <:patt< ($p$ : $_$) >> -> is_irrefut_patt p
|
||||||
| <:patt< ($list:pl$) >> -> List.for_all is_irrefut_patt pl
|
| <:patt< ($list:pl$) >> -> List.for_all is_irrefut_patt pl
|
||||||
| <:patt< ? $_$ : $p$ >> -> is_irrefut_patt p
|
| <:patt< ? $_$ : ($p$) >> -> is_irrefut_patt p
|
||||||
| <:patt< ? $_$ : ($p$ = $_$) >> -> is_irrefut_patt p
|
| <:patt< ? $_$ : ($p$ = $_$) >> -> is_irrefut_patt p
|
||||||
| <:patt< ~ $_$ : $p$ >> -> is_irrefut_patt p
|
| <:patt< ~ $_$ : $p$ >> -> is_irrefut_patt p
|
||||||
| _ -> False ]
|
| _ -> False ]
|
||||||
|
@ -872,9 +872,13 @@ pr_str_item.pr_levels :=
|
||||||
" *)"
|
" *)"
|
||||||
in
|
in
|
||||||
[: `S LR s :]
|
[: `S LR s :]
|
||||||
| <:str_item< exception $c$ of $list:tl$ >> ->
|
| <:str_item< exception $c$ of $list:tl$ = $b$ >> ->
|
||||||
fun curr next dg k ->
|
fun curr next dg k ->
|
||||||
[: `variant [: `S LR "exception" :] (c, tl) "" k :]
|
match b with
|
||||||
|
[ [] -> [: `variant [: `S LR "exception" :] (c, tl) "" k :]
|
||||||
|
| _ ->
|
||||||
|
[: `variant [: `S LR "exception" :] (c, tl) "" [: `S LR "=" :];
|
||||||
|
mod_ident b "" k :] ]
|
||||||
| <:str_item< include $me$ >> ->
|
| <:str_item< include $me$ >> ->
|
||||||
fun curr next dg k -> [: `S LR "include"; `module_expr me "" k :]
|
fun curr next dg k -> [: `S LR "include"; `module_expr me "" k :]
|
||||||
| <:str_item< type $list:tdl$ >> ->
|
| <:str_item< type $list:tdl$ >> ->
|
||||||
|
@ -1561,9 +1565,9 @@ pr_patt.pr_levels :=
|
||||||
| <:patt< ~ $i$ : $p$ >> ->
|
| <:patt< ~ $i$ : $p$ >> ->
|
||||||
fun curr next dg k ->
|
fun curr next dg k ->
|
||||||
[: `S LO ("~" ^ i ^ ":"); `simple_patt p "" k :]
|
[: `S LO ("~" ^ i ^ ":"); `simple_patt p "" k :]
|
||||||
| <:patt< ? $i$ : $lid:j$ >> when i = j ->
|
| <:patt< ? $i$ : ($lid:j$) >> when i = j ->
|
||||||
fun curr next dg k -> [: `S LR ("?" ^ i); k :]
|
fun curr next dg k -> [: `S LR ("?" ^ i); k :]
|
||||||
| <:patt< ? $i$ : $p$ >> ->
|
| <:patt< ? $i$ : ($p$) >> ->
|
||||||
fun curr next dg k ->
|
fun curr next dg k ->
|
||||||
[: `S LO ("?" ^ i ^ ":"); `simple_patt p "" k :]
|
[: `S LO ("?" ^ i ^ ":"); `simple_patt p "" k :]
|
||||||
| <:patt< ? $i$ : ($lid:j$ = $e$) >> when i = j ->
|
| <:patt< ? $i$ : ($lid:j$ = $e$) >> when i = j ->
|
||||||
|
|
|
@ -296,7 +296,7 @@ value rec is_irrefut_patt =
|
||||||
List.for_all (fun (_, p) -> is_irrefut_patt p) fpl
|
List.for_all (fun (_, p) -> is_irrefut_patt p) fpl
|
||||||
| <:patt< ($p$ : $_$) >> -> is_irrefut_patt p
|
| <:patt< ($p$ : $_$) >> -> is_irrefut_patt p
|
||||||
| <:patt< ($list:pl$) >> -> List.for_all is_irrefut_patt pl
|
| <:patt< ($list:pl$) >> -> List.for_all is_irrefut_patt pl
|
||||||
| <:patt< ? $_$ : $p$ >> -> is_irrefut_patt p
|
| <:patt< ? $_$ : ( $p$ ) >> -> is_irrefut_patt p
|
||||||
| <:patt< ? $_$ : ($p$ = $_$) >> -> is_irrefut_patt p
|
| <:patt< ? $_$ : ($p$ = $_$) >> -> is_irrefut_patt p
|
||||||
| <:patt< ~ $_$ : $p$ >> -> is_irrefut_patt p
|
| <:patt< ~ $_$ : $p$ >> -> is_irrefut_patt p
|
||||||
| _ -> False ]
|
| _ -> False ]
|
||||||
|
@ -324,7 +324,7 @@ value rec get_defined_ident =
|
||||||
| <:patt< $p1$ .. $p2$ >> -> get_defined_ident p1 @ get_defined_ident p2
|
| <:patt< $p1$ .. $p2$ >> -> get_defined_ident p1 @ get_defined_ident p2
|
||||||
| <:patt< ($p$ : $_$) >> -> get_defined_ident p
|
| <:patt< ($p$ : $_$) >> -> get_defined_ident p
|
||||||
| <:patt< ~ $_$ : $p$ >> -> get_defined_ident p
|
| <:patt< ~ $_$ : $p$ >> -> get_defined_ident p
|
||||||
| <:patt< ? $_$ : $p$ >> -> get_defined_ident p
|
| <:patt< ? $_$ : ($p$) >> -> get_defined_ident p
|
||||||
| <:patt< ? $_$ : ($p$ = $e$) >> -> get_defined_ident p
|
| <:patt< ? $_$ : ($p$ = $e$) >> -> get_defined_ident p
|
||||||
| MLast.PaAnt _ p -> get_defined_ident p ]
|
| MLast.PaAnt _ p -> get_defined_ident p ]
|
||||||
;
|
;
|
||||||
|
@ -870,9 +870,13 @@ pr_str_item.pr_levels :=
|
||||||
" *)"
|
" *)"
|
||||||
in
|
in
|
||||||
[: `S LR s :]
|
[: `S LR s :]
|
||||||
| <:str_item< exception $c$ of $list:tl$ >> ->
|
| <:str_item< exception $c$ of $list:tl$ = $b$ >> ->
|
||||||
fun curr next _ k ->
|
fun curr next _ k ->
|
||||||
[: `variant [: `S LR "exception" :] (c, tl) k :]
|
match b with
|
||||||
|
[ [] -> [: `variant [: `S LR "exception" :] (c, tl) k :]
|
||||||
|
| _ ->
|
||||||
|
[: `variant [: `S LR "exception" :] (c, tl) [: `S LR "=" :];
|
||||||
|
mod_ident b k :] ]
|
||||||
| <:str_item< include $me$ >> ->
|
| <:str_item< include $me$ >> ->
|
||||||
fun curr next _ k -> [: `S LR "include"; `module_expr me k :]
|
fun curr next _ k -> [: `S LR "include"; `module_expr me k :]
|
||||||
| <:str_item< type $list:tdl$ >> ->
|
| <:str_item< type $list:tdl$ >> ->
|
||||||
|
@ -1391,18 +1395,19 @@ pr_patt.pr_levels :=
|
||||||
| <:patt< ` $i$ >> -> fun curr next _ k -> [: `S LR ("`" ^ i); k :]
|
| <:patt< ` $i$ >> -> fun curr next _ k -> [: `S LR ("`" ^ i); k :]
|
||||||
| <:patt< # $list:sl$ >> ->
|
| <:patt< # $list:sl$ >> ->
|
||||||
fun curr next _ k -> [: `S LO "#"; mod_ident sl k :]
|
fun curr next _ k -> [: `S LO "#"; mod_ident sl k :]
|
||||||
| <:patt< ~ $i$ : $lid:j$ >> when i = j ->
|
|
||||||
fun curr next _ k -> [: `S LR ("~" ^ i); k :]
|
|
||||||
| <:patt< ~ $i$ : $p$ >> ->
|
| <:patt< ~ $i$ : $p$ >> ->
|
||||||
fun curr next _ k -> [: `S LO ("~" ^ i ^ ":"); curr p "" k :]
|
fun curr next _ k -> [: `S LO ("~" ^ i ^ ":"); curr p "" k :]
|
||||||
| <:patt< ? $i$ : $lid:j$ >> when i = j ->
|
| <:patt< ? $i$ : ($p$ : $t$) >> ->
|
||||||
fun curr next _ k -> [: `S LR ("?" ^ i); k :]
|
|
||||||
| <:patt< ? $i$ : $p$ >> ->
|
|
||||||
fun curr next _ k -> [: `S LO ("?" ^ i ^ ":"); curr p "" k :]
|
|
||||||
| <:patt< ? $i$ : ($lid:j$ = $e$) >> when i = j ->
|
|
||||||
fun curr next _ k ->
|
fun curr next _ k ->
|
||||||
[: `S LO "?"; `S LO "("; `S LR (var_escaped j); `S LR "=";
|
[: `S LO ("?"^ i ^ ":"); `S LO "("; `patt p [: `S LR ":" :];
|
||||||
`expr e [: `S RO ")"; k :] :]
|
`ctyp t [: `S RO ")"; k :] :]
|
||||||
|
| <:patt< ? $i$ : ($p$) >> ->
|
||||||
|
fun curr next _ k ->
|
||||||
|
[: `S LO ("?"^ i ^ ":"); `S LO "("; `patt p [: `S RO ")"; k :] :]
|
||||||
|
| <:patt< ? $i$ : ($p$ : $t$ = $e$) >> ->
|
||||||
|
fun curr next _ k ->
|
||||||
|
[: `S LO ("?" ^ i ^ ":"); `S LO "("; `patt p [: `S LR ":" :];
|
||||||
|
`ctyp t [: `S LR "=" :]; `expr e [: `S RO ")"; k :] :]
|
||||||
| <:patt< ? $i$ : ($p$ = $e$) >> ->
|
| <:patt< ? $i$ : ($p$ = $e$) >> ->
|
||||||
fun curr next _ k ->
|
fun curr next _ k ->
|
||||||
[: `S LO ("?" ^ i ^ ":"); `S LO "("; `patt p [: `S LR "=" :];
|
[: `S LO ("?" ^ i ^ ":"); `S LO "("; `patt p [: `S LR "=" :];
|
||||||
|
|
|
@ -180,8 +180,8 @@ EXTEND
|
||||||
[ "top"
|
[ "top"
|
||||||
[ "declare"; st = LIST0 [ s = str_item; ";" -> s ]; "end" ->
|
[ "declare"; st = LIST0 [ s = str_item; ";" -> s ]; "end" ->
|
||||||
<:str_item< declare $list:st$ end >>
|
<:str_item< declare $list:st$ end >>
|
||||||
| "exception"; (c, tl) = constructor_declaration ->
|
| "exception"; (c, tl) = constructor_declaration; b = rebind_exn ->
|
||||||
<:str_item< exception $c$ of $list:tl$ >>
|
<:str_item< exception $c$ of $list:tl$ = $b$ >>
|
||||||
| "external"; i = LIDENT; ":"; t = ctyp; "="; pd = LIST1 STRING ->
|
| "external"; i = LIDENT; ":"; t = ctyp; "="; pd = LIST1 STRING ->
|
||||||
<:str_item< external $i$ : $t$ = $list:pd$ >>
|
<:str_item< external $i$ : $t$ = $list:pd$ >>
|
||||||
| "include"; me = module_expr -> <:str_item< include $me$ >>
|
| "include"; me = module_expr -> <:str_item< include $me$ >>
|
||||||
|
@ -196,6 +196,10 @@ EXTEND
|
||||||
<:str_item< value $rec:o2b r$ $list:l$ >>
|
<:str_item< value $rec:o2b r$ $list:l$ >>
|
||||||
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
| e = expr -> <:str_item< $exp:e$ >> ] ]
|
||||||
;
|
;
|
||||||
|
rebind_exn:
|
||||||
|
[ [ "="; sl = mod_ident -> sl
|
||||||
|
| -> [] ] ]
|
||||||
|
;
|
||||||
module_binding:
|
module_binding:
|
||||||
[ RIGHTA
|
[ RIGHTA
|
||||||
[ "("; m = UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
|
[ "("; m = UIDENT; ":"; mt = module_type; ")"; mb = SELF ->
|
||||||
|
@ -787,14 +791,21 @@ EXTEND
|
||||||
| "#"; sl = mod_ident -> <:patt< # $list:sl$ >> ] ]
|
| "#"; sl = mod_ident -> <:patt< # $list:sl$ >> ] ]
|
||||||
;
|
;
|
||||||
ipatt:
|
ipatt:
|
||||||
[ [ i = TILDEIDENTCOLON; p = SELF -> <:patt< ~ $i$ : $p$ >>
|
[ [ i = TILDEIDENTCOLON; p = SELF ->
|
||||||
| i = TILDEIDENT -> <:patt< ~ $i$ >>
|
<:patt< ~ $i$ : $p$ >>
|
||||||
| i = QUESTIONIDENTCOLON; j = LIDENT -> <:patt< ? $i$ : $lid:j$ >>
|
| i = TILDEIDENT ->
|
||||||
| i = QUESTIONIDENTCOLON; "("; j = LIDENT; "="; e = expr; ")" ->
|
<:patt< ~ $i$ >>
|
||||||
<:patt< ? $i$ : ( $lid:j$ = $e$ ) >>
|
| i = QUESTIONIDENTCOLON; "("; p = ipatt; ")" ->
|
||||||
| i = QUESTIONIDENT -> <:patt< ? $i$ : $lid:i$ >>
|
<:patt< ? $i$ : ( $p$ ) >>
|
||||||
| "?"; "("; i = LIDENT; "="; e = expr; ")" ->
|
| i = QUESTIONIDENTCOLON; "("; p = ipatt; "="; e = expr; ")" ->
|
||||||
<:patt< ? $i$ : ( $lid:i$ = $e$ ) >> ] ]
|
<:patt< ? $i$ : ( $p$ = $e$ ) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; "("; p = ipatt; ":"; t = ctyp; ")" ->
|
||||||
|
<:patt< ? $i$ : ( $p$ : $t$ ) >>
|
||||||
|
| i = QUESTIONIDENTCOLON; "("; p = ipatt; ":"; t = ctyp; "=";
|
||||||
|
e = expr; ")" ->
|
||||||
|
<:patt< ? $i$ : ( $p$ : $t$ = $e$ ) >>
|
||||||
|
| i = QUESTIONIDENT ->
|
||||||
|
<:patt< ? $i$ >> ] ]
|
||||||
;
|
;
|
||||||
expr: AFTER "apply"
|
expr: AFTER "apply"
|
||||||
[ "label"
|
[ "label"
|
||||||
|
|
|
@ -124,9 +124,9 @@ EXTEND
|
||||||
[ [ "declare"; st = SLIST0 [ s = str_item; ";" -> s ]; "end" ->
|
[ [ "declare"; st = SLIST0 [ s = str_item; ";" -> s ]; "end" ->
|
||||||
Node "StDcl" [st]
|
Node "StDcl" [st]
|
||||||
| "#"; n = lident; dp = dir_param -> Node "StDir" [n; dp]
|
| "#"; n = lident; dp = dir_param -> Node "StDir" [n; dp]
|
||||||
| "exception"; ctl = constructor_declaration ->
|
| "exception"; ctl = constructor_declaration; b = rebind_exn ->
|
||||||
match ctl with
|
match ctl with
|
||||||
[ Tuple ctl -> Node "StExc" ctl
|
[ Tuple ctl -> Node "StExc" (ctl @ [b])
|
||||||
| _ -> match () with [] ]
|
| _ -> match () with [] ]
|
||||||
| "external"; i = lident; ":"; t = ctyp; "="; p = SLIST1 string ->
|
| "external"; i = lident; ":"; t = ctyp; "="; p = SLIST1 string ->
|
||||||
Node "StExt" [i; t; p]
|
Node "StExt" [i; t; p]
|
||||||
|
@ -142,6 +142,10 @@ EXTEND
|
||||||
| e = expr -> Node "StExp" [e]
|
| e = expr -> Node "StExp" [e]
|
||||||
| e = anti_exp -> Node "StExp" [e] ] ]
|
| e = anti_exp -> Node "StExp" [e] ] ]
|
||||||
;
|
;
|
||||||
|
rebind_exn:
|
||||||
|
[ [ "="; sl = mod_ident -> sl
|
||||||
|
| -> List [] ] ]
|
||||||
|
;
|
||||||
module_binding:
|
module_binding:
|
||||||
[ RIGHTA
|
[ RIGHTA
|
||||||
[ "("; m = uident; ":"; mt = module_type; ")"; mb = SELF ->
|
[ "("; m = uident; ":"; mt = module_type; ")"; mb = SELF ->
|
||||||
|
@ -384,12 +388,19 @@ EXTEND
|
||||||
| [ p1 = SELF; p2 = SELF -> Node "PaApp" [p1; p2] ]
|
| [ p1 = SELF; p2 = SELF -> Node "PaApp" [p1; p2] ]
|
||||||
| [ p1 = SELF; "."; p2 = SELF -> Node "PaAcc" [p1; p2] ]
|
| [ p1 = SELF; "."; p2 = SELF -> Node "PaAcc" [p1; p2] ]
|
||||||
| NONA
|
| NONA
|
||||||
[ "~"; i = lident; ":"; p = SELF -> Node "PaLab" [i; p]
|
[ "~"; i = lident; ":"; p = SELF ->
|
||||||
| "~"; i = lident -> Node "PaLab" [i; Node "PaLid" [i]]
|
Node "PaLab" [i; p]
|
||||||
| "?"; i = lident; ":"; p = SELF -> Node "PaOlb" [i; p; Option None]
|
| "~"; i = lident ->
|
||||||
| "?"; i = lident; ":"; "("; p = SELF; "="; e = expr; ")" ->
|
Node "PaLab" [i; Node "PaLid" [i]]
|
||||||
Node "PaOlb" [i; p; Option (Some e)]
|
| "?"; i = lident; ":"; "("; p = patt; e = OPT [ "="; e = expr -> e ];
|
||||||
| "?"; i = lident -> Node "PaOlb" [i; Node "PaLid" [i]; Option None] ]
|
")" ->
|
||||||
|
Node "PaOlb" [i; p; Option e]
|
||||||
|
| "?"; i = lident; ":"; "("; p = patt; ":"; t = ctyp;
|
||||||
|
e = OPT [ "="; e = expr -> e ]; ")" ->
|
||||||
|
let p = Node "PaTyc" [p; t] in
|
||||||
|
Node "PaOlb" [i; p; Option e]
|
||||||
|
| "?"; i = lident ->
|
||||||
|
Node "PaOlb" [i; Node "PaLid" [i]; Option None] ]
|
||||||
| "simple"
|
| "simple"
|
||||||
[ v = LIDENT -> Node "PaLid" [Str v]
|
[ v = LIDENT -> Node "PaLid" [Str v]
|
||||||
| v = UIDENT -> Node "PaUid" [Str v]
|
| v = UIDENT -> Node "PaUid" [Str v]
|
||||||
|
|
|
@ -636,8 +636,14 @@ and str_item s l =
|
||||||
mkstr loc (Pstr_class_type (List.map (class_info class_type) ctd)) :: l
|
mkstr loc (Pstr_class_type (List.map (class_info class_type) ctd)) :: l
|
||||||
| StDcl (loc, sl) -> List.fold_right str_item sl l
|
| StDcl (loc, sl) -> List.fold_right str_item sl l
|
||||||
| StDir (loc, _, _) -> l
|
| StDir (loc, _, _) -> l
|
||||||
| StExc (loc, n, tl) ->
|
| StExc (loc, n, tl, sl) ->
|
||||||
mkstr loc (Pstr_exception (n, List.map ctyp tl)) :: l
|
let si =
|
||||||
|
match tl, sl with
|
||||||
|
tl, [] -> Pstr_exception (n, List.map ctyp tl)
|
||||||
|
| [], sl -> Pstr_exn_rebind (n, long_id_of_string_list loc sl)
|
||||||
|
| _ -> error loc "bad exception declaration"
|
||||||
|
in
|
||||||
|
mkstr loc si :: l
|
||||||
| StExp (loc, e) -> mkstr loc (Pstr_eval (expr e)) :: l
|
| StExp (loc, e) -> mkstr loc (Pstr_eval (expr e)) :: l
|
||||||
| StExt (loc, n, t, p) ->
|
| StExt (loc, n, t, p) ->
|
||||||
mkstr loc (Pstr_primitive (n, mkvalue_desc t p)) :: l
|
mkstr loc (Pstr_primitive (n, mkvalue_desc t p)) :: l
|
||||||
|
|
|
@ -136,7 +136,7 @@ and str_item =
|
||||||
| StClt of loc * class_type class_infos list
|
| StClt of loc * class_type class_infos list
|
||||||
| StDcl of loc * str_item list
|
| StDcl of loc * str_item list
|
||||||
| StDir of loc * string * expr option
|
| StDir of loc * string * expr option
|
||||||
| StExc of loc * string * ctyp list
|
| StExc of loc * string * ctyp list * string list
|
||||||
| StExp of loc * expr
|
| StExp of loc * expr
|
||||||
| StExt of loc * string * ctyp * string list
|
| StExt of loc * string * ctyp * string list
|
||||||
| StInc of loc * module_expr
|
| StInc of loc * module_expr
|
||||||
|
|
|
@ -222,7 +222,8 @@ and str_item floc sh =
|
||||||
StClt (floc loc, List.map (class_infos class_type floc sh) x1)
|
StClt (floc loc, List.map (class_infos class_type floc sh) x1)
|
||||||
| StDcl (loc, x1) -> StDcl (floc loc, List.map self x1)
|
| StDcl (loc, x1) -> StDcl (floc loc, List.map self x1)
|
||||||
| StDir (loc, x1, x2) -> StDir (floc loc, x1, x2)
|
| StDir (loc, x1, x2) -> StDir (floc loc, x1, x2)
|
||||||
| StExc (loc, x1, x2) -> StExc (floc loc, x1, List.map (ctyp floc sh) x2)
|
| StExc (loc, x1, x2, x3) ->
|
||||||
|
StExc (floc loc, x1, List.map (ctyp floc sh) x2, x3)
|
||||||
| StExp (loc, x1) -> StExp (floc loc, expr floc sh x1)
|
| StExp (loc, x1) -> StExp (floc loc, expr floc sh x1)
|
||||||
| StExt (loc, x1, x2, x3) -> StExt (floc loc, x1, ctyp floc sh x2, x3)
|
| StExt (loc, x1, x2, x3) -> StExt (floc loc, x1, ctyp floc sh x2, x3)
|
||||||
| StInc (loc, x1) -> StInc (floc loc, module_expr floc sh x1)
|
| StInc (loc, x1) -> StInc (floc loc, module_expr floc sh x1)
|
||||||
|
|
|
@ -148,6 +148,8 @@ Grammar.extend
|
||||||
and str_item_semi : 'str_item_semi Grammar.Entry.e =
|
and str_item_semi : 'str_item_semi Grammar.Entry.e =
|
||||||
grammar_entry_create "str_item_semi"
|
grammar_entry_create "str_item_semi"
|
||||||
and phrase : 'phrase Grammar.Entry.e = grammar_entry_create "phrase"
|
and phrase : 'phrase Grammar.Entry.e = grammar_entry_create "phrase"
|
||||||
|
and rebind_exn : 'rebind_exn Grammar.Entry.e =
|
||||||
|
grammar_entry_create "rebind_exn"
|
||||||
and module_binding : 'module_binding Grammar.Entry.e =
|
and module_binding : 'module_binding Grammar.Entry.e =
|
||||||
grammar_entry_create "module_binding"
|
grammar_entry_create "module_binding"
|
||||||
and module_declaration : 'module_declaration Grammar.Entry.e =
|
and module_declaration : 'module_declaration Grammar.Entry.e =
|
||||||
|
@ -385,10 +387,13 @@ Grammar.extend
|
||||||
Gramext.Snterm
|
Gramext.Snterm
|
||||||
(Grammar.Entry.obj
|
(Grammar.Entry.obj
|
||||||
(constructor_declaration :
|
(constructor_declaration :
|
||||||
'constructor_declaration Grammar.Entry.e))],
|
'constructor_declaration Grammar.Entry.e));
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (rebind_exn : 'rebind_exn Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (c, tl : 'constructor_declaration) _ (loc : int * int) ->
|
(fun (b : 'rebind_exn) (c, tl : 'constructor_declaration) _
|
||||||
(MLast.StExc (loc, c, tl) : 'str_item));
|
(loc : int * int) ->
|
||||||
|
(MLast.StExc (loc, c, tl, b) : 'str_item));
|
||||||
[Gramext.Stoken ("", "declare");
|
[Gramext.Stoken ("", "declare");
|
||||||
Gramext.Slist0
|
Gramext.Slist0
|
||||||
(Gramext.srules
|
(Gramext.srules
|
||||||
|
@ -401,6 +406,14 @@ Grammar.extend
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (st : 'e__2 list) _ (loc : int * int) ->
|
(fun _ (st : 'e__2 list) _ (loc : int * int) ->
|
||||||
(MLast.StDcl (loc, st) : 'str_item))]];
|
(MLast.StDcl (loc, st) : 'str_item))]];
|
||||||
|
Grammar.Entry.obj (rebind_exn : 'rebind_exn Grammar.Entry.e), None,
|
||||||
|
[None, None,
|
||||||
|
[[], Gramext.action (fun (loc : int * int) -> ([] : 'rebind_exn));
|
||||||
|
[Gramext.Stoken ("", "=");
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (mod_ident : 'mod_ident Grammar.Entry.e))],
|
||||||
|
Gramext.action
|
||||||
|
(fun (sl : 'mod_ident) _ (loc : int * int) -> (sl : 'rebind_exn))]];
|
||||||
Grammar.Entry.obj (module_binding : 'module_binding Grammar.Entry.e),
|
Grammar.Entry.obj (module_binding : 'module_binding Grammar.Entry.e),
|
||||||
None,
|
None,
|
||||||
[None, Some Gramext.RightA,
|
[None, Some Gramext.RightA,
|
||||||
|
@ -2358,29 +2371,39 @@ Grammar.extend
|
||||||
(MLast.PaVrn (loc, s) : 'patt))]];
|
(MLast.PaVrn (loc, s) : 'patt))]];
|
||||||
Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e), None,
|
Grammar.Entry.obj (ipatt : 'ipatt Grammar.Entry.e), None,
|
||||||
[None, None,
|
[None, None,
|
||||||
[[Gramext.Stoken ("", "?"); Gramext.Stoken ("", "(");
|
[[Gramext.Stoken ("QUESTIONIDENT", "")],
|
||||||
Gramext.Stoken ("LIDENT", ""); Gramext.Stoken ("", "=");
|
|
||||||
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
|
||||||
Gramext.Stoken ("", ")")],
|
|
||||||
Gramext.action
|
|
||||||
(fun _ (e : 'expr) _ (i : string) _ _ (loc : int * int) ->
|
|
||||||
(MLast.PaOlb (loc, i, MLast.PaLid (loc, i), Some e) : 'ipatt));
|
|
||||||
[Gramext.Stoken ("QUESTIONIDENT", "")],
|
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (i : string) (loc : int * int) ->
|
(fun (i : string) (loc : int * int) ->
|
||||||
(MLast.PaOlb (loc, i, MLast.PaLid (loc, i), None) : 'ipatt));
|
(MLast.PaOlb (loc, i, MLast.PaLid (loc, i), None) : 'ipatt));
|
||||||
[Gramext.Stoken ("QUESTIONIDENTCOLON", ""); Gramext.Stoken ("", "(");
|
[Gramext.Stoken ("QUESTIONIDENTCOLON", ""); Gramext.Stoken ("", "(");
|
||||||
Gramext.Stoken ("LIDENT", ""); Gramext.Stoken ("", "=");
|
Gramext.Sself; Gramext.Stoken ("", ":");
|
||||||
|
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e));
|
||||||
|
Gramext.Stoken ("", "=");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||||
Gramext.Stoken ("", ")")],
|
Gramext.Stoken ("", ")")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (e : 'expr) _ (j : string) _ (i : string) (loc : int * int) ->
|
(fun _ (e : 'expr) _ (t : 'ctyp) _ (p : 'ipatt) _ (i : string)
|
||||||
(MLast.PaOlb (loc, i, MLast.PaLid (loc, j), Some e) : 'ipatt));
|
(loc : int * int) ->
|
||||||
[Gramext.Stoken ("QUESTIONIDENTCOLON", "");
|
(MLast.PaOlb (loc, i, MLast.PaTyc (loc, p, t), Some e) : 'ipatt));
|
||||||
Gramext.Stoken ("LIDENT", "")],
|
[Gramext.Stoken ("QUESTIONIDENTCOLON", ""); Gramext.Stoken ("", "(");
|
||||||
|
Gramext.Sself; Gramext.Stoken ("", ":");
|
||||||
|
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e));
|
||||||
|
Gramext.Stoken ("", ")")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (j : string) (i : string) (loc : int * int) ->
|
(fun _ (t : 'ctyp) _ (p : 'ipatt) _ (i : string) (loc : int * int) ->
|
||||||
(MLast.PaOlb (loc, i, MLast.PaLid (loc, j), None) : 'ipatt));
|
(MLast.PaOlb (loc, i, MLast.PaTyc (loc, p, t), None) : 'ipatt));
|
||||||
|
[Gramext.Stoken ("QUESTIONIDENTCOLON", ""); Gramext.Stoken ("", "(");
|
||||||
|
Gramext.Sself; Gramext.Stoken ("", "=");
|
||||||
|
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
||||||
|
Gramext.Stoken ("", ")")],
|
||||||
|
Gramext.action
|
||||||
|
(fun _ (e : 'expr) _ (p : 'ipatt) _ (i : string) (loc : int * int) ->
|
||||||
|
(MLast.PaOlb (loc, i, p, Some e) : 'ipatt));
|
||||||
|
[Gramext.Stoken ("QUESTIONIDENTCOLON", ""); Gramext.Stoken ("", "(");
|
||||||
|
Gramext.Sself; Gramext.Stoken ("", ")")],
|
||||||
|
Gramext.action
|
||||||
|
(fun _ (p : 'ipatt) _ (i : string) (loc : int * int) ->
|
||||||
|
(MLast.PaOlb (loc, i, p, None) : 'ipatt));
|
||||||
[Gramext.Stoken ("TILDEIDENT", "")],
|
[Gramext.Stoken ("TILDEIDENT", "")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (i : string) (loc : int * int) ->
|
(fun (i : string) (loc : int * int) ->
|
||||||
|
|
|
@ -124,7 +124,9 @@ Grammar.extend
|
||||||
let grammar_entry_create s =
|
let grammar_entry_create s =
|
||||||
Grammar.Entry.create (Grammar.of_entry sig_item) s
|
Grammar.Entry.create (Grammar.of_entry sig_item) s
|
||||||
in
|
in
|
||||||
let module_binding : 'module_binding Grammar.Entry.e =
|
let rebind_exn : 'rebind_exn Grammar.Entry.e =
|
||||||
|
grammar_entry_create "rebind_exn"
|
||||||
|
and module_binding : 'module_binding Grammar.Entry.e =
|
||||||
grammar_entry_create "module_binding"
|
grammar_entry_create "module_binding"
|
||||||
and module_declaration : 'module_declaration Grammar.Entry.e =
|
and module_declaration : 'module_declaration Grammar.Entry.e =
|
||||||
grammar_entry_create "module_declaration"
|
grammar_entry_create "module_declaration"
|
||||||
|
@ -399,14 +401,17 @@ Grammar.extend
|
||||||
Gramext.Snterm
|
Gramext.Snterm
|
||||||
(Grammar.Entry.obj
|
(Grammar.Entry.obj
|
||||||
(constructor_declaration :
|
(constructor_declaration :
|
||||||
'constructor_declaration Grammar.Entry.e))],
|
'constructor_declaration Grammar.Entry.e));
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (rebind_exn : 'rebind_exn Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (ctl : 'constructor_declaration) _ (loc : int * int) ->
|
(fun (b : 'rebind_exn) (ctl : 'constructor_declaration) _
|
||||||
|
(loc : int * int) ->
|
||||||
(match ctl with
|
(match ctl with
|
||||||
Tuple ctl -> Node ("StExc", ctl)
|
Tuple ctl -> Node ("StExc", (ctl @ [b]))
|
||||||
| _ ->
|
| _ ->
|
||||||
match () with
|
match () with
|
||||||
_ -> raise (Match_failure ("meta/q_MLast.ml", 4375, 4391)) :
|
_ -> raise (Match_failure ("meta/q_MLast.ml", 4399, 4415)) :
|
||||||
'str_item));
|
'str_item));
|
||||||
[Gramext.Stoken ("", "#");
|
[Gramext.Stoken ("", "#");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
||||||
|
@ -436,6 +441,14 @@ Grammar.extend
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (st : ast) _ (loc : int * int) ->
|
(fun _ (st : ast) _ (loc : int * int) ->
|
||||||
(Node ("StDcl", [st]) : 'str_item))]];
|
(Node ("StDcl", [st]) : 'str_item))]];
|
||||||
|
Grammar.Entry.obj (rebind_exn : 'rebind_exn Grammar.Entry.e), None,
|
||||||
|
[None, None,
|
||||||
|
[[], Gramext.action (fun (loc : int * int) -> (List [] : 'rebind_exn));
|
||||||
|
[Gramext.Stoken ("", "=");
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (mod_ident : 'mod_ident Grammar.Entry.e))],
|
||||||
|
Gramext.action
|
||||||
|
(fun (sl : 'mod_ident) _ (loc : int * int) -> (sl : 'rebind_exn))]];
|
||||||
Grammar.Entry.obj (module_binding : 'module_binding Grammar.Entry.e),
|
Grammar.Entry.obj (module_binding : 'module_binding Grammar.Entry.e),
|
||||||
None,
|
None,
|
||||||
[None, Some Gramext.RightA,
|
[None, Some Gramext.RightA,
|
||||||
|
@ -635,7 +648,7 @@ Grammar.extend
|
||||||
Tuple ctl -> Node ("SgExc", ctl)
|
Tuple ctl -> Node ("SgExc", ctl)
|
||||||
| _ ->
|
| _ ->
|
||||||
match () with
|
match () with
|
||||||
_ -> raise (Match_failure ("meta/q_MLast.ml", 6289, 6305)) :
|
_ -> raise (Match_failure ("meta/q_MLast.ml", 6388, 6404)) :
|
||||||
'sig_item));
|
'sig_item));
|
||||||
[Gramext.Stoken ("", "#");
|
[Gramext.Stoken ("", "#");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
||||||
|
@ -1467,19 +1480,37 @@ Grammar.extend
|
||||||
[Gramext.Stoken ("", "?");
|
[Gramext.Stoken ("", "?");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
||||||
Gramext.Stoken ("", ":"); Gramext.Stoken ("", "("); Gramext.Sself;
|
Gramext.Stoken ("", ":"); Gramext.Stoken ("", "("); Gramext.Sself;
|
||||||
Gramext.Stoken ("", "=");
|
Gramext.Stoken ("", ":");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (expr : 'expr Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (ctyp : 'ctyp Grammar.Entry.e));
|
||||||
|
Gramext.Sopt
|
||||||
|
(Gramext.srules
|
||||||
|
[[Gramext.Stoken ("", "=");
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||||
|
Gramext.action
|
||||||
|
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__19))]);
|
||||||
Gramext.Stoken ("", ")")],
|
Gramext.Stoken ("", ")")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (e : 'expr) _ (p : 'patt) _ _ (i : 'lident) _
|
(fun _ (e : 'e__19 option) (t : 'ctyp) _ (p : 'patt) _ _ (i : 'lident)
|
||||||
(loc : int * int) ->
|
_ (loc : int * int) ->
|
||||||
(Node ("PaOlb", [i; p; Option (Some e)]) : 'patt));
|
(let p = Node ("PaTyc", [p; t]) in
|
||||||
|
Node ("PaOlb", [i; p; Option e]) :
|
||||||
|
'patt));
|
||||||
[Gramext.Stoken ("", "?");
|
[Gramext.Stoken ("", "?");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e));
|
||||||
Gramext.Stoken ("", ":"); Gramext.Sself],
|
Gramext.Stoken ("", ":"); Gramext.Stoken ("", "("); Gramext.Sself;
|
||||||
|
Gramext.Sopt
|
||||||
|
(Gramext.srules
|
||||||
|
[[Gramext.Stoken ("", "=");
|
||||||
|
Gramext.Snterm
|
||||||
|
(Grammar.Entry.obj (expr : 'expr Grammar.Entry.e))],
|
||||||
|
Gramext.action
|
||||||
|
(fun (e : 'expr) _ (loc : int * int) -> (e : 'e__18))]);
|
||||||
|
Gramext.Stoken ("", ")")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (p : 'patt) _ (i : 'lident) _ (loc : int * int) ->
|
(fun _ (e : 'e__18 option) (p : 'patt) _ _ (i : 'lident) _
|
||||||
(Node ("PaOlb", [i; p; Option None]) : 'patt));
|
(loc : int * int) ->
|
||||||
|
(Node ("PaOlb", [i; p; Option e]) : 'patt));
|
||||||
[Gramext.Stoken ("", "~");
|
[Gramext.Stoken ("", "~");
|
||||||
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e))],
|
Gramext.Snterm (Grammar.Entry.obj (lident : 'lident Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
@ -1578,10 +1609,10 @@ Grammar.extend
|
||||||
Gramext.Snterm
|
Gramext.Snterm
|
||||||
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
|
(Grammar.Entry.obj (patt : 'patt Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__18))]);
|
(fun (p : 'patt) _ (loc : int * int) -> (p : 'e__20))]);
|
||||||
Gramext.Stoken ("", "]")],
|
Gramext.Stoken ("", "]")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (last : 'e__18 option) (pl : 'patt list) _ (loc : int * int) ->
|
(fun _ (last : 'e__20 option) (pl : 'patt list) _ (loc : int * int) ->
|
||||||
(mklistpat last pl : 'patt));
|
(mklistpat last pl : 'patt));
|
||||||
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
[Gramext.Stoken ("", "["); Gramext.Stoken ("", "]")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
@ -2586,9 +2617,9 @@ Grammar.extend
|
||||||
Gramext.Stoken ("", ";")],
|
Gramext.Stoken ("", ";")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (cf : 'class_str_item) (loc : int * int) ->
|
(fun _ (cf : 'class_str_item) (loc : int * int) ->
|
||||||
(cf : 'e__19))])],
|
(cf : 'e__21))])],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (l : 'e__19 list) (loc : int * int) -> (list l : 'anti));
|
(fun (l : 'e__21 list) (loc : int * int) -> (list l : 'anti));
|
||||||
[Gramext.Snterm
|
[Gramext.Snterm
|
||||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
@ -2683,9 +2714,9 @@ Grammar.extend
|
||||||
Gramext.Stoken ("", ";")],
|
Gramext.Stoken ("", ";")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (s : 'class_str_item) (loc : int * int) ->
|
(fun _ (s : 'class_str_item) (loc : int * int) ->
|
||||||
(s : 'e__20))])],
|
(s : 'e__22))])],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (l : 'e__20 list) (loc : int * int) -> (list l : 'anti));
|
(fun (l : 'e__22 list) (loc : int * int) -> (list l : 'anti));
|
||||||
[Gramext.Snterm
|
[Gramext.Snterm
|
||||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
@ -2759,9 +2790,9 @@ Grammar.extend
|
||||||
Gramext.Stoken ("", ";")],
|
Gramext.Stoken ("", ";")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (csf : 'class_sig_item) (loc : int * int) ->
|
(fun _ (csf : 'class_sig_item) (loc : int * int) ->
|
||||||
(csf : 'e__21))])],
|
(csf : 'e__23))])],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (l : 'e__21 list) (loc : int * int) -> (list l : 'anti));
|
(fun (l : 'e__23 list) (loc : int * int) -> (list l : 'anti));
|
||||||
[Gramext.Snterm
|
[Gramext.Snterm
|
||||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
@ -2882,9 +2913,9 @@ Grammar.extend
|
||||||
Gramext.Stoken ("", ";")],
|
Gramext.Stoken ("", ";")],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun _ (s : 'class_sig_item) (loc : int * int) ->
|
(fun _ (s : 'class_sig_item) (loc : int * int) ->
|
||||||
(s : 'e__22))])],
|
(s : 'e__24))])],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
(fun (l : 'e__22 list) (loc : int * int) -> (list l : 'anti));
|
(fun (l : 'e__24 list) (loc : int * int) -> (list l : 'anti));
|
||||||
[Gramext.Snterm
|
[Gramext.Snterm
|
||||||
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
(Grammar.Entry.obj (anti_list : 'anti_list Grammar.Entry.e))],
|
||||||
Gramext.action
|
Gramext.action
|
||||||
|
|
Loading…
Reference in New Issue