Fixing misspellings

master
JPR 2019-05-21 10:23:27 +02:00
parent 1aeb9b2301
commit 6dc59549ce
14 changed files with 16 additions and 16 deletions

View File

@ -6155,7 +6155,7 @@ Bug Fixes:
- #5575: Random states are not marshallable across architectures - #5575: Random states are not marshallable across architectures
- #5579: camlp4: when a plugin is loaded in the toplevel, - #5579: camlp4: when a plugin is loaded in the toplevel,
Token.Filter.define_filter has no effect before the first syntax error Token.Filter.define_filter has no effect before the first syntax error
- #5585: typo: "explicitely" - #5585: typo: "explicitly"
- #5587: documentation: "allows to" is not correct English - #5587: documentation: "allows to" is not correct English
- #5593: remove C file when -output-obj fails - #5593: remove C file when -output-obj fails
- #5597: register names for instrtrace primitives in embedded bytecode - #5597: register names for instrtrace primitives in embedded bytecode
@ -6437,7 +6437,7 @@ Native-code compiler:
float comparisons. float comparisons.
Standard library: Standard library:
- Format: new function ikfprintf analoguous to ifprintf with a continuation - Format: new function ikfprintf analogous to ifprintf with a continuation
argument. argument.
* #4210, #4245: stricter range checking in string->integer conversion * #4210, #4245: stricter range checking in string->integer conversion
functions (int_of_string, Int32.of_string, Int64.of_string, functions (int_of_string, Int32.of_string, Int64.of_string,

2
News
View File

@ -156,7 +156,7 @@ Some highlights include:
- Instrumentation support for fuzzing with afl-fuzz. - Instrumentation support for fuzzing with afl-fuzz.
(GPR#504, by Stephen Dolan) (GPR#504, by Stephen Dolan)
- The compilers now accept new `-args/-args0 <file>` comand-line - The compilers now accept new `-args/-args0 <file>` command-line
parameters to provide extra command-line arguments in a file. User parameters to provide extra command-line arguments in a file. User
programs may implement similar options using the new `Expand` programs may implement similar options using the new `Expand`
constructor of the `Arg` module. constructor of the `Arg` module.

View File

@ -578,7 +578,7 @@ let main () =
"-all", Arg.Set all_dependencies, "-all", Arg.Set all_dependencies,
" Generate dependencies on all files"; " Generate dependencies on all files";
"-allow-approx", Arg.Set allow_approximation, "-allow-approx", Arg.Set allow_approximation,
" Fallback to a lexer-based approximation on unparseable files"; " Fallback to a lexer-based approximation on unparsable files";
"-as-map", Arg.Set Clflags.transparent_modules, "-as-map", Arg.Set Clflags.transparent_modules,
" Omit delayed dependencies for module aliases (-no-alias-deps -w -49)"; " Omit delayed dependencies for module aliases (-no-alias-deps -w -49)";
(* "compiler uses -no-alias-deps, and no module is coerced"; *) (* "compiler uses -no-alias-deps, and no module is coerced"; *)

View File

@ -111,7 +111,7 @@
% Changed \next to \html@next to prevent clashes with other sty files % Changed \next to \html@next to prevent clashes with other sty files
% (mike@emn.fr) % (mike@emn.fr)
% Changed \html@next to \htmlnext so the \makeatletter and % Changed \html@next to \htmlnext so the \makeatletter and
% \makeatother commands could be removed (they were cuasing other % \makeatother commands could be removed (they were causing other
% style files - changebar.sty - to crash) (nikos@cbl.leeds.ac.uk) % style files - changebar.sty - to crash) (nikos@cbl.leeds.ac.uk)

View File

@ -1138,7 +1138,7 @@ let create_set_of_closures ~function_decls ~free_vars ~specialised_args
This would be true when the function is known never to have This would be true when the function is known never to have
been inlined. been inlined.
Note that something like that may maybe enforcable in Note that something like that may maybe enforceable in
inline_and_simplify, but there is no way to do that on other inline_and_simplify, but there is no way to do that on other
passes. passes.

View File

@ -53,7 +53,7 @@ static DWORD do_create_process_native(wchar_t * exefile, wchar_t * cmdline,
err = GetLastError(); goto ret3; err = GetLastError(); goto ret3;
} }
/* If we do not have a console window, then we must create one /* If we do not have a console window, then we must create one
before running the process (keep it hidden for apparence). before running the process (keep it hidden for appearance).
If we are starting a GUI application, the newly created If we are starting a GUI application, the newly created
console should not matter. */ console should not matter. */
if (win_has_console()) if (win_has_console())

View File

@ -101,7 +101,7 @@ value caml_remove_debug_info(code_t start);
* The first function, [caml_current_callstack_size] computes the size * The first function, [caml_current_callstack_size] computes the size
* (in words) of the needed buffer, while the second actually writes * (in words) of the needed buffer, while the second actually writes
* the call stack to the buffer as an object of type * the call stack to the buffer as an object of type
* [raw_backtrace]. It should always be called with a bufer of the * [raw_backtrace]. It should always be called with a buffer of the
* size predicted by [caml_current_callstack_size]. The reason we use * size predicted by [caml_current_callstack_size]. The reason we use
* two separated functions is to allow using either [caml_alloc] (for * two separated functions is to allow using either [caml_alloc] (for
* performance) or [caml_alloc_shr] (when we need to avoid a call to * performance) or [caml_alloc_shr] (when we need to avoid a call to

View File

@ -123,7 +123,7 @@ static int32_t mt_generate_poisson(double len)
next_mt_generate_poisson -= cur_lambda; next_mt_generate_poisson -= cur_lambda;
if(next_mt_generate_poisson > 0) { if(next_mt_generate_poisson > 0) {
/* Fast path if [cur_lambda] is small: we reuse the same /* Fast path if [cur_lambda] is small: we reuse the same
exponential sample accross several calls to exponential sample across several calls to
[mt_generate_poisson]. */ [mt_generate_poisson]. */
return 0; return 0;
} else { } else {
@ -461,7 +461,7 @@ void caml_memprof_track_young(tag_t tag, uintnat wosize)
/* Write the ephemeron if not [None]. */ /* Write the ephemeron if not [None]. */
if(Is_block(ephe)) { if(Is_block(ephe)) {
/* Subtlety: we are actually writing the ephemeron with an invalid /* Subtlety: we are actually writing the ephemeron with an invalid
(unitialized) block. This is correct for two reasons: (uninitialized) block. This is correct for two reasons:
- The logic of [caml_ephemeron_set_key] never inspects the content of - The logic of [caml_ephemeron_set_key] never inspects the content of
the block. In only checks that the block is young. the block. In only checks that the block is young.
- The allocation and initialization happens right after returning - The allocation and initialization happens right after returning

View File

@ -177,7 +177,7 @@ CAMLexport void caml_leave_blocking_section(void)
Another case where this is necessary (even in a single threaded Another case where this is necessary (even in a single threaded
setting) is when the blocking section unmasks a pending signal: setting) is when the blocking section unmasks a pending signal:
If the signal is pending and masked but has already been If the signal is pending and masked but has already been
examinated by [caml_process_pending_signals], then examined by [caml_process_pending_signals], then
[caml_signals_are_pending] is 0 but the signal needs to be [caml_signals_are_pending] is 0 but the signal needs to be
handled at this point. */ handled at this point. */
caml_signals_are_pending = 1; caml_signals_are_pending = 1;

View File

@ -76,7 +76,7 @@ void caml_garbage_collection(void)
{ {
/* TEMPORARY: if we have just sampled an allocation in native mode, /* TEMPORARY: if we have just sampled an allocation in native mode,
we simply renew the sample to ignore it. Otherwise, renewing now we simply renew the sample to ignore it. Otherwise, renewing now
will not have any efect on the sampling distribution, because of will not have any effect on the sampling distribution, because of
the memorylessness of the Poisson process. */ the memorylessness of the Poisson process. */
caml_memprof_renew_minor_sample(); caml_memprof_renew_minor_sample();
if (caml_requested_major_slice || caml_requested_minor_gc || if (caml_requested_major_slice || caml_requested_minor_gc ||

View File

@ -52,7 +52,7 @@ val check_suffix : string -> string -> bool
val chop_suffix : string -> string -> string val chop_suffix : string -> string -> string
(** [chop_suffix name suff] removes the suffix [suff] from (** [chop_suffix name suff] removes the suffix [suff] from
the filename [name]. The behavior is undefined if [name] does not the filename [name]. The behavior is undefined if [name] does not
end with the suffix [suff]. It is thus recommmended to use end with the suffix [suff]. It is thus recommended to use
[chop_suffix_opt] instead. [chop_suffix_opt] instead.
*) *)

View File

@ -104,7 +104,7 @@ Error: This expression has type b = a but an expression was expected of type
representative for an ambivalent type escaping its scope. representative for an ambivalent type escaping its scope.
The commit that was implemented poses problems of its own: we are now The commit that was implemented poses problems of its own: we are now
unifying the type of the patterns in the environment of each pattern, instead unifying the type of the patterns in the environment of each pattern, instead
of the outter one. The code discussed in PR#7617 passes because each branch of the outer one. The code discussed in PR#7617 passes because each branch
contains the same equation, but consider the following cases: *) contains the same equation, but consider the following cases: *)
let f (type a b) (x : (a, b) eq) = let f (type a b) (x : (a, b) eq) =

View File

@ -69,7 +69,7 @@ val check : 'a t -> (Persistent_signature.t -> 'a)
[penv] (it may have failed) *) [penv] (it may have failed) *)
val looked_up : 'a t -> modname -> bool val looked_up : 'a t -> modname -> bool
(* [is_imported penv md] checks if [md] has been succesfully (* [is_imported penv md] checks if [md] has been successfully
imported in the environment [penv] *) imported in the environment [penv] *)
val is_imported : 'a t -> modname -> bool val is_imported : 'a t -> modname -> bool

View File

@ -616,7 +616,7 @@ let merge_constraint initial_env remove_aliases loc sg constr =
fun s path -> Subst.add_type_function path ~params ~body s fun s path -> Subst.add_type_function path ~params ~body s
in in
let sub = List.fold_left how_to_extend_subst Subst.identity !real_ids in let sub = List.fold_left how_to_extend_subst Subst.identity !real_ids in
(* This signature will not be used direcly, it will always be freshened (* This signature will not be used directly, it will always be freshened
by the caller. So what we do with the scope doesn't really matter. But by the caller. So what we do with the scope doesn't really matter. But
making it local makes it unlikely that we will ever use the result of making it local makes it unlikely that we will ever use the result of
this function unfreshened without issue. *) this function unfreshened without issue. *)