summaryrefslogtreecommitdiffstats
path: root/stdlib/string.ml
diff options
context:
space:
mode:
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