diff --git a/lib/kernel/doc/guides/logger_chapter.md b/lib/kernel/doc/guides/logger_chapter.md index 1d809b57668c..a281e1570c8c 100644 --- a/lib/kernel/doc/guides/logger_chapter.md +++ b/lib/kernel/doc/guides/logger_chapter.md @@ -59,8 +59,8 @@ flowchart TD API ---> ML[Module Level
Global Level
Global Filters] API -.Update configuration.-> DB ML -.-> DB - ML ---> HL1[Hander Level
Handler Filter] - ML ---> HL2[Hander Level
Handler Filter] + ML ---> HL1[Handler Level
Handler Filter] + ML ---> HL2[Handler Level
Handler Filter] HL1 ---> HC1[Handler Callback] HL2 ---> HC2[Handler Callback] HL1 -.-> DB diff --git a/lib/kernel/doc/guides/socket_usage.md b/lib/kernel/doc/guides/socket_usage.md index d6b97fa80ebc..ec5ea5c48fe3 100644 --- a/lib/kernel/doc/guides/socket_usage.md +++ b/lib/kernel/doc/guides/socket_usage.md @@ -310,7 +310,7 @@ handler_loop(Sock, {select_info, recv, SelectHandle}) -> end; %% This is the (asyncronous) behaviour on platforms that support 'completion', -%% currently only Windows. +%% currently onla Windows. handler_loop(Sock, {completion_info, recv, CompletionHandle}) -> receive {'$socket', Sock, completion, {CompletionHandle, CompletionStatus}} -> diff --git a/lib/kernel/examples/gen_tcp_dist/src/gen_tcp_dist.erl b/lib/kernel/examples/gen_tcp_dist/src/gen_tcp_dist.erl index b00de7a55ebe..95daa98dc9c9 100644 --- a/lib/kernel/examples/gen_tcp_dist/src/gen_tcp_dist.erl +++ b/lib/kernel/examples/gen_tcp_dist/src/gen_tcp_dist.erl @@ -573,7 +573,7 @@ call_ctrlr(Ctrlr, Msg) -> %% the connection supervisor. %% %% We are not allowed to block the connection -%% superviser when writing a tick and we also want +%% supervisor when writing a tick and we also want %% the tick to go through even during a heavily %% loaded system. gen_tcp does not have a %% non-blocking send operation exposed in its API 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 6110ce6a7242..7a7d0bec6261 100644 --- a/lib/kernel/examples/uds_dist/c_src/uds_drv.c +++ b/lib/kernel/examples/uds_dist/c_src/uds_drv.c @@ -118,7 +118,7 @@ typedef enum { portTypeCommand, /* A connected open port in command mode */ portTypeIntermediate, /* A connected open port in special half active mode */ - portTypeData /* A connectec open port in data mode */ + portTypeData /* A connected open port in data mode */ } PortType; typedef unsigned char Byte; diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl index f6ed418b5c4a..5550c1a4c916 100644 --- a/lib/kernel/src/application_controller.erl +++ b/lib/kernel/src/application_controller.erl @@ -312,7 +312,7 @@ control_application(AppName) -> %% different view of e.g. the distributed applications. %% This is solved by syncing the release installation. %% However, strange things may happen if a node crashes -%% and two other nodes have different opinons about who's +%% and two other nodes have different opinions about who's %% gonna start the applications. The release handler must %% shutdown each involved node in this case. %% Note that this function is used to change existing apps, @@ -767,7 +767,7 @@ handle_call({permit_application, AppName, Bool}, From, S) -> false -> case {Bool, IsLoaded, IsStarting, IsSPF, IsStarted, IsRunning} of %%------------------------ - %% permit the applicaition + %% permit the application %%------------------------ %% already running {true, _, _, _, _, {value, _Tuple}} -> diff --git a/lib/kernel/src/auth.erl b/lib/kernel/src/auth.erl index 372be7967fc6..ed89ed747a3d 100644 --- a/lib/kernel/src/auth.erl +++ b/lib/kernel/src/auth.erl @@ -293,7 +293,7 @@ handle_info({From,badcookie,rex,_Msg}, O) -> handle_info({From,badcookie,net_kernel,{'$gen_call',{From,Tag},{is_auth,_Node}}}, O) -> %% ho ho From ! {Tag, no}, {noreply, O}; -handle_info({_From,badcookie,To,{{auth_reply,N},R}}, O) ->%% Let auth replys through +handle_info({_From,badcookie,To,{{auth_reply,N},R}}, O) ->%% Let auth replies through catch To ! {{auth_reply,N},R}, {noreply, O}; handle_info({From,badcookie,Name,Mess}, Opened) -> diff --git a/lib/kernel/src/dist_ac.erl b/lib/kernel/src/dist_ac.erl index 6f93355d39b3..66bb844ca019 100644 --- a/lib/kernel/src/dist_ac.erl +++ b/lib/kernel/src/dist_ac.erl @@ -860,7 +860,7 @@ wait_dist_start(Node, Appl, Name, Nodes, PermittedNodes, S, Type) -> _ = ac_error(Type, Name, {Node, R}), monitor_node(Node, false), {Appl#appl.id, false}; - {dist_ac_weight, Name, _Weigth, Node} -> + {dist_ac_weight, Name, _Weight, Node} -> %% This is the situation: {Name, [RNode, {Node}, node()]} %% and permit(false) is called on RNode, and we sent the %% weight first. Node handled it in handle_info, and diff --git a/lib/kernel/src/erl_reply.erl b/lib/kernel/src/erl_reply.erl index a25148ac2fcc..0d6167be93c2 100644 --- a/lib/kernel/src/erl_reply.erl +++ b/lib/kernel/src/erl_reply.erl @@ -20,7 +20,7 @@ -module(erl_reply). -moduledoc false. -%% Syncronisation with erl_start (erl_interface) +%% Synchronisation with erl_start (erl_interface) -export([reply/1]). diff --git a/lib/kernel/src/erpc.erl b/lib/kernel/src/erpc.erl index db28e54bb23d..ced38ed99e7f 100644 --- a/lib/kernel/src/erpc.erl +++ b/lib/kernel/src/erpc.erl @@ -588,7 +588,7 @@ collection only containing associations of already handled or abandoned requests to [`receive_response/3`](`receive_response/3`), it will always block until a timeout determined by `Timeout` is triggered. -Note that a response might have been consumed uppon an `{erpc, badarg}` +Note that a response might have been consumed upon an `{erpc, badarg}` exception and if so, will be lost for ever. """. -doc(#{since => <<"OTP 25.0">>}). @@ -736,7 +736,7 @@ containing associations of already handled or abandoned requests to [`wait_response/3`](`wait_response/3`), it will always block until a timeout determined by `WaitTime` is triggered and then return `no_response`. -Note that a response might have been consumed uppon an `{erpc, badarg}` +Note that a response might have been consumed upon an `{erpc, badarg}` exception and if so, will be lost for ever. """. -doc(#{since => <<"OTP 25.0">>}). @@ -860,7 +860,7 @@ collection only containing associations of already handled or abandoned requests to [`check_response/3`](`check_response/3`), it will always return `no_response`. -Note that a response might have been consumed uppon an `{erpc, badarg}` +Note that a response might have been consumed upon an `{erpc, badarg}` exception and if so, will be lost for ever. """. -doc(#{since => <<"OTP 25.0">>}). diff --git a/lib/kernel/src/error_logger.erl b/lib/kernel/src/error_logger.erl index 3922b2f1e536..951a318a0939 100644 --- a/lib/kernel/src/error_logger.erl +++ b/lib/kernel/src/error_logger.erl @@ -856,7 +856,7 @@ how to configure Logger for live systems. `Request` is one of the following: - **`{open, Filename}`** - Opens log file `Filename`. Returns `ok` if - successful, or `{error, allready_have_logfile}` if logging to file is already + successful, or `{error, already_have_logfile}` if logging to file is already enabled, or an error tuple if another error occurred (for example, if `Filename` cannot be opened). The file is opened with encoding UTF-8. @@ -868,7 +868,7 @@ how to configure Logger for live systems. """. -spec logfile(Request :: {open, Filename}) -> ok | {error, OpenReason} when Filename ::file:name(), - OpenReason :: allready_have_logfile | open_error() + OpenReason :: already_have_logfile | open_error() ; (Request :: close) -> ok | {error, CloseReason} when CloseReason :: module_not_found ; (Request :: filename) -> Filename | {error, FilenameReason} when @@ -878,7 +878,7 @@ how to configure Logger for live systems. logfile({open, File}) -> case lists:member(error_logger_file_h,which_report_handlers()) of true -> - {error, allready_have_logfile}; + {error, already_have_logfile}; _ -> add_report_handler(error_logger_file_h, File) end; diff --git a/lib/kernel/src/file.erl b/lib/kernel/src/file.erl index 67ee96578593..cd387f94084d 100644 --- a/lib/kernel/src/file.erl +++ b/lib/kernel/src/file.erl @@ -2692,7 +2692,7 @@ The option list can contain the following options: Offset :: non_neg_integer(), Bytes :: non_neg_integer(), Opts :: [sendfile_option()]. -sendfile(File, _Sock, _Offet, _Bytes, _Opts) when is_pid(File) -> +sendfile(File, _Sock, _Offset, _Bytes, _Opts) when is_pid(File) -> {error, badarg}; sendfile(File, Sock, Offset, Bytes, []) -> sendfile(File, Sock, Offset, Bytes, ?MAX_CHUNK_SIZE, [], [], []); diff --git a/lib/kernel/src/gen_sctp.erl b/lib/kernel/src/gen_sctp.erl index fd2c642d92cf..dff45ab9bd3b 100644 --- a/lib/kernel/src/gen_sctp.erl +++ b/lib/kernel/src/gen_sctp.erl @@ -1156,7 +1156,7 @@ Initiates a new association for socket `Socket`, with the peer The fundamental difference between this API and `connect/*` is that the return value is that of the underlying OS `connect(2)` system call. -If `ok` is returned, the operation has been succesfully initiated, +If `ok` is returned, the operation has been successfully initiated, and the final result result of the association establishment is sent to the socket owner (controlling process) as an [`#sctp_assoc_change{}`](#record-sctp_assoc_change) event. diff --git a/lib/kernel/src/gen_tcp.erl b/lib/kernel/src/gen_tcp.erl index cd67a28d9e75..532ca660106a 100644 --- a/lib/kernel/src/gen_tcp.erl +++ b/lib/kernel/src/gen_tcp.erl @@ -822,10 +822,10 @@ Close a TCP socket. Note that in most implementations of TCP, doing a `close` does not guarantee that the data sent is delivered to the recipient. It is guaranteed that -the recepient will see all sent data before getting the close, but the +the recipient will see all sent data before getting the close, but the sender gets no indication of that. -If the sender needs to know that the recepient has received all data +If the sender needs to know that the recipient has received all data there are two common ways to achieve this: 1. Use [`gen_tcp:shutdown(Sock, write)`](`shutdown/2`) to signal that no more diff --git a/lib/kernel/src/gen_tcp_socket.erl b/lib/kernel/src/gen_tcp_socket.erl index 6f208145a30c..1d368bb3f054 100644 --- a/lib/kernel/src/gen_tcp_socket.erl +++ b/lib/kernel/src/gen_tcp_socket.erl @@ -3168,7 +3168,7 @@ error_report(Report) -> %% ------------------------------------------------------------------------- -%% formated_timestamp() -> +%% formatted_timestamp() -> %% format_timestamp(os:timestamp()). %% format_timestamp(TS) -> @@ -3179,4 +3179,4 @@ error_report(Report) -> %% d(F, A) -> %% io:format("*** [~s] ~p ~w " ++ F ++ "~n", -%% [formated_timestamp(), self(), ?MODULE | A]). +%% [formatted_timestamp(), self(), ?MODULE | A]). diff --git a/lib/kernel/src/gen_udp.erl b/lib/kernel/src/gen_udp.erl index 97fce0603d9a..558dcf8a634b 100644 --- a/lib/kernel/src/gen_udp.erl +++ b/lib/kernel/src/gen_udp.erl @@ -474,7 +474,7 @@ send(S, Host, Port, Packet) when is_port(S) -> -doc """ Send a packet to the specified destination, with ancillary data. -Equvalent to [`send(Socket, Host, Port, Packet)`](`send/4`) +Equivalent to [`send(Socket, Host, Port, Packet)`](`send/4`) regarding `Host` and `Port` and also equivalent to [`send(Socket, Destination, AncData, Packet)`](#send-4-AncData) regarding the ancillary data: `AncData`. diff --git a/lib/kernel/src/gen_udp_socket.erl b/lib/kernel/src/gen_udp_socket.erl index 970484126a77..869c589173df 100644 --- a/lib/kernel/src/gen_udp_socket.erl +++ b/lib/kernel/src/gen_udp_socket.erl @@ -1163,7 +1163,7 @@ server_read_opts() -> deliver => term, %% WHAT DO WE DO ABOUT THIS!!! %% This option, read_packets, is *currently* not used, - %% but accepted for backward compatibillity reasons. + %% but accepted for backward compatibility reasons. read_packets => 5, start_opts => [], % Just to make it settable %% XXX not implemented yet @@ -1673,7 +1673,7 @@ handle_event( #recv{info = ?completion_info(Handle)}, {#params{socket = Socket} = P, D}) -> %% ?DBG(['socket abort', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {reason, Reason}, {p, P}, {d, D}]), handle_reading(P, cleanup_recv_reply(P, D, [], Reason)); @@ -1849,26 +1849,26 @@ handle_recv(#params{recv_method = []} = P, case Reason0 of {completion_status, #{info := more_data = _INFO}} -> %% ?DBG(['completion status', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {info, INFO}, %% {p, P}, {d, D}]), emsgsize; {completion_status, more_data = _INFO} -> %% ?DBG(['completion status', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {info, INFO}, %% {p, P}, {d, D}]), emsgsize; {completion_status, #{info := INFO}} -> %% ?DBG(['completion status', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {info, INFO}, %% {p, P}, {d, D}]), INFO; {completion_status, INFO} -> %% ?DBG(['completion status', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {info, INFO}, %% {p, P}, {d, D}]), INFO; @@ -1965,7 +1965,7 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> timeout -> %% ?DBG(['error - timeout', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {p, P}, {d, D}]), Owner ! {udp_error, ModuleSocket, Reason0}, @@ -1973,7 +1973,7 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> closed -> %% ?DBG(['closed', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {p, P}, {d, D}]), Owner ! {udp_closed, ModuleSocket}, @@ -1981,7 +1981,7 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> emsgsize -> %% ?DBG(['error - emsgsize', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {p, P}, {d, D}]), Owner ! {udp_error, ModuleSocket, Reason0}, @@ -1992,34 +1992,34 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> {completion_status, #{info := more_data = _INFO}} -> %% ?DBG(['completion status', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {info, INFO}, {p, P}, {d, D}, %% {mq, mq(Owner)}]), R = emsgsize, Owner ! {udp_error, ModuleSocket, R}, %% ?DBG(['udp error sent', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {mq, mq(Owner)}]), R; {completion_status, more_data = _INFO} -> %% ?DBG(['completion status', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {info, INFO}, {p, P}, {d, D}, %% {mq, mq(Owner)}]), R = emsgsize, Owner ! {udp_error, ModuleSocket, R}, %% ?DBG(['udp error sent', - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {mq, mq(Owner)}]), R; {completion_status, #{info := INFO}} -> %% ?DBG(['completion status', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {info, INFO}, {p, P}, {d, D}]), Owner ! {udp_error, ModuleSocket, INFO}, @@ -2027,7 +2027,7 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> {completion_status, INFO} -> %% ?DBG(['completion status', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {info, INFO}, {p, P}, {d, D}]), Owner ! {udp_error, ModuleSocket, INFO}, @@ -2036,7 +2036,7 @@ cleanup_recv_reply(P, D, ActionsR, Reason0) -> _ -> %% ?DBG(['error and closed', %% {owner, Owner}, - %% {timestamp, formated_timestamp()}, + %% {timestamp, formatted_timestamp()}, %% {module_socket, ModuleSocket}, %% {reason, Reason0}, {p, P}, {d, D}]), Owner ! {udp_error, ModuleSocket, Reason0}, @@ -2507,7 +2507,7 @@ reverse(L1, L2) -> lists:reverse(L1, L2). %% ------------------------------------------------------------------------- -%% formated_timestamp() -> +%% formatted_timestamp() -> %% format_timestamp(os:timestamp()). %% format_timestamp({_N1, _N2, N3} = TS) -> diff --git a/lib/kernel/src/global.erl b/lib/kernel/src/global.erl index a562be44420d..84a33a4aa38b 100644 --- a/lib/kernel/src/global.erl +++ b/lib/kernel/src/global.erl @@ -923,7 +923,7 @@ init([]) -> %% received. The init_connect_ack messages are only there to confirm %% that both nodes has the same view of which connect session is %% ongoing. If lockers get out of sync, the lock will not be able -%% to be aquired on both nodes. The out of sync lock operation will +%% to be acquired on both nodes. The out of sync lock operation will %% be detected when the init_connect_ack message is received and the %% operation can be cancelled and then restarted. %% @@ -1493,8 +1493,8 @@ handle_info({lost_connection, NodeA, XCreationA, OpIdA, NodeB} = Msg, false -> NodeB; true -> - %% This toghether with NodeA being known by - %% us probably is unusal, but can happen + %% This together with NodeA being known by + %% us probably is unusual, but can happen %% since lost_connection messages are %% reapeted by receiving nodes. All other %% nodes will remove us, so there is no @@ -1877,7 +1877,7 @@ restart_connect(Node, MyTag, S0) -> %% and send a new init_connect... handle_nodeup(Node, S2); true -> - %% Node is down from our prespective; wait until + %% Node is down from our perspective; wait until %% global_group say Node is up by sending us a %% group_nodeup message... S2 diff --git a/lib/kernel/src/global_group.erl b/lib/kernel/src/global_group.erl index b3a673a2f87a..690a5d2070be 100644 --- a/lib/kernel/src/global_group.erl +++ b/lib/kernel/src/global_group.erl @@ -390,7 +390,7 @@ request(Req, Time) -> P when is_pid(P) -> gen_server:call(global_group, Req, Time); _Other -> - {error, global_group_not_runnig} + {error, global_group_not_running} end. %%%==================================================================================== @@ -739,7 +739,7 @@ handle_call({global_groups_changed, NewPara}, _From, case GState of no_conf -> - exit({error, 'no global_groups definiton'}); + exit({error, 'no global_groups definition'}); {error, _Err, NodeGrps} -> exit({error, {'invalid global_groups definition', NodeGrps}}); _ -> @@ -793,7 +793,7 @@ handle_call({global_groups_added, NewPara}, _From, case GState of no_conf -> - exit({error, 'no global_groups definiton'}); + exit({error, 'no global_groups definition'}); {error, _Err, NodeGrps} -> exit({error, {'invalid global_groups definition', NodeGrps}}); _ -> diff --git a/lib/kernel/src/group.erl b/lib/kernel/src/group.erl index 64ecda71719c..2dbe650d359c 100644 --- a/lib/kernel/src/group.erl +++ b/lib/kernel/src/group.erl @@ -954,23 +954,23 @@ get_chars_echo_off1(Drv, Shell) -> end. format_expression(Cont, Drv) -> - FormatingCommand = application:get_env(stdlib, format_shell_func, default), + FormattingCommand = application:get_env(stdlib, format_shell_func, default), Buffer = edlin:current_line(Cont), try - case FormatingCommand of + case FormattingCommand of default -> string:trim(Buffer, trailing, "\n"); {M,F} when is_atom(M), is_atom(F) -> M:F(Buffer); - FormatingCommand1 when is_list(FormatingCommand1) -> - format_expression1(Buffer, FormatingCommand1) + FormattingCommand1 when is_list(FormattingCommand1) -> + format_expression1(Buffer, FormattingCommand1) end catch _:_ -> - send_drv_reqs(Drv, [{put_chars, unicode, io_lib:format("* Bad format function: ~tp~n", [FormatingCommand])}]), + send_drv_reqs(Drv, [{put_chars, unicode, io_lib:format("* Bad format function: ~tp~n", [FormattingCommand])}]), _ = shell:format_shell_func(default), string:trim(Buffer, trailing, "\n") end. -format_expression1(Buffer, FormatingCommand) -> +format_expression1(Buffer, FormattingCommand) -> %% Write the current expression to a file, format it with a formatting tool %% provided by the user and read the file back MkTemp = case os:type() of @@ -981,7 +981,7 @@ format_expression1(Buffer, FormatingCommand) -> end, TmpFile = string:chomp(MkTemp) ++ ".erl", _ = file:write_file(TmpFile, unicode:characters_to_binary(Buffer, unicode)), - FormattingCommand1 = string:replace(FormatingCommand, "${file}", TmpFile), + FormattingCommand1 = string:replace(FormattingCommand, "${file}", TmpFile), _ = os:cmd(FormattingCommand1), {ok, Content} = file:read_file(TmpFile), _ = file:del_dir_r(TmpFile), diff --git a/lib/kernel/src/heart.erl b/lib/kernel/src/heart.erl index 83786d7a3c34..4ed34b5fd3df 100644 --- a/lib/kernel/src/heart.erl +++ b/lib/kernel/src/heart.erl @@ -108,7 +108,7 @@ In the following descriptions, all functions fail with reason `badarg` if %%% This is a rewrite of pre_heart from BS.3. %%% %%% The purpose of this process-module is to act as a supervisor -%%% of the entire erlang-system. This 'heart' beats with a frequence +%%% of the entire erlang-system. This 'heart' beats with a frequency %%% satisfying an external port program *not* reboot the entire %%% system. If however the erlang-emulator would hang, a reboot is %%% then needed. diff --git a/lib/kernel/src/inet.erl b/lib/kernel/src/inet.erl index ee4cbcc8101e..fdd3b474f8b0 100644 --- a/lib/kernel/src/inet.erl +++ b/lib/kernel/src/inet.erl @@ -329,7 +329,7 @@ Function `parse_address/1` can be useful: element(1, Record) =:= element(1, RS), tuple_size(Record) =:= element(2, RS)). -%% Two kinds of debug macros (depnds on what you need to debug) +%% Two kinds of debug macros (depends on what you need to debug) %% -define(DBG(T), erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})). %% -define(DBG(F, A), io:format("~w -> " ++ F ++ "~n", [?FUNCTION_NAME | A])). %% -define(DBG(F), ?DBG(F, [])). @@ -2721,7 +2721,7 @@ getfd(Socket) -> %% -doc """ -Resolve a host to an address, in a specific addresss family. +Resolve a host to an address, in a specific address family. Returns the [IP address](`t:ip_address/0`) for `Host` as a tuple of integers. `Host` can be an [IP address](`t:ip_address/0`), a single `t:hostname/0`, diff --git a/lib/kernel/src/inet_db.erl b/lib/kernel/src/inet_db.erl index 364f81bf2357..fcade7d77ec3 100644 --- a/lib/kernel/src/inet_db.erl +++ b/lib/kernel/src/inet_db.erl @@ -709,13 +709,13 @@ make_hostent(Name, Addrs, Aliases, ?S_AAAA) -> h_addr_list = Addrs, h_aliases = Aliases }; -make_hostent(Name, Datas, Aliases, Type) -> +make_hostent(Name, Data, Aliases, Type) -> %% Use #hostent{} for other Types as well ! #hostent { h_name = Name, h_addrtype = Type, - h_length = length(Datas), - h_addr_list = Datas, + h_length = length(Data), + h_addr_list = Data, h_aliases = Aliases }. @@ -1869,7 +1869,7 @@ eq_domains([A | As], [B | Bs]) -> is_integer(B), 0 =< B, B =< 16#10FFFF -> %% An upper bound of 255 would be right right now, %% but this algorithm works for any integer. That - %% guard just gives the compiler the opportuinity + %% guard just gives the compiler the opportunity %% to optimize bit operations for machine word size, %% so we might as well use the Unicode upper bound instead. Xor = (A bxor B), diff --git a/lib/kernel/src/inet_dns.hrl b/lib/kernel/src/inet_dns.hrl index d3b5930b4c2e..bed2ab4b4fca 100644 --- a/lib/kernel/src/inet_dns.hrl +++ b/lib/kernel/src/inet_dns.hrl @@ -202,7 +202,7 @@ { header, %% dns_header record qdlist = [], %% list of question (for UPDATE 'zone') entries - anlist = [], %% list of answer (for UPDATE 'prequisites') entries + anlist = [], %% list of answer (for UPDATE 'prerequisites') entries nslist = [], %% list of authority (for UPDATE 'update') entries arlist = [] %% list of resource entries }). diff --git a/lib/kernel/src/inet_dns_tsig.erl b/lib/kernel/src/inet_dns_tsig.erl index aa8206c09aa4..b0195a9a7d7a 100644 --- a/lib/kernel/src/inet_dns_tsig.erl +++ b/lib/kernel/src/inet_dns_tsig.erl @@ -25,7 +25,7 @@ %% RFC 8945: Secret Key Transaction Authentication for DNS (TSIG) %% WARNING: in the spirit of inet_dns.erl, this module only handles the -%% cryptographic operations and does not absolve you of your responsibities +%% cryptographic operations and does not absolve you of your responsibilities %% that include: %% * implement a truncation policy as per RFC8945, section 5.2 %% * verifying that for TSIG over TCP the last message contains a TSIG RR diff --git a/lib/kernel/src/logger_server.erl b/lib/kernel/src/logger_server.erl index 2beb248e6850..9dac1d4f0e16 100644 --- a/lib/kernel/src/logger_server.erl +++ b/lib/kernel/src/logger_server.erl @@ -380,7 +380,7 @@ call(Request) when is_tuple(Request) -> Action == add_handler; Action == remove_handler; Action == add_filter; Action == remove_filter; Action == change_config -> - {error,{attempting_syncronous_call_to_self,Request}}; + {error,{attempting_synchronous_call_to_self,Request}}; _ -> gen_server:call(?SERVER,Request,?DEFAULT_LOGGER_CALL_TIMEOUT) end. diff --git a/lib/kernel/src/net.erl b/lib/kernel/src/net.erl index 1513516bac71..956983a2bf59 100644 --- a/lib/kernel/src/net.erl +++ b/lib/kernel/src/net.erl @@ -275,7 +275,7 @@ getnameinfo(SockAddr) -> getnameinfo(SockAddr, undefined). -doc """ -Address-to-name translation in a protocol-independant manner. +Address-to-name translation in a protocol-independent manner. This function is the inverse of [`getaddrinfo`](`getaddrinfo/1`). It converts a socket address to a corresponding host and service. @@ -607,7 +607,7 @@ win_getifaddrs_iat3(Name, connecting -> [up, pointtopoint]; connected -> - [up, runnning, pointtopoint]; + [up, running, pointtopoint]; operational -> [up, running]; _ -> @@ -710,7 +710,7 @@ win_getifaddrs_aa3(Name, connecting -> [up, pointtopoint]; connected -> - [up, runnning, pointtopoint]; + [up, running, pointtopoint]; operational -> [up, running]; _ -> @@ -1025,7 +1025,7 @@ if_name2index(Name) when is_list(Name) -> catch C : E : S when (C =:= error) andalso (E =:= notsup) -> %% This is *most likely* Windows, so try that. - %% If not (another catch), raise the original catched error. + %% If not (another catch), raise the original caught error. try win_name2index(Name) catch _:_:_ -> @@ -1054,7 +1054,7 @@ if_index2name(Idx) when is_integer(Idx) -> catch C : E : S when (C =:= error) andalso (E =:= notsup) -> %% This is *most likely* Windows, so try that. - %% If not (another catch), raise the original catched error. + %% If not (another catch), raise the original caught error. try win_index2name(Idx) catch _:_:_ -> @@ -1082,7 +1082,7 @@ if_names() -> catch C : E : S when (C =:= error) andalso (E =:= notsup) -> %% This is *most likely* Windows, so try that. - %% If not (another catch), raise the original catched error. + %% If not (another catch), raise the original caught error. try {ok, win_names()} catch _:_:_ -> diff --git a/lib/kernel/src/net_kernel.erl b/lib/kernel/src/net_kernel.erl index f99e847c10cd..00ce6e6c1c76 100644 --- a/lib/kernel/src/net_kernel.erl +++ b/lib/kernel/src/net_kernel.erl @@ -204,13 +204,13 @@ in the Erlang Reference Manual. -record(tick, {ticker :: pid(), %% ticker time :: pos_integer(), %% net tick time (ms) - intensity :: 4..1000 %% ticks until timout + intensity :: 4..1000 %% ticks until timeout }). -record(tick_change, {ticker :: pid(), %% ticker time :: pos_integer(), %% net tick time (ms) - intensity :: 4..1000, %% ticks until timout + intensity :: 4..1000, %% ticks until timeout how :: 'longer' | 'shorter' %% What type of change }). @@ -848,7 +848,7 @@ Turns a non-distributed node into a distributed node by starting `net_kernel` and other necessary processes. `Options` list can only be exactly one of the following lists (order is -imporant): +important): - **`[Name]`** - The same as `net_kernel:start([Name, longnames, 15000])`. @@ -1566,7 +1566,7 @@ handle_info({AcceptPid, {wait_pending, Node}}, State) -> ?debug({net_kernel, wait_pending, kill, OldCtrlr, new, AcceptPid}), exit(OldCtrlr, wait_pending); _ -> - %% Old connnection maybe already gone + %% Old connection maybe already gone ignore end, %% Exiting controller will trigger {Kernel,pending} reply diff --git a/lib/kernel/src/rpc.erl b/lib/kernel/src/rpc.erl index 950913d973e5..02d31f07f867 100644 --- a/lib/kernel/src/rpc.erl +++ b/lib/kernel/src/rpc.erl @@ -117,7 +117,7 @@ some specific side effects on the remote node. %% The rex server may receive a huge amount of %% messages. Make sure that they are stored off heap to -%% avoid exessive GCs. +%% avoid excessive GCs. -define(SPAWN_OPTS, [{spawn_opt,[{message_queue_data,off_heap}]}]). @@ -135,7 +135,7 @@ start() -> start_link() -> %% The rex server process may receive a huge amount of %% messages. Make sure that they are stored off heap to - %% avoid exessive GCs. + %% avoid excessive GCs. gen_server:start_link({local,?NAME}, ?MODULE, [], ?SPAWN_OPTS). -doc false. diff --git a/lib/kernel/src/trace.erl b/lib/kernel/src/trace.erl index 087bf005e4f3..93874b47c9f8 100644 --- a/lib/kernel/src/trace.erl +++ b/lib/kernel/src/trace.erl @@ -82,7 +82,7 @@ on the same local node as the call is made. To trace remote nodes use `m:dbg` or > The main difference is the old functions operate on a single static > trace session per node. That could impose the problem that different > users and tools would interfere with each other's trace settings. The new trace -> functions in this module all operate on dynamically created trace sesssions +> functions in this module all operate on dynamically created trace sessions > isolated from each other. Also, this makes it easier to safely disable all trace > settings when done by a single call to `session_destroy/1`. > @@ -1268,7 +1268,7 @@ functions. The only things not cleaned up are trace messages that have already been sent. Returns `true` if the session was active. Returns `false` if the session had -already been destroyed by either an earler call to this function or the garbage +already been destroyed by either an earlier call to this function or the garbage collector. """. -doc #{ since => <<"OTP 27.0">> }. diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl index 74b2a7d69c98..6dd3da52b020 100644 --- a/lib/kernel/test/disk_log_SUITE.erl +++ b/lib/kernel/test/disk_log_SUITE.erl @@ -3236,7 +3236,7 @@ chunk(Conf) when is_list(Conf) -> ok = disk_log:close(n), file:delete(File), - %% Minimal MD5-proctected term, and maximal unprotected term. + %% Minimal MD5-protected term, and maximal unprotected term. %% A chunk ends in the middle of the MD5-sum. MD5term = mk_bytes(64*1024-8), NotMD5term = mk_bytes((64*1024-8)-1), diff --git a/lib/kernel/test/erl_distribution_SUITE.erl b/lib/kernel/test/erl_distribution_SUITE.erl index dc6f9072a2f9..058e7e6bfb93 100644 --- a/lib/kernel/test/erl_distribution_SUITE.erl +++ b/lib/kernel/test/erl_distribution_SUITE.erl @@ -2270,13 +2270,13 @@ net_kernel_start(Config) when is_list(Config) -> net_kernel_start_test(MyName, 120, 8, true, true), net_kernel_start_test(MyName, undefined, undefined, undefined, undefined). -net_kernel_start_test(MyName, NetTickTime, NetTickIntesity, DistListen, Hidden) -> +net_kernel_start_test(MyName, NetTickTime, NetTickIntensity, DistListen, Hidden) -> TestNameStr = "net_kernel_start_test_node-" ++ integer_to_list(erlang:system_time(seconds)) ++ "-" ++ integer_to_list(erlang:unique_integer([monotonic,positive])), TestNode = list_to_atom(TestNameStr ++ "@" ++ atom_to_list(gethostname())), CmdLine = net_kernel_start_cmdline(MyName, list_to_atom(TestNameStr), - NetTickTime, NetTickIntesity, DistListen, Hidden), + NetTickTime, NetTickIntensity, DistListen, Hidden), io:format("Starting test node ~p: ~s~n", [TestNode, CmdLine]), case open_port({spawn, CmdLine}, []) of Port when is_port(Port) -> diff --git a/lib/kernel/test/erl_distribution_wb_SUITE.erl b/lib/kernel/test/erl_distribution_wb_SUITE.erl index 067209a34dfe..0679ad45a41e 100644 --- a/lib/kernel/test/erl_distribution_wb_SUITE.erl +++ b/lib/kernel/test/erl_distribution_wb_SUITE.erl @@ -814,8 +814,8 @@ recv_message(Socket) -> {ok,Data} -> B0 = list_to_binary(Data), <> = B0, - {Header,Siz} = binary_to_term(B1,[used]), - <<_:Siz/binary,B2/binary>> = B1, + {Header,Size} = binary_to_term(B1,[used]), + <<_:Size/binary,B2/binary>> = B1, Message = case (catch binary_to_term(B2)) of {'EXIT', _} -> {could_not_digest_message,B2}; diff --git a/lib/kernel/test/error_logger_SUITE.erl b/lib/kernel/test/error_logger_SUITE.erl index 5050ed1af8de..99bfeb68fbd8 100644 --- a/lib/kernel/test/error_logger_SUITE.erl +++ b/lib/kernel/test/error_logger_SUITE.erl @@ -75,7 +75,7 @@ end_per_group(_GroupName, Config) -> off_heap(_Config) -> %% The error_logger process may receive a huge amount of %% messages. Make sure that they are stored off heap to - %% avoid exessive GCs. + %% avoid excessive GCs. MQD = message_queue_data, {MQD,off_heap} = process_info(whereis(error_logger), MQD), ok. diff --git a/lib/kernel/test/esock_misc/socket_client.erl b/lib/kernel/test/esock_misc/socket_client.erl index edb73d432f9b..c0dad410111b 100644 --- a/lib/kernel/test/esock_misc/socket_client.erl +++ b/lib/kernel/test/esock_misc/socket_client.erl @@ -483,7 +483,7 @@ which_addr2(Domain, [_|IFO]) -> %% --- -%% formated_timestamp() -> +%% formatted_timestamp() -> %% format_timestamp(os:timestamp()). %% format_timestamp(Now) -> diff --git a/lib/kernel/test/esock_misc/socket_lib.erl b/lib/kernel/test/esock_misc/socket_lib.erl index e401a3195c5d..8407ab9f90a6 100644 --- a/lib/kernel/test/esock_misc/socket_lib.erl +++ b/lib/kernel/test/esock_misc/socket_lib.erl @@ -100,12 +100,12 @@ p(F, A) -> p(SName, F, A) -> io:format("[~s,~p][~s] " ++ F ++ "~n", - [SName,self(),formated_timestamp()|A]). + [SName,self(),formatted_timestamp()|A]). %% --- -formated_timestamp() -> +formatted_timestamp() -> format_timestamp(os:timestamp()). format_timestamp(Now) -> diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl index cdb28b3ee449..49155692e827 100644 --- a/lib/kernel/test/file_SUITE.erl +++ b/lib/kernel/test/file_SUITE.erl @@ -493,7 +493,7 @@ um_check_unicode(_Utf8Bin, {ok, _ListOrBin}, _, _UTF8_) -> %% end, %% io:format("In: ~w~n", [binary_to_list(Utf8Bin)]), %% io:format("Ut: ~w~n", [List]), - ?THROW_ERROR({shoud_be, no_translation}). + ?THROW_ERROR({should_be, no_translation}). um_filename(Bin, Dir, Options) when is_binary(Bin) -> um_filename(binary_to_list(Bin), Dir, Options); diff --git a/lib/kernel/test/file_SUITE_data/realmen.html b/lib/kernel/test/file_SUITE_data/realmen.html index eaaa65523a9f..157e7d2fadd5 100644 --- a/lib/kernel/test/file_SUITE_data/realmen.html +++ b/lib/kernel/test/file_SUITE_data/realmen.html @@ -476,7 +476,7 @@

THE FUTURE

will be Real Programmers willing to jump in and Solve The Problem, saving the documentation for later. Long live FORTRAN!

-

ACKNOWLEGEMENT

+

ACKNOWLEDGEMENT

I would like to thank Jan E., Dave S., Rich G., Rich E. for their help in characterizing the Real Programmer, Heather B. for the diff --git a/lib/kernel/test/gen_tcp_misc_SUITE.erl b/lib/kernel/test/gen_tcp_misc_SUITE.erl index d57ae645e8ba..ef31bf42aa7b 100644 --- a/lib/kernel/test/gen_tcp_misc_SUITE.erl +++ b/lib/kernel/test/gen_tcp_misc_SUITE.erl @@ -5785,7 +5785,7 @@ connector(Config, AccPort, Tester) -> ManyPorts = open_ports([]), ?P("[connector] length(ManyPorts): ~p", [length(ManyPorts)]), Tester ! {self(), sync}, - ?P("[connector] await continute from tester (~p)", [Tester]), + ?P("[connector] await continue from tester (~p)", [Tester]), receive {Tester, continue} -> timer:sleep(100) end, ?P("[connector] begin connecting"), ConnF = @@ -6481,7 +6481,7 @@ send_timeout_close(Sock) -> Pid ! {close, Sock}, ok; {error, Reason} -> - ?P("failed transfering ownership to closer process: " + ?P("failed transferring ownership to closer process: " "~n ~p", [Reason]), exit(Pid, kill), (catch gen_tcp:close(Sock)) diff --git a/lib/kernel/test/gen_udp_SUITE.erl b/lib/kernel/test/gen_udp_SUITE.erl index 10f925dd6fb5..1ff5a3947fad 100644 --- a/lib/kernel/test/gen_udp_SUITE.erl +++ b/lib/kernel/test/gen_udp_SUITE.erl @@ -1041,7 +1041,7 @@ do_open_fd(Config) when is_list(Config) -> "~n ~p", [inet:info(Socket)]), (catch gen_udp:close(Socket)), (catch gen_udp:close(S1)), - ct:fail(unexpected_succes) + ct:fail(unexpected_success) end, ?P("try open second socket with FD = ~w " @@ -2162,7 +2162,7 @@ implicit_inet6(Config, S1, Active, Addr) -> {Addr,P2} = ok(inet:sockname(S2)), ?P("send ping on \"local\" socket (to ~p:~p)", [Addr, P2]), %% On some platforms its allowed to specify address and port - %% (that is; when useing sendto) *even* if the socket is connected + %% (that is; when using sendto) *even* if the socket is connected %% (assuming the send destination is the same as connected destination). %% But on other platforms, e.g. FreeBSD, this is *not* allowed! %% Linux: diff --git a/lib/kernel/test/global_SUITE.erl b/lib/kernel/test/global_SUITE.erl index 6719e2152452..5dacaa1cc442 100644 --- a/lib/kernel/test/global_SUITE.erl +++ b/lib/kernel/test/global_SUITE.erl @@ -2200,7 +2200,7 @@ otp_5737(Config) when is_list(Config) -> connect_all_false(Config) when is_list(Config) -> %% OTP-6931. Ignore nodeup when connect_all=false. connect_all_false_test("-connect_all false", Config), - %% OTP-17934: multipl -connect_all false and kernel parameter connect_all + %% OTP-17934: multiple -connect_all false and kernel parameter connect_all connect_all_false_test("-connect_all false -connect_all false", Config), connect_all_false_test("-kernel connect_all false", Config), ok. diff --git a/lib/kernel/test/inet_SUITE.erl b/lib/kernel/test/inet_SUITE.erl index 2b9ee77e52e3..d2af7884e12b 100644 --- a/lib/kernel/test/inet_SUITE.erl +++ b/lib/kernel/test/inet_SUITE.erl @@ -40,7 +40,7 @@ ipv4_to_ipv6/0, ipv4_to_ipv6/1, host_and_addr/0, host_and_addr/1, t_gethostnative/1, - gethostnative_parallell/1, cname_loop/1, + gethostnative_parallel/1, cname_loop/1, missing_hosts_reload/1, hosts_file_quirks/1, gethostnative_soft_restart/0, gethostnative_soft_restart/1, gethostnative_debug_level/0, gethostnative_debug_level/1, @@ -57,7 +57,7 @@ -export([ get_hosts/1, get_ipv6_hosts/1, parse_hosts/1, parse_address/1, - kill_gethost/0, parallell_gethost/0, test_netns/0 + kill_gethost/0, parallel_gethost/0, test_netns/0 ]). @@ -73,7 +73,7 @@ all() -> t_gethostbyaddr, t_gethostbyname, t_gethostbyname_empty, t_getaddr, t_gethostbyaddr_v6, t_gethostbyname_v6, t_getaddr_v6, ipv4_to_ipv6, host_and_addr, is_ip_address, {group, parse}, - t_gethostnative, gethostnative_parallell, cname_loop, + t_gethostnative, gethostnative_parallel, cname_loop, missing_hosts_reload, hosts_file_quirks, gethostnative_debug_level, gethostnative_soft_restart, lookup_bad_search_option, @@ -566,7 +566,7 @@ try_host({Ip0, Host}) -> ok. %% Get all hosts from the system using 'ypcat hosts' or the local -%% equvivalent. +%% equivalent. get_hosts(_Config) -> case os:type() of @@ -623,12 +623,12 @@ parse_hosts(Config) when is_list(Config) -> inet_parse:resolv(ResolvErr1). parse_address(Config) when is_list(Config) -> - V4Reversable = + V4Reversible = [{{0,0,0,0},"0.0.0.0"}, {{1,2,3,4},"1.2.3.4"}, {{253,252,251,250},"253.252.251.250"}, {{1,2,255,254},"1.2.255.254"}], - V6Reversable = + V6Reversible = [{{0,0,0,0,0,0,0,0},"::"}, {{0,0,0,0,0,0,0,1},"::1"}, {{0,0,0,0,0,0,0,2},"::0.0.0.2"}, @@ -726,7 +726,7 @@ parse_address(Config) when is_list(Config) -> |[{list_to_tuple(P++[(D1 bsl 8) bor D2,(D3 bsl 8) bor D4]), Q++S} || {{D1,D2,D3,D4},S} <- - tl(V4Reversable), + tl(V4Reversible), {P,Q} <- [{[0,0,0,0,0,16#ffff],"::ffff:"}, {[0,0,0,0,0,0],"::"}]]], @@ -758,7 +758,7 @@ parse_address(Config) when is_list(Config) -> ++ [{{P,0,0,0,0,D2,(D1 bsl 8) bor D2,(D3 bsl 8) bor D4}, Q++erlang:integer_to_list(D2, 16)++":"++S} - || {{D1,D2,D3,D4},S} <- V4Reversable, + || {{D1,D2,D3,D4},S} <- V4Reversible, {P,Q} <- [{16#2001,"2001::"},{16#177,"177::"},{16#ff0,"Ff0::"}]], V4Err = @@ -809,17 +809,17 @@ parse_address(Config) when is_list(Config) -> t_parse_address (parse_ipv6strict_address, true, - V6Reversable++V6Err++V4Err), + V6Reversible++V6Err++V4Err), t_parse_address (parse_ipv4_address, false, - V4Reversable++V4Sloppy++V4Err++V6Err++[S || {_,S} <- V6Reversable]), + V4Reversible++V4Sloppy++V4Err++V6Err++[S || {_,S} <- V6Reversible]), t_parse_address (parse_ipv4strict_address, true, - V4Reversable++V4Err++V6Err++[S || {_,S} <- V4Sloppy++V6Reversable]). + V4Reversable++V4Err++V6Err++[S || {_,S} <- V4Sloppy++V6Reversible]). -t_parse_address(Func, _Reversable, []) -> +t_parse_address(Func, _Reversible, []) -> io:format("~p done.~n", [Func]), ok; t_parse_address(Func, Reversible, [{Addr,String}|L]) -> @@ -980,31 +980,31 @@ t_gethostnative(Config) when is_list(Config) -> end. %% Check that the emulator survives crashes in gethost_native. -gethostnative_parallell(Config) when is_list(Config) -> +gethostnative_parallel(Config) when is_list(Config) -> {ok,Hostname} = inet:gethostname(), {ok,_} = inet:gethostbyname(Hostname), case whereis(inet_gethost_native) of Pid when is_pid(Pid) -> - do_gethostnative_parallell(); + do_gethostnative_parallel(); _ -> {skipped, "Not running native gethostbyname"} end. -do_gethostnative_parallell() -> +do_gethostnative_parallel() -> {ok,Peer,Node} = ?CT_PEER(), - ok = rpc:call(Node, ?MODULE, parallell_gethost, []), + ok = rpc:call(Node, ?MODULE, parallel_gethost, []), receive after 10000 -> ok end, pong = net_adm:ping(Node), peer:stop(Peer), ok. -parallell_gethost() -> +parallel_gethost() -> {ok,Hostname} = inet:gethostname(), process_flag(trap_exit,true), - parallell_gethost_loop(10, Hostname). + parallel_gethost_loop(10, Hostname). -parallell_gethost_loop(0, _) -> ok; -parallell_gethost_loop(N, Hostname) -> +parallel_gethost_loop(0, _) -> ok; +parallel_gethost_loop(N, Hostname) -> case whereis(inet_gethost_native) of Pid when is_pid(Pid) -> true = exit(Pid,kill); @@ -1015,7 +1015,7 @@ parallell_gethost_loop(N, Hostname) -> L = spawn_gethosters(Hostname, 10), release_gethosters(L), collect_gethosters(10), - parallell_gethost_loop(N-1, Hostname). + parallel_gethost_loop(N-1, Hostname). spawn_gethosters(_, 0) -> []; diff --git a/lib/kernel/test/inet_res_SUITE.erl b/lib/kernel/test/inet_res_SUITE.erl index c62c5ca02899..ab3b3f2f59a2 100644 --- a/lib/kernel/test/inet_res_SUITE.erl +++ b/lib/kernel/test/inet_res_SUITE.erl @@ -1479,7 +1479,7 @@ update(Config) when is_list(Config) -> % note for implementors reading this, the usage of % inet_dns_tsig.erl is identical except you do not need -% to inspect the reponse for the presence of a TSIG RR +% to inspect the response for the presence of a TSIG RR tsig_client(Config) when is_list(Config) -> {NSIP,NSPort} = ns(Config), Domain = "otptest", diff --git a/lib/kernel/test/kernel_test_lib.erl b/lib/kernel/test/kernel_test_lib.erl index bb0c19292d5d..ec5df8c2b9f6 100644 --- a/lib/kernel/test/kernel_test_lib.erl +++ b/lib/kernel/test/kernel_test_lib.erl @@ -36,7 +36,7 @@ stop_node/1]). -export([f/2, print/1, print/2, - formated_timestamp/0]). + formatted_timestamp/0]). -export([good_hosts/1, lookup/3]). -export([ @@ -1909,7 +1909,7 @@ analyze_and_print_win_host_info(Version) -> %% 'VirtFactor' will be 0 unless virtual VirtFactor = win_virt_factor(SysMod), - %% On some machines this is a badly formated string + %% On some machines this is a badly formatted string %% (contains a char of 255), so we need to do some nasty stuff... MemFactor = try @@ -2385,7 +2385,7 @@ tc_end(Result) when is_list(Result) -> %% conditions. %% Pre: A fun that is nominally part of the test case %% but is an initiation that must be "undone". This is -%% done by the Post fun (regardless if the TC is successfull +%% done by the Post fun (regardless if the TC is successful %% or not). Example: Starts a couple of nodes, %% TC: The test case fun %% Post: A fun that undo what was done by the Pre fun. @@ -2525,7 +2525,7 @@ tc_print(F, Before, After) -> tc_print(F, A, Before, After) -> Name = tc_which_name(), FStr = f("*** [~s][~s][~p] " ++ F ++ "~n", - [formated_timestamp(),Name,self()|A]), + [formatted_timestamp(),Name,self()|A]), io:format(user, Before ++ FStr ++ After, []). tc_which_name() -> @@ -2934,7 +2934,7 @@ ts(us) -> f(F, A) -> lists:flatten(io_lib:format(F, A)). -formated_timestamp() -> +formatted_timestamp() -> format_timestamp(os:timestamp()). format_timestamp({_N1, _N2, N3} = TS) -> @@ -2948,4 +2948,4 @@ print(F) -> print(F, []). print(F, A) -> - io:format("~s ~p " ++ F ++ "~n", [formated_timestamp(), self() | A]). + io:format("~s ~p " ++ F ++ "~n", [formatted_timestamp(), self() | A]). diff --git a/lib/kernel/test/kernel_test_lib.hrl b/lib/kernel/test/kernel_test_lib.hrl index b3b8a6ba0acc..e132895a8092 100644 --- a/lib/kernel/test/kernel_test_lib.hrl +++ b/lib/kernel/test/kernel_test_lib.hrl @@ -73,7 +73,7 @@ -define(F(FORMAT, ARGS), ?LIB:f((FORMAT), (ARGS))). -define(P(F), ?LIB:print(F)). -define(P(F,A), ?LIB:print(F, A)). --define(FTS(), ?LIB:formated_timestamp()). +-define(FTS(), ?LIB:formatted_timestamp()). -define(SECS(I), timer:seconds(I)). -define(MINS(I), timer:minutes(I)). diff --git a/lib/kernel/test/logger_formatter_SUITE.erl b/lib/kernel/test/logger_formatter_SUITE.erl index a2f825f4a99f..c383c5e27d83 100644 --- a/lib/kernel/test/logger_formatter_SUITE.erl +++ b/lib/kernel/test/logger_formatter_SUITE.erl @@ -177,13 +177,13 @@ single_line(_Config) -> String3 = format(info,{"~s~p~n~s~p~n",[Prefix, lists:seq(1,10), Prefix, - #{a=>map,with=>a,few=>accociations}]}, + #{a=>map,with=>a,few=>associations}]}, #{time=>Time}, #{single_line=>true}), ct:log(String3), match = re:run(String3,"\\[1,2,3,4,5,6,7,8,9,10\\]",[{capture,none}]), match = re:run(String3, - "#{((a => map|with => a|few => accociations)[,}]){3}", + "#{((a => map|with => a|few => associations)[,}]){3}", [{capture,none}]), %% This part is added to make sure that the previous test made @@ -192,7 +192,7 @@ single_line(_Config) -> String4 = format(info,{"~s~p~n~s~p~n",[Prefix, lists:seq(1,10), Prefix, - #{a=>map,with=>a,few=>accociations}]}, + #{a=>map,with=>a,few=>associations}]}, #{time=>Time}, #{single_line=>false}), ct:log(String4), diff --git a/lib/kernel/test/net_SUITE.erl b/lib/kernel/test/net_SUITE.erl index a19666dd1a9a..e28105a964bc 100644 --- a/lib/kernel/test/net_SUITE.erl +++ b/lib/kernel/test/net_SUITE.erl @@ -1144,7 +1144,7 @@ skip(Reason) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -formated_timestamp() -> +formatted_timestamp() -> format_timestamp(os:timestamp()). format_timestamp({_N1, _N2, _N3} = TS) -> @@ -1195,7 +1195,7 @@ i(F) -> i(F, []). i(F, A) -> - FStr = f("[~s] " ++ F, [formated_timestamp()|A]), + FStr = f("[~s] " ++ F, [formatted_timestamp()|A]), io:format(user, FStr ++ "~n", []), io:format(FStr, []). diff --git a/lib/kernel/test/prim_file_SUITE_data/realmen.html b/lib/kernel/test/prim_file_SUITE_data/realmen.html index eaaa65523a9f..157e7d2fadd5 100644 --- a/lib/kernel/test/prim_file_SUITE_data/realmen.html +++ b/lib/kernel/test/prim_file_SUITE_data/realmen.html @@ -476,7 +476,7 @@

THE FUTURE

will be Real Programmers willing to jump in and Solve The Problem, saving the documentation for later. Long live FORTRAN!

-

ACKNOWLEGEMENT

+

ACKNOWLEDGEMENT

I would like to thank Jan E., Dave S., Rich G., Rich E. for their help in characterizing the Real Programmer, Heather B. for the diff --git a/lib/kernel/test/ram_file_SUITE_data/realmen.html b/lib/kernel/test/ram_file_SUITE_data/realmen.html index eaaa65523a9f..157e7d2fadd5 100644 --- a/lib/kernel/test/ram_file_SUITE_data/realmen.html +++ b/lib/kernel/test/ram_file_SUITE_data/realmen.html @@ -476,7 +476,7 @@

THE FUTURE

will be Real Programmers willing to jump in and Solve The Problem, saving the documentation for later. Long live FORTRAN!

-

ACKNOWLEGEMENT

+

ACKNOWLEDGEMENT

I would like to thank Jan E., Dave S., Rich G., Rich E. for their help in characterizing the Real Programmer, Heather B. for the diff --git a/lib/kernel/test/rpc_SUITE.erl b/lib/kernel/test/rpc_SUITE.erl index 8f77a9a30e31..b83d7c3cb09a 100644 --- a/lib/kernel/test/rpc_SUITE.erl +++ b/lib/kernel/test/rpc_SUITE.erl @@ -88,7 +88,7 @@ end_per_group(_GroupName, Config) -> off_heap(_Config) -> %% The rex server process may receive a huge amount of %% messages. Make sure that they are stored off heap to - %% avoid exessive GCs. + %% avoid excessive GCs. MQD = message_queue_data, {MQD,off_heap} = process_info(whereis(rex), MQD), ok. @@ -819,7 +819,7 @@ cast_old_against_new_test([NodeOld], [NodeCurr]) -> true = rpc:cast(NodeOld, erlang, send, [Me, {Ref, 3}]), true = rpc:cast(NodeCurr, erlang, send, [Me, {Ref, 4}]), - receive Msg -> error({unexcpected_message, Msg}) + receive Msg -> error({unexpected_message, Msg}) after 1000 -> ok end. diff --git a/lib/kernel/test/socket_api_SUITE.erl b/lib/kernel/test/socket_api_SUITE.erl index 0a3308785c5e..fb4ad23e8faa 100644 --- a/lib/kernel/test/socket_api_SUITE.erl +++ b/lib/kernel/test/socket_api_SUITE.erl @@ -4690,7 +4690,7 @@ api_ffd_open_and_info(InitState) -> %% %% This is *not* how its intended to be used. %% That an erlang process creating a socket and then handing over the -%% file descriptor to another erlang process. *But* its a convient way +%% file descriptor to another erlang process. *But* its a convenient way %% to test it! %% %% @@ -4722,7 +4722,7 @@ api_ffd_open_and_open_wod_and_send_udp4(_Config) when is_list(_Config) -> %% %% This is *not* how its intended to be used. %% That an erlang process creating a socket and then handing over the -%% file descriptor to another erlang process. *But* its a convient way +%% file descriptor to another erlang process. *But* its a convenient way %% to test it! %% %% @@ -5414,7 +5414,7 @@ api_ffd_open_and_open_and_send_udp2(InitState) -> %% %% This is *not* how its intended to be used. %% That an erlang process creating a socket and then handing over the -%% file descriptor to another erlang process. *But* its a convient way +%% file descriptor to another erlang process. *But* its a convenient way %% to test it! %% %% @@ -5445,7 +5445,7 @@ api_ffd_open_connect_and_open_wod_and_send_tcp4(_Config) when is_list(_Config) - %% %% This is *not* how its intended to be used. %% That an erlang process creating a socket and then handing over the -%% file descriptor to another erlang process. *But* its a convient way +%% file descriptor to another erlang process. *But* its a convenient way %% to test it! %% %% diff --git a/lib/kernel/test/socket_test_evaluator.erl b/lib/kernel/test/socket_test_evaluator.erl index 49b529461ff6..1e63a07763fe 100644 --- a/lib/kernel/test/socket_test_evaluator.erl +++ b/lib/kernel/test/socket_test_evaluator.erl @@ -666,7 +666,7 @@ print(Prefix, F, A) -> f("[~s][~p]", [SName, self()]) end, ?LOGGER:format("[~s]~s ~s" ++ F, - [?LIB:formated_timestamp(), IDStr, Prefix | A]). + [?LIB:formatted_timestamp(), IDStr, Prefix | A]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% diff --git a/lib/kernel/test/socket_test_lib.erl b/lib/kernel/test/socket_test_lib.erl index 2d8b4f5181da..781904c90257 100644 --- a/lib/kernel/test/socket_test_lib.erl +++ b/lib/kernel/test/socket_test_lib.erl @@ -33,7 +33,7 @@ %% Time stuff timestamp/0, tdiff/2, - formated_timestamp/0, + formatted_timestamp/0, format_timestamp/1, %% String and format @@ -101,7 +101,7 @@ tdiff({A1, B1, C1} = _T1x, {A2, B2, C2} = _T2x) -> T2 - T1. -formated_timestamp() -> +formatted_timestamp() -> format_timestamp(os:timestamp()). format_timestamp({_N1, _N2, _N3} = TS) -> @@ -121,7 +121,7 @@ print(F) -> print(F, []). print(F, A) -> - io:format("~s ~p " ++ F ++ "~n", [formated_timestamp(), self() | A]). + io:format("~s ~p " ++ F ++ "~n", [formatted_timestamp(), self() | A]). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% diff --git a/lib/kernel/test/socket_test_logger.erl b/lib/kernel/test/socket_test_logger.erl index b66811b31914..b133dca24e40 100644 --- a/lib/kernel/test/socket_test_logger.erl +++ b/lib/kernel/test/socket_test_logger.erl @@ -56,7 +56,7 @@ start(Quiet) -> end. register_logger(Pid) when is_pid(Pid) -> - print("[~s] try register logger (~p)", [?LIB:formated_timestamp(), Pid]), + print("[~s] try register logger (~p)", [?LIB:formatted_timestamp(), Pid]), yes = global:register_name(?LOGGER, Pid), exit(ok). @@ -64,15 +64,15 @@ register_logger(Pid) when is_pid(Pid) -> await_register_logger(Pid, MRef) -> receive {'DOWN', MRef, process, Pid, ok} -> - print("[~s] logger registration done", [?LIB:formated_timestamp()]), + print("[~s] logger registration done", [?LIB:formatted_timestamp()]), ok; {'DOWN', MRef, process, Pid, Reason} -> print("[~s] logger registration failed: " - "~n ~p", [?LIB:formated_timestamp(), Reason]), + "~n ~p", [?LIB:formatted_timestamp(), Reason]), {error, Reason} after 15000 -> print("[~s] logger registration failed: timeout", - [?LIB:formated_timestamp()]), + [?LIB:formatted_timestamp()]), erlang:demonitor(MRef, [flush]), exit(Pid, kill), {error, registration_timeout} @@ -106,18 +106,18 @@ do_format(Msg) -> init(Parent, Quiet) -> put(sname, "logger"), - print("[~s][logger] starting~n", [?LIB:formated_timestamp()]), + print("[~s][logger] starting~n", [?LIB:formatted_timestamp()]), loop(#{parent => Parent, quiet => Quiet}). loop(#{parent := Parent, quiet := Quiet} = State) -> receive {'EXIT', Parent, _} -> - print("[~s][logger] parent exit~n", [?LIB:formated_timestamp()]), + print("[~s][logger] parent exit~n", [?LIB:formatted_timestamp()]), exit(normal); {?MODULE, '$logger', stop} -> - print("[~s][logger] stopping~n", [?LIB:formated_timestamp()]), + print("[~s][logger] stopping~n", [?LIB:formatted_timestamp()]), exit(normal); {?MODULE, '$logger', {msg, Msg}} -> diff --git a/lib/kernel/test/socket_test_ttest_lib.erl b/lib/kernel/test/socket_test_ttest_lib.erl index ebce16dcfaf4..e8b6ee7df692 100644 --- a/lib/kernel/test/socket_test_ttest_lib.erl +++ b/lib/kernel/test/socket_test_ttest_lib.erl @@ -24,10 +24,10 @@ -export([ t/0, tdiff/2, - formated_timestamp/0, format_timestamp/1, + formatted_timestamp/0, format_timestamp/1, format_time/1, - formated_process_stats/1, formated_process_stats/2, + formatted_process_stats/1, formatted_process_stats/2, format/2, error/1, error/2, @@ -44,7 +44,7 @@ tdiff({A1, B1, C1} = _T1x, {A2, B2, C2} = _T2x) -> T2 = A2*1000000000+B2*1000+(C2 div 1000), T2 - T1. -formated_timestamp() -> +formatted_timestamp() -> format_timestamp(os:timestamp()). format_timestamp({_N1, _N2, N3} = TS) -> @@ -62,10 +62,10 @@ format_time(T) -> format("~w sec (~w ms)", [T div 1000, T]). -formated_process_stats(Pid) -> - formated_process_stats("", Pid). +formatted_process_stats(Pid) -> + formatted_process_stats("", Pid). -formated_process_stats(Prefix, Pid) when is_list(Prefix) andalso is_pid(Pid) -> +formatted_process_stats(Prefix, Pid) when is_list(Prefix) andalso is_pid(Pid) -> try begin TotHeapSz = pi(Pid, total_heap_size), @@ -123,5 +123,5 @@ info(F, A) -> print(undefined, F, A) -> print("- ", F, A); print(Prefix, F, A) -> - io:format("[~s, ~s] " ++ F ++ "~n", [formated_timestamp(), Prefix |A]). + io:format("[~s, ~s] " ++ F ++ "~n", [formatted_timestamp(), Prefix |A]). diff --git a/lib/kernel/test/socket_test_ttest_tcp_client.erl b/lib/kernel/test/socket_test_ttest_tcp_client.erl index aeaa66ab831a..0a17161d0094 100644 --- a/lib/kernel/test/socket_test_ttest_tcp_client.erl +++ b/lib/kernel/test/socket_test_ttest_tcp_client.erl @@ -707,7 +707,7 @@ mq(Pid) when is_pid(Pid) -> %% T2 = A2*1000000000+B2*1000+(C2 div 1000), %% T2 - T1. -%% formated_timestamp() -> +%% formatted_timestamp() -> %% format_timestamp(os:timestamp()). %% format_timestamp({_N1, _N2, N3} = TS) -> @@ -742,4 +742,4 @@ mq(Pid) when is_pid(Pid) -> %% p(undefined, F, A) -> %% p("- ", F, A); %% p(Prefix, F, A) -> -%% io:format("[~s, ~s] " ++ F ++ "~n", [formated_timestamp(), Prefix |A]). +%% io:format("[~s, ~s] " ++ F ++ "~n", [formatted_timestamp(), Prefix |A]). diff --git a/lib/kernel/test/socket_test_ttest_tcp_server.erl b/lib/kernel/test/socket_test_ttest_tcp_server.erl index 1d471ebc630a..babb99bd41bb 100644 --- a/lib/kernel/test/socket_test_ttest_tcp_server.erl +++ b/lib/kernel/test/socket_test_ttest_tcp_server.erl @@ -302,11 +302,11 @@ server_handle_message(#{mod := Mod, end. server_handle_stats(ProcStr, Pid) -> - case ?LIB:formated_process_stats(Pid) of + case ?LIB:formatted_process_stats(Pid) of "" -> skip; - FormatedStats -> - ?I("Statistics for ~s ~p:~s", [ProcStr, Pid, FormatedStats]), + FormattedStats -> + ?I("Statistics for ~s ~p:~s", [ProcStr, Pid, FormattedStats]), ok end. @@ -688,7 +688,7 @@ reply(Pid, Ref, Reply) -> %% T2 = A2*1000000000+B2*1000+(C2 div 1000), %% T2 - T1. -%% formated_timestamp() -> +%% formatted_timestamp() -> %% format_timestamp(os:timestamp()). %% format_timestamp({_N1, _N2, N3} = TS) -> @@ -720,5 +720,5 @@ reply(Pid, Ref, Reply) -> %% p(undefined, F, A) -> %% p("- ", F, A); %% p(Prefix, F, A) -> -%% io:format("[~s, ~s] " ++ F ++ "~n", [formated_timestamp(), Prefix |A]). +%% io:format("[~s, ~s] " ++ F ++ "~n", [formatted_timestamp(), Prefix |A]). diff --git a/lib/kernel/test/zlib_SUITE_data/zipdoc b/lib/kernel/test/zlib_SUITE_data/zipdoc index e63952e3ef2b..25847e1dbed8 100644 --- a/lib/kernel/test/zlib_SUITE_data/zipdoc +++ b/lib/kernel/test/zlib_SUITE_data/zipdoc @@ -557,7 +557,7 @@ General Format of a ZIP file . . . - TagN Short VMS attribute tage value #N + TagN Short VMS attribute tag value #N SizeN Short Size of attribute #N, in bytes (var.) SizeN Attribute #N data