summaryrefslogtreecommitdiffstats
path: root/stdlib/array.ml
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>1997-11-12 08:56:35 +0000
committerPierre Weis <Pierre.Weis@inria.fr>1997-11-12 08:56:35 +0000
commit91f7a1961e4a37bebdf744b05f031a8ce26e00f2 (patch)
tree487b64560d7559b20dc9329061d9163735c735ff /stdlib/array.ml
parent5f7de2a00071620fe066a45b0b884afd9e1051ad (diff)
Ajout de Array.init
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1759 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/array.ml')
-rw-r--r--stdlib/array.ml16
1 files changed, 12 insertions, 4 deletions
diff --git a/stdlib/array.ml b/stdlib/array.ml
index 8aef73b8d..3c012062b 100644
--- a/stdlib/array.ml
+++ b/stdlib/array.ml
@@ -21,6 +21,14 @@ external unsafe_set: 'a array -> int -> 'a -> unit = "%array_unsafe_set"
external make: int -> 'a -> 'a array = "make_vect"
external create: int -> 'a -> 'a array = "make_vect"
+let init l f =
+ if l = 0 then [||] else
+ let res = create l (f 0) in
+ for i = 1 to pred l do
+ unsafe_set res i (f i)
+ done;
+ res
+
let make_matrix sx sy init =
let res = create sx [||] in
for x = 0 to pred sx do
@@ -33,11 +41,11 @@ let create_matrix = make_matrix
let copy a =
let l = length a in
if l = 0 then [||] else begin
- let r = create l (unsafe_get a 0) in
- for i = 1 to l-1 do
- unsafe_set r i (unsafe_get a i)
+ let res = create l (unsafe_get a 0) in
+ for i = 1 to pred l do
+ unsafe_set res i (unsafe_get a i)
done;
- r
+ res
end
let append a1 a2 =