summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2007-04-16 11:06:51 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2007-04-16 11:06:51 +0000
commit8c9e42862c7f32a0d51a5493589d32acf70ce4cd (patch)
treed55de9f4fa5777c45452e760e767fecabe0395f0
parent95295f121e312c2f9af6765c98837f0723d53550 (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
-rw-r--r--Changes2
-rw-r--r--VERSION2
-rw-r--r--stdlib/char.ml31
-rw-r--r--stdlib/string.ml12
4 files changed, 28 insertions, 19 deletions
diff --git a/Changes b/Changes
index ce93fdada..1b2353927 100644
--- a/Changes
+++ b/Changes
@@ -49,6 +49,8 @@ Standard library:
- List: List.nth now tail-recursive.
- Sys: added Sys.is_directory. Some functions (e.g. Sys.command) that
could incorrectly raise Sys_io_blocked now raise Sys_error as intended.
+- String and Char: the function ``escaped'' now escapes all the characters
+ especially handled by the compiler's lexer (PR#4220).
Other libraries:
- Bigarray: mmap_file takes an optional argument specifying
diff --git a/VERSION b/VERSION
index 73e0df82d..3fcc31833 100644
--- a/VERSION
+++ b/VERSION
@@ -1,4 +1,4 @@
-3.10+dev24 (2007-02-16)
+3.10+dev25 (2007-04-15)
# The version string is the first line of this file.
# It must be in the format described in stdlib/sys.mli
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')
diff --git a/stdlib/string.ml b/stdlib/string.ml
index dc1e6418d..652bdd705 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -87,8 +87,8 @@ let escaped s =
for i = 0 to length s - 1 do
n := !n +
(match unsafe_get s i with
- '"' | '\\' | '\n' | '\t' -> 2
- | c -> if is_printable c then 1 else 4)
+ | '"' | '\\' | '\n' | '\t' | '\r' | '\b' -> 2
+ | c -> if is_printable c then 1 else 4)
done;
if !n = length s then s else begin
let s' = create !n in
@@ -96,12 +96,16 @@ let escaped s =
for i = 0 to length s - 1 do
begin
match unsafe_get s i with
- ('"' | '\\') as c ->
+ | ('"' | '\\') as c ->
unsafe_set s' !n '\\'; incr n; unsafe_set s' !n c
| '\n' ->
unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'n'
| '\t' ->
unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 't'
+ | '\r' ->
+ unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'r'
+ | '\b' ->
+ unsafe_set s' !n '\\'; incr n; unsafe_set s' !n 'b'
| c ->
if is_printable c then
unsafe_set s' !n c
@@ -174,4 +178,4 @@ let contains s c = contains_from s 0 c;;
type t = string
-let compare (x: t) (y: t) = Pervasives.compare x y
+let compare = Pervasives.compare