File 3711-dbg-deprecates-function-dbg-stop_clear-1.patch of Package erlang

From 861be72c5a1261ee1694ee468540256f6db11e87 Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Mon, 20 Feb 2023 16:03:45 +0100
Subject: [PATCH 1/3] dbg: deprecates function dbg:stop_clear/1

function `dbg:stop_clear/1` is not documented in the API but was kept
for compatibility reasons. in this commit we make a step forward to
deprecating its use such that it will be eventually removed.

closes GH-6903.
---
 erts/emulator/test/map_SUITE.erl              |  4 +-
 lib/common_test/src/ct_run.erl                |  2 +-
 lib/compiler/test/compile_SUITE.erl           |  2 +-
 .../test/indent_SUITE_data/src/map_galore.erl |  4 +-
 .../test/map_SUITE_data/src/map_galore.erl    |  4 +-
 lib/diameter/src/info/diameter_dbg.erl        |  2 +-
 lib/diameter/test/diameter_config_SUITE.erl   |  2 +-
 lib/et/src/et_collector.erl                   |  2 +-
 lib/ftp/test/ftp_SUITE.erl                    |  2 +-
 lib/inets/test/httpd_SUITE.erl                |  2 +-
 lib/kernel/test/logger_disk_log_h_SUITE.erl   | 22 +++++-----
 lib/kernel/test/logger_std_h_SUITE.erl        |  2 +-
 lib/kernel/test/logger_stress_SUITE.erl       |  2 +-
 lib/observer/src/ttb.erl                      |  6 +--
 lib/runtime_tools/src/dbg.erl                 |  7 ++--
 lib/runtime_tools/test/dbg_SUITE.erl          | 40 +++++++++----------
 lib/ssh/src/ssh_dbg.erl                       |  2 +-
 lib/stdlib/test/gen_statem_SUITE.erl          |  2 +-
 lib/stdlib/test/supervisor_SUITE.erl          |  8 ++--
 system/doc/general_info/DEPRECATIONS          |  1 +
 20 files changed, 60 insertions(+), 58 deletions(-)

diff --git a/erts/emulator/test/map_SUITE.erl b/erts/emulator/test/map_SUITE.erl
index 030ad5ee13..317b3a1e77 100644
--- a/erts/emulator/test/map_SUITE.erl
+++ b/erts/emulator/test/map_SUITE.erl
@@ -3232,7 +3232,7 @@ t_dets(_Config) ->
 
 t_tracing(_Config) ->
 
-    dbg:stop_clear(),
+    dbg:stop(),
     {ok,Tracer} = dbg:tracer(process,{fun trace_collector/2, self()}),
     dbg:p(self(),c),
 
@@ -3285,7 +3285,7 @@ t_tracing(_Config) ->
     %% Check to extra messages
     timeout = getmsg(Tracer),
 
-    dbg:stop_clear(),
+    dbg:stop(),
     ok.
 
 getmsg(_Tracer) ->
diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl
index 4ce0d562d3..df12121197 100644
--- a/lib/common_test/src/ct_run.erl
+++ b/lib/common_test/src/ct_run.erl
@@ -3276,7 +3276,7 @@ do_trace(Terms) ->
     ok.
 
 stop_trace(true) ->
-    dbg:stop_clear();
+    dbg:stop();
 stop_trace(false) ->
     ok.
 
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index ed397a2e9f..b856f4044b 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -1577,7 +1577,7 @@ pre_load_check(Config) ->
             try
                 do_pre_load_check(Config)
             after
-                dbg:stop_clear()
+                dbg:stop()
             end
     end.
 
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
index 616d4d62bf..46c4c77d98 100644
--- a/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
+++ b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
@@ -2644,7 +2644,7 @@ t_dets(_Config) ->
 
 t_tracing(_Config) ->
 
-    dbg:stop_clear(),
+    dbg:stop(),
     {ok,Tracer} = dbg:tracer(process,{fun trace_collector/2, self()}),
     dbg:p(self(),c),
 
@@ -2697,7 +2697,7 @@ t_tracing(_Config) ->
     %% Check to extra messages
     timeout = getmsg(Tracer),
 
-    dbg:stop_clear(),
+    dbg:stop(),
     ok.
 
 getmsg(_Tracer) ->
diff --git a/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl b/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
index 99eb73a5f6..dfb0e18b3a 100644
--- a/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
+++ b/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
@@ -2644,7 +2644,7 @@ t_dets(_Config) ->
 
 t_tracing(_Config) ->
 
