Fixing typos in various files (#2246)

Note: Typos found with https://github.com/codespell-project/codespell

Here is the (semi-manual) command used to get (and correct) the typos:

$ codespell -i 3 -w --skip=".png,.gif,./ocaml/boot,./ocaml/.git,./ocaml/manual/styles,./ocaml/manual/manual/htmlman" -L minimise,instal,contructor,"o'caml",cristal,pres,clos,cmo,uint,iff,te,objext,nto,nd,mut,upto,larg,exten,leage,mthod,delte,tim,atleast,langage,hten,iwth,mke,contant,succint,methids,eles,valu,clas,modul,que,classe,missings,froms,defaut,correspondance,differents,configury,reachs,cas,approche,normale,dur,millon,amin,oje,transfert
master
Fourchaux 2019-02-13 14:04:56 +01:00 committed by Armaël Guéneau
parent 07794568eb
commit 1946594bd7
69 changed files with 120 additions and 120 deletions

View File

@ -8,7 +8,7 @@
# See the MAPPING AUTHORS section of 'man git-shortlog' for more details.
# Such a remapping may be useful in particular for tracking authorship
# of commits erroneously made under an obscure alias or email adress.
# of commits erroneously made under an obscure alias or email address.
# (Some Name <some@name.com>, pour ne pas le citer)

42
Changes
View File

@ -135,7 +135,7 @@ OCaml 4.08.0
- GPR#1957: Add Stack.{top_opt,pop_opt} and Queue.{peek_opt,take_opt}.
(Vladimir Keleshev, review by Nicolás Ojeda Bär and Gabriel Scherer)
- GPR#1959: Add Format.dprintf, a printing function which ouputs a closure
- GPR#1959: Add Format.dprintf, a printing function which outputs a closure
usable with %t.
(Gabriel Radanne, request by Armaël Guéneau,
review by Florian Angeletti and Gabriel Scherer)
@ -1005,11 +1005,11 @@ OCaml 4.07.0 (10 July 2018)
- GPR#1627: Reduce cmx sizes by sharing variable names (Flambda only).
(Fuyong Quah, Leo White, review by Xavier Clerc)
- GPR#1665: reduce the size of cmx files in classic mode by droping the
- GPR#1665: reduce the size of cmx files in classic mode by dropping the
bodies of functions that will not be inlined.
(Fuyong Quah, review by Leo White and Pierre Chambart)
- GPR#1666: reduce the size of cmx files in classic mode by droping the
- GPR#1666: reduce the size of cmx files in classic mode by dropping the
bodies of functions that cannot be reached from the module block.
(Fuyong Quah, review by Leo White and Pierre Chambart)
@ -1825,7 +1825,7 @@ OCaml 4.06.0 (3 Nov 2017):
* MPR#7478, GPR#1037: ocamldoc, do not use as a module preamble documentation
comments that occur after the first module element. This change may break
existing documenation. In particular, module preambles must now come before
existing documentation. In particular, module preambles must now come before
any `open` statement.
(Florian Angeletti, review by David Allsopp and report by Daniel Bünzli)
@ -3471,7 +3471,7 @@ OCaml 4.03.0 (25 Apr 2016):
this is the semantics they wanted).
(Alain Frisch, request by Martin Jambon and John Whitington)
- PR#6920: fix debug informations around uses of %apply or %revapply
- PR#6920: fix debug information around uses of %apply or %revapply
(Jérémie Dimino, report by Daniel Bünzli)
- PR#6939: Segfault with improper use of let-rec
@ -4067,7 +4067,7 @@ OCaml 4.03.0 (25 Apr 2016):
- PR#6980: Assert failure from polymorphic variants and existentials
(Jacques Garrigue, report by Leo White)
- PR#6981: Ctype.Unify(_) with associated functor arg refering to previous one
- PR#6981: Ctype.Unify(_) with associated functor arg referring to previous one
(Jacques Garrigue, report by Nicholas Labich)
- PR#6982: unexpected type error when packing a module alias
@ -4183,7 +4183,7 @@ OCaml 4.03.0 (25 Apr 2016):
(Jacques Garrigue, report by Stephen Dolan)
- PR#7324: OCaml 4.03.0 type checker dies with an assert failure when
given some cyclic recusive module expression
given some cyclic recursive module expression
(Jacques Garrigue, report by jmcarthur)
- PR#7368: Manual major GC fails to compact the heap
@ -4256,7 +4256,7 @@ OCaml 4.03.0 (25 Apr 2016):
- PR#6367, GPR#25: introduce Asttypes.arg_label to encode labelled arguments
(Frédéric Bour and Jacques Garrigue)
- PR#6452, GPR#140: add internal suport for custom printing formats
- PR#6452, GPR#140: add internal support for custom printing formats
(Jérémie Dimino)
- PR#6611: remove the option wrapper on optional arguments in the syntax tree
@ -4279,7 +4279,7 @@ OCaml 4.03.0 (25 Apr 2016):
(Simon Cruanes)
* PR#6816: reject integer and float literals directly followed by an identifier.
This was prevously read as two separate tokens.
This was previously read as two separate tokens.
[let abc = 1 in (+) 123abc] was accepted and is now rejected.
(Hugo Heuzard)
@ -4618,7 +4618,7 @@ Bug fixes:
(Stephen Dolan, Mark Shinwell)
Feature wishes:
- PR#6452, GPR#140: add internal suport for custom printing formats
- PR#6452, GPR#140: add internal support for custom printing formats
(Jérémie Dimino)
- PR#6641: add -g, -ocamlcflags, -ocamloptflags options to ocamlmklib
(whitequark)
@ -4885,7 +4885,7 @@ Bug fixes:
(Jacques Garrigue and John Whitington)
- PR#6174: OCaml compiler loops on an example using GADTs (-rectypes case)
(Jacques Garrigue and Grégoire Henry, report by Chantal Keller)
- PR#6175: open! was not suppored by camlp4
- PR#6175: open! was not supported by camlp4
(Hongbo Zhang)
- PR#6184: ocamlbuild: `ocamlfind ocamldep` does not support -predicate
(Jacques-Pascal Deplaix)
@ -5216,7 +5216,7 @@ Bug fixes:
(Damien Doligez, report by Markus Mottl)
* PR#5580: missed opportunities for constant propagation
(Xavier Leroy and John Carr)
- PR#5611: avoid clashes betwen .cmo files and output files during linking
- PR#5611: avoid clashes between .cmo files and output files during linking
(Wojciech Meyer)
- PR#5662: typo in md5.c
(Olivier Andrieu)
@ -5230,7 +5230,7 @@ Bug fixes:
(Fabrice Le Fessant)
- PR#5697: better location for warnings on statement expressions
(Dan Bensen)
- PR#5698: remove harcoded limit of 200000 labels in emitaux.ml
- PR#5698: remove hardcoded limit of 200000 labels in emitaux.ml
(Fabrice Le Fessant, report by Marcin Sawicki)
- PR#5702: bytecomp/bytelibrarian lib_sharedobjs was defined but never used
(Hongbo Zhang, Fabrice Le Fessant)
@ -5303,7 +5303,7 @@ Bug fixes:
- PR#5824: Generate more efficient code for immediate right shifts.
(Pierre Chambart, review by Xavier Leroy)
- PR#5825: Add a toplevel primitive to use source file wrapped with the
coresponding module
corresponding module
(Grégoire Henry, Wojciech Meyer, caml-list discussion)
- PR#5833: README.win32 can leave the wrong flexlink in the path
(Damien Doligez, report by William Smith)
@ -5323,7 +5323,7 @@ Bug fixes:
(Alain Frisch, Gabriel Scherer, report by Julien Moutinho)
- PR#5877: multiple "open" can become expensive in memory
(Fabrice Le Fessant and Alain Frisch)
- PR#5880: 'Genlex.make_lexer' documention mentions the wrong exception
- PR#5880: 'Genlex.make_lexer' documentation mentions the wrong exception
(Xavier Clerc, report by Virgile Prevosto)
- PR#5885: Incorrect rule for compiling C stubs when shared libraries are not
supported.
@ -5572,7 +5572,7 @@ Native-code compiler:
OCamldoc:
- PR#5645: ocamldoc doesn't handle module/type substitution in signatures
- PR#5544: improve HTML output (less formatting in html code)
- PR#5522: allow refering to record fields and variant constructors
- PR#5522: allow referring to record fields and variant constructors
- fix PR#5419 (error message in french)
- fix PR#5535 (no cross ref to class after dump+load)
* Use first class modules for custom generators, to be able to
@ -6470,7 +6470,7 @@ Standard library:
and prints nothing (useful to print conditionally).
- Scanf:
new function format_from_string to convert a string to a format string;
new %r conversion to accomodate user defined scanners.
new %r conversion to accommodate user defined scanners.
- Filename: improved Win32 implementation of Filename.quote.
- List: List.nth now tail-recursive.
- Sys: added Sys.is_directory. Some functions (e.g. Sys.command) that
@ -7490,7 +7490,7 @@ Both compilers:
- Option -warn-error to turn warnings into errors.
- Option -where to print the location of the standard library directory.
- Assertions are now type-checked even if the -noassert option is given,
thus -noassert can no longe change the types of modules.
thus -noassert can no longer change the types of modules.
Bytecode compiler and bytecode interpreter:
- Print stack backtrace when a program aborts due to an uncaught exception
@ -7508,7 +7508,7 @@ Native-code compiler:
- Removed spurious dependency on the -lcurses library.
Toplevel environment:
- Revised handling of top-level value definitions, allows reclaimation
- Revised handling of top-level value definitions, allows reclamation
of definitions that are shadowed by later definitions with the same names.
(E.g. "let x = <big list>;; let x = 1;;" allows <big list> to be reclaimed.)
- Revised the tracing facility so that for standard library functions,
@ -8274,7 +8274,7 @@ Objective Caml 1.03 (29 Oct 1996):
exp() or log() cause a domain error; fixed bug with
String.length "literal";
- Sparc, Mips, HPPA: removed marking of scanned stack frames
(benefits do not outweight cost).
(benefits do not outweigh cost).
* Standard library:
- Arg.parse now prints documentation for command-line options;
@ -8434,7 +8434,7 @@ marshaling to/from strings.
* Thread library: much better support for I/O and blocking system calls.
* Graphics library: faster reclaimation of unused pixmaps.
* Graphics library: faster reclamation of unused pixmaps.
* Unix library: new functions {set,clear}_nonblock, {set,clear}_close_on_exec,
{set,get}itimer, inet_addr_any, {get,set}sockopt.

