File 2436-snmp-test-Some-os-calls-on-windows-takes-a-long-time.patch of Package erlang

From b4e754dfa75e2d3623d947028fa51319cf7e3af0 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 29 Apr 2020 15:58:40 +0200
Subject: [PATCH 6/6] [snmp|test] Some os calls on windows takes a *long* time

We try to wrap os:cmd("systeminfo") in a process spawn in order
to provide a timeout.
---
 lib/snmp/test/snmp_test_lib.erl | 62 ++++++++++++++++++++-------------
 lib/snmp/test/snmp_test_lib.hrl |  3 ++
 2 files changed, 40 insertions(+), 25 deletions(-)

diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index 661d85920b..1d3e66a901 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -25,6 +25,7 @@
 
 -export([tc_try/2, tc_try/3,
          tc_try/4, tc_try/5]).
+-export([proxy_call/3]).
 -export([hostname/0, hostname/1, localhost/0, localhost/1, os_type/0, sz/1,
 	 display_suite_info/1]).
 -export([non_pc_tc_maybe_skip/4,
@@ -257,6 +258,19 @@ tc_which_name() ->
 %% Misc functions
 %%
 
+proxy_call(F, Timeout, Default)
+  when is_function(F, 0) andalso is_integer(Timeout) andalso (Timeout > 0) ->
+    {P, M} = erlang:spawn_monitor(fun() -> exit(F()) end),
+    receive
+        {'DOWN', M, process, P, Reply} ->
+            Reply
+    after Timeout ->
+            erlang:demonitor(M, [flush]),
+            exit(P, kill),
+            Default
+    end.
+
+
 hostname() ->
     hostname(node()).
 
@@ -268,20 +282,6 @@ hostname(Node) ->
             []
     end.
 
-%% localhost() ->
-%%     {ok, Ip} = snmp_misc:ip(net_adm:localhost()),
-%%     Ip.
-%% localhost(Family) ->
-%%     {ok, Ip} = snmp_misc:ip(net_adm:localhost(), Family),
-%%     Ip.
-
-%% localhost() ->
-%%     {ok, Ip} = snmp_misc:ip(net_adm:localhost()),
-%%     Ip.
-%% localhost(Family) ->
-%%     {ok, Ip} = snmp_misc:ip(net_adm:localhost(), Family),
-%%     Ip.
-
 localhost() ->
     localhost(inet).
 
@@ -623,6 +623,8 @@ old_is_ipv6_host(Hostname) ->
 
 init_per_suite(Config) ->
 
+    ct:timetrap(minutes(2)),
+
     %% We have some crap machines that causes random test case failures
     %% for no obvious reason. So, attempt to identify those without actually
     %% checking for the host name...
@@ -1791,14 +1793,24 @@ win_sys_info_lookup(Key, SysInfo, Def) ->
 
 %% This function only extracts the prop we actually care about!
 which_win_system_info() ->
-    SysInfo = os:cmd("systeminfo"),
-    try process_win_system_info(string:tokens(SysInfo, [$\r, $\n]), [])
-    catch
-        _:_:_ ->
-            io:format("Failed process System info: "
-                      "~s~n", [SysInfo]),
-            []
-    end.
+    F = fun() ->
+                try
+                    begin
+                        SysInfo = os:cmd("systeminfo"),
+                        process_win_system_info(
+                          string:tokens(SysInfo, [$\r, $\n]), [])
+                    end
+                catch
+                    C:E:S ->
+                        io:format("Failed get or process System info: "
+                                  "   Error Class: ~p"
+                                  "   Error:       ~p"
+                                  "   Stack:       ~p"
+                                  "~n", [C, E, S]),
+                        []
+                end
+        end,
+    proxy_call(F, minutes(1), []).
 
 process_win_system_info([], Acc) ->
     Acc;
@@ -1885,7 +1897,7 @@ sleep(MSecs) ->
 
 %% ----------------------------------------------------------------
 %% Process utility function
-%% 
+%%
 
 flush_mqueue() ->
     io:format("~p~n", [lists:reverse(flush_mqueue([]))]).
@@ -1900,10 +1912,10 @@ flush_mqueue(MQ) ->
 
     
 trap_exit() -> 
-    {trap_exit,Flag} = process_info(self(),trap_exit),Flag.
+    {trap_exit, Flag} = process_info(self(),trap_exit), Flag.
 
 trap_exit(Flag) -> 
-    process_flag(trap_exit,Flag).
+    process_flag(trap_exit, Flag).
 
 
 
diff --git a/lib/snmp/test/snmp_test_lib.hrl b/lib/snmp/test/snmp_test_lib.hrl
index f4863c9a1e..a853d3cc09 100644
--- a/lib/snmp/test/snmp_test_lib.hrl
+++ b/lib/snmp/test/snmp_test_lib.hrl
@@ -52,10 +52,13 @@
 -define(OS_BASED_SKIP(Skippable), ?LIB:os_based_skip(Skippable)).
 -define(NON_PC_TC_MAYBE_SKIP(Config, Condition),
         ?LIB:non_pc_tc_maybe_skip(Config, Condition, ?MODULE, ?LINE)).
+
 -define(SKIP(Reason),        ?LIB:skip(Reason, ?MODULE, ?LINE)).
 -define(FAIL(Reason),        ?LIB:fail(Reason, ?MODULE, ?LINE)).
 -define(HAS_SUPPORT_IPV6(),  ?LIB:has_support_ipv6()).
 
+-define(PCALL(F, T, D),      ?LIB:proxy_call(F, T, D)).
+
 
 %% - Time macros -
 
-- 
2.26.1

openSUSE Build Service is sponsored by