File 7102-snmp-manager-BACKWARD-compatibility-cleanup.patch of Package erlang

From e2ea7296d5d75740f4946645c377f36a40075483 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 8 Sep 2021 18:03:16 +0200
Subject: [PATCH 2/5] [snmp|manager] BACKWARD compatibility cleanup

OTP-17612
---
 lib/snmp/src/manager/snmpm_config.erl       |  88 +-------
 lib/snmp/src/manager/snmpm_server.erl       | 212 --------------------
 lib/snmp/test/snmp_manager_config_SUITE.erl |  28 ++-
 3 files changed, 26 insertions(+), 302 deletions(-)

diff --git a/lib/snmp/src/manager/snmpm_config.erl b/lib/snmp/src/manager/snmpm_config.erl
index 356ba44b08..06457d9167 100644
--- a/lib/snmp/src/manager/snmpm_config.erl
+++ b/lib/snmp/src/manager/snmpm_config.erl
@@ -38,7 +38,7 @@
 
 	 register_agent/3, unregister_agent/2, 
 	 agent_info/0, agent_info/2, agent_info/3, 
-	 update_agent_info/3, update_agent_info/4, 
+	 update_agent_info/3,
 	 which_agents/0, which_agents/1, 
 
 	 is_known_engine_id/2, 
@@ -94,9 +94,7 @@
 
 %% Backward compatibillity exports
 -export([
-	 register_user/3,
 	 unregister_agent/3, 
-	 update_agent_info/5,
 	 is_known_engine_id/3, 
 	 get_agent_engine_id/2, 
 	 get_agent_engine_max_message_size/2, 
@@ -109,12 +107,15 @@
 	 check_manager_config/2,
 	 check_user_config/1,
 	 check_agent_config/1,
-	 check_usm_user_config/1]).
+	 check_usm_user_config/1
+        ]).
 
 
 %% gen_server callbacks
--export([init/1, handle_call/3, handle_cast/2, handle_info/2, 
-	 code_change/3, terminate/2]).
+-export([
+         init/1, handle_call/3, handle_cast/2, handle_info/2, 
+	 code_change/3, terminate/2
+        ]).
 
 
 %% Includes:
@@ -191,10 +192,6 @@ is_started() ->
 backup(BackupDir) when is_list(BackupDir) ->
     call({backup, BackupDir}).
 
-%% Backward compatibillity
-register_user(UserId, UserMod, UserData) ->
-    register_user(UserId, UserMod, UserData, []).
-
 register_user(UserId, UserMod, UserData, DefaultAgentConfig) 
   when (UserId =/= ?DEFAULT_USER) andalso is_list(DefaultAgentConfig) ->
     case (catch verify_user_behaviour(UserMod)) of
@@ -214,20 +211,6 @@ register_user(UserId, _UserMod, _UserData, DefaultAgentConfig)
 register_user(UserId, _, _, _) ->
     {error, {bad_user_id, UserId}}.
 
-%% default_agent_config(DefaultAgentConfig) ->
-%%     {ok, SystemDefaultAgentConfig} = agent_info(),
-%%     default_agent_config(SystemDefaultAgentConfig, DefaultAgentConfig).
-
-%% default_agent_config([], DefaultAgentConfig) ->
-%%     DefaultAgentConfig;
-%% default_agent_config([{Key, _} = Entry|T], DefaultAgentConfig) ->
-%%     case lists:keymember(Key, 1, DefaultAgentConfig) of
-%% 	true ->
-%% 	    default_agent_config(T, DefaultAgentConfig);
-%% 	false ->
-%% 	    default_agent_config(T, [Entry|DefaultAgentConfig])
-%%     end.
-
 
 verify_user_behaviour(UserMod) ->
     case snmp_misc:verify_behaviour(snmpm_user, UserMod) of
@@ -546,23 +529,6 @@ which_agents(UserId) ->
 update_agent_info(UserId, TargetName, Info) ->
     call({update_agent_info, UserId, TargetName, Info}).
 
