File 2421-snmp-manager-test-Deprecation-updates.patch of Package erlang

From 5b56a7c9e300a1ea59bcd5383e2f12d880ba75fb Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 2 Apr 2020 19:05:35 +0200
Subject: [PATCH 1/2] [snmp|manager|test] Deprecation updates

---
 lib/snmp/test/snmp_manager_SUITE.erl | 2078 ++++++++++++++++++++++------------
 lib/snmp/test/snmp_manager_user.erl  |  324 +++---
 2 files changed, 1531 insertions(+), 871 deletions(-)

diff --git a/lib/snmp/test/snmp_manager_SUITE.erl b/lib/snmp/test/snmp_manager_SUITE.erl
index 6e695f5ddf..a5de28d52d 100644
--- a/lib/snmp/test/snmp_manager_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_SUITE.erl
@@ -68,33 +68,33 @@
 	 info/1,
          usm_priv_aes/1,
 	 
-	 simple_sync_get2/1, 
+	 %% simple_sync_get2/1, 
 	 simple_sync_get3/1, 
-	 simple_async_get2/1, 
+	 %% simple_async_get2/1, 
 	 simple_async_get3/1, 
 	
-  	 simple_sync_get_next2/1, 
+  	 %% simple_sync_get_next2/1, 
   	 simple_sync_get_next3/1, 
-  	 simple_async_get_next2/1, 
+  	 %% simple_async_get_next2/1, 
          simple_async_get_next3_cbp_def/1,
          simple_async_get_next3_cbp_temp/1,
          simple_async_get_next3_cbp_perm/1,
 	 
-	 simple_sync_set2/1, 
+	 %% simple_sync_set2/1, 
 	 simple_sync_set3/1, 
-	 simple_async_set2/1, 
+	 %% simple_async_set2/1, 
          simple_async_set3_cbp_def/1,
          simple_async_set3_cbp_temp/1,
          simple_async_set3_cbp_perm/1,
 	 
-  	 simple_sync_get_bulk2/1, 
+  	 %% simple_sync_get_bulk2/1, 
   	 simple_sync_get_bulk3/1, 
-  	 simple_async_get_bulk2/1, 
+  	 %% simple_async_get_bulk2/1, 
          simple_async_get_bulk3_cbp_def/1,
          simple_async_get_bulk3_cbp_temp/1,
          simple_async_get_bulk3_cbp_perm/1,
 	 
-  	 misc_async2/1, 
+  	 %% misc_async2/1, 
 
 	 discovery/1,
 	 
@@ -206,8 +206,8 @@ groups() ->
        {group, get_tests}, 
        {group, get_next_tests}, 
        {group, set_tests}, 
