File 3480-snmp-Improve-config-utility.patch of Package erlang

From 247c4e5c5e501bf1fbd8db557e4bde8e9e6b53fc Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 29 Sep 2020 19:06:46 +0200
Subject: [PATCH 10/21] [snmp] Improve config utility

Make it possible to configure several agent transports
using the snmp config utility ( snmp:config() ).

OTP-16649
---
 lib/snmp/src/misc/snmp_config.erl | 199 ++++++++++++++++++++++++++----
 1 file changed, 178 insertions(+), 21 deletions(-)

diff --git a/lib/snmp/src/misc/snmp_config.erl b/lib/snmp/src/misc/snmp_config.erl
index eff43fbb1a..a8829cc21f 100644
--- a/lib/snmp/src/misc/snmp_config.erl
+++ b/lib/snmp/src/misc/snmp_config.erl
@@ -501,6 +501,48 @@ config_agent_sys() ->
     {Vsns, ConfigDir, SysConfig}.
 
 
+config_agent_transports(ID) ->
+    config_agent_transports(ID, []).
+
+config_agent_transports(ID, []) ->
+    i(ID ++ ". Configure atleast one transport: "),
+    T = config_agent_transport(ID),
+    config_agent_transports(ID, [T]);
+config_agent_transports(ID, Acc) ->
+    case ask(ID ++ ". Configure another transport (yes/no)?",
+             "yes", fun verify_yes_or_no/1) of
+        yes ->
+            T = config_agent_transport(ID),
+            config_agent_transports(ID, [T|Acc]);
+        no ->
+            lists:reverse(Acc)
+    end.
+
+config_agent_transport(ID) ->
+    TDomain  = ask(ID ++ "a. Transport Domain "
+                   "(UDP IPv4 (u4) or UDP IPv6 (u6))", 
+                   "u4", fun verify_transport_domain/1),
+    Host     = host(TDomain),
+    Address  = ask(ID ++ "b. Address of transport",
+                   Host, fun(A) -> verify_transport_address(TDomain, A) end),
+    PortInfo = ask(ID ++ "c. Port number info (how we shall choose a port)"
+                   "~n    Note that we do not allow all variants here! "
+                   "~n    Edit manually for more variants (range/ranges)."
+                   "~n    default(d)/system(s)/pos-integer",
+                   "4000", fun verify_port_number_info/1),
+    TAddress = {Address, PortInfo},
+    Kind = ask(ID ++ "d. Kind of transport "
+               "(all(a)/request-responder(rr)/trap-sender(ts))",
+               "a", fun verify_transport_kind/1),
+    i("*** We do not ask about the transport options here ***~n"
+      "*** the user must manually edit the config files!  ***"),
+    case Kind of
+        all ->
+            {TDomain, TAddress, []};
+        _ when (Kind =:= req_responder) orelse (Kind =:= trap_sender) ->
+            {TDomain, TAddress, Kind, []}
+    end.
+
 config_agent_snmp(Dir, Vsns) ->
     i("~nAgent snmp config: "
       "~n------------------"),
@@ -512,21 +554,25 @@ config_agent_snmp(Dir, Vsns) ->
 		      EngineName, fun verify_engine_id/1),
     MMS        = ask("3. Max message size?", "484", 
 		     fun verify_max_message_size/1),
-    AgentUDP   = ask("4. The UDP port the agent listens to. "
-		     "(standard 161)",
-		     "4000", fun verify_port_number/1),
-    Host       = host(),
-    AgentIP    = ask("5. IP address for the agent (only used as id ~n"
-		     "   when sending traps)", Host, fun verify_address/1),
-    %% We intentionally skip TDomain...
-    %% If the user wish to use IPv6, the user must create an dummy entry here
-    %% and then manually edit these entries later.
+    ATransports = config_agent_transports("4"),
+    %% AgentUDP   = ask("4. The UDP port the agent listens to. "
+    %%     	     "(standard 161)",
+    %%     	     "4000", fun verify_port_number/1),
+    %% AgentIP    = ask("5. IP address for the agent (only used as id ~n"
+    %%     	     "   when sending traps)", Host, fun verify_address/1),
+
+    ManagerTDomain  = ask("5. Manager Transport Domain"
+                          "(UDP IPv4 (u4) or UDP IPv6 (u6))", 
+                          "u4", fun verify_transport_domain/1),
+    Host       = host(ManagerTDomain),
     ManagerIP  = ask("6. IP address for the manager (only this manager ~n"
 		     "   will have access to the agent, traps are sent ~n"
-		     "   to this one)", Host, fun verify_address/1),
-    TrapUdp    = ask("7. To what UDP port at the manager should traps ~n"
+		     "   to this one)", Host,
+                     fun(A) -> verify_transport_address(ManagerTDomain, A) end),
+    ManagerUdp = ask("7. To what UDP port at the manager should traps ~n"
 		     "   be sent (standard 162)?", "5000", 
 		     fun verify_port_number/1),
