summaryrefslogtreecommitdiffstats
path: root/camlp4/Camlp4/Printers
diff options
context:
space:
mode:
authorNicolas Pouillard <np@nicolaspouillard.fr>2008-10-05 16:25:28 +0000
committerNicolas Pouillard <np@nicolaspouillard.fr>2008-10-05 16:25:28 +0000
commit926961ed062959718d51097e4c5dd9925143e11a (patch)
treebfe791f8e80044a1d17a94c4d46a86167f003ee3 /camlp4/Camlp4/Printers
parenta71f5a0fe21c78a5bf843045d94f6f1fac75df4b (diff)
camlp4,printer: Fix a printing bug, parens in "include(struct end:sig end)"
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9066 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'camlp4/Camlp4/Printers')
-rw-r--r--camlp4/Camlp4/Printers/OCaml.ml14
-rw-r--r--camlp4/Camlp4/Printers/OCaml.mli1
-rw-r--r--camlp4/Camlp4/Printers/OCamlr.ml7
3 files changed, 18 insertions, 4 deletions
diff --git a/camlp4/Camlp4/Printers/OCaml.ml b/camlp4/Camlp4/Printers/OCaml.ml
index 1e1887596..c3f8fc282 100644
--- a/camlp4/Camlp4/Printers/OCaml.ml
+++ b/camlp4/Camlp4/Printers/OCaml.ml
@@ -822,7 +822,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
| <:str_item< $exp:e$ >> ->
pp f "@[<2>let _ =@ %a%(%)@]" o#expr e semisep
| <:str_item< include $me$ >> ->
- pp f "@[<2>include@ %a%(%)@]" o#module_expr me semisep
+ pp f "@[<2>include@ %a%(%)@]" o#simple_module_expr me semisep
| <:str_item< class type $ct$ >> ->
pp f "@[<2>class type %a%(%)@]" o#class_type ct semisep
| <:str_item< class $ce$ >> ->
@@ -864,6 +864,15 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
let () = o#node f me Ast.loc_of_module_expr in
match me with
[ <:module_expr<>> -> assert False
+ | <:module_expr< ( struct $st$ end : sig $sg$ end ) >> ->
+ pp f "@[<2>@[<hv2>struct@ %a@]@ end :@ @[<hv2>sig@ %a@]@ end@]"
+ o#str_item st o#sig_item sg
+ | _ -> o#simple_module_expr f me ];
+
+ method simple_module_expr f me =
+ let () = o#node f me Ast.loc_of_module_expr in
+ match me with
+ [ <:module_expr<>> -> assert False
| <:module_expr< $id:i$ >> -> o#ident f i
| <:module_expr< $anti:s$ >> -> o#anti f s
| <:module_expr< $me1$ $me2$ >> ->
@@ -872,9 +881,6 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
pp f "@[<2>functor@ @[<1>(%a :@ %a)@]@ ->@ %a@]" o#var s o#module_type mt o#module_expr me
| <:module_expr< struct $st$ end >> ->
pp f "@[<hv0>@[<hv2>struct@ %a@]@ end@]" o#str_item st
- | <:module_expr< ( struct $st$ end : sig $sg$ end ) >> ->
- pp f "@[<2>@[<hv2>struct@ %a@]@ end :@ @[<hv2>sig@ %a@]@ end@]"
- o#str_item st o#sig_item sg
| <:module_expr< ( $me$ : $mt$ ) >> ->
pp f "@[<1>(%a :@ %a)@]" o#module_expr me o#module_type mt ];
diff --git a/camlp4/Camlp4/Printers/OCaml.mli b/camlp4/Camlp4/Printers/OCaml.mli
index e24eca78e..6bc573b64 100644
--- a/camlp4/Camlp4/Printers/OCaml.mli
+++ b/camlp4/Camlp4/Printers/OCaml.mli
@@ -101,6 +101,7 @@ module Make (Syntax : Sig.Camlp4Syntax) : sig
method match_case_aux : formatter -> Ast.match_case -> unit;
method mk_expr_list : Ast.expr -> (list Ast.expr * option Ast.expr);
method mk_patt_list : Ast.patt -> (list Ast.patt * option Ast.patt);
+ method simple_module_expr : formatter -> Ast.module_expr -> unit;
method module_expr : formatter -> Ast.module_expr -> unit;
method module_expr_get_functor_args :
list (string * Ast.module_type) ->
diff --git a/camlp4/Camlp4/Printers/OCamlr.ml b/camlp4/Camlp4/Printers/OCamlr.ml
index 64086607d..987d8ac0e 100644
--- a/camlp4/Camlp4/Printers/OCamlr.ml
+++ b/camlp4/Camlp4/Printers/OCamlr.ml
@@ -227,6 +227,13 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
pp f "@[<2>%a@,(%a)@]" o#module_expr me1 o#module_expr me2
| me -> super#module_expr f me ];
+ method simple_module_expr f me =
+ let () = o#node f me Ast.loc_of_module_expr in
+ match me with
+ [ <:module_expr< $_$ $_$ >> ->
+ pp f "(%a)" o#module_expr me
+ | _ -> super#simple_module_expr f me ];
+
method implem f st = pp f "@[<v0>%a@]@." o#str_item st;
method class_type f ct =