File 7101-snmp-agent-BACKWARD-compatibility-cleanup.patch of Package erlang

From 375a21b15e880628ebfd2aa9a5ccd0da3cd46c9f Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Mon, 6 Sep 2021 18:04:54 +0200
Subject: [PATCH 1/5] [snmp|agent] BACKWARD compatibility cleanup

Deleted "dead", 'BACKWARD compatibility, code.

OTP-17612
---
 lib/snmp/src/agent/snmpa.erl            |  15 +-
 lib/snmp/src/agent/snmpa_agent.erl      | 242 +-----------------------
 lib/snmp/src/agent/snmpa_mib.erl        |  24 ---
 lib/snmp/src/agent/snmpa_net_if.erl     |  12 --
 lib/snmp/src/agent/snmpa_trap.erl       |  18 --
 lib/snmp/test/snmp_agent_mibs_SUITE.erl |   4 +-
 6 files changed, 14 insertions(+), 301 deletions(-)

diff --git a/lib/snmp/src/agent/snmpa.erl b/lib/snmp/src/agent/snmpa.erl
index 995e6d627d..74205e5716 100644
--- a/lib/snmp/src/agent/snmpa.erl
+++ b/lib/snmp/src/agent/snmpa.erl
@@ -149,6 +149,11 @@
 %% Options specific to the above module
 -type mib_storage_options() :: list().
 
+-type mib_module()    :: atom().
+-type table_name()    :: atom().
+-type variable_name() :: atom().
+-type mib_info()      :: {mib_module(), [table_name()], [variable_name()]}.
+
 
 %%-----------------------------------------------------------------
 %% This utility function is used to convert an old SNMP application
@@ -340,11 +345,11 @@ unload_mib(Agent, Mib) ->
     end.
 
 unload_mibs(Mibs) ->
-    unload_mibs(snmp_master_agent, Mibs, false).
+    unload_mibs(snmp_master_agent, Mibs).
 unload_mibs(Agent, Mibs) when is_list(Mibs) -> 
-    snmpa_agent:unload_mibs(Agent, Mibs);
+    unload_mibs(Agent, Mibs, false);
 unload_mibs(Mibs, Force) 