-       {group, bulk_tests}, 
-       {group, misc_request_tests} 
+       {group, bulk_tests}%% , 
+       %% {group, misc_request_tests} 
       ]
      },
      {request_tests_mt, [],
@@ -215,23 +215,23 @@ groups() ->
        {group, get_tests}, 
        {group, get_next_tests},
        {group, set_tests}, 
-       {group, bulk_tests},
-       {group, misc_request_tests}
+       {group, bulk_tests}%% ,
+       %% {group, misc_request_tests}
       ]
      },
      {get_tests, [],
       [
-       simple_sync_get2, 
+       %% simple_sync_get2, 
        simple_sync_get3, 
-       simple_async_get2,
+       %% simple_async_get2,
        simple_async_get3
       ]
      },
      {get_next_tests, [],
       [
-       simple_sync_get_next2,
+       %% simple_sync_get_next2,
        simple_sync_get_next3,
-       simple_async_get_next2,
+       %% simple_async_get_next2,
        simple_async_get_next3_cbp_def,
        simple_async_get_next3_cbp_temp,
        simple_async_get_next3_cbp_perm
@@ -239,9 +239,9 @@ groups() ->
      },
      {set_tests, [],
       [
-       simple_sync_set2, 
+       %% simple_sync_set2, 
        simple_sync_set3, 
-       simple_async_set2,
+       %% simple_async_set2,
        simple_async_set3_cbp_def,
        simple_async_set3_cbp_temp,
        simple_async_set3_cbp_perm
@@ -249,19 +249,19 @@ groups() ->
      },
      {bulk_tests, [],
       [
-       simple_sync_get_bulk2,
+       %% simple_sync_get_bulk2,
        simple_sync_get_bulk3,
-       simple_async_get_bulk2, 
+       %% simple_async_get_bulk2, 
        simple_async_get_bulk3_cbp_def,
        simple_async_get_bulk3_cbp_temp,
        simple_async_get_bulk3_cbp_perm
       ]
      },
-     {misc_request_tests, [], 
-      [
-       misc_async2
-      ]
-     },
+     %% {misc_request_tests, [], 
+     %%  [
+     %%   %% misc_async2
+     %%  ]
+     %% },
      {event_tests, [],
       [
        trap1, 
@@ -315,16 +315,16 @@ ipv6_tests() ->
     [
      register_agent_old,
      simple_sync_get_next3,
-     simple_async_get2,
+     %% simple_async_get2,
      simple_sync_get3,
-     simple_async_get_next2,
+     %% simple_async_get_next2,
      simple_sync_set3,
-     simple_async_set2,
-     simple_sync_get_bulk2,
+     %% simple_async_set2,
+     %% simple_sync_get_bulk2,
      simple_async_get_bulk3_cbp_def,
      simple_async_get_bulk3_cbp_temp,
      simple_async_get_bulk3_cbp_perm,
-     misc_async2,
+     %% misc_async2,
      inform1,
      inform_swarm_cbp_def,
      inform_swarm_cbp_temp,
@@ -564,15 +564,15 @@ init_per_testcase2(Case, Config) ->
 init_per_testcase3(Case, Config) ->
     ApiCases02 = 
 	[
-	 simple_sync_get2, 
-	 simple_async_get2, 
-	 simple_sync_get_next2, 
-	 simple_async_get_next2, 
-	 simple_sync_set2, 
-	 simple_async_set2, 
-	 simple_sync_get_bulk2, 
-	 simple_async_get_bulk2,
-	 misc_async2,
+	 %% simple_sync_get2, 
+	 %% simple_async_get2, 
+	 %% simple_sync_get_next2, 
+	 %% simple_async_get_next2, 
+	 %% simple_sync_set2, 
+	 %% simple_async_set2, 
+	 %% simple_sync_get_bulk2, 
+	 %% simple_async_get_bulk2,
+	 %% misc_async2,
 	 otp8395_1
 	],
     ApiCases03 = 
@@ -702,15 +702,15 @@ end_per_testcase(Case, Config) when is_list(Config) ->
 end_per_testcase2(Case, Config) ->
     ApiCases02 = 
 	[
-	 simple_sync_get2, 
-	 simple_async_get2, 
-	 simple_sync_get_next2, 
-	 simple_async_get_next2, 
-	 simple_sync_set2, 
-	 simple_async_set2, 
-	 simple_sync_get_bulk2, 
-	 simple_async_get_bulk2,
-	 misc_async2,
+	 %% simple_sync_get2, 
+	 %% simple_async_get2, 
+	 %% simple_sync_get_next2, 
+	 %% simple_async_get_next2, 
+	 %% simple_sync_set2, 
+	 %% simple_async_set2, 
+	 %% simple_sync_get_bulk2, 
+	 %% simple_async_get_bulk2,
+	 %% misc_async2,
 	 otp8395_1
 	],
     ApiCases03 = 
@@ -2142,25 +2142,111 @@ do_register_agent3([ManagerNode], Config) ->
 
 %%======================================================================
 
-simple_sync_get2(doc) -> 
-    ["Simple sync get-request - Version 2 API (TargetName)"];
-simple_sync_get2(suite) -> [];
-simple_sync_get2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_get2,
-            fun() -> do_simple_sync_get2(Config) end).
+%% simple_sync_get2(doc) -> 
+%%     ["Simple sync get-request - Version 2 API (TargetName)"];
+%% simple_sync_get2(suite) -> [];
+%% simple_sync_get2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_sync_get2,
+%%             fun() -> do_simple_sync_get2(Config) end).
+
+%% do_simple_sync_get2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+%%     Get = fun(Node, TargetName, Oids) -> 
+%% 		  mgr_user_sync_get(Node, TargetName, Oids) 
+%% 	  end, 
+%%     PostVerify = fun() -> ok end,
+%%     Res = do_simple_sync_get2(Config, Get, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_sync_get2(Config, Get, PostVerify) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+
+%%     Node       = ?config(manager_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     ?IPRINT("issue get-request without loading the mib"),
+%%     Oids1 = [?sysObjectID_instance, ?sysDescr_instance, ?sysUpTime_instance],
+%%     ?line ok = do_simple_sync_get2(Node, TargetName, Oids1, Get, PostVerify),
+
+%%     ?IPRINT("issue get-request after first loading the mibs"),
+%%     ?line ok = mgr_user_load_mib(Node, std_mib()),
+%%     Oids2 = [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
+%%     ?line ok = do_simple_sync_get2(Node, TargetName, Oids2, Get, PostVerify),
+%%     ok.
+
+%% do_simple_sync_get2(Node, TargetName, Oids, Get, PostVerify) 
+%%   when is_function(Get, 3) andalso is_function(PostVerify, 0) ->
+%%     ?line {ok, Reply, _Rem} = Get(Node, TargetName, Oids),
+
+%%     ?DBG("~n   Reply: ~p"
+%% 	 "~n   Rem:   ~w", [Reply, _Rem]),
+
+%%     %% verify that the operation actually worked:
+%%     %% The order should be the same, so no need to search
+%%     ?line ok = case Reply of
+%% 		   {noError, 0, [#varbind{oid   = ?sysObjectID_instance,
+%% 					  value = SysObjectID}, 
+%% 				 #varbind{oid   = ?sysDescr_instance,
+%% 					  value = SysDescr},
+%% 				 #varbind{oid   = ?sysUpTime_instance,
+%% 					  value = SysUpTime}]} ->
+%% 		       ?IPRINT("expected result from get: "
+%%                                "~n   SysObjectID: ~p"
+%%                                "~n   SysDescr:    ~s"
+%%                                "~n   SysUpTime:   ~w", 
+%%                                [SysObjectID, SysDescr, SysUpTime]),
+%% 		       PostVerify();
+%% 		   {noError, 0, Vbs} ->
+%% 		       ?EPRINT("unexpected varbinds: "
+%%                                "~n      ~p", [Vbs]),
+%% 		       {error, {unexpected_vbs, Vbs}};
+%% 		   Else ->
+%% 		       ?EPRINT("unexpected reply: "
+%%                                "~n      ~p", [Else]),
+%% 		       {error, {unexpected_response, Else}}
+%% 	       end,
+%%     ok.
+
+
+%%======================================================================
+
+simple_sync_get3(doc) -> 
+    ["Simple sync get-request - Version 3 API (TargetName and send-opts)"];
+simple_sync_get3(suite) -> [];
+simple_sync_get3(Config) when is_list(Config) ->
+    ?TC_TRY(simple_sync_get3,
+            fun() -> do_simple_sync_get3(Config) end).
 
-do_simple_sync_get2(Config) ->
+do_simple_sync_get3(Config) ->
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
+    Self  = self(), 
+    Msg   = simple_sync_get3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
     Get = fun(Node, TargetName, Oids) -> 
-		  mgr_user_sync_get(Node, TargetName, Oids) 
-	  end, 
-    PostVerify = fun() -> ok end,
-    Res = do_simple_sync_get2(Config, Get, PostVerify),
+		  mgr_user_sync_get2(Node, TargetName, Oids, SendOpts) 
+	  end,
+    PostVerify = 
+	fun() ->
+		receive
+		    Msg ->
+			ok
+		end
+	end,
+    Res = do_simple_sync_get3(Config, Get, PostVerify),
     display_log(Config),
     Res.
 
-do_simple_sync_get2(Config, Get, PostVerify) ->
+
+do_simple_sync_get3(Config, Get, PostVerify) ->
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
 
@@ -2169,15 +2255,15 @@ do_simple_sync_get2(Config, Get, PostVerify) ->
 
     ?IPRINT("issue get-request without loading the mib"),
     Oids1 = [?sysObjectID_instance, ?sysDescr_instance, ?sysUpTime_instance],
-    ?line ok = do_simple_sync_get2(Node, TargetName, Oids1, Get, PostVerify),
+    ?line ok = do_simple_sync_get3(Node, TargetName, Oids1, Get, PostVerify),
 
     ?IPRINT("issue get-request after first loading the mibs"),
     ?line ok = mgr_user_load_mib(Node, std_mib()),
     Oids2 = [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
-    ?line ok = do_simple_sync_get2(Node, TargetName, Oids2, Get, PostVerify),
+    ?line ok = do_simple_sync_get3(Node, TargetName, Oids2, Get, PostVerify),
     ok.
 
-do_simple_sync_get2(Node, TargetName, Oids, Get, PostVerify) 
+do_simple_sync_get3(Node, TargetName, Oids, Get, PostVerify) 
   when is_function(Get, 3) andalso is_function(PostVerify, 0) ->
     ?line {ok, Reply, _Rem} = Get(Node, TargetName, Oids),
 
@@ -2211,43 +2297,6 @@ do_simple_sync_get2(Node, TargetName, Oids, Get, PostVerify)
     ok.
 
 
-%%======================================================================
-
-simple_sync_get3(doc) -> 
-    ["Simple sync get-request - Version 3 API (TargetName and send-opts)"];
-simple_sync_get3(suite) -> [];
-simple_sync_get3(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_get3,
-            fun() -> do_simple_sync_get3(Config) end).
-
-do_simple_sync_get3(Config) ->
-    ?IPRINT("starting with Config: "
-            "~n      ~p", [Config]),
-    Self  = self(), 
-    Msg   = simple_sync_get3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-    Get = fun(Node, TargetName, Oids) -> 
-		  mgr_user_sync_get2(Node, TargetName, Oids, SendOpts) 
-	  end,
-    PostVerify = 
-	fun() ->
-		receive
-		    Msg ->
-			ok
-		end
-	end,
-    Res = do_simple_sync_get2(Config, Get, PostVerify),
-    display_log(Config),
-    Res.
-
-
-
-
 %%======================================================================
 
 sag_verify({noError, 0, _Vbs}, any) ->
@@ -2283,35 +2332,134 @@ sag_verify_vbs([Vb|_], [E|_]) ->
 
 %%======================================================================
 
-simple_async_get2(doc) -> 
-    ["Simple (async) get-request - Version 2 API (TargetName)"];
-simple_async_get2(suite) -> [];
-simple_async_get2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_async_get2,
-            fun() -> do_simple_async_get2(Config) end).
+%% simple_async_get2(doc) -> 
+%%     ["Simple (async) get-request - Version 2 API (TargetName)"];
+%% simple_async_get2(suite) -> [];
+%% simple_async_get2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_async_get2,
+%%             fun() -> do_simple_async_get2(Config) end).
+
+%% do_simple_async_get2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+%%     Get        = fun(Oids) -> async_g_exec2(MgrNode, TargetName, Oids) end,
+%%     PostVerify = fun(Res) -> Res end, 
+%%     do_simple_async_sync_get2(Config, MgrNode, AgentNode, Get, PostVerify),
+%%     display_log(Config),
+%%     ok.
+
+%% do_simple_async_sync_get2(Config, MgrNode, AgentNode, Get, PostVerify) ->
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+%%     do_simple_async_sync_get2(fun() -> mgr_info(MgrNode) end,
+%% 			      fun() -> agent_info(AgentNode) end,
+%% 			      Get, PostVerify).
+
+%% do_simple_async_sync_get2(MgrInfo, AgentInfo, Get, PostVerify) 
+%%   when is_function(MgrInfo, 0) andalso 
+%%        is_function(AgentInfo, 0) andalso 
+%%        is_function(Get, 1) andalso 
+%%        is_function(PostVerify, 1) ->
+%%     Requests = 
+%% 	[
+%% 	 { 1,  
+%% 	   [?sysObjectID_instance], 
+%% 	   Get, 
+%% 	   fun(X) -> 
+%% 		   PostVerify(sag_verify(X, [?sysObjectID_instance])) end}, 
+%% 	 { 2,  
+%% 	   [?sysDescr_instance, ?sysUpTime_instance],
+%% 	   Get, 
+%% 	   fun(X) -> 
+%% 		   PostVerify(sag_verify(X, [?sysObjectID_instance, 
+%% 					     ?sysUpTime_instance]))
+%% 	   end}, 
+%% 	 { 3,  
+%% 	   [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
+%% 	   Get, 
+%% 	   fun(X) -> 
+%% 		   PostVerify(sag_verify(X, [?sysObjectID_instance, 
+%% 					     ?sysDescr_instance, 
+%% 					     ?sysUpTime_instance]))
+		       
+%% 	   end}, 
+%% 	 { 4,  
+%% 	   [?sysObjectID_instance, 
+%% 	    ?sysDescr_instance, 
+%% 	    ?sysUpTime_instance],
+%% 	   Get, 
+%% 	   fun(X) -> 
+%% 		   PostVerify(sag_verify(X, [?sysObjectID_instance, 
+%% 					     ?sysDescr_instance, 
+%% 					     ?sysUpTime_instance]))
+%% 	   end}
+%% 	],
+    
+%%     ?IPRINT("manager info when starting test: "
+%%             "~n      ~p", [MgrInfo()]),
+%%     ?IPRINT("agent info when starting test: "
+%%             "~n      ~p",   [AgentInfo()]),
+
+%%     ?line ok = async_exec(Requests, []),
+
+%%     ?IPRINT("manager info when ending test: "
+%%             "~n      ~p", [MgrInfo()]),
+%%     ?IPRINT("agent info when ending test: "
+%%             "~n      ~p",   [AgentInfo()]),
 
-do_simple_async_get2(Config) ->
+%%     ok.
+
+%% async_g_exec2(Node, TargetName, Oids) ->
+%%     mgr_user_async_get(Node, TargetName, Oids).
+
+
+%%======================================================================
+
+simple_async_get3(doc) -> 
+    ["Simple (async) get-request - Version 3 API (TargetName and send-opts)"];
+simple_async_get3(suite) -> [];
+simple_async_get3(Config) when is_list(Config) ->
+    ?TC_TRY(simple_async_get3,
+            fun() -> do_simple_async_get3(Config) end).
+
+do_simple_async_get3(Config) ->
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
     MgrNode    = ?config(manager_node, Config),
     AgentNode  = ?config(agent_node, Config),
     TargetName = ?config(manager_agent_target_name, Config),
-    Get        = fun(Oids) -> async_g_exec2(MgrNode, TargetName, Oids) end,
-    PostVerify = fun(Res) -> Res end, 
-    do_simple_async_sync_get2(Config, MgrNode, AgentNode, Get, PostVerify),
+    Self  = self(), 
+    Msg   = simple_async_get3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
+    Get = fun(Oids) -> async_g_exec3(MgrNode, TargetName, Oids, SendOpts) end,
+    PostVerify = fun(ok)    -> receive Msg -> ok end;
+		    (Error) -> Error 
+		 end,
+    Res = do_simple_async_sync_get3(Config, MgrNode, AgentNode,
+                                    Get, PostVerify),
     display_log(Config),
-    ok.
+    Res.
 
-do_simple_async_sync_get2(Config, MgrNode, AgentNode, Get, PostVerify) ->
+do_simple_async_sync_get3(Config, MgrNode, AgentNode, Get, PostVerify) ->
     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
     Test2Mib = test2_mib(Config), 
     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
     ?line ok = agent_load_mib(AgentNode, Test2Mib),
-    do_simple_async_sync_get2(fun() -> mgr_info(MgrNode) end,
+    do_simple_async_sync_get3(fun() -> mgr_info(MgrNode) end,
 			      fun() -> agent_info(AgentNode) end,
 			      Get, PostVerify).
 
-do_simple_async_sync_get2(MgrInfo, AgentInfo, Get, PostVerify) 
+do_simple_async_sync_get3(MgrInfo, AgentInfo, Get, PostVerify) 
   when is_function(MgrInfo, 0) andalso 
        is_function(AgentInfo, 0) andalso 
        is_function(Get, 1) andalso 
@@ -2365,41 +2513,6 @@ do_simple_async_sync_get2(MgrInfo, AgentInfo, Get, PostVerify)
 
     ok.
 
-async_g_exec2(Node, TargetName, Oids) ->
-    mgr_user_async_get(Node, TargetName, Oids).
-
-
-%%======================================================================
-
-simple_async_get3(doc) -> 
-    ["Simple (async) get-request - Version 3 API (TargetName and send-opts)"];
-simple_async_get3(suite) -> [];
-simple_async_get3(Config) when is_list(Config) ->
-    ?TC_TRY(simple_async_get3,
-            fun() -> do_simple_async_get3(Config) end).
-
-do_simple_async_get3(Config) ->
-    ?IPRINT("starting with Config: "
-            "~n      ~p", [Config]),
-    MgrNode    = ?config(manager_node, Config),
-    AgentNode  = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
-    Self  = self(), 
-    Msg   = simple_async_get3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-    Get = fun(Oids) -> async_g_exec3(MgrNode, TargetName, Oids, SendOpts) end,
-    PostVerify = fun(ok)    -> receive Msg -> ok end;
-		    (Error) -> Error 
-		 end,
-    Res = do_simple_async_sync_get2(Config, MgrNode, AgentNode, Get, PostVerify),
-    display_log(Config),
-    Res.
-
 async_g_exec3(Node, TargetName, Oids, SendOpts) ->
     mgr_user_async_get2(Node, TargetName, Oids, SendOpts).
 
@@ -2440,27 +2553,162 @@ check_ssgn_vbs([Vb|_], [E|_]) ->
 
 %%======================================================================
 
-simple_sync_get_next2(doc) -> 
-    ["Simple (sync) get_next-request - Version 2 API (TargetName)"];
-simple_sync_get_next2(suite) -> [];
-simple_sync_get_next2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_get_next2,
-            fun() -> do_simple_sync_get_next2(Config) end).
+%% simple_sync_get_next2(doc) -> 
+%%     ["Simple (sync) get_next-request - Version 2 API (TargetName)"];
+%% simple_sync_get_next2(suite) -> [];
+%% simple_sync_get_next2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_sync_get_next2,
+%%             fun() -> do_simple_sync_get_next2(Config) end).
+
+%% do_simple_sync_get_next2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+
+%%     GetNext = fun(Node, TargetName, Oids) -> 
+%% 		      mgr_user_sync_get_next(Node, TargetName, Oids) 
+%% 	      end,
+%%     PostVerify = fun(Res) -> Res end,
+%%     Res = do_simple_sync_get_next2(Config, GetNext, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+
+%% do_simple_sync_get_next2(Config, GetNext, PostVerify) 
+%%   when is_function(GetNext, 3) andalso is_function(PostVerify, 1) ->
+
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     %% -- 1 --
+%%     Oids01 = [[1,3,7,1]],
+%%     VF01   = fun(X) -> verify_ssgn_reply1(X, [{[1,3,7,1],endOfMibView}]) end,
+%%     ?line ok = do_simple_get_next(1, 
+%% 				  MgrNode, TargetName, Oids01, VF01, 
+%% 				  GetNext, PostVerify),
+    
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+
+%%     %% -- 2 --
+%%     Oids02 = [[sysDescr], [1,3,7,1]], 
+%%     VF02   = fun(X) -> 
+%% 		     verify_ssgn_reply1(X, [?sysDescr_instance, endOfMibView]) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(2, 
+%% 				  MgrNode, TargetName, Oids02, VF02, 
+%% 				  GetNext, PostVerify),
+    
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
+%%     %% -- 3 --
+%%     ?line {ok, [TCnt2|_]} = mgr_user_name_to_oid(MgrNode, tCnt2),
+%%     Oids03 = [[TCnt2, 1]], 
+%%     VF03   = fun(X) -> 
+%% 		     verify_ssgn_reply1(X, [{fl([TCnt2,2]), 100}]) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(3, 
+%% 				  MgrNode, TargetName, Oids03, VF03, 
+%% 				  GetNext, PostVerify),
+    
+%%     %% -- 4 --
+%%     Oids04 = [[TCnt2, 2]], 
+%%     VF04   = fun(X) -> 
+%% 		     verify_ssgn_reply1(X, [{fl([TCnt2,2]), endOfMibView}]) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(4, 
+%% 				  MgrNode, TargetName, Oids04, VF04, 
+%% 				  GetNext, PostVerify),
+    
+%%     %% -- 5 --
+%%     ?line {ok, [TGenErr1|_]} = mgr_user_name_to_oid(MgrNode, tGenErr1),
+%%     Oids05 = [TGenErr1], 
+%%     VF05   = fun(X) -> 
+%% 		     verify_ssgn_reply2(X, {genErr, 1, [TGenErr1]}) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(5, 
+%% 				  MgrNode, TargetName, Oids05, VF05, 
+%% 				  GetNext, PostVerify),
+    
+%%     %% -- 6 --
+%%     ?line {ok, [TGenErr2|_]} = mgr_user_name_to_oid(MgrNode, tGenErr2),
+%%     Oids06 = [TGenErr2], 
+%%     VF06   = fun(X) -> 
+%% 		     verify_ssgn_reply2(X, {genErr, 1, [TGenErr2]}) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(6, 
+%% 				  MgrNode, TargetName, Oids06, VF06, 
+%% 				  GetNext, PostVerify),
+    
+%%     %% -- 7 --
+%%     ?line {ok, [TGenErr3|_]} = mgr_user_name_to_oid(MgrNode, tGenErr3),
+%%     Oids07 = [[sysDescr], TGenErr3], 
+%%     VF07   = fun(X) -> 
+%% 		     verify_ssgn_reply2(X, {genErr, 2, 
+%% 					   [?sysDescr, TGenErr3]}) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(7, 
+%% 				  MgrNode, TargetName, Oids07, VF07, 
+%% 				  GetNext, PostVerify),
+    
+%%     %% -- 8 --
+%%     ?line {ok, [TTooBig|_]} = mgr_user_name_to_oid(MgrNode, tTooBig),
+%%     Oids08 = [TTooBig], 
+%%     VF08   = fun(X) -> 
+%% 		     verify_ssgn_reply2(X, {tooBig, 0, []}) 
+%% 	     end,
+%%     ?line ok = do_simple_get_next(8, 
+%% 				  MgrNode, TargetName, Oids08, VF08, 
+%% 				  GetNext, PostVerify),
+%%     ok.
+
+
+%% do_simple_get_next(N, Node, TargetName, Oids, Verify, GetNext, PostVerify) ->
+%%     ?IPRINT("issue get-next command ~w", [N]),
+%%     case GetNext(Node, TargetName, Oids) of
+%% 	{ok, Reply, _Rem} ->
+%% 	    ?DBG("get-next ok:"
+%% 		 "~n   Reply: ~p"
+%% 		 "~n   Rem:   ~w", [Reply, _Rem]),
+%% 	    PostVerify(Verify(Reply));
+
+%% 	Error ->
+%% 	    {error, {unexpected_reply, Error}}
+%%     end.
+
 
-do_simple_sync_get_next2(Config) ->
+%%======================================================================
+
+simple_sync_get_next3(doc) -> 
+    ["Simple (sync) get_next-request - "
+     "Version 3 API (TargetName with send-opts)"];
+simple_sync_get_next3(suite) -> [];
+simple_sync_get_next3(Config) when is_list(Config) ->
+    process_flag(trap_exit, true),
+    put(tname, ssgn3),
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
-
+    Self  = self(), 
+    Msg   = simple_sync_get_next3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
     GetNext = fun(Node, TargetName, Oids) -> 
-		      mgr_user_sync_get_next(Node, TargetName, Oids) 
+		      mgr_user_sync_get_next2(Node, TargetName, Oids, SendOpts) 
 	      end,
-    PostVerify = fun(Res) -> Res end,
-    Res = do_simple_sync_get_next2(Config, GetNext, PostVerify),
+    PostVerify = fun(ok)    -> receive Msg -> ok end;
+		    (Error) -> Error 
+		 end,
+    do_simple_sync_get_next3(Config, GetNext, PostVerify),
     display_log(Config),
-    Res.
+    ok.
 
 
-do_simple_sync_get_next2(Config, GetNext, PostVerify) 
+do_simple_sync_get_next3(Config, GetNext, PostVerify) 
   when is_function(GetNext, 3) andalso is_function(PostVerify, 1) ->
 
     MgrNode    = ?config(manager_node, Config),
@@ -2550,7 +2798,6 @@ do_simple_sync_get_next2(Config, GetNext, PostVerify)
 				  GetNext, PostVerify),
     ok.
 
-
 do_simple_get_next(N, Node, TargetName, Oids, Verify, GetNext, PostVerify) ->
     ?IPRINT("issue get-next command ~w", [N]),
     case GetNext(Node, TargetName, Oids) of
@@ -2565,46 +2812,153 @@ do_simple_get_next(N, Node, TargetName, Oids, Verify, GetNext, PostVerify) ->
     end.
 
 
+
 %%======================================================================
 
-simple_sync_get_next3(doc) -> 
-    ["Simple (sync) get_next-request - "
-     "Version 3 API (TargetName with send-opts)"];
-simple_sync_get_next3(suite) -> [];
-simple_sync_get_next3(Config) when is_list(Config) ->
-    process_flag(trap_exit, true),
-    put(tname, ssgn3),
-    ?IPRINT("starting with Config: "
-            "~n      ~p", [Config]),
-    Self  = self(), 
-    Msg   = simple_sync_get_next3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-    GetNext = fun(Node, TargetName, Oids) -> 
-		      mgr_user_sync_get_next2(Node, TargetName, Oids, SendOpts) 
-	      end,
-    PostVerify = fun(ok)    -> receive Msg -> ok end;
-		    (Error) -> Error 
-		 end,
-    do_simple_sync_get_next2(Config, GetNext, PostVerify),
-    display_log(Config),
-    ok.
+%% simple_async_get_next2(doc) -> 
+%%     ["Simple (async) get_next-request - Version 2 API (TargetName)"];
+%% simple_async_get_next2(suite) -> [];
+%% simple_async_get_next2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_async_get_next2,
+%%             fun() -> do_simple_async_get_next2(Config) end).
+
+%% do_simple_async_get_next2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+%%     GetNext = fun(Oids) ->
+%% 		      async_gn_exec2(MgrNode, TargetName, Oids)
+%% 	      end,
+%%     PostVerify = fun(Res) -> Res end,
+%%     Res = do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify) 
+%%   when is_function(GetNext, 1) andalso is_function(PostVerify, 1) ->
+%%     ?line {ok, [TCnt2|_]}    = mgr_user_name_to_oid(MgrNode, tCnt2),
+%%     ?line {ok, [TGenErr1|_]} = mgr_user_name_to_oid(MgrNode, tGenErr1),
+%%     ?line {ok, [TGenErr2|_]} = mgr_user_name_to_oid(MgrNode, tGenErr2),
+%%     ?line {ok, [TGenErr3|_]} = mgr_user_name_to_oid(MgrNode, tGenErr3),
+%%     ?line {ok, [TTooBig|_]}  = mgr_user_name_to_oid(MgrNode, tTooBig),
+
+%%     Requests = 
+%% 	[
+%% 	 {1, 
+%% 	  [[1,3,7,1]], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply1(X, [{[1,3,7,1], endOfMibView}])) 
+		  
+%% 	  end}, 
+%% 	 {2, 
+%% 	  [[sysDescr], [1,3,7,1]], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply1(X, [?sysDescr_instance, endOfMibView]))
+%% 	  end}, 
+%% 	 {3, 
+%% 	  [[TCnt2, 1]], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply1(X, [{fl([TCnt2,2]), 100}]))
+%% 	  end}, 
+%% 	 {4, 
+%% 	  [[TCnt2, 2]], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply1(X, [{fl([TCnt2,2]), endOfMibView}]))
+%% 	  end}, 
+%% 	 {5, 
+%% 	  [TGenErr1], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply2(X, {genErr, 1, [TGenErr1]}))
+%% 	  end}, 
+%% 	 {6, 
+%% 	  [TGenErr2], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply2(X, {genErr, 1, [TGenErr2]}))
+%% 	  end}, 
+%% 	 {7, 
+%% 	  [[sysDescr], TGenErr3], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply2(X, {genErr, 2, [TGenErr3]}))
+%% 	  end}, 
+%% 	 {8, 
+%% 	  [TTooBig], 
+%% 	  GetNext, 
+%% 	  fun(X) ->
+%% 		  PostVerify(
+%% 		    verify_ssgn_reply2(X, {tooBig, 0, []}))
+%% 	  end}
+%% 	],
+
+%%     ?IPRINT("manager info when starting test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when starting test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ?line ok = async_exec(Requests, []),
+
+%%     ?IPRINT("manager info when ending test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when ending test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ok.
+
+
+%% async_gn_exec2(Node, TargetName, Oids) ->
+%%     mgr_user_async_get_next(Node, TargetName, Oids).
 
 
 %%======================================================================
 
-simple_async_get_next2(doc) -> 
-    ["Simple (async) get_next-request - Version 2 API (TargetName)"];
-simple_async_get_next2(suite) -> [];
-simple_async_get_next2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_async_get_next2,
-            fun() -> do_simple_async_get_next2(Config) end).
+simple_async_get_next3_cbp_def(doc) -> 
+    ["Simple (async) get_next-request - "
+     "Version 3 API (TargetName with send-opts)"];
+simple_async_get_next3_cbp_def(suite) -> [];
+simple_async_get_next3_cbp_def(Config) when is_list(Config) ->
+    simple_async_get_next3(ssgn2_cbp_def, Config).
+
+simple_async_get_next3_cbp_temp(doc) -> 
+    ["Simple (async) get_next-request - "
+     "Version 3 API (TargetName with send-opts)"];
+simple_async_get_next3_cbp_temp(suite) -> [];
+simple_async_get_next3_cbp_temp(Config) when is_list(Config) ->
+    simple_async_get_next3(ssgn2_cbp_temp, Config).
 
-do_simple_async_get_next2(Config) ->
+simple_async_get_next3_cbp_perm(doc) -> 
+    ["Simple (async) get_next-request - "
+     "Version 3 API (TargetName with send-opts)"];
+simple_async_get_next3_cbp_perm(suite) -> [];
+simple_async_get_next3_cbp_perm(Config) when is_list(Config) ->
+    simple_async_get_next3(ssgn2_cbp_perm, Config).
+
+simple_async_get_next3(Case, Config) when is_list(Config) ->
+    ?TC_TRY(Case,
+            fun() -> do_simple_async_get_next3(Config) end).
+
+do_simple_async_get_next3(Config) ->
+    %% process_flag(trap_exit, true),
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
 
@@ -2616,15 +2970,28 @@ do_simple_async_get_next2(Config) ->
     Test2Mib = test2_mib(Config), 
     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
+    Self  = self(), 
+    Msg   = simple_async_get_next3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
+
     GetNext = fun(Oids) ->
-		      async_gn_exec2(MgrNode, TargetName, Oids)
+		      async_gn_exec3(MgrNode, TargetName, Oids, SendOpts)
 	      end,
-    PostVerify = fun(Res) -> Res end,
-    Res = do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify),
+    PostVerify = fun(ok)    -> receive Msg -> ok end;
+		    (Error) -> Error 
+		 end,
+
+    Res = do_simple_async_get_next3(MgrNode, AgentNode, GetNext, PostVerify),
     display_log(Config),
     Res.
 
