diff options
author | Pierre Weis <Pierre.Weis@inria.fr> | 2007-04-16 11:06:51 +0000 |
---|---|---|
committer | Pierre Weis <Pierre.Weis@inria.fr> | 2007-04-16 11:06:51 +0000 |
commit | 8c9e42862c7f32a0d51a5493589d32acf70ce4cd (patch) | |
tree | d55de9f4fa5777c45452e760e767fecabe0395f0 /stdlib/char.ml | |
parent | 95295f121e312c2f9af6765c98837f0723d53550 (diff) |
The functions that escape characters ([escaped]) now handle characters
consistently with the compiler's lexer (PR#4220).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8189 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/char.ml')
-rw-r--r-- | stdlib/char.ml | 31 |
1 files changed, 17 insertions, 14 deletions
diff --git a/stdlib/char.ml b/stdlib/char.ml index 4fbc82583..28a1bcc46 100644 --- a/stdlib/char.ml +++ b/stdlib/char.ml @@ -29,23 +29,26 @@ external string_unsafe_set : string -> int -> char -> unit = "%string_unsafe_set" let escaped = function - '\'' -> "\\'" + | '\'' -> "\\'" | '\\' -> "\\\\" | '\n' -> "\\n" | '\t' -> "\\t" - | c -> if is_printable c then begin - let s = string_create 1 in - string_unsafe_set s 0 c; - s - end else begin - let n = code c in - let s = string_create 4 in - string_unsafe_set s 0 '\\'; - string_unsafe_set s 1 (unsafe_chr (48 + n / 100)); - string_unsafe_set s 2 (unsafe_chr (48 + (n / 10) mod 10)); - string_unsafe_set s 3 (unsafe_chr (48 + n mod 10)); - s - end + | '\r' -> "\\r" + | '\b' -> "\\b" + | c -> + if is_printable c then begin + let s = string_create 1 in + string_unsafe_set s 0 c; + s + end else begin + let n = code c in + let s = string_create 4 in + string_unsafe_set s 0 '\\'; + string_unsafe_set s 1 (unsafe_chr (48 + n / 100)); + string_unsafe_set s 2 (unsafe_chr (48 + (n / 10) mod 10)); + string_unsafe_set s 3 (unsafe_chr (48 + n mod 10)); + s + end let lowercase c = if (c >= 'A' && c <= 'Z') |