Using formats %S and %C.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4959 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2002-06-27 09:27:14 +00:00
parent de4faabfce
commit a829d1d7d6
6 changed files with 11 additions and 11 deletions

View File

@ -22,9 +22,9 @@ open Lambda
let rec struct_const ppf = function
| Const_base(Const_int n) -> fprintf ppf "%i" n
| Const_base(Const_char c) ->
fprintf ppf "'%s'" (Char.escaped c)
fprintf ppf "%C" c
| Const_base(Const_string s) ->
fprintf ppf "\"%s\"" (String.escaped s)
fprintf ppf "%S" s
| Const_base(Const_float s) ->
fprintf ppf "%s" s
| Const_pointer n -> fprintf ppf "%ia" n

View File

@ -39,7 +39,7 @@ let fmt_constant f x =
| Const_int (i) -> fprintf f "Const_int %d" i;
| Const_char (c) -> fprintf f "Const_char %02x" (Char.code c);
| Const_string (s) ->
fprintf f "Const_string \"%s\"" (String.escaped s);
fprintf f "Const_string %S" s;
| Const_float (s) -> fprintf f "Const_float %s" s;
;;

View File

@ -27,7 +27,7 @@ let field x i =
if not (Obj.is_block f) then
sprintf "%d" (Obj.magic f : int) (* can also be a char *)
else if Obj.tag f = Obj.string_tag then
sprintf "\"%s\"" (String.escaped (Obj.magic f : string))
sprintf "%S" (Obj.magic f : string)
else if Obj.tag f = Obj.double_tag then
string_of_float (Obj.magic f : float)
else

View File

@ -85,9 +85,9 @@ let rec print_struct_const = function
| Const_base(Const_float f) ->
print_float f
| Const_base(Const_string s) ->
printf "\"%s\"" (String.escaped s)
printf "%S" s
| Const_base(Const_char c) ->
printf "'%s'" (Char.escaped c)
printf "%C" c
| Const_pointer n ->
printf "%da" n
| Const_block(tag, args) ->
@ -112,7 +112,7 @@ let rec print_obj x =
if Obj.is_block x then begin
match Obj.tag x with
252 -> (* string *)
printf "\"%s\"" (String.escaped (Obj.magic x : string))
printf "%S" (Obj.magic x : string)
| 253 -> (* float *)
printf "%.12g" (Obj.magic x : float)
| 254 -> (* float array *)

View File

@ -55,9 +55,9 @@ let print_out_value ppf tree =
function
Oval_int i -> fprintf ppf "%i" i
| Oval_float f -> fprintf ppf "%s" (string_of_float f)
| Oval_char c -> fprintf ppf "'%s'" (Char.escaped c)
| Oval_char c -> fprintf ppf "%C" c
| Oval_string s ->
begin try fprintf ppf "\"%s\"" (String.escaped s) with
begin try fprintf ppf "%S" s with
Invalid_argument "String.create" -> fprintf ppf "<huge string>"
end
| Oval_list tl ->

View File

@ -157,9 +157,9 @@ let rec pretty_val ppf v = match v.pat_desc with
| Tpat_var x -> Ident.print ppf x
| Tpat_constant (Const_int i) -> fprintf ppf "%d" i
| Tpat_constant (Const_char c) ->
fprintf ppf "'%s'" (Char.escaped c)
fprintf ppf "%C" c
| Tpat_constant (Const_string s) ->
fprintf ppf "\"%s\"" (String.escaped s)
fprintf ppf "%S" s
| Tpat_constant (Const_float s) ->
fprintf ppf "%s" s
| Tpat_tuple vs ->