File 7667-snmp-test-Conditional-docker-skip-for-one-troublesom.patch of Package erlang

From b216479114f62f6a5575bfb9a99ba216d6de8637 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Fri, 21 Jan 2022 12:59:11 +0100
Subject: [PATCH 07/12] [snmp|test] Conditional docker skip (for one
 troublesome tc)

---
 lib/snmp/test/snmp_agent_SUITE.erl | 108 +++++++++++++++--------------
 lib/snmp/test/snmp_test_lib.erl    |  93 ++++++++++++++++---------
 2 files changed, 117 insertions(+), 84 deletions(-)

diff --git a/lib/snmp/test/snmp_agent_SUITE.erl b/lib/snmp/test/snmp_agent_SUITE.erl
index 7f5c2dfec4..e2ff145d37 100644
--- a/lib/snmp/test/snmp_agent_SUITE.erl
+++ b/lib/snmp/test/snmp_agent_SUITE.erl
@@ -1092,59 +1092,65 @@ init_per_testcase1(v3_inform_i = _Case, Config) when is_list(Config) ->
 	 "~n   Config: ~p", [_Case, Config]),
     wd_start(10, Config);
 init_per_testcase1(v3_des_priv = _Case, Config) when is_list(Config) ->
-    ?DBG("init_per_testcase1 -> entry with"
-	 "~n   Case:   ~p"
-	 "~n   Config: ~p", [_Case, Config]),
-    %% <CONDITIONAL-SKIP>
-    %% This is intended to catch Yellow Dog Linux release 6.2 (2.6.29)
-    LinuxVersionVerify = 
-	fun() ->
-		case string:to_lower(os:cmd("uname -m")) of
-		    "ppc" ++ _ ->
-			case file:read_file_info("/etc/issue") of
-			    {ok, _} ->
-				case string:to_lower(
-                                       os:cmd("grep -i yellow /etc/issue")) of
-				    "yellow dog " ++ _ ->
-					case os:version() of
-					    {2, 6, 29} ->
-                                                ?IPRINT("(PPC Linux) "
-                                                        "kernel version check: "
-                                                        "{2, 6, 29} => SKIP"),
-						true;
-					    V ->
-                                                ?IPRINT("(PPC Linux) "
-                                                        "kernel version check: "
-                                                        "~p != {2, 6, 29} => "
-                                                        "*NO* SKIP", [V]),
-						false
-					end;
-				    _ -> % Maybe plain Debian or Ubuntu
-                                        ?IPRINT("(PPC Linux) => *NO* SKIP"),
-					false
-				end;
-			    _ ->
-                                ?IPRINT("(PPC Linux) Unknown distro => "
-                                        "*NO* SKIP"),
-				false
-			end;
-		    _ ->
-                        ?IPRINT("(Linux) Not PPC => *NO* SKIP"),
-			false
-		end
-	end,
-    Skippable = [{unix, [{linux, LinuxVersionVerify}]}],
-    %% </CONDITIONAL-SKIP>
-    case ?OS_BASED_SKIP(Skippable) of
-        true ->
-            {skip, "Host *may* not *properly* handle this test case"};
-        false ->
-            wd_start(6, Config)
+    ?IPRINT("init_per_testcase1 -> entry with"
+            "~n   Case:   ~p"
+            "~n   Config: ~p", [_Case, Config]),
+    case ?config(label, Config) of
+        docker ->
+            ?IPRINT("Running in docker => SKIP"),
+            {skip, "Behaves badly when run in a docker"};
+        _ ->
+            %% <OS-CONDITIONAL-SKIP>
+            %% This is intended to catch Yellow Dog Linux release 6.2 (2.6.29)
+            LinuxVersionVerify = 
+                fun() ->
+                        case string:to_lower(os:cmd("uname -m")) of
+                            "ppc" ++ _ ->
+                                case file:read_file_info("/etc/issue") of
+                                    {ok, _} ->
+                                        case string:to_lower(
+                                               os:cmd("grep -i yellow /etc/issue")) of
+                                            "yellow dog " ++ _ ->
+                                                case os:version() of
+                                                    {2, 6, 29} ->
+                                                        ?IPRINT("(PPC Linux) "
+                                                                "kernel version check: "
+                                                                "{2, 6, 29} => SKIP"),
+                                                        true;
+                                                    V ->
+                                                        ?IPRINT("(PPC Linux) "
+                                                                "kernel version check: "
+                                                                "~p != {2, 6, 29} => "
+                                                                "*NO* SKIP", [V]),
+                                                        false
+                                                end;
+                                            _ -> % Maybe plain Debian or Ubuntu
+                                                ?IPRINT("(PPC Linux) => *NO* SKIP"),
+                                                false
+                                        end;
+                                    _ ->
+                                        ?IPRINT("(PPC Linux) Unknown distro => "
+                                                "*NO* SKIP"),
+                                        false
+                                end;
+                            _ ->
+                                ?IPRINT("(Linux) Not PPC => *NO* SKIP"),
+                                false
+                        end
+                end,
+            OSSkippable = [{unix, [{linux, LinuxVersionVerify}]}],
+            %% </OS-CONDITIONAL-SKIP>
+            case ?OS_BASED_SKIP(OSSkippable) of
+                true ->
+                    {skip, "Host *may* not *properly* handle this test case"};
+                false ->
+                    wd_start(6, Config)
+            end
     end;
 init_per_testcase1(_Case, Config) when is_list(Config) ->
