File 5608-megaco-test-More-info-on-NetBSD-and-Windows.patch of Package erlang

From b5eed9e4e63f17d367b0bcc91b5db0d696dfd31f Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 4 Mar 2020 19:51:03 +0100
Subject: [PATCH 8/8] [megaco|test] More info on NetBSD and Windows

Enhanzed the host analyze function. Add analyze for
NetBSD.
Add system model to the windows analyze function.
---
 lib/megaco/test/megaco_test_lib.erl | 176 +++++++++++++++++++++++++++++++++---
 1 file changed, 161 insertions(+), 15 deletions(-)

diff --git a/lib/megaco/test/megaco_test_lib.erl b/lib/megaco/test/megaco_test_lib.erl
index 1e4b7841ee..d73ed45add 100644
--- a/lib/megaco/test/megaco_test_lib.erl
+++ b/lib/megaco/test/megaco_test_lib.erl
@@ -482,20 +482,20 @@ init_per_suite(Config) ->
     %% which are *old and crappy" and slow, because it
     %% causes a bunch of test cases to fail randomly.
     %% But we don not want to test for the host name...
-    WinVersionVerify =
-        fun(V) when (V =:= {6,2,9200}) ->
-                try erlang:system_info(schedulers) of
-                    2 ->
-                        true;
-                    _ ->
-                        false
-                catch
-                    _:_:_ ->
-                        true
-                end;
-           (_) ->
-                false
-        end,
+    %% WinVersionVerify =
+    %%     fun(V) when (V =:= {6,2,9200}) ->
+    %%             try erlang:system_info(schedulers) of
+    %%                 2 ->
+    %%                     true;
+    %%                 _ ->
+    %%                     false
+    %%             catch
+    %%                 _:_:_ ->
+    %%                     true
+    %%             end;
+    %%        (_) ->
+    %%             false
+    %% end,
     COND = [
             {unix, [{linux,  LinuxVersionVerify}, 
 		    {darwin, DarwinVersionVerify}]},
@@ -589,6 +589,8 @@ analyze_and_print_host_info() ->
             analyze_and_print_openbsd_host_info(Version);
         {unix, freebsd} ->
             analyze_and_print_freebsd_host_info(Version);           
+        {unix, netbsd} ->
+            analyze_and_print_netbsd_host_info(Version);           
         {unix, sunos} ->
             analyze_and_print_solaris_host_info(Version);
         {win32, nt} ->
@@ -982,6 +984,142 @@ analyze_freebsd_item(Extract, Key, Process, Default) ->
     end.
 
 
+analyze_and_print_netbsd_host_info(Version) ->
+    io:format("NetBSD:"
+              "~n   Version: ~p"
+              "~n", [Version]),
+    %% This test require that the program 'sysctl' is in the path.
+    %% First test with 'which sysctl', if that does not work
+    %% try with 'which /sbin/sysctl'. If that does not work either,
+    %% we skip the test...
+    try
+        begin
+            SysCtl =
+                case string:trim(os:cmd("which sysctl")) of
+                    [] ->
+                        case string:trim(os:cmd("which /sbin/sysctl")) of
+                            [] ->
+                                throw(sysctl);
+                            SC2 ->
+                                SC2
+                        end;
+                    SC1 ->
+                        SC1
+                end,
+            Extract =
+                fun(Key) ->
+                        [string:trim(S) ||
+                            S <-
+                                string:tokens(string:trim(os:cmd(SysCtl ++ " " ++ Key)),
+                                              [$=])]
+                end,
+            CPU      = analyze_netbsd_cpu(Extract),
+            Machine  = analyze_netbsd_machine(Extract),
+            Arch     = analyze_netbsd_machine_arch(Extract),
+            CPUSpeed = analyze_netbsd_cpu_speed(Extract),
+            NCPU     = analyze_netbsd_ncpu(Extract),
+            Memory   = analyze_netbsd_memory(Extract),
+            io:format("CPU:"
+                      "~n   Model:          ~s (~s, ~s)"
+                      "~n   Speed:          ~w MHz"
+                      "~n   N:              ~w"
+                      "~n   Num Schedulers: ~w"
+                      "~nMemory:"
+                      "~n   ~w KB"
+                      "~n",
+                      [CPU, Machine, Arch, CPUSpeed, NCPU,
+                       erlang:system_info(schedulers), Memory]),
+            CPUFactor =
+                if
+                    (CPUSpeed =:= -1) ->
+                        1;
+                    (CPUSpeed >= 2000) ->
+                        if
+                            (NCPU >= 4) ->
+                                1;
+                            (NCPU >= 2) ->
+                                2;
+                            true ->
+                                3
+                        end;
+                    true ->
+                        if
+                            (NCPU =:= -1) ->
+                                1;
+                            (NCPU >= 4) ->
+                                2;
+                            (NCPU >= 2) ->
+                                3;
+                            true ->
+                                4
+                        end
+                end,
+            MemAddFactor =
+                if
+                    (Memory =:= -1) ->
+                        0;
+                    (Memory >= 8388608) ->
+                        0;
+                    (Memory >= 4194304) ->
+                        1;
+                    (Memory >= 2097152) ->
+                        2;
+                    true ->
+                        3
+                end,
+            CPUFactor + MemAddFactor
+        end
+    catch
+        _:_:_ ->
+            io:format("CPU:"
+                      "~n   Num Schedulers: ~w"
+                      "~n", [erlang:system_info(schedulers)]),
+            case erlang:system_info(schedulers) of
+                1 ->
+                    10;
+                2 ->
+                    5;
+                _ ->
+                    2
+            end
+    end.
+
+analyze_netbsd_cpu(Extract) ->
+    analyze_netbsd_item(Extract, "hw.model", fun(X) -> X end, "-").
+
+analyze_netbsd_machine(Extract) ->
+    analyze_netbsd_item(Extract, "hw.machine", fun(X) -> X end, "-").
+
+analyze_netbsd_machine_arch(Extract) ->
+    analyze_netbsd_item(Extract, "hw.machine_arch", fun(X) -> X end, "-").
+
+analyze_netbsd_cpu_speed(Extract) ->
+    analyze_netbsd_item(Extract, "machdep.dmi.processor-frequency", 
+                        fun(X) -> case string:tokens(X, [$\ ]) of
+                                      [MHz, "MHz"] ->
+                                          list_to_integer(MHz);
+                                      _ ->
+                                          -1
+                                  end
+                        end, "-").
+
+analyze_netbsd_ncpu(Extract) ->
+    analyze_netbsd_item(Extract,
+                        "hw.ncpu",
+                        fun(X) -> list_to_integer(X) end,
+                        -1).
+
+analyze_netbsd_memory(Extract) ->
+    analyze_netbsd_item(Extract,
+                        "hw.physmem64",
+                        fun(X) -> list_to_integer(X) div 1024 end,
+                        -1).
+
+analyze_netbsd_item(Extract, Key, Process, Default) ->
+    analyze_freebsd_item(Extract, Key, Process, Default).
+
+
+
 analyze_and_print_solaris_host_info(Version) ->
     Release =
         case file:read_file_info("/etc/release") of
@@ -1113,14 +1251,19 @@ analyze_and_print_win_host_info(Version) ->
     OsName     = win_sys_info_lookup(os_name,             SysInfo),
     OsVersion  = win_sys_info_lookup(os_version,          SysInfo),
     SysMan     = win_sys_info_lookup(system_manufacturer, SysInfo),
+    SysMod     = win_sys_info_lookup(system_model,        SysInfo),
     NumProcs   = win_sys_info_lookup(num_processors,      SysInfo),
     TotPhysMem = win_sys_info_lookup(total_phys_memory,   SysInfo),
     io:format("Windows: ~s"
               "~n   OS Version:             ~s (~p)"
               "~n   System Manufacturer:    ~s"
+              "~n   System Model:           ~s"
               "~n   Number of Processor(s): ~s"
               "~n   Total Physical Memory:  ~s"
-              "~n", [OsName, OsVersion, Version, SysMan, NumProcs, TotPhysMem]),
+              "~n   Num Schedulers:         ~s"
+              "~n", [OsName, OsVersion, Version,
+		     SysMan, SysMod, NumProcs, TotPhysMem,
+		     str_num_schedulers()]),
     MemFactor =
         try
             begin
@@ -1211,6 +1354,9 @@ process_win_system_info([H|T], Acc) ->
                 "system manufacturer" ->
                     process_win_system_info(T,
                                             [{system_manufacturer, string:trim(Value)}|Acc]);
+                "system model" ->
+                    process_win_system_info(T,
+                                            [{system_model, string:trim(Value)}|Acc]);
                 "processor(s)" ->
                     [NumProcStr|_] = string:tokens(Value, [$\ ]),
                     T2 = lists:nthtail(list_to_integer(NumProcStr), T),
-- 
2.16.4

openSUSE Build Service is sponsored by