summaryrefslogtreecommitdiffstats
path: root/stdlib/string.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1997-11-06 17:28:16 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1997-11-06 17:28:16 +0000
commit55bb1486306dff90e5f4b31f0cc4693d305f861b (patch)
treeec35a07fa969ebcdcdc31c4751c9196fbc15d33c /stdlib/string.ml
parent839a16499124f2c60b301fe0473a27c6906bfaf7 (diff)
Retour au code d'origine pour List.iter. Je veux un seul test par
iteration, dammit. Suppression de dependances spurieuses dans Array et String. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1756 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/string.ml')
-rw-r--r--stdlib/string.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/string.ml b/stdlib/string.ml
index 145901c0e..2b2e3e972 100644
--- a/stdlib/string.ml
+++ b/stdlib/string.ml
@@ -138,7 +138,7 @@ let capitalize s = apply1 Char.uppercase s
let uncapitalize s = apply1 Char.lowercase s
let rec index_from s i c =
- if i >= String.length s then raise Not_found
+ if i >= length s then raise Not_found
else if s.[i] = c then i
else index_from s (i+1) c
@@ -149,4 +149,4 @@ let rec rindex_from s i c =
else if s.[i] = c then i
else rindex_from s (i-1) c
-let rindex s c = rindex_from s (String.length s - 1) c
+let rindex s c = rindex_from s (length s - 1) c