View File

@ -24,7 +24,7 @@ type op_class =
| Op_other (* anything else that does not allocate nor store in memory *)
class cse_generic : object
(* The following methods can be overriden to handle processor-specific
(* The following methods can be overridden to handle processor-specific
operations. *)
method class_of_operation: Mach.operation -> op_class

View File

@ -86,7 +86,7 @@ val record_global_approx_toplevel: unit -> unit
clambda-only *)
val set_export_info: Export_info.t -> unit
(* Record the informations of the unit being compiled
(* Record the information of the unit being compiled
flambda-only *)
val approx_env: unit -> Export_info.t
(* Returns all the information loaded from external compilation units

View File

@ -614,7 +614,7 @@ m4_popdef([AS_MESSAGE_LOG_FD])])])# _LT_GENERATED_FILE_INIT
# LT_OUTPUT
# ---------
# This macro allows early generation of the libtool script (before
# AC_OUTPUT is called), incase it is used in configure for compilation
# AC_OUTPUT is called), in case it is used in configure for compilation
# tests.
AC_DEFUN([LT_OUTPUT],
[: ${CONFIG_LT=./config.lt}
@ -651,7 +651,7 @@ configured by $[0], generated by m4_PACKAGE_STRING.
Copyright (C) 2011 Free Software Foundation, Inc.
This config.lt script is free software; the Free Software Foundation
gives unlimited permision to copy, distribute and modify it."
gives unlimited permission to copy, distribute and modify it."
while test 0 != $[#]
do
@ -2866,7 +2866,7 @@ linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*)
# before this can be enabled.
hardcode_into_libs=yes
# Ideally, we could use ldconfig to report *all* directores which are
# Ideally, we could use ldconfig to report *all* directories which are
# searched for libraries, however this is still not possible. Aside from not
# being certain /sbin/ldconfig is available, command
# 'ldconfig -N -X -v | grep ^/' on 64bit Fedora does not report /usr/lib64,

View File

@ -546,7 +546,7 @@ func_require_term_colors ()
# _G_HAVE_PLUSEQ_OP
# Can be empty, in which case the shell is probed, "yes" if += is
# useable or anything else if it does not work.
# usable or anything else if it does not work.
test -z "$_G_HAVE_PLUSEQ_OP" \
&& (eval 'x=a; x+=" b"; test "a b" = "$x"') 2>/dev/null \
&& _G_HAVE_PLUSEQ_OP=yes
@ -696,7 +696,7 @@ eval 'func_dirname ()
# to NONDIR_REPLACEMENT.
# value returned in "$func_dirname_result"
# basename: Compute filename of FILE.
# value retuned in "$func_basename_result"
# value returned in "$func_basename_result"
# For efficiency, we do not delegate to the functions above but instead
# duplicate the functionality here.
eval 'func_dirname_and_basename ()
@ -854,7 +854,7 @@ func_mkdir_p ()
# While some portion of DIR does not yet exist...
while test ! -d "$_G_directory_path"; do
# ...make a list in topmost first order. Use a colon delimited
# list incase some portion of path contains whitespace.
# list in case some portion of path contains whitespace.
_G_dir_list=$_G_directory_path:$_G_dir_list
# If the last portion added has no slash in it, the list is done
@ -1630,7 +1630,7 @@ func_run_hooks ()
case " $hookable_fns " in
*" $1 "*) ;;
*) func_fatal_error "'$1' does not support hook funcions.n" ;;
*) func_fatal_error "'$1' does not support hook functions.n" ;;
esac
eval _G_hook_fns=\$$1_hooks; shift
@ -5961,7 +5961,7 @@ EOF
{
/* however, if there is an option in the LTWRAPPER_OPTION_PREFIX
namespace, but it is not one of the ones we know about and
have already dealt with, above (inluding dump-script), then
have already dealt with, above (including dump-script), then
report an error. Otherwise, targets might begin to believe
they are allowed to use options in the LTWRAPPER_OPTION_PREFIX
namespace. The first time any user complains about this, we'll

View File

@ -108,6 +108,6 @@ type instruction =
let immed_min = -0x40000000
and immed_max = 0x3FFFFFFF
(* Actually the abstract machine accomodates -0x80000000 to 0x7FFFFFFF,
(* Actually the abstract machine accommodates -0x80000000 to 0x7FFFFFFF,
but these numbers overflow the OCaml type int if the compiler runs on
a 32-bit processor. *)

View File

@ -362,7 +362,7 @@ exception Not_simple
let max_raw = 32
let make_key e =
let count = ref 0 (* Used for controling size *)
let count = ref 0 (* Used for controlling size *)
and make_key = Ident.make_key_generator () in
(* make_key is used for normalizing let-bound variables *)
let rec tr_rec env e =

View File

@ -882,7 +882,7 @@ let rebuild_nexts arg nexts k =
in actions (cf. simplify_cases).
Additionally, if the match argument is a variable, matchings whose
first column is made of variables only are splitted further
first column is made of variables only are split further
(cf. precompile_var).
*)
@ -1067,7 +1067,7 @@ and precompile_var args cls def k = match args with
| [] -> assert false
| _::((Lvar v as av,_) as arg)::rargs ->
begin match cls with
| [_] -> (* as splitted as it can *)
| [_] -> (* as split as it can *)
dont_precompile_var args cls def k
| _ ->
(* Precompile *)
@ -2523,7 +2523,7 @@ let rec event_branch repr lam =
compile_list (for compiling switch results) catch Unused
comp_match_handlers (for compiling splitted matches)
comp_match_handlers (for compiling split matches)
may reraise Unused

View File

@ -134,7 +134,7 @@ end
Adaptation of
R.L. Berstein
``Producing good code for the case statement''
Sofware Practice and Experience, 15(10) (1985)
Software Practice and Experience, 15(10) (1985)
and
D.L. Spuler
``Two-Way Comparison Search Trees, a Generalisation of Binary Search Trees

6
configure vendored
View File

@ -2974,7 +2974,7 @@ case $host in #(
syslib='-l$(1)' ;;
esac
# Environment variables that are taken into acocunt
# Environment variables that are taken into account
@ -11129,7 +11129,7 @@ fi
# before this can be enabled.
hardcode_into_libs=yes
# Ideally, we could use ldconfig to report *all* directores which are
# Ideally, we could use ldconfig to report *all* directories which are
# searched for libraries, however this is still not possible. Aside from not
# being certain /sbin/ldconfig is available, command
# 'ldconfig -N -X -v | grep ^/' on 64bit Fedora does not report /usr/lib64,
@ -13270,7 +13270,7 @@ $as_echo "$ac_cv_c_bigendian" >&6; }
;; #(
*)
as_fn_error $? "could not determine endiannes." "$LINENO" 5 ;;
as_fn_error $? "could not determine endianness." "$LINENO" 5 ;;
esac

View File

@ -192,7 +192,7 @@ AS_CASE([$host],
outputexe='-o $(EMPTY)'
syslib='-l$(1)'])
# Environment variables that are taken into acocunt
# Environment variables that are taken into account
AC_ARG_VAR([AS], [which assembler to use])
AC_ARG_VAR([ASPP], [which assembler (with preprocessor) to use])
@ -677,7 +677,7 @@ AC_MSG_NOTICE([Target is a $bits bits architecture])
AC_C_BIGENDIAN(
[AC_DEFINE([ARCH_BIG_ENDIAN], [1])],
[],
[AC_MSG_ERROR([could not determine endiannes.])],
[AC_MSG_ERROR([could not determine endianness.])],
[AC_MSG_ERROR([unable to handle universal endianness])]
)

View File

@ -1043,7 +1043,7 @@ With no argument, reset the search path." };
"exit the debugger." };
{ instr_name = "shell"; instr_prio = false;
instr_action = instr_shell; instr_repeat = true; instr_help =
"Execute a given COMMAND thru the system shell." };
"Execute a given COMMAND through the system shell." };
{ instr_name = "environment"; instr_prio = false;
instr_action = instr_env; instr_repeat = false; instr_help =
"environment variable to give to program being debugged when it is started." };

View File

@ -257,7 +257,7 @@ let duplicate_current_checkpoint () =
(* --- about this exception. *)
let interrupted = ref false
(* Informations about last breakpoint encountered *)
(* Information about last breakpoint encountered *)
let last_breakpoint = ref None
(* Ensure we stop on an event. *)

View File

@ -8,7 +8,7 @@ Prerequisites
- A LaTeX installation.
- The HeVeA LaTeX-to-HTML convertor (available in OPAM):
- The HeVeA LaTeX-to-HTML converter (available in OPAM):
<http://hevea.inria.fr/>
Note that you must make sure `hevea.sty` is installed into TeX properly. Your

View File

@ -478,7 +478,7 @@ floating-point numbers.}
\entree{"Abstract_tag"}{A block representing an abstract datatype.}
\entree{"Custom_tag"}{A block representing an abstract datatype
with user-defined finalization, comparison, hashing,
serialization and deserialization functions atttached.}
serialization and deserialization functions attached.}
\end{tableau}
\subsection{Pointers outside the heap}
@ -1366,7 +1366,7 @@ arguments as their non-"_exn" counterparts, but catch escaping
exceptions and return them to the C code. The return value \var{v} of the
"caml_callback*_exn" functions must be tested with the macro
"Is_exception_result("\var{v}")". If the macro returns ``false'', no
exception occured, and \var{v} is the value returned by the OCaml
exception occurred, and \var{v} is the value returned by the OCaml
function. If "Is_exception_result("\var{v}")" returns ``true'',
an exception escaped, and its value (the exception descriptor) can be
recovered using "Extract_exception("\var{v}")".

View File

@ -118,7 +118,7 @@ In regular expressions that follow this declaration, the identifier
The names of the entry points must be valid identifiers for OCaml
values (starting with a lowercase letter).
Similarily, the arguments \texttt{\var{arg$_1$}\ldots{}
Similarly, the arguments \texttt{\var{arg$_1$}\ldots{}
\var{arg$_n$}} must be valid identifiers for OCaml.
Each entry point becomes an
OCaml function that takes $n+1$ arguments,

View File

@ -541,7 +541,7 @@ class type my_class_type =
(** The comment for variable x. *)
val mutable x : int
(** The commend for method m. *)
(** The comment for method m. *)
method m : int -> int
end
@ -637,7 +637,7 @@ class type my_class_type =
object
(** The comment for the instance variable x. *)
val mutable x : int
(** The commend for method m. *)
(** The comment for method m. *)
method m : int -> int
end

View File

@ -274,7 +274,7 @@ class-body: ['(' pattern [':' typexpr] ')'] { class-field }
The expression
@'object' class-body 'end'@ denotes
a class body. This is the prototype for an object : it lists the
instance variables and methods of an objet of this class.
instance variables and methods of an object of this class.
A class body is a class value: it is not evaluated at once. Rather,
its components are evaluated each time an object is created.

View File

@ -1550,7 +1550,7 @@ Some attributes are understood by the type-checker:
(such as an expression, or a type expression)
in which case its scope is limited to that item.
Note that it is not well-defined which scope is used for a specific
warning. This is implementation dependant and can change between versions.
warning. This is implementation dependent and can change between versions.
Some warnings are even completely outside the control of ``ocaml.warning''
(for instance, warnings 1, 2, 14, 29 and 50).
@ -2347,7 +2347,7 @@ to the user when the alert is triggered (i.e. when the marked
component is referenced).
The "ocaml.alert" or "alert" attribute serves two purposes: (i) to
mark component with an alert to be triggerred when the component is
mark component with an alert to be triggered when the component is
referenced, and (ii) to control which alert names are enabled. In the
first form, the attribute takes an identifier possibly
followed by a message. Here is an example of a value declaration marked

View File

@ -723,7 +723,7 @@ parameter.
let sum (lst : _ #iterator) = lst#fold (fun x y -> x+y) 0;;
\end{caml_example}
Of course the constraint may also be an explicit method type.
Only occurences of quantified variables are required.
Only occurrences of quantified variables are required.
\begin{caml_example}{toplevel}
let sum lst =
(lst : < fold : 'a. ('a -> _ -> 'a) -> 'a -> 'a; .. >)#fold (+) 0;;

View File

@ -525,7 +525,7 @@ let rec simplify_project_var env r ~(project_var : Flambda.project_var)
The rewriting occurs in an environment filled with:
* The approximation of the free variables
* An explicitely unknown approximation for function parameters,
* An explicitly unknown approximation for function parameters,
except for those where it is known to be safe: those present in the
[specialised_args] set.
* An approximation for the closures in the set. It contains the code of

View File

@ -191,7 +191,7 @@ type state = {
(* List of functions that still need to be copied to the new set
of closures *)
new_funs : Flambda.function_declaration Variable.Map.t;
(* The function declerations for the new set of closures *)
(* The function declarations for the new set of closures *)
new_free_vars_with_old_projections : Flambda.specialised_to Variable.Map.t;
(* The free variables for the new set of closures, but the projection
fields still point to old free variables. *)

View File

@ -679,7 +679,7 @@ let equal_floats f1 f2 =
The approximation for [f 1] and [f 2] could both contain the
description of [g]. But if [f] where inlined, a new [g] would
be created in each branch, leading to incompatible description.
And we must never make the descrition for a function less
And we must never make the description for a function less
precise that it used to be: its information are needed for
rewriting [Project_var] and [Project_closure] constructions
in [Flambdainline.loop]

View File

@ -171,10 +171,10 @@ and function_declaration = private {
(* CR-soon mshinwell: add support for the approximations of the results, so we
can do all of the tricky higher-order cases. *)
(* when [is_classic_mode] is [false], functions in [function_declarations]
are guranteed to have function bodies (ie:
are guaranteed to have function bodies (ie:
[function_declaration.function_body] will be of the [Some] variant).
When it [is_classic_mode] is [true], however, no gurantees about the
When it [is_classic_mode] is [true], however, no guarantees about the
function_bodies are given.
*)
and value_set_of_closures = private {

View File

@ -80,7 +80,7 @@ Release 3.08.0:
- mod: one section per to module in latex output + improve latex output
- mod: odoc_latex: use buffers instead of string concatenation
- add: new ocamldoc man page, thanks to Samuel Mimram
- fix: useless parenthesis around agruments of arguments of a type constructor in
- fix: useless parentheses around arguments of arguments of a type constructor in
type definitions, and aournd arguments of exceptions in exception definitions.
- fix: blank lines in verbatim, latex, code pre, code and ele ref modes
are now accepted
@ -110,7 +110,7 @@ Release 3.08.0:
- fix: bug preventing to get the code in a .mli
- fix: missing spaces after carriage return in types (Odoc_misc.string_of_type_expr)
- fixes: some bugs in the text parser
( ]} meaning end of code and somehting else instead of end of precode)
( ]} meaning end of code and something else instead of end of precode)
- add: in Odoc_info: text_of_string, text_string_of_text, info_of_string
- fix: better output of titles in html (use more the style)
- add: -intro option to use a file content as ocamldoc comment to use as
@ -144,7 +144,7 @@ Release 3.05 :
.ml and .mli when merging
- option -werr becomes -warn-error
- possibility to define and reference section labels
Exemple:
Example:
(** {2:mysectionlabel My title bla bla bla} *)
in module Foo

View File

@ -108,9 +108,9 @@ let no_header = " Suppress header in generated documentation\n\t\t"^latex_texi_o
let no_trailer = " Suppress trailer in generated documentation\n\t\t"^latex_texi_only
let separate_files = " Generate one file per toplevel module "^latex_only
let latex_title ref_titles =
"n,style Associate {n } to the given sectionning style\n"^
"n,style Associate {n } to the given sectioning style\n"^
"\t\t(e.g. 'section') in the latex output "^latex_only^"\n"^
"\t\tDefault sectionning is:\n\t\t"^
"\t\tDefault sectioning is:\n\t\t"^
(String.concat "\n\t\t"
(List.map (fun (n,t) -> Printf.sprintf " %d -> %s" n t) !ref_titles))
@ -204,9 +204,9 @@ let merge_all = ('A', "merge all")
let no_index = " Do not build index for Info files "^texi_only
let esc_8bits = " Escape accentuated characters in Info files "^texi_only
let texinfo_title r=
"n,style Associate {n } to the given sectionning style\n"^
"n,style Associate {n } to the given sectioning style\n"^
"\t\t(e.g. 'section') in the texInfo output "^texi_only^"\n"^
"\t\tDefault sectionning is:\n\t\t"^
"\t\tDefault sectioning is:\n\t\t"^
(String.concat "\n\t\t"
(List.map (fun (n,(t,h)) ->
Printf.sprintf " %d -> %s, %s " n t h) !r))

View File

@ -45,11 +45,11 @@ ocamltest needs to know two things:
1. Where the sources of the OCaml compiler to test are located.
This is determined while OCaml is built. The default location can be
overriden by defining the OCAMLSRCDIR environment variable.
overridden by defining the OCAMLSRCDIR environment variable.
2. Which directory to use to build tests. The default value for this is
"ocamltest" under Filename.get_temp_dir_name(). This value can be
overriden by defining the OCAMLTESTDIR environemnt variable.
overridden by defining the OCAMLTESTDIR environment variable.
# Running tests
@ -122,7 +122,7 @@ find tests -name 'Makefile'
In other words, the directories that still need to be migrated are
the subdirectories of testsuite/tests that still contain a Makefile.
Once you knwo which directory you want to migrate, say foo, here is
Once you know which directory you want to migrate, say foo, here is
what you should do:
Read foo/Makefile to see how many tests the directory contains and how
@ -146,7 +146,7 @@ comment that looks like this:
*)
In particular, if the test's main file is foo.ml and the test uses
modules m1.ml and m2.ml, the test block will look like ths:
modules m1.ml and m2.ml, the test block will look like this:
(* TEST
modules = "m1.ml m2.ml"

View File

@ -148,7 +148,7 @@ static void update_environment(array local_env)
}
/*
This function should retunr an exitcode that can itslef be returned
This function should return an exitcode that can itself be returned
to its father through the exit system call.
So it returns 0 to report success and 1 to report an error
@ -231,7 +231,7 @@ child_failed:
* Its termination status as returned by wait(2)
* A string giving a prefix for the core file name.
(the file will be called prefix.pid.core but may come from a
diffferent process)
different process)
* Returns the code to return if this is the child process
*/
static int handle_process_termination(

View File

@ -23,7 +23,7 @@ type 'a located = {
type environment_statement =
| Assignment of bool * string located * string located (* variable = value *)
| Append of string located * string located
| Include of string located (* include named environemnt *)
| Include of string located (* include named environment *)
type tsl_item =
| Environment_statement of environment_statement located

View File

@ -23,7 +23,7 @@ type 'a located = {
type environment_statement =
| Assignment of bool * string located * string located (* variable = value *)
| Append of string located * string located (* variable += value *)
| Include of string located (* include named environemnt *)
| Include of string located (* include named environment *)
type tsl_item =
| Environment_statement of environment_statement located

View File

@ -79,7 +79,7 @@ void caml_gr_handle_event(XEvent * event)
if (caml_gr_window.w > caml_gr_bstore.w
|| caml_gr_window.h > caml_gr_bstore.h) {
/* Allocate a new backing store large enough to accomodate
/* Allocate a new backing store large enough to accommodate
both the old backing store and the current window. */
struct canvas newbstore;
newbstore.w = max(caml_gr_window.w, caml_gr_bstore.w);

View File

@ -124,7 +124,7 @@ val matched_string : string -> string
- {!Str.global_substitute}
- {!Str.substitute_first}
provided that none of the following functions was called inbetween:
provided that none of the following functions was called in between:
- {!Str.global_replace}
- {!Str.replace_first}
- {!Str.split}

View File

@ -124,7 +124,7 @@ CAMLprim value unix_lockf(value fd, value cmd, value span)
err = GetLastError();
break;
case 3: /* F_TEST - check whether a write lock can be obtained */
/* I'm doing this by aquiring an immediate write
/* I'm doing this by acquiring an immediate write
* lock and then releasing it. It is not clear that
* this behavior matches anything in particular, but
* it is not clear the nature of the lock test performed

View File

@ -630,7 +630,7 @@ LPSELECTDATA socket_poll_add (LPSELECTDATA lpSelectData,
candidate = NULL;
aQueries = NULL;
/* Polling socket can be done mulitple handle at the same time. You just
/* Polling socket can be done multiple handle at the same time. You just
need one worker to use it. Try to find if there is already a worker
handling this kind of request.
Only one event can be associated with a given socket which means

View File

@ -182,7 +182,7 @@ LPWORKER worker_pop (void)
}
nWorkersCurrent++;
nWorkersMax = (nWorkersCurrent > nWorkersMax ? nWorkersCurrent : nWorkersMax);
DEBUG_PRINT("Workers running current/runnning max/waiting: %d/%d/%d",
DEBUG_PRINT("Workers running current/running max/waiting: %d/%d/%d",
nWorkersCurrent,
nWorkersMax,
list_length((LPLIST)lpWorkers));
@ -222,7 +222,7 @@ void worker_push(LPWORKER lpWorker)
bFreeWorker = FALSE;
};
nWorkersCurrent--;
DEBUG_PRINT("Workers running current/runnning max/waiting: %d/%d/%d",
DEBUG_PRINT("Workers running current/running max/waiting: %d/%d/%d",
nWorkersCurrent,
nWorkersMax,
list_length((LPLIST)lpWorkers));

View File

@ -562,7 +562,7 @@ let lines_around_from_file
input.
It first tries to read from [!input_lexbuf], then if that fails (because the
lexbuf no longers contains the input we want), it reads from [!input_name]
lexbuf no longer contains the input we want), it reads from [!input_name]
directly *)
let lines_around_from_current_input ~start_pos ~end_pos =
(* Be a bit defensive, and do not try to open one of the possible

View File

@ -252,7 +252,7 @@ value caml_interprete(code_t prog, asize_t prog_size)
accu = caml_exn_bucket;
pc = saved_pc; saved_pc = NULL;
if (pc != NULL) pc += 2;
/* +2 adjustement for the sole purpose of backtraces */
/* +2 adjustment for the sole purpose of backtraces */
goto raise_exception;
}
caml_external_raise = &raise_buf;

View File

@ -231,7 +231,7 @@ static void init_sweep_phase(void)
if (caml_major_gc_hook) (*caml_major_gc_hook)();
}
/* auxillary function of mark_slice */
/* auxiliary function of mark_slice */
static inline value* mark_slice_darken(value *gray_vals_ptr,
value v, mlsize_t i,
int in_ephemeron, int *slice_pointers)

View File

@ -580,7 +580,7 @@ CAMLexport value caml_alloc_shr (mlsize_t wosize, tag_t tag)
that depend on the GC (and finalizers) for deallocation.
For the GC to take dependent memory into account when computing
its automatic speed setting,
you must call [caml_alloc_dependent_memory] when you alloate some
you must call [caml_alloc_dependent_memory] when you allocate some
dependent memory, and [caml_free_dependent_memory] when you
free it. In both cases, you pass as argument the size (in bytes)
of the block being allocated or freed.

View File

@ -2582,7 +2582,7 @@ let fmt_ebb_of_string ?legacy_behavior str =
end;
fmt_result
(* Parse formatting informations (after '@'). *)
(* Parse formatting information (after '@'). *)
and parse_after_at : type e f . int -> int -> (_, _, e, f) fmt_ebb =
fun str_ind end_ind ->
if str_ind = end_ind then Fmt_EBB (Char_literal ('@', End_of_format))

View File

@ -13,7 +13,7 @@
(* *)
(**************************************************************************)
(* Testing auxilliaries. *)
(* Testing auxiliaries. *)
open Scanf;;

View File

@ -13,7 +13,7 @@
(* *)
(**************************************************************************)
(* Testing auxilliaries. *)
(* Testing auxiliaries. *)
val test : bool -> unit;;
(** [test e] tests that [e] evaluates to [true]. *)

View File

@ -112,7 +112,7 @@ val x : 'a option -> unit = <fun>
val y : 'a list -> unit = <fun>
|}];;
(* this is accepted as all fields are overriden *)
(* this is accepted as all fields are overridden *)
let rec x = { x with contents = 3 } [@ocaml.warning "-23"];;
[%%expect{|
val x : int ref = {contents = 3}

View File

@ -454,7 +454,7 @@ let rec scan_elems ib accu =
bscanf ib " %c " (fun c ->
match c with
| '[' when accu = [] ->
(* begginning of list: could find either
(* beginning of list: could find either
- an int, if the list is not empty,
- the char ], if the list is empty. *)
bscanf ib "%[]]"
@ -931,7 +931,7 @@ let scan_string_list = scan_list (fun ib -> Scanf.bscanf ib "%S");;
let scan_bool_list = scan_list (fun ib -> Scanf.bscanf ib "%B");;
let scan_char_list = scan_list (fun ib -> Scanf.bscanf ib "%C");;
(* [scan_list] is truely polymorphic: scanning a list of lists of items
(* [scan_list] is truly polymorphic: scanning a list of lists of items
is a one liner!
Here we scan list of lists of floats. *)
@ -983,7 +983,7 @@ let test35 () =
test (test340 () && test35 ())
;;
(* The prefered reader functionnals. *)
(* The preferred reader functionnals. *)
(* To read a list as in OCaml (elements are ``blank + semicolon + blank''
separated, and the list is enclosed in brackets). *)

View File

@ -10,7 +10,7 @@
One possible fix for this would be to make it possible for ocamltest to
compile C-only programs, which will be a bit of work to handle the
output of msvc and will also duplicate what the ocaml compiler itslef
output of msvc and will also duplicate what the OCaml compiler itself
already does.
*)

View File

@ -2,7 +2,7 @@
(* Tests from manual, section intf-c *)
(*
This test is currently skipped because there is no proper way to
figure out whether Curses is avaiblable or not. If it becomes possible
figure out whether Curses is available or not. If it becomes possible
to figure that out, it would be nice to be able to check that the test
compiles. Executing seems lessrelevant.
*)

View File

@ -57,7 +57,7 @@ and pp_var fmt v =
pp_form v.form
type env = {
(** resizeable array for cheap *)
(** resizable array for cheap *)
vars : (int,var) Hashtbl.t;
(** the ephemerons must be alive *)
ephes : ephe Stack.t;

View File

@ -304,7 +304,7 @@ let pop_castable () =
| [] -> raise Not_found
;;
(* We can add foos and bars to this list, and retrive them *)
(* We can add foos and bars to this list, and retrieve them *)
push_castable (new foo);;
push_castable (new bar);;
@ -6762,7 +6762,7 @@ module PR7135 = struct
f (x :> int) (y :> int)
end;;
(* exemple of non-ground coercion *)
(* example of non-ground coercion *)
module Test1 = struct
type t = private int

View File

@ -23,7 +23,7 @@ let remove_locs =
let attrs = default_mapper.attributes mapper attrs in
List.filter (fun a ->
a.Parsetree.attr_name.Location.txt <> "#punning#")
attrs (* this is to accomodate a LexiFi custom extension *)
attrs (* this is to accommodate a LexiFi custom extension *)
)
}

View File

@ -86,7 +86,7 @@ module Manual : sig
(** The comment for variable x. *)
val mutable x : int
(** The commend for method m. *)
(** The comment for method m. *)
method m : int -> int
(** This is a docstring that OCaml <= 4.07.1 misplaces.
@ -246,7 +246,7 @@ module Manual :
[@@@ocaml.text
" This is a docstring that OCaml <= 4.07.1 drops.\n For some reason, when a class type begins with two docstrings,\n it keeps only the second one.\n This is fixed by GPR#2151. "]
val mutable x : int[@@ocaml.doc " The comment for variable x. "]
method m : int -> int[@@ocaml.doc " The commend for method m. "]
method m : int -> int[@@ocaml.doc " The comment for method m. "]
[@@@ocaml.text
" This is a docstring that OCaml <= 4.07.1 misplaces.\n For some reason, when a class type ends with two docstrings,\n it keeps both of them, but exchanges their order.\n This is again fixed by GPR#2151. "]
[@@@ocaml.text " Another docstring that OCaml <= 4.07.1 misplaces. "]

View File

@ -21,7 +21,7 @@
\section{Level 0}
A level 0 heading is guaranted to be at the same level that
A level 0 heading is guaranteed to be at the same level that
the main heading of the module.

View File

@ -9,7 +9,7 @@
Standard heading levels start at 1.
{0 Level 0}
A level 0 heading is guaranted to be at the same level that
A level 0 heading is guaranteed to be at the same level that
the main heading of the module.
This setup allows users to start their standard heading at level 1 rather

View File

@ -41,7 +41,7 @@
<li>An enumerated list first element</li>
<li>second element</li>
</OL>
<div align=left>Alignement test: left</div><div align=right>Right</div><center>Center</center>
<div align=left>Alignment test: left</div><div align=right>Right</div><center>Center</center>
<p>Other complex text<sub class="subscript">in subscript </sub><sup class="superscript">and superscript</sup></p>
<p>There is also html specific elements.</p>

View File

@ -30,7 +30,7 @@
+ An enumerated list first element
+ second element
{L Alignement test: left}
{L Alignment test: left}
{R Right}
{C Center}

View File

@ -82,7 +82,7 @@ let pop_castable () =
| [] -> raise Not_found
;;
(* We can add foos and bars to this list, and retrive them *)
(* We can add foos and bars to this list, and retrieve them *)
push_castable (new foo);;
push_castable (new bar);;

View File

@ -136,7 +136,7 @@ Error: In this definition, a type variable has a variance that
cannot be deduced from the type parameters.
It was expected to be unrestricted, but it is covariant.
|}];;
(* shoud fail: we do not know for sure the variance of Queue.t *)
(* should fail: we do not know for sure the variance of Queue.t *)
type +'a t = T of 'a;;
type +'a s = 'b constraint 'a = 'b t;; (* ok *)

View File

@ -244,7 +244,7 @@ Error: This expression is packed module, but the expected type is int
|}]
(** Bultin [%extension_constructor *)
(** Builtin [%extension_constructor *)
type t = A
let x = [%extension_constructor A]
[%%expect {|

View File

@ -53,7 +53,7 @@ module PR7135 :
end
|}]
(* exemple of non-ground coercion *)
(* example of non-ground coercion *)
module Test1 = struct
type t = private int

View File

@ -39,7 +39,7 @@ error () {
arch_error() {
configure_url="https://ci.inria.fr/ocaml/computer/${NODE_NAME}/configure"
msg="Unknown architecture. Make sure the OCAML_ARCH environemnt"
msg="Unknown architecture. Make sure the OCAML_ARCH environment"
msg="$msg variable has been defined."
msg="$msg\nSee ${configure_url}"
error "$msg"

View File

@ -42,7 +42,7 @@ error () {
arch_error() {
configure_url="https://ci.inria.fr/ocaml/computer/${NODE_NAME}/configure"
msg="Unknown architecture. Make sure the OCAML_ARCH environemnt"
msg="Unknown architecture. Make sure the OCAML_ARCH environment"
msg="$msg variable has been defined."
msg="$msg\nSee ${configure_url}"
error "$msg"

View File

@ -39,7 +39,7 @@ error () {
arch_error() {
configure_url="https://ci.inria.fr/ocaml/computer/${NODE_NAME}/configure"
msg="Unknown architecture. Make sure the OCAML_ARCH environemnt"
msg="Unknown architecture. Make sure the OCAML_ARCH environment"
msg="$msg variable has been defined."
msg="$msg\nSee ${configure_url}"
error "$msg"

View File

@ -6,7 +6,7 @@ typechecker is overly complex and fragile. A big rewriting "from
scratch" might be possible or desirable at some point, or not, but
incremental cleanup steps are certainly accessible and could bring the
current implementation in a better shape at a relatively small cost
and in a reasonnably distant future.
and in a reasonably distant future.
Goals of the cleanup:

View File

@ -19,7 +19,7 @@ open Asttypes
open Types
module Unification_trace: sig
(** Unification traces are used to explain unification errrors
(** Unification traces are used to explain unification errors
when printing error messages *)
type position = First | Second

View File

@ -91,7 +91,7 @@ let zero = make_pat (Tpat_constant (Const_int 0)) Ctype.none Env.empty
a value would be ill-typed, so we can never actually get there.
Checking the first column at each step of the recursion and making the
concious decision of "aborting" the algorithm whenever the first column
conscious decision of "aborting" the algorithm whenever the first column
becomes incoherent, allows us to retain the initial assumption in later
stages of the algorithms.
@ -229,7 +229,7 @@ let first_column simplified_matrix =
The second clause above will NOT (and cannot) be flagged as useless.
Finally, there are two compatibility fonction
Finally, there are two compatibility functions:
compat p q ---> 'syntactic compatibility, used for diagnostics.
may_compat p q ---> a safe approximation of possible compat,
for compilation

View File

@ -270,8 +270,8 @@ module Mode = struct
a variable in an expression in which it does not occur. *)
| Delay
(** A [Delay] context can be fully evaluated without evaluting its argument,
which will only be needed at a later point of program execution. For
(** A [Delay] context can be fully evaluated without evaluating its argument
, which will only be needed at a later point of program execution. For
example, [fun x -> ?] or [lazy ?] are [Delay] contexts. *)
| Guard

View File

@ -788,7 +788,7 @@ and class_field_aux self_loc cl_num self_type meths vars
(* N.B. the self type of a final object type doesn't contain a dummy method in
the beginning.
We only explicitely add a dummy method to class definitions (and class (type)
We only explicitly add a dummy method to class definitions (and class (type)
declarations)), which are later removed (made absent) by [final_decl].
If we ever find a dummy method in a final object self type, it means that

View File

@ -12,7 +12,7 @@
(* *)
(**************************************************************************)
(** Manangement of include directories.
(** Management of include directories.
This module offers a high level interface to locating files in the
load path, which is constructed from [-I] command line flags and a few

View File

@ -21,7 +21,7 @@
/* The line size must be a positive integer. One hundred was chosen */
/* because few lines in Yacc input grammars exceed 100 characters. */
/* Note that if a line exceeds LINESIZE characters, the line buffer */
/* will be expanded to accomodate it. */
/* will be expanded to accommodate it. */
#define LINESIZE 100