summaryrefslogtreecommitdiffstats
path: root/stdlib/camlinternalFormatBasics.ml
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-06-14 21:08:50 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-06-14 21:08:50 +0000
commit49d3f7b9f89826ed1b2d33a144277b390bbc3f2e (patch)
treeeb2b30f059e83becd27eff964d963677b82b6650 /stdlib/camlinternalFormatBasics.ml
parent25b93e0823edfb8e1e09c9fa8dfd6c8497e9f5e9 (diff)
PR#6418: support "@[<hov %d>" in the new format implementation (Benoît Vaugon)
The bootstrap procedure, as for commit trunk@14973 (see there for detailed build instructions), requires to first commit a temporary patch: > diff -Naur old/typing/typecore.ml new/typing/typecore.ml > --- old/typing/typecore.ml 2014-06-11 18:16:24.851647309 +0200 > +++ new/typing/typecore.ml 2014-06-11 18:15:50.075646418 +0200 > @@ -2758,16 +2758,9 @@ > let mk_int n = mk_cst (Const_int n) > and mk_string str = mk_cst (Const_string (str, None)) > and mk_char chr = mk_cst (Const_char chr) in > - let mk_block_type bty = match bty with > - | Pp_hbox -> mk_constr "Pp_hbox" [] > - | Pp_vbox -> mk_constr "Pp_vbox" [] > - | Pp_hvbox -> mk_constr "Pp_hvbox" [] > - | Pp_hovbox -> mk_constr "Pp_hovbox" [] > - | Pp_box -> mk_constr "Pp_box" [] > - | Pp_fits -> mk_constr "Pp_fits" [] in > let rec mk_formatting_lit fmting = match fmting with > - | Open_box (org, bty, idt) -> > - mk_constr "Open_box" [ mk_string org; mk_block_type bty; mk_int idt ] > + | Open_box _ -> > + assert false > | Close_box -> > mk_constr "Close_box" [] > | Close_tag -> > @@ -2950,6 +2943,19 @@ > mk_constr "Alpha" [ mk_fmt rest ] > | Theta rest -> > mk_constr "Theta" [ mk_fmt rest ] > + | Formatting_lit (Open_box (org, _bty, _idt), rest) -> > + mk_constr "Formatting_gen" [ > + mk_constr "Open_box" [ > + mk_constr "Format" [ > + mk_constr "String_literal" [ > + mk_string "<>"; > + mk_constr "End_of_format" []; > + ]; > + mk_string "@[<>"; > + ] > + ]; > + mk_fmt rest; > + ] > | Formatting_lit (fmting, rest) -> > mk_constr "Formatting_lit" [ mk_formatting_lit fmting; mk_fmt rest ] > | Formatting_gen (fmting, rest) -> git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14984 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/camlinternalFormatBasics.ml')
-rw-r--r--stdlib/camlinternalFormatBasics.ml3
1 files changed, 2 insertions, 1 deletions
diff --git a/stdlib/camlinternalFormatBasics.ml b/stdlib/camlinternalFormatBasics.ml
index 47e661fe4..e51e4e2ce 100644
--- a/stdlib/camlinternalFormatBasics.ml
+++ b/stdlib/camlinternalFormatBasics.ml
@@ -211,7 +211,6 @@ type block_type =
(* Formatting element used by the Format pretty-printter. *)
type formatting_lit =
- | Open_box of string * block_type * int (* @[ *)
| Close_box (* @] *)
| Close_tag (* @} *)
| Break of string * int * int (* @, | @ | @; | @;<> *)
@@ -227,6 +226,8 @@ type formatting_lit =
type ('a, 'b, 'c, 'd, 'e, 'f) formatting_gen =
| Open_tag : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> (* @{ *)
('a, 'b, 'c, 'd, 'e, 'f) formatting_gen
+ | Open_box : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> (* @[ *)
+ ('a, 'b, 'c, 'd, 'e, 'f) formatting_gen
(***)