summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2011-12-21 15:37:54 +0000
committerDamien Doligez <damien.doligez-inria.fr>2011-12-21 15:37:54 +0000
commitcca0035fbb25e0539c85a62b554c5b0abed66062 (patch)
treea3d0f4a8b1eb522c2107d9f920a07857d8080659 /stdlib
parenta85549ccf6b923198293f7335986b9b18417d06b (diff)
continuing to change the name to OCaml
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11922 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/callback.ml2
-rw-r--r--stdlib/callback.mli6
-rw-r--r--stdlib/gc.mli2
-rw-r--r--stdlib/genlex.mli2
-rw-r--r--stdlib/marshal.mli2
-rw-r--r--stdlib/pervasives.mli2
-rw-r--r--stdlib/printf.ml8
-rw-r--r--stdlib/printf.mli8
-rw-r--r--stdlib/queue.ml2
-rw-r--r--stdlib/scanf.ml8
-rw-r--r--stdlib/scanf.mli14
-rw-r--r--stdlib/sys.mli4
12 files changed, 30 insertions, 30 deletions
diff --git a/stdlib/callback.ml b/stdlib/callback.ml
index a8a490c46..5dd789484 100644
--- a/stdlib/callback.ml
+++ b/stdlib/callback.ml
@@ -13,7 +13,7 @@
(* $Id$ *)
-(* Registering Caml values with the C runtime for later callbacks *)
+(* Registering OCaml values with the C runtime for later callbacks *)
external register_named_value : string -> Obj.t -> unit
= "caml_register_named_value"
diff --git a/stdlib/callback.mli b/stdlib/callback.mli
index dfb31617a..ca5f1f073 100644
--- a/stdlib/callback.mli
+++ b/stdlib/callback.mli
@@ -13,11 +13,11 @@
(* $Id$ *)
-(** Registering Caml values with the C runtime.
+(** Registering OCaml values with the C runtime.
- This module allows Caml values to be registered with the C runtime
+ This module allows OCaml values to be registered with the C runtime
under a symbolic name, so that C code can later call back registered
- Caml functions, or raise registered Caml exceptions.
+ OCaml functions, or raise registered OCaml exceptions.
*)
val register : string -> 'a -> unit
diff --git a/stdlib/gc.mli b/stdlib/gc.mli
index ec6cc17c3..b7abae0c1 100644
--- a/stdlib/gc.mli
+++ b/stdlib/gc.mli
@@ -221,7 +221,7 @@ val finalise : ('a -> unit) -> 'a -> unit
- [ let f = fun x -> ... ;; let v = ... in Gc.finalise f v ]
- The [f] function can use all features of O'Caml, including
+ The [f] function can use all features of OCaml, including
assignments that make the value reachable again. It can also
loop forever (in this case, the other
finalisation functions will not be called during the execution of f,
diff --git a/stdlib/genlex.mli b/stdlib/genlex.mli
index d7cecc781..41ce68d0f 100644
--- a/stdlib/genlex.mli
+++ b/stdlib/genlex.mli
@@ -18,7 +18,7 @@
This module implements a simple ``standard'' lexical analyzer, presented
as a function from character streams to token streams. It implements
- roughly the lexical conventions of Caml, but is parameterized by the
+ roughly the lexical conventions of OCaml, but is parameterized by the
set of keywords of your language.
diff --git a/stdlib/marshal.mli b/stdlib/marshal.mli
index 90e6dbffe..86e1ebd19 100644
--- a/stdlib/marshal.mli
+++ b/stdlib/marshal.mli
@@ -27,7 +27,7 @@
making it impossible to check that the data read back possesses the
type expected by the context. In particular, the result type of
the [Marshal.from_*] functions is given as ['a], but this is
- misleading: the returned Caml value does not possess type ['a]
+ misleading: the returned OCaml value does not possess type ['a]
for all ['a]; it has one, unique type which cannot be determined
at compile-type. The programmer should explicitly give the expected
type of the returned value, using the following syntax:
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index d2141cd74..fc3bc60f2 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -229,7 +229,7 @@ external ( asr ) : int -> int -> int = "%asrint"
(** {6 Floating-point arithmetic}
- Caml's floating-point numbers follow the
+ OCaml's floating-point numbers follow the
IEEE 754 standard, using double precision (64 bits) numbers.
Floating-point operations never raise an exception on overflow,
underflow, division by zero, etc. Instead, special IEEE numbers
diff --git a/stdlib/printf.ml b/stdlib/printf.ml
index afca2034e..5508768dc 100644
--- a/stdlib/printf.ml
+++ b/stdlib/printf.ml
@@ -391,7 +391,7 @@ type positional_specification =
with $n$ being the {\em value} of the integer argument defining [*]; we
clearly cannot statically guess the value of this parameter in the general
case. Put it another way: this means type dependency, which is completely
- out of scope of the Caml type algebra. *)
+ out of scope of the OCaml type algebra. *)
let scan_positional_spec fmt got_spec i =
match Sformat.unsafe_get fmt i with
@@ -430,7 +430,7 @@ let get_index spec n =
| Spec_index p -> p
;;
-(* Format a float argument as a valid Caml lexeme. *)
+(* Format a float argument as a valid OCaml lexeme. *)
let format_float_lexeme =
(* To be revised: this procedure should be a unique loop that performs the
@@ -443,7 +443,7 @@ let format_float_lexeme =
let make_valid_float_lexeme s =
(* Check if s is already a valid lexeme:
in this case do nothing,
- otherwise turn s into a valid Caml lexeme. *)
+ otherwise turn s into a valid OCaml lexeme. *)
let l = String.length s in
let rec valid_float_loop i =
if i >= l then s ^ "." else
@@ -670,7 +670,7 @@ let sprintf fmt = ksprintf (fun s -> s) fmt;;
(* Obsolete and deprecated. *)
let kprintf = ksprintf;;
-(* For Caml system internal use only: needed to implement modules [Format]
+(* For OCaml system internal use only: needed to implement modules [Format]
and [Scanf]. *)
module CamlinternalPr = struct
diff --git a/stdlib/printf.mli b/stdlib/printf.mli
index 797a354dd..83366a532 100644
--- a/stdlib/printf.mli
+++ b/stdlib/printf.mli
@@ -42,12 +42,12 @@ val fprintf : out_channel -> ('a, out_channel, unit) format -> 'a
using uppercase letters.
- [o]: convert an integer argument to unsigned octal.
- [s]: insert a string argument.
- - [S]: insert a string argument in Caml syntax (double quotes, escapes).
+ - [S]: insert a string argument in OCaml syntax (double quotes, escapes).
- [c]: insert a character argument.
- - [C]: insert a character argument in Caml syntax (single quotes, escapes).
+ - [C]: insert a character argument in OCaml syntax (single quotes, escapes).
- [f]: convert a floating-point argument to decimal notation,
in the style [dddd.ddd].
- - [F]: convert a floating-point argument to Caml syntax ([dddd.]
+ - [F]: convert a floating-point argument to OCaml syntax ([dddd.]
or [dddd.ddd] or [d.ddd e+-dd]).
- [e] or [E]: convert a floating-point argument to decimal notation,
in the style [d.ddd e+-dd] (mantissa and exponent).
@@ -153,7 +153,7 @@ val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b;;
(**/**)
-(* For Caml system internal use only. Don't call directly. *)
+(* For OCaml system internal use only. Don't call directly. *)
module CamlinternalPr : sig
diff --git a/stdlib/queue.ml b/stdlib/queue.ml
index 605a89204..4e12eb3d2 100644
--- a/stdlib/queue.ml
+++ b/stdlib/queue.ml
@@ -15,7 +15,7 @@
exception Empty
-(* O'Caml currently does not allow the components of a sum type to be
+(* OCaml currently does not allow the components of a sum type to be
mutable. Yet, for optimal space efficiency, we must have cons cells
whose [next] field is mutable. This leads us to define a type of
cyclic lists, so as to eliminate the [Nil] case and the sum
diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml
index ee80f5e7a..11abe0212 100644
--- a/stdlib/scanf.ml
+++ b/stdlib/scanf.ml
@@ -737,7 +737,7 @@ let scan_exp_part width ib =
;;
(* Scan the integer part of a floating point number, (not using the
- Caml lexical convention since the integer part can be empty):
+ OCaml lexical convention since the integer part can be empty):
an optional sign, followed by a possibly empty sequence of decimal
digits (e.g. -.1). *)
let scan_int_part width ib =
@@ -925,7 +925,7 @@ let scan_backslash_char width ib =
bad_input_escape c
;;
-(* Scan a character (a Caml token). *)
+(* Scan a character (an OCaml token). *)
let scan_Char width ib =
let rec find_start width =
@@ -946,7 +946,7 @@ let scan_Char width ib =
find_start width
;;
-(* Scan a delimited string (a Caml token). *)
+(* Scan a delimited string (an OCaml token). *)
let scan_String width ib =
let rec find_start width =
@@ -979,7 +979,7 @@ let scan_String width ib =
find_start width
;;
-(* Scan a boolean (a Caml token). *)
+(* Scan a boolean (an OCaml token). *)
let scan_bool width ib =
if width < 4 then bad_token_length "a boolean" else
let c = Scanning.checked_peek_char ib in
diff --git a/stdlib/scanf.mli b/stdlib/scanf.mli
index 1e8a74484..755649388 100644
--- a/stdlib/scanf.mli
+++ b/stdlib/scanf.mli
@@ -65,16 +65,16 @@
(** {7 Formatted input as a functional feature} *)
-(** The Caml scanning facility is reminiscent of the corresponding C feature.
+(** The OCaml scanning facility is reminiscent of the corresponding C feature.
However, it is also largely different, simpler, and yet more powerful:
the formatted input functions are higher-order functionals and the
parameter passing mechanism is just the regular function application not
the variable assignment based mechanism which is typical for formatted
- input in imperative languages; the Caml format strings also feature
+ input in imperative languages; the OCaml format strings also feature
useful additions to easily define complex tokens; as expected within a
functional programming language, the formatted input functions also
support polymorphism, in particular arbitrary interaction with
- polymorphic user-defined scanners. Furthermore, the Caml formatted input
+ polymorphic user-defined scanners. Furthermore, the OCaml formatted input
facility is fully type-checked at compile time. *)
(** {6 Formatted input channel} *)
@@ -298,18 +298,18 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
Hence, the [%s] conversion always succeeds: it returns an empty
string, if the bounding condition holds when the scan begins.
- [S]: reads a delimited string argument (delimiters and special
- escaped characters follow the lexical conventions of Caml).
+ escaped characters follow the lexical conventions of OCaml).
- [c]: reads a single character. To test the current input character
without reading it, specify a null field width, i.e. use
specification [%0c]. Raise [Invalid_argument], if the field width
specification is greater than 1.
- [C]: reads a single delimited character (delimiters and special
- escaped characters follow the lexical conventions of Caml).
+ escaped characters follow the lexical conventions of OCaml).
- [f], [e], [E], [g], [G]: reads an optionally signed
floating-point number in decimal notation, in the style [dddd.ddd
e/E+-dd].
- [F]: reads a floating point number according to the lexical
- conventions of Caml (hence the decimal point is mandatory if the
+ conventions of OCaml (hence the decimal point is mandatory if the
exponent part is not mentioned).
- [B]: reads a boolean argument ([true] or [false]).
- [b]: reads a boolean argument (for backward compatibility; do not use
@@ -392,7 +392,7 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
nothing to read in the input: in this case, it simply returns [""].
- in addition to the relevant digits, ['_'] characters may appear
- inside numbers (this is reminiscent to the usual Caml lexical
+ inside numbers (this is reminiscent to the usual OCaml lexical
conventions). If stricter scanning is desired, use the range
conversion facility instead of the number conversions.
diff --git a/stdlib/sys.mli b/stdlib/sys.mli
index ee5021dcc..4913bef8e 100644
--- a/stdlib/sys.mli
+++ b/stdlib/sys.mli
@@ -75,13 +75,13 @@ val interactive : bool ref
the interactive toplevel system [ocaml]. *)
val os_type : string
-(** Operating system currently executing the Caml program. One of
+(** Operating system currently executing the OCaml program. One of
- ["Unix"] (for all Unix versions, including Linux and Mac OS X),
- ["Win32"] (for MS-Windows, OCaml compiled with MSVC++ or Mingw),
- ["Cygwin"] (for MS-Windows, OCaml compiled with Cygwin). *)
val word_size : int
-(** Size of one word on the machine currently executing the Caml
+(** Size of one word on the machine currently executing the OCaml
program, in bits: 32 or 64. *)
val max_string_length : int