-do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify) 
+do_simple_async_get_next3(MgrNode, AgentNode, GetNext, PostVerify) 
   when is_function(GetNext, 1) andalso is_function(PostVerify, 1) ->
     ?line {ok, [TCnt2|_]}    = mgr_user_name_to_oid(MgrNode, tCnt2),
     ?line {ok, [TGenErr1|_]} = mgr_user_name_to_oid(MgrNode, tGenErr1),
@@ -2708,71 +3075,6 @@ do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify)
     ok.
 
 
-async_gn_exec2(Node, TargetName, Oids) ->
-    mgr_user_async_get_next(Node, TargetName, Oids).
-
-
-%%======================================================================
-
-simple_async_get_next3_cbp_def(doc) -> 
-    ["Simple (async) get_next-request - "
-     "Version 3 API (TargetName with send-opts)"];
-simple_async_get_next3_cbp_def(suite) -> [];
-simple_async_get_next3_cbp_def(Config) when is_list(Config) ->
-    simple_async_get_next3(ssgn2_cbp_def, Config).
-
-simple_async_get_next3_cbp_temp(doc) -> 
-    ["Simple (async) get_next-request - "
-     "Version 3 API (TargetName with send-opts)"];
-simple_async_get_next3_cbp_temp(suite) -> [];
-simple_async_get_next3_cbp_temp(Config) when is_list(Config) ->
-    simple_async_get_next3(ssgn2_cbp_temp, Config).
-
-simple_async_get_next3_cbp_perm(doc) -> 
-    ["Simple (async) get_next-request - "
-     "Version 3 API (TargetName with send-opts)"];
-simple_async_get_next3_cbp_perm(suite) -> [];
-simple_async_get_next3_cbp_perm(Config) when is_list(Config) ->
-    simple_async_get_next3(ssgn2_cbp_perm, Config).
-
-simple_async_get_next3(Case, Config) when is_list(Config) ->
-    ?TC_TRY(Case,
-            fun() -> do_simple_async_get_next3(Config) end).
-
-do_simple_async_get_next3(Config) ->
-    %% process_flag(trap_exit, true),
-    ?IPRINT("starting with Config: "
-            "~n      ~p", [Config]),
-
-    MgrNode    = ?config(manager_node, Config),
-    AgentNode  = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
-
-    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
-    Test2Mib = test2_mib(Config), 
-    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
-    ?line ok = agent_load_mib(AgentNode, Test2Mib),
-
-    Self  = self(), 
-    Msg   = simple_async_get_next3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-
-    GetNext = fun(Oids) ->
-		      async_gn_exec3(MgrNode, TargetName, Oids, SendOpts)
-	      end,
-    PostVerify = fun(ok)    -> receive Msg -> ok end;
-		    (Error) -> Error 
-		 end,
-
-    Res = do_simple_async_get_next2(MgrNode, AgentNode, GetNext, PostVerify),
-    display_log(Config),
-    Res.
-
 async_gn_exec3(Node, TargetName, Oids, SendOpts) ->
     mgr_user_async_get_next2(Node, TargetName, Oids, SendOpts).
 
@@ -2792,27 +3094,110 @@ value_of_vavs([{_Oid, Val}|VAVs], Acc) ->
 			       
 %%======================================================================
 
-simple_sync_set2(doc) -> 
-    ["Simple (sync) set-request - Version 2 API (TargetName)"];
-simple_sync_set2(suite) -> [];
-simple_sync_set2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_set2,
-            fun() -> do_simple_sync_set2(Config) end).
+%% simple_sync_set2(doc) -> 
+%%     ["Simple (sync) set-request - Version 2 API (TargetName)"];
+%% simple_sync_set2(suite) -> [];
+%% simple_sync_set2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_sync_set2,
+%%             fun() -> do_simple_sync_set2(Config) end).
+
+%% do_simple_sync_set2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p", [Config]),
+
+%%     Set = fun(Node, TargetName, VAVs) -> 
+%% 		  mgr_user_sync_set(Node, TargetName, VAVs) 
+%% 	  end,
+%%     PostVerify = fun() -> ok end,
+
+%%     Res = do_simple_sync_set2(Config, Set, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_sync_set2(Config, Set, PostVerify) 
+%%   when is_function(Set, 3) andalso is_function(PostVerify, 0) ->
+
+%%     Node       = ?config(manager_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     ?IPRINT("issue set-request without loading the mib"),
+%%     Val11 = "Arne Anka",
+%%     Val12 = "Stockholm",
+%%     VAVs1 = [
+%% 	     {?sysName_instance,     s, Val11},
+%% 	     {?sysLocation_instance, s, Val12}
+%% 	    ],
+%%     ?line ok = do_simple_set2(Node, TargetName, VAVs1, Set, PostVerify),
+
+%%     ?IPRINT("issue set-request after first loading the mibs"),
+%%     ?line ok = mgr_user_load_mib(Node, std_mib()),
+%%     Val21 = "Sune Anka",
+%%     Val22 = "Gothenburg",
+%%     VAVs2 = [
+%% 	     {[sysName, 0],     Val21},
+%% 	     {[sysLocation, 0], Val22}
+%% 	    ],
+%%     ?line ok = do_simple_set2(Node, TargetName, VAVs2, Set, PostVerify),
+%%     ok.
+
+%% do_simple_set2(Node, TargetName, VAVs, Set, PostVerify) ->
+%%     [SysName, SysLoc] = value_of_vavs(VAVs),
+%%     ?line {ok, Reply, _Rem} = Set(Node, TargetName, VAVs),
+
+%%     ?DBG("~n   Reply: ~p"
+%% 	 "~n   Rem:   ~w", [Reply, _Rem]),
+
+%%     %% verify that the operation actually worked:
+%%     %% The order should be the same, so no need to search
+%%     %% The value we get should be exactly the same as we sent
+%%     ?line ok = case Reply of
+%% 		   {noError, 0, [#varbind{oid   = ?sysName_instance,
+%% 					  value = SysName},
+%% 				 #varbind{oid   = ?sysLocation_instance,
+%% 					  value = SysLoc}]} ->
+%% 		       PostVerify();
+%% 		   {noError, 0, Vbs} ->
+%% 		       {error, {unexpected_vbs, Vbs}};
+%% 		   Else ->
+%% 		       ?EPRINT("unexpected reply: "
+%%                                "~n      ~p", [Else]),
+%% 		       {error, {unexpected_response, Else}}
+%% 	       end,
+%%     ok.
+
+
+%%======================================================================
 
-do_simple_sync_set2(Config) ->
+simple_sync_set3(doc) -> 
+    ["Simple (sync) set-request - Version 3 API (TargetName with send-opts)"];
+simple_sync_set3(suite) -> [];
+simple_sync_set3(Config) when is_list(Config) ->
+    ?TC_TRY(simple_sync_set3,
+            fun() -> do_simple_sync_set3(Config) end).
+
+do_simple_sync_set3(Config) ->
     ?IPRINT("starting with Config: "
             "~n      ~p", [Config]),
 
