File 0834-Fix-typos-in-erts-emulator-test.patch of Package erlang

From a60508673eca524920ae6f2612da4fdd8e002ff0 Mon Sep 17 00:00:00 2001
From: "Kian-Meng, Ang" <kianmeng@cpan.org>
Date: Thu, 2 Dec 2021 06:26:13 +0800
Subject: [PATCH] Fix typos in erts/emulator/test

---
 .../test/alloc_SUITE_data/bucket_mask.c        |  2 +-
 erts/emulator/test/alloc_SUITE_data/coalesce.c |  8 ++++----
 erts/emulator/test/beam_SUITE.erl              |  2 +-
 erts/emulator/test/bif_SUITE.erl               |  2 +-
 erts/emulator/test/code_SUITE.erl              |  4 ++--
 erts/emulator/test/dirty_bif_SUITE.erl         |  2 +-
 erts/emulator/test/dirty_nif_SUITE.erl         |  2 +-
 erts/emulator/test/distribution_SUITE.erl      |  4 ++--
 erts/emulator/test/driver_SUITE.erl            |  4 ++--
 .../driver_SUITE_data/vsn_mismatch_drv_impl.c  |  2 +-
 .../test/erl_drv_thread_SUITE_data/basic.c     |  4 ++--
 erts/emulator/test/erl_link_SUITE.erl          |  2 +-
 erts/emulator/test/estone_SUITE.erl            |  4 ++--
 erts/emulator/test/exception_SUITE.erl         |  2 +-
 erts/emulator/test/float_SUITE.erl             |  6 +++---
 erts/emulator/test/gc_SUITE.erl                |  4 ++--
 erts/emulator/test/guard_SUITE.erl             |  2 +-
 erts/emulator/test/hash_SUITE.erl              |  2 +-
 erts/emulator/test/hello_SUITE_data/hello.erl  |  4 ++--
 erts/emulator/test/match_spec_SUITE.erl        |  4 ++--
 .../emulator/test/message_queue_data_SUITE.erl |  2 +-
 erts/emulator/test/nif_SUITE.erl               |  2 +-
 erts/emulator/test/node_container_SUITE.erl    |  6 +++---
 erts/emulator/test/num_bif_SUITE.erl           |  2 +-
 erts/emulator/test/port_SUITE.erl              | 18 +++++++++---------
 erts/emulator/test/port_SUITE_data/port_test.c |  2 +-
 .../test/port_bif_SUITE_data/port_test.c       |  2 +-
 erts/emulator/test/process_SUITE.erl           |  6 +++---
 .../test/process_SUITE_data/fwd_node.c         |  2 +-
 erts/emulator/test/time_SUITE.erl              |  2 +-
 erts/emulator/test/tuple_SUITE.erl             |  8 ++++----
 erts/emulator/test/z_SUITE.erl                 |  4 ++--
 32 files changed, 61 insertions(+), 61 deletions(-)

diff --git a/erts/emulator/test/alloc_SUITE_data/bucket_mask.c b/erts/emulator/test/alloc_SUITE_data/bucket_mask.c
index c94c265f4e..36dbce9f20 100644
--- a/erts/emulator/test/alloc_SUITE_data/bucket_mask.c
+++ b/erts/emulator/test/alloc_SUITE_data/bucket_mask.c
@@ -24,7 +24,7 @@
 #include <stdio.h>
 
 #if defined(__WIN32__) && SIZEOF_VOID_P == 8
-/* Use larger threashold for win64 as block alignment
+/* Use larger threshold for win64 as block alignment
    is 16 bytes and not 8 */
 #define SBCT ((1024*1024))
 #else
diff --git a/erts/emulator/test/alloc_SUITE_data/coalesce.c b/erts/emulator/test/alloc_SUITE_data/coalesce.c
index 7791409a34..cbab000db7 100644
--- a/erts/emulator/test/alloc_SUITE_data/coalesce.c
+++ b/erts/emulator/test/alloc_SUITE_data/coalesce.c
@@ -126,7 +126,7 @@ test_free(TestCaseState_t *tcs, Allctr_t *a, Ulong bsz)
     FREE(a, p[0]);
     FREE(a, p[6]);
 
