File 0865-Fix-typos-in-lib-kernel.patch of Package erlang
From 796f11d4de1552abbcaf32052cc31f0ae5386222 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Sun, 19 Dec 2021 16:30:37 +0800
Subject: [PATCH] Fix typos in lib/kernel
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
Co-authored-by: Björn Gustavsson <bgustavsson@gmail.com>
---
lib/kernel/doc/src/config.xml | 2 +-
lib/kernel/doc/src/erl_ddll.xml | 4 +-
lib/kernel/doc/src/gen_sctp.xml | 2 +-
lib/kernel/doc/src/gen_tcp.xml | 8 +-
lib/kernel/doc/src/heart.xml | 2 +-
lib/kernel/doc/src/inet.xml | 8 +-
lib/kernel/doc/src/inet_res.xml | 2 +-
lib/kernel/doc/src/logger.xml | 2 +-
lib/kernel/doc/src/logger_chapter.xml | 4 +-
lib/kernel/doc/src/logger_std_h.xml | 2 +-
lib/kernel/doc/src/net.xml | 6 +-
lib/kernel/doc/src/net_kernel.xml | 2 +-
lib/kernel/doc/src/notes.xml | 18 ++--
lib/kernel/doc/src/os.xml | 2 +-
lib/kernel/doc/src/rpc.xml | 4 +-
lib/kernel/doc/src/seq_trace.xml | 2 +-
lib/kernel/doc/src/socket.xml | 26 ++---
lib/kernel/doc/src/socket_usage.xml | 6 +-
.../erl_uds_dist/src/erl_uds_dist.erl | 6 +-
.../gen_tcp_dist/src/gen_tcp_dist.erl | 8 +-
lib/kernel/examples/uds_dist/c_src/uds_drv.c | 2 +-
.../examples/uds_dist/src/uds_server.erl | 2 +-
lib/kernel/include/inet_sctp.hrl | 2 +-
lib/kernel/src/application_controller.erl | 6 +-
lib/kernel/src/code_server.erl | 2 +-
lib/kernel/src/disk_log.erl | 4 +-
lib/kernel/src/disk_log.hrl | 2 +-
lib/kernel/src/dist_ac.erl | 6 +-
lib/kernel/src/dist_util.erl | 4 +-
lib/kernel/src/erl_boot_server.erl | 4 +-
lib/kernel/src/erpc.erl | 2 +-
lib/kernel/src/file_io_server.erl | 2 +-
lib/kernel/src/gen_tcp_socket.erl | 2 +-
lib/kernel/src/gen_udp_socket.erl | 6 +-
lib/kernel/src/global_group.erl | 10 +-
lib/kernel/src/heart.erl | 2 +-
lib/kernel/src/inet.erl | 2 +-
lib/kernel/src/inet_config.erl | 2 +-
lib/kernel/src/inet_db.erl | 10 +-
lib/kernel/src/inet_dns.hrl | 6 +-
lib/kernel/src/inet_res.erl | 2 +-
lib/kernel/src/inet_res.hrl | 2 +-
lib/kernel/src/logger.erl | 4 +-
lib/kernel/src/logger_h_common.erl | 2 +-
lib/kernel/src/net_kernel.erl | 2 +-
lib/kernel/src/ram_file.erl | 4 +-
lib/kernel/src/rpc.erl | 6 +-
lib/kernel/src/socket.erl | 12 +--
lib/kernel/test/application_SUITE.erl | 8 +-
lib/kernel/test/code_SUITE.erl | 4 +-
lib/kernel/test/disk_log_SUITE.erl | 2 +-
lib/kernel/test/erl_distribution_SUITE.erl | 8 +-
lib/kernel/test/erl_distribution_wb_SUITE.erl | 2 +-
lib/kernel/test/erpc_SUITE_data/fwd_node.c | 2 +-
lib/kernel/test/error_logger_SUITE.erl | 2 +-
lib/kernel/test/file_SUITE.erl | 8 +-
lib/kernel/test/file_SUITE_data/realmen.html | 6 +-
lib/kernel/test/gen_tcp_api_SUITE.erl | 12 +--
lib/kernel/test/gen_tcp_misc_SUITE.erl | 38 +++----
lib/kernel/test/gen_udp_SUITE.erl | 6 +-
lib/kernel/test/global_SUITE.erl | 8 +-
lib/kernel/test/heart_SUITE.erl | 2 +-
lib/kernel/test/inet_SUITE.erl | 16 +--
lib/kernel/test/inet_res_SUITE.erl | 4 +-
.../test/kernel_test_global_sys_monitor.erl | 6 +-
lib/kernel/test/kernel_test_lib.erl | 16 +--
lib/kernel/test/logger_SUITE.erl | 2 +-
lib/kernel/test/logger_disk_log_h_SUITE.erl | 2 +-
lib/kernel/test/logger_std_h_SUITE.erl | 6 +-
lib/kernel/test/prim_file_SUITE.erl | 8 +-
.../test/prim_file_SUITE_data/realmen.html | 10 +-
.../test/ram_file_SUITE_data/realmen.html | 10 +-
lib/kernel/test/rpc_SUITE.erl | 8 +-
lib/kernel/test/socket_SUITE.erl | 98 +++++++++----------
lib/kernel/test/socket_test_evaluator.erl | 6 +-
.../test/socket_test_ttest_tcp_server.erl | 4 +-
.../test/socket_test_ttest_tcp_socket.erl | 2 +-
77 files changed, 267 insertions(+), 267 deletions(-)
diff --git a/lib/kernel/doc/src/erl_ddll.xml b/lib/kernel/doc/src/erl_ddll.xml
index 798789c2af..40d0a578d3 100644
--- a/lib/kernel/doc/src/erl_ddll.xml
+++ b/lib/kernel/doc/src/erl_ddll.xml
@@ -334,7 +334,7 @@
<desc>
<p>Loads and links the dynamic driver <c><anno>Name</anno></c>. <c><anno>Path</anno></c>
is a file path to the directory containing the driver.
- <c><anno>Name</anno></c> must be a sharable object/dynamic library. Two
+ <c><anno>Name</anno></c> must be a shareable object/dynamic library. Two
drivers with different <c><anno>Path</anno></c> parameters cannot be
loaded under the same name. The <c><anno>Name</anno></c> is a string or
atom containing at least one character.</p>
diff --git a/lib/kernel/doc/src/gen_sctp.xml b/lib/kernel/doc/src/gen_sctp.xml
index 9d5a4152a8..3a4655d1ef 100644
--- a/lib/kernel/doc/src/gen_sctp.xml
+++ b/lib/kernel/doc/src/gen_sctp.xml
@@ -817,7 +817,7 @@ connect(Socket, Ip, Port>,
<c>adaptation_ind</c> as the Adaptation Indication parameter for
establishing new associations. See
<url href="http://www.rfc-archive.org/getrfc.php?rfc=2960">RFC2960</url> and
- <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extenstions for SCTP</url> for more details.</p>
+ <url href="http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13">Sockets API Extentions for SCTP</url> for more details.</p>
</item>
<tag><c>{sctp_peer_addr_params, #sctp_paddrparams{}}</c></tag>
<item>
diff --git a/lib/kernel/doc/src/heart.xml b/lib/kernel/doc/src/heart.xml
index e1fb1323a5..6f956924b3 100644
--- a/lib/kernel/doc/src/heart.xml
+++ b/lib/kernel/doc/src/heart.xml
@@ -98,7 +98,7 @@
</item>
<tag><c><![CDATA[ERL_CRASH_DUMP_SECONDS=-1]]></c></tag>
<item><p> Setting the environment variable to a negative value will not reboot
- the runtime system until the crash dump file has been completly written.
+ the runtime system until the crash dump file has been completely written.
</p>
</item>
<tag><c><![CDATA[ERL_CRASH_DUMP_SECONDS=S]]></c></tag>
diff --git a/lib/kernel/doc/src/inet.xml b/lib/kernel/doc/src/inet.xml
index 8e7fe2f7bf..e1edf3e657 100644
--- a/lib/kernel/doc/src/inet.xml
+++ b/lib/kernel/doc/src/inet.xml
@@ -588,7 +588,7 @@ fe80::204:acff:fe17:bf38
correspond to the second, third and fourth/fifth parameters to the
<c>getsockopt</c> call in the C socket API. The value stored
in the buffer is returned as a binary <c>ValueBin</c>
- where all values are coded in the native endianess.</p>
+ where all values are coded in the native endianness.</p>
<p>Asking for and inspecting raw socket options require low
level information about the current operating system and TCP
stack.</p>
@@ -1621,7 +1621,7 @@ setcap cap_sys_admin,cap_sys_ptrace,cap_dac_read_search+epi beam.smp</code>
and the actual option value specified as a binary. This
corresponds to the second, third and fourth argument to the
<c>setsockopt</c> call in the C socket API. The option value
- needs to be coded in the native endianess of the platform and,
+ needs to be coded in the native endianness of the platform and,
if a structure is required, needs to follow the struct
alignment conventions on the specific platform.</p>
<p>Using raw socket options require detailed knowledge about
diff --git a/lib/kernel/doc/src/inet_res.xml b/lib/kernel/doc/src/inet_res.xml
index 0d654bbc0e..be049ae1e2 100644
--- a/lib/kernel/doc/src/inet_res.xml
+++ b/lib/kernel/doc/src/inet_res.xml
@@ -125,7 +125,7 @@
<datatype>
<name name="dns_msg"/>
<desc>
- <p>This is the start of a hiearchy of opaque data structures
+ <p>This is the start of a hierarchy of opaque data structures
that can be examined with access functions in inet_dns that
return lists of {Field,Value} tuples. The arity 2 functions
just return the value for a given field.</p>
diff --git a/lib/kernel/doc/src/notes.xml b/lib/kernel/doc/src/notes.xml
index cf08ba982d..2f0cc44d9b 100644
--- a/lib/kernel/doc/src/notes.xml
+++ b/lib/kernel/doc/src/notes.xml
@@ -4194,11 +4194,11 @@
Characteristics impact: A call to the
<c>garbage_collect/1</c> BIF or the
<c>check_process_code/2</c> BIF will normally take longer
- time to complete while the system as a whole wont be as
+ time to complete while the system as a whole won't be as
much negatively effected by the operation as before. A
call to <c>code:purge/1</c> and <c>code:soft_purge/1</c>
may complete faster or slower depending on the state of
- the system while the system as a whole wont be as much
+ the system while the system as a whole won't be as much
negatively effected by the operation as before.</p>
<p>
Own Id: OTP-11388 Aux Id: OTP-11535, OTP-11648 </p>
@@ -4559,7 +4559,7 @@
<item>
<p>
Change printout of application crash message on startup
- to formated strings (Thanks to Serge Aleynikov)</p>
+ to formatted strings (Thanks to Serge Aleynikov)</p>
<p>
Own Id: OTP-10620</p>
</item>
@@ -5341,7 +5341,7 @@
</item>
<item>
<p>
- - Add spec for function that does not return - Strenghen
+ - Add spec for function that does not return - Strengthen
spec - Introduce types to avoid duplication in specs -
Add specs for functions that do not return - Add specs
for behaviour callbacks - Simplify two specs</p>
@@ -5721,7 +5721,7 @@
app-vsn/ebin/mod.beam file, the file info for the app-vsn
and app-vsn/ebin directories are faked using the file
info from the archive file as origin. The virtual
- direcories can also be listed. For short, the top
+ directories can also be listed. For short, the top
directories are virtual if they does not exist.</p>
<p>
Own Id: OTP-8387</p>
diff --git a/lib/kernel/doc/src/os.xml b/lib/kernel/doc/src/os.xml
index 02f36a25ff..9ac0583d0a 100644
--- a/lib/kernel/doc/src/os.xml
+++ b/lib/kernel/doc/src/os.xml
@@ -345,7 +345,7 @@ calendar:now_to_universal_time(TS),
1> <input>io:format("~s~n",[print_time:format_utc_timestamp()]).</input>
29 Apr 2009 9:55:30.051711
</pre>
- <p>OS system time can also be retreived by
+ <p>OS system time can also be retrieved by
<seealso marker="#system_time/0"><c>os:system_time/0</c></seealso>,
and <seealso marker="#system_time/1"><c>os:system_time/1</c></seealso>.</p>
</desc>
diff --git a/lib/kernel/examples/uds_dist/c_src/uds_drv.c b/lib/kernel/examples/uds_dist/c_src/uds_drv.c
index 8c028ba910..6110ce6a72 100644
--- a/lib/kernel/examples/uds_dist/c_src/uds_drv.c
+++ b/lib/kernel/examples/uds_dist/c_src/uds_drv.c
@@ -1039,7 +1039,7 @@ static int try_lock(char *sockname, Byte *p_creation)
}
lseek(lockfd, 0, SEEK_SET);
write(lockfd, &creation, 1);
- fsync(lockfd); /* This could be concidered dangerous (blocking) */
+ fsync(lockfd); /* This could be considered dangerous (blocking) */
*p_creation = creation;
return lockfd;
}
diff --git a/lib/kernel/examples/uds_dist/src/uds_server.erl b/lib/kernel/examples/uds_dist/src/uds_server.erl
index c060130f9d..76eb869c5e 100644
--- a/lib/kernel/examples/uds_dist/src/uds_server.erl
+++ b/lib/kernel/examples/uds_dist/src/uds_server.erl
@@ -113,7 +113,7 @@ load_driver() ->
find_priv_lib() ->
PrivDir = case (catch code:priv_dir(uds_dist)) of
{'EXIT', _} ->
- %% Code server probably not startet yet
+ %% Code server probably not started yet
{ok, P} = erl_prim_loader:get_path(),
ModuleFile = atom_to_list(?MODULE) ++ extension(),
Pd = (catch lists:foldl
diff --git a/lib/kernel/include/inet_sctp.hrl b/lib/kernel/include/inet_sctp.hrl
index ddb3cdc26c..7b309b0e1c 100644
--- a/lib/kernel/include/inet_sctp.hrl
+++ b/lib/kernel/include/inet_sctp.hrl
@@ -120,7 +120,7 @@
}).
%% sctp_partial_delivery_event: XXX: Not clear whether it is delivered to
-%% the Sender or to the Recepient (probably the
+%% the Sender or to the Recipient (probably the
%% former). Currently, there is only 1 possible
%% value for "indication":
-record(sctp_pdapi_event,
diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl
index bf7843b92b..1f428c560b 100644
--- a/lib/kernel/src/application_controller.erl
+++ b/lib/kernel/src/application_controller.erl
@@ -509,7 +509,7 @@ init(Init, Kernel) ->
{ok, ConfData} ->
%% Actually, we don't need this info in an ets table anymore.
%% This table was introduced because starting applications
- %% should be able to get som info from AC (e.g. loaded_apps).
+ %% should be able to get some info from AC (e.g. loaded_apps).
%% The new implementation makes sure the AC process can be
%% called during start-up of any app.
case check_conf_data(ConfData) of
@@ -670,7 +670,7 @@ handle_call({start_application, AppName, RestartType}, From, S) ->
#state{running = Running, starting = Starting, start_p_false = SPF,
started = Started, start_req = Start_req} = S,
%% Check if the commandline environment variables are OK.
- %% Incase of erroneous variables do not start the application,
+ %% In case of erroneous variables do not start the application,
%% if the application is permanent crash the node.
%% Check if the application is already starting.
case lists:keyfind(AppName, 1, Start_req) of
@@ -1731,7 +1731,7 @@ check_user() ->
%%-----------------------------------------------------------------
-%% Prepare for a release upgrade by reading all the evironment variables.
+%% Prepare for a release upgrade by reading all the environment variables.
%%-----------------------------------------------------------------
do_prep_config_change(Apps) ->
do_prep_config_change(Apps, []).
diff --git a/lib/kernel/src/disk_log.erl b/lib/kernel/src/disk_log.erl
index a420a133d0..19225c9be5 100644
--- a/lib/kernel/src/disk_log.erl
+++ b/lib/kernel/src/disk_log.erl
@@ -368,7 +368,7 @@ pid2name(Pid) ->
end.
%% This function Takes 3 args, a Log, a Continuation and N.
-%% It retuns a {Cont2, ObjList} | eof | {error, Reason}
+%% It returns a {Cont2, ObjList} | eof | {error, Reason}
%% The initial continuation is the atom 'start'
-type chunk_error_rsn() :: no_such_log
@@ -1151,7 +1151,7 @@ system_terminate(Reason, _Parent, _, State) ->
exit(Reason).
%%-----------------------------------------------------------------
-%% Temporay code for upgrade.
+%% Temporary code for upgrade.
%%-----------------------------------------------------------------
system_code_change(State, _Module, _OldVsn, _Extra) ->
{ok, State}.
diff --git a/lib/kernel/src/disk_log.hrl b/lib/kernel/src/disk_log.hrl
index 1e773e4730..6cb2c13f02 100644
--- a/lib/kernel/src/disk_log.hrl
+++ b/lib/kernel/src/disk_log.hrl
@@ -143,7 +143,7 @@
%% since log was opened if info/1
%% has not yet been used on this log.
accFull :: non_neg_integer()} %% noFull+accFull is number of
- %% oveflows since the log was opened.
+ %% overflows since the log was opened.
).
-record(log,
diff --git a/lib/kernel/src/dist_ac.erl b/lib/kernel/src/dist_ac.erl
index 2a5cf0ba92..7b7f598de9 100644
--- a/lib/kernel/src/dist_ac.erl
+++ b/lib/kernel/src/dist_ac.erl
@@ -42,7 +42,7 @@
-define(DIST_AC, ?MODULE).
-define(LOCK_ID, ?MODULE).
-%% This is the protocol version for the dist_ac protcol (between nodes)
+%% This is the protocol version for the dist_ac protocol (between nodes)
-define(vsn, 1).
%%%-----------------------------------------------------------------
@@ -862,8 +862,8 @@ wait_dist_start(Node, Appl, Name, Nodes, PermittedNodes, S, Type) ->
{dist_ac_weight, Name, _Weigth, Node} ->
%% This is the situation: {Name, [RNode, {Node}, node()]}
%% and permit(false) is called on RNode, and we sent the
- %% weigth first. Node handled it in handle_info, and
- %% now we must send him a weigth msg. We can use any weigth;
+ %% weight first. Node handled it in handle_info, and
+ %% now we must send him a weight msg. We can use any weight;
%% he wins anyway.
monitor_node(Node, false),
{?DIST_AC, Node} !
diff --git a/lib/kernel/src/dist_util.erl b/lib/kernel/src/dist_util.erl
index c724083be2..832fd2d485 100644
--- a/lib/kernel/src/dist_util.erl
+++ b/lib/kernel/src/dist_util.erl
@@ -1183,8 +1183,8 @@ send_status(#hs_data{socket = Socket, other_node = Node,
%% ticker process, In that case this code will never run
%% And then every 60 seconds we also check the connection and
-%% close it if we havn't received anything on it for the
-%% last 60 secs. If ticked == tick we havn't received anything
+%% close it if we haven't received anything on it for the
+%% last 60 secs. If ticked == tick we haven't received anything
%% on the connection the last 60 secs.
%% The detection time interval is thus, by default, 45s < DT < 75s
diff --git a/lib/kernel/src/erl_boot_server.erl b/lib/kernel/src/erl_boot_server.erl
index 4ac945ce01..7fdb1f3bb8 100644
--- a/lib/kernel/src/erl_boot_server.erl
+++ b/lib/kernel/src/erl_boot_server.erl
@@ -34,7 +34,7 @@
add_subnet/2, delete_subnet/2,
which_slaves/0]).
-%% Exports for testing (dont't remove; tests suites depend on them).
+%% Exports for testing (don't remove; tests suites depend on them).
-export([would_be_booted/1]).
%% Internal exports
@@ -46,7 +46,7 @@
{
priority = 0, %% priority of this server
version = "" :: string(), %% Version handled i.e "4.5.3" etc
- udp_sock, %% listen port for broadcase requests
+ udp_sock, %% listen port for broadcast requests
udp_port, %% port number must be ?EBOOT_PORT!
listen_sock, %% listen sock for incoming file requests
listen_port, %% listen port number
diff --git a/lib/kernel/src/file_io_server.erl b/lib/kernel/src/file_io_server.erl
index b848e5ef75..691fc00b14 100644
--- a/lib/kernel/src/file_io_server.erl
+++ b/lib/kernel/src/file_io_server.erl
@@ -673,7 +673,7 @@ get_chars_apply(Mod, Func, XtraArg, S0, OutEnc,
end.
%% A hack that tries to inform the caller about the position where the
-%% error occured.
+%% error occurred.
invalid_unicode_error(Mod, Func, XtraArg, S) ->
try
{erl_scan,tokens,_Args} = XtraArg,
diff --git a/lib/kernel/src/global_group.erl b/lib/kernel/src/global_group.erl
index 77ed46de5f..2d818bc01f 100644
--- a/lib/kernel/src/global_group.erl
+++ b/lib/kernel/src/global_group.erl
@@ -71,7 +71,7 @@
%%%====================================================================================
%%% The state of the global_group process
%%%
-%%% sync_state = no_conf (global_groups not defined, inital state) |
+%%% sync_state = no_conf (global_groups not defined, initial state) |
%%% synced
%%% group_name = Own global group name
%%% nodes = Nodes in the own global group
@@ -219,9 +219,9 @@ request(Req, Time) ->
%%% at release upgrade when all nodes are not yet upgraded.
%%%
%%% It is possible to manually force a sync of the global_group. This is done for
-%%% instance after a release upgrade, after all nodes in the group beeing upgraded.
+%%% instance after a release upgrade, after all nodes in the group being upgraded.
%%% The nodes are not synced automatically because it would cause the node to be
-%%% disconnected from those not yet beeing upgraded.
+%%% disconnected from those not yet being upgraded.
%%%
%%% The three process dictionary variables (registered_names, send, and whereis_name)
%%% are used to store information needed if the search process crashes.
@@ -281,7 +281,7 @@ init([]) ->
%%% sync() -> ok
%%%
%%% An operator ordered sync of the own global group. This must be done after
-%%% a release upgrade. It can also be ordered if somthing has made the nodes
+%%% a release upgrade. It can also be ordered if something has made the nodes
%%% to disagree of the global_groups definition.
%%%====================================================================================
handle_call(sync, _From, S) ->
@@ -525,7 +525,7 @@ handle_call({global_groups_changed, NewPara}, _From, S) ->
%% group) global is not going to be synced to these nodes. We disconnect instead
%% of connect because upgrades can be done node by node and we cannot really
%% know what nodes these new nodes are synced to. The operator can always
- %% manually force a sync of the nodes after all nodes beeing uppgraded.
+ %% manually force a sync of the nodes after all nodes being uppgraded.
%% We must disconnect also if some nodes to which we have a connection
%% will not be in any global group at all.
force_nodedown(nodes(connected) -- NewNodes),
diff --git a/lib/kernel/src/heart.erl b/lib/kernel/src/heart.erl
index ffd9fd668a..dadcfaea0e 100644
--- a/lib/kernel/src/heart.erl
+++ b/lib/kernel/src/heart.erl
@@ -370,7 +370,7 @@ check_system([?SCHEDULER_CHECK_OPT|Opts]) ->
%% return 'ok' if everything is alright.
%% Terminate if with reason if something is a miss.
%% It is fine to timeout in the callback, in fact that is the intention
-%% if something goes wront -> no heartbeat.
+%% if something goes wrong -> no heartbeat.
check_callback(Callback) ->
case Callback of
diff --git a/lib/kernel/src/inet.erl b/lib/kernel/src/inet.erl
index 99bc8a6278..65b5c92bb7 100644
--- a/lib/kernel/src/inet.erl
+++ b/lib/kernel/src/inet.erl
@@ -1516,7 +1516,7 @@ fdopen(Fd, Opts, Protocol, Family, Type, Module) ->
Bound ->
%% We do not do any binding if default
%% port+addr options where given in order
- %% to keep backwards compatability with
+ %% to keep backwards compatibility with
%% pre Erlang/TOP 17
{ok, ok};
is_list(Addr) ->
diff --git a/lib/kernel/src/inet_config.erl b/lib/kernel/src/inet_config.erl
index c1ff478cc2..9931e344d2 100644
--- a/lib/kernel/src/inet_config.erl
+++ b/lib/kernel/src/inet_config.erl
@@ -213,7 +213,7 @@ add_dns_lookup([],Acc) ->
%%
%% Set the hostname (SHORT)
%% If hostname is long use the suffix as default domain
-%% and initalize the search option with the parts of domain
+%% and initialize the search option with the parts of domain
%%
set_hostname() ->
case inet_udp:open(0,[]) of
diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl
index 01912fdb57..c704a1dc1f 100644
--- a/lib/kernel/src/inet_db.erl
+++ b/lib/kernel/src/inet_db.erl
@@ -308,7 +308,7 @@ translate_lookup([]) -> [].
valid_lookup() -> [dns, file, yp, nis, nisplus, native].
-%% Reconstruct an inetrc sturcture from inet_db
+%% Reconstruct an inetrc structure from inet_db
get_rc() ->
get_rc([hosts, domain, nameservers, search, alt_nameservers,
timeout, retry, inet6, usevc,
@@ -899,7 +899,7 @@ take_socket_type(MRef) ->
%% --------------------
%% {node_auth,N} Ls - List of authentication for node N
%% {node_crypt,N} Ls - List of encryption methods for node N
-%% node_auth Ls - Default authenication
+%% node_auth Ls - Default authentication
%% node_crypt Ls - Default encryption
%%
diff --git a/lib/kernel/src/inet_dns.hrl b/lib/kernel/src/inet_dns.hrl
index a911110e05..5288c570b2 100644
--- a/lib/kernel/src/inet_dns.hrl
+++ b/lib/kernel/src/inet_dns.hrl
@@ -18,7 +18,7 @@
%% %CopyrightEnd%
%%
%%
-%% Defintion for Domain Name System
+%% Definition for Domain Name System
%%
%%
@@ -153,7 +153,7 @@
%%
%% Structure for query header, the order of the fields is machine and
%% compiler dependent, in our case, the bits within a byte are assignd
-%% least significant first, while the order of transmition is most
+%% least significant first, while the order of transmission is most
%% significant first. This requires a somewhat confusing rearrangement.
%%
-record(dns_header,
@@ -162,7 +162,7 @@
%% byte F0
qr = 0, %% :1 response flag
opcode = 0, %% :4 purpose of message
- aa = 0, %% :1 authoritive answer
+ aa = 0, %% :1 authoritative answer
tc = 0, %% :1 truncated message
rd = 0, %% :1 recursion desired
%% byte F1
diff --git a/lib/kernel/src/inet_res.erl b/lib/kernel/src/inet_res.erl
index fda656831e..e579999c2f 100644
--- a/lib/kernel/src/inet_res.erl
+++ b/lib/kernel/src/inet_res.erl
@@ -738,7 +738,7 @@ do_udp_recv(I, IP, Port, Timeout, Decode, Time, PollCnt) ->
{ok,Reply} ->
case Decode(Reply) of
false when T =:= 0 ->
- %% This is a compromize between the hard way i.e
+ %% This is a compromise between the hard way i.e
%% in the clause below if NewT becomes 0 bailout
%% immediately and risk that the right reply lies
%% ahead after some bad id replies, and the
diff --git a/lib/kernel/src/inet_res.hrl b/lib/kernel/src/inet_res.hrl
index c812550328..7d3c8762ba 100644
--- a/lib/kernel/src/inet_res.hrl
+++ b/lib/kernel/src/inet_res.hrl
@@ -18,7 +18,7 @@
%% %CopyrightEnd%
%%
%%
-%% Dns & resolver defintions
+%% Dns & resolver definitions
%%
-define(RES_TIMEOUT, 2000). %% milli second between retries
diff --git a/lib/kernel/src/net_kernel.erl b/lib/kernel/src/net_kernel.erl
index bc2f8a6573..0628e35bcd 100644
--- a/lib/kernel/src/net_kernel.erl
+++ b/lib/kernel/src/net_kernel.erl
@@ -458,7 +458,7 @@ do_auto_connect_2(Node, ConnId, From, State, ConnLookup) ->
?connect_failure(Node,{dist_auto_connect,never}),
false;
% This might happen due to connection close
- % not beeing propagated to user space yet.
+ % not being propagated to user space yet.
% Save the day by just not connecting...
{ok, once} when Else =/= [],
(hd(Else))#connection.state =:= up ->
diff --git a/lib/kernel/src/ram_file.erl b/lib/kernel/src/ram_file.erl
index e7b5e1eedb..ae0784b770 100644
--- a/lib/kernel/src/ram_file.erl
+++ b/lib/kernel/src/ram_file.erl
@@ -41,7 +41,7 @@
%% --------------------------------------------------------------------------
%% These operation codes were once identical between efile_drv.c
-%% and ram_file_drv.c, but now these drivers are not depeding on each other.
+%% and ram_file_drv.c, but now these drivers are not depending on each other.
%% So, the codes could be changed to more logical values now, but why indeed?
%% Defined "file" functions
@@ -394,7 +394,7 @@ ll_close(Port) ->
%% Converts a list of mode atoms into an mode word for the driver.
-%% Returns {Mode, Opts} wher Opts is a list of options for
+%% Returns {Mode, Opts} where Opts is a list of options for
%% erlang:open_port/2, or {error, einval} upon failure.
open_mode(List) when is_list(List) ->
diff --git a/lib/kernel/src/rpc.erl b/lib/kernel/src/rpc.erl
index 6b3b3100b6..52de9527ef 100644
--- a/lib/kernel/src/rpc.erl
+++ b/lib/kernel/src/rpc.erl
@@ -547,9 +547,9 @@ abcast([Node|Tail], Name, Mess) ->
abcast([], _,_) -> abcast.
-%% Syncronous broadcast, returns a list of the nodes which had Name
+%% Synchronous broadcast, returns a list of the nodes which had Name
%% as a registered server. Returns {Goodnodes, Badnodes}.
-%% Syncronous in the sense that we know that all servers have received the
+%% Synchronous in the sense that we know that all servers have received the
%% message when we return from the call, we can't know that they have
%% processed the message though.
@@ -741,7 +741,7 @@ rec_nodes(Name, [{N,R} | Tail], Badnodes, Replies) ->
end.
%% Now for an asynchronous rpc.
-%% An asyncronous version of rpc that is faster for series of
+%% An asynchronous version of rpc that is faster for series of
%% rpc's towards the same node. I.e. it returns immediately and
%% it returns a Key that can be used in a subsequent yield(Key).
diff --git a/lib/kernel/test/application_SUITE.erl b/lib/kernel/test/application_SUITE.erl
index 3584b90378..36d79fedff 100644
--- a/lib/kernel/test/application_SUITE.erl
+++ b/lib/kernel/test/application_SUITE.erl
@@ -371,7 +371,7 @@ permissions(Conf) when is_list(Conf) ->
false = is_started(app1, Cp3),
true = is_started(app1, Cp2),
- % Start app3, make sure noone starts it
+ % Start app3, make sure no one starts it
{[ok,ok,ok],[]} =
rpc:multicall(Cps, application, load, [app3()]),
?UNTIL(is_loaded(app3, Cps)),
@@ -744,7 +744,7 @@ permit_false_start_local(Conf) when is_list(Conf) ->
true = is_started(app1, Cp2),
false = is_started(app1, Cp3),
- % Unpermit it agin
+ % Unpermit it again
ok = rpc:call(Cp1, application, permit, [app1, false]),
test_server:sleep(1000),
false = is_started(app1, Cp1),
@@ -1225,7 +1225,7 @@
%%-----------------------------------------------------------------
otp_2973(suite) -> [];
otp_2973(doc) ->
- ["Test of two processes simultanously starting the same application."];
+ ["Test of two processes simultaneously starting the same application."];
otp_2973(Conf) when is_list(Conf) ->
% Write a .app file
{ok, Fd} = file:open("app0.app", [write]),
@@ -1546,7 +1546,7 @@
%%-----------------------------------------------------------------
otp_5606(suite) -> [];
otp_5606(doc) ->
- ["Test of several processes simultanously starting the same "
+ ["Test of several processes simultaneously starting the same "
"distributed application."];
otp_5606(Conf) when is_list(Conf) ->
diff --git a/lib/kernel/test/code_SUITE.erl b/lib/kernel/test/code_SUITE.erl
index dd5d11f0d9..a53f43b61c 100644
--- a/lib/kernel/test/code_SUITE.erl
+++ b/lib/kernel/test/code_SUITE.erl
@@ -303,7 +303,7 @@ replace_path(Config) when is_list(Config) ->
true = code:set_path(P), %Reset path
ok = file:del_dir("./kernel-2.11"),
- %% Add a completly new application.
+ %% Add a completely new application.
NewAppName = 'blurf_blarfer',
NewAppDir = filename:join(Cwd, atom_to_list(NewAppName) ++ "-6.33.1"),
@@ -776,7 +776,7 @@ clash(Config) when is_list(Config) ->
true = code:add_path(TmpEzFile++"/foobar-0.1/ebin"),
case os:type() of
{win32,_} ->
- %% The file wont be deleted on windows until it's closed, why we
+ %% The file won't be deleted on windows until it's closed, why we
%% need to rename instead.
ok = file:rename(TmpEzFile,TmpEzFile++".moved");
_ ->
diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl
index 9dd008d978..cea7cd52e9 100644
--- a/lib/kernel/test/disk_log_SUITE.erl
+++ b/lib/kernel/test/disk_log_SUITE.erl
@@ -1045,7 +1045,7 @@ m() ->
one_line("halt,int.inf. (10,1000)", W5, R5, Rep5, C5),
io:format("\n"),
io:format("\tWrap log time depends on how often the log wraps, as this\n"),
- io:format("\tinvolves opening of new files, which costs alot."),
+ io:format("\tinvolves opening of new files, which costs a lot."),
io:format("\n").
one_line(Txt, W, R, Rep, C) ->
diff --git a/lib/kernel/test/erl_distribution_wb_SUITE.erl b/lib/kernel/test/erl_distribution_wb_SUITE.erl
index ba1b18745f..31ef27fcac 100644
--- a/lib/kernel/test/erl_distribution_wb_SUITE.erl
+++ b/lib/kernel/test/erl_distribution_wb_SUITE.erl
@@ -524,7 +524,7 @@ gen_digest(Challenge, Cookie) when is_integer(Challenge), is_atom(Cookie) ->
%%
-%% The differrent stages of the MD5 handshake
+%% The different stages of the MD5 handshake
%%
send_status(Socket, Stat) ->
diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl
index 60aa60bf9f..534886696f 100644
--- a/lib/kernel/test/file_SUITE.erl
+++ b/lib/kernel/test/file_SUITE.erl
@@ -1089,7 +1089,7 @@ close(Config) when is_list(Config) ->
?line {ok,Fd1} = ?FILE_MODULE:open(Name,read_write),
%% Just closing it is no fun, we did that a million times already
%% This is a common error, for code written before Erlang 4.3
- %% bacause then ?FILE_MODULE:open just returned a Pid, and not everyone
+ %% because then ?FILE_MODULE:open just returned a Pid, and not everyone
%% really checked what they got.
?line {'EXIT',_Msg} = (catch ok = ?FILE_MODULE:close({ok,Fd1})),
?line ok = ?FILE_MODULE:close(Fd1),
@@ -1253,7 +1253,7 @@ append(Config) when is_list(Config) ->
?line ok = ?FILE_MODULE:make_dir(NewDir),
?line First = "First line\n",
- ?line Second = "Seond lines comes here\n",
+ ?line Second = "Second lines comes here\n",
?line Third = "And here is the third line\n",
%% Write a small text file.
@@ -2238,7 +2238,7 @@ allocate(Config) when is_list(Config) ->
allocate_and_assert(Fd, Offset, Length) ->
% Just verify that calls to ?PRIM_FILE:allocate/3 don't crash or have
- % any other negative side effect. We can't really asssert against a
+ % any other negative side effect. We can't really assert against a
% specific return value, because support for file space pre-allocation
% depends on the OS, OS version and underlying filesystem.
%
@@ -2603,7 +2603,7 @@ e_rename(Config) when is_list(Config) ->
ok ->
{ok, {comment,
"Moving between filesystems "
- "suceeded, files are probably "
+ "succeeded, files are probably "
"in the same filesystem!"}};
{error, eperm} ->
{ok, {comment, "SBS! You don't "
diff --git a/lib/kernel/test/file_SUITE_data/realmen.html b/lib/kernel/test/file_SUITE_data/realmen.html
index 92e13f23b8..eaaa65523a 100644
--- a/lib/kernel/test/file_SUITE_data/realmen.html
+++ b/lib/kernel/test/file_SUITE_data/realmen.html
@@ -121,7 +121,7 @@ based on data structures, instead of the other way around. As all Real
Programmers know, the only useful data structure is the
array. Strings, lists, structures, sets -- these are all special cases
of arrays and and can be treated that way just as easily without
-messing up your programing language with all sorts of
+messing up your programming language with all sorts of
complications. The worst thing about fancy data types is that you have
to declare them, and Real Programming Languages, as we all know, have
implicit typing based on the first letter of the (six character)
@@ -318,7 +318,7 @@ thing slightly more trivial than the destruction of life as we know
it, providing there's enough money in it. There are several Real
Programmers building video games at Atari, for example. (But not
playing them. A Real Programmer knows how to beat the machine every
-time: no challange in that.) Everyone working at LucasFilm is a Real
+time: no challenge in that.) Everyone working at LucasFilm is a Real
Programmer. (It would be crazy to turn down the money of 50 million
Star Wars fans.) The proportion of Real Programmers in Computer
Graphics is somewhat lower than the norm, mostly because nobody has
@@ -384,7 +384,7 @@ coffee. In some cases, the cups will contain Orange Crush.
and the Principles of Operation open to some particularly interesting
pages.
-<LI> Taped to the wall is a line-printer Snoopy calender for the year
+<LI> Taped to the wall is a line-printer Snoopy calendar for the year
1969.
<LI> Strewn about the floor are several wrappers for peanut butter
diff --git a/lib/kernel/test/gen_tcp_misc_SUITE.erl b/lib/kernel/test/gen_tcp_misc_SUITE.erl
index f8561a44c4..27a4cd5b3d 100644
--- a/lib/kernel/test/gen_tcp_misc_SUITE.erl
+++ b/lib/kernel/test/gen_tcp_misc_SUITE.erl
@@ -425,7 +425,7 @@ do_default_options(Config) ->
"-kernel inet_default_listen_options "
"\"{delay_send,true}\"",
fun do_delay_send_2/0),
- %% Active is to dangerous and is supressed
+ %% Active is to dangerous and is suppressed
{true,true,true} =
do_delay_on_other_node("-kernel inet_default_connect_options "
"\"{active,false}\" "
@@ -984,7 +984,7 @@ iter_max_socks(Config) when is_list(Config) ->
Dir = filename:dirname(code:which(?MODULE)),
{ok,Node} = test_server:start_node(test_iter_max_socks,slave,
[{args,"+Q 2048 -pa " ++ Dir}]),
- L = rpc:call(Node,?MODULE,do_iter_max_socks,[N, initalize]),
+ L = rpc:call(Node,?MODULE,do_iter_max_socks,[N, initialize]),
test_server:stop_node(Node),
io:format("Result: ~p",[L]),
@@ -1019,7 +1019,7 @@ iter_max_socks_run(Node, F) ->
do_iter_max_socks(0, _) ->
[];
-do_iter_max_socks(N, initalize) ->
+do_iter_max_socks(N, initialize) ->
MS = max_socks(),
[MS|do_iter_max_socks(N-1, MS)];
do_iter_max_socks(N, failed) ->
@@ -3271,14 +3271,14 @@ test_prio_accept_async(Config) ->
{Ref,{ok,[{priority,4},{tos,Tos1}]}} ->
ok;
{Ref,Error} ->
- ?t:fail({missmatch,Error})
+ ?t:fail({mismatch,Error})
after 5000 -> ?t:fail({error,"helper process timeout"})
end,
receive
{Ref,{ok,[{priority,4},{tos,Tos1}]}} ->
ok;
{Ref,Error2} ->
- ?t:fail({missmatch,Error2})
+ ?t:fail({mismatch,Error2})
after 5000 -> ?t:fail({error,"helper process timeout"})
end,
@@ -4035,7 +4035,7 @@ send_timeout(Config) when is_list(Config) ->
%% Let test_server slave die...
Mon = erlang:monitor(process, Pid),
receive {'DOWN',Mon,process,Pid,_} -> ok end,
- %% Check that parallell writers do not hang forever
+ %% Check that parallel writers do not hang forever
ParaFun =
fun(AutoClose) ->
{Loop,A,RNode} = setup_timeout_sink(1000, AutoClose),
diff --git a/lib/kernel/test/global_SUITE.erl b/lib/kernel/test/global_SUITE.erl
index 74dab9b1cc..8eaeb525e9 100644
--- a/lib/kernel/test/global_SUITE.erl
+++ b/lib/kernel/test/global_SUITE.erl
@@ -764,7 +764,7 @@ locks(Config) when is_list(Config) ->
% start two procs
?line Pid = start_proc(),
?line Pid2 = rpc:call(Cp1, ?MODULE, start_proc, []),
- % set a lock, and make sure noone else can set the same lock
+ % set a lock, and make sure no one else can set the same lock
?line true = global:set_lock({test_lock, self()}, ?NODES, 1),
?line false = req(Pid, {set_lock, test_lock, self()}),
?line false = req(Pid2, {set_lock, test_lock, self()}),
@@ -1481,7 +1481,7 @@ stress_partition(Config) when is_list(Config) ->
ok.
-%% Use this one to test alot of connection tests
+%% Use this one to test a lot of connection tests
%% erl -sname ts -rsh ctrsh -pa /clearcase/otp/internal_tools/test_server/ebin/ -ring_line 10000 -s test_server run_test global_SUITE
ring_line(suite) -> [];
@@ -2550,7 +2550,7 @@ mon_by_servers(Proc) ->
-define(REGNAME, contact_a_2).
leftover_name(suite) -> [];
-leftover_name(doc) -> ["OTP-5563. Bug: nodedown while synching."];
+leftover_name(doc) -> ["OTP-5563. Bug: nodedown while syncing."];
leftover_name(Config) when is_list(Config) ->
Timeout = 30,
ct:timetrap({seconds,Timeout}),
diff --git a/lib/kernel/test/heart_SUITE.erl b/lib/kernel/test/heart_SUITE.erl
index f5ca6d0e1d..1488517d30 100644
--- a/lib/kernel/test/heart_SUITE.erl
+++ b/lib/kernel/test/heart_SUITE.erl
@@ -584,7 +584,7 @@ stop_node(Node) ->
%%% This code is run in a slave node to ensure that
-%%% A heart command really gets set syncronously
+%%% A heart command really gets set synchronously
%%% and cannot get "dropped".
send_to(_,_,0) ->
diff --git a/lib/kernel/test/inet_SUITE.erl b/lib/kernel/test/inet_SUITE.erl
index cf3ff47325..3df19369e7 100644
--- a/lib/kernel/test/inet_SUITE.erl
+++ b/lib/kernel/test/inet_SUITE.erl
@@ -103,7 +103,7 @@ socknames_cases() ->
groups() ->
[{parse, [], [parse_hosts, parse_address]}].
-%% Required configuaration
+%% Required configuration
required(v4) ->
[{require, test_host_ipv4_only},
{require, test_dummy_host}];
@@ -521,7 +521,7 @@ ipv4_to_ipv6(Config) when is_list(Config) ->
host_and_addr() -> required(hosts).
host_and_addr(doc) -> ["Test looking up hosts and addresses. Use 'ypcat hosts' ",
- "or the local eqivalent to find all hosts."];
+ "or the local equivalent to find all hosts."];
host_and_addr(suite) -> [];
host_and_addr(Config) when is_list(Config) ->
?line Dog = test_server:timetrap(test_server:minutes(5)),
@@ -1302,7 +1302,7 @@ gethostnative_control(Config, Opts) ->
?line {skipped, "Not running native gethostbyname"}
end;
_ ->
- ?line {skipped, "Native not only lookup metod"}
+ ?line {skipped, "Native not only lookup method"}
end.
gethostnative_control_1(Config,
diff --git a/lib/kernel/test/inet_res_SUITE.erl b/lib/kernel/test/inet_res_SUITE.erl
index 7bacddd603..0214db00e5 100644
--- a/lib/kernel/test/inet_res_SUITE.erl
+++ b/lib/kernel/test/inet_res_SUITE.erl
@@ -1241,7 +1241,7 @@ last_ms_answer(Config) when is_list(Config) ->
PSpec = proxy_start(last_ms_answer, NS),
ProxyNS = proxy_ns(PSpec),
%%
- %% resolve; whith short timeout to trigger Timeout =:= 0 in inet_res
+ %% resolve; with short timeout to trigger Timeout =:= 0 in inet_res
{error,timeout} =
inet_res:resolve(
Name, in, a, [{nameservers,[ProxyNS]},verbose], Time + 10),
diff --git a/lib/kernel/test/prim_file_SUITE.erl b/lib/kernel/test/prim_file_SUITE.erl
index 6fc1ff2cd7..9f8229964e 100644
--- a/lib/kernel/test/prim_file_SUITE.erl
+++ b/lib/kernel/test/prim_file_SUITE.erl
@@ -435,7 +435,7 @@ close(Config) when is_list(Config) ->
?line {ok,Fd1} = ?PRIM_FILE:open(Name, [read, write]),
%% Just closing it is no fun, we did that a million times already
%% This is a common error, for code written before Erlang 4.3
- %% bacause then ?PRIM_FILE:open just returned a Pid, and not everyone
+ %% because then ?PRIM_FILE:open just returned a Pid, and not everyone
%% really checked what they got.
?line {'EXIT',_Msg} = (catch ok = ?PRIM_FILE:close({ok,Fd1})),
?line ok = ?PRIM_FILE:close(Fd1),
@@ -535,7 +535,7 @@ append(Config) when is_list(Config) ->
?line ok = ?PRIM_FILE:make_dir(NewDir),
?line First = "First line\n",
- ?line Second = "Seond lines comes here\n",
+ ?line Second = "Second lines comes here\n",
?line Third = "And here is the third line\n",
%% Write a small text file.
@@ -1222,7 +1222,7 @@ allocate(Config) when is_list(Config) ->
allocate_and_assert(Fd, Offset, Length) ->
% Just verify that calls to ?PRIM_FILE:allocate/3 don't crash or have
- % any other negative side effect. We can't really asssert against a
+ % any other negative side effect. We can't really assert against a
% specific return value, because support for file space pre-allocation
% depends on the OS, OS version and underlying filesystem.
%
@@ -1458,7 +1458,7 @@ e_rename(Config) when is_list(Config) ->
ok ->
{ok, {comment,
"Moving between filesystems "
- "suceeded, files are probably "
+ "succeeded, files are probably "
"in the same filesystem!"}};
{error, eperm} ->
{ok, {comment, "SBS! You don't "
diff --git a/lib/kernel/test/prim_file_SUITE_data/realmen.html b/lib/kernel/test/prim_file_SUITE_data/realmen.html
index c810a5d088..eaaa65523a 100644
--- a/lib/kernel/test/prim_file_SUITE_data/realmen.html
+++ b/lib/kernel/test/prim_file_SUITE_data/realmen.html
@@ -121,7 +121,7 @@ based on data structures, instead of the other way around. As all Real
Programmers know, the only useful data structure is the
array. Strings, lists, structures, sets -- these are all special cases
of arrays and and can be treated that way just as easily without
-messing up your programing language with all sorts of
+messing up your programming language with all sorts of
complications. The worst thing about fancy data types is that you have
to declare them, and Real Programming Languages, as we all know, have
implicit typing based on the first letter of the (six character)
@@ -237,7 +237,7 @@ destroy most of the interesting uses for EQUIVALENCE, and make it
impossible to modify the operating system code with negative
subscripts. Worst of all, bounds checking is inefficient.
-<LI> Source code maintainance systems. A Real Programmer keeps his
+<LI> Source code maintenance systems. A Real Programmer keeps his
code locked up in a card file, because it implies that its owner
cannot leave his important programs unguarded [5].
@@ -318,7 +318,7 @@ thing slightly more trivial than the destruction of life as we know
it, providing there's enough money in it. There are several Real
Programmers building video games at Atari, for example. (But not
playing them. A Real Programmer knows how to beat the machine every
-time: no challange in that.) Everyone working at LucasFilm is a Real
+time: no challenge in that.) Everyone working at LucasFilm is a Real
Programmer. (It would be crazy to turn down the money of 50 million
Star Wars fans.) The proportion of Real Programmers in Computer
Graphics is somewhat lower than the norm, mostly because nobody has
@@ -384,7 +384,7 @@ coffee. In some cases, the cups will contain Orange Crush.
and the Principles of Operation open to some particularly interesting
pages.
-<LI> Taped to the wall is a line-printer Snoopy calender for the year
+<LI> Taped to the wall is a line-printer Snoopy calendar for the year
1969.
<LI> Strewn about the floor are several wrappers for peanut butter
@@ -396,7 +396,7 @@ double stuff Oreos for special occasions.
<LI> Underneath the Oreos is a flow-charting template, left there by
the previous occupant of the office. (Real Programmers write programs,
-not documentation. Leave that to the maintainence people.)
+not documentation. Leave that to the maintenance people.)
</UL> <P>
diff --git a/lib/kernel/test/ram_file_SUITE_data/realmen.html b/lib/kernel/test/ram_file_SUITE_data/realmen.html
index c810a5d088..eaaa65523a 100644
--- a/lib/kernel/test/ram_file_SUITE_data/realmen.html
+++ b/lib/kernel/test/ram_file_SUITE_data/realmen.html
@@ -121,7 +121,7 @@ based on data structures, instead of the other way around. As all Real
Programmers know, the only useful data structure is the
array. Strings, lists, structures, sets -- these are all special cases
of arrays and and can be treated that way just as easily without
-messing up your programing language with all sorts of
+messing up your programming language with all sorts of
complications. The worst thing about fancy data types is that you have
to declare them, and Real Programming Languages, as we all know, have
implicit typing based on the first letter of the (six character)
@@ -237,7 +237,7 @@ destroy most of the interesting uses for EQUIVALENCE, and make it
impossible to modify the operating system code with negative
subscripts. Worst of all, bounds checking is inefficient.
-<LI> Source code maintainance systems. A Real Programmer keeps his
+<LI> Source code maintenance systems. A Real Programmer keeps his
code locked up in a card file, because it implies that its owner
cannot leave his important programs unguarded [5].
@@ -318,7 +318,7 @@ thing slightly more trivial than the destruction of life as we know
it, providing there's enough money in it. There are several Real
Programmers building video games at Atari, for example. (But not
playing them. A Real Programmer knows how to beat the machine every
-time: no challange in that.) Everyone working at LucasFilm is a Real
+time: no challenge in that.) Everyone working at LucasFilm is a Real
Programmer. (It would be crazy to turn down the money of 50 million
Star Wars fans.) The proportion of Real Programmers in Computer
Graphics is somewhat lower than the norm, mostly because nobody has
@@ -384,7 +384,7 @@ coffee. In some cases, the cups will contain Orange Crush.
and the Principles of Operation open to some particularly interesting
pages.
-<LI> Taped to the wall is a line-printer Snoopy calender for the year
+<LI> Taped to the wall is a line-printer Snoopy calendar for the year
1969.
<LI> Strewn about the floor are several wrappers for peanut butter
@@ -396,7 +396,7 @@ double stuff Oreos for special occasions.
<LI> Underneath the Oreos is a flow-charting template, left there by
the previous occupant of the office. (Real Programmers write programs,
-not documentation. Leave that to the maintainence people.)
+not documentation. Leave that to the maintenance people.)
</UL> <P>
--
2.31.1