summaryrefslogtreecommitdiffstats
path: root/stdlib/array.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2002-07-12 09:47:54 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2002-07-12 09:47:54 +0000
commitede12e6163058650508a0fbb08177ab4ee4daf02 (patch)
tree6241a927f8d50e772b0cd74ba83e5cdc0d456c5c /stdlib/array.ml
parent4865d98f29e1f648c7b45a9304dff12604d6abb8 (diff)
Remplacement des tests ofs + len > length par ofs > len - length, pour eviter le debordement lors de l'addition (PR#1229)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4993 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/array.ml')
-rw-r--r--stdlib/array.ml8
1 files changed, 4 insertions, 4 deletions
diff --git a/stdlib/array.ml b/stdlib/array.ml
index 175a3516f..20d949675 100644
--- a/stdlib/array.ml
+++ b/stdlib/array.ml
@@ -85,7 +85,7 @@ let concat al =
in find_init al
let sub a ofs len =
- if ofs < 0 || len < 0 || ofs + len > length a then invalid_arg "Array.sub"
+ if ofs < 0 || len < 0 || ofs > length a - len then invalid_arg "Array.sub"
else if len = 0 then [||]
else begin
let r = create len (unsafe_get a ofs) in
@@ -94,13 +94,13 @@ let sub a ofs len =
end
let fill a ofs len v =
- if ofs < 0 || len < 0 || ofs + len > length a
+ if ofs < 0 || len < 0 || ofs > length a - len
then invalid_arg "Array.fill"
else for i = ofs to ofs + len - 1 do unsafe_set a i v done
let blit a1 ofs1 a2 ofs2 len =
- if len < 0 || ofs1 < 0 || ofs1 + len > length a1
- || ofs2 < 0 || ofs2 + len > length a2
+ if len < 0 || ofs1 < 0 || ofs1 > length a1 - len
+ || ofs2 < 0 || ofs2 > length a2 - len
then invalid_arg "Array.blit"
else if ofs1 < ofs2 then
(* Top-down copy *)