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