-    dbg:stop_clear(),
+    dbg:stop(),
     {ok,Tracer} = dbg:tracer(process,{fun trace_collector/2, self()}),
     dbg:p(self(),c),
 
@@ -2697,7 +2697,7 @@ t_tracing(_Config) ->
     %% Check to extra messages
     timeout = getmsg(Tracer),
 
-    dbg:stop_clear(),
+    dbg:stop(),
     ok.
 
 getmsg(_Tracer) ->
diff --git a/lib/diameter/src/info/diameter_dbg.erl b/lib/diameter/src/info/diameter_dbg.erl
index 9e6eb88de4..8ad393eb82 100644
--- a/lib/diameter/src/info/diameter_dbg.erl
+++ b/lib/diameter/src/info/diameter_dbg.erl
@@ -357,7 +357,7 @@ p(T) ->
 
 stop() ->
     dbg:ctp(),
-    dbg:stop_clear().
+    dbg:stop().
 
 %% tpl/1
 %% tp/1
diff --git a/lib/diameter/test/diameter_config_SUITE.erl b/lib/diameter/test/diameter_config_SUITE.erl
index 90773e8f6d..0aa0d95085 100644
--- a/lib/diameter/test/diameter_config_SUITE.erl
+++ b/lib/diameter/test/diameter_config_SUITE.erl
@@ -227,7 +227,7 @@ run(List)
     try
         ?util:run([[[fun run/1, {F, 5000}] || F <- List]])
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         diameter:stop()
     end;
 
diff --git a/lib/et/src/et_collector.erl b/lib/et/src/et_collector.erl
index 75ed1179bf..a1b7306c63 100644
--- a/lib/et/src/et_collector.erl
+++ b/lib/et/src/et_collector.erl
@@ -684,7 +684,7 @@ monitor_trace_port(CollectorPid, Parameters) ->
 		  MonitorRef = erlang:monitor(process, CollectorPid),
 		  receive
 		      {'DOWN', MonitorRef, _, _, _} ->
-			  dbg:stop_clear()
+			  dbg:stop()
 		  end
 	  end),
     Res.
diff --git a/lib/ftp/test/ftp_SUITE.erl b/lib/ftp/test/ftp_SUITE.erl
index 843cd38b8a..c1284f6ff6 100644
--- a/lib/ftp/test/ftp_SUITE.erl
+++ b/lib/ftp/test/ftp_SUITE.erl
@@ -1084,7 +1084,7 @@ error_datafail(Config) ->
     dbg:tpl(ftp_internal, verbose, []),
     dbg:p(Pid, [call]),
     {error,_} = ftp:ls(Pid),
-    dbg:stop_clear(),
+    dbg:stop(),
     Recv = fun(Recv) ->
         receive
             Msg when is_list(Msg) ->
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index b773459b95..df628257ec 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -395,7 +395,7 @@ dbg(Case, Config, Status) ->
 		    Config;
 		'end' ->
 		    io:format("dbg: stopped~n"),
-		    dbg:stop_clear(),
+		    dbg:stop(),
 		    ok
 	    end;
 	false ->
diff --git a/lib/kernel/test/logger_disk_log_h_SUITE.erl b/lib/kernel/test/logger_disk_log_h_SUITE.erl
index 08908b8b7a..fab125e5ae 100644
--- a/lib/kernel/test/logger_disk_log_h_SUITE.erl
+++ b/lib/kernel/test/logger_disk_log_h_SUITE.erl
@@ -674,7 +674,7 @@ sync(Config) ->
     check_tracer(100),
     ok.
 sync(cleanup,_Config) ->
-    dbg:stop_clear(),
+    dbg:stop(),
     logger:remove_handler(?MODULE).
 
 disk_log_wrap(Config) ->
@@ -720,7 +720,7 @@ disk_log_wrap(Config) ->
 
     %% wait for trace messages
     timer:sleep(1000),
