diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 1998-04-27 09:55:50 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 1998-04-27 09:55:50 +0000 |
commit | 95933de17c122f254bd91231d04b9cab89f134c3 (patch) | |
tree | dcb89d15970690700b3c6ccf95a5c4a0f3d8b3e6 /stdlib/array.mli | |
parent | 208be2cae2ec48293f30590ba9184f0e813402d2 (diff) |
Corrections mineures sur la documentation
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1933 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/array.mli')
-rw-r--r-- | stdlib/array.mli | 6 |
1 files changed, 4 insertions, 2 deletions
diff --git a/stdlib/array.mli b/stdlib/array.mli index cc0665165..e2933d46c 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -39,7 +39,9 @@ external create: int -> 'a -> 'a array = "make_vect" will modify all other entries at the same time. *) val init: int -> (int -> 'a) -> 'a array (* [Array.init n f] returns a fresh array of length [n], - with element number [i] equal to [f i]. *) + with element number [i] initialized to the result of [f i]. + In other terms, [Array.init n f] tabulates the results of [f] + applied to the integers [0] to [n-1]. *) val make_matrix: int -> int -> 'a -> 'a array array val create_matrix: int -> int -> 'a -> 'a array array (* [Array.make_matrix dimx dimy e] returns a two-dimensional array @@ -50,7 +52,7 @@ val create_matrix: int -> int -> 'a -> 'a array array with the notation [m.(x).(y)]. *) val append: 'a array -> 'a array -> 'a array (* [Array.append v1 v2] returns a fresh array containing the - concatenation of arrays [v1] and [v2]. *) + concatenation of the arrays [v1] and [v2]. *) val concat: 'a array list -> 'a array (* Same as [Array.append], but catenates a list of arrays. *) val sub: 'a array -> int -> int -> 'a array |