+    Self  = self(), 
+    Msg   = simple_sync_set3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
+    
     Set = fun(Node, TargetName, VAVs) -> 
-		  mgr_user_sync_set(Node, TargetName, VAVs) 
+		  mgr_user_sync_set2(Node, TargetName, VAVs, SendOpts) 
 	  end,
-    PostVerify = fun() -> ok end,
+    PostVerify = fun() -> receive Msg -> ok end end,
 
-    Res = do_simple_sync_set2(Config, Set, PostVerify),
+    Res = do_simple_sync_set3(Config, Set, PostVerify),
     display_log(Config),
     Res.
 
-do_simple_sync_set2(Config, Set, PostVerify) 
+do_simple_sync_set3(Config, Set, PostVerify) 
   when is_function(Set, 3) andalso is_function(PostVerify, 0) ->
 
     Node       = ?config(manager_node, Config),
@@ -2825,7 +3210,7 @@ do_simple_sync_set2(Config, Set, PostVerify)
 	     {?sysName_instance,     s, Val11},
 	     {?sysLocation_instance, s, Val12}
 	    ],
-    ?line ok = do_simple_set2(Node, TargetName, VAVs1, Set, PostVerify),
+    ?line ok = do_simple_set3(Node, TargetName, VAVs1, Set, PostVerify),
 
     ?IPRINT("issue set-request after first loading the mibs"),
     ?line ok = mgr_user_load_mib(Node, std_mib()),
@@ -2835,10 +3220,10 @@ do_simple_sync_set2(Config, Set, PostVerify)
 	     {[sysName, 0],     Val21},
 	     {[sysLocation, 0], Val22}
 	    ],
-    ?line ok = do_simple_set2(Node, TargetName, VAVs2, Set, PostVerify),
+    ?line ok = do_simple_set3(Node, TargetName, VAVs2, Set, PostVerify),
     ok.
 
-do_simple_set2(Node, TargetName, VAVs, Set, PostVerify) ->
+do_simple_set3(Node, TargetName, VAVs, Set, PostVerify) ->
     [SysName, SysLoc] = value_of_vavs(VAVs),
     ?line {ok, Reply, _Rem} = Set(Node, TargetName, VAVs),
 
@@ -2864,38 +3249,6 @@ do_simple_set2(Node, TargetName, VAVs, Set, PostVerify) ->
     ok.
 
 
-%%======================================================================
-
-simple_sync_set3(doc) -> 
-    ["Simple (sync) set-request - Version 3 API (TargetName with send-opts)"];
-simple_sync_set3(suite) -> [];
-simple_sync_set3(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_set3,
-            fun() -> do_simple_sync_set3(Config) end).
-
-do_simple_sync_set3(Config) ->
-    ?IPRINT("starting with Config: "
-            "~n      ~p", [Config]),
-
-    Self  = self(), 
-    Msg   = simple_sync_set3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-    
-    Set = fun(Node, TargetName, VAVs) -> 
-		  mgr_user_sync_set2(Node, TargetName, VAVs, SendOpts) 
-	  end,
-    PostVerify = fun() -> receive Msg -> ok end end,
-
-    Res = do_simple_sync_set2(Config, Set, PostVerify),
-    display_log(Config),
-    Res.
-
-
 %%======================================================================
 
 sas_verify({noError, 0, _Vbs}, any) ->
@@ -2930,83 +3283,83 @@ sas_verify_vbs([Vb|_], [E|_]) ->
     
 %%======================================================================
 
