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-0dff7051ff02master
parent
c7f2f72c07
commit
bcaa58a035
|
@ -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
|
||||
|
|
|
@ -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"
|
||||
|
|
|
@ -27,10 +27,24 @@ val escaped : char -> string
|
|||
of OCaml. *)
|
||||
|
||||
val lowercase : char -> char
|
||||
(** Convert the given character to its equivalent lowercase character. *)
|
||||
[@@ocaml.deprecated "Use Char.lowercase_ascii instead."]
|
||||
(** Convert the given character to its equivalent lowercase character,
|
||||
using the ISO Latin-1 (8859-1) character set.
|
||||
@deprecated Functions operating on Latin-1 character set are deprecated. *)
|
||||
|
||||
val uppercase : char -> char
|
||||
(** Convert the given character to its equivalent uppercase character. *)
|
||||
[@@ocaml.deprecated "Use Char.uppercase_ascii instead."]
|
||||
(** Convert the given character to its equivalent uppercase character,
|
||||
using the ISO Latin-1 (8859-1) character set.
|
||||
@deprecated Functions operating on Latin-1 character set are deprecated. *)
|
||||
|
||||
val lowercase_ascii : char -> char
|
||||
(** Convert the given character to its equivalent lowercase character,
|
||||
using the US-ASCII character set. *)
|
||||
|
||||
val uppercase_ascii : char -> char
|
||||
(** Convert the given character to its equivalent uppercase character,
|
||||
using the US-ASCII character set. *)
|
||||
|
||||
type t = char
|
||||
(** An alias for the type of characters. *)
|
||||
|
@ -47,9 +61,6 @@ val equal: t -> t -> bool
|
|||
|
||||
(**/**)
|
||||
|
||||
val lowercase_ascii : char -> char
|
||||
val uppercase_ascii : char -> char
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_chr : int -> char = "%identity"
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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"
|
||||
|
|
Loading…
Reference in New Issue