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