Add Bigarray 'init' functions (#9779)

Add Bigarray init functions.
master
Jeremy Yallop 2020-08-05 13:26:10 +01:00 committed by GitHub
parent 93fe89e150
commit 395a47eed9
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
5 changed files with 336 additions and 3 deletions

View File

@ -133,6 +133,10 @@ Working version
- #9781: add injectivity annotations to parameterized abstract types
(Jeremy Yallop, review by Nicolás Ojeda Bär)
* #9765: add init functions to Bigarray.
(Jeremy Yallop, review by Gabriel Scherer, Nicolás Ojeda Bär, and
Xavier Leroy)
* #9554: add primitive __FUNCTION__ that returns the name of the current method
or function, including any enclosing module or class.
(Nicolás Ojeda Bär, Stephen Dolan, review by Stephen Dolan)

View File

@ -99,6 +99,27 @@ module Genarray = struct
= "caml_ba_get_generic"
external set: ('a, 'b, 'c) t -> int array -> 'a -> unit
= "caml_ba_set_generic"
let rec cloop arr idx f col max =
if col = Array.length idx then set arr idx (f idx)
else for j = 0 to pred max.(col) do
idx.(col) <- j;
cloop arr idx f (succ col) max
done
let rec floop arr idx f col max =
if col < 0 then set arr idx (f idx)
else for j = 1 to max.(col) do
idx.(col) <- j;
floop arr idx f (pred col) max
done
let init (type t) kind (layout : t layout) dims f =
let arr = create kind layout dims in
match Array.length dims, layout with
| 0, _ -> arr
| dlen, C_layout -> cloop arr (Array.make dlen 0) f 0 dims; arr
| dlen, Fortran_layout -> floop arr (Array.make dlen 1) f (pred dlen) dims;
arr
external num_dims: ('a, 'b, 'c) t -> int = "caml_ba_num_dims"
external nth_dim: ('a, 'b, 'c) t -> int -> int = "caml_ba_dim"
let dims a =
@ -152,6 +173,7 @@ module Array0 = struct
let a = create kind layout in
set a v;
a
let init = of_value
end
module Array1 = struct
@ -180,6 +202,15 @@ module Array1 = struct
| Fortran_layout -> (Genarray.slice_right a [|n|]: (_, _, t) Genarray.t)
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "caml_ba_blit"
external fill: ('a, 'b, 'c) t -> 'a -> unit = "caml_ba_fill"
let c_init arr dim f =
for i = 0 to pred dim do unsafe_set arr i (f i) done
let fortran_init arr dim f =
for i = 1 to dim do unsafe_set arr i (f i) done
let init (type t) kind (layout : t layout) dim f =
let arr = create kind layout dim in
match layout with
| C_layout -> c_init arr dim f; arr
| Fortran_layout -> fortran_init arr dim f; arr
let of_array (type t) kind (layout: t layout) data =
let ba = create kind layout (Array.length data) in
let ofs =
@ -221,6 +252,23 @@ module Array2 = struct
let slice_right a n = Genarray.slice_right a [|n|]
external blit: ('a, 'b, 'c) t -> ('a, 'b, 'c) t -> unit = "caml_ba_blit"
external fill: ('a, 'b, 'c) t -> 'a -> unit = "caml_ba_fill"
let c_init arr dim1 dim2 f =
for i = 0 to pred dim1 do
for j = 0 to pred dim2 do
unsafe_set arr i j (f i j)
done
done
let fortran_init arr dim1 dim2 f =
for j = 1 to dim2 do
for i = 1 to dim1 do
unsafe_set arr i j (f i j)
done
done
let init (type t) kind (layout : t layout) dim1 dim2 f =
let arr = create kind layout dim1 dim2 in
match layout with
| C_layout -> c_init arr dim1 dim2 f; arr
| Fortran_layout -> fortran_init arr dim1 dim2 f; arr
let of_array (type t) kind (layout: t layout) data =
let dim1 = Array.length data in
let dim2 = if dim1 = 0 then 0 else Array.length data.(0) in
@ -275,6 +323,27 @@ 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 = "caml_ba_blit"
external fill: ('a, 'b, 'c) t -> 'a -> unit = "caml_ba_fill"
let c_init arr dim1 dim2 dim3 f =
for i = 0 to pred dim1 do
for j = 0 to pred dim2 do
for k = 0 to pred dim3 do
unsafe_set arr i j k (f i j k)
done
done
done
let fortran_init arr dim1 dim2 dim3 f =
for k = 1 to dim3 do
for j = 1 to dim2 do
for i = 1 to dim1 do
unsafe_set arr i j k (f i j k)
done
done
done
let init (type t) kind (layout : t layout) dim1 dim2 dim3 f =
let arr = create kind layout dim1 dim2 dim3 in
match layout with
| C_layout -> c_init arr dim1 dim2 dim3 f; arr
| Fortran_layout -> fortran_init arr dim1 dim2 dim3 f; arr
let of_array (type t) kind (layout: t layout) data =
let dim1 = Array.length data in
let dim2 = if dim1 = 0 then 0 else Array.length data.(0) in

View File

@ -298,6 +298,34 @@ module Genarray :
is not in the range 0 to 16 inclusive, or if one of the dimensions
is negative. *)
val init: ('a, 'b) kind -> 'c layout -> int array -> (int array -> 'a) ->
('a, 'b, 'c) t
(** [Genarray.init kind layout dimensions f] returns a new Bigarray [b]
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 Bigarray in each dimension.
The length of [dimensions] determines the number of dimensions
of the Bigarray.
Each element [Genarray.get b i] is initialized to the result of [f i].
In other words, [Genarray.init kind layout dimensions f] tabulates
the results of [f] applied to the indices of a new Bigarray whose
layout is described by [kind], [layout] and [dimensions]. The index
array [i] may be shared and mutated between calls to f.
For instance, [Genarray.init int c_layout [|2; 1; 3|]
(Array.fold_left (+) 0)] returns a fresh Bigarray of integers, in C
layout, having three dimensions (2, 1, 3, respectively), with the
element values 0, 1, 2, 1, 2, 3.
[Genarray.init] raises [Invalid_argument] if the number of dimensions
is not in the range 0 to 16 inclusive, or if one of the dimensions
is negative.
@since 4.12.0 *)
external num_dims: ('a, 'b, 'c) t -> int = "caml_ba_num_dims"
(** Return the number of dimensions of the given Bigarray. *)
@ -486,6 +514,12 @@ module Array0 : sig
[kind] and [layout] determine the array element kind and the array
layout as described for {!Genarray.create}. *)
val init: ('a, 'b) kind -> 'c layout -> 'a -> ('a, 'b, 'c) t
(** [Array0.init kind layout v] behaves like [Array0.create kind layout]
except that the element is additionally initialized to the value [v].
@since 4.12.0 *)
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
(** Return the kind of the given Bigarray. *)
@ -545,6 +579,22 @@ module Array1 : sig
determine the array element kind and the array layout
as described for {!Genarray.create}. *)
val init: ('a, 'b) kind -> 'c layout -> int -> (int -> 'a) ->
('a, 'b, 'c) t
(** [Array1.init kind layout dim f] returns a new Bigarray [b]
of one dimension, whose size is [dim]. [kind] and [layout]
determine the array element kind and the array layout
as described for {!Genarray.create}.
Each element [Array1.get b i] of the array is initialized to the
result of [f i].
In other words, [Array1.init kind layout dimensions f] tabulates
the results of [f] applied to the indices of a new Bigarray whose
layout is described by [kind], [layout] and [dim].
@since 4.12.0 *)
external dim: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the size (dimension) of the given one-dimensional
Bigarray. *)
@ -638,11 +688,28 @@ module Array2 :
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
two dimensions, 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 {!Bigarray.Genarray.create}. *)
val init: ('a, 'b) kind -> 'c layout -> int -> int ->
(int -> int -> 'a) -> ('a, 'b, 'c) t
(** [Array2.init kind layout dim1 dim2 f] returns a new Bigarray [b]
of two dimensions, whose size is [dim2] 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 {!Bigarray.Genarray.create}.
Each element [Array2.get b i j] of the array is initialized to
the result of [f i j].
In other words, [Array2.init kind layout dim1 dim2 f] tabulates
the results of [f] applied to the indices of a new Bigarray whose
layout is described by [kind], [layout], [dim1] and [dim2].
@since 4.12.0 *)
external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the first dimension of the given two-dimensional Bigarray. *)
@ -754,11 +821,28 @@ module Array3 :
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,
three dimensions, 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 {!Bigarray.Genarray.create}. *)
val init: ('a, 'b) kind -> 'c layout -> int -> int -> int ->
(int -> int -> int -> 'a) -> ('a, 'b, 'c) t
(** [Array3.init kind layout dim1 dim2 dim3 f] returns a new Bigarray [b]
of three dimensions, 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 {!Bigarray.Genarray.create}.
Each element [Array3.get b i j k] of the array is initialized to
the result of [f i j k].
In other words, [Array3.init kind layout dim1 dim2 dim3 f] tabulates
the results of [f] applied to the indices of a new Bigarray whose
layout is described by [kind], [layout], [dim1], [dim2] and [dim3].
@since 4.12.0 *)
external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the first dimension of the given three-dimensional Bigarray. *)

View File

@ -28,6 +28,12 @@ let test test_number answer correct_answer =
printf " %d..." test_number
end
let with_trace f =
let events = ref [] in
let trace e = events := e :: !events in
let v = f trace in
(v, List.rev !events)
(* One-dimensional arrays *)
(* flambda can cause some of these values not to be reclaimed by the Gc, which
@ -489,6 +495,26 @@ let tests () =
test 7 (Array1.slice a 2) (Array0.of_value int fortran_layout 4);
test 8 (Array1.slice a 3) (Array0.of_value int fortran_layout 3);
testing_function "init";
let check1 arr graph = List.for_all (fun (i, fi) -> arr.{i} = fi) graph in
let ba, log = with_trace @@ fun trace ->
Array1.init int c_layout 5 (fun x -> trace (x,x); x) in
test 1 log [0,0;
1,1;
2,2;
3,3;
4,4];
test 2 true (check1 ba log);
let ba, log = with_trace @@ fun trace ->
Array1.init int fortran_layout 5 (fun x -> trace (x,x); x) in
test 3 log [1,1;
2,2;
3,3;
4,4;
5,5];
test 4 true (check1 ba log);
(* Bi-dimensional arrays *)
@ -651,6 +677,25 @@ let tests () =
test 8 (Array2.slice_right a 3)
(from_list_fortran int [1003;2003;3003;4003;5003]);
testing_function "init";
let check2 arr graph = List.for_all (fun ((i,j), fij) -> arr.{i,j} = fij) graph in
let ba, log = with_trace @@ fun trace ->
Array2.init int c_layout 4 2
(fun x y -> let v = 10*x + y in trace ((x,y),v); v) in
test 1 log [(0,0), 00; (0,1), 01;
(1,0), 10; (1,1), 11;
(2,0), 20; (2,1), 21;
(3,0), 30; (3,1), 31];
test 2 true (check2 ba log);
let ba, log = with_trace @@ fun trace ->
Array2.init int fortran_layout 4 2
(fun x y -> let v = 10*x + y in trace ((x,y),v); v) in
test 3 log [(1,1), 11; (2,1), 21; (3,1), 31; (4,1), 41;
(1,2), 12; (2,2), 22; (3,2), 32; (4,2), 42];
test 4 true (check2 ba log);
(* Tri-dimensional arrays *)
print_newline();
@ -778,10 +823,125 @@ let tests () =
test 6 (Array3.slice_right_1 a 1 2) (from_list_fortran int [112;212;312]);
test 7 (Array3.slice_right_1 a 3 1) (from_list_fortran int [131;231;331]);
testing_function "init";
let check3 arr graph =
List.for_all (fun ((i,j,k), fijk) -> arr.{i,j,k} = fijk) graph in
let ba, log = with_trace @@ fun trace ->
Array3.init int c_layout 4 2 3
(fun x y z -> let v = 100*x + 10*y + z in trace ((x,y,z),v); v) in
test 1 log [(0,0,0), 000; (0,0,1), 001; (0,0,2), 002;
(0,1,0), 010; (0,1,1), 011; (0,1,2), 012;
(1,0,0), 100; (1,0,1), 101; (1,0,2), 102;
(1,1,0), 110; (1,1,1), 111; (1,1,2), 112;
(2,0,0), 200; (2,0,1), 201; (2,0,2), 202;
(2,1,0), 210; (2,1,1), 211; (2,1,2), 212;
(3,0,0), 300; (3,0,1), 301; (3,0,2), 302;
(3,1,0), 310; (3,1,1), 311; (3,1,2), 312];
test 2 true (check3 ba log);
let ba, log = with_trace @@ fun trace ->
Array3.init int fortran_layout 4 2 3
(fun x y z -> let v = 100*x + 10*y + z in trace ((x,y,z), v); v) in
test 3 log [(1,1,1), 111; (2,1,1), 211; (3,1,1), 311; (4,1,1), 411;
(1,2,1), 121; (2,2,1), 221; (3,2,1), 321; (4,2,1), 421;
(1,1,2), 112; (2,1,2), 212; (3,1,2), 312; (4,1,2), 412;
(1,2,2), 122; (2,2,2), 222; (3,2,2), 322; (4,2,2), 422;
(1,1,3), 113; (2,1,3), 213; (3,1,3), 313; (4,1,3), 413;
(1,2,3), 123; (2,2,3), 223; (3,2,3), 323; (4,2,3), 423];
test 4 true (check3 ba log);
testing_function "size_in_bytes_general";
let a = Genarray.create int c_layout [|2;2;2;2;2|] in
test 1 (Genarray.size_in_bytes a) (32 * (kind_size_in_bytes int));
testing_function "init";
let checkgen arr graph =
List.for_all (fun (i, fi) -> Genarray.get arr i = fi) graph in
let ba, log = with_trace @@ fun trace ->
Genarray.init int c_layout [|4; 2; 3; 2|]
(fun i -> let v = 1000*i.(0) + 100*i.(1) + 10*i.(2) + i.(3) in
trace (Array.copy i, v); v) in
test 1 log [[|0;0;0;0|], 0000; [|0;0;0;1|], 0001;
[|0;0;1;0|], 0010; [|0;0;1;1|], 0011;
[|0;0;2;0|], 0020; [|0;0;2;1|], 0021;
[|0;1;0;0|], 0100; [|0;1;0;1|], 0101;
[|0;1;1;0|], 0110; [|0;1;1;1|], 0111;
[|0;1;2;0|], 0120; [|0;1;2;1|], 0121;
[|1;0;0;0|], 1000; [|1;0;0;1|], 1001;
[|1;0;1;0|], 1010; [|1;0;1;1|], 1011;
[|1;0;2;0|], 1020; [|1;0;2;1|], 1021;
[|1;1;0;0|], 1100; [|1;1;0;1|], 1101;
[|1;1;1;0|], 1110; [|1;1;1;1|], 1111;
[|1;1;2;0|], 1120; [|1;1;2;1|], 1121;
[|2;0;0;0|], 2000; [|2;0;0;1|], 2001;
[|2;0;1;0|], 2010; [|2;0;1;1|], 2011;
[|2;0;2;0|], 2020; [|2;0;2;1|], 2021;
[|2;1;0;0|], 2100; [|2;1;0;1|], 2101;
[|2;1;1;0|], 2110; [|2;1;1;1|], 2111;
[|2;1;2;0|], 2120; [|2;1;2;1|], 2121;
[|3;0;0;0|], 3000; [|3;0;0;1|], 3001;
[|3;0;1;0|], 3010; [|3;0;1;1|], 3011;
[|3;0;2;0|], 3020; [|3;0;2;1|], 3021;
[|3;1;0;0|], 3100; [|3;1;0;1|], 3101;
[|3;1;1;0|], 3110; [|3;1;1;1|], 3111;
[|3;1;2;0|], 3120; [|3;1;2;1|], 3121;];
test 2 true (checkgen ba log);
let ba, log = with_trace @@ fun trace ->
Genarray.init int fortran_layout [|4; 2; 3; 2|]
(fun i -> let v = 1000*i.(0) + 100*i.(1) + 10*i.(2) + i.(3) in
trace (Array.copy i, v); v) in
test 3 log [[|1;1;1;1|], 1111; [|2;1;1;1|], 2111;
[|3;1;1;1|], 3111; [|4;1;1;1|], 4111;
[|1;2;1;1|], 1211; [|2;2;1;1|], 2211;
[|3;2;1;1|], 3211; [|4;2;1;1|], 4211;
[|1;1;2;1|], 1121; [|2;1;2;1|], 2121;
[|3;1;2;1|], 3121; [|4;1;2;1|], 4121;
[|1;2;2;1|], 1221; [|2;2;2;1|], 2221;
[|3;2;2;1|], 3221; [|4;2;2;1|], 4221;
[|1;1;3;1|], 1131; [|2;1;3;1|], 2131;
[|3;1;3;1|], 3131; [|4;1;3;1|], 4131;
[|1;2;3;1|], 1231; [|2;2;3;1|], 2231;
[|3;2;3;1|], 3231; [|4;2;3;1|], 4231;
[|1;1;1;2|], 1112; [|2;1;1;2|], 2112;
[|3;1;1;2|], 3112; [|4;1;1;2|], 4112;
[|1;2;1;2|], 1212; [|2;2;1;2|], 2212;
[|3;2;1;2|], 3212; [|4;2;1;2|], 4212;
[|1;1;2;2|], 1122; [|2;1;2;2|], 2122;
[|3;1;2;2|], 3122; [|4;1;2;2|], 4122;
[|1;2;2;2|], 1222; [|2;2;2;2|], 2222;
[|3;2;2;2|], 3222; [|4;2;2;2|], 4222;
[|1;1;3;2|], 1132; [|2;1;3;2|], 2132;
[|3;1;3;2|], 3132; [|4;1;3;2|], 4132;
[|1;2;3;2|], 1232; [|2;2;3;2|], 2232;
[|3;2;3;2|], 3232; [|4;2;3;2|], 4232];
test 4 true (checkgen ba log);
(* Zero-dimensional arrays *)
testing_function "------ Array0 --------";
testing_function "create/set/get";
@ -886,6 +1046,12 @@ let tests () =
{im=0.5;re= -2.0}, {im=0.5;re= -2.0};
{im=3.1415;re=1.2345678}, {im=3.1415;re=1.2345678}]);
testing_function "init";
let ba = Array0.init int c_layout 10 in
test 1 ba (Array0.of_value int c_layout 10);
let ba = Array0.init int fortran_layout 10 in
test 2 ba (Array0.of_value int fortran_layout 10);
(* Kind size *)
testing_function "kind_size_in_bytes";
@ -945,7 +1111,7 @@ let tests () =
test 9 (Genarray.get c [|0|]) 3;
test 10 (Genarray.get (Genarray.slice_left c [|0|]) [||]) 3;
(* I/O *)
(* I/O *)
print_newline();
testing_function "------ I/O --------";

View File

@ -21,6 +21,8 @@ blit, fill
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12...
slice
1... 2... 3... 6... 7... 8...
init
1... 2... 3... 4...
------ Array2 --------
@ -38,6 +40,8 @@ sub
1... 2...
slice
1... 2... 3... 4... 5... 6... 7... 8...
init
1... 2... 3... 4...
------ Array3 --------
@ -53,12 +57,18 @@ size_in_bytes_three
1...
slice1
1... 2... 3... 4... 5... 6... 7...
init
1... 2... 3... 4...
size_in_bytes_general
1...
init
1... 2... 3... 4...
------ Array0 --------
create/set/get
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12...
init
1... 2...
kind_size_in_bytes
1... 2... 3... 4... 5... 6... 7... 8... 9... 10... 11... 12... 13...