-    dbg:stop_clear(),
+    dbg:stop(),
     Received = lists:flatmap(fun({trace,_M,handle_info,
                                   [_,{disk_log,_Node,_Name,What},_]}) ->
                                      [{trace,What}];
@@ -732,7 +732,7 @@ disk_log_wrap(Config) ->
     ok.
 
 disk_log_wrap(cleanup,_Config) ->
-    dbg:stop_clear(),
+    dbg:stop(),
     logger:remove_handler(?MODULE).
 
 disk_log_full(Config) ->
@@ -766,7 +766,7 @@ disk_log_full(Config) ->
 
     %% wait for trace messages
     timer:sleep(2000),
-    dbg:stop_clear(),
+    dbg:stop(),
     Received = lists:flatmap(fun({trace,_M,handle_info,
                                   [_,{disk_log,_Node,_Name,What},_]}) ->
                                      [{trace,What}];
@@ -782,7 +782,7 @@ disk_log_full(Config) ->
     %%  {trace,{error_status,{error,{full,_}}}}] = Received,
     ok.
 disk_log_full(cleanup, _Config) ->
-    dbg:stop_clear(),
+    dbg:stop(),
     logger:remove_handler(?MODULE).    
 
 disk_log_events(_Config) ->
@@ -816,7 +816,7 @@ disk_log_events(_Config) ->
     [whereis(h_proc_name()) ! E || E <- Events],
     %% wait for trace messages
     timer:sleep(2000),
-    dbg:stop_clear(),
+    dbg:stop(),
     Received = lists:map(fun({trace,_M,handle_info,
                               [_,Got,_]}) -> Got
                          end, test_server:messages_get()),
@@ -828,7 +828,7 @@ disk_log_events(_Config) ->
                   end, Received),
     ok.
 disk_log_events(cleanup, _Config) ->
-    dbg:stop_clear(),
+    dbg:stop(),
     logger:remove_handler(?MODULE).    
 
 write_failure(Config) ->
@@ -1603,7 +1603,7 @@ tpl([{{M,F,A},MS}|Trace]) ->
         {_,_,1} ->
             ok;
         _ ->
-            dbg:stop_clear(),
+            dbg:stop(),
             throw({skip,"Can't trace "++atom_to_list(M)++":"++
                        atom_to_list(F)++"/"++integer_to_list(A)})
     end,
@@ -1636,13 +1636,13 @@ maybe_tracer_done(Pid,Expected,Got,Caller) ->
 check_tracer(T) ->
     receive
         tracer_done ->
-            dbg:stop_clear(),
+            dbg:stop(),
             ok;
         {tracer_got_unexpected,Got,Expected} ->
-            dbg:stop_clear(),
+            dbg:stop(),
             ct:fail({tracer_got_unexpected,Got,Expected})
     after T ->
-            dbg:stop_clear(),
+            dbg:stop(),
             ct:fail({timeout,tracer})
     end.
 
diff --git a/lib/kernel/test/logger_std_h_SUITE.erl b/lib/kernel/test/logger_std_h_SUITE.erl
index ead4418d0d..88aac32f6f 100644
--- a/lib/kernel/test/logger_std_h_SUITE.erl
+++ b/lib/kernel/test/logger_std_h_SUITE.erl
@@ -2219,7 +2219,7 @@ tpl([]) ->
     ok.
 
 stop_clear() ->
-    dbg:stop_clear(),
+    dbg:stop(),
     %% Remove tracer from all processes in order to eliminate
     %% race conditions.
     erlang:trace(all,false,[all]).
diff --git a/lib/kernel/test/logger_stress_SUITE.erl b/lib/kernel/test/logger_stress_SUITE.erl
index 7fe12ca823..9209026322 100644
--- a/lib/kernel/test/logger_stress_SUITE.erl
+++ b/lib/kernel/test/logger_stress_SUITE.erl
@@ -343,7 +343,7 @@ cascade({PNode,PMFA,_PStatProcs},{CNode,CMFA,_CStatProcs},TestFun) ->
     after TO ->
             All = ets:lookup_element(Tab,producer,2),
             Written = ets:lookup_element(Tab,consumer,2),
-            dbg:stop_clear(),
+            dbg:stop(),
             ?COLLECT_STATS(All,
                            [{PNode,P,Id} || {Id,P} <- _PStatProcs] ++
                                [{CNode,P,Id} || {Id,P} <- _CStatProcs]),
diff --git a/lib/observer/src/ttb.erl b/lib/observer/src/ttb.erl
index c4161f4e2a..e7a1ae164f 100644
--- a/lib/observer/src/ttb.erl
+++ b/lib/observer/src/ttb.erl
@@ -784,7 +784,7 @@ do_stop(nofetch, Sender, NodeInfo, SessionInfo) ->
       ok,
       NodeInfo),
     stop_ip_to_file_trace_ports(SessionInfo),
-    dbg:stop_clear(),
+    dbg:stop(),
     ets:delete(?history_table),
     Sender ! {?MODULE, stopped};
 
