File 0889-spelling-rewrite-hopeful-internal-usage.patch of Package erlang

From 9a6a7e1a3bd756fb312621363925f93af820e9bc Mon Sep 17 00:00:00 2001
From: Adam Wight <adam.wight@wikimedia.de>
Date: Sun, 23 Feb 2025 22:10:57 +0100
Subject: [PATCH] spelling: rewrite "hopeful" internal usage

hopefull -> hopeful
---
 erts/emulator/beam/dist.h                 | 12 +++++-----
 erts/emulator/beam/external.c             | 26 ++++++++++-----------
 erts/emulator/test/distribution_SUITE.erl | 28 +++++++++++------------
 3 files changed, 33 insertions(+), 33 deletions(-)

diff --git a/erts/emulator/beam/dist.h b/erts/emulator/beam/dist.h
index 41f4086830..de807dc257 100644
--- a/erts/emulator/beam/dist.h
+++ b/erts/emulator/beam/dist.h
@@ -275,8 +275,8 @@ typedef struct TTBSizeContext_ {
 
 typedef struct TTBEncodeContext_ {
     Uint64 dflags;
-    Uint64 hopefull_flags;
-    byte *hopefull_flagsp;
+    Uint64 hopeful_flags;
+    byte *hopeful_flagsp;
     int level;
     byte* ep;
     Eterm obj;
@@ -289,7 +289,7 @@ typedef struct TTBEncodeContext_ {
     Sint vlen;
     Uint size;
     byte *payload_ixp;
-    byte *hopefull_ixp;
+    byte *hopeful_ixp;
     SysIOVec* iov;
     ErlDrvBinary** binv;
     Eterm *termv;
@@ -326,9 +326,9 @@ typedef struct TTBEncodeContext_ {
         (Ctx)->binv = NULL;                                     \
         (Ctx)->fragment_size = ~((Uint) 0);                     \
         if ((Flags) & DFLAG_PENDING_CONNECT) {                  \
-            (Ctx)->hopefull_flags = 0;                          \
-            (Ctx)->hopefull_flagsp = NULL;                      \
-            (Ctx)->hopefull_ixp = NULL;                         \
+            (Ctx)->hopeful_flags = 0;                           \
+            (Ctx)->hopeful_flagsp = NULL;                       \
+            (Ctx)->hopeful_ixp = NULL;                          \
             (Ctx)->payload_ixp = NULL;                          \
         }                                                       \
     } while (0)
diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index 4e2690a98a..026b896bf8 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -356,7 +356,7 @@ erts_encode_ext_dist_header_size(TTBEncodeContext *ctx,
                                  Uint fragments)
 {
     if (ctx->dflags & DFLAG_PENDING_CONNECT) {
-        /* HOPEFUL_DATA + hopefull flags + hopefull ix + payload ix */
+        /* HOPEFUL_DATA + hopeful flags + hopeful ix + payload ix */
         return 1 + 8 + 4 + 4;
     }
     else if (!acmp && !(ctx->dflags & DFLAG_FRAGMENTS))
@@ -396,10 +396,10 @@ byte *erts_encode_ext_dist_header_setup(TTBEncodeContext *ctx,
         ctx->payload_ixp = ep;
         put_int32(0, ep);
         ep -= 4;
-        ctx->hopefull_ixp = ep;
+        ctx->hopeful_ixp = ep;
         put_int32(ERTS_NO_HIX, ep);
         ep -= 8;
-        ctx->hopefull_flagsp = ep;
+        ctx->hopeful_flagsp = ep;
         put_int64(0, ep);
         *--ep = HOPEFUL_DATA;
         return ep;
@@ -787,8 +787,8 @@ int erts_encode_dist_ext(Eterm term, byte **ext, Uint64 flags, ErtsAtomCacheMap
     if (fragmentsp)
         *fragmentsp = res == 0 ? ctx->frag_ix + 1 : ctx->frag_ix;
     if (flags & DFLAG_PENDING_CONNECT) {
-        ASSERT(ctx->hopefull_flagsp);
-        put_int64(ctx->hopefull_flags, ctx->hopefull_flagsp);
+        ASSERT(ctx->hopeful_flagsp);
+        put_int64(ctx->hopeful_flags, ctx->hopeful_flagsp);
     }
     return res;
 }
@@ -6382,17 +6382,17 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
      * element 1:
      *
      * +---+--------------+-----------+----------+
-     * |'H'|Hopefull Flags|Hopefull IX|Payload IX|
+     * |'H'|Hopeful Flags|Hopeful IX|Payload IX|
      * +---+--------------+-----------+----------+
      *   1         8            4          4
      *
-     * Hopefull flags: Flags corresponding to actual
-     *                 hopefull encodings in this
+     * Hopeful flags:  Flags corresponding to actual
+     *                 hopeful encodings in this
      *                 buffer.
-     * Hopefull IX:    Vector index of first hopefull
-     *                 encoding. Each hopefull encoding
+     * Hopeful IX:     Vector index of first hopeful
+     *                 encoding. Each hopeful encoding
      *                 is preceeded by 4 bytes containing
-     *                 next vector index of hopefull
+     *                 next vector index of hopeful
      *                 encoding. ERTS_NO_HIX marks the
      *                 end.
      * Payload IX:     Vector index of the beginning
@@ -6437,7 +6437,7 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
         return reds;
     }
 
-    /* Currently, the hopefull flags and IX are not used. */
+    /* Currently, the hopeful flags and IX are not used. */
     hdr++;
     hdr += 8;
 
@@ -6793,7 +6793,7 @@ Sint transcode_dist_obuf(ErtsDistOutputBuf* ob,
     start_r = r = reds*ERTS_TRANSCODE_REDS_FACT;
 
     /*
-     * Replace hopefull data header with actual header...
+     * Replace hopeful data header with actual header...
      */
     ep = (byte *) iov[1].iov_base;
     eiov->size -= iov[1].iov_len;
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index a02988c90b..f774769ac5 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -77,8 +77,8 @@
          message_latency_large_exit2/0,
          dist_entry_refc_race/1,
          system_limit/1,
-         hopefull_data_encoding/1,
-         hopefull_export_fun_bug/1,
+         hopeful_data_encoding/1,
+         hopeful_export_fun_bug/1,
          huge_iovec/1,
          is_alive/1,
          dyn_node_name_monitor_node/1,
@@ -119,7 +119,7 @@ all() ->
      {group, bad_dist}, {group, bad_dist_ext},
      dist_entry_refc_race,
      start_epmd_false, no_epmd, epmd_module, system_limit,
-     hopefull_data_encoding, hopefull_export_fun_bug,
+     hopeful_data_encoding, hopeful_export_fun_bug,
      huge_iovec, is_alive, dyn_node_name_monitor_node, dyn_node_name_monitor,
      {group, async_dist}, creation_selection].
 
@@ -3094,21 +3094,21 @@ address_please(_Name, "dummy", inet) ->
 address_please(_Name, "dummy", inet6) ->
     {ok, {0,0,0,0,0,0,0,1}}.
 
-hopefull_data_encoding(Config) when is_list(Config) ->
-    MkHopefullData = fun(Ref,Pid) -> mk_hopefull_data(Ref,Pid) end,
-    test_hopefull_data_encoding(MkHopefullData),
+hopeful_data_encoding(Config) when is_list(Config) ->
+    MkHopefulData = fun(Ref,Pid) -> mk_hopeful_data(Ref,Pid) end,
+    test_hopeful_data_encoding(MkHopefulData),
 
     %% Test funs with hopefully encoded term in environment
     MkBitstringInFunEnv = fun(_,_) -> [mk_fun_with_env(<<5:7>>)] end,
-    test_hopefull_data_encoding(MkBitstringInFunEnv),
+    test_hopeful_data_encoding(MkBitstringInFunEnv),
     MkExpFunInFunEnv = fun(_,_) -> [mk_fun_with_env(fun a:a/0)] end,
-    test_hopefull_data_encoding(MkExpFunInFunEnv),
+    test_hopeful_data_encoding(MkExpFunInFunEnv),
     ok.
 
 mk_fun_with_env(Term) ->
     fun() -> Term end.
 
-test_hopefull_data_encoding(MkDataFun) ->
+test_hopeful_data_encoding(MkDataFun) ->
     {ok, PeerProxy, ProxyNode} = ?CT_PEER(),
     {ok, PeerBouncer, BouncerNode} = ?CT_PEER(["-hidden"]),
     Tester = self(),
@@ -3161,18 +3161,18 @@ bounce_loop() ->
     end,
     bounce_loop().
 
-mk_hopefull_data(RemoteRef, RemotePid) ->
+mk_hopeful_data(RemoteRef, RemotePid) ->
     HugeBs = list_to_bitstring([lists:duplicate(12*1024*1024, 85), <<6:6>>]),
     <<_:1/bitstring,HugeBs2/bitstring>> = HugeBs,
-    mk_hopefull_data(list_to_binary(lists:seq(1,255))) ++
+    mk_hopeful_data(list_to_binary(lists:seq(1,255))) ++
         [1234567890, HugeBs, fun gurka:banan/3, fun erlang:node/1,
          RemotePid, self(), fun erlang:self/0] ++
-        mk_hopefull_data(list_to_binary(lists:seq(1,32))) ++
+        mk_hopeful_data(list_to_binary(lists:seq(1,32))) ++
         [an_atom,
          fun lists:reverse/1, RemoteRef, make_ref(), HugeBs2,
          fun blipp:blapp/7].
 
-mk_hopefull_data(BS) ->
+mk_hopeful_data(BS) ->
     BSsz = bit_size(BS),
     lists:concat(
       [lists:map(fun (Offset) ->
@@ -3211,7 +3211,7 @@ mk_hopefull_data(BS) ->
                  end, lists:seq(BSsz-32, BSsz-17))]).
 
 %% ERL-1254
-hopefull_export_fun_bug(Config) when is_list(Config) ->
+hopeful_export_fun_bug(Config) when is_list(Config) ->
     Msg = [1, fun blipp:blapp/7,
            2, fun blipp:blapp/7],
     {dummy, dummy@dummy} ! Msg.  % Would crash on debug VM
-- 
2.43.0

openSUSE Build Service is sponsored by