summaryrefslogtreecommitdiffstats
path: root/otherlibs
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs')
-rw-r--r--otherlibs/bigarray/bigarray.ml12
-rw-r--r--otherlibs/bigarray/bigarray.mli12
-rw-r--r--otherlibs/bigarray/bigarray_stubs.c15
3 files changed, 27 insertions, 12 deletions
diff --git a/otherlibs/bigarray/bigarray.ml b/otherlibs/bigarray/bigarray.ml
index 26bdaac52..4cadfd917 100644
--- a/otherlibs/bigarray/bigarray.ml
+++ b/otherlibs/bigarray/bigarray.ml
@@ -107,7 +107,7 @@ module Array1 = struct
external set: ('a, 'b, 'c) t -> int -> 'a -> unit = "%caml_ba_set_1"
external unsafe_get: ('a, 'b, 'c) t -> int -> 'a = "%caml_ba_unsafe_ref_1"
external unsafe_set: ('a, 'b, 'c) t -> int -> 'a -> unit = "%caml_ba_unsafe_set_1"
- let dim a = Genarray.nth_dim a 0
+ external dim: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
external layout: ('a, 'b, 'c) t -> 'c layout = "caml_ba_layout"
external sub: ('a, 'b, 'c) t -> int -> int -> ('a, 'b, 'c) t = "caml_ba_sub"
@@ -130,8 +130,8 @@ module Array2 = struct
external set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit = "%caml_ba_set_2"
external unsafe_get: ('a, 'b, 'c) t -> int -> int -> 'a = "%caml_ba_unsafe_ref_2"
external unsafe_set: ('a, 'b, 'c) t -> int -> int -> 'a -> unit = "%caml_ba_unsafe_set_2"
- let dim1 a = Genarray.nth_dim a 0
- let dim2 a = Genarray.nth_dim a 1
+ external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
+ external dim2: ('a, 'b, 'c) t -> int = "%caml_ba_dim_2"
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
external layout: ('a, 'b, 'c) t -> 'c layout = "caml_ba_layout"
external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t
@@ -170,9 +170,9 @@ module Array3 = struct
= "%caml_ba_set_3"
external unsafe_get: ('a, 'b, 'c) t -> int -> int -> int -> 'a = "%caml_ba_unsafe_ref_3"
external unsafe_set: ('a, 'b, 'c) t -> int -> int -> int -> 'a -> unit = "%caml_ba_unsafe_set_3"
- let dim1 a = Genarray.nth_dim a 0
- let dim2 a = Genarray.nth_dim a 1
- let dim3 a = Genarray.nth_dim a 2
+ external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
+ external dim2: ('a, 'b, 'c) t -> int = "%caml_ba_dim_2"
+ external dim3: ('a, 'b, 'c) t -> int = "%caml_ba_dim_3"
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
external layout: ('a, 'b, 'c) t -> 'c layout = "caml_ba_layout"
external sub_left: ('a, 'b, c_layout) t -> int -> int -> ('a, 'b, c_layout) t
diff --git a/otherlibs/bigarray/bigarray.mli b/otherlibs/bigarray/bigarray.mli
index 515079fca..a14a5e4fc 100644
--- a/otherlibs/bigarray/bigarray.mli
+++ b/otherlibs/bigarray/bigarray.mli
@@ -446,7 +446,7 @@ module Array1 : sig
determine the array element kind and the array layout
as described for [Genarray.create]. *)
- val dim: ('a, 'b, 'c) t -> int
+ external dim: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the size (dimension) of the given one-dimensional
big array. *)
@@ -526,10 +526,10 @@ module Array2 :
determine the array element kind and the array layout
as described for {!Bigarray.Genarray.create}. *)
- val dim1: ('a, 'b, 'c) t -> int
+ external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the first dimension of the given two-dimensional big array. *)
- val dim2: ('a, 'b, 'c) t -> int
+ external dim2: ('a, 'b, 'c) t -> int = "%caml_ba_dim_2"
(** Return the second dimension of the given two-dimensional big array. *)
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
@@ -629,13 +629,13 @@ module Array3 :
[kind] and [layout] determine the array element kind and
the array layout as described for {!Bigarray.Genarray.create}. *)
- val dim1: ('a, 'b, 'c) t -> int
+ external dim1: ('a, 'b, 'c) t -> int = "%caml_ba_dim_1"
(** Return the first dimension of the given three-dimensional big array. *)
- val dim2: ('a, 'b, 'c) t -> int
+ external dim2: ('a, 'b, 'c) t -> int = "%caml_ba_dim_2"
(** Return the second dimension of the given three-dimensional big array. *)
- val dim3: ('a, 'b, 'c) t -> int
+ external dim3: ('a, 'b, 'c) t -> int = "%caml_ba_dim_3"
(** Return the third dimension of the given three-dimensional big array. *)
external kind: ('a, 'b, 'c) t -> ('a, 'b) kind = "caml_ba_kind"
diff --git a/otherlibs/bigarray/bigarray_stubs.c b/otherlibs/bigarray/bigarray_stubs.c
index 567a72deb..4af0bfde6 100644
--- a/otherlibs/bigarray/bigarray_stubs.c
+++ b/otherlibs/bigarray/bigarray_stubs.c
@@ -475,6 +475,21 @@ CAMLprim value caml_ba_dim(value vb, value vn)
return Val_long(b->dim[n]);
}
+CAMLprim value caml_ba_dim_1(value vb)
+{
+ return caml_ba_dim(vb, Val_int(0));
+}
+
+CAMLprim value caml_ba_dim_2(value vb)
+{
+ return caml_ba_dim(vb, Val_int(1));
+}
+
+CAMLprim value caml_ba_dim_3(value vb)
+{
+ return caml_ba_dim(vb, Val_int(2));
+}
+
/* Return the kind of a big array */
CAMLprim value caml_ba_kind(value vb)