@@ -807,7 +807,7 @@ do_stop({FetchOrFormat, UserDir}, Sender, NodeInfo, SessionInfo) ->
           [],
           NodeInfo),
     stop_ip_to_file_trace_ports(SessionInfo),
-    dbg:stop_clear(),
+    dbg:stop(),
     AllNodes =
         lists:map(
           fun({Node,MetaFile}) ->
@@ -1055,7 +1055,7 @@ format(Files,Out,Handler,DisableSort) when is_list(Files), is_list(hd(Files)) ->
     file:close(Fd),
     ets:delete(?MODULE),
     case StopDbg of
-	true -> dbg:stop_clear();
+	true -> dbg:stop();
 	false -> ok
     end,
     R.
diff --git a/lib/runtime_tools/src/dbg.erl b/lib/runtime_tools/src/dbg.erl
index ca1ce7948c..8cb65000ec 100644
--- a/lib/runtime_tools/src/dbg.erl
+++ b/lib/runtime_tools/src/dbg.erl
@@ -41,6 +41,8 @@
 
 -export_type([match_spec/0]).
 
+-deprecated([{stop_clear,0, "use dbg:stop/0 instead"}]).
+
 %%% Shell callable utility
 -spec fun2ms(LiteralFun) -> MatchSpec when
       LiteralFun :: fun((term()) -> term()),
@@ -582,14 +583,14 @@ c(M, F, A, Flags) ->
 	    Mref = erlang:monitor(process, Pid),
 	    receive
 		{'DOWN', Mref, _, _, Reason} ->
-		    stop_clear(),
+		    stop(),
 		    {error, Reason};
 		{Pid, Res} ->
 		    erlang:demonitor(Mref, [flush]),
 		    %% 'sleep' prevents the tracer (recv_all_traces) from
 		    %% receiving garbage {'EXIT',...} when dbg i stopped.
 		    timer:sleep(1),
-		    stop_clear(),
+		    stop(),
 		    Res
 	    end
     end.
@@ -1953,6 +1954,6 @@ h(stop) ->
 h(stop_clear) ->
     help_display(
       ["stop_clear() -> ok",
-       " - Stops the dbg server and the tracing of all processes,",
+       " - Deprecated. Stops the dbg server and the tracing of all processes,",
        "   and clears all trace patterns."]).
 
diff --git a/lib/runtime_tools/test/dbg_SUITE.erl b/lib/runtime_tools/test/dbg_SUITE.erl
index ce4e122107..7983e62389 100644
--- a/lib/runtime_tools/test/dbg_SUITE.erl
+++ b/lib/runtime_tools/test/dbg_SUITE.erl
@@ -50,7 +50,7 @@ init_per_suite(Config) ->
     Config.
 
 end_per_suite(_Config) ->
-    dbg:stop_clear(),
+    dbg:stop(),
     ok.
 
 %% Rudimentary interface test
@@ -89,7 +89,7 @@ big(Config) when is_list(Config) ->
 
         ok=file:set_cwd(OldCurDir)
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -120,7 +120,7 @@ tiny(Config) when is_list(Config) ->
                 failure
         end
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         ok = file:set_cwd(OldCurDir)
     end,
     ok.
@@ -136,7 +136,7 @@ simple(Config) when is_list(Config) ->
         S = self(),
         [{trace,S,call,{dbg,ltp,[]}}] = flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -152,7 +152,7 @@ message(Config) when is_list(Config) ->
         ok = dbg:ltp(),
         ok = dbg:ln()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     S = self(),
     [{trace,S,call,{dbg,ltp,[]},S},
@@ -235,7 +235,7 @@ send(Config) when is_list(Config) ->
         ok
 
     after
-	dbg:stop_clear(),
+	dbg:stop(),
         peer:stop(Peer)
     end.
 
@@ -347,7 +347,7 @@ recv(Config) when is_list(Config) ->
         ok
 
     after
-	dbg:stop_clear(),
+	dbg:stop(),
         peer:stop(Peer)
     end.
 
@@ -412,7 +412,7 @@ distributed(Config) when is_list(Config) ->
         %%
         stop()
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         peer:stop(Peer)
     end,
     ok.
@@ -463,7 +463,7 @@ local_trace(Config) when is_list(Config) ->
           {dbg_SUITE,not_exported,1},
           {error,badarith}}] = flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -488,7 +488,7 @@ port(Config) when is_list(Config) ->
          {trace,Port,getting_linked,S},
          {trace,Port,closed,normal}] = flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -514,7 +514,7 @@ saved_patterns(Config) when is_list(Config) ->
         S = self(),
         [{trace,S,call,{dbg,ltp,[]},blahonga}] = flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -546,7 +546,7 @@ ip_port(Config) when is_list(Config) ->
         [{trace,S,call,{dbg,ltp,[]},S},
          {trace,S,call,{dbg,ln,[]},hej}] = flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -562,7 +562,7 @@ ip_port_busy(Config) when is_list(Config) ->
         io:format("Error reason = ~p~n", [Reason]),
         true = port_close(Port)
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -587,7 +587,7 @@ file_port(Config) when is_list(Config) ->
          {trace,S,call,{dbg,ln,[]},hej},
          end_of_trace] = flush()
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         file:delete(FName)
     end,
     ok.
