File 0142-Fix-typos.patch of Package erlang

From e74f4e2a1052038533ada9b725800dbbdf8804e6 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Wed, 29 Dec 2021 14:02:58 +0800
Subject: [PATCH] Fix typos

---
 lib/sasl/src/release_handler.erl        |  2 +-
 lib/sasl/src/release_handler_1.erl      |  4 ++--
 lib/sasl/src/systools.erl               |  8 ++++----
 lib/sasl/src/systools_make.erl          | 14 +++++++-------
 lib/sasl/test/installer.erl             |  4 ++--
 lib/sasl/test/release_handler_SUITE.erl |  6 +++---
 lib/sasl/test/rh_test_lib.erl           |  2 +-
 lib/sasl/test/systools_SUITE.erl        |  2 +-
 8 files changed, 21 insertions(+), 21 deletions(-)

diff --git a/lib/sasl/src/release_handler.erl b/lib/sasl/src/release_handler.erl
index 3313f08ff0..7635b1ef78 100644
--- a/lib/sasl/src/release_handler.erl
+++ b/lib/sasl/src/release_handler.erl
@@ -2310,7 +2310,7 @@ safe_write_file_m(File, Data, FileOpts, Masters) ->
 %%
 %% A different situation is when the same application version is used
 %% in old and new release, but the path has changed. This is not
-%% handled here - instead it must be explicitely indicated by the
+%% handled here - instead it must be explicitly indicated by the
 %% 'update_paths' option to release_handler:install_release/2 if the
 %% code path shall be updated then.
 %% -----------------------------------------------------------------
diff --git a/lib/sasl/src/release_handler_1.erl b/lib/sasl/src/release_handler_1.erl
index cc46fa5133..3a5883dfb9 100644
--- a/lib/sasl/src/release_handler_1.erl
+++ b/lib/sasl/src/release_handler_1.erl
@@ -248,7 +248,7 @@ syntax_check_script([]) ->
 %%   {load_object_code, [Mod1, Mod2]},
 %%   % delete old version
 %%   {remove, {Mod1, brutal_purge}}, {remove, {Mod2, brutal_purge}},
-%%   % now, some procs migth be running prev current (now old) version
+%%   % now, some procs might be running prev current (now old) version
 %%   % kill them, and load new version
 %%   {load, {Mod1, brutal_purge}}, {load, {Mod2, brutal_purge}}
 %%   % now, there is one version of the code (new, current)
@@ -279,7 +279,7 @@ syntax_check_script([]) ->
 %%    If a process doesn't repsond - never mind.  It will be killed
 %%    later on (if a purge is performed).
 %%    Hmm, we must do something smart here... we should probably kill it,
-%%    but we cant, because its supervisor will restart it directly!  Maybe
+%%    but we can't, because its supervisor will restart it directly!  Maybe
 %%    we should keep a list of those, call supervisor:terminate_child()
 %%    when all others are suspended, and call sup:restart_child() when the
 %%    others are resumed.
diff --git a/lib/sasl/src/systools.erl b/lib/sasl/src/systools.erl
index a97db3a20e..889cf924a3 100644
--- a/lib/sasl/src/systools.erl
+++ b/lib/sasl/src/systools.erl
@@ -43,7 +43,7 @@
 
 %%-----------------------------------------------------------------
 %% Options is a list of {path, Path} | silent | local where path sets
-%% the search path, silent supresses error message printing on console,
+%% the search path, silent suppresses error message printing on console,
 %% local generates a script with references to the directories there
 %% the applications are found.
 %%-----------------------------------------------------------------
@@ -57,7 +57,7 @@ make_script(RelName, Opt) ->
 %%-----------------------------------------------------------------
 %% Options is a list of {path, Path} | silent |
 %%    {dirs, [src,include,examples,..]} | {erts, ErtsDir} where path
-%% sets the search path, silent supresses error message printing on console,
+%% sets the search path, silent suppresses error message printing on console,
 %% dirs includes the specified directories (per application) in the
 %% release package and erts specifies that the erts-Vsn/bin directory
 %% should be included in the release package and there it can be found.
@@ -116,8 +116,8 @@ script2boot(File, Output0, _Opt) ->
 
 %%-----------------------------------------------------------------
 %% Options is a list of {path, Path} | silent | noexec where path sets
