summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--camlp4/Camlp4/Printers/OCaml.ml8
-rw-r--r--camlp4/boot/Camlp4Ast.ml4
2 files changed, 6 insertions, 6 deletions
diff --git a/camlp4/Camlp4/Printers/OCaml.ml b/camlp4/Camlp4/Printers/OCaml.ml
index c1b5f1d90..6cd292aba 100644
--- a/camlp4/Camlp4/Printers/OCaml.ml
+++ b/camlp4/Camlp4/Printers/OCaml.ml
@@ -106,8 +106,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
"Cannot print %S this identifier does not respect OCaml lexing rules (%s)"
str (Lexer.Error.to_string exn)) ];
- value ocaml_char x =
- match x with [ "'" -> "\\'" | c -> c ];
+ (* This is to be sure character literals are always escaped. *)
+ value ocaml_char x = Char.escaped (Struct.Token.Eval.char x);
value rec get_expr_args a al =
match a with
@@ -557,7 +557,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
| <:expr< $int64:s$ >> -> o#numeric f s "L"
| <:expr< $int32:s$ >> -> o#numeric f s "l"
| <:expr< $flo:s$ >> -> o#numeric f s ""
- | <:expr< $chr:s$ >> -> pp f "'%s'" s
+ | <:expr< $chr:s$ >> -> pp f "'%s'" (ocaml_char s)
| <:expr< $id:i$ >> -> o#var_ident f i
| <:expr< { $b$ } >> ->
pp f "@[<hv0>@[<hv2>{%a@]@ }@]" o#record_binding b
@@ -667,7 +667,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
| <:patt< $int32:s$ >> -> o#numeric f s "l"
| <:patt< $int:s$ >> -> o#numeric f s ""
| <:patt< $flo:s$ >> -> o#numeric f s ""
- | <:patt< $chr:s$ >> -> pp f "'%s'" s
+ | <:patt< $chr:s$ >> -> pp f "'%s'" (ocaml_char s)
| <:patt< ~ $s$ >> -> pp f "~%s" s
| <:patt< ` $uid:s$ >> -> pp f "`%a" o#var s
| <:patt< # $i$ >> -> pp f "@[<2>#%a@]" o#ident i
diff --git a/camlp4/boot/Camlp4Ast.ml b/camlp4/boot/Camlp4Ast.ml
index fb49d01b5..a8d43cd4e 100644
--- a/camlp4/boot/Camlp4Ast.ml
+++ b/camlp4/boot/Camlp4Ast.ml
@@ -471,10 +471,10 @@ module Make (Loc : Sig.Loc) : Sig.Camlp4Ast with module Loc = Loc =
value meta_loc = meta_loc_expr;
module Expr =
struct
- value meta_string _loc s = Ast.ExStr _loc s;
+ value meta_string _loc s = Ast.ExStr _loc (safe_string_escaped s);
value meta_int _loc s = Ast.ExInt _loc s;
value meta_float _loc s = Ast.ExFlo _loc s;
- value meta_char _loc s = Ast.ExChr _loc s;
+ value meta_char _loc s = Ast.ExChr _loc (String.escaped s);
value meta_bool _loc =
fun
[ False -> Ast.ExId _loc (Ast.IdUid _loc "False")