summaryrefslogtreecommitdiffstats
path: root/otherlibs/bigarray/bigarray.mli
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-01-09 16:24:32 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-01-09 16:24:32 +0000
commita2f40d86765e7697321f22427997060a443d0548 (patch)
treec21042dc881b89f14d9990578598a74f3cd682e5 /otherlibs/bigarray/bigarray.mli
parent844052b22ea80f7cb5f0b9c20c89469423679902 (diff)
make bigarray.mli's documentation consistent with the new GADT interface
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14392 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/bigarray/bigarray.mli')
-rw-r--r--otherlibs/bigarray/bigarray.mli51
1 files changed, 33 insertions, 18 deletions
diff --git a/otherlibs/bigarray/bigarray.mli b/otherlibs/bigarray/bigarray.mli
index f25a6d41d..058c25904 100644
--- a/otherlibs/bigarray/bigarray.mli
+++ b/otherlibs/bigarray/bigarray.mli
@@ -52,8 +52,9 @@
- platform-native signed integers (32 bits on 32-bit architectures,
64 bits on 64-bit architectures) ({!Bigarray.nativeint_elt}).
- Each element kind is represented at the type level by one
- of the abstract types defined below.
+ Each element kind is represented at the type level by one of the
+ [*_elt] types defined below (defined with a single constructor instead
+ of abstract types for technical injectivity reasons).
*)
type float32_elt = Float32_elt
@@ -92,12 +93,28 @@ type ('a, 'b) kind =
its elements from OCaml uses the OCaml type [float], which is
64-bit double precision floats.
- The abstract type [('a, 'b) kind] captures this association
+ The GADT type [('a, 'b) kind] captures this association
of an OCaml 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 OCaml types with
- element kinds: *)
+ of the big array. Its constructors list all possible associations
+ of OCaml types with element kinds, and are re-exported below for
+ backward-compatibility reasons.
+
+ Using a generalized algebraic datatype (GADT) here allows to write
+ well-typed polymorphic functions whose return type depend on the
+ argument type, such as:
+
+{[
+ let zero : type a b. (a, b) kind -> a = function
+ | Float32 -> 0.0 | Complex32 -> Complex.zero
+ | Float64 -> 0.0 | Complex64 -> Complex.zero
+ | Int8_signed -> 0 | Int8_unsigned -> 0
+ | Int16_signed -> 0 | Int16_unsigned -> 0
+ | Int32 -> 0l | Int64 -> 0L
+ | Int -> 0 | Nativeint -> 0n
+ | Char -> '\000'
+]}
+*)
val float32 : (float, float32_elt) kind
(** See {!Bigarray.char}. *)
@@ -140,7 +157,7 @@ val char : (char, int8_unsigned_elt) kind
big arrays of kind [float32_elt] and [float64_elt] are
accessed using the OCaml type [float]. Big arrays of complex kinds
[complex32_elt], [complex64_elt] are accessed with the OCaml type
- {!Complex.t}. Big arrays of
+ {!Complex.t}. Big arrays of
integer kinds are accessed using the smallest OCaml integer
type large enough to represent the array elements:
[int] for 8- and 16-bit integer bigarrays, as well as OCaml-integer
@@ -177,22 +194,20 @@ type fortran_layout = Fortran_layout_typ
and [(x+1, y)] are adjacent in memory.
Each layout style is identified at the type level by the
- abstract types {!Bigarray.c_layout} and [fortran_layout] respectively. *)
-
-type 'a layout =
- C_layout: c_layout layout
- | Fortran_layout: fortran_layout layout
-(** The type ['a layout] represents one of the two supported
- memory layouts: C-style if ['a] is {!Bigarray.c_layout}, Fortran-style
- if ['a] is {!Bigarray.fortran_layout}. *)
-
+ phantom types {!Bigarray.c_layout} and {!Bigarray.fortran_layout}
+ respectively. *)
(** {7 Supported layouts}
- The abstract values [c_layout] and [fortran_layout] represent
- the two supported layouts at the level of values.
+ The GADT type ['a layout] represents one of the two supported
+ memory layouts: C-style or Fortran-style. Its constructors are
+ re-exported as values below for backward-compatibility reasons.
*)
+type 'a layout =
+ C_layout: c_layout layout
+ | Fortran_layout: fortran_layout layout
+
val c_layout : c_layout layout
val fortran_layout : fortran_layout layout