summaryrefslogtreecommitdiffstats
path: root/stdlib/string.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/string.mli')
-rw-r--r--stdlib/string.mli39
1 files changed, 30 insertions, 9 deletions
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"