summaryrefslogtreecommitdiffstats
path: root/otherlibs/bigarray/bigarray.mli
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2012-02-10 16:15:24 +0000
committerDamien Doligez <damien.doligez-inria.fr>2012-02-10 16:15:24 +0000
commite7f5b858c2aee1fc6caeefc3d7c80ca696be2897 (patch)
treef6e4f76927ce2a4f604fcc0596f1b6505cc39fe3 /otherlibs/bigarray/bigarray.mli
parentd7cbf2a01a390f2fe6bedef1292bb5aa55d8b6f7 (diff)
More renaming to OCaml
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12149 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/bigarray/bigarray.mli')
-rw-r--r--otherlibs/bigarray/bigarray.mli34
1 files changed, 17 insertions, 17 deletions
diff --git a/otherlibs/bigarray/bigarray.mli b/otherlibs/bigarray/bigarray.mli
index ed60976f7..8b260bf79 100644
--- a/otherlibs/bigarray/bigarray.mli
+++ b/otherlibs/bigarray/bigarray.mli
@@ -18,13 +18,13 @@
This module implements multi-dimensional arrays of integers and
floating-point numbers, thereafter referred to as ``big arrays''.
The implementation allows efficient sharing of large numerical
- arrays between Caml code and C or Fortran numerical libraries.
+ arrays between OCaml code and C or Fortran numerical libraries.
Concerning the naming conventions, users of this module are encouraged
to do [open Bigarray] in their source, then refer to array types and
operations via short dot notation, e.g. [Array1.t] or [Array2.sub].
- Big arrays support all the Caml ad-hoc polymorphic operations:
+ Big arrays support all the OCaml ad-hoc polymorphic operations:
- comparisons ([=], [<>], [<=], etc, as well as {!Pervasives.compare});
- hashing (module [Hash]);
- and structured input-output ({!Pervasives.output_value}
@@ -47,7 +47,7 @@
({!Bigarray.int8_signed_elt} or {!Bigarray.int8_unsigned_elt}),
- 16-bit integers (signed or unsigned)
({!Bigarray.int16_signed_elt} or {!Bigarray.int16_unsigned_elt}),
-- Caml integers (signed, 31 bits on 32-bit architectures,
+- OCaml integers (signed, 31 bits on 32-bit architectures,
63 bits on 64-bit architectures) ({!Bigarray.int_elt}),
- 32-bit signed integer ({!Bigarray.int32_elt}),
- 64-bit signed integers ({!Bigarray.int64_elt}),
@@ -72,20 +72,20 @@ type int64_elt
type nativeint_elt
type ('a, 'b) kind
-(** To each element kind is associated a Caml type, which is
- the type of Caml values that can be stored in the big array
+(** To each element kind is associated an OCaml type, which is
+ the type of OCaml values that can be stored in the big array
or read back from it. This type is not necessarily the same
as the type of the array elements proper: for instance,
a big array whose elements are of kind [float32_elt] contains
32-bit single precision floats, but reading or writing one of
- its elements from Caml uses the Caml type [float], which is
+ 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
- of a Caml type ['a] for values read or written in the big array,
+ 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 Caml types with
+ [kind] list all possible associations of OCaml types with
element kinds: *)
val float32 : (float, float32_elt) kind
@@ -127,12 +127,12 @@ 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 complex kinds
- [complex32_elt], [complex64_elt] are accessed with the Caml type
+ 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
- integer kinds are accessed using the smallest Caml integer
+ 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 Caml-integer
+ [int] for 8- and 16-bit integer bigarrays, as well as OCaml-integer
bigarrays; [int32] for 32-bit integer bigarrays; [int64]
for 64-bit integer bigarrays; and [nativeint] for
platform-native integer bigarrays. Finally, big arrays of
@@ -195,7 +195,7 @@ module Genarray :
The three type parameters to [Genarray.t] identify the array element
kind and layout, as follows:
- - the first parameter, ['a], is the Caml type for accessing array
+ - the first parameter, ['a], is the OCaml type for accessing array
elements ([float], [int], [int32], [int64], [nativeint]);
- the second parameter, ['b], is the actual kind of array elements
([float32_elt], [float64_elt], [int8_signed_elt], [int8_unsigned_elt],
@@ -206,7 +206,7 @@ module Genarray :
For instance, [(float, float32_elt, fortran_layout) Genarray.t]
is the type of generic big arrays containing 32-bit floats
in Fortran layout; reads and writes in this array use the
- Caml type [float]. *)
+ OCaml type [float]. *)
external create: ('a, 'b) kind -> 'c layout -> int array -> ('a, 'b, 'c) t
= "caml_ba_create"
@@ -440,7 +440,7 @@ module Genarray :
module Array1 : sig
type ('a, 'b, 'c) t
(** The type of one-dimensional big arrays whose elements have
- Caml type ['a], representation kind ['b], and memory layout ['c]. *)
+ OCaml type ['a], representation kind ['b], and memory layout ['c]. *)
val create: ('a, 'b) kind -> 'c layout -> int -> ('a, 'b, 'c) t
(** [Array1.create kind layout dim] returns a new bigarray of
@@ -519,7 +519,7 @@ module Array2 :
sig
type ('a, 'b, 'c) t
(** The type of two-dimensional big arrays whose elements have
- Caml type ['a], representation kind ['b], and memory layout ['c]. *)
+ OCaml type ['a], representation kind ['b], and memory layout ['c]. *)
val create: ('a, 'b) kind -> 'c layout -> int -> int -> ('a, 'b, 'c) t
(** [Array2.create kind layout dim1 dim2] returns a new bigarray of
@@ -622,7 +622,7 @@ module Array3 :
sig
type ('a, 'b, 'c) t
(** The type of three-dimensional big arrays whose elements have
- Caml type ['a], representation kind ['b], and memory layout ['c]. *)
+ OCaml type ['a], representation kind ['b], and memory layout ['c]. *)
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