summaryrefslogtreecommitdiffstats
path: root/stdlib/string.mli
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1997-10-24 15:54:07 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1997-10-24 15:54:07 +0000
commit56e001e1c4b07c45aa8e0d9ff4cbb085e8ac1bf8 (patch)
tree38db19ad695cfc911477581b49e5fe1139448fa4 /stdlib/string.mli
parent7de9d9776f1f2f9226e720355133e6a8731255d3 (diff)
Array.iteri Array.mapi Array.fold_left Array.fold_right
String.index String.rindex Filename: utiliser String.rindex Genlex: erreur dans doc git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1741 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/string.mli')
-rw-r--r--stdlib/string.mli9
1 files changed, 9 insertions, 0 deletions
diff --git a/stdlib/string.mli b/stdlib/string.mli
index d12b52180..627c8ad62 100644
--- a/stdlib/string.mli
+++ b/stdlib/string.mli
@@ -70,6 +70,15 @@ val escaped: string -> string
by escape sequences, following the lexical conventions of
Objective Caml. *)
+val index: string -> char -> int
+ (* [index s c] returns the position of the leftmost occurrence of
+ character [c] in string [s]. Raise [Not_found] if [c] does not
+ occur in [s]. *)
+val rindex: string -> char -> int
+ (* [rindex s c] returns the position of the rightmost occurrence of
+ character [c] in string [s]. Raise [Not_found] if [c] does not
+ occur in [s]. *)
+
val uppercase: string -> string
(* Return a copy of the argument, with all lowercase letters
translated to uppercase, including accented letters of the ISO