-    ?DBG("init_per_testcase -> entry with"
-	 "~n   Case:   ~p"
-	 "~n   Config: ~p", [_Case, Config]),
+    ?IPRINT("init_per_testcase -> entry with"
+            "~n   Case:   ~p"
+            "~n   Config: ~p", [_Case, Config]),
     wd_start(6, Config).
 
 init_per_testcase2(Case, Config) ->
diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index fa976b16f7..6b272abdff 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -710,7 +710,12 @@ init_per_suite(Config) ->
                     {skip, "Unstable host and/or os (or combo thererof)"};
                 false ->
                     snmp_test_global_sys_monitor:start(),
-                    [{snmp_factor, Factor} | Config]
+                    case lists:keysearch(label, 1, HostInfo) of
+                        {value, Label} ->
+                            [{snmp_factor, Factor}, Label | Config];
+                        false ->
+                            [{snmp_factor, Factor} | Config]
+                    end
             catch
                 throw:{skip, _} = SKIP ->
                     SKIP
@@ -772,7 +777,7 @@ maybe_skip(_HostInfo) ->
         end,
     DarwinVersionVerify =
         fun(V) when (V > {9, 8, 0}) ->
-                %% This version is OK: No Skip
+                %% These version(s) are OK: No Skip
                 false;
            (_V) ->
                 %% This version is *not* ok: Skip
@@ -985,8 +990,17 @@ ts_extra_flatform_label() ->
         Val   -> Val
     end.
 
+simplify_label(Label) ->
+    case string:to_lower(Label) of
+        "docker" ++ _ ->
+            docker;
+        _ ->
+            host
+    end.
+
 
 linux_which_distro(Version) ->
+    Label = ts_extra_flatform_label(),
     case file:read_file_info("/etc/issue") of
         {ok, _} ->
             case [string:trim(S) ||
@@ -996,41 +1010,49 @@ linux_which_distro(Version) ->
                               "~n   Distro:                  ~s"
                               "~n   TS Extra Platform Label: ~s"
                               "~n",
-                              [Version, DistroStr, ts_extra_flatform_label()]),
-                    case DistroStr of
-                        "Wind River Linux" ++ _ ->
-                            wind_river;
-                        "MontaVista" ++ _ ->
-                            montavista;
-                        "Yellow Dog" ++ _ ->
-                            yellow_dog;
-                        _ ->
-                            other
-                    end;
+                              [Version, DistroStr, Label]),
+                    {case DistroStr of
+                         "Wind River Linux" ++ _ ->
+                             wind_river;
+                         "MontaVista" ++ _ ->
+                             montavista;
+                         "Yellow Dog" ++ _ ->
+                             yellow_dog;
+                         _ ->
+                             other
+                     end,
+                     simplify_label(Label)};
                 X ->
                     io:format("Linux: ~s"
                               "~n   Distro:                  ~p"
                               "~n   TS Extra Platform Label: ~s"
                               "~n",
-                              [Version, X, ts_extra_flatform_label()]),
-                    other
+                              [Version, X, Label]),
+                    {other, simplify_label(Label)}
             end;
         _ ->
             io:format("Linux: ~s"
-                      "~n", [Version]),
-            other
+                      "~n   TS Extra Platform Label: ~s"
+                      "~n", [Version, Label]),
+            {other, simplify_label(Label)}
     end.
-    
+
+label2factor(docker) ->
+    4;
+label2factor(host) ->
+    0.
+
 analyze_and_print_linux_host_info(Version) ->
-    Distro =
+    {Distro, Label} =
         case file:read_file_info("/etc/issue") of
             {ok, _} ->
                 linux_which_distro(Version);
             _ ->
+                L = ts_extra_flatform_label(),
                 io:format("Linux: ~s"
                           "~n   TS Extra Platform Label: ~s"
-                          "~n", [Version, ts_extra_flatform_label()]),
-                other
+                          "~n", [Version, L]),
+                {other, simplify_label(L)}
         end,
     Factor =
         case (catch linux_which_cpuinfo(Distro)) of
@@ -1069,19 +1091,24 @@ analyze_and_print_linux_host_info(Version) ->
             _ ->
                 5
         end,
+    AddLabelFactor = label2factor(Label),
     %% Check if we need to adjust the factor because of the memory
-    try linux_which_meminfo() of
-        AddFactor ->
-            io:format("TS Scale Factor: ~w (~w + ~w)~n",
-                      [timetrap_scale_factor(), Factor, AddFactor]),
-            {Factor + AddFactor, []}
-    catch
-        _:_:_ ->
-            io:format("TS Scale Factor: ~w (~w)~n",
-                      [timetrap_scale_factor(), Factor]),
-            {Factor, []}
-    end.
-
+    AddMemFactor = try linux_which_meminfo()
+                   catch _:_:_ -> 0
+                   end,
+    TSScaleFactor = case timetrap_scale_factor() of
+                        N when is_integer(N) andalso (N > 0) ->
+                            N - 1;
+                        _ ->
+                            0
+                    end,
+    io:format("Factor calc:"
+              "~n      Base Factor:     ~w"
+              "~n      Label Factor:    ~w"
+              "~n      Mem Factor:      ~w"
+              "~n      TS Scale Factor: ~w"
+             "~n", [Factor, AddLabelFactor, AddMemFactor, TSScaleFactor]),
+    {Factor + AddLabelFactor + AddMemFactor + TSScaleFactor, [{label, Label}]}.
 
 
 linux_cpuinfo_lookup(Key) when is_list(Key) ->
-- 
2.34.1

openSUSE Build Service is sponsored by