summaryrefslogtreecommitdiffstats
path: root/otherlibs/bigarray/bigarray.ml
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/bigarray/bigarray.ml')
-rw-r--r--otherlibs/bigarray/bigarray.ml101
1 files changed, 64 insertions, 37 deletions
diff --git a/otherlibs/bigarray/bigarray.ml b/otherlibs/bigarray/bigarray.ml
index 0aea1f4cb..960c97241 100644
--- a/otherlibs/bigarray/bigarray.ml
+++ b/otherlibs/bigarray/bigarray.ml
@@ -17,48 +17,63 @@ external init : unit -> unit = "caml_ba_init"
let _ = init()
-type ('a, 'b) kind = int
+type float32_elt = Float32_elt
+type float64_elt = Float64_elt
+type int8_signed_elt = Int8_signed_elt
+type int8_unsigned_elt = Int8_unsigned_elt
+type int16_signed_elt = Int16_signed_elt
+type int16_unsigned_elt = Int16_unsigned_elt
+type int32_elt = Int32_elt
+type int64_elt = Int64_elt
+type int_elt = Int_elt
+type nativeint_elt = Nativeint_elt
+type complex32_elt = Complex32_elt
+type complex64_elt = Complex64_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
-type float32_elt
-type float64_elt
-type complex32_elt
-type complex64_elt
+type ('a, 'b) kind =
+ Float32 : (float, float32_elt) kind
+ | Float64 : (float, float64_elt) kind
+ | Int8_signed : (int, int8_signed_elt) kind
+ | Int8_unsigned : (int, int8_unsigned_elt) kind
+ | Int16_signed : (int, int16_signed_elt) kind
+ | Int16_unsigned : (int, int16_unsigned_elt) kind
+ | Int32 : (int32, int32_elt) kind
+ | Int64 : (int64, int64_elt) kind
+ | Int : (int, int_elt) kind
+ | Nativeint : (nativeint, nativeint_elt) kind
+ | Complex32 : (Complex.t, complex32_elt) kind
+ | Complex64 : (Complex.t, complex64_elt) kind
+ | Char : (char, int8_unsigned_elt) kind
(* Keep those constants in sync with the caml_ba_kind enumeration
in bigarray.h *)
-let float32 = 0
-let float64 = 1
-let int8_signed = 2
-let int8_unsigned = 3
-let int16_signed = 4
-let int16_unsigned = 5
-let int32 = 6
-let int64 = 7
-let int = 8
-let nativeint = 9
-let char = int8_unsigned
-let complex32 = 10
-let complex64 = 11
+let float32 = Float32
+let float64 = Float64
+let int8_signed = Int8_signed
+let int8_unsigned = Int8_unsigned
+let int16_signed = Int16_signed
+let int16_unsigned = Int16_unsigned
+let int32 = Int32
+let int64 = Int64
+let int = Int
+let nativeint = Nativeint
+let complex32 = Complex32
+let complex64 = Complex64
+let char = Char
-type 'a layout = int
+type c_layout = C_layout_typ
+type fortran_layout = Fortran_layout_typ
-type c_layout
-type fortran_layout
+type 'a layout =
+ C_layout: c_layout layout
+ | Fortran_layout: fortran_layout layout
(* Keep those constants in sync with the caml_ba_layout enumeration
in bigarray.h *)
-let c_layout = 0
-let fortran_layout = 0x100
+let c_layout = C_layout
+let fortran_layout = Fortran_layout
module Genarray = struct
type ('a, 'b, 'c) t
@@ -114,9 +129,13 @@ module Array1 = struct
external sub: ('a, 'b, 'c) t -> int -> int -> ('a, 'b, 'c) t = "caml_ba_sub"
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 of_array kind layout data =
+ let of_array (type t) kind (layout: t layout) data =
let ba = create kind layout (Array.length data) in
- let ofs = if layout = c_layout then 0 else 1 in
+ let ofs =
+ match layout with
+ C_layout -> 0
+ | Fortran_layout -> 1
+ in
for i = 0 to Array.length data - 1 do unsafe_set ba (i + ofs) data.(i) done;
ba
let map_file fd ?pos kind layout shared dim =
@@ -146,11 +165,15 @@ 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 of_array kind layout data =
+ 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
let ba = create kind layout dim1 dim2 in
- let ofs = if layout = c_layout then 0 else 1 in
+ let ofs =
+ match layout with
+ C_layout -> 0
+ | Fortran_layout -> 1
+ in
for i = 0 to dim1 - 1 do
let row = data.(i) in
if Array.length row <> dim2 then
@@ -191,12 +214,16 @@ 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 of_array kind layout data =
+ 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
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 layout = c_layout then 0 else 1 in
+ let ofs =
+ match layout with
+ C_layout -> 0
+ | Fortran_layout -> 1
+ in
for i = 0 to dim1 - 1 do
let row = data.(i) in
if Array.length row <> dim2 then