-simple_async_set2(doc) -> 
-    ["Simple (async) set-request - Version 2 API (TargetName)"];
-simple_async_set2(suite) -> [];
-simple_async_set2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_async_set2,
-            fun() -> do_simple_async_set2(Config) end).
-
-do_simple_async_set2(Config) ->
-    ?IPRINT("starting with Config: "
-            "~n      ~p"
-            "~n", [Config]),
-
-    MgrNode    = ?config(manager_node, Config),
-    AgentNode  = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
-
-    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
-    Test2Mib = test2_mib(Config), 
-    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
-    ?line ok = agent_load_mib(AgentNode, Test2Mib),
-
-    Set = 
-	fun(Oids) ->
-		async_s_exec2(MgrNode, TargetName, Oids)
-	end,
-    PostVerify = fun(Res) -> Res end,
-
-    Res = do_simple_async_set2(MgrNode, AgentNode, Set, PostVerify),
-    display_log(Config),
-    Res.
-
-do_simple_async_set2(MgrNode, AgentNode, Set, PostVerify) ->
-    Requests = 
-	[
-	 {1,
-	  [{?sysName_instance, s, "Arne Anka"}],
-	  Set,
-	  fun(X) ->
-		  PostVerify(sas_verify(X, [?sysName_instance]))
-	  end},
-	 {2,
-	  [{?sysLocation_instance, s, "Stockholm"}, 
-	   {?sysName_instance,     s, "Arne Anka"}],
-	  Set,
-	  fun(X) ->
-		  PostVerify(sas_verify(X, 
-					[?sysLocation_instance, 
-					 ?sysName_instance]))
-	  end},
-	 {3,
-	  [{[sysName, 0],     "Gothenburg"}, 
-	   {[sysLocation, 0], "Sune Anka"}],
-	  Set,
-	  fun(X) ->
-		  PostVerify(sas_verify(X, 
-					[?sysName_instance, 
-					 ?sysLocation_instance]))
-	  end}
-	],
-
-    ?IPRINT("manager info when starting test: "
-            "~n      ~p", [mgr_info(MgrNode)]),
-    ?IPRINT("agent info when starting test: "
-            "~n      ~p", [agent_info(AgentNode)]),
-
-    ?line ok = async_exec(Requests, []),
-
-    ?IPRINT("manager info when ending test: "
-            "~n      ~p", [mgr_info(MgrNode)]),
-    ?IPRINT("agent info when ending test: "
-            "~n      ~p", [agent_info(AgentNode)]),
-
-    ok.
-
-
-async_s_exec2(Node, TargetName, VAVs) ->
-    mgr_user_async_set(Node, TargetName, VAVs).
+%% simple_async_set2(doc) -> 
+%%     ["Simple (async) set-request - Version 2 API (TargetName)"];
+%% simple_async_set2(suite) -> [];
+%% simple_async_set2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_async_set2,
+%%             fun() -> do_simple_async_set2(Config) end).
+
+%% do_simple_async_set2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p"
+%%             "~n", [Config]),
+
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
+%%     Set = 
+%% 	fun(Oids) ->
+%% 		async_s_exec2(MgrNode, TargetName, Oids)
+%% 	end,
+%%     PostVerify = fun(Res) -> Res end,
+
+%%     Res = do_simple_async_set2(MgrNode, AgentNode, Set, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_async_set2(MgrNode, AgentNode, Set, PostVerify) ->
+%%     Requests = 
+%% 	[
+%% 	 {1,
+%% 	  [{?sysName_instance, s, "Arne Anka"}],
+%% 	  Set,
+%% 	  fun(X) ->
+%% 		  PostVerify(sas_verify(X, [?sysName_instance]))
+%% 	  end},
+%% 	 {2,
+%% 	  [{?sysLocation_instance, s, "Stockholm"}, 
+%% 	   {?sysName_instance,     s, "Arne Anka"}],
+%% 	  Set,
+%% 	  fun(X) ->
+%% 		  PostVerify(sas_verify(X, 
+%% 					[?sysLocation_instance, 
+%% 					 ?sysName_instance]))
+%% 	  end},
+%% 	 {3,
+%% 	  [{[sysName, 0],     "Gothenburg"}, 
+%% 	   {[sysLocation, 0], "Sune Anka"}],
+%% 	  Set,
+%% 	  fun(X) ->
+%% 		  PostVerify(sas_verify(X, 
+%% 					[?sysName_instance, 
+%% 					 ?sysLocation_instance]))
+%% 	  end}
+%% 	],
+
+%%     ?IPRINT("manager info when starting test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when starting test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ?line ok = async_exec(Requests, []),
+
+%%     ?IPRINT("manager info when ending test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when ending test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ok.
+
+
+%% async_s_exec2(Node, TargetName, VAVs) ->
+%%     mgr_user_async_set(Node, TargetName, VAVs).
 
 
 %%======================================================================
@@ -3063,10 +3416,54 @@ do_simple_async_set3(Config) ->
 		    (Res) -> Res 
 		 end,
 
-    Res = do_simple_async_set2(MgrNode, AgentNode, Set, PostVerify),
+    Res = do_simple_async_set3(MgrNode, AgentNode, Set, PostVerify),
     display_log(Config),
     Res.
 
+do_simple_async_set3(MgrNode, AgentNode, Set, PostVerify) ->
+    Requests = 
+	[
+	 {1,
+	  [{?sysName_instance, s, "Arne Anka"}],
+	  Set,
+	  fun(X) ->
+		  PostVerify(sas_verify(X, [?sysName_instance]))
+	  end},
+	 {2,
+	  [{?sysLocation_instance, s, "Stockholm"}, 
+	   {?sysName_instance,     s, "Arne Anka"}],
+	  Set,
+	  fun(X) ->
+		  PostVerify(sas_verify(X, 
+					[?sysLocation_instance, 
+					 ?sysName_instance]))
+	  end},
+	 {3,
+	  [{[sysName, 0],     "Gothenburg"}, 
+	   {[sysLocation, 0], "Sune Anka"}],
+	  Set,
+	  fun(X) ->
+		  PostVerify(sas_verify(X, 
+					[?sysName_instance, 
+					 ?sysLocation_instance]))
+	  end}
+	],
+
+    ?IPRINT("manager info when starting test: "
+            "~n      ~p", [mgr_info(MgrNode)]),
+    ?IPRINT("agent info when starting test: "
+            "~n      ~p", [agent_info(AgentNode)]),
+
+    ?line ok = async_exec(Requests, []),
+
+    ?IPRINT("manager info when ending test: "
+            "~n      ~p", [mgr_info(MgrNode)]),
+    ?IPRINT("agent info when ending test: "
+            "~n      ~p", [agent_info(AgentNode)]),
+
+    ok.
+
+
 async_s_exec3(Node, TargetName, VAVs, SendOpts) ->
     mgr_user_async_set2(Node, TargetName, VAVs, SendOpts).
 
@@ -3110,14 +3507,173 @@ check_ssgb_vbs([R|_], [E|_]) ->
 
 %%======================================================================
 
-simple_sync_get_bulk2(doc) -> 
-    ["Simple (sync) get_bulk-request - Version 2 API (TargetName)"];
-simple_sync_get_bulk2(suite) -> [];
-simple_sync_get_bulk2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_get_bulk2,
-            fun() -> do_simple_sync_get_bulk2(Config) end).
+%% simple_sync_get_bulk2(doc) -> 
+%%     ["Simple (sync) get_bulk-request - Version 2 API (TargetName)"];
+%% simple_sync_get_bulk2(suite) -> [];
+%% simple_sync_get_bulk2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_sync_get_bulk2,
+%%             fun() -> do_simple_sync_get_bulk2(Config) end).
+
+%% do_simple_sync_get_bulk2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p~n", [Config]),
+
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     GetBulk = 
+%% 	fun(NonRep, MaxRep, Oids) ->
+%% 		mgr_user_sync_get_bulk(MgrNode, TargetName, 
+%% 				       NonRep, MaxRep, Oids)    
+%% 	end,
+%%     PostVerify = fun(Res) -> Res end,
+
+%%     Res = do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
+%%     %% -- 1 --
+%%     ?line ok = do_simple_get_bulk2(1,
+%% 				   1,  1, [], 
+%% 				   fun verify_ssgb_reply1/1, 
+%% 				   GetBulk, PostVerify), 
+    
+%%     %% -- 2 --
+%%     ?line ok = do_simple_get_bulk2(2, 
+%% 				   -1,  1, [], 
+%% 				   fun verify_ssgb_reply1/1, 
+%% 				   GetBulk, PostVerify), 
+
+%%     %% -- 3 --
+%%     ?line ok = do_simple_get_bulk2(3, 
+%% 				   -1, -1, [], 
+%% 				   fun verify_ssgb_reply1/1, 
+%% 				   GetBulk, PostVerify), 
+
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     %% -- 4 --
+%%     VF04 = fun(X) -> 
+%% 		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(4,
+%% 				   2, 0, [[sysDescr],[1,3,7,1]], VF04, 
+%% 				   GetBulk, PostVerify),
+
+%%     %% -- 5 --
+%%     ?line ok = do_simple_get_bulk2(5,
+%% 				   1, 2, [[sysDescr],[1,3,7,1]], VF04, 
+%% 				   GetBulk, PostVerify),
+
+%%     %% -- 6 --
+%%     VF06 = fun(X) -> 
+%% 		   verify_ssgb_reply2(X, 
+%% 				      [?sysDescr_instance,    endOfMibView,
+%% 				       ?sysObjectID_instance, endOfMibView]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(6,
+%% 				   0, 2, [[sysDescr],[1,3,7,1]], VF06, 
+%% 				   GetBulk, PostVerify), 
+
+%%     %% -- 7 --
+%%     VF07 = fun(X) -> 
+%% 		   verify_ssgb_reply2(X, 
+%% 				      [?sysDescr_instance,    endOfMibView,
+%% 				       ?sysDescr_instance,    endOfMibView,
+%% 				       ?sysObjectID_instance, endOfMibView]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(7,
+%% 				   2, 2, 
+%% 				   [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]],
+%% 				   VF07, 
+%% 				   GetBulk, PostVerify), 
+
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
+%%     %% -- 8 --
+%%     VF08 = fun(X) -> 
+%% 		   verify_ssgb_reply2(X, 
+%% 				      [?sysDescr_instance, 
+%% 				       ?sysDescr_instance]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(8,
+%% 				   1, 2, 
+%% 				   [[sysDescr],[sysDescr],[tTooBig]],
+%% 				   VF08, 
+%% 				   GetBulk, PostVerify), 
+
+%%     %% -- 9 --
+%%     ?line ok = do_simple_get_bulk2(9,
+%% 				   1, 12, 
+%% 				   [[tDescr2], [sysDescr]], 
+%% 				   fun verify_ssgb_reply1/1, 
+%% 				   GetBulk, PostVerify),
+
+%%     %% -- 10 --
+%%     VF10 = fun(X) -> 
+%% 		   verify_ssgb_reply3(X, 
+%% 				      [{?sysDescr,    'NULL'}, 
+%% 				       {?sysObjectID, 'NULL'},
+%% 				       {?tGenErr1,    'NULL'},
+%% 				       {?sysDescr,    'NULL'}]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(10,
+%% 				   2, 2, 
+%% 				   [[sysDescr], 
+%% 				    [sysObjectID], 
+%% 				    [tGenErr1], 
+%% 				    [sysDescr]],
+%% 				   VF10, 
+%% 				   GetBulk, PostVerify), 
+
+%%     %% -- 11 --
+%%     ?line {ok, [TCnt2|_]} = mgr_user_name_to_oid(MgrNode, tCnt2),
+%%     ?IPRINT("TCnt2: ~p", [TCnt2]),
+%%     VF11 = fun(X) -> 
+%% 		   verify_ssgb_reply2(X, 
+%% 				      [{fl([TCnt2,2]), 100}, 
+%% 				       {fl([TCnt2,2]), endOfMibView}]) 
+%% 	   end,
+%%     ?line ok = do_simple_get_bulk2(11,
+%% 				   0, 2, 
+%% 				   [[TCnt2, 1]], VF11, 
+%% 				   GetBulk, PostVerify),
+    
+%%     ok.
+
+%% do_simple_get_bulk2(N, 
+%% 		    NonRep, MaxRep, Oids, 
+%% 		    Verify, GetBulk, PostVerify) 
+%%   when is_function(Verify, 1) andalso 
+%%        is_function(GetBulk, 3) andalso 
+%%        is_function(PostVerify) ->
+%%     ?IPRINT("issue get-bulk command ~w", [N]),
+%%     case GetBulk(NonRep, MaxRep, Oids) of
+%% 	{ok, Reply, _Rem} ->
+%% 	    ?DBG("get-bulk ok:"
+%% 		 "~n   Reply: ~p"
+%% 		 "~n   Rem:   ~w", [Reply, _Rem]),
+%% 	    PostVerify(Verify(Reply));
+
+%% 	Error ->
+%% 	    {error, {unexpected_reply, Error}}
+%%     end.
+
+
+%%======================================================================
+
+simple_sync_get_bulk3(doc) -> 
+    ["Simple (sync) get_bulk-request - "
+     "Version 3 API (TargetName with send-opts)"];
+simple_sync_get_bulk3(suite) -> [];
+simple_sync_get_bulk3(Config) when is_list(Config) ->
+    ?TC_TRY(simple_sync_get_bulk3,
+            fun() -> do_simple_sync_get_bulk3(Config) end).
 
-do_simple_sync_get_bulk2(Config) ->
+do_simple_sync_get_bulk3(Config) ->
     ?IPRINT("starting with Config: "
             "~n      ~p~n", [Config]),
 
@@ -3125,32 +3681,43 @@ do_simple_sync_get_bulk2(Config) ->
     AgentNode  = ?config(agent_node, Config),
     TargetName = ?config(manager_agent_target_name, Config),
 
+    Self  = self(), 
+    Msg   = simple_async_set3, 
+    Fun   = fun() -> Self ! Msg end,
+    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
+    SendOpts = 
+	[
+	 {extra, Extra}
+	], 
+
     GetBulk = 
 	fun(NonRep, MaxRep, Oids) ->
-		mgr_user_sync_get_bulk(MgrNode, TargetName, 
-				       NonRep, MaxRep, Oids)    
+		mgr_user_sync_get_bulk2(MgrNode, TargetName, 
+					NonRep, MaxRep, Oids, SendOpts)    
 	end,
-    PostVerify = fun(Res) -> Res end,
+    PostVerify = fun(ok) -> receive Msg -> ok end;
+		    (Res) -> Res 
+		 end,
 
-    Res = do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify),
+    Res = do_simple_sync_get_bulk3(Config, MgrNode, AgentNode, GetBulk, PostVerify),
     display_log(Config),
     Res.
 
-do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
+do_simple_sync_get_bulk3(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
     %% -- 1 --
-    ?line ok = do_simple_get_bulk2(1,
+    ?line ok = do_simple_get_bulk3(1,
 				   1,  1, [], 
 				   fun verify_ssgb_reply1/1, 
 				   GetBulk, PostVerify), 
     
     %% -- 2 --
-    ?line ok = do_simple_get_bulk2(2, 
+    ?line ok = do_simple_get_bulk3(2, 
 				   -1,  1, [], 
 				   fun verify_ssgb_reply1/1, 
 				   GetBulk, PostVerify), 
 
     %% -- 3 --
-    ?line ok = do_simple_get_bulk2(3, 
+    ?line ok = do_simple_get_bulk3(3, 
 				   -1, -1, [], 
 				   fun verify_ssgb_reply1/1, 
 				   GetBulk, PostVerify), 
@@ -3160,12 +3727,12 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
     VF04 = fun(X) -> 
 		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(4,
+    ?line ok = do_simple_get_bulk3(4,
 				   2, 0, [[sysDescr],[1,3,7,1]], VF04, 
 				   GetBulk, PostVerify),
 
     %% -- 5 --
-    ?line ok = do_simple_get_bulk2(5,
+    ?line ok = do_simple_get_bulk3(5,
 				   1, 2, [[sysDescr],[1,3,7,1]], VF04, 
 				   GetBulk, PostVerify),
 
@@ -3175,7 +3742,7 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
 				      [?sysDescr_instance,    endOfMibView,
 				       ?sysObjectID_instance, endOfMibView]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(6,
+    ?line ok = do_simple_get_bulk3(6,
 				   0, 2, [[sysDescr],[1,3,7,1]], VF06, 
 				   GetBulk, PostVerify), 
 
@@ -3186,7 +3753,7 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
 				       ?sysDescr_instance,    endOfMibView,
 				       ?sysObjectID_instance, endOfMibView]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(7,
+    ?line ok = do_simple_get_bulk3(7,
 				   2, 2, 
 				   [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]],
 				   VF07, 
@@ -3202,14 +3769,14 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
 				      [?sysDescr_instance, 
 				       ?sysDescr_instance]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(8,
+    ?line ok = do_simple_get_bulk3(8,
 				   1, 2, 
 				   [[sysDescr],[sysDescr],[tTooBig]],
 				   VF08, 
 				   GetBulk, PostVerify), 
 
     %% -- 9 --
-    ?line ok = do_simple_get_bulk2(9,
+    ?line ok = do_simple_get_bulk3(9,
 				   1, 12, 
 				   [[tDescr2], [sysDescr]], 
 				   fun verify_ssgb_reply1/1, 
@@ -3223,7 +3790,7 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
 				       {?tGenErr1,    'NULL'},
 				       {?sysDescr,    'NULL'}]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(10,
+    ?line ok = do_simple_get_bulk3(10,
 				   2, 2, 
 				   [[sysDescr], 
 				    [sysObjectID], 
@@ -3240,14 +3807,14 @@ do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify) ->
 				      [{fl([TCnt2,2]), 100}, 
 				       {fl([TCnt2,2]), endOfMibView}]) 
 	   end,
-    ?line ok = do_simple_get_bulk2(11,
+    ?line ok = do_simple_get_bulk3(11,
 				   0, 2, 
 				   [[TCnt2, 1]], VF11, 
 				   GetBulk, PostVerify),
     
     ok.
 
-do_simple_get_bulk2(N, 
+do_simple_get_bulk3(N, 
 		    NonRep, MaxRep, Oids, 
 		    Verify, GetBulk, PostVerify) 
   when is_function(Verify, 1) andalso 
@@ -3268,15 +3835,181 @@ do_simple_get_bulk2(N,
 
 %%======================================================================
 
-simple_sync_get_bulk3(doc) -> 
-    ["Simple (sync) get_bulk-request - "
+%% simple_async_get_bulk2(doc) -> 
+%%     ["Simple (async) get_bulk-request - Version 2 API (TargetName)"];
+%% simple_async_get_bulk2(suite) -> [];
+%% simple_async_get_bulk2(Config) when is_list(Config) ->
+%%     ?TC_TRY(simple_async_get_bulk2,
+%%             fun() -> do_simple_async_get_bulk2(Config) end).
+
+%% do_simple_async_get_bulk2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~p      ~n", [Config]),
+    
+%%     MgrNode    = ?config(manager_node, Config),
+%%     AgentNode  = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
+
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
+%%     GetBulk = 
+%% 	fun(Data) ->
+%% 		async_gb_exec2(MgrNode, TargetName, Data)
+%% 	end,
+%%     PostVerify = fun(Res) -> Res end,
+
+%%     Res = do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify),
+%%     display_log(Config),
+%%     Res.
+
+%% do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify) ->
+%%     %% We re-use the verification functions from the ssgb test-case
+%%     VF04 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]))
+%% 	   end,
+%%     VF06 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply2(X, 
+%% 					[?sysDescr_instance,    endOfMibView,
+%% 					 ?sysObjectID_instance, endOfMibView]))
+%% 	   end,
+%%     VF07 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply2(X, 
+%% 					[?sysDescr_instance,    endOfMibView,
+%% 					 ?sysDescr_instance,    endOfMibView,
+%% 					 ?sysObjectID_instance, endOfMibView]))
+%% 	   end,
+%%     VF08 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply2(X, 
+%% 					[?sysDescr_instance, 
+%% 					 ?sysDescr_instance])) 
+%% 	   end,
+%%     VF10 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply3(X, 
+%% 					[{?sysDescr,    'NULL'}, 
+%% 					 {?sysObjectID, 'NULL'},
+%% 					 {?tGenErr1,    'NULL'},
+%% 					 {?sysDescr,    'NULL'}])) 
+%% 	   end,
+%%     ?line {ok, [TCnt2|_]} = mgr_user_name_to_oid(MgrNode, tCnt2),
+%%     VF11 = fun(X) -> 
+%% 		   PostVerify(
+%% 		     verify_ssgb_reply2(X, 
+%% 					[{fl([TCnt2,2]), 100}, 
+%% 					 {fl([TCnt2,2]), endOfMibView}]))
+%% 	   end,
+%%     Requests = [
+%% 		{ 1,  
+%% 		  {1,  1, []}, 
+%% 		  GetBulk, 
+%% 		  fun(X) -> PostVerify(verify_ssgb_reply1(X)) end},
+%% 		{ 2, 
+%% 		  {-1,  1, []}, 
+%% 		  GetBulk, 
+%% 		  fun(X) -> PostVerify(verify_ssgb_reply1(X)) end},
+%% 		{ 3, 
+%% 		  {-1, -1, []}, 
+%% 		  GetBulk, 
+%% 		  fun(X) -> PostVerify(verify_ssgb_reply1(X)) end},
+%% 		{ 4,  
+%% 		  {2,  0, [[sysDescr],[1,3,7,1]]}, 
+%% 		  GetBulk, 
+%% 		  VF04},
+%% 		{ 5,  
+%% 		  {1,  2, [[sysDescr],[1,3,7,1]]}, 
+%% 		  GetBulk, 
+%% 		  VF04},
+%% 		{ 6,  
+%% 		  {0,  2, [[sysDescr],[1,3,7,1]]}, 
+%% 		  GetBulk, 
+%% 		  VF06},
+%% 		{ 7,  
+%% 		  {2,  2, [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]]}, 
+%% 		  GetBulk, 
+%% 		  VF07},
+%% 		{ 8,  
+%% 		  {1,  2, [[sysDescr],[sysDescr],[tTooBig]]}, 
+%% 		  GetBulk, 
+%% 		  VF08},
+%% 		{ 9,  
+%% 		  {1, 12, [[tDescr2], [sysDescr]]}, 
+%% 		  GetBulk, 
+%% 		  fun(X) -> PostVerify(verify_ssgb_reply1(X)) end},
+%% 		{10,  
+%% 		 {2,  2, [[sysDescr],[sysObjectID], [tGenErr1],[sysDescr]]}, 
+%% 		 GetBulk, 
+%% 		 VF10},
+%% 		{11,  
+%% 		 {0,  2, [[TCnt2, 1]]}, 
+%% 		 GetBulk,
+%% 		 VF11}, 
+%% 		{12,  
+%% 		 {2,  0, [[sysDescr],[1,3,7,1]]}, 
+%% 		 GetBulk,
+%% 		 VF04},
+%% 		{13,  
+%% 		 {1, 12, [[tDescr2], [sysDescr]]},
+%% 		 GetBulk, 
+%% 		 fun(X) -> PostVerify(verify_ssgb_reply1(X)) end},
+%% 		{14,  
+%% 		 {2,  2, [[sysDescr],[sysObjectID],[tGenErr1],[sysDescr]]},
+%% 		 GetBulk, 
+%% 		 VF10},
+%% 		{15,  
+%% 		 {0,  2, [[TCnt2, 1]]},
+%% 		 GetBulk, 
+%% 		 VF11},
+%% 		{16,  
+%% 		 {2,  2, [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]]},
+%% 		 GetBulk, 
+%% 		 VF07},
+%% 		{17,  
+%% 		 {2,  2, [[sysDescr],[sysObjectID], [tGenErr1],[sysDescr]]},
+%% 		 GetBulk, 
+%% 		 VF10}
+%% 	       ],
+
+%%     ?IPRINT("manager info when starting test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when starting test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ?line ok = async_exec(Requests, []),
+
+%%     ?IPRINT("manager info when ending test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when ending test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
+
+%%     ok.
+
+
+%% async_gb_exec2(Node, TargetName, {NR, MR, Oids}) ->
+%%     mgr_user_async_get_bulk(Node, TargetName, NR, MR, Oids).
+
+
+%%======================================================================
+
+simple_async_get_bulk3_cbp_def(doc) -> 
+    ["Simple (async) get_bulk-request - "
      "Version 3 API (TargetName with send-opts)"];
-simple_sync_get_bulk3(suite) -> [];
-simple_sync_get_bulk3(Config) when is_list(Config) ->
-    ?TC_TRY(simple_sync_get_bulk3,
-            fun() -> do_simple_sync_get_bulk3(Config) end).
+simple_async_get_bulk3_cbp_def(suite) -> [];
+simple_async_get_bulk3_cbp_def(Config) when is_list(Config) ->
+    simple_async_get_bulk3(sagb3_cbp_def, Config).
 
-do_simple_sync_get_bulk3(Config) ->
+simple_async_get_bulk3(Case, Config) ->
+    ?TC_TRY(Case,
+            fun() -> do_simple_async_get_bulk3(Config) end).
+
+do_simple_async_get_bulk3(Config) ->
+    process_flag(trap_exit, true),
     ?IPRINT("starting with Config: "
             "~n      ~p~n", [Config]),
 
@@ -3284,8 +4017,13 @@ do_simple_sync_get_bulk3(Config) ->
     AgentNode  = ?config(agent_node, Config),
     TargetName = ?config(manager_agent_target_name, Config),
 
+    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+    Test2Mib = test2_mib(Config), 
+    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+    ?line ok = agent_load_mib(AgentNode, Test2Mib),
+
     Self  = self(), 
-    Msg   = simple_async_set3, 
+    Msg   = simple_async_get_bulk3, 
     Fun   = fun() -> Self ! Msg end,
     Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
     SendOpts = 
@@ -3294,52 +4032,18 @@ do_simple_sync_get_bulk3(Config) ->
 	], 
 
     GetBulk = 
-	fun(NonRep, MaxRep, Oids) ->
-		mgr_user_sync_get_bulk2(MgrNode, TargetName, 
-					NonRep, MaxRep, Oids, SendOpts)    
+	fun(Data) ->
+		async_gb_exec3(MgrNode, TargetName, Data, SendOpts)
 	end,
-    PostVerify = fun(ok) -> receive Msg -> ok end;
+    PostVerify = fun(ok)  -> receive Msg -> ok end;
 		    (Res) -> Res 
 		 end,
 
-    Res = do_simple_sync_get_bulk2(Config, MgrNode, AgentNode, GetBulk, PostVerify),
-    display_log(Config),
-    Res.
-
-
-%%======================================================================
-
-simple_async_get_bulk2(doc) -> 
-    ["Simple (async) get_bulk-request - Version 2 API (TargetName)"];
-simple_async_get_bulk2(suite) -> [];
-simple_async_get_bulk2(Config) when is_list(Config) ->
-    ?TC_TRY(simple_async_get_bulk2,
-            fun() -> do_simple_async_get_bulk2(Config) end).
-
-do_simple_async_get_bulk2(Config) ->
-    ?IPRINT("starting with Config: "
-            "~p      ~n", [Config]),
-    
-    MgrNode    = ?config(manager_node, Config),
-    AgentNode  = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
-
-    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
-    Test2Mib = test2_mib(Config), 
-    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
-    ?line ok = agent_load_mib(AgentNode, Test2Mib),
-
-    GetBulk = 
-	fun(Data) ->
-		async_gb_exec2(MgrNode, TargetName, Data)
-	end,
-    PostVerify = fun(Res) -> Res end,
-
-    Res = do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify),
+    Res = do_simple_async_get_bulk3(MgrNode, AgentNode, GetBulk, PostVerify),
     display_log(Config),
     Res.
 
-do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify) ->
+do_simple_async_get_bulk3(MgrNode, AgentNode, GetBulk, PostVerify) ->
     %% We re-use the verification functions from the ssgb test-case
     VF04 = fun(X) -> 
 		   PostVerify(
@@ -3465,58 +4169,6 @@ do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify) ->
     ok.
 
 
-async_gb_exec2(Node, TargetName, {NR, MR, Oids}) ->
-    mgr_user_async_get_bulk(Node, TargetName, NR, MR, Oids).
-
-
-%%======================================================================
-
-simple_async_get_bulk3_cbp_def(doc) -> 
-    ["Simple (async) get_bulk-request - "
-     "Version 3 API (TargetName with send-opts)"];
-simple_async_get_bulk3_cbp_def(suite) -> [];
-simple_async_get_bulk3_cbp_def(Config) when is_list(Config) ->
-    simple_async_get_bulk3(sagb3_cbp_def, Config).
-
-simple_async_get_bulk3(Case, Config) ->
-    ?TC_TRY(Case,
-            fun() -> do_simple_async_get_bulk3(Config) end).
-
-do_simple_async_get_bulk3(Config) ->
-    process_flag(trap_exit, true),
-    ?IPRINT("starting with Config: "
-            "~n      ~p~n", [Config]),
-
-    MgrNode    = ?config(manager_node, Config),
-    AgentNode  = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
-
-    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
-    Test2Mib = test2_mib(Config), 
-    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
-    ?line ok = agent_load_mib(AgentNode, Test2Mib),
-
-    Self  = self(), 
-    Msg   = simple_async_get_bulk3, 
-    Fun   = fun() -> Self ! Msg end,
-    Extra = {?SNMPM_EXTRA_INFO_TAG, Fun}, 
-    SendOpts = 
-	[
-	 {extra, Extra}
-	], 
-
-    GetBulk = 
-	fun(Data) ->
-		async_gb_exec3(MgrNode, TargetName, Data, SendOpts)
-	end,
-    PostVerify = fun(ok)  -> receive Msg -> ok end;
-		    (Res) -> Res 
-		 end,
-
-    Res = do_simple_async_get_bulk2(MgrNode, AgentNode, GetBulk, PostVerify),
-    display_log(Config),
-    Res.
-
 async_gb_exec3(Node, TargetName, {NR, MR, Oids}, SendOpts) ->
     mgr_user_async_get_bulk2(Node, TargetName, NR, MR, Oids, SendOpts).
 
@@ -3543,199 +4195,199 @@ simple_async_get_bulk3_cbp_perm(Config) when is_list(Config) ->
 
 %%======================================================================
 
-misc_async2(doc) -> 
-    ["Misc (async) request(s) - Version 2 API (TargetName)"];
-misc_async2(suite) -> [];
-misc_async2(Config) when is_list(Config) ->
-    ?TC_TRY(misc_async2,
-            fun() -> do_misc_async2(Config) end).
-
-do_misc_async2(Config) ->
-    ?IPRINT("starting with Config: "
-            "~n      ~p"
-            "~n", [Config]),
-
-    MgrNode   = ?config(manager_node, Config),
-    AgentNode = ?config(agent_node, Config),
-    TargetName = ?config(manager_agent_target_name, Config),
+%% misc_async2(doc) -> 
+%%     ["Misc (async) request(s) - Version 2 API (TargetName)"];
+%% misc_async2(suite) -> [];
+%% misc_async2(Config) when is_list(Config) ->
+%%     ?TC_TRY(misc_async2,
+%%             fun() -> do_misc_async2(Config) end).
+
+%% do_misc_async2(Config) ->
+%%     ?IPRINT("starting with Config: "
+%%             "~n      ~p"
+%%             "~n", [Config]),
+
+%%     MgrNode   = ?config(manager_node, Config),
+%%     AgentNode = ?config(agent_node, Config),
+%%     TargetName = ?config(manager_agent_target_name, Config),
     
-    ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
-    Test2Mib = test2_mib(Config), 
-    ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
-    ?line ok = agent_load_mib(AgentNode, Test2Mib),
+%%     ?line ok = mgr_user_load_mib(MgrNode, std_mib()),
+%%     Test2Mib = test2_mib(Config), 
+%%     ?line ok = mgr_user_load_mib(MgrNode, Test2Mib),
+%%     ?line ok = agent_load_mib(AgentNode, Test2Mib),
     
-    ExecG = fun(Data) ->
-		    async_g_exec2(MgrNode, TargetName, Data)
-	    end,
+%%     ExecG = fun(Data) ->
+%% 		    async_g_exec2(MgrNode, TargetName, Data)
+%% 	    end,
     
-    ExecGN = fun(Data) ->
-		     async_gn_exec2(MgrNode, TargetName, Data)
-	     end,
+%%     ExecGN = fun(Data) ->
+%% 		     async_gn_exec2(MgrNode, TargetName, Data)
+%% 	     end,
     
-    ExecS = fun(Data) ->
-		    async_s_exec2(MgrNode, TargetName, Data)
-	    end,
+%%     ExecS = fun(Data) ->
+%% 		    async_s_exec2(MgrNode, TargetName, Data)
+%% 	    end,
     
-    ExecGB = fun(Data) ->
-		     async_gb_exec2(MgrNode, TargetName, Data)
-	     end,
+%%     ExecGB = fun(Data) ->
+%% 		     async_gb_exec2(MgrNode, TargetName, Data)
+%% 	     end,
     
-    ?line {ok, [TCnt2|_]}    = mgr_user_name_to_oid(MgrNode, tCnt2),
-    ?line {ok, [TGenErr1|_]} = mgr_user_name_to_oid(MgrNode, tGenErr1),
-    ?line {ok, [TGenErr2|_]} = mgr_user_name_to_oid(MgrNode, tGenErr2),
-    ?line {ok, [TGenErr3|_]} = mgr_user_name_to_oid(MgrNode, tGenErr3),
-    ?line {ok, [TTooBig|_]}  = mgr_user_name_to_oid(MgrNode, tTooBig),
-
-    Requests = 
-	[
-	 { 1,  
-	   [?sysObjectID_instance], 
-	   ExecG, 
-	   fun(X) -> 
-		   sag_verify(X, [?sysObjectID_instance]) 
-	   end
-	  },
-	 { 2,  
-	   {1,  1, []}, 
-	   ExecGB, 
-	   fun verify_ssgb_reply1/1},
-	 { 3, 
-	   {-1,  1, []}, 
-	   ExecGB, 
-	   fun verify_ssgb_reply1/1},
-	 { 4,
-	   [{?sysLocation_instance, s, "Stockholm"}, 
-	    {?sysName_instance,     s, "Arne Anka"}],
-	   ExecS,
-	   fun(X) ->
-		   sas_verify(X, [?sysLocation_instance, ?sysName_instance])
-	   end}, 
-	 { 5, 
-	   [[sysDescr], [1,3,7,1]], 
-	   ExecGN, 
-	   fun(X) ->
-		   verify_ssgn_reply1(X, [?sysDescr_instance, endOfMibView])
-	   end}, 
-	 { 6,  
-	   [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
-	   ExecG, 
-	   fun(X) -> 
-		   sag_verify(X, [?sysObjectID_instance, 
-				  ?sysDescr_instance, 
-				  ?sysUpTime_instance]) 
-	   end}, 
-	 { 7, 
-	  [TGenErr2], 
-	   ExecGN, 
-	   fun(X) ->
-		   verify_ssgn_reply2(X, {genErr, 1, [TGenErr2]}) 
-	   end}, 
-	 { 8,  
-	   {2,  0, [[sysDescr],[1,3,7,1]]}, 
-	   ExecGB, 
-	   fun(X) -> 
-		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
-	   end},
-	 { 9,  
-	   {1,  2, [[sysDescr],[1,3,7,1]]}, 
-	   ExecGB, 
-	   fun(X) -> 
-		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
-	   end},
-	 {10, 
-	  [TGenErr1], 
-	  ExecGN, 
-	  fun(X) ->
-		  verify_ssgn_reply2(X, {genErr, 1, [TGenErr1]}) 
-	  end}, 
-	 {11,  
-	  {0,  2, [[sysDescr],[1,3,7,1]]}, 
-	  ExecGB, 
-	  fun(X) -> 
-		  verify_ssgb_reply2(X, 
-				     [?sysDescr_instance,    endOfMibView,
-				      ?sysObjectID_instance, endOfMibView]) 
-	  end},
-	 {12,
-	  [{[sysName, 0],     "Gothenburg"}, 
-	   {[sysLocation, 0], "Sune Anka"}],
-	  ExecS,
-	  fun(X) ->
-		  sas_verify(X, [?sysName_instance, ?sysLocation_instance])
-	  end},
-	 {13,  
-	  {2,  2, [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]]}, 
-	  ExecGB, 
-	  fun(X) -> 
-		  verify_ssgb_reply2(X, 
-				     [?sysDescr_instance,    endOfMibView,
-				      ?sysDescr_instance,    endOfMibView,
-				      ?sysObjectID_instance, endOfMibView]) 
-	  end},
-	 {14,  
-	  {1,  2, [[sysDescr],[sysDescr],[tTooBig]]}, 
-	  ExecGB, 
-	  fun(X) -> 
-		  verify_ssgb_reply2(X, 
-				     [?sysDescr_instance, 
-				      ?sysDescr_instance]) 
-	  end},
-	 {15,  
-	  {1, 12, [[tDescr2], [sysDescr]]}, 
-	  ExecGB, 
-	  fun verify_ssgb_reply1/1},
-	 {16,  
-	  {2,  2, [[sysDescr],[sysObjectID], [tGenErr1],[sysDescr]]}, 
-	  ExecGB, 
-	  fun(X) -> 
-		  verify_ssgb_reply3(X, 
-				     [{?sysDescr,    'NULL'}, 
-				      {?sysObjectID, 'NULL'},
-				      {?tGenErr1,    'NULL'},
-				      {?sysDescr,    'NULL'}]) 
-	  end},
-	 {17, 
-	  [[sysDescr], TGenErr3], 
-	  ExecGN, 
-	  fun(X) ->
-		  verify_ssgn_reply2(X, {genErr, 2, [TGenErr3]}) 
-	  end}, 
-	 {18,  
-	  {0,  2, [[TCnt2, 1]]}, 
-	  ExecGB,
-	  fun(X) -> 
-		  verify_ssgb_reply2(X, 
-				     [{fl([TCnt2,2]), 100}, 
-				      {fl([TCnt2,2]), endOfMibView}]) 
-	  end},
-	 {19, 
-	  [TTooBig], 
-	  ExecGN, 
-	  fun(X) ->
-		  verify_ssgn_reply2(X, {tooBig, 0, []}) 
-	  end},
-	 {20, 
-	  [TTooBig], 
-	  ExecGN, 
-	  fun(X) ->
-		  verify_ssgn_reply2(X, {tooBig, 0, []}) 
-	  end}
-	],
+%%     ?line {ok, [TCnt2|_]}    = mgr_user_name_to_oid(MgrNode, tCnt2),
+%%     ?line {ok, [TGenErr1|_]} = mgr_user_name_to_oid(MgrNode, tGenErr1),
+%%     ?line {ok, [TGenErr2|_]} = mgr_user_name_to_oid(MgrNode, tGenErr2),
+%%     ?line {ok, [TGenErr3|_]} = mgr_user_name_to_oid(MgrNode, tGenErr3),
+%%     ?line {ok, [TTooBig|_]}  = mgr_user_name_to_oid(MgrNode, tTooBig),
+
+%%     Requests = 
+%% 	[
+%% 	 { 1,  
+%% 	   [?sysObjectID_instance], 
+%% 	   ExecG, 
+%% 	   fun(X) -> 
+%% 		   sag_verify(X, [?sysObjectID_instance]) 
+%% 	   end
+%% 	  },
+%% 	 { 2,  
+%% 	   {1,  1, []}, 
+%% 	   ExecGB, 
+%% 	   fun verify_ssgb_reply1/1},
+%% 	 { 3, 
+%% 	   {-1,  1, []}, 
+%% 	   ExecGB, 
+%% 	   fun verify_ssgb_reply1/1},
+%% 	 { 4,
+%% 	   [{?sysLocation_instance, s, "Stockholm"}, 
+%% 	    {?sysName_instance,     s, "Arne Anka"}],
+%% 	   ExecS,
+%% 	   fun(X) ->
+%% 		   sas_verify(X, [?sysLocation_instance, ?sysName_instance])
+%% 	   end}, 
+%% 	 { 5, 
+%% 	   [[sysDescr], [1,3,7,1]], 
+%% 	   ExecGN, 
+%% 	   fun(X) ->
+%% 		   verify_ssgn_reply1(X, [?sysDescr_instance, endOfMibView])
+%% 	   end}, 
+%% 	 { 6,  
+%% 	   [[sysObjectID, 0], [sysDescr, 0], [sysUpTime, 0]],
+%% 	   ExecG, 
+%% 	   fun(X) -> 
+%% 		   sag_verify(X, [?sysObjectID_instance, 
+%% 				  ?sysDescr_instance, 
+%% 				  ?sysUpTime_instance]) 
+%% 	   end}, 
+%% 	 { 7, 
+%% 	  [TGenErr2], 
+%% 	   ExecGN, 
+%% 	   fun(X) ->
+%% 		   verify_ssgn_reply2(X, {genErr, 1, [TGenErr2]}) 
+%% 	   end}, 
+%% 	 { 8,  
+%% 	   {2,  0, [[sysDescr],[1,3,7,1]]}, 
+%% 	   ExecGB, 
+%% 	   fun(X) -> 
+%% 		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
+%% 	   end},
+%% 	 { 9,  
+%% 	   {1,  2, [[sysDescr],[1,3,7,1]]}, 
+%% 	   ExecGB, 
+%% 	   fun(X) -> 
+%% 		   verify_ssgb_reply2(X, [?sysDescr_instance, endOfMibView]) 
+%% 	   end},
+%% 	 {10, 
+%% 	  [TGenErr1], 
+%% 	  ExecGN, 
+%% 	  fun(X) ->
+%% 		  verify_ssgn_reply2(X, {genErr, 1, [TGenErr1]}) 
+%% 	  end}, 
+%% 	 {11,  
+%% 	  {0,  2, [[sysDescr],[1,3,7,1]]}, 
+%% 	  ExecGB, 
+%% 	  fun(X) -> 
+%% 		  verify_ssgb_reply2(X, 
+%% 				     [?sysDescr_instance,    endOfMibView,
+%% 				      ?sysObjectID_instance, endOfMibView]) 
+%% 	  end},
+%% 	 {12,
+%% 	  [{[sysName, 0],     "Gothenburg"}, 
+%% 	   {[sysLocation, 0], "Sune Anka"}],
+%% 	  ExecS,
+%% 	  fun(X) ->
+%% 		  sas_verify(X, [?sysName_instance, ?sysLocation_instance])
+%% 	  end},
+%% 	 {13,  
+%% 	  {2,  2, [[sysDescr],[1,3,7,1],[sysDescr],[1,3,7,1]]}, 
+%% 	  ExecGB, 
+%% 	  fun(X) -> 
+%% 		  verify_ssgb_reply2(X, 
+%% 				     [?sysDescr_instance,    endOfMibView,
+%% 				      ?sysDescr_instance,    endOfMibView,
+%% 				      ?sysObjectID_instance, endOfMibView]) 
+%% 	  end},
+%% 	 {14,  
+%% 	  {1,  2, [[sysDescr],[sysDescr],[tTooBig]]}, 
+%% 	  ExecGB, 
+%% 	  fun(X) -> 
+%% 		  verify_ssgb_reply2(X, 
+%% 				     [?sysDescr_instance, 
+%% 				      ?sysDescr_instance]) 
+%% 	  end},
+%% 	 {15,  
+%% 	  {1, 12, [[tDescr2], [sysDescr]]}, 
+%% 	  ExecGB, 
+%% 	  fun verify_ssgb_reply1/1},
+%% 	 {16,  
+%% 	  {2,  2, [[sysDescr],[sysObjectID], [tGenErr1],[sysDescr]]}, 
+%% 	  ExecGB, 
+%% 	  fun(X) -> 
+%% 		  verify_ssgb_reply3(X, 
+%% 				     [{?sysDescr,    'NULL'}, 
+%% 				      {?sysObjectID, 'NULL'},
+%% 				      {?tGenErr1,    'NULL'},
+%% 				      {?sysDescr,    'NULL'}]) 
+%% 	  end},
+%% 	 {17, 
+%% 	  [[sysDescr], TGenErr3], 
+%% 	  ExecGN, 
+%% 	  fun(X) ->
+%% 		  verify_ssgn_reply2(X, {genErr, 2, [TGenErr3]}) 
+%% 	  end}, 
+%% 	 {18,  
+%% 	  {0,  2, [[TCnt2, 1]]}, 
+%% 	  ExecGB,
+%% 	  fun(X) -> 
+%% 		  verify_ssgb_reply2(X, 
+%% 				     [{fl([TCnt2,2]), 100}, 
+%% 				      {fl([TCnt2,2]), endOfMibView}]) 
+%% 	  end},
+%% 	 {19, 
+%% 	  [TTooBig], 
+%% 	  ExecGN, 
+%% 	  fun(X) ->
+%% 		  verify_ssgn_reply2(X, {tooBig, 0, []}) 
+%% 	  end},
+%% 	 {20, 
+%% 	  [TTooBig], 
+%% 	  ExecGN, 
+%% 	  fun(X) ->
+%% 		  verify_ssgn_reply2(X, {tooBig, 0, []}) 
+%% 	  end}
+%% 	],
     
-    ?IPRINT("manager info when starting test: "
-            "~n      ~p", [mgr_info(MgrNode)]),
-    ?IPRINT("agent info when starting test: "
-            "~n      ~p", [agent_info(AgentNode)]),
+%%     ?IPRINT("manager info when starting test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when starting test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
 
-    ?line ok = async_exec(Requests, []),
+%%     ?line ok = async_exec(Requests, []),
 
-    ?IPRINT("manager info when ending test: "
-            "~n      ~p", [mgr_info(MgrNode)]),
-    ?IPRINT("agent info when ending test: "
-            "~n      ~p", [agent_info(AgentNode)]),
+%%     ?IPRINT("manager info when ending test: "
+%%             "~n      ~p", [mgr_info(MgrNode)]),
+%%     ?IPRINT("agent info when ending test: "
+%%             "~n      ~p", [agent_info(AgentNode)]),
 
-    display_log(Config),
-    ok.
+%%     display_log(Config),
+%%     ok.
 
 
 %%======================================================================
@@ -5001,7 +5653,7 @@ otp8395_1(Config) when is_list(Config) ->
             fun() -> do_otp8395_1(Config) end).
 
 do_otp8395_1(Config) ->
-    do_simple_sync_get2(Config).
+    do_simple_sync_get3(Config).
 
 
 %%======================================================================
@@ -5707,16 +6359,16 @@ mgr_user_load_mib(Node, Mib) ->
 
 %% mgr_user_sync_get(Node, Oids) ->
 %%     mgr_user_sync_get(Node, ?LOCALHOST(), ?AGENT_PORT, Oids).
-mgr_user_sync_get(Node, TargetName, Oids) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, sync_get, [TargetName, Oids]).
+%% mgr_user_sync_get(Node, TargetName, Oids) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, sync_get, [TargetName, Oids]).
 
 mgr_user_sync_get2(Node, TargetName, Oids, SendOpts) when is_list(TargetName) ->
     rcall(Node, snmp_manager_user, sync_get2, [TargetName, Oids, SendOpts]).
 
 %% mgr_user_async_get(Node, Oids) ->
 %%     mgr_user_async_get(Node, ?LOCALHOST(), ?AGENT_PORT, Oids).
-mgr_user_async_get(Node, TargetName, Oids) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, async_get, [TargetName, Oids]).
+%% mgr_user_async_get(Node, TargetName, Oids) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, async_get, [TargetName, Oids]).
 
 mgr_user_async_get2(Node, TargetName, Oids, SendOpts) 
   when is_list(TargetName) ->
@@ -5724,8 +6376,8 @@ mgr_user_async_get2(Node, TargetName, Oids, SendOpts)
 
 %% mgr_user_sync_get_next(Node, Oids) ->
 %%     mgr_user_sync_get_next(Node, ?LOCALHOST(), ?AGENT_PORT, Oids).
-mgr_user_sync_get_next(Node, TargetName, Oids) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, sync_get_next, [TargetName, Oids]).
+%% mgr_user_sync_get_next(Node, TargetName, Oids) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, sync_get_next, [TargetName, Oids]).
 
 mgr_user_sync_get_next2(Node, TargetName, Oids, SendOpts) 
   when is_list(TargetName) ->