+
     SecType    = ask("8. Do you want a none- minimum- or semi-secure"
 		     " configuration? ~n"
 		     "   Note that if you chose v1 or v2, you won't get any"
@@ -572,8 +618,13 @@ config_agent_snmp(Dir, Vsns) ->
 		end,
 		NT
 	end,
+
+
+
     case (catch write_agent_snmp_files(
-		  Dir, Vsns, ManagerIP, TrapUdp, AgentIP, AgentUDP, SysName,
+		  Dir, Vsns,
+                  ManagerTDomain, ManagerIP, ManagerUdp,
+                  ATransports, SysName,
 		  NotifType, SecType, Passwd, EngineID, MMS)) of
 	ok ->
 	   i("~n- - - - - - - - - - - - -"),
@@ -680,7 +731,7 @@ config_manager_sys() ->
 		      "(true/false)?",
 		      "false", fun verify_bool/1),
     NetIfNoReuse = ask("17. Shall the manager IP address and port "
-		       "be not reusable (true/false)?",
+		       "be *not* reusable (true/false)?",
 		       "false", fun verify_bool/1),
     NetIfRecbuf = 
 	case ask("18. Receive buffer size of the manager (in bytes) "
@@ -1114,8 +1165,14 @@ verify_address(A, transportDomainUdpIpv6 = _Domain) ->
     do_verify_address(A, inet6).
 
 do_verify_address(A, Family) ->
+    do_verify_address(A, Family, list).
+
+do_verify_address(A, Family, Form)
+  when (Form =:= list) orelse (Form =:= tuple) ->
     case (catch snmp_misc:ip(A, Family)) of
-	{ok, IP} ->
+	{ok, IP} when (Form =:= tuple) ->
+	    {ok, IP};
+	{ok, IP} when (Form =:= list) ->
 	    {ok, tuple_to_list(IP)};
 	{error, _} ->
 	    {error, "invalid address: " ++ A};
@@ -1349,6 +1406,55 @@ verify_irb_user(TO) ->
     end.
     
 
+verify_transport_domain("u4") ->
+    {ok, transportDomainUdpIpv4};
+verify_transport_domain("udp4") ->
+    {ok, transportDomainUdpIpv4};
+verify_transport_domain("transportDomainUdpIpv4") ->
+    {ok, transportDomainUdpIpv4};
+verify_transport_domain("u6") ->
+    {ok, transportDomainUdpIpv6};
+verify_transport_domain("udp6") ->
+    {ok, transportDomainUdpIpv6};
+verify_transport_domain("transportDomainUdpIpv6") ->
+    {ok, transportDomainUdpIpv6};
+verify_transport_domain(TS) ->
+    {error, "invalid transport domain: " ++ TS}.
+
+
+verify_transport_address(transportDomainUdpIpv4 = _Domain, A) ->
+    do_verify_address(A, inet, tuple);
+verify_transport_address(transportDomainUdpIpv6 = _Domain, A) ->
+    do_verify_address(A, inet6, tuple).
+
+
+verify_transport_kind("a") ->
+    {ok, all};
+verify_transport_kind("rr") ->
+    {ok, req_responder};
+verify_transport_kind("ts") ->
+    {ok, trap_sender};
+verify_transport_kind(K) ->
+    {error, "invalid transport kind: " ++ K}.
+
+
+verify_port_number_info("d") ->
+    {ok, 0};
+verify_port_number_info("default") ->
+    {ok, 0};
+verify_port_number_info("s") ->
+    {ok, system};
+verify_port_number_info("system") ->
+    {ok, system};
+verify_port_number_info(P) ->
+    case (catch list_to_integer(P)) of
+	N when is_integer(N) andalso (N > 0) ->
+	    {ok, N};
+	_ ->
+	    {error, "invalid port number: " ++ P}
+    end.
+
+
 verify_term_disco_behaviour("discovery") ->
     {ok, discovery};
 verify_term_disco_behaviour("plain") ->
@@ -1541,17 +1647,29 @@ ask(Q, Default, Verify) when is_list(Q) andalso is_function(Verify) ->
 
 
 host() ->
+    do_host(inet).
+
+host(transportDomainUdpIpv4) ->
+    do_host(inet);
+host(transportDomainUdpIpv6) ->
+    do_host(inet6).
+
+do_host(Fam) ->
     case (catch inet:gethostname()) of
 	{ok, Name} ->
-	    case (catch inet:getaddr(Name, inet)) of
+	    case (catch inet:getaddr(Name, Fam)) of
 		{ok, Addr} when is_tuple(Addr) ->
 		    lists:flatten(
 		      io_lib:format("~w.~w.~w.~w", tuple_to_list(Addr)));
-		_ ->
-		    "127.0.0.1"
+		_ when (Fam =:= inet) ->
+		    "127.0.0.1";
+                _ when (Fam =:= inet6)  ->
+                    "::1"
 	    end;
-	_ -> 
-	    "127.0.0.1"
+        _ when (Fam =:= inet) ->
+            "127.0.0.1";
+        _ when (Fam =:= inet6)  ->
+            "::1"
     end.
 
 guess_agent_name() ->
@@ -1690,7 +1808,14 @@ write_agent_snmp_files(
     ok;
 write_agent_snmp_files(
   Dir, Vsns, Domain, ManagerAddr, AgentAddr, SysName,
-  NotifType, SecType, Passwd, EngineID, MMS) when is_tuple(AgentAddr) ->
+  NotifType, SecType, Passwd, EngineID, MMS)
+  when is_list(Dir) andalso
+       is_list(Vsns) andalso
+       is_atom(Domain) andalso
+       is_tuple(ManagerAddr) andalso
+       is_tuple(ManagerAddr) andalso
+       is_list(SysName) andalso
+       is_atom(NotifType) ->
     write_agent_snmp_conf(Dir, [{Domain, AgentAddr}], EngineID, MMS),
     write_agent_snmp_context_conf(Dir),
     write_agent_snmp_community_conf(Dir),
@@ -1704,7 +1829,15 @@ write_agent_snmp_files(
 
 write_agent_snmp_files(
   Dir, Vsns, ManagerIP, TrapUDP, AgentIP, AgentUDP, SysName,
-  NotifType, SecType, Passwd, EngineID, MMS) ->
+  NotifType, SecType, Passwd, EngineID, MMS) 
+  when is_list(Dir) andalso
+       is_list(Vsns) andalso
+       is_list(ManagerIP) andalso
+       is_integer(TrapUDP) andalso
+       is_list(AgentIP) andalso
+       is_integer(AgentUDP) andalso
+       is_list(SysName) andalso
+       is_atom(NotifType) ->
     Domain = snmp_target_mib:default_domain(),
     ManagerAddr = {ManagerIP, TrapUDP},
     write_agent_snmp_conf(Dir, AgentIP, AgentUDP, EngineID, MMS),
@@ -1716,6 +1849,30 @@ write_agent_snmp_files(
     write_agent_snmp_notify_conf(Dir, NotifType),
     write_agent_snmp_usm_conf(Dir, Vsns, EngineID, SecType, Passwd),
     write_agent_snmp_vacm_conf(Dir, Vsns, SecType),
+    ok;
+write_agent_snmp_files(
+  Dir, Vsns,
+  ManagerTDomain, ManagerIP, ManagerTrapUDP,
+  AgentTransports, SysName,
+  NotifType, SecType, Passwd, EngineID, MMS) 
+  when is_list(Dir) andalso
+       is_list(Vsns) andalso
+       is_atom(ManagerTDomain) andalso
+       is_tuple(ManagerIP) andalso
+       is_integer(ManagerTrapUDP) andalso
+       is_list(AgentTransports) andalso
+       is_list(SysName) andalso
+       is_atom(NotifType) ->
+    ManagerAddr = {ManagerIP, ManagerTrapUDP},
+    write_agent_snmp_conf(Dir, AgentTransports, EngineID, MMS),
+    write_agent_snmp_context_conf(Dir),
+    write_agent_snmp_community_conf(Dir),
+    write_agent_snmp_standard_conf(Dir, SysName),
+    write_agent_snmp_target_addr_conf(Dir, ManagerTDomain, ManagerAddr, Vsns),
+    write_agent_snmp_target_params_conf(Dir, Vsns),
+    write_agent_snmp_notify_conf(Dir, NotifType),
+    write_agent_snmp_usm_conf(Dir, Vsns, EngineID, SecType, Passwd),
+    write_agent_snmp_vacm_conf(Dir, Vsns, SecType),
     ok.
 
 
-- 
2.26.2

openSUSE Build Service is sponsored by