diff options
Diffstat (limited to 'stdlib/array.mli')
-rw-r--r-- | stdlib/array.mli | 29 |
1 files changed, 14 insertions, 15 deletions
diff --git a/stdlib/array.mli b/stdlib/array.mli index fce9dd300..dcff7ea8f 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -42,13 +42,13 @@ external create: int -> 'a -> 'a array = "make_vect" If the value of [x] is a floating-point number, then the maximum size is only [Sys.max_array_length / 2]. [Array.create] is a deprecated alias for [Array.make]. *) -val init: int -> f:(int -> 'a) -> 'a array +val init: int -> (int -> 'a) -> 'a array (* [Array.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] applied to the integers [0] to [n-1]. *) -val make_matrix: dimx:int -> dimy:int -> 'a -> 'a array array -val create_matrix: dimx:int -> dimy:int -> 'a -> 'a array array +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 (an array of arrays) with first dimension [dimx] and second dimension [dimy]. All the elements of this new matrix @@ -66,7 +66,7 @@ val append: 'a array -> 'a array -> 'a array 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 -> pos:int -> len:int -> 'a array +val sub: 'a array -> int -> int -> 'a array (* [Array.sub a start len] returns a fresh array of length [len], containing the elements number [start] to [start + len - 1] of array [a]. @@ -76,13 +76,12 @@ val sub: 'a array -> pos:int -> len:int -> 'a array val copy: 'a array -> 'a array (* [Array.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 +val fill: 'a array -> int -> int -> 'a -> unit (* [Array.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 designate a valid subarray of [a]. *) -val blit: src:'a array -> src_pos:int -> - dst:'a array -> dst_pos:int -> len:int -> unit +val blit: 'a array -> int -> 'a array -> int -> int -> unit (* [Array.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 @@ -96,30 +95,30 @@ val to_list: 'a array -> 'a list val of_list: 'a list -> 'a array (* [Array.of_list l] returns a fresh array containing the elements of [l]. *) -val iter: f:('a -> unit) -> 'a array -> unit +val iter: ('a -> unit) -> 'a array -> unit (* [Array.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); ()]. *) -val map: f:('a -> 'b) -> 'a array -> 'b array +val map: ('a -> 'b) -> 'a array -> 'b array (* [Array.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) |]]. *) -val iteri: f:(int -> 'a -> unit) -> 'a array -> unit -val mapi: f:(int -> 'a -> 'b) -> 'a array -> 'b array +val iteri: (int -> 'a -> unit) -> 'a array -> unit +val mapi: (int -> 'a -> 'b) -> 'a array -> 'b array (* Same as [Array.iter] and [Array.map] respectively, but the function is applied to the index of the element as first argument, and the element itself as second argument. *) -val fold_left: f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a +val fold_left: ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a (* [Array.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 +val fold_right: ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a (* [Array.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]. *) (** Sorting *) -val sort : cmp:('a -> 'a -> int) -> 'a array -> unit;; +val sort : ('a -> 'a -> int) -> 'a array -> unit;; (* Sort an array in increasing order according to a comparison function. The comparison function must return 0 if its arguments compare as equal, a positive integer if the first is greater, @@ -134,7 +133,7 @@ val sort : cmp:('a -> 'a -> int) -> 'a array -> unit;; stack space. *) -val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit;; +val stable_sort : ('a -> 'a -> int) -> 'a array -> unit;; (* Same as [Array.sort], but the sorting algorithm is stable and not guaranteed to use a fixed amount of heap memory. The current implementation is Merge Sort. It uses [n/2] |