-    testcase_printf(tcs," --- free() with block size %lu succeded ---\n",bsz);
+    testcase_printf(tcs," --- free() with block size %lu succeeded ---\n",bsz);
 }
 
 static void
@@ -195,7 +195,7 @@ test_realloc(TestCaseState_t *tcs, Allctr_t *a, Ulong bsz)
     ASSERT(tcs, IS_FREE_BLK(blk));
     ASSERT(tcs, NXT_BLK(blk) == UMEM2BLK(p[2]));
 
-    /* Grow upto next alloced block by allocating just enough so that no
+    /* Grow up to next allocated block by allocating just enough so that no
        free block fits between them */
     nbsz = BLK_SZ(blk) + UMEM_SZ(UMEM2BLK(p[0]));
     nbsz -= MIN_BLK_SZ(a) - 1;
@@ -227,7 +227,7 @@ test_realloc(TestCaseState_t *tcs, Allctr_t *a, Ulong bsz)
     ASSERT(tcs, blk == UMEM2BLK(p[2]));
 
     /* Shrink just as much so that a free block can fit between
-       the alloced blocks */
+       the allocated blocks */
     nbsz -= 1;
     ptr = REALLOC(a, p[0], nbsz);
     ASSERT(tcs, p[0] == ptr);
@@ -253,7 +253,7 @@ test_realloc(TestCaseState_t *tcs, Allctr_t *a, Ulong bsz)
     FREE(a, p[0]);
     FREE(a, p[2]);
 
-    testcase_printf(tcs, " --- realloc() with block size %lu succeded ---\n",
+    testcase_printf(tcs, " --- realloc() with block size %lu succeeded ---\n",
 		    bsz);
 
 }
diff --git a/erts/emulator/test/beam_SUITE.erl b/erts/emulator/test/beam_SUITE.erl
index d76df2cff3..01b58caa40 100644
--- a/erts/emulator/test/beam_SUITE.erl
+++ b/erts/emulator/test/beam_SUITE.erl
@@ -239,7 +239,7 @@ heap_sizes(Config) when is_list(Config) ->
 
     %% Verify that the largest heap size consists of
     %%  - 31 bits of bytes on 32 bits arch
