summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-12-21 11:46:18 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-12-21 11:46:18 +0000
commitbcaa58a035c4dd7163a503d30f83efb45fa4662c (patch)
tree28982623440e7e996a4a409ee44da78f3e3f0022 /stdlib
parentc7f2f72c07e34e0e28836ae3c0f8f9c7a12128eb (diff)
PR6694: Deprecate Latin-1 string manipulation functions.
Also, add documentation for the US-ASCII variants. From: Peter Zotov <whitequark@whitequark.org> git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15729 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/bytes.ml14
-rw-r--r--stdlib/bytes.mli45
-rw-r--r--stdlib/char.mli21
-rw-r--r--stdlib/string.ml19
-rw-r--r--stdlib/string.mli39
5 files changed, 97 insertions, 41 deletions
diff --git a/stdlib/bytes.ml b/stdlib/bytes.ml
index b3e7679a6..193c3ceea 100644
--- a/stdlib/bytes.ml
+++ b/stdlib/bytes.ml
@@ -203,9 +203,6 @@ let mapi f s =
r
end
-let uppercase s = map Char.uppercase s
-let lowercase s = map Char.lowercase s
-
let uppercase_ascii s = map Char.uppercase_ascii s
let lowercase_ascii s = map Char.lowercase_ascii s
@@ -216,9 +213,6 @@ let apply1 f s =
r
end
-let capitalize s = apply1 Char.uppercase s
-let uncapitalize s = apply1 Char.lowercase s
-
let capitalize_ascii s = apply1 Char.uppercase_ascii s
let uncapitalize_ascii s = apply1 Char.lowercase_ascii s
@@ -267,3 +261,11 @@ type t = bytes
let compare (x: t) (y: t) = Pervasives.compare x y
external equal : t -> t -> bool = "caml_string_equal"
+
+(* Deprecated functions implemented via other deprecated functions *)
+[@@@ocaml.warning "-3"]
+let uppercase s = map Char.uppercase s
+let lowercase s = map Char.lowercase s
+
+let capitalize s = apply1 Char.uppercase s
+let uncapitalize s = apply1 Char.lowercase s
diff --git a/stdlib/bytes.mli b/stdlib/bytes.mli
index e4ceb0811..6cb4b1374 100644
--- a/stdlib/bytes.mli
+++ b/stdlib/bytes.mli
@@ -229,22 +229,46 @@ val rcontains_from : bytes -> int -> char -> bool
position in [s]. *)
val uppercase : bytes -> bytes
+ [@@ocaml.deprecated "Use Bytes.uppercase_ascii instead."]
(** Return a copy of the argument, with all lowercase letters
- translated to uppercase, including accented letters of the ISO
- Latin-1 (8859-1) character set. *)
+ translated to uppercase, including accented letters of the ISO
+ Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val lowercase : bytes -> bytes
+ [@@ocaml.deprecated "Use Bytes.lowercase_ascii instead."]
(** Return a copy of the argument, with all uppercase letters
- translated to lowercase, including accented letters of the ISO
- Latin-1 (8859-1) character set. *)
+ translated to lowercase, including accented letters of the ISO
+ Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val capitalize : bytes -> bytes
-(** Return a copy of the argument, with the first byte set to
- uppercase. *)
+ [@@ocaml.deprecated "Use Bytes.capitalize_ascii instead."]
+(** Return a copy of the argument, with the first character set to uppercase,
+ using the ISO Latin-1 (8859-1) character set..
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val uncapitalize : bytes -> bytes
-(** Return a copy of the argument, with the first byte set to
- lowercase. *)
+ [@@ocaml.deprecated "Use Bytes.uncapitalize_ascii instead."]
+(** Return a copy of the argument, with the first character set to lowercase,
+ using the ISO Latin-1 (8859-1) character set..
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
+
+val uppercase_ascii : bytes -> bytes
+(** Return a copy of the argument, with all lowercase letters
+ translated to uppercase, using the US-ASCII character set. *)
+
+val lowercase_ascii : bytes -> bytes
+(** Return a copy of the argument, with all uppercase letters
+ translated to lowercase, using the US-ASCII character set. *)
+
+val capitalize_ascii : bytes -> bytes
+(** Return a copy of the argument, with the first character set to uppercase,
+ using the US-ASCII character set. *)
+
+val uncapitalize_ascii : bytes -> bytes
+(** Return a copy of the argument, with the first character set to lowercase,
+ using the US-ASCII character set. *)
type t = bytes
(** An alias for the type of byte sequences. *)
@@ -390,11 +414,6 @@ let s = Bytes.of_string "hello"
(**/**)
-val lowercase_ascii : bytes -> bytes
-val uppercase_ascii : bytes -> bytes
-val capitalize_ascii : bytes -> bytes
-val uncapitalize_ascii : bytes -> bytes
-
(* The following is for system use only. Do not call directly. *)
external unsafe_get : bytes -> int -> char = "%string_unsafe_get"
diff --git a/stdlib/char.mli b/stdlib/char.mli
index 88094bd2b..f70ab5ea5 100644
--- a/stdlib/char.mli
+++ b/stdlib/char.mli
@@ -27,10 +27,24 @@ val escaped : char -> string
of OCaml. *)
val lowercase : char -> char
-(** Convert the given character to its equivalent lowercase character. *)
+ [@@ocaml.deprecated "Use Char.lowercase_ascii instead."]
+(** Convert the given character to its equivalent lowercase character,
+ using the ISO Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val uppercase : char -> char
-(** Convert the given character to its equivalent uppercase character. *)
+ [@@ocaml.deprecated "Use Char.uppercase_ascii instead."]
+(** Convert the given character to its equivalent uppercase character,
+ using the ISO Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
+
+val lowercase_ascii : char -> char
+(** Convert the given character to its equivalent lowercase character,
+ using the US-ASCII character set. *)
+
+val uppercase_ascii : char -> char
+(** Convert the given character to its equivalent uppercase character,
+ using the US-ASCII character set. *)
type t = char
(** An alias for the type of characters. *)
@@ -47,9 +61,6 @@ val equal: t -> t -> bool
(**/**)
-val lowercase_ascii : char -> char
-val uppercase_ascii : char -> char
-
(* The following is for system use only. Do not call directly. *)
external unsafe_chr : int -> char = "%identity"
diff --git a/stdlib/string.ml b/stdlib/string.ml
index f78e1395e..0cea7acb7 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -112,14 +112,6 @@ let contains_from s i c =
B.contains_from (bos s) i c
let rcontains_from s i c =
B.rcontains_from (bos s) i c
-let uppercase s =
- B.uppercase (bos s) |> bts
-let lowercase s =
- B.lowercase (bos s) |> bts
-let capitalize s =
- B.capitalize (bos s) |> bts
-let uncapitalize s =
- B.uncapitalize (bos s) |> bts
let uppercase_ascii s =
B.uppercase_ascii (bos s) |> bts
@@ -134,3 +126,14 @@ type t = string
let compare (x: t) (y: t) = Pervasives.compare x y
external equal : string -> string -> bool = "caml_string_equal"
+
+(* Deprecated functions implemented via other deprecated functions *)
+[@@@ocaml.warning "-3"]
+let uppercase s =
+ B.uppercase (bos s) |> bts
+let lowercase s =
+ B.lowercase (bos s) |> bts
+let capitalize s =
+ B.capitalize (bos s) |> bts
+let uncapitalize s =
+ B.uncapitalize (bos s) |> bts
diff --git a/stdlib/string.mli b/stdlib/string.mli
index 1f6191512..3a0af298f 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -215,20 +215,46 @@ val rcontains_from : string -> int -> char -> bool
position in [s]. *)
val uppercase : string -> string
+ [@@ocaml.deprecated "Use String.uppercase_ascii instead."]
(** Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO
- Latin-1 (8859-1) character set. *)
+ Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val lowercase : string -> string
+ [@@ocaml.deprecated "Use String.lowercase_ascii instead."]
(** Return a copy of the argument, with all uppercase letters
translated to lowercase, including accented letters of the ISO
- Latin-1 (8859-1) character set. *)
+ Latin-1 (8859-1) character set.
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val capitalize : string -> string
-(** Return a copy of the argument, with the first character set to uppercase. *)
+ [@@ocaml.deprecated "Use String.capitalize_ascii instead."]
+(** Return a copy of the argument, with the first character set to uppercase,
+ using the ISO Latin-1 (8859-1) character set..
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
val uncapitalize : string -> string
-(** Return a copy of the argument, with the first character set to lowercase. *)
+ [@@ocaml.deprecated "Use String.uncapitalize_ascii instead."]
+(** Return a copy of the argument, with the first character set to lowercase,
+ using the ISO Latin-1 (8859-1) character set..
+ @deprecated Functions operating on Latin-1 character set are deprecated. *)
+
+val uppercase_ascii : string -> string
+(** Return a copy of the argument, with all lowercase letters
+ translated to uppercase, using the US-ASCII character set. *)
+
+val lowercase_ascii : string -> string
+(** Return a copy of the argument, with all uppercase letters
+ translated to lowercase, using the US-ASCII character set. *)
+
+val capitalize_ascii : string -> string
+(** Return a copy of the argument, with the first character set to uppercase,
+ using the US-ASCII character set. *)
+
+val uncapitalize_ascii : string -> string
+(** Return a copy of the argument, with the first character set to lowercase,
+ using the US-ASCII character set. *)
type t = string
(** An alias for the type of strings. *)
@@ -245,11 +271,6 @@ val equal: t -> t -> bool
(**/**)
-val lowercase_ascii : string -> string
-val uppercase_ascii : string -> string
-val capitalize_ascii : string -> string
-val uncapitalize_ascii : string -> string
-
(* The following is for system use only. Do not call directly. *)
external unsafe_get : string -> int -> char = "%string_unsafe_get"