summaryrefslogtreecommitdiffstats
path: root/stdlib/bytes.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/bytes.ml')
-rw-r--r--stdlib/bytes.ml14
1 files changed, 8 insertions, 6 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