-%% search path, silent supresses error message printing on console,
-%% noexec supresses writing the output "relup" file
+%% search path, silent suppresses error message printing on console,
+%% noexec suppresses writing the output "relup" file
 %%-----------------------------------------------------------------
 make_relup(ReleaseName, UpNameList, DownNameList) ->
     systools_relup:mk_relup(ReleaseName, UpNameList, DownNameList, []).
diff --git a/lib/sasl/src/systools_make.erl b/lib/sasl/src/systools_make.erl
index 0cac1099d3..fd2a14954a 100644
--- a/lib/sasl/src/systools_make.erl
+++ b/lib/sasl/src/systools_make.erl
@@ -56,7 +56,7 @@
 %% Create a boot script from a release file.
 %% Options is a list of {path, Path} | silent | local
 %%         | warnings_as_errors
-%% where path sets the search path, silent supresses error message
+%% where path sets the search path, silent suppresses error message
 %% printing on console, local generates a script with references
 %% to the directories there the applications are found,
 %% and warnings_as_errors treats warnings as errors.
@@ -195,7 +195,7 @@ do_make_hybrid_boot(TmpVsn, OldBoot, NewBoot, Args) ->
     {script,{_RelName1,_RelVsn1},OldScript} = binary_to_term(OldBoot),
     {script,{NewRelName,_RelVsn2},NewScript} = binary_to_term(NewBoot),
 
-    %% Everyting upto kernel_load_completed must come from the new script
+    %% Everything up to kernel_load_completed must come from the new script
     Fun1 = fun({progress,kernel_load_completed}) -> false;
               (_) -> true
            end,
@@ -345,7 +345,7 @@ add_apply_upgrade(Script,Args) ->
 %% Create a release package from a release file.
 %% Options is a list of {path, Path} | silent |
 %%    {dirs, [src,include,examples,..]} | {erts, ErtsDir} where path
-%% sets the search path, silent supresses error message printing,
+%% sets the search path, silent suppresses error message printing,
 %% dirs includes the specified directories (per application) in the
 %% release package and erts specifies that the erts-Vsn/bin directory
 %% should be included in the release package and there it can be found.
@@ -674,7 +674,7 @@ parse_application({application, Name, Dict}, File, Vsn, Incls)
 parse_application(Other, _, _, _) ->
     {error, {badly_formatted_application, Other}}.
 
-%% Test if all included applications specifed in the .rel file
+%% Test if all included applications specified in the .rel file
 %% exists in the {included_applications,Incs} specified in the
 %% .app file.
 override_include(Name, Incs, Incls) ->
@@ -1370,7 +1370,7 @@ find_all(CheckingApp, [Name|T], L, Visited, Found, NotFound) ->
     case find_app(Name, L) of
 	{value, App} ->
 	    {_A,R} = App,