@@ -5733,8 +6385,8 @@ mgr_user_sync_get_next2(Node, TargetName, Oids, SendOpts)
 
 %% mgr_user_async_get_next(Node, Oids) ->
 %%     mgr_user_async_get_next(Node, ?LOCALHOST(), ?AGENT_PORT, Oids).
-mgr_user_async_get_next(Node, TargetName, Oids) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, async_get_next, [TargetName, Oids]).
+%% mgr_user_async_get_next(Node, TargetName, Oids) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, async_get_next, [TargetName, Oids]).
 
 mgr_user_async_get_next2(Node, TargetName, Oids, SendOpts) 
   when is_list(TargetName) ->
@@ -5742,16 +6394,16 @@ mgr_user_async_get_next2(Node, TargetName, Oids, SendOpts)
 
 %% mgr_user_sync_set(Node, VAV) ->
 %%     mgr_user_sync_set(Node, ?LOCALHOST(), ?AGENT_PORT, VAV).
-mgr_user_sync_set(Node, TargetName, VAV) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, sync_set, [TargetName, VAV]).
+%% mgr_user_sync_set(Node, TargetName, VAV) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, sync_set, [TargetName, VAV]).
 
 mgr_user_sync_set2(Node, TargetName, VAV, SendOpts) when is_list(TargetName) ->
     rcall(Node, snmp_manager_user, sync_set2, [TargetName, VAV, SendOpts]).
 
 %% mgr_user_async_set(Node, VAV) ->
 %%     mgr_user_async_set(Node, ?LOCALHOST(), ?AGENT_PORT, VAV).