-    %%  - atleast 52 bits of bytes (48 is the maximum virtual address)
+    %%  - at least 52 bits of bytes (48 is the maximum virtual address)
     %%    and at the most 63 bits on 64 bit archs
     %% heap sizes are in words
     case erlang:system_info(wordsize) of
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index 4983829a2b..6af1ee9af5 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -2326,7 +2326,7 @@ send_bad_ctl(BadNode, ToNode) when is_atom(BadNode), is_atom(ToNode) ->
     spawn_link(BadNode,
 	       fun () ->
 		       pong = net_adm:ping(ToNode),
-		       %% We creat a valid ctl msg and replace an
+		       %% We create a valid ctl msg and replace an
 		       %% atom with an invalid atom cache reference
 		       <<131,Replace/binary>> = term_to_binary(replace),
 		       Ctl = dmsg_ext({?DOP_REG_SEND,
@@ -2383,7 +2383,7 @@ set_internal_state(Op, Val) ->
 dmsg_hdr() ->
     [131, % Version Magic
      $D,  % Dist header
-     0].  % No atom cache referenses
+     0].  % No atom cache references
 
 dmsg_bad_hdr() ->
     [131, % Version Magic
diff --git a/erts/emulator/test/driver_SUITE.erl b/erts/emulator/test/driver_SUITE.erl
index 751c4a9e5d..51701f42b1 100644
--- a/erts/emulator/test/driver_SUITE.erl
+++ b/erts/emulator/test/driver_SUITE.erl
@@ -537,7 +537,7 @@ timer_delay(Config) when is_list(Config) ->
     ?line test_server:timetrap_cancel(Dog),
     ok.
 
-%% Test that driver_set_timer with new timout really changes
+%% Test that driver_set_timer with new timeout really changes
 %% the timer (ticket OTP-5942), it didn't work before
 
 timer_change(Config) when is_list(Config) ->
@@ -2177,7 +2177,7 @@ consume_timeslice(Config) when is_list(Config) ->
     %% scheduling counts.
     %%
     %% When signal is delivered immediately we must take into account
-    %% that process and port are "virtualy" scheduled out and in
+    %% that process and port are "virtually" scheduled out and in
     %% in the trace generated.
     %%
     %% Port ! {_, {command, _}, and port_command() differs. The send
diff --git a/erts/emulator/test/driver_SUITE_data/vsn_mismatch_drv_impl.c b/erts/emulator/test/driver_SUITE_data/vsn_mismatch_drv_impl.c
index 6750b8a78b..f1fee767f0 100644
--- a/erts/emulator/test/driver_SUITE_data/vsn_mismatch_drv_impl.c
+++ b/erts/emulator/test/driver_SUITE_data/vsn_mismatch_drv_impl.c
@@ -22,7 +22,7 @@
  *
  * Description: Implementation of a driver that fakes driver version. It
  *              is used for checking that version mismatches are handled
- *              correct by the emulator. The following makros have to be
+ *              correct by the emulator. The following macros have to be
  *		defined before it can be used:
  *		* VSN_MISMATCH_DRV_NAME_STR
  *		* VSN_MISMATCH_DRV_NAME
diff --git a/erts/emulator/test/erl_drv_thread_SUITE_data/basic.c b/erts/emulator/test/erl_drv_thread_SUITE_data/basic.c
index 8ceb9eff08..7b07ae4dfe 100644
--- a/erts/emulator/test/erl_drv_thread_SUITE_data/basic.c
+++ b/erts/emulator/test/erl_drv_thread_SUITE_data/basic.c
@@ -242,11 +242,11 @@ testcase_run(TestCaseState_t *tcs)
     ASSERT_CLNUP(tcs, tres[1] == &res_tf1, erl_drv_mutex_unlock(mtx));
     ASSERT_CLNUP(tcs, res_tf1 == 1, erl_drv_mutex_unlock(mtx));
 
-    /* Test signaling when noone waits */
+    /* Test signaling when no one waits */
 
     erl_drv_cond_signal(cnd);
 
-    /* Test broadcasting when noone waits */
+    /* Test broadcasting when no one waits */
 
     erl_drv_cond_broadcast(cnd);
 
diff --git a/erts/emulator/test/erl_link_SUITE.erl b/erts/emulator/test/erl_link_SUITE.erl
index 45da19932d..45ff0cdcfa 100644
--- a/erts/emulator/test/erl_link_SUITE.erl
+++ b/erts/emulator/test/erl_link_SUITE.erl
@@ -1238,7 +1238,7 @@ dctrl(Node) when is_atom(Node) ->
 dmsg_hdr() ->
     [131, % Version Magic
      $D,  % Dist header
-     0].  % No atom cache referenses
+     0].  % No atom cache references
 
 dmsg_ext(Term) ->	
     <<131, Res/binary>> = term_to_binary(Term),
diff --git a/erts/emulator/test/estone_SUITE.erl b/erts/emulator/test/estone_SUITE.erl
index 0138ca572e..77da7bf742 100644
--- a/erts/emulator/test/estone_SUITE.erl
+++ b/erts/emulator/test/estone_SUITE.erl
@@ -279,12 +279,12 @@ micro(int_arith) ->
     #micro{function = int_arith,
 	   weight = 3,
 	   loops = 4157,
-	   str = "Small Integer arithmetics"};
+	   str = "Small Integer arithmetic"};
 micro(float_arith) ->
     #micro{function = float_arith,
 	   weight = 1,
 	   loops = 5526,
-	   str = "Float arithmetics"};
+	   str = "Float arithmetic"};
 micro(fcalls) ->
     #micro{function = fcalls,
 	   weight = 5,
