summaryrefslogtreecommitdiffstats
path: root/stdlib/array.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/array.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/array.ml')
-rw-r--r--stdlib/array.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/array.ml b/stdlib/array.ml
index f6477d1f9..8aef73b8d 100644
--- a/stdlib/array.ml
+++ b/stdlib/array.ml
@@ -140,14 +140,14 @@ let of_list = function
let fold_left f x a =
let r = ref x in
- for i = 0 to Array.length a - 1 do
+ for i = 0 to length a - 1 do
r := f !r (unsafe_get a i)
done;
!r
let fold_right f a x =
let r = ref x in
- for i = Array.length a - 1 downto 0 do
+ for i = length a - 1 downto 0 do
r := f (unsafe_get a i) !r
done;
!r