Previous Contents Next
Chapter 28 The bigarray library

The bigarray library implements large, multi-dimensional, numerical arrays. These arrays are called ``big arrays'' to distinguish them from the standard Caml arrays described in section 19.2. The main differences between ``big arrays'' and standard Caml arrays are as follows: Programs that use the bigarray library must be linked as follows:
        ocamlc other options bigarray.cma other files
        ocamlopt other options bigarray.cmxa other files
For interactive use of the bigarray library, do:
        ocamlmktop -o mytop bigarray.cma
        ./mytop
28.1 Module Bigarray: large, multi-dimensional, numerical arrays


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.

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
type int16_unsigned_elt
type int_elt
type int32_elt
type int64_elt
type nativeint_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
val int16_unsigned: (int, int16_unsigned_elt) kind
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 char: (char, int8_unsigned_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. Finally, big arrays of kind int8_unsigned_elt can also be accessed as arrays of characters instead of arrays of small integers, by using the kind value char instead of int8_unsigned.
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.
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:
    kind:('a, 'b) kind -> layout:'c layout -> dims:int array -> ('a, 'b, 'c) t
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
Return the number of dimensions of the given big array.
  external nth_dim: ('a, 'b, 'c) t -> int -> int
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
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, ..., 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
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, ..., 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 -> pos:int -> len:int -> ('a, 'b, c_layout) t
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 ->
    pos:int -> len:int -> ('a, 'b, fortran_layout) t
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
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, ..., 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
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, ..., 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: src:('a, 'b, 'c) t -> dst:('a, 'b, 'c) t -> unit
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
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.
  external map_file:
    Unix.file_descr -> kind:('a, 'b) kind -> layout:'c layout ->
    shared:bool -> dims:int array -> ('a, 'b, 'c) t
Memory mapping of a file as a big array. Genarray.map_file fd kind layout shared dims returns a big array of kind kind, layout layout, and dimensions as specified in dims. The data contained in this big array are the contents of the file referred to by the file descriptor fd (as opened previously with Unix.openfile, for example). If shared is true, all modifications performed on the array are reflected in the file. This requires that fd be opened with write permissions. If shared is false, modifications performed on the array are done in memory only, using copy-on-write of the modified pages; the underlying file is not affected.

Genarray.map_file is much more efficient than reading the whole file in a big array, modifying that big array, and writing it afterwards.

To adjust automatically the dimensions of the big array to the actual size of the file, the major dimension (that is, the first dimension for an array with C layout, and the last dimension for an array with Fortran layout) can be given as -1. Genarray.map_file then determines the major dimension from the size of the file. The file must contain an integral number of sub-arrays as determined by the non-major dimensions, otherwise Failure is raised.

If all dimensions of the big array are given, the file size is matched against the size of the big array. If the file is larger than the big array, only the initial portion of the file is mapped to the big array. If the file is smaller than the big array, the file is automatically grown to the size of the big array. This requires write permissions on fd.
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:
    kind:('a, 'b) kind -> layout:'c layout -> dim: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
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
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 -> pos:int -> len:int -> ('a, 'b, 'c) t
Extract a sub-array of the given one-dimensional big array. See Genarray.sub_left for more details.
  external blit: src:('a, 'b, 'c) t -> dst:('a, 'b, 'c) t -> unit
Copy the first big array to the second big array. See Genarray.blit for more details.
  external fill: ('a, 'b, 'c) t -> 'a -> unit
Fill the given big array with the given value. See Genarray.fill for more details.
  val of_array:
    kind:('a, 'b) kind -> layout:'c layout -> 'a array -> ('a, 'b, 'c) t
Build a one-dimensional big array initialized from the given array.
  val map_file: Unix.file_descr -> kind:('a, 'b) kind -> layout:'c layout ->
                shared:bool -> dim:int -> ('a, 'b, 'c) t
Memory mapping of a file as a one-dimensional big array. See Genarray.map_file 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:
    kind:('a, 'b) kind ->
    layout:'c layout -> dim1:int -> dim2: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
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
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 -> pos:int -> len:int -> ('a, 'b, c_layout) t
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 ->
    pos:int -> len:int -> ('a, 'b, fortran_layout) t
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 -> x: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 -> y: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: src:('a, 'b, 'c) t -> dst:('a, 'b, 'c) t -> unit
Copy the first big array to the second big array. See Genarray.blit for more details.
  external fill: ('a, 'b, 'c) t -> 'a -> unit
Fill the given big array with the given value. See Genarray.fill for more details.
  val of_array:
    kind:('a, 'b) kind -> layout:'c layout -> 'a array array -> ('a, 'b, 'c) t
Build a two-dimensional big array initialized from the given array of arrays.
  val map_file: Unix.file_descr -> kind:('a, 'b) kind -> layout:'c layout ->
                shared:bool -> dim1:int -> dim2:int -> ('a, 'b, 'c) t
Memory mapping of a file as a two-dimensional big array. See Genarray.map_file 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:
    kind:('a, 'b) kind -> layout:'c layout ->
    dim1:int -> dim2:int -> dim3: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
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
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 -> pos:int -> len:int -> ('a, 'b, c_layout) t
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 ->
    pos:int -> len:int -> ('a, 'b, fortran_layout) t
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 -> x:int -> y: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 -> y:int -> z: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 -> x: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 -> z: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 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: src:('a, 'b, 'c) t -> dst:('a, 'b, 'c) t -> unit
Copy the first big array to the second big array. See Genarray.blit for more details.
  external fill: ('a, 'b, 'c) t -> 'a -> unit
Fill the given big array with the given value. See Genarray.fill for more details.
  val of_array:
        kind:('a, 'b) kind -> layout:'c layout ->
        'a array array array -> ('a, 'b, 'c) t
Build a three-dimensional big array initialized from the given array of arrays of arrays.
  val map_file: Unix.file_descr -> kind:('a, 'b) kind -> layout:'c layout ->
             shared:bool -> dim1:int -> dim2:int -> dim3:int -> ('a, 'b, 'c) t
Memory mapping of a file as a three-dimensional big array. See Genarray.map_file for more details.
end
Coercions between generic big arrays and fixed-dimension big arrays
val genarray_of_array1: ('a, 'b, 'c) Array1.t -> ('a, 'b, 'c) Genarray.t
val genarray_of_array2: ('a, 'b, 'c) Array2.t -> ('a, 'b, 'c) Genarray.t
val genarray_of_array3: ('a, 'b, 'c) Array3.t -> ('a, 'b, 'c) Genarray.t
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.
28.2 Big arrays in the Caml-C interface

C stub code that interface C or Fortran code with Caml code, as described in chapter 17, can exploit big arrays as follows.

28.2.1 Include file

The include file <caml/bigarray.h> must be included in the C stub file. It declares the functions, constants and macros discussed below.

28.2.2 Accessing a Caml bigarray from C or Fortran

If v is a Caml value representing a big array, the expression Data_bigarray_val(v) returns a pointer to the data part of the array. This pointer is of type void * and can be cast to the appropriate C type for the array (e.g. double [], char [][10], etc).

Various characteristics of the Caml big array can be consulted from C as follows:

C expression Returns
Bigarray_val(v)->num_dims number of dimensions
Bigarray_val(v)->dim[i[i] i-th dimension
Bigarray_val(v)->flags & BIGARRAY_KIND_MASK kind of array elements

The kind of array elements is one of the following constants:

Constant Element kind
BIGARRAY_FLOAT32 32-bit single-precision floats
BIGARRAY_FLOAT64 64-bit double-precision floats
BIGARRAY_SINT8 8-bit signed integers
BIGARRAY_UINT8 8-bit unsigned integers
BIGARRAY_SINT16 16-bit signed integers
BIGARRAY_UINT16 16-bit unsigned integers
BIGARRAY_INT32 32-bit signed integers
BIGARRAY_INT64 64-bit signed integers
BIGARRAY_CAML_INT 31- or 63-bit signed integers
BIGARRAY_NATIVE_INT 32- or 64-bit (platform-native) integers

The following example shows the passing of a two-dimensional big array to a C function and a Fortran function.
    extern void my_c_function(double * data, int dimx, int dimy);
    extern void my_fortran_function_(double * data, int * dimx, int * dimy);

    value caml_stub(value bigarray)
    {
      int dimx = Bigarray_val(bigarray)->dim[0];
      int dimy = Bigarray_val(bigarray)->dim[1];
      /* C passes scalar parameters by value */
      my_c_function(Data_bigarray_val(bigarray), dimx, dimy);
      /* Fortran passes all parameters by reference */
      my_fortran_function_(Data_bigarray_val(bigarray), &dimx, &dimy);
      return Val_unit;
    }
28.2.3 Wrapping a C or Fortran array as a Caml big array

A pointer p to an already-allocated C or Fortran array can be wrapped and returned to Caml as a big array using the alloc_bigarray or alloc_bigarray_dims functions. The following example illustrates how statically-allocated C and Fortran arrays can be made available to Caml.
    extern long my_c_array[100][200];
    extern float my_fortran_array_[300][400];

    value caml_get_c_array(value unit)
    {
      long dims[2];
      dims[0] = 100; dims[1] = 200;
      return alloc_bigarray(BIGARRAY_NATIVEINT | BIGARRAY_C_LAYOUT,
                            2, my_c_array, dims);
    }

    value caml_get_fortran_array(value unit)
    {
      return alloc_bigarray_dims(BIGARRAY_FLOAT32 | BIGARRAY_FORTRAN_LAYOUT,
                                 2, my_fortran_array_, 300L, 400L);
    }

Previous Contents Next