diff options
Diffstat (limited to 'parsing')
-rw-r--r-- | parsing/parser.mly | 21 | ||||
-rw-r--r-- | parsing/parsetree.mli | 2 | ||||
-rw-r--r-- | parsing/printast.ml | 15 |
3 files changed, 37 insertions, 1 deletions
diff --git a/parsing/parser.mly b/parsing/parser.mly index 574112f1d..6f673e9e8 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -326,7 +326,8 @@ The precedences must be listed from low to high. %nonassoc IN %nonassoc below_SEMI %nonassoc SEMI /* below EQUAL ({lbl=...; lbl=...}) */ -%nonassoc LET /* above SEMI ( ...; let ... in ...) */ +%nonassoc LET AND /* above SEMI ( ...; let ... in ...) */ + /* below WITH (module rec A: SIG with ... and ...) */ %nonassoc below_WITH %nonassoc FUNCTION WITH /* below BAR (match ... with ...) */ %nonassoc THEN /* below ELSE (if ... then ...) */ @@ -455,6 +456,8 @@ structure_item: { mkstr(Pstr_exn_rebind($2, $4)) } | MODULE UIDENT module_binding { mkstr(Pstr_module($2, $3)) } + | MODULE REC module_rec_bindings + { mkstr(Pstr_recmodule(List.rev $3)) } | MODULE TYPE ident EQUAL module_type { mkstr(Pstr_modtype($3, $5)) } | OPEN mod_longident @@ -474,6 +477,13 @@ module_binding: | LPAREN UIDENT COLON module_type RPAREN module_binding { mkmod(Pmod_functor($2, $4, $6)) } ; +module_rec_bindings: + module_rec_binding { [$1] } + | module_rec_bindings AND module_rec_binding { $3 :: $1 } +; +module_rec_binding: + UIDENT COLON module_type EQUAL module_expr { ($1, $3, $5) } +; /* Module types */ @@ -510,6 +520,8 @@ signature_item: { mksig(Psig_exception($2, $3)) } | MODULE UIDENT module_declaration { mksig(Psig_module($2, $3)) } + | MODULE REC module_rec_declarations + { mksig(Psig_recmodule(List.rev $3)) } | MODULE TYPE ident { mksig(Psig_modtype($3, Pmodtype_abstract)) } | MODULE TYPE ident EQUAL module_type @@ -530,6 +542,13 @@ module_declaration: | LPAREN UIDENT COLON module_type RPAREN module_declaration { mkmty(Pmty_functor($2, $4, $6)) } ; +module_rec_declarations: + module_rec_declaration { [$1] } + | module_rec_declarations AND module_rec_declaration { $3 :: $1 } +; +module_rec_declaration: + UIDENT COLON module_type { ($1, $3) } +; /* Class expressions */ diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index 69763d256..10c7bcd2d 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -209,6 +209,7 @@ and signature_item_desc = | Psig_type of (string * type_declaration) list | Psig_exception of string * exception_declaration | Psig_module of string * module_type + | Psig_recmodule of (string * module_type) list | Psig_modtype of string * modtype_declaration | Psig_open of Longident.t | Psig_include of module_type @@ -250,6 +251,7 @@ and structure_item_desc = | Pstr_exception of string * exception_declaration | Pstr_exn_rebind of string * Longident.t | Pstr_module of string * module_expr + | Pstr_recmodule of (string * module_type * module_expr) list | Pstr_modtype of string * module_type | Pstr_open of Longident.t | Pstr_class of class_declaration list diff --git a/parsing/printast.ml b/parsing/printast.ml index 5ea5d4e0d..9cc166d44 100644 --- a/parsing/printast.ml +++ b/parsing/printast.ml @@ -494,6 +494,9 @@ and signature_item i ppf x = | Psig_module (s, mt) -> line i ppf "Psig_module \"%s\"\n" s; module_type i ppf mt; + | Psig_recmodule decls -> + line i ppf "Psig_recmodule\n"; + list i string_x_module_type ppf decls; | Psig_modtype (s, md) -> line i ppf "Psig_modtype \"%s\"\n" s; modtype_declaration i ppf md; @@ -569,6 +572,9 @@ and structure_item i ppf x = | Pstr_module (s, me) -> line i ppf "Pstr_module \"%s\"\n" s; module_expr i ppf me; + | Pstr_recmodule bindings -> + line i ppf "Pstr_type\n"; + list i string_x_modtype_x_module ppf bindings; | Pstr_modtype (s, mt) -> line i ppf "Pstr_modtype \"%s\"\n" s; module_type i ppf mt; @@ -587,6 +593,15 @@ and string_x_type_declaration i ppf (s, td) = string i ppf s; type_declaration (i+1) ppf td; +and string_x_module_type i ppf (s, mty) = + string i ppf s; + module_type (i+1) ppf mty; + +and string_x_modtype_x_module i ppf (s, mty, modl) = + string i ppf s; + module_type (i+1) ppf mty; + module_expr (i+1) ppf modl; + and longident_x_with_constraint i ppf (li, wc) = line i ppf "%a\n" fmt_longident li; with_constraint (i+1) ppf wc; |