1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Module [Array]: array operations *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
external length : 'a array -> int = "%array_length"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Return the length (number of elements) of the given array. *)
|
1995-07-10 02:48:27 -07:00
|
|
|
external get: 'a array -> int -> 'a = "%array_safe_get"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.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].
|
|
|
|
Raise [Invalid_argument "Array.get"] if [n] is outside the range
|
|
|
|
0 to [(Array.length a - 1)].
|
1995-09-12 07:05:37 -07:00
|
|
|
You can also write [a.(n)] instead of [Array.get a n]. *)
|
1995-07-10 02:48:27 -07:00
|
|
|
external set: 'a array -> int -> 'a -> unit = "%array_safe_set"
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.set a n x] modifies array [a] in place, replacing
|
|
|
|
element number [n] with [x].
|
|
|
|
Raise [Invalid_argument "Array.set"] if [n] is outside the range
|
|
|
|
0 to [Array.length a - 1].
|
1995-09-12 07:05:37 -07:00
|
|
|
You can also write [a.(n) <- x] instead of [Array.set a n x]. *)
|
1996-04-22 04:15:41 -07:00
|
|
|
external create: int -> 'a -> 'a array = "make_vect"
|
|
|
|
(* [Array.create n x] returns a fresh array of length [n],
|
1995-08-09 06:15:01 -07:00
|
|
|
initialized with [x].
|
|
|
|
All the elements of this new array are initially
|
|
|
|
physically equal to [x] (in the sense of the [==] predicate).
|
|
|
|
Consequently, if [x] is mutable, it is shared among all elements
|
|
|
|
of the array, and modifying [x] through one of the array entries
|
|
|
|
will modify all other entries at the same time. *)
|
1996-04-22 04:15:41 -07:00
|
|
|
val create_matrix: int -> int -> 'a -> 'a array array
|
|
|
|
(* [Array.create_matrix dimx dimy e] returns a two-dimensional array
|
1995-08-09 06:15:01 -07:00
|
|
|
(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].
|
|
|
|
The element ([x,y]) of a matrix [m] is accessed
|
|
|
|
with the notation [m.(x).(y)]. *)
|
1995-06-05 06:42:38 -07:00
|
|
|
val append: 'a array -> 'a array -> 'a array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.append v1 v2] returns a fresh array containing the
|
|
|
|
concatenation of arrays [v1] and [v2]. *)
|
1995-06-05 06:42:38 -07:00
|
|
|
val concat: 'a array list -> 'a array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Same as [Array.append], but catenates a list of arrays. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val sub: 'a array -> int -> int -> 'a array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.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]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val copy: 'a array -> 'a array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.copy a] returns a copy of [a], that is, a fresh array
|
|
|
|
containing the same elements as [a]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val fill: 'a array -> int -> int -> 'a -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [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]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val blit: 'a array -> int -> 'a array -> int -> int -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [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
|
|
|
|
[v1] and [v2] are the same array, and the source and
|
|
|
|
destination chunks overlap.
|
|
|
|
Raise [Invalid_argument "Array.blit"] if [o1] and [len] do not
|
|
|
|
designate a valid subarray of [v1], or if [o2] and [len] do not
|
|
|
|
designate a valid subarray of [v2]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val iter: ('a -> 'b) -> 'a array -> unit
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.iter f a] applies function [f] in turn to all
|
|
|
|
the elements of [a], discarding all the results:
|
|
|
|
[f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val map: ('a -> 'b) -> 'a array -> 'b array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [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) |]]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val to_list: 'a array -> 'a list
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.to_list a] returns the list of all the elements of [a]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
val of_list: 'a list -> 'a array
|
1995-08-09 06:15:01 -07:00
|
|
|
(* [Array.of_list l] returns a fresh array containing the elements
|
|
|
|
of [l]. *)
|
|
|
|
|
|
|
|
(*--*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-06-15 01:10:01 -07:00
|
|
|
external unsafe_get: 'a array -> int -> 'a = "%array_unsafe_get"
|
|
|
|
external unsafe_set: 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
1995-05-04 03:15:53 -07:00
|
|
|
|