-mgr_user_async_set(Node, TargetName, VAV) when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, async_set, [TargetName, VAV]).
+%% mgr_user_async_set(Node, TargetName, VAV) when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, async_set, [TargetName, VAV]).
 
 mgr_user_async_set2(Node, TargetName, VAV, SendOpts) when is_list(TargetName) ->
     rcall(Node, snmp_manager_user, async_set2, [TargetName, VAV, SendOpts]).
@@ -5772,10 +6424,10 @@ mgr_user_sync_get_bulk2(Node, TargetName, NonRep, MaxRep, Oids, SendOpts)
 %% mgr_user_async_get_bulk(Node, NonRep, MaxRep, Oids) ->
 %%     mgr_user_async_get_bulk(Node, ?LOCALHOST(), ?AGENT_PORT, 
 %% 			   NonRep, MaxRep, Oids).
-mgr_user_async_get_bulk(Node, TargetName, NonRep, MaxRep, Oids) 
-  when is_list(TargetName) ->
-    rcall(Node, snmp_manager_user, async_get_bulk, 
-	  [TargetName, NonRep, MaxRep, Oids]).
+%% mgr_user_async_get_bulk(Node, TargetName, NonRep, MaxRep, Oids) 
+%%   when is_list(TargetName) ->
+%%     rcall(Node, snmp_manager_user, async_get_bulk, 
+%% 	  [TargetName, NonRep, MaxRep, Oids]).
 
 mgr_user_async_get_bulk2(Node, TargetName, NonRep, MaxRep, Oids, SendOpts) 
   when is_list(TargetName) ->
diff --git a/lib/snmp/test/snmp_manager_user.erl b/lib/snmp/test/snmp_manager_user.erl
index 409f87cf40..2587634e4a 100644
--- a/lib/snmp/test/snmp_manager_user.erl
+++ b/lib/snmp/test/snmp_manager_user.erl
@@ -51,14 +51,22 @@
 	 update_agent_info/3, 
 	 which_all_agents/0, which_own_agents/0, 
 	 load_mib/1, unload_mib/1, 
-	 sync_get/1,       sync_get/2,       sync_get2/3, 
-	 async_get/1,      async_get/2,      async_get2/3,
-	 sync_get_next/1,  sync_get_next/2,  sync_get_next2/3,
-	 async_get_next/1, async_get_next/2, async_get_next2/3,
-	 sync_set/1,       sync_set/2,       sync_set2/3, 
-	 async_set/1,      async_set/2,      async_set2/3, 
-	 sync_get_bulk/3,  sync_get_bulk/4,  sync_get_bulk2/5,
-	 async_get_bulk/3, async_get_bulk/4, async_get_bulk2/5,
+	 %% sync_get/1,       sync_get/2,
+         sync_get2/3, 
+	 %% async_get/1,      async_get/2,
+         async_get2/3,
+	 %% sync_get_next/1,  sync_get_next/2,
+         sync_get_next2/3,
+	 %% async_get_next/1, async_get_next/2,
+         async_get_next2/3,
+	 %% sync_set/1,       sync_set/2,
+         sync_set2/3, 
+	 %% async_set/1,      async_set/2,
+         async_set2/3, 
+	 %% sync_get_bulk/3,  sync_get_bulk/4,
+         sync_get_bulk2/5,
+	 %% async_get_bulk/3, async_get_bulk/4,
+         async_get_bulk2/5,
 	 name_to_oid/1, oid_to_name/1, 
 	 purify_oid/1	 
         ]).
