PR6695: Add ASCII counterparts to case-mapping functions.

This updates Char, String, Bytes in the stdlib.

For now, they are hidden from documentation and are only for
internal compiler use.

From: Peter Zotov <whitequark@whitequark.org>

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15726 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Gabriel Scherer 2014-12-21 11:46:10 +00:00
parent 85b75d7963
commit a533618a7a
6 changed files with 38 additions and 0 deletions

View File

@ -206,6 +206,9 @@ let mapi f s =
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
let apply1 f s =
if length s = 0 then s else begin
let r = copy s in
@ -216,6 +219,9 @@ let apply1 f s =
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
let rec index_rec s lim i c =
if i >= lim then raise Not_found else
if unsafe_get s i = c then i else index_rec s lim (i + 1) c;;

View File

@ -390,6 +390,11 @@ 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"

View File

@ -62,6 +62,16 @@ let uppercase c =
then unsafe_chr(code c - 32)
else c
let lowercase_ascii c =
if (c >= 'A' && c <= 'Z')
then unsafe_chr(code c + 32)
else c
let uppercase_ascii c =
if (c >= 'a' && c <= 'z')
then unsafe_chr(code c - 32)
else c
type t = char
let compare c1 c2 = code c1 - code c2

View File

@ -47,6 +47,9 @@ 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"

View File

@ -121,6 +121,15 @@ let capitalize s =
let uncapitalize s =
B.uncapitalize (bos s) |> bts
let uppercase_ascii s =
B.uppercase_ascii (bos s) |> bts
let lowercase_ascii s =
B.lowercase_ascii (bos s) |> bts
let capitalize_ascii s =
B.capitalize_ascii (bos s) |> bts
let uncapitalize_ascii s =
B.uncapitalize_ascii (bos s) |> bts
type t = string
let compare (x: t) (y: t) = Pervasives.compare x y

View File

@ -245,6 +245,11 @@ 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"