-	    %% It is OK to have a dependecy like
+	    %% It is OK to have a dependency like
 	    %% X includes Y, Y uses X.
 	    case lists:member(CheckingApp, R#application.includes) of
 		true ->
@@ -1410,7 +1410,7 @@ del_apps([], L) ->
 %%______________________________________________________________________
 %% Create the load path used in the generated script.
 %% If PathFlag is true a script intended to be used as a complete
-%% system (e.g. in an embbeded system), i.e. all applications are
+%% system (e.g. in an embedded system), i.e. all applications are
 %% located under $ROOT/lib.
 %% Otherwise all paths are set according to dir per application.
 
@@ -1779,7 +1779,7 @@ add_system_files(Tar, RelName, Release, Path1) ->
     %% (well, actually the boot file was looked for in the same
     %% directory as RelName, which is not necessarily the same as cwd)
     %% --
-    %% but also in the path specfied as an option to systools:make_tar
+    %% but also in the path specified as an option to systools:make_tar
     %% (but make sure to search the RelName directory and cwd first)
     Path = case filename:dirname(RelName) of
 	       "." ->
diff --git a/lib/sasl/test/installer.erl b/lib/sasl/test/installer.erl
index 5ad31c508e..05b0156574 100644
--- a/lib/sasl/test/installer.erl
+++ b/lib/sasl/test/installer.erl
@@ -381,7 +381,7 @@ install_14(TestNode) ->
 
 
 %%%-----------------------------------------------------------------
-%%% Ths test checks that an upgrade which both upgrades to a new
+%%% The test checks that an upgrade which both upgrades to a new
 %%% emulator version, and had a restart_emulator option to
 %%% systools:make_relup will be restarted twice on upgrade.
 %%% (On downgrade it will happen only once.)
@@ -411,7 +411,7 @@ upgrade_restart_2(TestNode) ->
 	{"SASL-test","P2B"} ->
 	    upgrade_restart_2a(TestNode);
 	{"SASL-test","__new_emulator__P1G"} ->
-	    %% catched the node too early - give it another try
+	    %% caught the node too early - give it another try
 	    {wait,whereis(init)}
     end.
 
diff --git a/lib/sasl/test/release_handler_SUITE.erl b/lib/sasl/test/release_handler_SUITE.erl
index 78626bbc91..f0433fd522 100644
--- a/lib/sasl/test/release_handler_SUITE.erl
+++ b/lib/sasl/test/release_handler_SUITE.erl
@@ -654,7 +654,7 @@ upgrade_restart(Conf) when is_list(Conf) ->
 	ok ->
 	    ok;
 	{wait,TestNodeInit2a} ->
-	    %% We catched the node too early - it was supposed to
+	    %% We caught the node too early - it was supposed to
 	    %% restart twice, so let's wait for one more restart.
 	    wait_nodes_up([{TestNode,TestNodeInit2a}],"upgrade_restart_2a",[]),
 	    ok = rpc_inst(TestNode, upgrade_restart_2a, [])
@@ -2505,7 +2505,7 @@ copy_tree(Conf, Src, NewName, DestDir) ->
     TempTarName = filename:join(PrivDir, "temp_tar_file.tar"),
     %% Not compressing tar file here since that would increase test
     %% suite time by almost 100%, and the tar file is deleted
-    %% imediately anyway.
+    %% immediately anyway.
     {ok,Tar} = erl_tar:open(TempTarName, [write]),
     ok = erl_tar:add(Tar, Src, NewName, []),
     ok = erl_tar:close(Tar),
@@ -2925,7 +2925,7 @@ permanent_p1h(Node) ->
     ok = rpc_inst(Node, permanent_p1h, []).
 
 %% For each node in ToNodes, create a target installation which is
-%% indentical to the target installation for FromNode.
+%% identical to the target installation for FromNode.
 copy_installed(Conf,FromNode,ToNodes) ->
     PrivDir = priv_dir(Conf),
     DataDir = ?config(data_dir,Conf),
diff --git a/lib/sasl/test/rh_test_lib.erl b/lib/sasl/test/rh_test_lib.erl
index 7fffb310fc..dba45bece6 100644
--- a/lib/sasl/test/rh_test_lib.erl
+++ b/lib/sasl/test/rh_test_lib.erl
@@ -20,7 +20,7 @@ cmd(Cmd,Args,Env) ->
     case open_port({spawn_executable, Cmd}, [{args,Args},{env,Env}]) of
         Port when is_port(Port) ->
             unlink(Port),
-            catch erlang:port_close(Port), % migth already be closed, so catching
+            catch erlang:port_close(Port), % might already be closed, so catching
 	    ok;
         Error ->
             Error
diff --git a/lib/sasl/test/systools_SUITE.erl b/lib/sasl/test/systools_SUITE.erl
index cd7a157d59..801660ddac 100644
--- a/lib/sasl/test/systools_SUITE.erl
+++ b/lib/sasl/test/systools_SUITE.erl
@@ -1398,7 +1398,7 @@ src_tests_tar(Config) when is_list(Config) ->
 
 %% make_tar: Check that make_tar handles generation and placement of
 %% tar files for variables outside the main tar file.
-%% Test the {var_tar, include | ownfile | omit} optio.
+%% Test the {var_tar, include | ownfile | omit} option.
 var_tar(Config) when is_list(Config) ->
     {ok, OldDir} = file:get_cwd(),
     PSAVE = code:get_path(),		% Save path
-- 
2.31.1

openSUSE Build Service is sponsored by