diff options
author | Alain Frisch <alain@frisch.fr> | 2013-05-16 13:34:53 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-05-16 13:34:53 +0000 |
commit | a3b1c67fffd7de640ee9a0791f1fd0fad965b867 (patch) | |
tree | c858e0cb4ebdd42a648b25e620a19a53fc1fa6e6 /parsing | |
parent | e4098f9f42000fbf2381a96115142a4aa3ba4a34 (diff) |
#5980: explicit way to silence the new warning (open! X).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13685 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'parsing')
-rw-r--r-- | parsing/ast_mapper.ml | 12 | ||||
-rw-r--r-- | parsing/ast_mapper.mli | 6 | ||||
-rw-r--r-- | parsing/parser.mly | 14 | ||||
-rw-r--r-- | parsing/parsetree.mli | 6 | ||||
-rw-r--r-- | parsing/pprintast.ml | 12 | ||||
-rw-r--r-- | parsing/printast.ml | 15 |
6 files changed, 36 insertions, 29 deletions
diff --git a/parsing/ast_mapper.ml b/parsing/ast_mapper.ml index 3cb24a45a..2caca7c67 100644 --- a/parsing/ast_mapper.ml +++ b/parsing/ast_mapper.ml @@ -173,7 +173,7 @@ module MT = struct let module_ ?loc a b = mk_item ?loc (Psig_module (a, b)) let rec_module ?loc a = mk_item ?loc (Psig_recmodule a) let modtype ?loc a b = mk_item ?loc (Psig_modtype (a, b)) - let open_ ?loc a = mk_item ?loc (Psig_open a) + let open_ ?loc a b = mk_item ?loc (Psig_open (a, b)) let include_ ?loc a = mk_item ?loc (Psig_include a) let class_ ?loc a = mk_item ?loc (Psig_class a) let class_type ?loc a = mk_item ?loc (Psig_class_type a) @@ -188,7 +188,7 @@ module MT = struct | Psig_recmodule l -> rec_module ~loc (List.map (map_tuple (map_loc sub) (sub # module_type)) l) | Psig_modtype (s, Pmodtype_manifest mt) -> modtype ~loc (map_loc sub s) (Pmodtype_manifest (sub # module_type mt)) | Psig_modtype (s, Pmodtype_abstract) -> modtype ~loc (map_loc sub s) Pmodtype_abstract - | Psig_open s -> open_ ~loc (map_loc sub s) + | Psig_open (ovf, s) -> open_ ~loc ovf (map_loc sub s) | Psig_include mt -> include_ ~loc (sub # module_type mt) | Psig_class l -> class_ ~loc (List.map (sub # class_description) l) | Psig_class_type l -> class_type ~loc (List.map (sub # class_type_declaration) l) @@ -227,7 +227,7 @@ module M = struct let module_ ?loc a b = mk_item ?loc (Pstr_module (a, b)) let rec_module ?loc a = mk_item ?loc (Pstr_recmodule a) let modtype ?loc a b = mk_item ?loc (Pstr_modtype (a, b)) - let open_ ?loc a = mk_item ?loc (Pstr_open a) + let open_ ?loc a b = mk_item ?loc (Pstr_open (a, b)) let class_ ?loc a = mk_item ?loc (Pstr_class a) let class_type ?loc a = mk_item ?loc (Pstr_class_type a) let include_ ?loc a = mk_item ?loc (Pstr_include a) @@ -244,7 +244,7 @@ module M = struct | Pstr_module (s, m) -> module_ ~loc (map_loc sub s) (sub # module_expr m) | Pstr_recmodule l -> rec_module ~loc (List.map (fun (s, mty, me) -> (map_loc sub s, sub # module_type mty, sub # module_expr me)) l) | Pstr_modtype (s, mty) -> modtype ~loc (map_loc sub s) (sub # module_type mty) - | Pstr_open lid -> open_ ~loc (map_loc sub lid) + | Pstr_open (ovf, lid) -> open_ ~loc ovf (map_loc sub lid) | Pstr_class l -> class_ ~loc (List.map (sub # class_declaration) l) | Pstr_class_type l -> class_type ~loc (List.map (sub # class_type_declaration) l) | Pstr_include e -> include_ ~loc (sub # module_expr e) @@ -287,7 +287,7 @@ module E = struct let object_ ?loc a = mk ?loc (Pexp_object a) let newtype ?loc a b = mk ?loc (Pexp_newtype (a, b)) let pack ?loc a = mk ?loc (Pexp_pack a) - let open_ ?loc a b = mk ?loc (Pexp_open (a, b)) + let open_ ?loc a b c = mk ?loc (Pexp_open (a, b, c)) let lid ?(loc = Location.none) lid = ident ~loc (mkloc (Longident.parse lid) loc) let apply_nolabs ?loc f el = apply ?loc f (List.map (fun e -> ("", e)) el) @@ -328,7 +328,7 @@ module E = struct | Pexp_object cls -> object_ ~loc (sub # class_structure cls) | Pexp_newtype (s, e) -> newtype ~loc s (sub # expr e) | Pexp_pack me -> pack ~loc (sub # module_expr me) - | Pexp_open (lid, e) -> open_ ~loc (map_loc sub lid) (sub # expr e) + | Pexp_open (ovf, lid, e) -> open_ ~loc ovf (map_loc sub lid) (sub # expr e) end module P = struct diff --git a/parsing/ast_mapper.mli b/parsing/ast_mapper.mli index 74714cdb2..10be4a8eb 100644 --- a/parsing/ast_mapper.mli +++ b/parsing/ast_mapper.mli @@ -145,7 +145,7 @@ module MT: val module_: ?loc:Location.t -> string loc -> module_type -> signature_item val rec_module: ?loc:Location.t -> (string loc * module_type) list -> signature_item val modtype: ?loc:Location.t -> string loc -> modtype_declaration -> signature_item - val open_: ?loc:Location.t -> Longident.t loc -> signature_item + val open_: ?loc:Location.t -> override_flag -> Longident.t loc -> signature_item val include_: ?loc:Location.t -> module_type -> signature_item val class_: ?loc:Location.t -> class_description list -> signature_item val class_type: ?loc:Location.t -> class_type_declaration list -> signature_item @@ -172,7 +172,7 @@ module M: val module_: ?loc:Location.t -> string loc -> module_expr -> structure_item val rec_module: ?loc:Location.t -> (string loc * module_type * module_expr) list -> structure_item val modtype: ?loc:Location.t -> string loc -> module_type -> structure_item - val open_: ?loc:Location.t -> Longident.t loc -> structure_item + val open_: ?loc:Location.t -> override_flag -> Longident.t loc -> structure_item val class_: ?loc:Location.t -> class_declaration list -> structure_item val class_type: ?loc:Location.t -> class_type_declaration list -> structure_item val include_: ?loc:Location.t -> module_expr -> structure_item @@ -214,7 +214,7 @@ module E: val object_: ?loc:Location.t -> class_structure -> expression val newtype: ?loc:Location.t -> string -> expression -> expression val pack: ?loc:Location.t -> module_expr -> expression - val open_: ?loc:Location.t -> Longident.t loc -> expression -> expression + val open_: ?loc:Location.t -> override_flag -> Longident.t loc -> expression -> expression val lid: ?loc:Location.t -> string -> expression val apply_nolabs: ?loc:Location.t -> expression -> expression list -> expression val strconst: ?loc:Location.t -> string -> expression diff --git a/parsing/parser.mly b/parsing/parser.mly index 35145b597..429d6bec0 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -594,8 +594,8 @@ structure_item: { mkstr(Pstr_recmodule(List.rev $3)) } | MODULE TYPE ident EQUAL module_type { mkstr(Pstr_modtype(mkrhs $3 3, $5)) } - | OPEN mod_longident - { mkstr(Pstr_open (mkrhs $2 2)) } + | OPEN override_flag mod_longident + { mkstr(Pstr_open ($2, mkrhs $3 3)) } | CLASS class_declarations { mkstr(Pstr_class (List.rev $2)) } | CLASS TYPE class_type_declarations @@ -664,8 +664,8 @@ signature_item: { mksig(Psig_modtype(mkrhs $3 3, Pmodtype_abstract)) } | MODULE TYPE ident EQUAL module_type { mksig(Psig_modtype(mkrhs $3 3, Pmodtype_manifest $5)) } - | OPEN mod_longident - { mksig(Psig_open (mkrhs $2 2)) } + | OPEN override_flag mod_longident + { mksig(Psig_open ($2, mkrhs $3 3)) } | INCLUDE module_type { mksig(Psig_include $2) } | CLASS class_descriptions @@ -970,8 +970,8 @@ expr: { mkexp(Pexp_let($2, List.rev $3, $5)) } | LET MODULE UIDENT module_binding IN seq_expr { mkexp(Pexp_letmodule(mkrhs $3 3, $4, $6)) } - | LET OPEN mod_longident IN seq_expr - { mkexp(Pexp_open(mkrhs $3 3, $5)) } + | LET OPEN override_flag mod_longident IN seq_expr + { mkexp(Pexp_open($3, mkrhs $4 4, $6)) } | FUNCTION opt_bar match_cases { mkexp(Pexp_function("", None, List.rev $3)) } | FUN labeled_simple_pattern fun_def @@ -1088,7 +1088,7 @@ simple_expr: | simple_expr DOT label_longident { mkexp(Pexp_field($1, mkrhs $3 3)) } | mod_longident DOT LPAREN seq_expr RPAREN - { mkexp(Pexp_open(mkrhs $1 1, $4)) } + { mkexp(Pexp_open(Fresh, mkrhs $1 1, $4)) } | mod_longident DOT LPAREN seq_expr error { unclosed "(" 3 ")" 5 } | simple_expr DOT LPAREN seq_expr RPAREN diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index b802fc85a..ce6ac362d 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -118,7 +118,7 @@ and expression_desc = | Pexp_object of class_structure | Pexp_newtype of string * expression | Pexp_pack of module_expr - | Pexp_open of Longident.t loc * expression + | Pexp_open of override_flag * Longident.t loc * expression (* Value descriptions *) @@ -242,7 +242,7 @@ and signature_item_desc = | Psig_module of string loc * module_type | Psig_recmodule of (string loc * module_type) list | Psig_modtype of string loc * modtype_declaration - | Psig_open of Longident.t loc + | Psig_open of override_flag * Longident.t loc | Psig_include of module_type | Psig_class of class_description list | Psig_class_type of class_type_declaration list @@ -287,7 +287,7 @@ and structure_item_desc = | Pstr_module of string loc * module_expr | Pstr_recmodule of (string loc * module_type * module_expr) list | Pstr_modtype of string loc * module_type - | Pstr_open of Longident.t loc + | Pstr_open of override_flag * Longident.t loc | Pstr_class of class_declaration list | Pstr_class_type of class_type_declaration list | Pstr_include of module_expr diff --git a/parsing/pprintast.ml b/parsing/pprintast.ml index 812867522..e409849c7 100644 --- a/parsing/pprintast.ml +++ b/parsing/pprintast.ml @@ -612,8 +612,8 @@ class printer ()= object(self:'self) pp f "@[<hov2>lazy@ %a@]" self#simple_expr e | Pexp_poly _ -> assert false - | Pexp_open (lid, e) -> - pp f "@[<2>let open %a in@;%a@]" self#longident_loc lid + | Pexp_open (ovf, lid, e) -> + pp f "@[<2>let open%s %a in@;%a@]" (override ovf) self#longident_loc lid self#expression e | Pexp_variant (l,Some eo) -> pp f "@[<2>`%s@;%a@]" l self#simple_expr eo @@ -881,8 +881,8 @@ class printer ()= object(self:'self) pp f "@[<hov>module@ %s@ :@ %a@]" s.txt self#module_type mt - | Psig_open li -> - pp f "@[<hov2>open@ %a@]" self#longident_loc li + | Psig_open (ovf, li) -> + pp f "@[<hov2>open%s@ %a@]" (override ovf) self#longident_loc li | Psig_include (mt) -> pp f "@[<hov2>include@ %a@]" self#module_type mt @@ -1017,8 +1017,8 @@ class printer ()= object(self:'self) | _ -> pp f " =@ %a" self#module_expr me )) me - | Pstr_open (li) -> - pp f "@[<2>open@;%a@]" self#longident_loc li; + | Pstr_open (ovf, li) -> + pp f "@[<2>open%s@;%a@]" (override ovf) self#longident_loc li; | Pstr_modtype (s, mt) -> pp f "@[<2>module type %s =@;%a@]" s.txt self#module_type mt | Pstr_class l -> diff --git a/parsing/printast.ml b/parsing/printast.ml index 41e13eaeb..22c68ee4b 100644 --- a/parsing/printast.ml +++ b/parsing/printast.ml @@ -334,8 +334,9 @@ and expression i ppf x = | Pexp_pack me -> line i ppf "Pexp_pack\n"; module_expr i ppf me - | Pexp_open (m, e) -> - line i ppf "Pexp_open \"%a\"\n" fmt_longident_loc m; + | Pexp_open (ovf, m, e) -> + line i ppf "Pexp_open %a \"%a\"\n" fmt_override_flag ovf + fmt_longident_loc m; expression i ppf e and value_description i ppf x = @@ -558,7 +559,10 @@ and signature_item i ppf x = | Psig_modtype (s, md) -> line i ppf "Psig_modtype %a\n" fmt_string_loc s; modtype_declaration i ppf md; - | Psig_open li -> line i ppf "Psig_open %a\n" fmt_longident_loc li; + | Psig_open (ovf, li) -> + line i ppf "Psig_open %a %a\n" + fmt_override_flag ovf + fmt_longident_loc li; | Psig_include (mt) -> line i ppf "Psig_include\n"; module_type i ppf mt; @@ -645,7 +649,10 @@ and structure_item i ppf x = | Pstr_modtype (s, mt) -> line i ppf "Pstr_modtype %a\n" fmt_string_loc s; module_type i ppf mt; - | Pstr_open li -> line i ppf "Pstr_open %a\n" fmt_longident_loc li; + | Pstr_open (ovf, li) -> + line i ppf "Pstr_open %a %a\n" + fmt_override_flag ovf + fmt_longident_loc li; | Pstr_class (l) -> line i ppf "Pstr_class\n"; list i class_declaration ppf l; |