-%% <BACKWARD-COMPAT-2>
-%% This is wrapped in the interface module, so this function is
-%% only here to catch code-upgrade problems.
-update_agent_info(UserId, TargetName, Item, Val) ->
-    update_agent_info(UserId, TargetName, [{Item, Val}]).
-%% </BACKWARD-COMPAT-2>
-
-%% <BACKWARD-COMPAT-1>
-update_agent_info(UserId, Addr, Port, Item, Val)  ->
-    case agent_info(Addr, Port, target_name) of
-	{ok, TargetName} ->
-	    update_agent_info(UserId, TargetName, Item, Val);
-	Error ->
-	    Error
-    end.
-%% </BACKWARD-COMPAT-1>
-
 is_known_engine_id(EngineID, TargetName) ->
     case agent_info(TargetName, engine_id) of
 	{ok, EngineID} ->
@@ -2444,18 +2410,6 @@ handle_call({update_agent_info, UserId, TargetName, Info},
     Reply = handle_update_agent_info(UserId, TargetName, Info),
     {reply, Reply, State};
 
-%% <BACKWARD-COMPAT>
-handle_call({update_agent_info, UserId, TargetName, Item, Val}, 
-	    _From, State) ->
-    ?vlog("received update_agent_info request: "
-	  "~n   UserId:     ~p"
-	  "~n   TargetName: ~p"
-	  "~n   Item:       ~p"
-	  "~n   Val:        ~p", [UserId, TargetName, Item, Val]),
-    Reply = handle_update_agent_info(UserId, TargetName, Item, Val),
-    {reply, Reply, State};
-%% </BACKWARD-COMPAT>
-
 handle_call({register_usm_user, User}, _From, State) ->
     ?vlog("received register_usm_user request: "
 	  "~n   User: ~p", [User]),
@@ -2828,6 +2782,7 @@ handle_register_agent(UserId, TargetName, Config) ->
 			    "   FixedConfig: ~p", [FixedConfig]),
 		    do_handle_register_agent(
 		      TargetName, [{user_id, UserId}|FixedConfig]),
+
 		    %% <DIRTY-BACKWARD-COMPATIBILLITY>
 		    %% And now for some (backward compatibillity)
 		    %% dirty crossref stuff
@@ -2841,25 +2796,6 @@ handle_register_agent(UserId, TargetName, Config) ->
 			       {{Domain, Address, target_name}, TargetName}),
 		    %% </DIRTY-BACKWARD-COMPATIBILLITY>
 
-%%		    %% First, insert this users default config
-%%		    ?vtrace("handle_register_agent -> store default config", []),
-%%		    do_handle_register_agent(TargetName, DefConfig),
-%%		    %% Second, insert the config for this agent
-%%		    ?vtrace("handle_register_agent -> store config", []),
-%%		    do_handle_register_agent(TargetName,
-%%					     [{user_id, UserId}|Config]),
-%%		    %% <DIRTY-BACKWARD-COMPATIBILLITY>
-%%		    %% And now for some (backward compatibillity)
-%%		    %% dirty crossref stuff
-%%		    ?vtrace("handle_register_agent -> lookup taddress", []),
-%%		    {ok, {Addr, Port} = TAddress} =
-%%			agent_info(TargetName, taddress),
-%%		    ?vtrace("handle_register_agent -> taddress: ~p",
-%%			    [TAddress]),
-%%		    ?vtrace("handle_register_agent -> register cross-ref fix", []),
-%%		    ets:insert(snmpm_agent_table,
-%%			       {{Addr, Port, target_name}, TargetName}),
-%%		    %% </DIRTY-BACKWARD-COMPATIBILLITY>
 		    ok;
 		_ ->
 		    {error, {not_found, UserId}}
@@ -2964,14 +2900,6 @@ handle_update_agent_info(TargetName, Info) ->
 	    {error, {failed_info_verification, Info, T, E}}
     end.
 
