summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-12-19 17:31:43 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-12-19 17:31:43 +0000
commit010deb2fee9ff63ae5594872f205b593955dc4f6 (patch)
tree984d9f18dd82d57226c6017edeaf4b91baa6a2cd /stdlib
parent512d128918544ae1da0c808e811f3a7f177524d2 (diff)
Change 'Array' to 'ArrayLabels' in the ArrayLabels documentation.
From: Jeremy Yallop <yallop@gmail.com> git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15685 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/arrayLabels.mli62
1 files changed, 31 insertions, 31 deletions
diff --git a/stdlib/arrayLabels.mli b/stdlib/arrayLabels.mli
index bc8519913..8fa55de43 100644
--- a/stdlib/arrayLabels.mli
+++ b/stdlib/arrayLabels.mli
@@ -17,24 +17,24 @@ external length : 'a array -> int = "%array_length"
(** Return the length (number of elements) of the given array. *)
external get : 'a array -> int -> 'a = "%array_safe_get"
-(** [Array.get a n] returns the element number [n] of array [a].
+(** [ArrayLabels.get a n] returns the element number [n] of array [a].
The first element has number 0.
- The last element has number [Array.length a - 1].
- You can also write [a.(n)] instead of [Array.get a n].
+ The last element has number [ArrayLabels.length a - 1].
+ You can also write [a.(n)] instead of [ArrayLabels.get a n].
Raise [Invalid_argument "index out of bounds"]
- if [n] is outside the range 0 to [(Array.length a - 1)]. *)
+ if [n] is outside the range 0 to [(ArrayLabels.length a - 1)]. *)
external set : 'a array -> int -> 'a -> unit = "%array_safe_set"
-(** [Array.set a n x] modifies array [a] in place, replacing
+(** [ArrayLabels.set a n x] modifies array [a] in place, replacing
element number [n] with [x].
- You can also write [a.(n) <- x] instead of [Array.set a n x].
+ You can also write [a.(n) <- x] instead of [ArrayLabels.set a n x].
Raise [Invalid_argument "index out of bounds"]
- if [n] is outside the range 0 to [Array.length a - 1]. *)
+ if [n] is outside the range 0 to [ArrayLabels.length a - 1]. *)
external make : int -> 'a -> 'a array = "caml_make_vect"
-(** [Array.make n x] returns a fresh array of length [n],
+(** [ArrayLabels.make n x] returns a fresh array of length [n],
initialized with [x].
All the elements of this new array are initially
physically equal to [x] (in the sense of the [==] predicate).
@@ -51,9 +51,9 @@ external create : int -> 'a -> 'a array = "caml_make_vect"
(** @deprecated [ArrayLabels.create] is an alias for {!ArrayLabels.make}. *)
val init : int -> f:(int -> 'a) -> 'a array
-(** [Array.init n f] returns a fresh array of length [n],
+(** [ArrayLabels.init n f] returns a fresh array of length [n],
with element number [i] initialized to the result of [f i].
- In other terms, [Array.init n f] tabulates the results of [f]
+ In other terms, [ArrayLabels.init n f] tabulates the results of [f]
applied to the integers [0] to [n-1].
Raise [Invalid_argument] if [n < 0] or [n > Sys.max_array_length].
@@ -61,7 +61,7 @@ val init : int -> f:(int -> 'a) -> 'a array
size is only [Sys.max_array_length / 2].*)
val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
-(** [Array.make_matrix dimx dimy e] returns a two-dimensional array
+(** [ArrayLabels.make_matrix dimx dimy e] returns a two-dimensional array
(an array of arrays) with first dimension [dimx] and
second dimension [dimy]. All the elements of this new matrix
are initially physically equal to [e].
@@ -79,27 +79,27 @@ val create_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
{!ArrayLabels.make_matrix}. *)
val append : 'a array -> 'a array -> 'a array
-(** [Array.append v1 v2] returns a fresh array containing the
+(** [ArrayLabels.append v1 v2] returns a fresh array containing the
concatenation of the arrays [v1] and [v2]. *)
val concat : 'a array list -> 'a array
-(** Same as [Array.append], but concatenates a list of arrays. *)
+(** Same as [ArrayLabels.append], but concatenates a list of arrays. *)
val sub : 'a array -> pos:int -> len:int -> 'a array
-(** [Array.sub a start len] returns a fresh array of length [len],
+(** [ArrayLabels.sub a start len] returns a fresh array of length [len],
containing the elements number [start] to [start + len - 1]
of array [a].
Raise [Invalid_argument "Array.sub"] if [start] and [len] do not
designate a valid subarray of [a]; that is, if
- [start < 0], or [len < 0], or [start + len > Array.length a]. *)
+ [start < 0], or [len < 0], or [start + len > ArrayLabels.length a]. *)
val copy : 'a array -> 'a array
-(** [Array.copy a] returns a copy of [a], that is, a fresh array
+(** [ArrayLabels.copy a] returns a copy of [a], that is, a fresh array
containing the same elements as [a]. *)
val fill : 'a array -> pos:int -> len:int -> 'a -> unit
-(** [Array.fill a ofs len x] modifies the array [a] in place,
+(** [ArrayLabels.fill a ofs len x] modifies the array [a] in place,
storing [x] in elements number [ofs] to [ofs + len - 1].
Raise [Invalid_argument "Array.fill"] if [ofs] and [len] do not
@@ -108,7 +108,7 @@ val fill : 'a array -> pos:int -> len:int -> 'a -> unit
val blit :
src:'a array -> src_pos:int -> dst:'a array -> dst_pos:int -> len:int ->
unit
-(** [Array.blit v1 o1 v2 o2 len] copies [len] elements
+(** [ArrayLabels.blit v1 o1 v2 o2 len] copies [len] elements
from array [v1], starting at element number [o1], to array [v2],
starting at element number [o2]. It works correctly even if
[v1] and [v2] are the same array, and the source and
@@ -119,21 +119,21 @@ val blit :
designate a valid subarray of [v2]. *)
val to_list : 'a array -> 'a list
-(** [Array.to_list a] returns the list of all the elements of [a]. *)
+(** [ArrayLabels.to_list a] returns the list of all the elements of [a]. *)
val of_list : 'a list -> 'a array
-(** [Array.of_list l] returns a fresh array containing the elements
+(** [ArrayLabels.of_list l] returns a fresh array containing the elements
of [l]. *)
val iter : f:('a -> unit) -> 'a array -> unit
-(** [Array.iter f a] applies function [f] in turn to all
+(** [ArrayLabels.iter f a] applies function [f] in turn to all
the elements of [a]. It is equivalent to
- [f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
+ [f a.(0); f a.(1); ...; f a.(ArrayLabels.length a - 1); ()]. *)
val map : f:('a -> 'b) -> 'a array -> 'b array
-(** [Array.map f a] applies function [f] to all the elements of [a],
+(** [ArrayLabels.map f a] applies function [f] to all the elements of [a],
and builds an array with the results returned by [f]:
- [[| f a.(0); f a.(1); ...; f a.(Array.length a - 1) |]]. *)
+ [[| f a.(0); f a.(1); ...; f a.(ArrayLabels.length a - 1) |]]. *)
val iteri : f:(int -> 'a -> unit) -> 'a array -> unit
(** Same as {!ArrayLabels.iter}, but the
@@ -146,12 +146,12 @@ val mapi : f:(int -> 'a -> 'b) -> 'a array -> 'b array
and the element itself as second argument. *)
val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
-(** [Array.fold_left f x a] computes
+(** [ArrayLabels.fold_left f x a] computes
[f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)],
where [n] is the length of the array [a]. *)
val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
-(** [Array.fold_right f a x] computes
+(** [ArrayLabels.fold_right f a x] computes
[f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))],
where [n] is the length of the array [a]. *)
@@ -170,9 +170,9 @@ val sort : cmp:('a -> 'a -> int) -> 'a array -> unit
and a negative integer if the first is smaller (see below for a
complete specification). For example, {!Pervasives.compare} is
a suitable comparison function, provided there are no floating-point
- NaN values in the data. After calling [Array.sort], the
+ NaN values in the data. After calling [ArrayLabels.sort], the
array is sorted in place in increasing order.
- [Array.sort] is guaranteed to run in constant heap space
+ [ArrayLabels.sort] is guaranteed to run in constant heap space
and (at most) logarithmic stack space.
The current implementation uses Heap Sort. It runs in constant
@@ -184,7 +184,7 @@ val sort : cmp:('a -> 'a -> int) -> 'a array -> unit
- [cmp x y] > 0 if and only if [cmp y x] < 0
- if [cmp x y] >= 0 and [cmp y z] >= 0 then [cmp x z] >= 0
- When [Array.sort] returns, [a] contains the same elements as before,
+ When [ArrayLabels.sort] returns, [a] contains the same elements as before,
reordered in such a way that for all i and j valid indices of [a] :
- [cmp a.(i) a.(j)] >= 0 if and only if i >= j
*)
@@ -200,8 +200,8 @@ val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
*)
val fast_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
-(** Same as {!Array.sort} or {!Array.stable_sort}, whichever is faster
- on typical input.
+(** Same as {!ArrayLabels.sort} or {!ArrayLabels.stable_sort}, whichever is
+ faster on typical input.
*)