summaryrefslogtreecommitdiffstats
path: root/stdlib/string.ml
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/string.ml
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/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