-handle_update_agent_info(UserId, TargetName, Item, Val) ->
-    ?vdebug("handle_update_agent_info -> entry with"
-	    "~n   UserId:     ~p"
-	    "~n   TargetName: ~p"
-	    "~n   Item:       ~p"
-	    "~n   Val:        ~p", [UserId, TargetName, Item, Val]),
-    handle_update_agent_info(TargetName, [{Item, Val}]).
-
 do_update_agent_info(TargetName, Info) ->
     ?vtrace("do_update_agent_info -> entry with~n"
 	    "   TargetName: ~p~n"
diff --git a/lib/snmp/src/manager/snmpm_server.erl b/lib/snmp/src/manager/snmpm_server.erl
index ca18637b8d..07c3a335d8 100644
--- a/lib/snmp/src/manager/snmpm_server.erl
+++ b/lib/snmp/src/manager/snmpm_server.erl
@@ -571,24 +571,6 @@ handle_call({sync_get, Pid, UserId, TargetName, Oids, SendOpts},
 	    {reply, Error, State}
     end;
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({sync_get, 
-	     Pid, UserId, TargetName, CtxName, Oids, Timeout, ExtraInfo}, 
-	    From, State) ->
-    ?vlog("[~p,~p,~p] received sync_get request for: "
-	  "~n   ~p", [UserId, TargetName, CtxName, Oids]),
-    case (catch handle_sync_get(Pid, 
-				UserId, TargetName, CtxName, Oids, 
-				Timeout, ExtraInfo, From, State)) of
-	ok ->
-	    {noreply, State};
-	Error ->
-	    {reply, Error, State}
-    end;
-%% </BACKWARD-COMPAT>
-
-
 handle_call({sync_get_next, Pid, UserId, TargetName, Oids, SendOpts}, 
 	    From, State) ->
     ?vlog("[~p,~p] received sync_get_next request for: "
@@ -603,24 +585,6 @@ handle_call({sync_get_next, Pid, UserId, TargetName, Oids, SendOpts},
     end;
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({sync_get_next, 
-	     Pid, UserId, TargetName, CtxName, Oids, Timeout, ExtraInfo}, 
-	    From, State) ->
-    ?vlog("[~p,~p,~p] received sync_get_next request for"
-	  "~n   ~p", [UserId, TargetName, CtxName, Oids]),
-    case (catch handle_sync_get_next(Pid, 
-				     UserId, TargetName, CtxName, Oids, 
-				     Timeout, ExtraInfo, From, State)) of
-	ok ->
-	    {noreply, State};
-	Error ->
-	    {reply, Error, State}
-    end;
-%% </BACKWARD-COMPAT>
-
-
 %% Check agent version? This op not in v1
 handle_call({sync_get_bulk, 
 	     Pid, UserId, TargetName, NonRep, MaxRep, Oids, SendOpts}, 
@@ -636,24 +600,6 @@ handle_call({sync_get_bulk,
 	    {reply, Error, State}
     end;
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({sync_get_bulk, Pid, UserId, TargetName, 
-	     NonRep, MaxRep, CtxName, Oids, Timeout, ExtraInfo}, 
-	    From, State) ->
-    ?vlog("[~p,~p] received sync_get_bulk request for: ~p"
-	  "~n   ~p", [UserId, TargetName, CtxName, Oids]),
-    case (catch handle_sync_get_bulk(Pid, 
-				     UserId, TargetName, CtxName, 
-				     NonRep, MaxRep, Oids, 
-				     Timeout, ExtraInfo, From, State)) of
-	ok ->
-	    {noreply, State};
-	Error ->
-	    {reply, Error, State}
-    end;
-%% </BACKWARD-COMPAT>
-
 
 handle_call({sync_set, 
 	     Pid, UserId, TargetName, VarsAndVals, SendOpts}, 
@@ -670,24 +616,6 @@ handle_call({sync_set,
     end;
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({sync_set, Pid, UserId, TargetName, 
-	     CtxName, VarsAndVals, Timeout, ExtraInfo}, 
-	    From, State) ->
-    ?vlog("[~p,~p,~p] received sync_set request for: "
-	  "~n   ~p", [UserId, TargetName, CtxName, VarsAndVals]),
-    case (catch handle_sync_set(Pid, 
-				UserId, TargetName, CtxName, VarsAndVals, 
-				Timeout, ExtraInfo, From, State)) of
-	ok ->
-	    {noreply, State};
-	Error ->
-	    {reply, Error, State}
-    end;
-%% </BACKWARD-COMPAT>
-
-
 handle_call({async_get, Pid, UserId, TargetName, Oids, SendOpts}, 
 	    _From, State) ->
     ?vlog("[~p,~p] received async_get request for: "
@@ -698,19 +626,6 @@ handle_call({async_get, Pid, UserId, TargetName, Oids, SendOpts},
     {reply, Reply, State};
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({async_get, Pid, UserId, TargetName, 
-	     CtxName, Oids, Expire, ExtraInfo}, 
-	    _From, State) ->
-    ?vlog("[~p,~p,~p] received async_get request for: "
-	  "~n   ~p", [UserId, TargetName, CtxName, Oids]),
-    Reply = (catch handle_async_get(Pid, UserId, TargetName, CtxName, Oids, 
-				    Expire, ExtraInfo, State)),
-    {reply, Reply, State};
-%% </BACKWARD-COMPAT>
-
-
 handle_call({async_get_next, Pid, UserId, TargetName, Oids, SendOpts}, 
 	    _From, State) ->
     ?vlog("[~p,~p] received async_get_next request for: "
@@ -721,19 +636,6 @@ handle_call({async_get_next, Pid, UserId, TargetName, Oids, SendOpts},
     {reply, Reply, State};
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({async_get_next, Pid, UserId, TargetName, 
-	     CtxName, Oids, Expire, ExtraInfo}, 
-	    _From, State) ->
-    ?vlog("[~p,~p,~p] received async_get_next request for: ", 
-	  [UserId, TargetName, CtxName, Oids]),
-    Reply = (catch handle_async_get_next(Pid, UserId, TargetName, CtxName, 
-					 Oids, Expire, ExtraInfo, State)),
-    {reply, Reply, State};
-%% </BACKWARD-COMPAT>
-
-
 %% Check agent version? This op not in v1
 handle_call({async_get_bulk, 
 	     Pid, UserId, TargetName, NonRep, MaxRep, Oids, SendOpts}, 
@@ -747,21 +649,6 @@ handle_call({async_get_bulk,
     {reply, Reply, State};
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({async_get_bulk, Pid, UserId, TargetName, 
-	     NonRep, MaxRep, CtxName, Oids, Expire, ExtraInfo}, 
-	    _From, State) ->
-    ?vlog("[~p,~p,~p] received async_get_bulk request for: "
-	  "~n   ~p", [UserId, TargetName, CtxName, Oids]),
-    Reply = (catch handle_async_get_bulk(Pid, 
-					 UserId, TargetName, CtxName, 
-					 NonRep, MaxRep, Oids, 
-					 Expire, ExtraInfo, State)),
-    {reply, Reply, State};
-%% </BACKWARD-COMPAT>
-
-
 handle_call({async_set, 
 	     Pid, UserId, TargetName, VarsAndVals, SendOpts}, 
 	    _From, State) ->
@@ -773,19 +660,6 @@ handle_call({async_set,
     {reply, Reply, State};
 
 
-%% <BACKWARD-COMPAT>
-%% The only case where this would be called is during code upgrade
-handle_call({async_set, Pid, UserId, TargetName, 
-	     CtxName, VarsAndVals, Expire, ExtraInfo}, 
-	    _From, State) ->
-    ?vlog("[~p,~p,~p] received async_set request for: "
-	  "~n   ~p", [UserId, TargetName, CtxName, VarsAndVals]),
-    Reply = (catch handle_async_set(Pid, UserId, TargetName, CtxName, 
-				    VarsAndVals, Expire, ExtraInfo, State)),
-    {reply, Reply, State};
-%% </BACKWARD-COMPAT>
-
-
 handle_call({cancel_async_request, UserId, ReqId}, _From, State) ->
     ?vlog("received cancel_async_request request", []),
     Reply = (catch handle_cancel_async_request(UserId, ReqId, State)),
@@ -1024,16 +898,6 @@ terminate(Reason, #state{nis_pid = NIS, gct = GCT, cbproxy = CBP}) ->
 %% 
 %%----------------------------------------------------------------------
 
-handle_sync_get(Pid, UserId, TargetName, CtxName, Oids, Timeout, ExtraInfo, 
-		From, State) ->    
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Timeout},
-	 {extra,   ExtraInfo}
-	],
-    handle_sync_get(Pid, UserId, TargetName, Oids, SendOpts, From, State).
-
 handle_sync_get(Pid, UserId, TargetName, Oids, SendOpts, From, State) -> 
     ?vtrace("handle_sync_get -> entry with"
 	    "~n   Pid:        ~p"
@@ -1076,16 +940,6 @@ handle_sync_get(Pid, UserId, TargetName, Oids, SendOpts, From, State) ->
 	    Error
     end.
     
-handle_sync_get_next(Pid, UserId, TargetName, CtxName, Oids, Timeout, 
-		     ExtraInfo, From, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Timeout},
-	 {extra,   ExtraInfo}
-	],
-    handle_sync_get_next(Pid, UserId, TargetName, Oids, SendOpts, From, State).
-
 handle_sync_get_next(Pid, UserId, TargetName, Oids, SendOpts, 
 		     From, State) ->
     ?vtrace("handle_sync_get_next -> entry with"
@@ -1131,18 +985,6 @@ handle_sync_get_next(Pid, UserId, TargetName, Oids, SendOpts,
     end.
 
 
-handle_sync_get_bulk(Pid, UserId, TargetName, CtxName, 
-		     NonRep, MaxRep, Oids, Timeout, 
-		     ExtraInfo, From, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Timeout},
-	 {extra,   ExtraInfo}
-	],
-    handle_sync_get_bulk(Pid, UserId, TargetName, NonRep, MaxRep, Oids, 
-			 SendOpts, From, State).
-
 handle_sync_get_bulk(Pid, UserId, TargetName, NonRep, MaxRep, Oids, SendOpts, 
 		     From, State) ->
     ?vtrace("handle_sync_get_bulk -> entry with"
@@ -1190,17 +1032,6 @@ handle_sync_get_bulk(Pid, UserId, TargetName, NonRep, MaxRep, Oids, SendOpts,
     end.
 
 
-handle_sync_set(Pid, UserId, TargetName, CtxName, VarsAndVals, Timeout, 
-		ExtraInfo, From, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Timeout},
-	 {extra,   ExtraInfo}
-	],
-    handle_sync_set(Pid, UserId, TargetName, VarsAndVals, SendOpts, 
-		    From, State).
-
 handle_sync_set(Pid, UserId, TargetName, VarsAndVals, SendOpts, From, State) ->
     ?vtrace("handle_sync_set -> entry with"
 	    "~n   Pid:         ~p"
@@ -1245,16 +1076,6 @@ handle_sync_set(Pid, UserId, TargetName, VarsAndVals, SendOpts, From, State) ->
     end.
 
  
-handle_async_get(Pid, UserId, TargetName, CtxName, Oids, Expire, ExtraInfo, 
-		 State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Expire},
-	 {extra,   ExtraInfo}
-	],
-    handle_async_get(Pid, UserId, TargetName, Oids, SendOpts, State).
-
 handle_async_get(Pid, UserId, TargetName, Oids, SendOpts, State) ->
     ?vtrace("handle_async_get -> entry with"
 	    "~n   Pid:        ~p"
@@ -1294,16 +1115,6 @@ handle_async_get(Pid, UserId, TargetName, Oids, SendOpts, State) ->
     end.
 
 
-handle_async_get_next(Pid, UserId, TargetName, CtxName, Oids, Expire, 
-		      ExtraInfo, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Expire},
-	 {extra,   ExtraInfo}
-	],
-    handle_async_get_next(Pid, UserId, TargetName, Oids, SendOpts, State).
-
 handle_async_get_next(Pid, UserId, TargetName, Oids, SendOpts, State) ->
     ?vtrace("handle_async_get_next -> entry with"
 	    "~n   Pid:        ~p"
@@ -1343,19 +1154,6 @@ handle_async_get_next(Pid, UserId, TargetName, Oids, SendOpts, State) ->
     end.
 
 
-handle_async_get_bulk(Pid, UserId, TargetName, CtxName, 
-		      NonRep, MaxRep, Oids, Expire, 
-		      ExtraInfo, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Expire},
-	 {extra,   ExtraInfo}
-	],
-    handle_async_get_bulk(Pid, 
-			  UserId, TargetName, NonRep, MaxRep, Oids, SendOpts, 
-			  State).
-
 handle_async_get_bulk(Pid, 
 		      UserId, TargetName, NonRep, MaxRep, Oids, SendOpts, 
 		      State) ->
@@ -1398,16 +1196,6 @@ handle_async_get_bulk(Pid,
     end.
 
 
-handle_async_set(Pid, UserId, TargetName, CtxName, VarsAndVals, Expire, 
-		 ExtraInfo, State) ->
-    SendOpts = 
-	[
-	 {context, CtxName},
-	 {timeout, Expire},
-	 {extra,   ExtraInfo}
-	],
-    handle_async_set(Pid, UserId, TargetName, VarsAndVals, SendOpts, State).
-
 handle_async_set(Pid, UserId, TargetName, VarsAndVals, SendOpts, State) ->
     ?vtrace("handle_async_set -> entry with"
 	    "~n   Pid:         ~p"
diff --git a/lib/snmp/test/snmp_manager_config_SUITE.erl b/lib/snmp/test/snmp_manager_config_SUITE.erl
index f7f7fd6928..3eaf2d1af1 100644
--- a/lib/snmp/test/snmp_manager_config_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_config_SUITE.erl
@@ -2037,18 +2037,18 @@ do_register_agent_using_file(Conf) ->
     
     %% --
     ?IPRINT("EngineID (~p) for agent <~w,~w>", [EngineID2, AgentAddr2, AgentPort2]),
-    ?line {ok, EngineID2} = 
+    ?line {ok, EngineID2} =
 	snmpm_config:agent_info(AgentAddr2, AgentPort2, engine_id),
 
     %% --
-    ?line {ok, MMS2} = 
+    ?line {ok, MMS2} =
 	snmpm_config:agent_info(AgentAddr2, AgentPort2, max_message_size),
     NewMMS21 = 2048,
     ?IPRINT("try update agent info max-message-size to ~w for agent <~w,~w>", 
       [NewMMS21, AgentAddr2, AgentPort2]),
-    ?line ok = snmpm_config:update_agent_info(UserId2, AgentAddr2, AgentPort2,
-					      max_message_size, NewMMS21),
-    ?line {ok, NewMMS21} = 
+    ?line ok = update_agent_info(UserId2, AgentAddr2, AgentPort2,
+                                 max_message_size, NewMMS21),
+    ?line {ok, NewMMS21} =
 	snmpm_config:agent_info(AgentAddr2, AgentPort2, max_message_size),
 
     %% --
@@ -2057,8 +2057,8 @@ do_register_agent_using_file(Conf) ->
       "with user ~w (not owner)", 
       [NewMMS21, AgentAddr2, AgentPort2, UserId1]),
     ?line {error, Reason01} = 
-	snmpm_config:update_agent_info(UserId1, AgentAddr2, AgentPort2,
-				       max_message_size, NewMMS21),
+	update_agent_info(UserId1, AgentAddr2, AgentPort2,
+                          max_message_size, NewMMS21),
     ?IPRINT("expected failure. Reason01: ~p", [Reason01]), 
     ?line {ok, NewMMS21} = 
 	snmpm_config:agent_info(AgentAddr2, AgentPort2, max_message_size),
@@ -2069,9 +2069,9 @@ do_register_agent_using_file(Conf) ->
       "for agent <~w,~w>", 
       [NewMMS22, AgentAddr2, AgentPort2]),
     ?line {error, Reason02} = 
-	snmpm_config:update_agent_info(UserId1, AgentAddr2, AgentPort2,
-				       max_message_size, NewMMS22),
-    ?IPRINT("expected failure. Reason02: ~p", [Reason02]), 
+	update_agent_info(UserId1, AgentAddr2, AgentPort2,
+                          max_message_size, NewMMS22),
+    ?IPRINT("expected failre. Reason02: ~p", [Reason02]), 
 
     %% --
     ?IPRINT("done"),
@@ -2744,6 +2744,14 @@ otp8395_incr_counter(Counter, Initial, Increment, Max) ->
 %% Internal functions
 %%======================================================================
 
+update_agent_info(UserId, Addr, Port, Item, Val)  ->
+    case snmpm_config:agent_info(Addr, Port, target_name) of
+	{ok, TargetName} ->
+	    snmpm_config:update_agent_info(UserId, TargetName, [{Item, Val}]);
+	Error ->
+	    Error
+    end.
+
 config_start(Opts) ->
     (catch snmpm_config:start_link(Opts)).
 
-- 
2.31.1

openSUSE Build Service is sponsored by