diff --git a/erts/emulator/test/exception_SUITE.erl b/erts/emulator/test/exception_SUITE.erl
index 1623740918..eb115b0fb8 100644
--- a/erts/emulator/test/exception_SUITE.erl
+++ b/erts/emulator/test/exception_SUITE.erl
@@ -163,7 +163,7 @@ pending({Code,[{?MODULE,Func,Arity,Loc}|_]}, Func, Args, Code)
 pending(Reason, _Function, _Args, _Code) ->
     test_server:fail({bad_exit_reason,Reason}).
 
-%% Test that doing arithmetics on [] gives a badarith EXIT and not a crash.
+%% Test that doing arithmetic on [] gives a badarith EXIT and not a crash.
 
 nil_arith(Config) when is_list(Config) ->
     ?line ba_plus_minus_times([], []),
diff --git a/erts/emulator/test/float_SUITE.erl b/erts/emulator/test/float_SUITE.erl
index 2c88a5608e..1195ef41a6 100644
--- a/erts/emulator/test/float_SUITE.erl
+++ b/erts/emulator/test/float_SUITE.erl
@@ -192,7 +192,7 @@ cmp_zero(_Config) ->
     cmp(0.5e-323,0).
 
 cmp_integer(_Config) ->
-    Axis = (1 bsl 53)-2.0, %% The point where floating points become unprecise
+    Axis = (1 bsl 53)-2.0, %% The point where floating points become imprecise
     span_cmp(Axis,2,200),
     cmp(Axis*Axis,round(Axis)).
 
@@ -286,7 +286,7 @@ stop_node(Node) ->
 
 
 %% Test that operations that might hide infinite intermediate results
-%% do not supress the badarith.
+%% do not suppress the badarith.
 hidden_inf(Config) when is_list(Config) ->
     ZeroP = 0.0,
     ZeroN = id(ZeroP) * (-1),
diff --git a/erts/emulator/test/guard_SUITE.erl b/erts/emulator/test/guard_SUITE.erl
index f2c1595392..37435aa2bc 100644
--- a/erts/emulator/test/guard_SUITE.erl
+++ b/erts/emulator/test/guard_SUITE.erl
@@ -310,7 +310,7 @@ guard_bifs(Config) when is_list(Config) ->
     ?line Big = -237849247829874297658726487367328971246284736473821617265433,
     ?line Float = 387924.874,
 
-    %% Succeding use of guard bifs.
+    %% Succeeding use of guard bifs.
 
     ?line try_gbif('abs/1', Big, -Big),
     ?line try_gbif('float/1', Big, float(Big)),
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index 7734c2d07f..638eb5eb8e 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -21,7 +21,7 @@
 %%
 %% Verifying erlang:phash/2. And now also phash2/2, to some extent.
 %% Test the hashing algorithm for integer numbers in 2 ways:
-%% 1 Test that numbers in diferent sequences get sufficiently spread
+%% 1 Test that numbers in different sequences get sufficiently spread
 %%   in a "bit pattern" way (modulo 256 etc).
 %% 2 Test that numbers are correctly hashed compared to a reference implementation,
 %%   regardless of their internal representation. The hashing algorithm should never 
diff --git a/erts/emulator/test/node_container_SUITE.erl b/erts/emulator/test/node_container_SUITE.erl
index 2b614b6799..c68de2fbc9 100644
--- a/erts/emulator/test/node_container_SUITE.erl
+++ b/erts/emulator/test/node_container_SUITE.erl
@@ -1042,14 +1042,14 @@ nc_refc_check(Node) when is_atom(Node) ->
 					     Self ! {Ref, ErrMsg, failed},
 					     exit(normal)
 				     end),
-		       Self ! {Ref, succeded}
+		       Self ! {Ref, succeeded}
 	       end),
     receive
 	{Ref, ErrorMsg, failed} ->
 	    ?t:format("~s~n", [ErrorMsg]),
 	    ?t:fail(reference_count_check_failed);
-	{Ref, succeded} ->
-	    ?t:format("Reference count check of node ~w succeded!~n", [Node]),
+	{Ref, succeeded} ->
+	    ?t:format("Reference count check of node ~w succeeded!~n", [Node]),
 	    ok
     end.
 