@@ -616,7 +616,7 @@ file_port2(Config) when is_list(Config) ->
         stop(),
         [] = flush()
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         file:delete(FName)
     end,
     ok.
@@ -641,7 +641,7 @@ file_tracer(Config) when is_list(Config) ->
         <<"dbg:ln()",_/binary>> = string:find(LN, "dbg:ln() (hej)"),
         stop()
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         file:delete(FName)
     end,
     ok.
@@ -709,7 +709,7 @@ wrap_port(Config) when is_list(Config) ->
         %%
         lists:map(fun(F) -> file:delete(F) end, Files)
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -781,7 +781,7 @@ wrap_port_time(Config) when is_list(Config) ->
          end_of_trace] = flush(),
         lists:map(fun(F) -> file:delete(F) end, Files)
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -807,7 +807,7 @@ with_seq_trace(Config) when is_list(Config) ->
          {seq_trace,0,{send,_,Server,S,{dbg,{ok,Tracer}}}}] =
         flush()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end,
     ok.
 
@@ -818,7 +818,7 @@ dead_suspend(Config) when is_list(Config) ->
     try
         survived = run_dead_suspend()
     after
-        dbg:stop_clear()
+        dbg:stop()
     end.
 
 run_dead_suspend() ->
diff --git a/lib/ssh/src/ssh_dbg.erl b/lib/ssh/src/ssh_dbg.erl
index 85b3399295..7ef69630fe 100644
--- a/lib/ssh/src/ssh_dbg.erl
+++ b/lib/ssh/src/ssh_dbg.erl
@@ -113,7 +113,7 @@ start(IoFmtFun) when is_function(IoFmtFun,2) ; is_function(IoFmtFun,3) ->
 
 stop() ->
     try
-        dbg:stop_clear(),
+        dbg:stop(),
         gen_server:stop(?SERVER)
     catch
         _:_ -> ok
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 6bff254b0b..d99c7e9786 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -1409,7 +1409,7 @@ terminate_crash_format(Config) ->
         terminate_crash_format(Config,format_status_statem,
                                {{formatted,idle},{formatted,crash_terminate}})
     after
-        dbg:stop_clear(),
+        dbg:stop(),
         process_flag(trap_exit, OldFl),
         error_logger_forwarder:unregister()
     end.
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index bc36c2acb7..a9cf48e997 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -2633,7 +2633,7 @@ order_of_children(_Config) ->
     [{ok,[_]} = dbg:p(P,procs) || P <- Expected1],
     terminate(Pid3, abnormal),
     receive {exited,ExitedPids1} ->
-            dbg:stop_clear(),
+            dbg:stop(),
             case ExitedPids1 of
                 Expected1 -> ok;
                 _ -> ct:fail({faulty_termination_order,
@@ -2641,7 +2641,7 @@ order_of_children(_Config) ->
                               {got,ExitedPids1}})
             end
     after 3000 ->
-            dbg:stop_clear(),
+            dbg:stop(),
             ct:fail({shutdown_fail,timeout})
     end,
 
@@ -2662,7 +2662,7 @@ order_of_children(_Config) ->
     [{ok,[_]} = dbg:p(P,procs) || P <- Expected2],
     exit(SupPid,shutdown),
     receive {exited,ExitedPids2} ->
-            dbg:stop_clear(),
+            dbg:stop(),
             case ExitedPids2 of
                 Expected2 -> ok;
                 _ -> ct:fail({faulty_termination_order,
@@ -2670,7 +2670,7 @@ order_of_children(_Config) ->
                               {got,ExitedPids2}})
             end
     after 3000 ->
-            dbg:stop_clear(),
+            dbg:stop(),
             ct:fail({shutdown_fail,timeout})
     end,
     ok.
-- 
2.35.3

openSUSE Build Service is sponsored by