Skip to content

Commit

Permalink
Reimplement string escape in oprint
Browse files Browse the repository at this point in the history
  • Loading branch information
Octachron committed Jul 14, 2017
1 parent 0902e49 commit a9b3057
Showing 1 changed file with 44 additions and 15 deletions.
59 changes: 44 additions & 15 deletions typing/oprint.ml
Original file line number Diff line number Diff line change
Expand Up @@ -74,21 +74,50 @@ let parenthesize_if_neg ppf fmt v isneg =
fprintf ppf fmt v;
if isneg then pp_print_char ppf ')'

let escape s =
(* Escape only C0 control characters (bytes <= 0x1F), DEL(0x7F) and '"' *)
let n = ref 0 in
for i = 0 to String.length s - 1 do
n := !n +
(match String.unsafe_get s i with
| '\"' | '\\' | '\n' | '\t' | '\r' | '\b' -> 2
| '\x00' .. '\x1F'
| '\x7F' -> 4
| _ -> 1)
done;
if !n = String.length s then s else begin
let s' = Bytes.create !n in
n := 0;
for i = 0 to String.length s - 1 do
begin match String.unsafe_get s i with
| ('\"' | '\\') as c ->
Bytes.unsafe_set s' !n '\\'; incr n; Bytes.unsafe_set s' !n c
| '\n' ->
Bytes.unsafe_set s' !n '\\'; incr n; Bytes.unsafe_set s' !n 'n'
| '\t' ->
Bytes.unsafe_set s' !n '\\'; incr n; Bytes.unsafe_set s' !n 't'
| '\r' ->
Bytes.unsafe_set s' !n '\\'; incr n; Bytes.unsafe_set s' !n 'r'
| '\b' ->
Bytes.unsafe_set s' !n '\\'; incr n; Bytes.unsafe_set s' !n 'b'
| '\x00' .. '\x1F' | '\x7F' as c ->
let a = Char.code c in
Bytes.unsafe_set s' !n '\\';
incr n;
Bytes.unsafe_set s' !n (Char.chr (48 + a / 100));
incr n;
Bytes.unsafe_set s' !n (Char.chr (48 + (a / 10) mod 10));
incr n;
Bytes.unsafe_set s' !n (Char.chr (48 + a mod 10));
| c -> Bytes.unsafe_set s' !n c
end;
incr n
done;
Bytes.to_string s'
end


let print_out_string ppf s =
let rec segm left right ppf s =
(* Escape only C0 control characters (bytes <= 0x1F), DEL(0x7F) and '"' *)
if right >= String.length s then
pp_print_string ppf (String.sub s left (right - left))
else
let c = s.[right] in
if Char.code c <= 0x1F || c = '\x7F' || c = '"' || c ='\\' then
begin
pp_print_string ppf (String.sub s left (right - left));
pp_print_string ppf (if c ='"' then {|\"|} else Char.escaped c);
segm (right+1) (right+1) ppf s
end
else
segm left (right+1) ppf s in
let not_escaped =
(* let the user dynamically choose if strings should be escaped: *)
match Sys.getenv_opt "OCAMLTOP_UTF_8" with
Expand All @@ -98,7 +127,7 @@ let print_out_string ppf s =
| None -> true
| Some f -> f in
if not_escaped then
fprintf ppf "\"%a\"" (segm 0 0) s
fprintf ppf "\"%s\"" (escape s)
else
fprintf ppf "%S" s

Expand Down

0 comments on commit a9b3057

Please sign in to comment.