summaryrefslogtreecommitdiffstats
path: root/stdlib/array.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1996-05-22 16:21:16 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1996-05-22 16:21:16 +0000
commit6561e39b8270cccc126650e7e11f898baa78f7b3 (patch)
tree63b43b7437af9f814ff3a577d885a1b78bb6cfd2 /stdlib/array.ml
parent5f1ae6943bdae6ab3c58fbe3ce8cfb1fb89114ee (diff)
Bug dans Array.blit.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@832 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/array.ml')
-rw-r--r--stdlib/array.ml6
1 files changed, 6 insertions, 0 deletions
diff --git a/stdlib/array.ml b/stdlib/array.ml
index 0bfebdeb5..d398e68f7 100644
--- a/stdlib/array.ml
+++ b/stdlib/array.ml
@@ -84,7 +84,13 @@ let blit a1 ofs1 a2 ofs2 len =
if len < 0 or ofs1 < 0 or ofs1 + len > length a1
or ofs2 < 0 or ofs2 + len > length a2
then invalid_arg "Array.blit"
+ else if ofs1 < ofs2 then
+ (* Top-down copy *)
+ for i = len - 1 downto 0 do
+ unsafe_set a2 (ofs2 + i) (unsafe_get a1 (ofs1 + i))
+ done
else
+ (* Bottom-up copy *)
for i = 0 to len - 1 do
unsafe_set a2 (ofs2 + i) (unsafe_get a1 (ofs1 + i))
done