Sys.Signals module for a Variant type of signals (and a set_signal function that...
[ocaml.git] / stdlib / arrayLabels.mli
blobf45f70c6dec326aa6a2fe765ff725009f18d1484
1 (***********************************************************************)
2 (* *)
3 (* Objective Caml *)
4 (* *)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
6 (* *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
11 (* *)
12 (***********************************************************************)
14 (* $Id$ *)
16 (** Array operations. *)
18 external length : 'a array -> int = "%array_length"
19 (** Return the length (number of elements) of the given array. *)
21 external get : 'a array -> int -> 'a = "%array_safe_get"
22 (** [Array.get a n] returns the element number [n] of array [a].
23 The first element has number 0.
24 The last element has number [Array.length a - 1].
25 You can also write [a.(n)] instead of [Array.get a n].
27 Raise [Invalid_argument "index out of bounds"]
28 if [n] is outside the range 0 to [(Array.length a - 1)]. *)
30 external set : 'a array -> int -> 'a -> unit = "%array_safe_set"
31 (** [Array.set a n x] modifies array [a] in place, replacing
32 element number [n] with [x].
33 You can also write [a.(n) <- x] instead of [Array.set a n x].
35 Raise [Invalid_argument "index out of bounds"]
36 if [n] is outside the range 0 to [Array.length a - 1]. *)
38 external make : int -> 'a -> 'a array = "caml_make_vect"
39 (** [Array.make n x] returns a fresh array of length [n],
40 initialized with [x].
41 All the elements of this new array are initially
42 physically equal to [x] (in the sense of the [==] predicate).
43 Consequently, if [x] is mutable, it is shared among all elements
44 of the array, and modifying [x] through one of the array entries
45 will modify all other entries at the same time.
47 Raise [Invalid_argument] if [n < 0] or [n > Sys.max_array_length].
48 If the value of [x] is a floating-point number, then the maximum
49 size is only [Sys.max_array_length / 2].*)
51 external create : int -> 'a -> 'a array = "caml_make_vect"
52 (** @deprecated [Array.create] is an alias for {!ArrayLabels.make}. *)
54 val init : int -> f:(int -> 'a) -> 'a array
55 (** [Array.init n f] returns a fresh array of length [n],
56 with element number [i] initialized to the result of [f i].
57 In other terms, [Array.init n f] tabulates the results of [f]
58 applied to the integers [0] to [n-1].
60 Raise [Invalid_argument] if [n < 0] or [n > Sys.max_array_length].
61 If the return type of [f] is [float], then the maximum
62 size is only [Sys.max_array_length / 2].*)
64 val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
65 (** [Array.make_matrix dimx dimy e] returns a two-dimensional array
66 (an array of arrays) with first dimension [dimx] and
67 second dimension [dimy]. All the elements of this new matrix
68 are initially physically equal to [e].
69 The element ([x,y]) of a matrix [m] is accessed
70 with the notation [m.(x).(y)].
72 Raise [Invalid_argument] if [dimx] or [dimy] is negative or
73 greater than [Sys.max_array_length].
74 If the value of [e] is a floating-point number, then the maximum
75 size is only [Sys.max_array_length / 2]. *)
77 val create_matrix : dimx:int -> dimy:int -> 'a -> 'a array array
78 (** @deprecated [Array.create_matrix] is an alias for
79 {!ArrayLabels.make_matrix}. *)
81 val append : 'a array -> 'a array -> 'a array
82 (** [Array.append v1 v2] returns a fresh array containing the
83 concatenation of the arrays [v1] and [v2]. *)
85 val concat : 'a array list -> 'a array
86 (** Same as [Array.append], but concatenates a list of arrays. *)
88 val sub : 'a array -> pos:int -> len:int -> 'a array
89 (** [Array.sub a start len] returns a fresh array of length [len],
90 containing the elements number [start] to [start + len - 1]
91 of array [a].
93 Raise [Invalid_argument "Array.sub"] if [start] and [len] do not
94 designate a valid subarray of [a]; that is, if
95 [start < 0], or [len < 0], or [start + len > Array.length a]. *)
97 val copy : 'a array -> 'a array
98 (** [Array.copy a] returns a copy of [a], that is, a fresh array
99 containing the same elements as [a]. *)
101 val fill : 'a array -> pos:int -> len:int -> 'a -> unit
102 (** [Array.fill a ofs len x] modifies the array [a] in place,
103 storing [x] in elements number [ofs] to [ofs + len - 1].
105 Raise [Invalid_argument "Array.fill"] if [ofs] and [len] do not
106 designate a valid subarray of [a]. *)
108 val blit :
109 src:'a array -> src_pos:int -> dst:'a array -> dst_pos:int -> len:int ->
110 unit
111 (** [Array.blit v1 o1 v2 o2 len] copies [len] elements
112 from array [v1], starting at element number [o1], to array [v2],
113 starting at element number [o2]. It works correctly even if
114 [v1] and [v2] are the same array, and the source and
115 destination chunks overlap.
117 Raise [Invalid_argument "Array.blit"] if [o1] and [len] do not
118 designate a valid subarray of [v1], or if [o2] and [len] do not
119 designate a valid subarray of [v2]. *)
121 val to_list : 'a array -> 'a list
122 (** [Array.to_list a] returns the list of all the elements of [a]. *)
124 val of_list : 'a list -> 'a array
125 (** [Array.of_list l] returns a fresh array containing the elements
126 of [l]. *)
128 val iter : f:('a -> unit) -> 'a array -> unit
129 (** [Array.iter f a] applies function [f] in turn to all
130 the elements of [a]. It is equivalent to
131 [f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
133 val map : f:('a -> 'b) -> 'a array -> 'b array
134 (** [Array.map f a] applies function [f] to all the elements of [a],
135 and builds an array with the results returned by [f]:
136 [[| f a.(0); f a.(1); ...; f a.(Array.length a - 1) |]]. *)
138 val iteri : f:(int -> 'a -> unit) -> 'a array -> unit
139 (** Same as {!ArrayLabels.iter}, but the
140 function is applied to the index of the element as first argument,
141 and the element itself as second argument. *)
143 val mapi : f:(int -> 'a -> 'b) -> 'a array -> 'b array
144 (** Same as {!ArrayLabels.map}, but the
145 function is applied to the index of the element as first argument,
146 and the element itself as second argument. *)
148 val fold_left : f:('a -> 'b -> 'a) -> init:'a -> 'b array -> 'a
149 (** [Array.fold_left f x a] computes
150 [f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)],
151 where [n] is the length of the array [a]. *)
153 val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
154 (** [Array.fold_right f a x] computes
155 [f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))],
156 where [n] is the length of the array [a]. *)
159 (** {6 Sorting} *)
162 val sort : cmp:('a -> 'a -> int) -> 'a array -> unit
163 (** Sort an array in increasing order according to a comparison
164 function. The comparison function must return 0 if its arguments
165 compare as equal, a positive integer if the first is greater,
166 and a negative integer if the first is smaller (see below for a
167 complete specification). For example, {!Pervasives.compare} is
168 a suitable comparison function, provided there are no floating-point
169 NaN values in the data. After calling [Array.sort], the
170 array is sorted in place in increasing order.
171 [Array.sort] is guaranteed to run in constant heap space
172 and (at most) logarithmic stack space.
174 The current implementation uses Heap Sort. It runs in constant
175 stack space.
177 Specification of the comparison function:
178 Let [a] be the array and [cmp] the comparison function. The following
179 must be true for all x, y, z in a :
180 - [cmp x y] > 0 if and only if [cmp y x] < 0
181 - if [cmp x y] >= 0 and [cmp y z] >= 0 then [cmp x z] >= 0
183 When [Array.sort] returns, [a] contains the same elements as before,
184 reordered in such a way that for all i and j valid indices of [a] :
185 - [cmp a.(i) a.(j)] >= 0 if and only if i >= j
188 val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
189 (** Same as {!ArrayLabels.sort}, but the sorting algorithm is stable (i.e.
190 elements that compare equal are kept in their original order) and
191 not guaranteed to run in constant heap space.
193 The current implementation uses Merge Sort. It uses [n/2]
194 words of heap space, where [n] is the length of the array.
195 It is usually faster than the current implementation of {!ArrayLabels.sort}.
198 val fast_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
199 (** Same as {!Array.sort} or {!Array.stable_sort}, whichever is faster
200 on typical input.
204 (**/**)
206 (** {6 Undocumented functions} *)
208 external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
209 external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"