-  when is_list(Mibs) andalso ((Force =:= true) orelse (Force =:= false)) ->
+  when is_list(Mibs) andalso is_boolean(Force) ->
     unload_mibs(snmp_master_agent, Mibs, Force).
 
 -spec unload_mibs(Agent :: pid() | atom(), 
@@ -353,7 +358,7 @@ unload_mibs(Mibs, Force)
     ok | {error, {'unload aborted at', MibName :: string(), InternalReason :: not_loaded | term()}}.
 
 unload_mibs(Agent, Mibs, Force) 
-  when is_list(Mibs) andalso ((Force =:= true) orelse (Force =:= false)) ->
+  when is_list(Mibs) andalso is_boolean(Force) ->
     snmpa_agent:unload_mibs(Agent, Mibs, Force).
 
 
@@ -369,6 +374,8 @@ whereis_mib(Agent, Mib) when is_atom(Mib) ->
 
 %% -
 
+-spec mibs_info() -> [mib_info()].
+
 mibs_info() ->
     [
      {snmp_standard_mib, 
diff --git a/lib/snmp/src/agent/snmpa_agent.erl b/lib/snmp/src/agent/snmpa_agent.erl
index 5039b08391..48630489fa 100644
--- a/lib/snmp/src/agent/snmpa_agent.erl
+++ b/lib/snmp/src/agent/snmpa_agent.erl
@@ -65,18 +65,11 @@
 -export([increment_counter/3]).
 -export([restart_worker/1, restart_set_worker/1, restart_notif_worker/1]).
 
-%% For backward compatibillity
--export([send_trap/6, send_trap/7]).
-
 %% Internal exports
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
 	 terminate/2, code_change/3, tr_var/2, tr_varbind/1,
 	 handle_pdu/8, worker/4, worker_loop/2, 
 	 do_send_trap/7, do_send_trap/8]).
-%% <BACKWARD-COMPAT>
--export([handle_pdu/7, 
-	 load_mibs/2, unload_mibs/2]).
-%% </BACKWARD-COMPAT>
 
 -include("snmpa_internal.hrl").
 
@@ -559,21 +552,9 @@ subagent_set(SubAgent, Arguments) ->
     call(SubAgent, {subagent_set, Arguments, PduData}).
 
 
-%% Called by administrator (not agent; deadlock would occur)
-%% <BACKWARD-COMPAT>
-load_mibs(Agent, Mibs) ->
-    load_mibs(Agent, Mibs, false).
-%% </BACKWARD-COMPAT>
-
 load_mibs(Agent, Mibs, Force) ->
     call(Agent, {load_mibs, Mibs, Force}).
 
-%% Called by administrator (not agent; deadlock would occur)
-%% <BACKWARD-COMPAT>
-unload_mibs(Agent, Mibs) ->
-    unload_mibs(Agent, Mibs, false).
-%% </BACKWARD-COMPAT>
-
 unload_mibs(Agent, Mibs, Force) ->
     call(Agent, {unload_mibs, Mibs, Force}).
 
@@ -622,51 +603,6 @@ send_notification(Agent, Notification, SendOpts) ->
     Msg = {send_notif, Notification, SendOpts},
     maybe_call(Agent, Msg).
     
-%% <BACKWARD-COMPAT>
-send_trap(Agent, Trap, NotifyName, CtxName, Recv, Varbinds) ->
-    ?d("send_trap -> entry with"
-       "~n   self():        ~p"
-       "~n   Agent:         ~p [~p]"
-       "~n   Trap:          ~p"
-       "~n   NotifyName:    ~p"
-       "~n   CtxName:       ~p"
-       "~n   Recv:          ~p"
-       "~n   Varbinds:      ~p", 
-       [self(), Agent, wis(Agent), 
-	Trap, NotifyName, CtxName, Recv, Varbinds]),
-    SendOpts = [
-		{receiver, Recv},
-		{varbinds, Varbinds}, 
-		{name,     NotifyName},
-		{context,  CtxName}, 
-		{extra,    ?DEFAULT_NOTIF_EXTRA_INFO}
-	       ],
-    send_notification(Agent, Trap, SendOpts).
-    
-send_trap(Agent, Trap, NotifyName, CtxName, Recv, Varbinds, LocalEngineID) ->
-    ?d("send_trap -> entry with"
-       "~n   self():        ~p"
-       "~n   Agent:         ~p [~p]"
-       "~n   Trap:          ~p"
-       "~n   NotifyName:    ~p"
-       "~n   CtxName:       ~p"
-       "~n   Recv:          ~p"
-       "~n   Varbinds:      ~p" 
-       "~n   LocalEngineID: ~p", 
-       [self(), Agent, wis(Agent), 
-	Trap, NotifyName, CtxName, Recv, Varbinds, LocalEngineID]),
-    SendOpts = [
-		{receiver,        Recv},
-		{varbinds,        Varbinds}, 
-		{name,            NotifyName},
-		{context,         CtxName}, 
-		{extra,           ?DEFAULT_NOTIF_EXTRA_INFO}, 
-		{local_engine_id, LocalEngineID}
-	       ],
-    send_notification(Agent, Trap, SendOpts).
-    
-%% </BACKWARD-COMPAT>
-
 
 %% -- Discovery functions --
 
@@ -863,51 +799,6 @@ handle_info({send_notif, Notification, SendOpts}, S) ->
 	    {noreply, S}
     end;
 
-%% <BACKWARD-COMPAT>
-handle_info({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}, S) ->
-    ?vlog("[handle_info] send trap request:"
-	  "~n   Trap:          ~p"
-	  "~n   NotifyName:    ~p"
-	  "~n   ContextName:   ~p"
-	  "~n   Recv:          ~p" 
-	  "~n   Varbinds:      ~p", 
-	  [Trap, NotifyName, ContextName, Recv, Varbinds]),
-    ExtraInfo     = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    LocalEngineID = local_engine_id(S),
-    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
-				 Recv, Varbinds, LocalEngineID, ExtraInfo)) of
-	{ok, NewS} ->
-	    {noreply, NewS};
-	{'EXIT', R} ->
-	    ?vinfo("Trap not sent:~n   ~p", [R]),
-	    {noreply, S};
-	_ ->
-	    {noreply, S}
-    end;
-
-handle_info({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds, 
-	     LocalEngineID}, S) ->
-    ?vlog("[handle_info] send trap request:"
-	  "~n   Trap:          ~p"
-	  "~n   NotifyName:    ~p"
-	  "~n   ContextName:   ~p"
-	  "~n   Recv:          ~p" 
-	  "~n   Varbinds:      ~p" 
-	  "~n   LocalEngineID: ~p", 
-	  [Trap, NotifyName, ContextName, Recv, Varbinds, LocalEngineID]),
-    ExtraInfo = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
-				 Recv, Varbinds, LocalEngineID, ExtraInfo)) of
-	{ok, NewS} ->
-	    {noreply, NewS};
-	{'EXIT', R} ->
-	    ?vinfo("Trap not sent:~n   ~p", [R]),
-	    {noreply, S};
-	_ ->
-	    {noreply, S}
-    end;
-%% </BACKWARD-COMPAT>
-
 handle_info({forward_trap, TrapRecord, NotifyName, ContextName, 
 	     Recv, Varbinds, ExtraInfo}, S) ->
     ?vlog("[handle_info] forward trap request:"
@@ -929,30 +820,6 @@ handle_info({forward_trap, TrapRecord, NotifyName, ContextName,
 	    {noreply, S}
     end;
 
-%% <BACKWARD-COMPAT>
-handle_info({forward_trap, TrapRecord, NotifyName, ContextName, 
-	     Recv, Varbinds}, S) ->
-    ?vlog("[handle_info] forward trap request:"
-	  "~n   TrapRecord:    ~p"
-	  "~n   NotifyName:    ~p"
-	  "~n   ContextName:   ~p"
-	  "~n   Recv:          ~p"
-	  "~n   Varbinds:      ~p", 
-	  [TrapRecord, NotifyName, ContextName, Recv, Varbinds]),
-    ExtraInfo     = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    LocalEngineID = ?DEFAULT_LOCAL_ENGINE_ID, 
-    case (catch maybe_send_trap(S, TrapRecord, NotifyName, ContextName,
-				Recv, Varbinds, LocalEngineID, ExtraInfo)) of
-	{ok, NewS} ->
-	    {noreply, NewS};
-	{'EXIT', R} ->
-	    ?vinfo("Trap not sent:~n   ~p", [R]),
-	    {noreply, S};
-	_ ->
-	    {noreply, S}
-    end;
-%% </BACKWARD-COMPAT>
-
 handle_info({backup_done, Reply}, #state{backup = {_, From}} = S) ->
     ?vlog("[handle_info] backup done:"
 	  "~n   Reply: ~p", [Reply]),
@@ -1075,55 +942,6 @@ handle_call({send_notif, Notification, SendOpts}, _From, S) ->
 	    {reply, {error, send_failed}, S}
     end;
 
-%% <BACKWARD-COMPAT>
-handle_call({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}, 
-	    _From, S) ->
-    ?vlog("[handle_call] send trap request:"
-	  "~n   Trap:          ~p"
-	  "~n   NotifyName:    ~p"
-	  "~n   ContextName:   ~p"
-	  "~n   Recv:          ~p" 
-	  "~n   Varbinds:      ~p", 
-	  [Trap, NotifyName, ContextName, Recv, Varbinds]),
-    ExtraInfo     = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    LocalEngineID = local_engine_id(S),
-    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
-				 Recv, Varbinds, LocalEngineID, ExtraInfo)) of
-	{ok, NewS} ->
-	    {reply, ok, NewS};
-	{'EXIT', Reason} ->
-	    ?vinfo("Trap not sent:~n   ~p", [Reason]),
-	    {reply, {error, {send_failed, Reason}}, S};
-	_ ->
-	    ?vinfo("Trap not sent", []),
-	    {reply, {error, send_failed}, S}
-    end;
-
-handle_call({send_trap, Trap, NotifyName, 
-	     ContextName, Recv, Varbinds, LocalEngineID}, 
-	    _From, S) ->
-    ?vlog("[handle_call] send trap request:"
-	  "~n   Trap:          ~p"
-	  "~n   NotifyName:    ~p"
-	  "~n   ContextName:   ~p"
-	  "~n   Recv:          ~p" 
-	  "~n   Varbinds:      ~p" 
-	  "~n   LocalEngineID: ~p", 
-	  [Trap, NotifyName, ContextName, Recv, Varbinds, LocalEngineID]),
-    ExtraInfo = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    case (catch handle_send_trap(S, Trap, NotifyName, ContextName,
-				 Recv, Varbinds, LocalEngineID, ExtraInfo)) of
-	{ok, NewS} ->
-	    {reply, ok, NewS};
-	{'EXIT', Reason} ->
-	    ?vinfo("Trap not sent:~n   ~p", [Reason]),
-	    {reply, {error, {send_failed, Reason}}, S};
-	_ ->
-	    ?vinfo("Trap not sent", []),
-	    {reply, {error, send_failed}, S}
-    end;
-%% </BACKWARD-COMPAT>
-
 handle_call({discovery, 
 	     TargetName, Notification, ContextName, Vbs, DiscoHandler, 
 	     ExtraInfo}, 
@@ -1262,22 +1080,10 @@ handle_call({unregister_subagent, SubTreeOid}, _From, S) ->
 	end,
     {reply, Reply, S};
 
-%% <BACKWARD-COMPAT>
-handle_call({load_mibs, Mibs}, _From, S) ->
-    ?vlog("load mibs ~p", [Mibs]),
-    {reply, snmpa_mib:load_mibs(get(mibserver), Mibs), S};
-%% </BACKWARD-COMPAT>
-
 handle_call({load_mibs, Mibs, Force}, _From, S) ->
     ?vlog("[~w] load mibs ~p", [Force, Mibs]),
     {reply, snmpa_mib:load_mibs(get(mibserver), Mibs, Force), S};
 
-%% <BACKWARD-COMPAT>
-handle_call({unload_mibs, Mibs}, _From, S) ->
-    ?vlog("unload mibs ~p", [Mibs]),
-    {reply, snmpa_mib:unload_mibs(get(mibserver), Mibs), S};
-%% </BACKWARD-COMPAT>
-
 handle_call({unload_mibs, Mibs, Force}, _From, S) ->
     ?vlog("[~w] unload mibs ~p", [Force, Mibs]),
     {reply, snmpa_mib:unload_mibs(get(mibserver), Mibs, Force), S};
@@ -1876,46 +1682,6 @@ worker_loop(Master, Report) ->
 		exit(normal);
 
 
-
-
-	    %% *************************************************************
-	    %% 
-	    %%         Kept for backward compatibillity reasons
-	    %% 
-	    %% *************************************************************
-	    
-	    {Vsn, Pdu, PduMS, ACMData, Address, Extra} ->
-		?vtrace("worker_loop -> received request", []),
-		handle_pdu2(Vsn, Pdu, PduMS, ACMData, Address, 
-			    ?DEFAULT_GB_MAX_VBS, Extra),
-		Master ! worker_available;
-	    
-	    %% We don't trap exits!
-	    {TrapRec, NotifyName, ContextName, Recv, Vbs} -> 
-		?vtrace("worker_loop -> send trap:"
-			"~n   ~p", [TrapRec]),
-		snmpa_trap:send_trap(TrapRec, NotifyName, 
-				     ContextName, Recv, Vbs, get(net_if)),
-		Master ! worker_available;
-	    
-	    %% We don't trap exits!
-	    {send_trap, 
-	     TrapRec, NotifyName, ContextName, Recv, Vbs, LocalEngineID,
-	     ExtraInfo} -> 
-		?vtrace("worker_loop -> send trap:"
-			"~n   ~p", [TrapRec]),
-		snmpa_trap:send_trap(TrapRec, NotifyName, 
-				     ContextName, Recv, Vbs, 
-				     LocalEngineID, ExtraInfo, 
-				     get(net_if)),
-		Master ! worker_available;
-	    
-	    {verbosity, Verbosity} ->
-		put(verbosity, snmp_verbosity:validate(Verbosity));
-	    
-	    terminate ->
-		exit(normal);
-	    
 	    _X ->
 		%% ignore
 		ignore_unknown
@@ -1972,12 +1738,6 @@ handle_snmp_pdu(_, _Vsn, _Pdu, _PduMS, _ACMData, _Address, _Extra, S) ->
     S.
 
 
-%% Called via the spawn_thread function
-%% <BACKWARD-COMPAT>
-handle_pdu(Vsn, Pdu, PduMS, ACMData, Address, Extra, Dict) ->
-    handle_pdu(Vsn, Pdu, PduMS, ACMData, Address, ?DEFAULT_GB_MAX_VBS, Extra, 
-	       Dict).
-%% </BACKWARD-COMPAT>
 handle_pdu(Vsn, Pdu, PduMS, ACMData, Address, GbMaxVBs, Extra, Dict) ->
     lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
     put(sname, pdu_handler_short_name(get(sname))),
diff --git a/lib/snmp/src/agent/snmpa_mib.erl b/lib/snmp/src/agent/snmpa_mib.erl
index 8e594213f9..5ac258b7c1 100644
--- a/lib/snmp/src/agent/snmpa_mib.erl
+++ b/lib/snmp/src/agent/snmpa_mib.erl
@@ -47,11 +47,6 @@
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2,
 	 code_change/3]).
 
-%% <BACKWARD-COMPAT>
--export([load_mibs/2, unload_mibs/2]).
-%% </BACKWARD-COMPAT>
-
-
 -include_lib("kernel/include/file.hrl").
 -include("snmpa_internal.hrl").
 -include("snmp_types.hrl").
@@ -204,11 +199,6 @@ next(MibServer, Oid, MibView) ->
 %% Returns: ok | {error, Reason}
 %%----------------------------------------------------------------------
 
-%% <BACKWARD-COMPAT>
-load_mibs(MibServer, Mibs) ->
-    load_mibs(MibServer, Mibs, false).
-%% </BACKWARD-COMPAT>
-
 load_mibs(MibServer, Mibs, Force) ->
     call(MibServer, {load_mibs, Mibs, Force}).
 
@@ -219,10 +209,6 @@ load_mibs(MibServer, Mibs, Force) ->
 %%       Force is a boolean
 %% Returns: ok | {error, Reason}
 %%----------------------------------------------------------------------
-%% <BACKWARD-COMPAT>
-unload_mibs(MibServer, Mibs) ->
-    unload_mibs(MibServer, Mibs, false).
-%% </BACKWARD-COMPAT>
 
 unload_mibs(MibServer, Mibs, Force) ->
     call(MibServer, {unload_mibs, Mibs, Force}).
@@ -514,11 +500,6 @@ handle_call({next, Oid, MibView}, _From,
     ?vdebug("next -> Reply: ~p", [Reply]), 
     {reply, Reply, NewState};
 
-%% <BACKWARD-COMPAT>
-handle_call({load_mibs, Mibs}, From, State) ->
-    handle_call({load_mibs, Mibs, false}, From, State);
-%% </BACKWARD-COMPAT>
-
 handle_call({load_mibs, Mibs, Force}, _From, 
 	    #state{data         = Data, 
 		   teo          = TeOverride, 
@@ -540,11 +521,6 @@ handle_call({load_mibs, Mibs, Force}, _From,
     Mod:sync(NData),
     {reply, Reply, State#state{data = NData, cache = NewCache}};
 
-%% <BACKWARD-COMPAT>
-handle_call({unload_mibs, Mibs}, From, State) ->
-    handle_call({unload_mibs, Mibs, false}, From, State);
-%% </BACKWARD-COMPAT>
-
 handle_call({unload_mibs, Mibs, Force}, _From, 
 	    #state{data         = Data, 
 		   teo          = TeOverride, 
diff --git a/lib/snmp/src/agent/snmpa_net_if.erl b/lib/snmp/src/agent/snmpa_net_if.erl
index cdb68afef4..c32d94d95a 100644
--- a/lib/snmp/src/agent/snmpa_net_if.erl
+++ b/lib/snmp/src/agent/snmpa_net_if.erl
@@ -678,18 +678,6 @@ loop(#state{transports = Transports,
 		  S, Vsn, Pdu, MsgData, TDomAddrs, From),
 	    loop(NewS);
 
-	%% Discovery Inform
-	%% <BACKWARD-COMPAT>
-	{send_discovery, Pdu, MsgData, To, From} ->
-	    ?vdebug("received send discovery request: "
-		    "~n   Pdu:  ~p"
-		    "~n   To:   ~p"
-		    "~n   From: ~p", 
-		    [Pdu, To, toname(From)]),
-	    NewS = handle_send_discovery(S, Pdu, MsgData, To, From),
-	    loop(NewS);
-	%% </BACKWARD-COMPAT>
-
 	%% Discovery Inform
 	{send_discovery, Pdu, MsgData, To, From, ExtraInfo} ->
 	    ?vdebug("received send discovery request: "
diff --git a/lib/snmp/src/agent/snmpa_trap.erl b/lib/snmp/src/agent/snmpa_trap.erl
index 9ee854b67d..f0e1e20713 100644
--- a/lib/snmp/src/agent/snmpa_trap.erl
+++ b/lib/snmp/src/agent/snmpa_trap.erl
@@ -34,11 +34,6 @@
 	 send_inform/6]).
 -export([init_discovery_inform/13, send_discovery_inform/5]).
 
-%% <BACKWARD-COMPAT>
--export([send_discovery/5, 
-	 init_discovery_inform/12]).
-%% </BACKWARD-COMPAT>
-
 -include_lib("snmp/include/snmp_types.hrl").
 -include_lib("snmp/src/agent/snmpa_internal.hrl").
 -include_lib("snmp/include/SNMPv2-MIB.hrl").
@@ -438,9 +433,6 @@ do_send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs,
     send_trap_pdus(Dests, ContextName, {TrapRec, VarbindList}, [], [], [],
 		   Recv, LocalEngineID, ExtraInfo, NetIf).
 
-send_discovery(TargetName, Record, ContextName, Vbs, NetIf) ->
-    ExtraInfo = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    send_discovery(TargetName, Record, ContextName, Vbs, NetIf, ExtraInfo).
 send_discovery(TargetName, Record, ContextName, Vbs, NetIf, ExtraInfo) ->
     case find_dest(TargetName) of
 	{ok, Dest} ->
@@ -715,16 +707,6 @@ send_discovery_pdu(Record, Dest, Vbs,
 				  ExtraInfo]),
     {ok, Sender, SecLevel}.
 
-init_discovery_inform(Parent, 
-		      Dest, 
-		      SecModel, SecName, SecLevel, TargetName, 
-		      ContextName, Timeout, Retry, Vbs, NetIf, Verbosity) ->
-    ExtraInfo = ?DEFAULT_NOTIF_EXTRA_INFO, 
-    init_discovery_inform(Parent, 
-			  Dest, 
-			  SecModel, SecName, SecLevel, TargetName, 
-			  ContextName, Timeout, Retry, Vbs, NetIf, 
-			  Verbosity, ExtraInfo).
 init_discovery_inform(Parent, 
 		      Dest, 
 		      SecModel, SecName, SecLevel, TargetName, 
diff --git a/lib/snmp/test/snmp_agent_mibs_SUITE.erl b/lib/snmp/test/snmp_agent_mibs_SUITE.erl
index ce6ec80322..d5ee395b89 100644
--- a/lib/snmp/test/snmp_agent_mibs_SUITE.erl
+++ b/lib/snmp/test/snmp_agent_mibs_SUITE.erl
@@ -989,13 +989,13 @@ mibs_info(Pid) ->
 
 load_mibs(Pid, Dir, Mibs0) ->
     Mibs = [join(Dir, Mib) || Mib <- Mibs0],
-    Res = snmpa_mib:load_mibs(Pid, Mibs),
+    Res = snmpa_mib:load_mibs(Pid, Mibs, false),
     %% ?DBG("load_mibs -> "
     %% 	 "~n   Res: ~p", [Res]),
     Res.
 
 unload_mibs(Pid, Mibs) ->
-    Res = snmpa_mib:unload_mibs(Pid, Mibs),
+    Res = snmpa_mib:unload_mibs(Pid, Mibs, false),
     %% ?DBG("unload_mibs -> "
     %% 	 "~n   Res: ~p", [Res]),
     Res.
-- 
2.31.1

openSUSE Build Service is sponsored by