MAJ et ecriture de la doc
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2859 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
aa1695e196
commit
76ad1e1a27
|
@ -24,14 +24,14 @@ type int_elt
|
|||
type int32_elt
|
||||
type int64_elt
|
||||
type nativeint_elt
|
||||
type float4_elt
|
||||
type float8_elt
|
||||
type float32_elt
|
||||
type float64_elt
|
||||
|
||||
(* Keep those constants in sync with the caml_bigarray_kind enumeration
|
||||
in bigarray.h *)
|
||||
|
||||
let float4 = 0
|
||||
let float8 = 1
|
||||
let float32 = 0
|
||||
let float64 = 1
|
||||
let int8_signed = 2
|
||||
let int8_unsigned = 3
|
||||
let int16_signed = 4
|
||||
|
|
|
@ -14,10 +14,25 @@
|
|||
|
||||
(* Module [Bigarray]: large, multi-dimensional, numerical arrays *)
|
||||
|
||||
(* Bla bla *)
|
||||
(* This module implements multi-dimensional arrays of integers and
|
||||
floating-point numbers, thereafter referred to as ``big arrays''.
|
||||
The implementation allows efficient sharing of large numerical
|
||||
arrays between Caml code and C or Fortran numerical libraries.
|
||||
|
||||
type ('a, 'b) kind
|
||||
Concerning the naming conventions, users of this module are encouraged
|
||||
to do [open Bigarray] in their source, then refer to array types and
|
||||
operations via short dot notation, e.g. [Array1.t] or [Array2.sub].
|
||||
|
||||
Big arrays support all the Caml ad-hoc polymorphic operations:
|
||||
comparisons ([=], [<>], [<=], etc, as well as [compare]);
|
||||
hashing (module [Hash]);
|
||||
and structured input-output ([output_value] and [input_value],
|
||||
as well as the functions from the [Marshal] module). *)
|
||||
|
||||
(*** Element kinds *)
|
||||
|
||||
type float32_elt
|
||||
type float64_elt
|
||||
type int8_signed_elt
|
||||
type int8_unsigned_elt
|
||||
type int16_signed_elt
|
||||
|
@ -26,9 +41,40 @@ type int_elt
|
|||
type int32_elt
|
||||
type int64_elt
|
||||
type nativeint_elt
|
||||
type float4_elt
|
||||
type float8_elt
|
||||
(* Big arrays can contain elements of the following kinds:
|
||||
- IEEE single precision (32 bits) floating-point numbers;
|
||||
- IEEE double precision (64 bits) floating-point numbers;
|
||||
- 8-bit integers (signed or unsigned);
|
||||
- 16-bit integers (signed or unsigned);
|
||||
- Caml integers (signed, 31 bits on 32-bit architectures,
|
||||
63 bits on 64-bit architectures);
|
||||
- 32-bit signed integers;
|
||||
- 64-bit signed integers;
|
||||
- platform-native signed integers (32 bits on 32-bit architectures,
|
||||
64 bits on 64-bit architectures).
|
||||
|
||||
Each element kind is represented at the type level by one
|
||||
of the abstract types defined above. *)
|
||||
|
||||
type ('a, 'b) kind
|
||||
(* To each element kind is associated a Caml type, which is
|
||||
the type of Caml values that can be stored in the big array
|
||||
or read back from it. This type is not necessarily the same
|
||||
as the type of the array elements proper: for instance,
|
||||
a big array whose elements are of kind [float32_elt] contains
|
||||
32-bit single precision floats, but reading or writing one of
|
||||
its elements from Caml uses the Caml type [float], which is
|
||||
64-bit double precision floats.
|
||||
|
||||
The abstract type [('a, 'b) kind] captures this association
|
||||
of a Caml type ['a] for values read or written in the big array,
|
||||
and of an element kind ['b] which represents the actual contents
|
||||
of the big array. The following predefined values of type
|
||||
[kind] list all possible associations of Caml types with
|
||||
element kinds: *)
|
||||
|
||||
val float32: (float, float32_elt) kind
|
||||
val float64: (float, float64_elt) kind
|
||||
val int8_signed: (int, int8_signed_elt) kind
|
||||
val int8_unsigned: (int, int8_unsigned_elt) kind
|
||||
val int16_signed: (int, int16_signed_elt) kind
|
||||
|
@ -37,79 +83,435 @@ val int: (int, int_elt) kind
|
|||
val int32: (int32, int32_elt) kind
|
||||
val int64: (int64, int64_elt) kind
|
||||
val nativeint: (nativeint, nativeint_elt) kind
|
||||
val float4: (float, float4_elt) kind
|
||||
val float8: (float, float8_elt) kind
|
||||
(* As shown by the types of the values above,
|
||||
big arrays of kind [float32_elt] and [float64_elt] are
|
||||
accessed using the Caml type [float]. Big arrays of
|
||||
integer kinds are accessed using the smallest Caml integer
|
||||
type large enough to represent the array elements:
|
||||
[int] for 8- and 16-bit integer bigarrays, as well as Caml-integer
|
||||
bigarrays; [int32] for 32-bit integer bigarrays; [int64]
|
||||
for 64-bit integer bigarrays; and [nativeint] for
|
||||
platform-native integer bigarrays. *)
|
||||
|
||||
type 'a layout
|
||||
(*** Array layouts *)
|
||||
|
||||
type c_layout
|
||||
type fortran_layout
|
||||
(* To facilitate interoperability with existing C and Fortran code,
|
||||
this library supports two different memory layouts for big arrays,
|
||||
one compatible with the C conventions,
|
||||
the other compatible with the Fortran conventions.
|
||||
|
||||
In the C-style layout, array indices start at 0, and
|
||||
multi-dimensional arrays are laid out in row-major format.
|
||||
That is, for a two-dimensional array, all elements of
|
||||
row 0 are contiguous in memory, followed by all elements of
|
||||
row 1, etc. In other terms, the array elements at [(x,y)]
|
||||
and [(x, y+1)] are adjacent in memory.
|
||||
|
||||
In the Fortran-style layout, array indices start at 1, and
|
||||
multi-dimensional arrays are laid out in column-major format.
|
||||
That is, for a two-dimensional array, all elements of
|
||||
column 0 are contiguous in memory, followed by all elements of
|
||||
column 1, etc. In other terms, the array elements at [(x,y)]
|
||||
and [(x+1, y)] are adjacent in memory.
|
||||
|
||||
Each layout style is identified at the type level by the
|
||||
abstract types [c_layout] and [fortran_layout] respectively. *)
|
||||
|
||||
type 'a layout
|
||||
(* The type ['a layout] represents one of the two supported
|
||||
memory layouts: C-style if ['a] is [c_layout], Fortran-style
|
||||
if ['a] is [fortran_layout]. *)
|
||||
|
||||
val c_layout: c_layout layout
|
||||
val fortran_layout: fortran_layout layout
|
||||
(* The abstract values [c_layout] and [fortran_layout] represent
|
||||
the two supported layouts at the level of values. *)
|
||||
|
||||
module Array1: sig
|
||||
type ('a, 'b, 'c) t
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> ('a, 'b, 'c) t
|
||||
external get: ('a, 'b, 'c) t -> int -> 'a = "bigarray_get_1"
|
||||
external set: ('a, 'b, 'c) t -> int -> 'a -> unit = "bigarray_set_1"
|
||||
val dim: ('a, 'b, 'c) t -> int
|
||||
external sub: ('a, 'b, 'c) t -> int -> int -> ('a, 'b, 'c) t = "bigarray_sub"
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
end
|
||||
|
||||
module Array2: sig
|
||||
type ('a, 'b, 'c) t
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> int -> ('a, 'b, 'c) t
|
||||
external get: ('a, 'b, 'c) t -> int -> int -> 'a = "bigarray_get_2"
|
||||
external set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit = "bigarray_set_2"
|
||||
val dim1: ('a, 'b, 'c) t -> int
|
||||
val dim2: ('a, 'b, 'c) t -> int
|
||||
external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
external sub_right: ('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
val slice_left: ('a, 'b, c_layout) t -> int -> ('a, 'b, c_layout) Array1.t
|
||||
val slice_right: ('a, 'b, fortran_layout) t -> int -> ('a, 'b, fortran_layout) Array1.t
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
end
|
||||
|
||||
module Array3: sig
|
||||
type ('a, 'b, 'c) t
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> int -> int -> ('a, 'b, 'c) t
|
||||
external get: ('a, 'b, 'c) t -> int -> int -> int -> 'a = "bigarray_get_3"
|
||||
external set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit = "bigarray_set_3"
|
||||
val dim1: ('a, 'b, 'c) t -> int
|
||||
val dim2: ('a, 'b, 'c) t -> int
|
||||
val dim3: ('a, 'b, 'c) t -> int
|
||||
external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
external sub_right: ('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
val slice_left_1: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) Array1.t
|
||||
val slice_right_1: ('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) Array1.t
|
||||
val slice_left_2: ('a, 'b, c_layout) t -> int -> ('a, 'b, c_layout) Array2.t
|
||||
val slice_right_2: ('a, 'b, fortran_layout) t -> int -> ('a, 'b, fortran_layout) Array2.t
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
end
|
||||
(*** Generic arrays (of arbitrarily many dimensions) *)
|
||||
|
||||
module Genarray: sig
|
||||
type ('a, 'b, 'c) t
|
||||
(* The type [Genarray.t] is the type of big arrays with variable
|
||||
numbers of dimensions. Any number of dimensions between 1 and 16
|
||||
is supported.
|
||||
|
||||
The three type parameters to [Genarray.t] identify the array element
|
||||
kind and layout, as follows:
|
||||
- the first parameter, ['a], is the Caml type for accessing array
|
||||
elements ([float], [int], [int32], [int64], [nativeint]);
|
||||
- the second parameter, ['b], is the actual kind of array elements
|
||||
([float32_elt], [float64_elt], [int8_signed_elt], [int8_unsigned_elt],
|
||||
etc);
|
||||
- the third parameter, ['c], identifies the array layout
|
||||
([c_layout] or [fortran_layout]).
|
||||
|
||||
For instance, [(float, float32_elt, fortran_layout) Genarray.t]
|
||||
is the type of generic big arrays containing 32-bit floats
|
||||
in Fortran layout; reads and writes in this array use the
|
||||
Caml type [float]. *)
|
||||
|
||||
external create: ('a, 'b) kind -> 'c layout -> int array -> ('a, 'b, 'c) t = "bigarray_create"
|
||||
external get: ('a, 'b, 'c) t -> int array -> 'a = "bigarray_get_generic"
|
||||
external set: ('a, 'b, 'c) t -> int array -> 'a -> unit = "bigarray_set_generic"
|
||||
(* [Genarray.create kind layout dimensions] returns a new big array
|
||||
whose element kind is determined by the parameter [kind] (one of
|
||||
[float32], [float64], [int8_signed], etc) and whose layout is
|
||||
determined by the parameter [layout] (one of [c_layout] or
|
||||
[fortran_layout]). The [dimensions] parameter is an array of
|
||||
integers that indicate the size of the big array in each dimension.
|
||||
The length of [dimensions] determines the number of dimensions
|
||||
of the bigarray.
|
||||
|
||||
For instance, [Genarray.create int32 c_layout [|4;6;8|]]
|
||||
returns a fresh big array of 32-bit integers, in C layout,
|
||||
having three dimensions, the three dimensions being 4, 6 and 8
|
||||
respectively.
|
||||
|
||||
Big arrays returned by [Genarray.create] are not initialized:
|
||||
the initial values of array elements is unspecified.
|
||||
|
||||
[Genarray.create] raises [Invalid_arg] if the number of dimensions
|
||||
is not in the range 1 to 16 inclusive, or if one of the dimensions
|
||||
is negative. *)
|
||||
external num_dims: ('a, 'b, 'c) t -> int = "bigarray_num_dims"
|
||||
(* Return the number of dimensions of the given big array. *)
|
||||
external nth_dim: ('a, 'b, 'c) t -> int -> int = "bigarray_dim"
|
||||
external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
external sub_right: ('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
external slice_left: ('a, 'b, c_layout) t -> int array -> ('a, 'b, c_layout) t = "bigarray_slice"
|
||||
external slice_right: ('a, 'b, fortran_layout) t -> int array -> ('a, 'b, fortran_layout) t = "bigarray_slice"
|
||||
(* [Genarray.nth_dim a n] returns the [n]-th dimension of the
|
||||
big array [a]. The first dimension corresponds to [n = 0];
|
||||
the second dimension corresponds to [n = 1]; the last dimension,
|
||||
to [n = Genarray.num_dims a - 1].
|
||||
Raise [Invalid_arg] if [n] is less than 0 or greater or equal than
|
||||
[Genarray.num_dims a]. *)
|
||||
external get: ('a, 'b, 'c) t -> int array -> 'a = "bigarray_get_generic"
|
||||
(* Read an element of a generic big array.
|
||||
[Genarray.get a [|i1; ...; iN|]] returns the element of [a]
|
||||
whose coordinates are [i1] in the first dimension, [i2] in
|
||||
the second dimension, \ldots, [iN] in the [N]-th dimension.
|
||||
|
||||
If [a] has C layout, the coordinates must be greater or equal than 0
|
||||
and strictly less than the corresponding dimensions of [a].
|
||||
If [a] has Fortran layout, the coordinates must be greater or equal
|
||||
than 1 and less or equal than the corresponding dimensions of [a].
|
||||
Raise [Invalid_arg] if the array [a] does not have exactly [N]
|
||||
dimensions, or if the coordinates are outside the array bounds.
|
||||
|
||||
If [N > 3], alternate syntax is provided: you can write
|
||||
[a.{i1, i2, ..., iN}] instead of [Genarray.get a [|i1; ...; iN|]].
|
||||
(The syntax [a.{...}] with one, two or three coordinates is
|
||||
reserved for accessing one-, two- and three-dimensional arrays
|
||||
as described below.) *)
|
||||
external set: ('a, 'b, 'c) t -> int array -> 'a -> unit = "bigarray_set_generic"
|
||||
(* Assign an element of a generic big array.
|
||||
[Genarray.set a [|i1; ...; iN|] v] stores the value [v] in the
|
||||
element of [a] whose coordinates are [i1] in the first dimension,
|
||||
[i2] in the second dimension, \ldots, [iN] in the [N]-th dimension.
|
||||
|
||||
The array [a] must have exactly [N] dimensions, and all coordinates
|
||||
must lie inside the array bounds, as described for [Genarray.get];
|
||||
otherwise, [Invalid_arg] is raised.
|
||||
|
||||
If [N > 3], alternate syntax is provided: you can write
|
||||
[a.{i1, i2, ..., iN} <- v] instead of
|
||||
[Genarray.set a [|i1; ...; iN|] v].
|
||||
(The syntax [a.{...} <- v] with one, two or three coordinates is
|
||||
reserved for updating one-, two- and three-dimensional arrays
|
||||
as described below.) *)
|
||||
external sub_left:
|
||||
('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
(* Extract a sub-array of the given big array by restricting the
|
||||
first (left-most) dimension. [Genarray.sub_left a ofs len]
|
||||
returns a big array with the same number of dimensions as [a],
|
||||
and the same dimensions as [a], except the first dimension,
|
||||
which corresponds to the interval [[ofs ... ofs + len - 1]]
|
||||
of the first dimension of [a]. No copying of elements is
|
||||
involved: the sub-array and the original array share the same
|
||||
storage space. In other terms, the element at coordinates
|
||||
[[|i1; ...; iN|]] of the sub-array is identical to the
|
||||
element at coordinates [[|i1+ofs; ...; iN|]] of the original
|
||||
array [a].
|
||||
|
||||
[Genarray.sub_left] applies only to big arrays in C layout.
|
||||
Raise [Invalid_arg] if [ofs] and [len] do not designate
|
||||
a valid sub-array of [a], that is, if [ofs] < 0, or [len] < 0,
|
||||
or [ofs + len > Genarray.nth_dim a 0]. *)
|
||||
external sub_right:
|
||||
('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
(* Extract a sub-array of the given big array by restricting the
|
||||
last (right-most) dimension. [Genarray.sub_right a ofs len]
|
||||
returns a big array with the same number of dimensions as [a],
|
||||
and the same dimensions as [a], except the last dimension,
|
||||
which corresponds to the interval [[ofs ... ofs + len - 1]]
|
||||
of the last dimension of [a]. No copying of elements is
|
||||
involved: the sub-array and the original array share the same
|
||||
storage space. In other terms, the element at coordinates
|
||||
[[|i1; ...; iN|]] of the sub-array is identical to the
|
||||
element at coordinates [[|i1; ...; iN+ofs|]] of the original
|
||||
array [a].
|
||||
|
||||
[Genarray.sub_right] applies only to big arrays in Fortran layout.
|
||||
Raise [Invalid_arg] if [ofs] and [len] do not designate
|
||||
a valid sub-array of [a], that is, if [ofs] < 1, or [len] < 0,
|
||||
or [ofs + len > Genarray.nth_dim a (Genarray.num_dims a - 1)]. *)
|
||||
external slice_left:
|
||||
('a, 'b, c_layout) t -> int array -> ('a, 'b, c_layout) t = "bigarray_slice"
|
||||
(* Extract a sub-array of lower dimension from the given big array
|
||||
by fixing one or several of the first (left-most) coordinates.
|
||||
[Genarray.slice_left a [|i1; ... ; iM|]] returns the ``slice''
|
||||
of [a] obtained by setting the first [M] coordinates to
|
||||
[i1], \ldots, [iM]. If [a] has [N] dimensions, the slice has
|
||||
dimension [N - M], and the element at coordinates
|
||||
[[|j1; ...; j(N-M)|]] in the slice is identical to the element
|
||||
at coordinates [[|i1; ...; iM; j1; ...; j(N-M)|]] in the original
|
||||
array [a]. No copying of elements is involved: the slice and
|
||||
the original array share the same storage space.
|
||||
|
||||
[Genarray.slice_left] applies only to big arrays in C layout.
|
||||
Raise [Invalid_arg] if [M >= N], or if [[|i1; ... ; iM|]]
|
||||
is outside the bounds of [a]. *)
|
||||
external slice_right:
|
||||
('a, 'b, fortran_layout) t -> int array -> ('a, 'b, fortran_layout) t = "bigarray_slice"
|
||||
(* Extract a sub-array of lower dimension from the given big array
|
||||
by fixing one or several of the last (right-most) coordinates.
|
||||
[Genarray.slice_right a [|i1; ... ; iM|]] returns the ``slice''
|
||||
of [a] obtained by setting the last [M] coordinates to
|
||||
[i1], \ldots, [iM]. If [a] has [N] dimensions, the slice has
|
||||
dimension [N - M], and the element at coordinates
|
||||
[[|j1; ...; j(N-M)|]] in the slice is identical to the element
|
||||
at coordinates [[|j1; ...; j(N-M); i1; ...; iM|]] in the original
|
||||
array [a]. No copying of elements is involved: the slice and
|
||||
the original array share the same storage space.
|
||||
|
||||
[Genarray.slice_right] applies only to big arrays in Fortran layout.
|
||||
Raise [Invalid_arg] if [M >= N], or if [[|i1; ... ; iM|]]
|
||||
is outside the bounds of [a]. *)
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
(* Copy all elements of a big array in another big array.
|
||||
[Genarray.blit src dst] copies all elements of [src] into
|
||||
[dst]. Both arrays [src] and [dst] must have the same number of
|
||||
dimensions and equal dimensions. Copying a sub-array of [src]
|
||||
to a sub-array of [dst] can be achieved by applying [Genarray.blit]
|
||||
to sub-array or slices of [src] and [dst]. *)
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
(* Set all elements of a big array to a given value.
|
||||
[Genarray.fill a v] stores the value [v] in all elements of
|
||||
the big array [a]. Setting only some elements of [a] to [v]
|
||||
can be achieved by applying [Genarray.fill] to a sub-array
|
||||
or a slice of [a]. *)
|
||||
end
|
||||
|
||||
(*** One-dimensional arrays *)
|
||||
|
||||
(* The [Array1] structure provides operations similar to those of
|
||||
[Genarray], but specialized to the case of one-dimensional arrays.
|
||||
(The [Array2] and [Array3] structures below provide operations
|
||||
specialized for two- and three-dimensional arrays.)
|
||||
Statically knowing the number of dimensions of the array allows
|
||||
faster operations, and more precise static type-checking. *)
|
||||
|
||||
module Array1: sig
|
||||
type ('a, 'b, 'c) t
|
||||
(* The type of one-dimensional big arrays whose elements have
|
||||
Caml type ['a], representation kind ['b], and memory layout ['c]. *)
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> ('a, 'b, 'c) t
|
||||
(* [Array1.create kind layout dim] returns a new bigarray of
|
||||
one dimension, whose size is [dim]. [kind] and [layout]
|
||||
determine the array element kind and the array layout
|
||||
as described for [Genarray.create]. *)
|
||||
val dim: ('a, 'b, 'c) t -> int
|
||||
(* Return the size (dimension) of the given one-dimensional
|
||||
big array. *)
|
||||
external get: ('a, 'b, 'c) t -> int -> 'a = "bigarray_get_1"
|
||||
(* [Array1.get a x], or alternatively [a.{x}],
|
||||
returns the element of [a] at index [x].
|
||||
[x] must be greater or equal than [0] and strictly less than
|
||||
[Array1.dim a] if [a] has C layout. If [a] has Fortran layout,
|
||||
[x] must be greater or equal than [1] and less or equal than
|
||||
[Array1.dim a]. Otherwise, [Invalid_arg] is raised. *)
|
||||
external set: ('a, 'b, 'c) t -> int -> 'a -> unit = "bigarray_set_1"
|
||||
(* [Array1.set a x v], also written [a.{x} <- v],
|
||||
stores the value [v] at index [x] in [a].
|
||||
[x] must be inside the bounds of [a] as described in [Array1.get];
|
||||
otherwise, [Invalid_arg] is raised. *)
|
||||
external sub: ('a, 'b, 'c) t -> int -> int -> ('a, 'b, 'c) t = "bigarray_sub"
|
||||
(* Extract a sub-array of the given one-dimensional big array.
|
||||
See [Genarray.sub_left] for more details. *)
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
(* Copy the first big array to the second big array.
|
||||
See [Genarray.blit] for more details. *)
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
(* Fill the given big array with the given value.
|
||||
See [Genarray.fill] for more details. *)
|
||||
end
|
||||
|
||||
(*** Two-dimensional arrays *)
|
||||
|
||||
(* The [Array2] structure provides operations similar to those of
|
||||
[Genarray], but specialized to the case of three-dimensional arrays. *)
|
||||
|
||||
module Array2: sig
|
||||
type ('a, 'b, 'c) t
|
||||
(* The type of two-dimensional big arrays whose elements have
|
||||
Caml type ['a], representation kind ['b], and memory layout ['c]. *)
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> int -> ('a, 'b, 'c) t
|
||||
(* [Array2.create kind layout dim1 dim2] returns a new bigarray of
|
||||
two dimension, whose size is [dim1] in the first dimension
|
||||
and [dim2] in the second dimension. [kind] and [layout]
|
||||
determine the array element kind and the array layout
|
||||
as described for [Genarray.create]. *)
|
||||
val dim1: ('a, 'b, 'c) t -> int
|
||||
(* Return the first dimension of the given two-dimensional
|
||||
big array. *)
|
||||
val dim2: ('a, 'b, 'c) t -> int
|
||||
(* Return the second dimension of the given two-dimensional
|
||||
big array. *)
|
||||
external get: ('a, 'b, 'c) t -> int -> int -> 'a = "bigarray_get_2"
|
||||
(* [Array2.get a x y], also written [a.{x,y}],
|
||||
returns the element of [a] at coordinates ([x], [y]).
|
||||
[x] and [y] must be within the bounds
|
||||
of [a], as described for [Genarray.get]; otherwise, [Invalid_arg]
|
||||
is raised. *)
|
||||
external set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit = "bigarray_set_2"
|
||||
(* [Array2.set a x y v], or alternatively [a.{x,y} <- v],
|
||||
stores the value [v] at coordinates ([x], [y]) in [a].
|
||||
[x] and [y] must be within the bounds of [a],
|
||||
as described for [Genarray.set];
|
||||
otherwise, [Invalid_arg] is raised. *)
|
||||
external sub_left:
|
||||
('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
(* Extract a two-dimensional sub-array of the given two-dimensional
|
||||
big array by restricting the first dimension.
|
||||
See [Genarray.sub_left] for more details. [Array2.sub_left]
|
||||
applies only to arrays with C layout. *)
|
||||
external sub_right:
|
||||
('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
(* Extract a two-dimensional sub-array of the given two-dimensional
|
||||
big array by restricting the second dimension.
|
||||
See [Genarray.sub_right] for more details. [Array2.sub_right]
|
||||
applies only to arrays with Fortran layout. *)
|
||||
val slice_left:
|
||||
('a, 'b, c_layout) t -> int -> ('a, 'b, c_layout) Array1.t
|
||||
(* Extract a row (one-dimensional slice) of the given two-dimensional
|
||||
big array. The integer parameter is the index of the row to
|
||||
extract. See [Genarray.slice_left] for more details.
|
||||
[Array2.slice_left] applies only to arrays with C layout. *)
|
||||
val slice_right:
|
||||
('a, 'b, fortran_layout) t -> int -> ('a, 'b, fortran_layout) Array1.t
|
||||
(* Extract a column (one-dimensional slice) of the given
|
||||
two-dimensional big array. The integer parameter is the
|
||||
index of the column to extract. See [Genarray.slice_right] for
|
||||
more details. [Array2.slice_right] applies only to arrays
|
||||
with Fortran layout. *)
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
(* Copy the first big array to the second big array.
|
||||
See [Genarray.blit] for more details. *)
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
(* Fill the given big array with the given value.
|
||||
See [Genarray.fill] for more details. *)
|
||||
end
|
||||
|
||||
(*** Three-dimensional arrays *)
|
||||
|
||||
(* The [Array3] structure provides operations similar to those of
|
||||
[Genarray], but specialized to the case of three-dimensional arrays. *)
|
||||
|
||||
module Array3: sig
|
||||
type ('a, 'b, 'c) t
|
||||
(* The type of three-dimensional big arrays whose elements have
|
||||
Caml type ['a], representation kind ['b], and memory layout ['c]. *)
|
||||
val create: ('a, 'b) kind -> 'c layout -> int -> int -> int -> ('a, 'b, 'c) t
|
||||
(* [Array3.create kind layout dim1 dim2 dim3] returns a new bigarray of
|
||||
three dimension, whose size is [dim1] in the first dimension,
|
||||
[dim2] in the second dimension, and [dim3] in the third.
|
||||
[kind] and [layout] determine the array element kind and
|
||||
the array layout as described for [Genarray.create]. *)
|
||||
val dim1: ('a, 'b, 'c) t -> int
|
||||
(* Return the first dimension of the given three-dimensional
|
||||
big array. *)
|
||||
val dim2: ('a, 'b, 'c) t -> int
|
||||
(* Return the second dimension of the given three-dimensional
|
||||
big array. *)
|
||||
val dim3: ('a, 'b, 'c) t -> int
|
||||
(* Return the third dimension of the given three-dimensional
|
||||
big array. *)
|
||||
external get: ('a, 'b, 'c) t -> int -> int -> int -> 'a = "bigarray_get_3"
|
||||
(* [Array3.get a x y z], also written [a.{x,y,z}],
|
||||
returns the element of [a] at coordinates ([x], [y], [z]).
|
||||
[x], [y] and [z] must be within the bounds of [a],
|
||||
as described for [Genarray.get]; otherwise, [Invalid_arg]
|
||||
is raised. *)
|
||||
external set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit = "bigarray_set_3"
|
||||
(* [Array3.set a x y v], or alternatively [a.{x,y,z} <- v],
|
||||
stores the value [v] at coordinates ([x], [y], [z]) in [a].
|
||||
[x], [y] and [z] must be within the bounds of [a],
|
||||
as described for [Genarray.set];
|
||||
otherwise, [Invalid_arg] is raised. *)
|
||||
external sub_left:
|
||||
('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t = "bigarray_sub"
|
||||
(* Extract a three-dimensional sub-array of the given
|
||||
three-dimensional big array by restricting the first dimension.
|
||||
See [Genarray.sub_left] for more details. [Array3.sub_left]
|
||||
applies only to arrays with C layout. *)
|
||||
external sub_right:
|
||||
('a, 'b, fortran_layout) t -> int -> int -> ('a, 'b, fortran_layout) t = "bigarray_sub"
|
||||
(* Extract a three-dimensional sub-array of the given
|
||||
three-dimensional big array by restricting the second dimension.
|
||||
See [Genarray.sub_right] for more details. [Array3.sub_right]
|
||||
applies only to arrays with Fortran layout. *)
|
||||
val slice_left_1:
|
||||
('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) Array1.t
|
||||
(* Extract a one-dimensional slice of the given three-dimensional
|
||||
big array by fixing the first two coordinates.
|
||||
The integer parameters are the coordinates of the slice to
|
||||
extract. See [Genarray.slice_left] for more details.
|
||||
[Array3.slice_left_1] applies only to arrays with C layout. *)
|
||||
val slice_right_1:
|
||||
('a, 'b, fortran_layout) t -> int -> int ->
|
||||
('a, 'b, fortran_layout) Array1.t
|
||||
(* Extract a one-dimensional slice of the given three-dimensional
|
||||
big array by fixing the last two coordinates.
|
||||
The integer parameters are the coordinates of the slice to
|
||||
extract. See [Genarray.slice_right] for more details.
|
||||
[Array3.slice_right_1] applies only to arrays with Fortran
|
||||
layout. *)
|
||||
val slice_left_2:
|
||||
('a, 'b, c_layout) t -> int -> ('a, 'b, c_layout) Array2.t
|
||||
(* Extract a two-dimensional slice of the given three-dimensional
|
||||
big array by fixing the first coordinate.
|
||||
The integer parameter is the first coordinate of the slice to
|
||||
extract. See [Genarray.slice_left] for more details.
|
||||
[Array3.slice_left_2] applies only to arrays with C layout. *)
|
||||
val slice_right_2:
|
||||
('a, 'b, fortran_layout) t -> int -> ('a, 'b, fortran_layout) Array2.t
|
||||
(* Extract a two-dimensional slice of the given
|
||||
three-dimensional big array by fixing the last coordinate.
|
||||
The integer parameter is the first coordinate of the slice
|
||||
to extract. See [Genarray.slice_right] for more details.
|
||||
[Array3.slice_right_2] applies only to arrays with Fortran
|
||||
layout. *)
|
||||
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
|
||||
(* Copy the first big array to the second big array.
|
||||
See [Genarray.blit] for more details. *)
|
||||
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
|
||||
(* Fill the given big array with the given value.
|
||||
See [Genarray.fill] for more details. *)
|
||||
end
|
||||
|
||||
(*** Coercions between generic big arrays and fixed-dimension big arrays *)
|
||||
|
||||
external genarray_of_array1: ('a, 'b, 'c) Array1.t -> ('a, 'b, 'c) Genarray.t = "%identity"
|
||||
external genarray_of_array2: ('a, 'b, 'c) Array2.t -> ('a, 'b, 'c) Genarray.t = "%identity"
|
||||
external genarray_of_array3: ('a, 'b, 'c) Array3.t -> ('a, 'b, 'c) Genarray.t = "%identity"
|
||||
(* Return the generic big array corresponding to the given
|
||||
one-dimensional, two-dimensional or three-dimensional big array. *)
|
||||
val array1_of_genarray: ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array1.t
|
||||
(* Return the one-dimensional big array corresponding to the given
|
||||
generic big array. Raise [Invalid_arg] if the generic big array
|
||||
does not have exactly one dimension. *)
|
||||
val array2_of_genarray: ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array2.t
|
||||
(* Return the two-dimensional big array corresponding to the given
|
||||
generic big array. Raise [Invalid_arg] if the generic big array
|
||||
does not have exactly two dimensions. *)
|
||||
val array3_of_genarray: ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array3.t
|
||||
(* Return the three-dimensional big array corresponding to the given
|
||||
generic big array. Raise [Invalid_arg] if the generic big array
|
||||
does not have exactly three dimensions. *)
|
||||
|
|
|
@ -14,6 +14,7 @@
|
|||
|
||||
#include <stddef.h>
|
||||
#include <stdarg.h>
|
||||
#include <string.h>
|
||||
#include "alloc.h"
|
||||
#include "bigarray.h"
|
||||
#include "custom.h"
|
||||
|
@ -36,7 +37,7 @@ static long bigarray_num_elts(struct caml_bigarray * b)
|
|||
/* Size in bytes of a bigarray element, indexed by bigarray kind */
|
||||
|
||||
static int bigarray_element_size[] =
|
||||
{ 4 /*FLOAT4*/, 8 /*FLOAT8*/,
|
||||
{ 4 /*FLOAT32*/, 8 /*FLOAT64*/,
|
||||
1 /*SINT8*/, 1 /*UINT8*/,
|
||||
2 /*SINT16*/, 2 /*UINT16*/,
|
||||
4 /*INT32*/, 8 /*INT64*/,
|
||||
|
@ -108,8 +109,12 @@ value bigarray_create(value vkind, value vlayout, value vdim)
|
|||
|
||||
num_dims = Wosize_val(vdim);
|
||||
if (num_dims < 1 || num_dims > MAX_NUM_DIMS)
|
||||
invalid_argument("Bigarray.alloc: bad number of dimensions");
|
||||
for (i = 0; i < num_dims; i++) dim[i] = Long_val(Field(vdim, i));
|
||||
invalid_argument("Bigarray.create: bad number of dimensions");
|
||||
for (i = 0; i < num_dims; i++) {
|
||||
dim[i] = Long_val(Field(vdim, i));
|
||||
if (dim[i] < 0 || dim[i] > 0x7FFFFFFFL)
|
||||
invalid_argument("Bigarray.create: negative dimension");
|
||||
}
|
||||
flags = Int_val(vkind) | Int_val(vlayout);
|
||||
return alloc_bigarray(flags, num_dims, NULL, dim);
|
||||
}
|
||||
|
@ -160,9 +165,9 @@ value bigarray_get_N(value vb, value * vind, int nind)
|
|||
offset = bigarray_offset(b, index);
|
||||
/* Perform read */
|
||||
switch ((b->flags) & BIGARRAY_KIND_MASK) {
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
return copy_double(((float *) b->data)[offset]);
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
return copy_double(((double *) b->data)[offset]);
|
||||
case BIGARRAY_SINT8:
|
||||
return Val_int(((schar *) b->data)[offset]);
|
||||
|
@ -255,9 +260,9 @@ static value bigarray_set_aux(value vb, value * vind, long nind, value newval)
|
|||
offset = bigarray_offset(b, index);
|
||||
/* Perform write */
|
||||
switch (b->flags & BIGARRAY_KIND_MASK) {
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
((float *) b->data)[offset] = Double_val(newval); break;
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
((double *) b->data)[offset] = Double_val(newval); break;
|
||||
case BIGARRAY_SINT8:
|
||||
case BIGARRAY_UINT8:
|
||||
|
@ -381,11 +386,7 @@ static int bigarray_compare(value v1, value v2)
|
|||
long n, num_elts;
|
||||
int i;
|
||||
|
||||
/* Compare kind and layout */
|
||||
int flags1 = b1->flags & (BIGARRAY_KIND_MASK | BIGARRAY_LAYOUT_MASK);
|
||||
int flags2 = b2->flags & (BIGARRAY_KIND_MASK | BIGARRAY_LAYOUT_MASK);
|
||||
if (flags1 != flags2) return flags2 - flags1;
|
||||
/* Same kind and layout: compare number of dimensions */
|
||||
/* Compare number of dimensions */
|
||||
if (b1->num_dims != b2->num_dims) return b2->num_dims - b1->num_dims;
|
||||
/* Same number of dimensions: compare dimensions lexicographically */
|
||||
for (i = 0; i < b1->num_dims; i++) {
|
||||
|
@ -406,9 +407,9 @@ static int bigarray_compare(value v1, value v2)
|
|||
}
|
||||
|
||||
switch (b1->flags & BIGARRAY_KIND_MASK) {
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
DO_COMPARISON(float);
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
DO_COMPARISON(double);
|
||||
case BIGARRAY_SINT8:
|
||||
DO_COMPARISON(schar);
|
||||
|
@ -464,7 +465,7 @@ static long bigarray_hash(value v)
|
|||
for (n = 0; n < num_elts; n++) h = COMBINE(h, *p++);
|
||||
break;
|
||||
}
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
case BIGARRAY_INT32:
|
||||
#ifndef ARCH_SIXTYFOUR
|
||||
case BIGARRAY_CAML_INT:
|
||||
|
@ -475,7 +476,7 @@ static long bigarray_hash(value v)
|
|||
for (n = 0; n < num_elts; n++) h = COMBINE(h, *p++);
|
||||
break;
|
||||
}
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
case BIGARRAY_INT64:
|
||||
#ifdef ARCH_SIXTYFOUR
|
||||
case BIGARRAY_CAML_INT:
|
||||
|
@ -551,10 +552,10 @@ static void bigarray_serialize(value v,
|
|||
case BIGARRAY_SINT16:
|
||||
case BIGARRAY_UINT16:
|
||||
serialize_block_2(b->data, num_elts); break;
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
case BIGARRAY_INT32:
|
||||
serialize_block_4(b->data, num_elts); break;
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
case BIGARRAY_INT64:
|
||||
serialize_block_8(b->data, num_elts); break;
|
||||
case BIGARRAY_CAML_INT:
|
||||
|
@ -617,10 +618,10 @@ unsigned long bigarray_deserialize(void * dst)
|
|||
case BIGARRAY_SINT16:
|
||||
case BIGARRAY_UINT16:
|
||||
deserialize_block_2(b->data, num_elts); break;
|
||||
case BIGARRAY_FLOAT4:
|
||||
case BIGARRAY_FLOAT32:
|
||||
case BIGARRAY_INT32:
|
||||
deserialize_block_4(b->data, num_elts); break;
|
||||
case BIGARRAY_FLOAT8:
|
||||
case BIGARRAY_FLOAT64:
|
||||
case BIGARRAY_INT64:
|
||||
deserialize_block_8(b->data, num_elts); break;
|
||||
case BIGARRAY_CAML_INT:
|
||||
|
@ -676,8 +677,7 @@ value bigarray_slice(value vb, value vind)
|
|||
char * sub_data;
|
||||
value res;
|
||||
|
||||
/* Check number of indices < number of dimensions of array
|
||||
(maybe not necessary if ML typing guarantees this) */
|
||||
/* Check number of indices < number of dimensions of array */
|
||||
num_inds = Wosize_val(vind);
|
||||
if (num_inds >= b->num_dims)
|
||||
invalid_argument("Bigarray.slice: too many indices");
|
||||
|
@ -732,7 +732,7 @@ value bigarray_sub(value vb, value vofs, value vlen)
|
|||
changed_dim = b->num_dims - 1;
|
||||
ofs--; /* Fortran arrays start at 1 */
|
||||
}
|
||||
if (ofs < 0 || len <= 0 || ofs + len > b->dim[changed_dim])
|
||||
if (ofs < 0 || len < 0 || ofs + len > b->dim[changed_dim])
|
||||
invalid_argument("Bigarray.sub: bad sub-array");
|
||||
sub_data =
|
||||
(char *) b->data +
|
||||
|
@ -780,13 +780,13 @@ value bigarray_fill(value vb, value vinit)
|
|||
long num_elts = bigarray_num_elts(b);
|
||||
|
||||
switch (b->flags & BIGARRAY_KIND_MASK) {
|
||||
case BIGARRAY_FLOAT4: {
|
||||
case BIGARRAY_FLOAT32: {
|
||||
float init = Double_val(vinit);
|
||||
float * p;
|
||||
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
|
||||
break;
|
||||
}
|
||||
case BIGARRAY_FLOAT8: {
|
||||
case BIGARRAY_FLOAT64: {
|
||||
double init = Double_val(vinit);
|
||||
double * p;
|
||||
for (p = b->data; num_elts > 0; p++, num_elts--) *p = init;
|
||||
|
|
Loading…
Reference in New Issue