File 1703-ssh-code-review-applied.patch of Package erlang

From 293f777f361a715f4d1b83515bb30768c15668f3 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 23 Oct 2024 18:50:58 +0200
Subject: [PATCH 3/3] ssh: code review applied

---
 lib/ssh/internal_doc/ssh_notes.md      | 108 +++++++++++++++++--------
 lib/ssh/src/ssh.erl                    |  39 ++++-----
 lib/ssh/src/ssh_connection_handler.erl |  22 ++---
 lib/ssh/src/ssh_lsocket.erl            |  58 +++++++------
 lib/ssh/src/ssh_options.erl            |   1 -
 lib/ssh/src/ssh_system_sup.erl         |   6 +-
 6 files changed, 142 insertions(+), 92 deletions(-)

diff --git a/lib/ssh/internal_doc/ssh_notes.md b/lib/ssh/internal_doc/ssh_notes.md
index 2d3b8c25eb..ef8705fa15 100644
--- a/lib/ssh/internal_doc/ssh_notes.md
+++ b/lib/ssh/internal_doc/ssh_notes.md
@@ -1,34 +1,73 @@
-# SSH supervision tree (prototype)
+# SSH supervision tree (server side update >= OTP-28)
 ```mermaid
 ---
-title: SSH supervision tree (prototype)
+title: SSH supervision tree
 ---
 flowchart RL
-    d_sup --> sup[["ssh_sup\n(ssh_app.erl)\n[o4o]"]]
+    d_sup --> sup[["ssh_sup<br />(ssh_app.erl)<br />[o4o]"]]
     c_sup --> sup
 
     subgraph client
-    connection_sup --> c_sup[["sshc_sup\n(ssh_app.erl)\n[o4o]\nauto_shutdown=never"]]
+    connection_sup --> c_sup[["sshc_sup<br />(ssh_app.erl)<br />[o4o]<br />auto_shutdown=never"]]
     subgraph connection_c
-    connection_handler["ssh_connection_handler\nSIGNIFICANT"] --> connection_sup[["ssh_connection_sup\n[o4a]\nauto_shutdown=any_significant"]]
-    channel_sup[["ssh_channel_sup\n[o4o]"]] --> connection_sup
+    connection_handler["ssh_connection_handler<br />SIGNIFICANT"] --> connection_sup[["ssh_connection_sup<br />[o4a]<br />auto_shutdown=any_significant"]]
+    channel_sup[["ssh_channel_sup<br />[o4o]"]] --> connection_sup
     sftp["ssh_sftp"] --> channel_sup
-    tcpip_forward_acceptor_sup[["ssh_tcpip_forward_acceptor_sup\n[o4o]"]] --> connection_sup
+    tcpip_forward_acceptor_sup[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> connection_sup
+    ssh_tcpip_forward_acceptor["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup
+    end
+    end
+
+    subgraph server
+    lsocket_sup[["ssh_lsocket_sup<br />[simple_one_for_one]"]] --> d_sup
+    ssh_lsocket_provider --> lsocket_sup
+    system_sup_s --> d_sup[["sshd_sup<br />(ssh_app.erl)<br />[o4o]"]]
+    acceptor_sup --> system_sup_s[["ssh_system_sup<br />[o4o]<br />auto_shutdown=all_significant"]]
+    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup<br />[o4o?]<br />SIGNIFICANT"]]
+
+    connection_sup_s --> system_sup_s
+
+    subgraph connection_s
+    connection_handler_s["ssh_connection_handler<br />SIGNIFICANT"] --> connection_sup_s[["ssh_connection_sup<br />[o4a]<br />auto_shutdown=any_significant<br />SIGNIFICANT"]]
+    channel_sup_s[["ssh_channel_sup<br />[o4o]"]] --> connection_sup_s
+    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> connection_sup_s
+    ssh_tcpip_forward_acceptor_s["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup_s
+    sftd1["ssh_sftpd"] --> channel_sup_s
+    end
+    end
+```
+
+# SSH supervision tree (client side update since ssh-5.2.3, ssh-5.1.4.3, ssh-4.15.3.7)
+```mermaid
+---
+title: SSH supervision tree
+---
+flowchart RL
+    d_sup --> sup[["ssh_sup<br />(ssh_app.erl)<br />[o4o]"]]
+    c_sup --> sup
+
+    subgraph client
+    connection_sup --> c_sup[["sshc_sup<br />(ssh_app.erl)<br />[o4o]<br />auto_shutdown=never"]]
+    subgraph connection_c
+    connection_handler["ssh_connection_handler<br />SIGNIFICANT"] --> connection_sup[["ssh_connection_sup<br />[o4a]<br />auto_shutdown=any_significant"]]
+    channel_sup[["ssh_channel_sup<br />[o4o]"]] --> connection_sup
+    sftp["ssh_sftp"] --> channel_sup
+    tcpip_forward_acceptor_sup[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> connection_sup
     ssh_tcpip_forward_acceptor["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup  
     end
     end
 
     subgraph server
-    system_sup_s --> d_sup[["sshd_sup\n(ssh_app.erl)\n[o4o]"]]
-    acceptor_sup --> system_sup_s[["ssh_system_sup\n[o4o]\nauto_shutdown=all_significant"]]
-    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup\n[o4o]\nSIGNIFICANT"]]
+    system_sup_s --> d_sup[["sshd_sup<br />(ssh_app.erl)<br />[o4o]"]]
+    acceptor_sup --> system_sup_s[["ssh_system_sup<br />[o4o]<br />auto_shutdown=all_significant"]]
+    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup<br />[o4o]<br />SIGNIFICANT"]]
 
     connection_sup_s --> system_sup_s
 
     subgraph connection_s
-    connection_handler_s["ssh_connection_handler\nSIGNIFICANT"] --> connection_sup_s[["ssh_connection_sup\n[o4a]\nauto_shutdown=any_significant\nSIGNIFICANT"]]
-    channel_sup_s[["ssh_channel_sup\n[o4o]"]] --> connection_sup_s
-    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup\n[o4o]"]] --> connection_sup_s
+    connection_handler_s["ssh_connection_handler<br />SIGNIFICANT"] --> connection_sup_s[["ssh_connection_sup<br />[o4a]<br />auto_shutdown=any_significant<br />SIGNIFICANT"]]
+    channel_sup_s[["ssh_channel_sup<br />[o4o]"]] --> connection_sup_s
+    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> connection_sup_s
     ssh_tcpip_forward_acceptor_s["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup_s
     sftd1["ssh_sftpd"] --> channel_sup_s
     end
@@ -41,33 +80,32 @@ flowchart RL
 title: SSH supervision tree (OTP >= 24)
 ---
 flowchart RL
-    d_sup --> sup[["ssh_sup\n(ssh_app.erl)\n[o4o]"]]
+    d_sup --> sup[["ssh_sup<br />(ssh_app.erl)<br />[o4o]"]]
     c_sup --> sup
 
     subgraph client
-    system_sup --> c_sup[["sshc_sup\n(ssh_app.erl)\n[o4o]\nauto_shutdown=never"]]
+    system_sup --> c_sup[["sshc_sup<br />(ssh_app.erl)<br />[o4o]<br />auto_shutdown=never"]]
     subgraph connection_c
-    subsystem_sup --> system_sup[["ssh_system_sup\n[o4o]\nauto_shutdown=all_significant"]]
-    connection_handler["ssh_connection_handler\nSIGNIFICANT"] --> subsystem_sup[["ssh_subsystem_sup\n[o4a]\nauto_shutdown=any_significant\nSIGNIFICANT"]]
-    channel_sup[["ssh_channel_sup\n[o4o]"]] --> subsystem_sup
+    subsystem_sup --> system_sup[["ssh_system_sup<br />[o4o]<br />auto_shutdown=all_significant"]]
+    connection_handler["ssh_connection_handler<br />SIGNIFICANT"] --> subsystem_sup[["ssh_subsystem_sup<br />[o4a]<br />auto_shutdown=any_significant<br />SIGNIFICANT"]]
+    channel_sup[["ssh_channel_sup<br />[o4o]"]] --> subsystem_sup
     sftp["ssh_sftp"] --> channel_sup
     ssh_tcpip_forward_client --> channel_sup
-    tcpip_forward_acceptor_sup[["ssh_tcpip_forward_acceptor_sup\n[o4o]"]] --> subsystem_sup
-    ssh_tcpip_forward_acceptor["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup
+    tcpip_forward_acceptor_sup[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> subsystem_sup
     end
     end
 
     subgraph server
-    system_sup_s --> d_sup[["sshd_sup\n(ssh_app.erl)\n[o4o]"]]
-    acceptor_sup --> system_sup_s[["ssh_system_sup\n[o4o]\nauto_shutdown=all_significant"]]
-    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup\n[o4o]\nSIGNIFICANT"]]
-
+    system_sup_s --> d_sup[["sshd_sup<br />(ssh_app.erl)<br />[o4o]"]]
+    acceptor_sup --> system_sup_s[["ssh_system_sup<br />[o4o]<br />auto_shutdown=all_significant"]]
+    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup<br />[o4o]<br />SIGNIFICANT"]]
+    acceptor_worker["acceptor<br />(parallel_login)"] o-. link .-o acceptor
     subsystem_sup_s --> system_sup_s
 
     subgraph connection_s
-    connection_handler_s["ssh_connection_handler\nSIGNIFICANT"] --> subsystem_sup_s[["ssh_subsystem_sup\n[o4a]\nauto_shutdown=any_significant\nSIGNIFICANT"]]
-    channel_sup_s[["ssh_channel_sup\n[o4o]"]] --> subsystem_sup_s
-    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup\n[o4o]"]] --> subsystem_sup_s
+    connection_handler_s["ssh_connection_handler<br />SIGNIFICANT"] --> subsystem_sup_s[["ssh_subsystem_sup<br />[o4a]<br />auto_shutdown=any_significant<br />SIGNIFICANT"]]
+    channel_sup_s[["ssh_channel_sup<br />[o4o]"]] --> subsystem_sup_s
+    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> subsystem_sup_s
     ssh_tcpip_forward_acceptor_s["ssh_tcpip_forward_acceptor"] --> tcpip_forward_acceptor_sup_s
     sftd1["ssh_sftpd"] --> channel_sup_s
     ssh_tcpip_forward_srv --> channel_sup_s
@@ -83,24 +121,24 @@ flowchart RL
 title: SSH supervision tree (OTP-22)
 ---
 flowchart RL
-    d_sup --> sup[["ssh_sup\n(ssh_app.erl)\n[o4o]"]]
+    d_sup --> sup[["ssh_sup<br />(ssh_app.erl)<br />[o4o]"]]
     c_sup --> sup
 
     subgraph client
-    connection_handler["ssh_connection_handler\nSIGNIFICANT?"] --> c_sup
+    connection_handler["ssh_connection_handler<br />SIGNIFICANT?"] --> c_sup
     end
 
     subgraph server
-    system_sup_s --> d_sup[["sshd_sup\n(ssh_app.erl)\n[o4o]"]]
-    acceptor_sup --> system_sup_s[["ssh_system_sup\n[o4o]\nauto_shutdown=all_significant"]]
-    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup\n[o4o]\nSIGNIFICANT"]]
+    system_sup_s --> d_sup[["sshd_sup<br />(ssh_app.erl)<br />[o4o]"]]
+    acceptor_sup --> system_sup_s[["ssh_system_sup<br />[o4o]<br />auto_shutdown=all_significant"]]
+    acceptor["ssh_acceptor"] --> acceptor_sup[["ssh_acceptor_sup<br />[o4o]<br />SIGNIFICANT"]]
 
     subsystem_sup_s --> system_sup_s
 
     subgraph connection_s
-    connection_handler_s["ssh_connection_handler\nSIGNIFICANT"] --> subsystem_sup_s[["ssh_subsystem_sup\n[o4a]\nauto_shutdown=any_significant\nSIGNIFICANT"]]
-    channel_sup_s[["ssh_channel_sup\n[o4o]"]] --> subsystem_sup_s
-    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup\n[o4o]"]] --> subsystem_sup_s
+    connection_handler_s["ssh_connection_handler<br />SIGNIFICANT"] --> subsystem_sup_s[["ssh_subsystem_sup<br />[o4a]<br />auto_shutdown=any_significant<br />SIGNIFICANT"]]
+    channel_sup_s[["ssh_channel_sup<br />[o4o]"]] --> subsystem_sup_s
+    tcpip_forward_acceptor_sup_s[["ssh_tcpip_forward_acceptor_sup<br />[o4o]"]] --> subsystem_sup_s
     sftd1["ssh_sftpd"] --> channel_sup_s
     end
 end
diff --git a/lib/ssh/src/ssh.erl b/lib/ssh/src/ssh.erl
index fdff8042eb..c651d336fb 100644
--- a/lib/ssh/src/ssh.erl
+++ b/lib/ssh/src/ssh.erl
@@ -596,12 +596,16 @@ daemon(Host0, Port0, UserOptions0)
     case ssh_options:handle_options(server, UserOptions) of
         #{} = Options0 ->
             case ssh_lsocket:get_lsocket(Host1, Port0, Options0) of
-                {ok, LSocketProvider, {ok, LSocket}} ->
-                    {Host, Port, Options1} = update_lsocket(LSocket, LSocketProvider, Options0),
+                {ok, {LSocketProvider, LSocket}} ->
+                    {Host, Port, Options1} =
+                        update_lsocket(LSocket, LSocketProvider, Options0),
                     try
-                        %% Now Host,Port is what to use for the supervisor to register its name,
-                        %% and ListenSocket, if provided,  is for listening on connections. But
-                        %% it is still owned by self()...
+                        %% Host,Port is what to use for the system
+                        %% supervisor to register its name (see
+                        %% #address record); LSocket is owned by
+                        %% LSocketProvider process.  Ownership will be
+                        %% transferred once ssh_acceptor_sup is
+                        %% started.
 
                         %% throws error:Error if no usable hostkey is found
                         ssh_connection_handler:available_hkey_algorithms(server, Options1),
@@ -610,32 +614,31 @@ daemon(Host0, Port0, UserOptions0)
                                                              profile = ?GET_OPT(profile,Options1)},
                                                     Options1)
                     of
-                        {ok,DaemonRef} ->
-                            {ok,DaemonRef};
-                        {error, {already_started, _}} ->
+                        {ok, DaemonRef} ->
+                            {ok, DaemonRef};
+                        {error, {already_started, _}} -> % ssh_system_sup with #address already register
                             close_listen_socket(LSocket, Options1),
                             {error, eaddrinuse};
                         {error, Error} ->
                             close_listen_socket(LSocket, Options1),
                             {error, Error}
                     catch
-                        error:{shutdown,Err} ->
+                        error:{shutdown, Err} -> % no suitable host key
                             close_listen_socket(LSocket, Options1),
-                            {error,Err};
-                        exit:{noproc, _} ->
+                            {error, Err};
+                        exit:{noproc, _} -> % ssh application not started
                             close_listen_socket(LSocket, Options1),
                             {error, ssh_not_started};
                         error:Error ->
                             close_listen_socket(LSocket, Options1),
-                            error(Error);
-                        exit:Exit ->
-                            close_listen_socket(LSocket, Options1),
-                            exit(Exit)
+                            {error, Error};
+                        _C:_E ->
+                            {error,{cannot_start_daemon,_C,_E}}
                     end;
-                Error = {error, _} ->
-                    Error
+                {error, {_, LSocketError}} ->
+                    {error, LSocketError}
             end;
-        OptionError = {error,_} ->
+        OptionError = {error, _} ->
             OptionError
     end;
 daemon(_, _, _) ->
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index 6502fed798..8746c2bbd4 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -2154,16 +2154,20 @@ ssh_dbg_format(connections, {call, {?MODULE,init, [[Role, Sock, Opts]]}}) ->
                             end
                     end,
                     Opts),
-    {ok, {IPp,Portp}} = inet:peername(Sock),
-    {ok, {IPs,Ports}} = inet:sockname(Sock),
+    Addresses =
+        case {inet:peername(Sock), inet:sockname(Sock)} of
+            {{ok, {IPp,Portp}}, {ok, {IPs,Ports}}} ->
+                io_lib:format("Socket = ~p, Peer = ~s, Local = ~s,~n"
+                              "Non-default options:~n~p",
+                              [Sock, ssh_lib:format_address_port(IPp,Portp),
+                               ssh_lib:format_address_port(IPs,Ports), NonDefaultOpts]);
+            {E1, E2} ->
+                io_lib:format("Socket = ~p, Peer = ~p, Local = ~p,~n"
+                              "Non-default options:~n~p",
+                              [Sock, E1, E2, NonDefaultOpts])
+        end,
     [io_lib:format("Starting ~p connection:\n",[Role]),
-     io_lib:format("Socket = ~p, Peer = ~s, Local = ~s,~n"
-                   "Non-default options:~n~p",
-                   [Sock,
-                    ssh_lib:format_address_port(IPp,Portp),
-                    ssh_lib:format_address_port(IPs,Ports),
-                    NonDefaultOpts])
-    ];
+     Addresses];
 ssh_dbg_format(connections, F) ->
     ssh_dbg_format(terminate, F);
 
diff --git a/lib/ssh/src/ssh_lsocket.erl b/lib/ssh/src/ssh_lsocket.erl
index c4d9853c0c..e92d88bac1 100644
--- a/lib/ssh/src/ssh_lsocket.erl
+++ b/lib/ssh/src/ssh_lsocket.erl
@@ -26,47 +26,53 @@
 -moduledoc false.
 
 -include("ssh.hrl").
--export([start_link/4, provide_lsocket/5, get_lsocket/3]).
+-export([start_link/4, provide_lsocket/4, get_lsocket/3]).
 
 -behaviour(ssh_dbg).
 -export([ssh_dbg_trace_points/0, ssh_dbg_flags/1, ssh_dbg_on/1, ssh_dbg_off/1,
          ssh_dbg_format/2, ssh_dbg_format/3]).
 
 get_lsocket(Host, Port, Options) ->
-    supervisor:start_child(ssh_lsocket_sup, [self(), Host, Port, Options]).
+    try
+        supervisor:start_child(ssh_lsocket_sup, [self(), Host, Port, Options])
+    of
+        {ok, LSocketProvider} ->
+            receive
+                Result = {_, {LSocketProvider, _}} ->
+                    Result
+            after
+                ?DEFAULT_TIMEOUT ->
+                    {error, LSocketProvider, no_response_from_lsocket_provider}
+            end
+    catch
+        exit:{noproc, _} ->
+            {error, {no_provider_pid, ssh_not_started}}
+    end.
 
 start_link(Caller, Host, Port, Options) ->
-    proc_lib:start_link(?MODULE, provide_lsocket,
-                            [self(), Caller, Host, Port, Options]).
+    {ok, proc_lib:spawn_link(?MODULE, provide_lsocket,
+                             [Caller, Host, Port, Options])}.
 
-provide_lsocket(Parent, _Caller, _Host1, Port0, Options) ->
-    OpenResult =
+provide_lsocket(Caller, _Host1, Port0, Options) ->
+    ListenResult =
         try
             try_listen(Port0, Options, 4)
         of
             {ok, LSocket} ->
-                {ok, LSocket};
-            Others ->
-                Others
+                {ok, {self(), LSocket}};
+            {error, Details} ->
+                {error, {self(), Details}}
         catch
-            throw:bad_fd ->
-                {error,bad_fd};
-            throw:bad_socket ->
-                {error,bad_socket};
-            error:{badmatch, {error,Error}} ->
-                {error,Error};
-            error:Error ->
-                {error,Error};
-            _C:_E ->
-                {error,{cannot_start_daemon,_C,_E}}
+            _Class:Exception ->
+                {error, {self(), Exception}}
         end,
-    case OpenResult of
-        {ok, LSocket1} ->
-            proc_lib:init_ack(Parent, {ok, self(), OpenResult}),
+    case ListenResult of
+        {ok, {_, LSocket1}} ->
+            Caller ! ListenResult,
             wait_for_acceptor_sup(LSocket1, Options),
             ok;
-        {error, _} ->
-            proc_lib:init_fail(Parent, OpenResult, {exit, normal})
+        {error, {_, _}} ->
+            Caller ! ListenResult
     end.
 
 wait_for_acceptor_sup(ListenSocket, Options) ->
@@ -118,14 +124,14 @@ ssh_dbg_trace_points() -> [connections].
 ssh_dbg_flags(connections) -> [c].
 
 ssh_dbg_on(connections) ->
-    dbg:tpl(?MODULE, provide_lsocket, 5, x),
+    dbg:tpl(?MODULE, provide_lsocket, 4, x),
     dbg:tpl(?MODULE, controlling_process, 3, x),
     dbg:tpl(?MODULE, try_listen, 4, x),
     dbg:tpl(?MODULE, wait_for_acceptor_sup, 2, x);
 ssh_dbg_on(tcp) -> dbg:tpl(?MODULE, accept, 3, x).
 
 ssh_dbg_off(connections) ->
-    dbg:ctpl(?MODULE, provide_lsocket, 5),
+    dbg:ctpl(?MODULE, provide_lsocket, 4),
     dbg:ctpl(?MODULE, controlling_process, 3),
     dbg:ctpl(?MODULE, try_listen, 4),
     dbg:ctpl(?MODULE, wait_for_acceptor_sup, 2);
diff --git a/lib/ssh/src/ssh_options.erl b/lib/ssh/src/ssh_options.erl
index 7aaeb4603d..6a55954bd0 100644
--- a/lib/ssh/src/ssh_options.erl
+++ b/lib/ssh/src/ssh_options.erl
@@ -229,7 +229,6 @@ handle_options(Role, OptsList0, Opts0) when is_map(Opts0),
         %% Enter the user's values into the map; unknown keys are
         %% treated as socket options
         check_and_save(OptsList2, OptionDefinitions, InitialMap)
-
     catch
         error:{EO, KV, Reason} when EO == eoptions ; EO == eerl_env ->
             if
diff --git a/lib/ssh/src/ssh_system_sup.erl b/lib/ssh/src/ssh_system_sup.erl
index 676c75f27f..f6b78d4e73 100644
--- a/lib/ssh/src/ssh_system_sup.erl
+++ b/lib/ssh/src/ssh_system_sup.erl
@@ -285,12 +285,12 @@ refresh_lsocket(Options0) ->
     {_OldLSock, LHost, LPort, _SockOwner} =
         ?GET_INTERNAL_OPT(lsocket, Options0, lsocket_undefined),
     case ssh_lsocket:get_lsocket(LHost, LPort, Options0) of
-        {ok, LSocketProvider, {ok, LSocket}} ->
+        {ok, {LSocketProvider, LSocket}} ->
             {_Host, _Port, Options} =
                 ssh:update_lsocket(LSocket, LSocketProvider, Options0),
             Options;
-        {error, Error} ->
-            {error, Error}
+        Error = {error, _} ->
+            Error
     end.
 
 %%%################################################################
-- 
2.43.0

openSUSE Build Service is sponsored by