diff --git a/erts/emulator/test/port_SUITE.erl b/erts/emulator/test/port_SUITE.erl
index 4380216f37..6146599942 100644
--- a/erts/emulator/test/port_SUITE.erl
+++ b/erts/emulator/test/port_SUITE.erl
@@ -1318,11 +1318,11 @@ otp_3906(Config, OSName) ->
 			     {failed, Reason};
 			 {emulator_pid, EmPid} ->
 			     case otp_3906_wait_result(FS, 0, 0) of
-				 {succeded,
+				 {succeeded,
 				  ?OTP_3906_CHILDREN,
 				  ?OTP_3906_CHILDREN} ->
-				     succeded;
-				 {succeded, Forked, Exited} ->
+				     succeeded;
+				 {succeeded, Forked, Exited} ->
 				     otp_3906_list_defunct(EmPid, OSName),
 				     {failed,
 				      {mismatch,
@@ -1337,7 +1337,7 @@ otp_3906(Config, OSName) ->
 	    process_flag(priority, OP),
 	    test_server:stop_node(Node),
 	    case Result of
-		succeded ->
+		succeeded ->
 		    ok;
 		_ ->
 		    test_server:fail(Result)
@@ -1401,8 +1401,8 @@ otp_3906_wait_result(ForkerStarter, F, E) ->
 	    otp_3906_wait_result(ForkerStarter, F, E+1);
 	tick ->
 	    otp_3906_wait_result(ForkerStarter, F, E);
-	succeded ->
-	    {succeded, F, E}
+	succeeded ->
+	    {succeeded, F, E}
     after
 	?OTP_3906_TICK_TIMEOUT ->
 	    unlink(ForkerStarter),
@@ -1439,7 +1439,7 @@ otp_3906_start_forker_starter(N, RefList, Sup, Prog) ->
 otp_3906_forker_starter(0, RefList, Sup, _) ->
     otp_3906_collect(RefList, Sup),
     unlink(Sup),
-    Sup ! succeded;
+    Sup ! succeeded;
 otp_3906_forker_starter(N, RefList, Sup, Prog)
   when length(RefList) >= ?OTP_3906_MAX_CONC_OSP ->
     otp_3906_forker_starter(N, otp_3906_collect_one(RefList, Sup), Sup, Prog);
@@ -1761,7 +1761,7 @@ test_bat_file(Dir) ->
     [DN,"hello","world"] = 
 	run_echo_args(Dir,FN,
 		      [default,"hello","world"]),
-    %% The arg0 argumant should be ignored when running batch files
+    %% The arg0 argument should be ignored when running batch files
     [DN,"hello","world"] = 
 	run_echo_args(Dir,FN,
 		      ["knaskurt","hello","world"]),
diff --git a/erts/emulator/test/port_SUITE_data/port_test.c b/erts/emulator/test/port_SUITE_data/port_test.c
index fa97b4c9d0..6c56cdf956 100644
--- a/erts/emulator/test/port_SUITE_data/port_test.c
+++ b/erts/emulator/test/port_SUITE_data/port_test.c
@@ -559,7 +559,7 @@ char* spec;			/* Specification for reply. */
 
     buf = (char *) malloc(total_size);
     if (buf == NULL) {
-	fprintf(stderr, "%s: insufficent memory for reply buffer of size %d\n",
+	fprintf(stderr, "%s: insufficient memory for reply buffer of size %d\n",
 		port_data->progname, total_size);
 	exit(1);
     }
diff --git a/erts/emulator/test/port_bif_SUITE_data/port_test.c b/erts/emulator/test/port_bif_SUITE_data/port_test.c
index ef6d12dc93..fa509d5a15 100644
--- a/erts/emulator/test/port_bif_SUITE_data/port_test.c
+++ b/erts/emulator/test/port_bif_SUITE_data/port_test.c
@@ -536,7 +536,7 @@ char* spec;			/* Specification for reply. */
 
     buf = (char *) malloc(total_size);
     if (buf == NULL) {
-	fprintf(stderr, "%s: insufficent memory for reply buffer of size %d\n",
+	fprintf(stderr, "%s: insufficient memory for reply buffer of size %d\n",
 		port_data->progname, total_size);
 	exit(1);
     }
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 221173c9ac..65754b1dd7 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -311,7 +311,7 @@ abnormal_suicide_exit(Config) when is_list(Config) ->
 	      Other -> test_server:fail({bad_message, Other})
 	  end.
 
-%% Tests that exit(self(), die) cannot be catched.
+%% Tests that exit(self(), die) cannot be caught.
 t_exit_2_catch(Config) when is_list(Config) ->
     process_flag(trap_exit, true),
     Pid = fun_spawn(fun() -> catch exit(self(), die) end),
@@ -1354,7 +1354,7 @@ yield(Config) when is_list(Config) ->
 	Level when is_integer(Level) ->
 	    {skipped,
 	     "Modified timing (level " ++ integer_to_list(Level)
-	     ++ ") is enabled. Testcase gets messed up by modfied "
+	     ++ ") is enabled. Testcase gets messed up by modified "
 	     "timing."};
 	_ ->
 	    MS = erlang:system_flag(multi_scheduling, block),
diff --git a/erts/emulator/test/tuple_SUITE.erl b/erts/emulator/test/tuple_SUITE.erl
index 9e6f21a090..36cd883f37 100644
--- a/erts/emulator/test/tuple_SUITE.erl
+++ b/erts/emulator/test/tuple_SUITE.erl
@@ -383,7 +383,7 @@ t_list_to_tuple(Config) when is_list(Config) ->
 t_list_to_upper_boundry_tuple(Config) when is_list(Config) ->
     sys_mem_cond_run(2048,
 		    fun () ->
-			    %% test upper boundry, 16777215 elements
+			    %% test upper boundary, 16777215 elements
 			    MaxSize  = 1 bsl 24 - 1,
 			    MaxTuple = list_to_tuple(lists:seq(1, MaxSize)),
 			    MaxSize  = size(MaxTuple),
@@ -432,7 +432,7 @@ t_make_tuple_2(Config) when is_list(Config) ->
 t_make_upper_boundry_tuple_2(Config) when is_list(Config) ->
     sys_mem_cond_run(2048,
 		     fun () ->
-			     %% test upper boundry, 16777215 elements
+			     %% test upper boundary, 16777215 elements
 			     t_make_tuple(1 bsl 24 - 1, a)
 		     end).
 
@@ -525,7 +525,7 @@ t_append_element(Config) when is_list(Config) ->
 t_append_element_upper_boundry(Config) when is_list(Config) ->
     sys_mem_cond_run(2048,
 		     fun () ->
-			     %% test upper boundry, 16777215 elements
+			     %% test upper boundary, 16777215 elements
 			     MaxSize  = 1 bsl 24 - 1,
 			     MaxTuple = list_to_tuple(lists:seq(1, MaxSize)),
 			     {'EXIT',{badarg,_}} = (catch erlang:append_element(MaxTuple, a)),
diff --git a/erts/emulator/test/z_SUITE.erl b/erts/emulator/test/z_SUITE.erl
index 5b2e77dfa2..cd73066b69 100644
--- a/erts/emulator/test/z_SUITE.erl
+++ b/erts/emulator/test/z_SUITE.erl
@@ -169,7 +169,7 @@ schedulers_alive(Config) when is_list(Config) ->
 		      enabled -> ?line ok
 		  end,
 	    erts_debug:set_internal_state(available_internal_state, true),
-	    %% node_and_dist_references will use emulator interal thread blocking...
+	    %% node_and_dist_references will use emulator internal thread blocking...
 	    erts_debug:get_internal_state(node_and_dist_references), 
 	    erts_debug:set_internal_state(available_internal_state, false),
 	    ?t:format("Testing not blocked~n"),
-- 
2.31.1

openSUSE Build Service is sponsored by