@@ -159,11 +167,11 @@ unload_mib(Mib) ->
 
 %% -- 
 
-sync_get(Oids) ->
-    call({sync_get, Oids}).
+%% sync_get(Oids) ->
+%%     call({sync_get, Oids}).
 
-sync_get(TargetName, Oids) ->
-    call({sync_get, TargetName, Oids}).
+%% sync_get(TargetName, Oids) ->
+%%     call({sync_get, TargetName, Oids}).
 
 sync_get2(TargetName, Oids, SendOpts) ->
     call({sync_get2, TargetName, Oids, SendOpts}).
@@ -171,77 +179,77 @@ sync_get2(TargetName, Oids, SendOpts) ->
 
 %% --
 
-async_get(Oids) ->
-    call({async_get, Oids}).
+%% async_get(Oids) ->
+%%     call({async_get, Oids}).
 
-async_get(TargetName, Oids) ->
-    call({async_get, TargetName, Oids}).
+%% async_get(TargetName, Oids) ->
+%%     call({async_get, TargetName, Oids}).
 
 async_get2(TargetName, Oids, SendOpts) ->
     call({async_get2, TargetName, Oids, SendOpts}).
 
 %% --
 
-sync_get_next(Oids) ->
-    call({sync_get_next, Oids}).
+%% sync_get_next(Oids) ->
+%%     call({sync_get_next, Oids}).
 
-sync_get_next(TargetName, Oids) ->
-    call({sync_get_next, TargetName, Oids}).
+%% sync_get_next(TargetName, Oids) ->
+%%     call({sync_get_next, TargetName, Oids}).
 
 sync_get_next2(TargetName, Oids, SendOpts) ->
     call({sync_get_next2, TargetName, Oids, SendOpts}).
 
 %% --
 
-async_get_next(Oids) ->
-    call({async_get_next, Oids}).
+%% async_get_next(Oids) ->
+%%     call({async_get_next, Oids}).
 
-async_get_next(TargetName, Oids) ->
-    call({async_get_next, TargetName, Oids}).
+%% async_get_next(TargetName, Oids) ->
+%%     call({async_get_next, TargetName, Oids}).
 
 async_get_next2(TargetName, Oids, SendOpts) ->
     call({async_get_next2, TargetName, Oids, SendOpts}).
 
 %% --
 
-sync_set(VAV) ->
-    call({sync_set, VAV}).
+%% sync_set(VAV) ->
+%%     call({sync_set, VAV}).
 
-sync_set(TargetName, VAV) ->
-    call({sync_set, TargetName, VAV}).
+%% sync_set(TargetName, VAV) ->
+%%     call({sync_set, TargetName, VAV}).
 
 sync_set2(TargetName, VAV, SendOpts) ->
     call({sync_set2, TargetName, VAV, SendOpts}).
 
 %% --
 
-async_set(VAV) ->
-    call({async_set, VAV}).
+%% async_set(VAV) ->
+%%     call({async_set, VAV}).
 
-async_set(TargetName, VAV) ->
-    call({async_set, TargetName, VAV}).
+%% async_set(TargetName, VAV) ->
+%%     call({async_set, TargetName, VAV}).
 
 async_set2(TargetName, VAV, SendOpts) ->
     call({async_set2, TargetName, VAV, SendOpts}).
 
 %% --
 
-sync_get_bulk(NonRep, MaxRep, Oids) ->
-    call({sync_get_bulk, NonRep, MaxRep, Oids}).
+%% sync_get_bulk(NonRep, MaxRep, Oids) ->
+%%     call({sync_get_bulk, NonRep, MaxRep, Oids}).
 
-sync_get_bulk(TargetName, NonRep, MaxRep, Oids) ->
-    call({sync_get_bulk, TargetName, NonRep, MaxRep, Oids}).
+%% sync_get_bulk(TargetName, NonRep, MaxRep, Oids) ->
+%%     call({sync_get_bulk, TargetName, NonRep, MaxRep, Oids}).
 
 sync_get_bulk2(TargetName, NonRep, MaxRep, Oids, SendOpts) ->
     call({sync_get_bulk2, TargetName, NonRep, MaxRep, Oids, SendOpts}).
 
 %% --
 
-async_get_bulk(NonRep, MaxRep, Oids) ->
-    call({async_get_bulk, NonRep, MaxRep, Oids}).
+%% async_get_bulk(NonRep, MaxRep, Oids) ->
+%%     call({async_get_bulk, NonRep, MaxRep, Oids}).
 
-async_get_bulk(TargetName, NonRep, MaxRep, Oids) ->
-    call({async_get_bulk, TargetName, NonRep, MaxRep, Oids}).
+%% async_get_bulk(TargetName, NonRep, MaxRep, Oids) ->
+%%     call({async_get_bulk, TargetName, NonRep, MaxRep, Oids}).
 
 async_get_bulk2(TargetName, NonRep, MaxRep, Oids, SendOpts) ->
     call({async_get_bulk2, TargetName, NonRep, MaxRep, Oids, SendOpts}).
@@ -377,22 +385,22 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{sync_get, Oids}, From, Ref} ->
-	    d("loop -> received sync_get request "
-	      "(for every agent of this user)"),
-	    Res = [snmpm:sync_get(Id, TargetName, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{sync_get, Oids}, From, Ref} ->
+	%%     d("loop -> received sync_get request "
+	%%       "(for every agent of this user)"),
+	%%     Res = [snmpm:sync_get(Id, TargetName, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{sync_get, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received sync_get request with"
-	      "~n   TargetName: ~p"
-	      "~n   Oids:       ~p", [TargetName, Oids]),
-	    Res = snmpm:sync_get(Id, TargetName, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{sync_get, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received sync_get request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   Oids:       ~p", [TargetName, Oids]),
+	%%     Res = snmpm:sync_get(Id, TargetName, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -409,21 +417,21 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{async_get, Oids}, From, Ref} ->
-	    d("loop -> received async_get request"),
-	    Res = [snmpm:async_get(Id, TargetName, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{async_get, Oids}, From, Ref} ->
+	%%     d("loop -> received async_get request"),
+	%%     Res = [snmpm:async_get(Id, TargetName, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{async_get, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received async_get request with"
-	      "~n   TargetName: ~p"
-	      "~n   Oids:       ~p", [TargetName, Oids]),
-	    Res = snmpm:async_get(Id, TargetName, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{async_get, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received async_get request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   Oids:       ~p", [TargetName, Oids]),
+	%%     Res = snmpm:async_get(Id, TargetName, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -440,21 +448,21 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{sync_get_next, Oids}, From, Ref} ->
-	    d("loop -> received sync_get_next request"),
-	    Res = [snmpm:sync_get_next(Id, TargetName, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{sync_get_next, Oids}, From, Ref} ->
+	%%     d("loop -> received sync_get_next request"),
+	%%     Res = [snmpm:sync_get_next(Id, TargetName, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{sync_get_next, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received sync_get_next request with"
-	      "~n   TargetName: ~p"
-	      "~n   Oids:       ~p", [TargetName, Oids]),
-	    Res = snmpm:sync_get_next(Id, TargetName, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{sync_get_next, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received sync_get_next request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   Oids:       ~p", [TargetName, Oids]),
+	%%     Res = snmpm:sync_get_next(Id, TargetName, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -471,21 +479,21 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{async_get_next, Oids}, From, Ref} ->
-	    d("loop -> received async_get_next request"),
-	    Res = [snmpm:async_get_next(Id, TargetName, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{async_get_next, Oids}, From, Ref} ->
+	%%     d("loop -> received async_get_next request"),
+	%%     Res = [snmpm:async_get_next(Id, TargetName, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{async_get_next, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received async_get_next request with"
-	      "~n   TargetName: ~p"
-	      "~n   Oids:       ~p", [TargetName, Oids]),
-	    Res = snmpm:async_get_next(Id, TargetName, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{async_get_next, TargetName, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received async_get_next request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   Oids:       ~p", [TargetName, Oids]),
+	%%     Res = snmpm:async_get_next(Id, TargetName, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -502,18 +510,18 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	{{sync_set, VAV}, From, Ref} ->
-	    d("loop -> received sync_set request"),
-	    Res = [snmpm:sync_set(Id, TargetName, VAV) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{sync_set, VAV}, From, Ref} ->
+	%%     d("loop -> received sync_set request"),
+	%%     Res = [snmpm:sync_set(Id, TargetName, VAV) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{sync_set, TargetName, VAV}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received sync_set request"),
-	    Res = snmpm:sync_set(Id, TargetName, VAV), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{sync_set, TargetName, VAV}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received sync_set request"),
+	%%     Res = snmpm:sync_set(Id, TargetName, VAV), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -530,18 +538,18 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	{{async_set, VAV}, From, Ref} ->
-	    d("loop -> received async_set request"),
-	    Res = [snmpm:async_set(Id, TargetName, VAV) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{async_set, VAV}, From, Ref} ->
+	%%     d("loop -> received async_set request"),
+	%%     Res = [snmpm:async_set(Id, TargetName, VAV) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{async_set, TargetName, VAV}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received async_set request"),
-	    Res = snmpm:async_set(Id, TargetName, VAV), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{async_set, TargetName, VAV}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received async_set request"),
+	%%     Res = snmpm:async_set(Id, TargetName, VAV), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -562,26 +570,26 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{sync_get_bulk, NonRep, MaxRep, Oids}, From, Ref} ->
-	    d("loop -> received sync_get_bulk request with"
-	      "~n   NonRep: ~w"
-	      "~n   MaxRep: ~w"
-	      "~n   Oids:   ~p", [NonRep, MaxRep, Oids]),
-	    Res = [snmpm:sync_get_bulk(Id, TargetName, NonRep, MaxRep, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{sync_get_bulk, NonRep, MaxRep, Oids}, From, Ref} ->
+	%%     d("loop -> received sync_get_bulk request with"
+	%%       "~n   NonRep: ~w"
+	%%       "~n   MaxRep: ~w"
+	%%       "~n   Oids:   ~p", [NonRep, MaxRep, Oids]),
+	%%     Res = [snmpm:sync_get_bulk(Id, TargetName, NonRep, MaxRep, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
-	{{sync_get_bulk, TargetName, NonRep, MaxRep, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received sync_get_bulk request with"
-	      "~n   TargetName: ~p"
-	      "~n   NonRep:     ~w"
-	      "~n   MaxRep:     ~w"
-	      "~n   Oids:       ~p", [TargetName, NonRep, MaxRep, Oids]),
-	    Res = snmpm:sync_get_bulk(Id, TargetName, NonRep, MaxRep, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% {{sync_get_bulk, TargetName, NonRep, MaxRep, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received sync_get_bulk request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   NonRep:     ~w"
+	%%       "~n   MaxRep:     ~w"
+	%%       "~n   Oids:       ~p", [TargetName, NonRep, MaxRep, Oids]),
+	%%     Res = snmpm:sync_get_bulk(Id, TargetName, NonRep, MaxRep, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
@@ -602,26 +610,26 @@ loop(#state{parent = Parent, id = Id} = S) ->
 	    reply(From, Res, Ref),
 	    loop(S);
 
-	%% No agent specified, so send it to all of them
-	{{async_get_bulk, NonRep, MaxRep, Oids}, From, Ref} ->
-	    d("loop -> received async_get_bulk request with"
-	      "~n   NonRep: ~w"
-	      "~n   MaxRep: ~w"
-	      "~n   Oids:   ~p", [NonRep, MaxRep, Oids]),
-	    Res = [snmpm:async_get_bulk(Id, TargetName, NonRep, MaxRep, Oids) ||
-		      TargetName <- snmpm:which_agents(Id)],
-	    reply(From, Res, Ref),
-	    loop(S);
-
-	{{async_get_bulk, TargetName, NonRep, MaxRep, Oids}, From, Ref} when is_list(TargetName) ->
-	    d("loop -> received async_get_bulk request with"
-	      "~n   TargetName: ~p"
-	      "~n   NonRep:     ~w"
-	      "~n   MaxRep:     ~w"
-	      "~n   Oids:       ~p", [TargetName, NonRep, MaxRep, Oids]),
-	    Res = snmpm:async_get_bulk(Id, TargetName, NonRep, MaxRep, Oids), 
-	    reply(From, Res, Ref),
-	    loop(S);
+	%% %% No agent specified, so send it to all of them
+	%% {{async_get_bulk, NonRep, MaxRep, Oids}, From, Ref} ->
+	%%     d("loop -> received async_get_bulk request with"
+	%%       "~n   NonRep: ~w"
+	%%       "~n   MaxRep: ~w"
+	%%       "~n   Oids:   ~p", [NonRep, MaxRep, Oids]),
+	%%     Res = [snmpm:async_get_bulk(Id, TargetName, NonRep, MaxRep, Oids) ||
+	%% 	      TargetName <- snmpm:which_agents(Id)],
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
+
+	%% {{async_get_bulk, TargetName, NonRep, MaxRep, Oids}, From, Ref} when is_list(TargetName) ->
+	%%     d("loop -> received async_get_bulk request with"
+	%%       "~n   TargetName: ~p"
+	%%       "~n   NonRep:     ~w"
+	%%       "~n   MaxRep:     ~w"
+	%%       "~n   Oids:       ~p", [TargetName, NonRep, MaxRep, Oids]),
+	%%     Res = snmpm:async_get_bulk(Id, TargetName, NonRep, MaxRep, Oids), 
+	%%     reply(From, Res, Ref),
+	%%     loop(S);
 
 
 	%% 
-- 
2.16.4

openSUSE Build Service is sponsored by