Typo dans bigarray.h.

Ajout des operations of_array.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2863 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2000-02-25 09:05:03 +00:00
parent 93fa509b14
commit 38f64c3ce6
3 changed files with 57 additions and 3 deletions

View File

@ -65,7 +65,7 @@ struct caml_bigarray {
extern value alloc_bigarray(int flags, int num_dims, void * data, long * dim);
extern value alloc_bigarray_dims(int flags, int num_dims, void * data,
/*dimensions, with type long */);
... /*dimensions, with type long */);
#endif

View File

@ -40,6 +40,7 @@ let int32 = 6
let int64 = 7
let int = 8
let nativeint = 9
let char = int8_unsigned
type 'a layout = int
@ -88,6 +89,11 @@ module Array1 = struct
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"
let of_array kind layout data =
let ba = create kind layout (Array.length data) in
let ofs = if (Obj.magic layout : 'a layout) = c_layout then 0 else 1 in
for i = 0 to Array.length data - 1 do set ba (i + ofs) data.(i) done;
ba
end
module Array2 = struct
@ -104,6 +110,20 @@ module Array2 = struct
let slice_right a n = Genarray.slice_right a [|n|]
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
let of_array kind layout data =
let dim1 = Array.length data in
let dim2 = if dim1 = 0 then 0 else Array.length data.(0) in
let ba = create kind layout dim1 dim2 in
let ofs = if (Obj.magic layout : 'a layout) = c_layout then 0 else 1 in
for i = 0 to dim1 - 1 do
let row = data.(i) in
if Array.length row <> dim2 then
invalid_arg("Bigarray.Array2.of_array: non-rectangular data");
for j = 0 to dim2 - 1 do
set ba (i + ofs) (j + ofs) row.(j)
done
done;
ba
end
module Array3 = struct
@ -123,6 +143,26 @@ module Array3 = struct
let slice_right_2 a n = Genarray.slice_right a [|n|]
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "bigarray_blit"
external fill: ('a, 'b, 'c) t -> 'a -> unit = "bigarray_fill"
let of_array kind layout data =
let dim1 = Array.length data in
let dim2 = if dim1 = 0 then 0 else Array.length data.(0) in
let dim3 = if dim2 = 0 then 0 else Array.length data.(0).(0) in
let ba = create kind layout dim1 dim2 dim3 in
let ofs = if (Obj.magic layout : 'a layout) = c_layout then 0 else 1 in
for i = 0 to dim1 - 1 do
let row = data.(i) in
if Array.length row <> dim2 then
invalid_arg("Bigarray.Array3.of_array: non-cubic data");
for j = 0 to dim2 - 1 do
let col = row.(j) in
if Array.length col <> dim3 then
invalid_arg("Bigarray.Array3.of_array: non-cubic data");
for k = 0 to dim3 - 1 do
set ba (i + ofs) (j + ofs) (k + ofs) col.(j)
done
done
done;
ba
end
external genarray_of_array1: ('a, 'b, 'c) Array1.t -> ('a, 'b, 'c) Genarray.t = "%identity"

View File

@ -83,6 +83,7 @@ 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
@ -91,7 +92,10 @@ val nativeint: (nativeint, nativeint_elt) kind
[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. *)
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 *)
@ -352,6 +356,9 @@ module Array1: sig
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. *)
val of_array: ('a, 'b) kind -> 'c layout -> 'a array -> ('a, 'b, 'c) t
(* Build a one-dimensional big array initialized from the
given array. *)
end
(*** Two-dimensional arrays *)
@ -422,6 +429,9 @@ module Array2: sig
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. *)
val of_array: ('a, 'b) kind -> 'c layout -> 'a array array -> ('a, 'b, 'c) t
(* Build a two-dimensional big array initialized from the
given array of arrays. *)
end
(*** Three-dimensional arrays *)
@ -503,7 +513,7 @@ module Array3: sig
('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 first coordinate of the slice
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. *)
@ -514,6 +524,10 @@ module Array3: sig
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. *)
val of_array:
('a, 'b) kind -> '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. *)
end
(*** Coercions between generic big arrays and fixed-dimension big arrays *)