File 2635-snmp-agent-Add-the-default-get-mechanism-module-snmp.patch of Package erlang

From c842e38a1be4a92f14a309a6ccb66f33b5585088 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 26 Mar 2019 11:25:50 +0100
Subject: [PATCH 5/8] [snmp|agent] Add the default get-mechanism module
 snmpa_get

Added the snmpa_get module as the default get-mechanism
for the agent.
This has been done by simply moving the do_get, do_get_next
and do_get_bulk functions from the snmpa_agent module.
Some functions where also moved into the lib module (with
the idea of beeing more generally useful).

OTP-15691
---
 lib/snmp/src/agent/depend.mk               |   14 +
 lib/snmp/src/agent/modules.mk              |    2 +
 lib/snmp/src/agent/snmpa_agent.erl         | 1147 ++-------------------------
 lib/snmp/src/agent/snmpa_get.erl           | 1148 ++++++++++++++++++++++++++++
 lib/snmp/src/agent/snmpa_get_lib.erl       |  253 ++++++
 lib/snmp/src/agent/snmpa_get_mechanism.erl |   27 +-
 lib/snmp/src/agent/tmp/snmpa_get.erl       |  859 +++++++++++++++++++++
 lib/snmp/src/agent/tmp/snmpa_get_lib.erl   |  507 ++++++++++++
 lib/snmp/src/app/snmp.app.src              |    3 +
 lib/snmp/src/app/snmp.config               |    1 +
 lib/snmp/test/modules.mk                   |    1 +
 lib/snmp/test/snmp_agent_test_get.erl      |   55 ++
 lib/snmp/test/snmp_agent_test_lib.erl      |    1 +
 13 files changed, 2931 insertions(+), 1087 deletions(-)
 create mode 100644 lib/snmp/src/agent/snmpa_get.erl
 create mode 100644 lib/snmp/src/agent/snmpa_get_lib.erl
 create mode 100644 lib/snmp/src/agent/tmp/snmpa_get.erl
 create mode 100644 lib/snmp/src/agent/tmp/snmpa_get_lib.erl
 create mode 100644 lib/snmp/test/snmp_agent_test_get.erl

diff --git a/lib/snmp/src/agent/depend.mk b/lib/snmp/src/agent/depend.mk
index 530a82f7ca..49c7669e41 100644
--- a/lib/snmp/src/agent/depend.mk
+++ b/lib/snmp/src/agent/depend.mk
@@ -81,6 +81,20 @@ $(EBIN)/snmpa_error_logger.$(EMULATOR): \
 	snmpa_error_report.erl \
 	snmpa_error_logger.erl
 
+$(EBIN)/snmpa_set.$(EMULATOR): \
+	snmpa_set_mechanism.erl \
+	snmpa_set.erl \
+	../misc/snmp_verbosity.hrl
+
+$(EBIN)/snmpa_get.$(EMULATOR): \
+	snmpa_get_mechanism.erl \
+	snmpa_get.erl \
+	../misc/snmp_verbosity.hrl
+
+$(EBIN)/snmpa_get_lib.$(EMULATOR): \
+	snmpa_get_lib.erl \
+	../misc/snmp_verbosity.hrl
+
 $(EBIN)/snmpa_local_db.$(EMULATOR): \
 	snmpa_local_db.erl \
 	../misc/snmp_debug.hrl \
diff --git a/lib/snmp/src/agent/modules.mk b/lib/snmp/src/agent/modules.mk
index d47ee34d98..49cc158c2e 100644
--- a/lib/snmp/src/agent/modules.mk
+++ b/lib/snmp/src/agent/modules.mk
@@ -59,6 +59,8 @@ MODULES = \
 	snmpa_error \
 	snmpa_error_io \
 	snmpa_error_logger \
+	snmpa_get \
+	snmpa_get_lib \
 	snmpa_local_db \
 	snmpa_mib_storage_ets \
 	snmpa_mib_storage_dets \
diff --git a/lib/snmp/src/agent/snmpa_agent.erl b/lib/snmp/src/agent/snmpa_agent.erl
index 458b88359b..f75c4cfee0 100644
--- a/lib/snmp/src/agent/snmpa_agent.erl
+++ b/lib/snmp/src/agent/snmpa_agent.erl
@@ -28,7 +28,8 @@
 
 %% External exports
 -export([start_link/4, start_link/5, stop/1]).
--export([subagent_set/2, 
+-export([subagent_get/3, subagent_get_next/3,
+         subagent_set/2, 
 	 load_mibs/3, unload_mibs/3, 
 	 which_mibs/1, whereis_mib/2, info/1,
 	 register_subagent/3, unregister_subagent/2,
@@ -362,12 +363,19 @@ do_init(Prio, Parent, Ref, Options) ->
 	  "~n   Options: ~p",[Prio, Parent, Ref, Options]),
 
     Mibs       = get_mibs(Options),
+
     SetModule  = get_set_mechanism(Options),
     put(set_module, SetModule),
+    ?vtrace("set-module: ~w", [SetModule]),
+
+    GetModule  = get_get_mechanism(Options),
+    put(get_module, GetModule),
+    ?vtrace("get-module: ~w", [GetModule]),
 
     %% OTP-3324. For AXD301.
     AuthModule = get_authentication_service(Options),
     put(auth_module, AuthModule),
+    ?vtrace("auth-module: ~w", [AuthModule]),
 
     MultiT  = get_multi_threaded(Options),
     Vsns    = get_versions(Options),
@@ -1133,7 +1141,7 @@ handle_call({subagent_get_next, MibView, Varbinds, PduData}, _From, S) ->
 	  "~n   PduData:  ~p", 
 	  [MibView,Varbinds,PduData]),
     put_pdu_data(PduData),
-    {reply, do_get_next(MibView, Varbinds, infinity), S};
+    {reply, do_get_next(MibView, Varbinds), S};
 handle_call({subagent_set, Arguments, PduData}, _From, S) ->
     ?vlog("[handle_call] subagent set:"
 	  "~n   Arguments: ~p"
@@ -1174,7 +1182,7 @@ handle_call({get_next, Vars, Context}, _From, S) ->
             ?vdebug("Varbinds: ~p",[Varbinds]),
             MibView = snmpa_acm:get_root_mib_view(),
             Reply =
-                case do_get_next(MibView, Varbinds, infinity) of
+                case do_get_next(MibView, Varbinds) of
                     {noError, 0, NewVarbinds} ->
                         Vbs = lists:keysort(#varbind.org_index, NewVarbinds),
 			[{Oid,Val} || #varbind{oid = Oid, value = Val} <- Vbs];
@@ -2559,7 +2567,7 @@ process_pdu(#pdu{type = 'get-next-request', request_id = ReqId, varbinds = Vbs},
 	    "~n   ReqId:   ~p"
 	    "~n   Vbs:     ~p"
 	    "~n   MibView: ~p",[ReqId, Vbs, MibView]),
-    Res = get_err(do_get_next(MibView, Vbs, infinity)),
+    Res = get_err(do_get_next(MibView, Vbs)),
     ?vtrace("get-next result: "
 	    "~n   ~p",[Res]),
     {ErrStatus, ErrIndex, ResVarbinds} = 
@@ -2650,8 +2658,7 @@ validate_next_v1_2([Vb | _Vbs], _MibView, _Res)
     {noSuchName, Vb#varbind.org_index};
 validate_next_v1_2([Vb | Vbs], MibView, Res)
   when Vb#varbind.variabletype =:= 'Counter64' ->
-    case validate_next_v1(
-	   do_get_next(MibView, [mk_next_oid(Vb)], infinity), MibView) of
+    case validate_next_v1( do_get_next(MibView, [mk_next_oid(Vb)]), MibView) of
 	{noError, 0, [NVb]} ->
 	    validate_next_v1_2(Vbs, MibView, [NVb | Res]);
 	{Error, Index, _OrgVb} ->
@@ -2692,6 +2699,19 @@ mk_next_oid(Vb) ->
 %%%   used, and thus a genErr will be returned anyway.
 %%%-----------------------------------------------------------------
 
+%%-----------------------------------------------------------------
+%% Func: do_get/2
+%% Purpose: Handles all VBs in a request that is inside the 
+%%          mibview (local).
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get(UnsortedVarbinds, IsNotification) ->
+    GetModule = get(get_module),
+    GetModule:do_get(UnsortedVarbinds, IsNotification).
+    
+
 %%-----------------------------------------------------------------
 %% Func: do_get/3
 %% Purpose: do_get handles "getRequests".
@@ -2700,390 +2720,23 @@ mk_next_oid(Vb) ->
 %%          {ErrorStatus, ErrorIndex, []}
 %%-----------------------------------------------------------------
 
-%% If this function is called from a worker-process, we *may* 
-%% need to tunnel into the master-agent and let it do the 
-%% work
+%% If this function is called from a worker-process (or other process),
+%% we *may* need to tunnel into the master-agent and let it do the work.
 
 do_get(MibView, UnsortedVarbinds, IsNotification) ->
-    do_get(MibView, UnsortedVarbinds, IsNotification, false).
+    GetModule = get(get_module),
+    GetModule:do_get(MibView, UnsortedVarbinds, IsNotification).
 
 do_get(MibView, UnsortedVarbinds, IsNotification, ForceMaster) ->
-    ?vtrace("do_get -> entry with"
-	    "~n   MibView:          ~p"
-	    "~n   UnsortedVarbinds: ~p"
-	    "~n   IsNotification:   ~p", 
-	    [MibView, UnsortedVarbinds, IsNotification]),
     case (whereis(snmp_master_agent) =:= self()) of
 	false when (ForceMaster =:= true) ->
-	    %% I am a lowly worker process, handoff to the master agent
 	    PduData = get_pdu_data(), 
 	    call(snmp_master_agent, 
 		 {do_get, MibView, UnsortedVarbinds, IsNotification, PduData});
-
-	_ ->
-	    %% This is me, the master, so go ahead
-	    {OutSideView, InSideView} = 
-		split_vbs_view(UnsortedVarbinds, MibView),
-	    {Error, Index, NewVbs} = 
-		do_get(InSideView, IsNotification),
-	    {Error, Index, NewVbs ++ OutSideView}
-
-    end.
-
-
-split_vbs_view(Vbs, MibView) ->
-    ?vtrace("split the varbinds view", []),
-    split_vbs_view(Vbs, MibView, [], []).
-
-split_vbs_view([Vb | Vbs], MibView, Out, In) ->
-    case snmpa_acm:validate_mib_view(Vb#varbind.oid, MibView) of
-	true -> split_vbs_view(Vbs, MibView, Out, [Vb | In]);
-	false -> split_vbs_view(Vbs, MibView,
-				[Vb#varbind{value = noSuchObject} | Out], In)
-    end;
-split_vbs_view([], _MibView, Out, In) ->
-    {Out, In}.
-	    
-do_get(UnsortedVarbinds, IsNotification) ->
-    {MyVarbinds, SubagentVarbinds} = sort_varbindlist(UnsortedVarbinds),
-    case do_get_local(MyVarbinds, [], IsNotification) of
-	{noError, 0, NewMyVarbinds} ->
-	    case do_get_subagents(SubagentVarbinds, IsNotification) of
-		{noError, 0, NewSubagentVarbinds} ->
-		    {noError, 0, NewMyVarbinds ++ NewSubagentVarbinds};
-		{ErrorStatus, ErrorIndex, _} ->
-		    {ErrorStatus, ErrorIndex, []}
-	    end;
-	{ErrorStatus, ErrorIndex, _} -> 
-	    {ErrorStatus, ErrorIndex, []}
-    end.
-
-%%-----------------------------------------------------------------
-%% Func: do_get_local/3
-%% Purpose: Loop the variablebindings list. We know that each varbind
-%%          in that list belongs to us.
-%% Returns: {noError, 0, ListOfNewVarbinds} |
-%%          {ErrorStatus, ErrorIndex, []}
-%%-----------------------------------------------------------------
-do_get_local([Vb | Vbs], Res, IsNotification) ->
-    case try_get(Vb, IsNotification) of
-	NewVb when is_record(NewVb, varbind) ->
-	    do_get_local(Vbs, [NewVb | Res], IsNotification);
-	ListOfNewVb when is_list(ListOfNewVb) ->
-	    do_get_local(Vbs, lists:append(ListOfNewVb, Res), IsNotification);
-	{error, Error, OrgIndex} ->
-	    {Error, OrgIndex, []}
-    end;
-do_get_local([], Res, _IsNotification) -> 
-    {noError, 0, Res}.
-
-%%-----------------------------------------------------------------
-%% Func: do_get_subagents/2
-%% Purpose: Loop the list of varbinds for different subagents.
-%%          For each of them, call sub_agent_get to retreive
-%%          the values for them.
-%% Returns: {noError, 0, ListOfNewVarbinds} |
-%%          {ErrorStatus, ErrorIndex, []}
-%%-----------------------------------------------------------------
-do_get_subagents(SubagentVarbinds, IsNotification) ->
-    do_get_subagents(SubagentVarbinds, [], IsNotification).
-do_get_subagents([{SubAgentPid, SAVbs} | Tail], Res, IsNotification) ->
-    {_SAOids, Vbs} = sa_split(SAVbs),
-    case catch subagent_get(SubAgentPid, Vbs, IsNotification) of
-	{noError, 0, NewVbs} ->
-	    do_get_subagents(Tail, lists:append(NewVbs, Res), IsNotification);
-	{ErrorStatus, ErrorIndex, _} ->
-	    {ErrorStatus, ErrorIndex, []};
-	{'EXIT', Reason} ->
-	    user_err("Lost contact with subagent (get) ~w. Using genErr", 
-		     [Reason]),
-	    {genErr, 0, []} 
-    end;
-do_get_subagents([], Res, _IsNotification) ->
-    {noError, 0, Res}.
-
-
-%%-----------------------------------------------------------------
-%% Func: try_get/2
-%% Returns: {error, ErrorStatus, OrgIndex} |
-%%          #varbind |
-%%          List of #varbind
-%%-----------------------------------------------------------------
-try_get(IVb, IsNotification) when is_record(IVb, ivarbind) ->
-    ?vtrace("try_get(ivarbind) -> entry with"
-	    "~n   IVb: ~p", [IVb]),
-    get_var_value_from_ivb(IVb, IsNotification);
-try_get({TableOid, TableVbs}, IsNotification) ->
-    ?vtrace("try_get(table) -> entry with"
-	    "~n   TableOid: ~p"
-	    "~n   TableVbs: ~p", [TableOid, TableVbs]),
-    [#ivarbind{mibentry = MibEntry}|_] = TableVbs,
-    {NoAccessVbs, AccessVbs} =
-	check_all_table_vbs(TableVbs, IsNotification, [], []),
-    case get_tab_value_from_mib(MibEntry, TableOid, AccessVbs) of
-	{error, ErrorStatus, OrgIndex} ->
-	    {error, ErrorStatus, OrgIndex};
-	NVbs ->
-	    NVbs ++ NoAccessVbs
-    end.
-
-%%-----------------------------------------------------------------
-%% Make sure all requested columns are accessible.
-%%-----------------------------------------------------------------
-check_all_table_vbs([IVb| IVbs], IsNotification, NoA, A) ->
-    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
-    case Me#me.access of
-	'not-accessible' -> 
-	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
-	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
-	'accessible-for-notify' when IsNotification =:= false -> 
-	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
-	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
-	'write-only' -> 
-	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
-	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
-	_ ->
-	    check_all_table_vbs(IVbs, IsNotification, NoA, [IVb | A])
-    end;
-check_all_table_vbs([], _IsNotification, NoA, A) -> {NoA, A}.
-
-%%-----------------------------------------------------------------
-%% Returns: {error, ErrorStatus, OrgIndex} |
-%%          #varbind
-%%-----------------------------------------------------------------
-get_var_value_from_ivb(IVb, IsNotification)
-  when IVb#ivarbind.status =:= noError ->
-    ?vtrace("get_var_value_from_ivb(noError) -> entry", []),
-    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
-    #varbind{org_index = OrgIndex, oid = Oid} = Vb,
-    case Me#me.access of
-	'not-accessible' -> 
-	    Vb#varbind{value = noSuchInstance};
-	'accessible-for-notify' when IsNotification =:= false -> 
-	    Vb#varbind{value = noSuchInstance};
-	'write-only' -> 
-	    Vb#varbind{value = noSuchInstance};
-	_ -> 
-	    case get_var_value_from_mib(Me, Oid) of
-		{value, Type, Value} ->
-		    Vb#varbind{variabletype = Type, value = Value};
-		{error, ErrorStatus} ->
-		    {error, ErrorStatus, OrgIndex}
-	    end
-    end;
-get_var_value_from_ivb(#ivarbind{status = Status, varbind = Vb}, _) ->
-    ?vtrace("get_var_value_from_ivb(~p) -> entry", [Status]),
-    Vb#varbind{value = Status}.
-
-%%-----------------------------------------------------------------
-%% Func: get_var_value_from_mib/1
-%% Purpose: 
-%% Returns: {error, ErrorStatus} |
-%%          {value, Type, Value}
-%%-----------------------------------------------------------------
-%% Pre: Oid is a correct instance Oid (lookup checked that).
-%% Returns: A correct return value (see make_value_a_correct_value)
-get_var_value_from_mib(#me{entrytype = variable,
-			   asn1_type = ASN1Type,
-			   mfa       = {Mod, Func, Args}},
-		       _Oid) ->
-    ?vtrace("get_var_value_from_mib(variable) -> entry when"
-	    "~n   Mod:  ~p"
-	    "~n   Func: ~p"
-	    "~n   Args: ~p", [Mod, Func, Args]),
-    Result = (catch dbg_apply(Mod, Func, [get | Args])),
-    % mib shall return {value, <a-nice-value-within-range>} |
-    % {noValue, noSuchName} (v1) | 
-    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
-    % everything else (including 'genErr') will generate 'genErr'.
-    make_value_a_correct_value(Result, ASN1Type, {Mod, Func, Args});
-
-get_var_value_from_mib(#me{entrytype = table_column,
-			   oid       = MeOid,
-			   asn1_type = ASN1Type,
-			   mfa       = {Mod, Func, Args}},
-		       Oid) ->
-    ?vtrace("get_var_value_from_mib(table_column) -> entry when"
-	    "~n   MeOid: ~p"
-	    "~n   Mod:   ~p"
-	    "~n   Func:  ~p"
-	    "~n   Args:  ~p"
-	    "~n   Oid:   ~p", [MeOid, Mod, Func, Args, Oid]),
-    Col = lists:last(MeOid),
-    Indexes = snmp_misc:diff(Oid, MeOid),
-    [Result] = (catch dbg_apply(Mod, Func, [get, Indexes, [Col] | Args])),
-    make_value_a_correct_value(Result, ASN1Type, 
-			       {Mod, Func, Args, Indexes, Col}).
-
-
-%% For table operations we need to pass RestOid down to the table-function.
-%% Its up to the table-function to check for noSuchInstance (ex: a 
-%% non-existing row).
-%% Returns: {error, ErrorStatus, OrgIndex} |
-%%          {value, Type, Value}
-get_tab_value_from_mib(#me{mfa = {Mod, Func, Args}}, TableOid, TableVbs) ->
-    ?vtrace("get_tab_value_from_mib -> entry when"
-	    "~n   Mod:  ~p"
-	    "~n   Func: ~p"
-	    "~n   Args: ~p", [Mod, Func, Args]),
-    TableOpsWithShortOids = deletePrefixes(TableOid, TableVbs),
-    SortedVBsRows = snmpa_svbl:sort_varbinds_rows(TableOpsWithShortOids), 
-    case get_value_all_rows(SortedVBsRows, Mod, Func, Args, []) of
-	{Error, Index} ->
-	    #ivarbind{varbind = Vb} = lists:nth(Index, TableVbs),
-	    {error, Error, Vb#varbind.org_index};
-	ListOfValues -> 
-	    merge_varbinds_and_value(TableVbs, ListOfValues)
+        _ ->
+            do_get(MibView, UnsortedVarbinds, IsNotification)
     end.
 
-%%-----------------------------------------------------------------
-%% Values is a scrambled list of {CorrectValue, Index}, where Index
-%% is index into the #ivarbind list. So for each Value, we must
-%% find the corresponding #ivarbind, and merge them into a new
-%% #varbind.
-%% The Values list comes from validate_tab_res.
-%%-----------------------------------------------------------------
-merge_varbinds_and_value(IVbs, [{{value, Type, Value}, Index} | Values]) ->
-    #ivarbind{varbind = Vb} = lists:nth(Index, IVbs),
-    [Vb#varbind{variabletype = Type, value = Value} |
-     merge_varbinds_and_value(IVbs, Values)];
-merge_varbinds_and_value(_, []) -> [].
-    
-get_value_all_rows([{[], OrgCols} | Rows], Mod, Func, Args, Res) ->
-    ?vtrace("get_value_all_rows -> entry when"
-	    "~n   OrgCols: ~p", [OrgCols]),
-    Cols   = [{{value, noValue, noSuchInstance}, Index} || 
-		 {_Col, _ASN1Type, Index} <- OrgCols], 
-    NewRes = lists:append(Cols, Res),
-    get_value_all_rows(Rows, Mod, Func, Args, NewRes);
-get_value_all_rows([{RowIndex, OrgCols} | Rows], Mod, Func, Args, Res) ->
-    ?vtrace("get_value_all_rows -> entry when"
-	    "~n   RowIndex: ~p"
-	    "~n   OrgCols:  ~p", [RowIndex, OrgCols]),
-    {DOrgCols, Dup} = remove_duplicates(OrgCols),
-    Cols   = delete_index(DOrgCols),
-    Result = (catch dbg_apply(Mod, Func, [get, RowIndex, Cols | Args])),
-    case validate_tab_res(Result, DOrgCols, {Mod, Func, Args}) of
-	Values when is_list(Values) ->
-	    NVals  = restore_duplicates(Dup, Values),
-	    NewRes = lists:append(NVals, Res),
-	    get_value_all_rows(Rows, Mod, Func, Args, NewRes);
-	{error, ErrorStatus, Index} ->
-	    validate_err(row_set, {ErrorStatus, Index}, {Mod, Func, Args})
-    end;
-get_value_all_rows([], _Mod, _Func, _Args, Res) -> 
-    ?vtrace("get_value_all_rows -> entry when done"
-	    "~n   Res: ~p", [Res]),
-    Res.
-
-%%-----------------------------------------------------------------
-%% Returns: list of {ShortOid, ASN1TYpe}
-%%-----------------------------------------------------------------
-deletePrefixes(Prefix, [#ivarbind{varbind = Varbind, mibentry = ME} | Vbs]) ->
-    #varbind{oid = Oid} = Varbind,
-    [{snmp_misc:diff(Oid, Prefix), ME#me.asn1_type} |
-     deletePrefixes(Prefix, Vbs)];
-deletePrefixes(_Prefix, []) -> [].
-
-%%-----------------------------------------------------------------
-%% Args: {RowIndex, list of {ShortOid, ASN1Type}}
-%% Returns: list of Col
-%%-----------------------------------------------------------------
-delete_index([{Col, _Val, _OrgIndex} | T]) ->
-    [Col | delete_index(T)];
-delete_index([]) -> [].
-
-%%-----------------------------------------------------------------
-%% This function is called before 'get' on a table, and removes
-%% any duplicate columns.  It returns {Cols, DupInfo}.  The Cols
-%% are the unique columns.  The instrumentation function is
-%% called to get the values.  These values, together with the
-%% DupInfo, is later passed to restore_duplicates, which uses
-%% the retrieved values to reconstruct the original column list,
-%% but with the retrieved value for each column.
-%%-----------------------------------------------------------------
-remove_duplicates(Cols) ->
-    remove_duplicates(Cols, [], []).
-
-
-remove_duplicates([{Col, V1, OrgIdx1}, {Col, V2, OrgIdx2} | T], NCols, Dup) ->
-    remove_duplicates([{Col, V1, OrgIdx1} | T], NCols, 
-		      [{Col, V2, OrgIdx2} | Dup]);
-remove_duplicates([Col | T], NCols, Dup) ->
-    remove_duplicates(T, [Col | NCols], Dup);
-remove_duplicates([], NCols, Dup) ->
-    {lists:reverse(NCols), lists:reverse(Dup)}.
-
-restore_duplicates([], Cols) ->
-    [{Val, OrgIndex} || {_Col, Val, OrgIndex} <- Cols];
-restore_duplicates([{Col, _Val2, OrgIndex2} | Dup],
-		   [{Col, NVal, OrgIndex1} | Cols]) ->
-    [{NVal, OrgIndex2} |
-     restore_duplicates(Dup, [{Col, NVal, OrgIndex1} | Cols])];
-restore_duplicates(Dup, [{_Col, Val, OrgIndex} | T]) ->
-    [{Val, OrgIndex} | restore_duplicates(Dup, T)].
-
-%% Maps the column number to Index.
-% col_to_index(0, _) -> 0;
-% col_to_index(Col, [{Col, _, Index}|_]) ->
-%     Index;
-% col_to_index(Col, [_|Cols]) ->
-%     col_to_index(Col, Cols).
-
-%%-----------------------------------------------------------------
-%% Three cases:
-%%   1) All values ok
-%%   2) table_func returned {Error, ...}
-%%   3) Some value in Values list is erroneous.
-%% Args: Value is a list of values from table_func(get..)
-%%       OrgCols is a list with {Col, ASN1Type, OrgIndex} 
-%%         each element in Values and OrgCols correspond to each
-%%         other.
-%%-----------------------------------------------------------------
-validate_tab_res(Values, OrgCols, Mfa) when is_list(Values) ->
-    {_Col, _ASN1Type, OneIdx} = hd(OrgCols),
-    validate_tab_res(Values, OrgCols, Mfa, [], OneIdx);
-validate_tab_res({noValue, Error}, OrgCols, Mfa) ->
-    Values = lists:duplicate(length(OrgCols), {noValue, Error}),
-    validate_tab_res(Values, OrgCols, Mfa);
-validate_tab_res({genErr, Col}, OrgCols, Mfa) ->
-    case lists:keysearch(Col, 1, OrgCols) of
-	{value, {_Col, _ASN1Type, Index}} ->
-	    {error, genErr, Index};
-	_ ->
-	    user_err("Invalid column in {genErr, ~w} from ~w (get)",
-		     [Col, Mfa]),
-	    [{_Col, _ASN1Type, Index} | _] = OrgCols,
-	    {error, genErr, Index}
-    end;
-validate_tab_res(genErr, [{_Col, __ASN1Type, Index} | _OrgCols], _Mfa) ->
-    {error, genErr, Index};
-validate_tab_res(Error, [{_Col, _ASN1Type, Index} | _OrgCols], Mfa) ->
-    user_err("Invalid return value ~w from ~w (get)",[Error, Mfa]),
-    {error, genErr, Index}.
-
-validate_tab_res([Value | Values], 
-		 [{Col, ASN1Type, Index} | OrgCols],
-		 Mfa, Res, I) ->
-    %% This one makes it possible to return a list of genErr, which
-    %% is not allowed according to the manual.  But that's ok, as
-    %% everything else will generate a genErr! (the only problem is
-    %% that it won't generate a user_error).
-    case make_value_a_correct_value(Value, ASN1Type, Mfa) of
-	{error, ErrorStatus} ->
-	    {error, ErrorStatus, Index};
-	CorrectValue ->
-	    NewRes = [{Col, CorrectValue, Index} | Res],
-	    validate_tab_res(Values, OrgCols, Mfa, NewRes, I)
-    end;
-validate_tab_res([], [], _Mfa, Res, _I) -> 
-    lists:reverse(Res);
-validate_tab_res([], [{_Col, _ASN1Type, Index}|_], Mfa, _Res, _I) ->
-    user_err("Too few values returned from ~w (get)", [Mfa]),
-    {error, genErr, Index};
-validate_tab_res(_TooMany, [], Mfa, _Res, I) ->
-    user_err("Too many values returned from ~w (get)", [Mfa]),
-    {error, genErr, I}.
 
 
 %%%-----------------------------------------------------------------
@@ -3125,491 +2778,11 @@ validate_tab_res(_TooMany, [], Mfa, _Res, I) ->
 %%      subagent must be considered to be very rare.
 %%-----------------------------------------------------------------
 
-%% It may be a bit agressive to check this already, 
-%% but since it is a security measure, it makes sense.
-do_get_next(_MibView, UnsortedVarbinds, GbMaxVBs) 
-  when (is_integer(GbMaxVBs) andalso (length(UnsortedVarbinds) > GbMaxVBs)) ->
-    {tooBig, 0, []}; % What is the correct index in this case?
-do_get_next(MibView, UnsortedVBs, GbMaxVBs) ->
-    ?vt("do_get_next -> entry when"
- 	"~n   MibView:          ~p"
- 	"~n   UnsortedVBs: ~p", [MibView, UnsortedVBs]),
-    SortedVBs = oid_sort_vbs(UnsortedVBs),
-    ?vt("do_get_next -> "
- 	"~n   SortedVBs: ~p", [SortedVBs]),
-    next_loop_varbinds([], SortedVBs, MibView, [], [], GbMaxVBs).
-
-oid_sort_vbs(Vbs) ->
-    lists:keysort(#varbind.oid, Vbs).
-
-next_loop_varbinds(_, Vbs, _MibView, Res, _LAVb, GbMaxVBs) 
-  when (is_integer(GbMaxVBs) andalso 
-	((length(Vbs) + length(Res)) > GbMaxVBs)) ->
-    {tooBig, 0, []}; % What is the correct index in this case?
-
-%% LAVb is Last Accessible Vb
-next_loop_varbinds([], [Vb | Vbs], MibView, Res, LAVb, GbMaxVBs) ->
-    ?vt("next_loop_varbinds -> entry when"
- 	"~n   Vb:      ~p"
- 	"~n   MibView: ~p", [Vb, MibView]),
-    case varbind_next(Vb, MibView) of
-	endOfMibView ->
-	    ?vt("next_loop_varbind -> endOfMibView", []),
-	    RVb = if LAVb =:= [] -> Vb;
-		     true -> LAVb
-		  end,
-	    NewVb = RVb#varbind{variabletype = 'NULL', value = endOfMibView},
-	    next_loop_varbinds([], Vbs, MibView, [NewVb | Res], [], GbMaxVBs);
-
-	{variable, ME, VarOid} when ((ME#me.access =/= 'not-accessible') andalso 
-				     (ME#me.access =/= 'write-only') andalso 
-				     (ME#me.access =/= 'accessible-for-notify')) -> 
-	    ?vt("next_loop_varbind -> variable: "
-		"~n   ME:     ~p"
-		"~n   VarOid: ~p", [ME, VarOid]),
-	    case try_get_instance(Vb, ME) of
-		{value, noValue, _NoSuchSomething} ->
-		    ?vt("next_loop_varbind -> noValue", []),
-		    %% Try next one
-		    NewVb = Vb#varbind{oid   = VarOid, 
-				       value = 'NULL'},
-		    next_loop_varbinds([], [NewVb | Vbs], MibView, Res, [], 
-				       GbMaxVBs);
-		{value, Type, Value} ->
-		    ?vt("next_loop_varbind -> value"
-			"~n   Type:  ~p"
-			"~n   Value: ~p", [Type, Value]),
-		    NewVb = Vb#varbind{oid          = VarOid, 
-				       variabletype = Type,
-				       value        = Value},
-		    next_loop_varbinds([], Vbs, MibView, [NewVb | Res], [],
-				       GbMaxVBs);
-		{error, ErrorStatus} ->
-		    ?vdebug("next loop varbinds:"
-			    "~n   ErrorStatus: ~p",[ErrorStatus]),
-		    {ErrorStatus, Vb#varbind.org_index, []}
-	    end;
-	{variable, _ME, VarOid} -> 
-	    ?vt("next_loop_varbind -> variable: "
-		"~n   VarOid: ~p", [VarOid]),
-	    RVb = if LAVb =:= [] -> Vb;
-		     true -> LAVb
-		  end,
-	    NewVb = Vb#varbind{oid = VarOid, value = 'NULL'},
-	    next_loop_varbinds([], [NewVb | Vbs], MibView, Res, RVb, GbMaxVBs);
-	{table, TableOid, TableRestOid, ME} ->
-	    ?vt("next_loop_varbind -> table: "
-		"~n   TableOid:     ~p"
-		"~n   TableRestOid: ~p"
-		"~n   ME:           ~p", [TableOid, TableRestOid, ME]),
-	    next_loop_varbinds({table, TableOid, ME,
-				[{tab_oid(TableRestOid), Vb}]},
-			       Vbs, MibView, Res, [], GbMaxVBs);
-	{subagent, SubAgentPid, SAOid} ->
-	    ?vt("next_loop_varbind -> subagent: "
-		"~n   SubAgentPid: ~p"
-		"~n   SAOid:       ~p", [SubAgentPid, SAOid]),
-	    NewVb = Vb#varbind{variabletype = 'NULL', value = 'NULL'},
-	    next_loop_varbinds({subagent, SubAgentPid, SAOid, [NewVb]},
-			       Vbs, MibView, Res, [], GbMaxVBs)
-    end;
-next_loop_varbinds({table, TableOid, ME, TabOids},
-		   [Vb | Vbs], MibView, Res, _LAVb, GbMaxVBs) ->
-    ?vt("next_loop_varbinds(table) -> entry with"
- 	"~n   TableOid: ~p"
- 	"~n   Vb:       ~p", [TableOid, Vb]),
-    case varbind_next(Vb, MibView) of
-	{table, TableOid, TableRestOid, _ME} ->
-	    next_loop_varbinds({table, TableOid, ME,
-				[{tab_oid(TableRestOid), Vb} | TabOids]},
-			       Vbs, MibView, Res, [], GbMaxVBs);
-	_ ->
-	    case get_next_table(ME, TableOid, TabOids, MibView) of
-		{ok, TabRes, TabEndOfTabVbs} ->
-		    NewVbs = lists:append(TabEndOfTabVbs, [Vb | Vbs]),
-		    NewRes = lists:append(TabRes, Res),
-		    next_loop_varbinds([], NewVbs, MibView, NewRes, [], 
-				       GbMaxVBs);
-		{ErrorStatus, OrgIndex} ->
-		    ?vdebug("next loop varbinds: next varbind"
-			    "~n   ErrorStatus: ~p"
-			    "~n   OrgIndex:    ~p",
-			    [ErrorStatus,OrgIndex]),
-		    {ErrorStatus, OrgIndex, []}
-	    end
-    end;
-next_loop_varbinds({table, TableOid, ME, TabOids},
-		   [], MibView, Res, _LAVb, GbMaxVBs) ->
-    ?vt("next_loop_varbinds(table) -> entry with"
-	"~n   TableOid: ~p", [TableOid]),
-    case get_next_table(ME, TableOid, TabOids, MibView) of
-	{ok, TabRes, TabEndOfTabVbs} ->
- 	    ?vt("next_loop_varbinds(table) -> get_next_table result:"
-		"~n   TabRes:         ~p"
-		"~n   TabEndOfTabVbs: ~p", [TabRes, TabEndOfTabVbs]),
-	    NewRes = lists:append(TabRes, Res),
-	    next_loop_varbinds([], TabEndOfTabVbs, MibView, NewRes, [], 
-			       GbMaxVBs);
-	{ErrorStatus, OrgIndex} ->
-	    ?vdebug("next loop varbinds: next table"
-		    "~n   ErrorStatus: ~p"
-		    "~n   OrgIndex:    ~p",
-		    [ErrorStatus,OrgIndex]),
-	    {ErrorStatus, OrgIndex, []}
-    end;
-next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
-		   [Vb | Vbs], MibView, Res, _LAVb, GbMaxVBs) ->
-    ?vt("next_loop_varbinds(subagent) -> entry with"
-	"~n   SAPid: ~p"
-	"~n   SAOid: ~p"
- 	"~n   Vb:    ~p", [SAPid, SAOid, Vb]),
-    case varbind_next(Vb, MibView) of
-	{subagent, _SubAgentPid, SAOid} ->
-	    next_loop_varbinds({subagent, SAPid, SAOid,
-				[Vb | SAVbs]},
-			       Vbs, MibView, Res, [], GbMaxVBs);
-	_ ->
-	    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
-		{ok, SARes, SAEndOfMibViewVbs} ->
-		    NewVbs = lists:append(SAEndOfMibViewVbs, [Vb | Vbs]),
-		    NewRes = lists:append(SARes, Res),
-		    next_loop_varbinds([], NewVbs, MibView, NewRes, [], 
-				       GbMaxVBs);
-		{noSuchName, OrgIndex} ->
-		    %% v1 reply, treat this Vb as endOfMibView, and try again
-		    %% for the others.
-		    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
-			{value, EVb} ->
-			    NextOid = next_oid(SAOid),
-			    EndOfVb = 
-				EVb#varbind{oid = NextOid,
-					    value = {endOfMibView, NextOid}},
-			    case lists:delete(EVb, SAVbs) of
-				[] ->
-				    next_loop_varbinds([], [EndOfVb, Vb | Vbs],
-						       MibView, Res, [],
-						       GbMaxVBs);
-				TryAgainVbs ->
-				    next_loop_varbinds({subagent, SAPid, SAOid,
-							TryAgainVbs},
-						       [EndOfVb, Vb | Vbs],
-						       MibView, Res, [],
-						       GbMaxVBs)
-			    end;
-			false ->
-			    %% bad index from subagent
-			    {genErr, (hd(SAVbs))#varbind.org_index, []}
-		    end;
-		{ErrorStatus, OrgIndex} ->
- 		    ?vdebug("next loop varbinds: next subagent"
- 			    "~n   Vb:          ~p"
- 			    "~n   ErrorStatus: ~p"
- 			    "~n   OrgIndex:    ~p",
- 			    [Vb,ErrorStatus,OrgIndex]),
-		    {ErrorStatus, OrgIndex, []}
-	    end
-    end;
-next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
-		   [], MibView, Res, _LAVb, GbMaxVBs) ->
-     ?vt("next_loop_varbinds(subagent) -> entry with"
-	 "~n   SAPid: ~p"
-	 "~n   SAOid: ~p", [SAPid, SAOid]),
-    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
-	{ok, SARes, SAEndOfMibViewVbs} ->
-	    NewRes = lists:append(SARes, Res),
-	    next_loop_varbinds([], SAEndOfMibViewVbs, MibView, NewRes, [],
-			       GbMaxVBs);
-	{noSuchName, OrgIndex} ->
-	    %% v1 reply, treat this Vb as endOfMibView, and try again for
-	    %% the others.
-	    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
-		{value, EVb} ->
-		    NextOid = next_oid(SAOid),
-		    EndOfVb = EVb#varbind{oid = NextOid,
-					  value = {endOfMibView, NextOid}},
-		    case lists:delete(EVb, SAVbs) of
-			[] ->
-			    next_loop_varbinds([], [EndOfVb], MibView, Res, [],
-					       GbMaxVBs);
-			TryAgainVbs ->
-			    next_loop_varbinds({subagent, SAPid, SAOid,
-						TryAgainVbs},
-					       [EndOfVb], MibView, Res, [],
-					       GbMaxVBs)
-		    end;
-		false ->
-		    %% bad index from subagent
-		    {genErr, (hd(SAVbs))#varbind.org_index, []}
-	    end;
-	{ErrorStatus, OrgIndex} ->
- 	    ?vdebug("next loop varbinds: next subagent"
- 		    "~n   ErrorStatus: ~p"
- 		    "~n   OrgIndex:    ~p",
- 		    [ErrorStatus,OrgIndex]),
- 	    {ErrorStatus, OrgIndex, []}
-    end;
-next_loop_varbinds([], [], _MibView, Res, _LAVb, _GbMaxVBs) ->
-    ?vt("next_loop_varbinds -> entry when done", []),
-    {noError, 0, Res}.
-
-try_get_instance(_Vb, #me{mfa = {M, F, A}, asn1_type = ASN1Type}) ->
-    ?vtrace("try_get_instance -> entry with"
-	    "~n   M: ~p"
-	    "~n   F: ~p"
-	    "~n   A: ~p", [M,F,A]),
-    Result = (catch dbg_apply(M, F, [get | A])),
-    % mib shall return {value, <a-nice-value-within-range>} |
-    % {noValue, noSuchName} (v1) | 
-    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
-    % everything else (including 'genErr') will generate 'genErr'.
-    make_value_a_correct_value(Result, ASN1Type, {M, F, A}).
-
-tab_oid([]) -> [0];
-tab_oid(X) -> X.
-
-
-%%-----------------------------------------------------------------
-%% Perform a next, using the varbinds Oid if value is simple
-%% value. If value is {endOf<something>, NextOid}, use NextOid.
-%% This case happens when a table has returned endOfTable, or
-%% a subagent has returned endOfMibView.
-%%-----------------------------------------------------------------
-varbind_next(#varbind{value = Value, oid = Oid}, MibView) ->
-    ?vt("varbind_next -> entry with"
- 	"~n   Value:   ~p"
- 	"~n   Oid:     ~p"
- 	"~n   MibView: ~p", [Value, Oid, MibView]),
-    case Value of
-	{endOfTable, NextOid} ->
-	    snmpa_mib:next(get(mibserver), NextOid, MibView);
-	{endOfMibView, NextOid} ->
-	    snmpa_mib:next(get(mibserver), NextOid, MibView);
-	_ ->
-	    snmpa_mib:next(get(mibserver), Oid, MibView)
-    end.
-
-get_next_table(#me{mfa = {M, F, A}}, TableOid, TableOids, MibView) ->
-    % We know that all TableOids have at least a column number as oid
-    ?vt("get_next_table -> entry with"
-	"~n   M:         ~p"
-	"~n   F:         ~p"
-	"~n   A:         ~p"
-	"~n   TableOid:  ~p"
-	"~n   TableOids: ~p"
-	"~n   MibView:   ~p", [M, F, A, TableOid, TableOids, MibView]),
-    Sorted = snmpa_svbl:sort_varbinds_rows(TableOids),
-    case get_next_values_all_rows(Sorted, M,F,A, [], TableOid) of
-	NewVbs when is_list(NewVbs) ->
- 	    ?vt("get_next_table -> "
-		"~n   NewVbs: ~p", [NewVbs]),
-	    % We must now check each Vb for endOfTable and that it is
-	    % in the MibView. If not, it becomes a endOfTable. We 
-	    % collect all of these together.
-	    transform_tab_next_result(NewVbs, {[], []}, MibView);
-	{ErrorStatus, OrgIndex} ->
-	    {ErrorStatus, OrgIndex}
-    end.
-
-get_next_values_all_rows([Row | Rows], M, F, A, Res, TabOid) ->
-    {RowIndex, TableOids} = Row,
-    Cols = delete_index(TableOids),
-    ?vt("get_next_values_all_rows -> "
-	"~n   Cols: ~p", [Cols]),
-    Result = (catch dbg_apply(M, F, [get_next, RowIndex, Cols | A])),
-    ?vt("get_next_values_all_rows -> "
- 	"~n   Result: ~p", [Result]),
-    case validate_tab_next_res(Result, TableOids, {M, F, A}, TabOid) of
-	Values when is_list(Values) -> 
- 	    ?vt("get_next_values_all_rows -> "
- 		"~n   Values: ~p", [Values]),
-	    NewRes = lists:append(Values, Res),
-	    get_next_values_all_rows(Rows, M, F, A, NewRes, TabOid);
-	{ErrorStatus, OrgIndex} ->
-	    {ErrorStatus, OrgIndex}
-    end;
-get_next_values_all_rows([], _M, _F, _A, Res, _TabOid) ->
-    Res.
-
-transform_tab_next_result([Vb | Vbs], {Res, EndOfs}, MibView) ->
-    case Vb#varbind.value of
-	{endOfTable, _} ->
-%% 	    ?vtrace("transform_tab_next_result -> endOfTable: "
-%% 		"split varbinds",[]),
-%% 	    R = split_varbinds(Vbs, Res, [Vb | EndOfs]),
-%% 	    ?vtrace("transform_tab_next_result -> "
-%% 		"~n   R: ~p", [R]),
-%% 	    R;
-	    split_varbinds(Vbs, Res, [Vb | EndOfs]);
-	_ ->
-	    case snmpa_acm:validate_mib_view(Vb#varbind.oid, MibView) of
-		true ->
-		    transform_tab_next_result(Vbs, {[Vb|Res], EndOfs},MibView);
-		_ ->
-		    Oid = Vb#varbind.oid,
-		    NewEndOf = Vb#varbind{value = {endOfTable, Oid}},
-		    transform_tab_next_result(Vbs, {Res, [NewEndOf | EndOfs]},
-					      MibView)
-	    end
-    end;
-transform_tab_next_result([], {Res, EndOfs}, _MibView) ->
-    ?vt("transform_tab_next_result -> entry with: "
- 	"~n   Res:    ~p"
- 	"~n   EndIfs: ~p",[Res, EndOfs]),
-    {ok, Res, EndOfs}.
-
-%%-----------------------------------------------------------------
-%% Three cases:
-%%   1) All values ok
-%%   2) table_func returned {Error, ...}
-%%   3) Some value in Values list is erroneous.
-%% Args: Value is a list of values from table_func(get_next, ...)
-%%       TableOids is a list of {TabRestOid, OrgVb} 
-%%         each element in Values and TableOids correspond to each
-%%         other.
-%% Returns: List of NewVarbinds |
-%%          {ErrorStatus, OrgIndex}
-%%          (In the NewVarbinds list, the value may be endOfTable)
-%%-----------------------------------------------------------------
-validate_tab_next_res(Values, TableOids, Mfa, TabOid) ->
-     ?vt("validate_tab_next_res -> entry with: "
-	 "~n   Values:     ~p"
-	 "~n   TableOids:  ~p"
-	 "~n   Mfa:        ~p"
-	 "~n   TabOid:     ~p", [Values, TableOids, Mfa, TabOid]),
-    {_Col, _ASN1Type, OneIdx} = hd(TableOids),
-    validate_tab_next_res(Values, TableOids, Mfa, [], TabOid,
-			  next_oid(TabOid), OneIdx).
-validate_tab_next_res([{NextOid, Value} | Values],
-		      [{_ColNo, OrgVb, _Index} | TableOids],
-		      Mfa, Res, TabOid, TabNextOid, I) ->
-    ?vt("validate_tab_next_res -> entry with: "
- 	"~n   NextOid:    ~p"
- 	"~n   Value:      ~p"
- 	"~n   Values:     ~p"
- 	"~n   TableOids:  ~p"
- 	"~n   Mfa:        ~p"
- 	"~n   TabOid:     ~p", 
- 	[NextOid, Value, Values, TableOids, Mfa, TabOid]),
-    #varbind{org_index = OrgIndex} = OrgVb,
-    ?vt("validate_tab_next_res -> OrgIndex: ~p", [OrgIndex]),
-    NextCompleteOid = lists:append(TabOid, NextOid),
-    case snmpa_mib:lookup(get(mibserver), NextCompleteOid) of
-	{table_column, #me{asn1_type = ASN1Type}, _TableEntryOid} ->
-  	    ?vt("validate_tab_next_res -> ASN1Type: ~p", [ASN1Type]),
-	    case make_value_a_correct_value({value, Value}, ASN1Type, Mfa) of
-		{error, ErrorStatus} ->
- 		    ?vt("validate_tab_next_res -> "
- 			"~n   ErrorStatus: ~p", [ErrorStatus]),
-		    {ErrorStatus, OrgIndex};
-		{value, Type, NValue} ->
- 		    ?vt("validate_tab_next_res -> "
-     			"~n   Type:   ~p"
-			"~n   NValue: ~p", [Type, NValue]),
-		    NewVb = OrgVb#varbind{oid = NextCompleteOid,
-					  variabletype = Type, value = NValue},
-		    validate_tab_next_res(Values, TableOids, Mfa,
-					  [NewVb | Res], TabOid, TabNextOid, I)
-	    end;
-	Error ->
-	    user_err("Invalid oid ~w from ~w (get_next). Using genErr => ~p",
-		     [NextOid, Mfa, Error]),
-	    {genErr, OrgIndex}
-    end;
-validate_tab_next_res([endOfTable | Values],
-		      [{_ColNo, OrgVb, _Index} | TableOids],
-		      Mfa, Res, TabOid, TabNextOid, I) ->
-     ?vt("validate_tab_next_res(endOfTable) -> entry with: "
-	 "~n   Values:     ~p"
-	 "~n   OrgVb:      ~p"
-	 "~n   TableOids:  ~p"
-	 "~n   Mfa:        ~p"
-	 "~n   Res:        ~p"
-	 "~n   TabOid:     ~p"
-	 "~n   TabNextOid: ~p"
-	 "~n   I:          ~p",
-	 [Values, OrgVb, TableOids, Mfa, Res, TabOid, TabNextOid, I]),
-    NewVb = OrgVb#varbind{value = {endOfTable, TabNextOid}},
-    validate_tab_next_res(Values, TableOids, Mfa, [NewVb | Res],
-			  TabOid, TabNextOid, I);
-validate_tab_next_res([], [], _Mfa, Res, _TabOid, _TabNextOid, _I) ->
-    Res;
-validate_tab_next_res([], [{_Col, _OrgVb, Index}|_], Mfa, _Res, _, _, _I) ->
-    user_err("Too few values returned from ~w (get_next)", [Mfa]),
-    {genErr, Index};
-validate_tab_next_res({genErr, ColNumber}, OrgCols,
-		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
-    OrgIndex = snmpa_svbl:col_to_orgindex(ColNumber, OrgCols),
-    validate_err(table_next, {genErr, OrgIndex}, Mfa);
-validate_tab_next_res({error, Reason}, [{_ColNo, OrgVb, _Index} | _TableOids],
-		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
-    #varbind{org_index = OrgIndex} = OrgVb,
-    user_err("Erroneous return value ~w from ~w (get_next)",
-	     [Reason, Mfa]),
-    {genErr, OrgIndex};
-validate_tab_next_res(Error, [{_ColNo, OrgVb, _Index} | _TableOids],
-		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
-    #varbind{org_index = OrgIndex} = OrgVb,
-    user_err("Invalid return value ~w from ~w (get_next)",
-	     [Error, Mfa]),
-    {genErr, OrgIndex};
-validate_tab_next_res(TooMany, [], Mfa, _Res, _, _, I) ->
-    user_err("Too many values ~w returned from ~w (get_next)",
-	     [TooMany, Mfa]),
-    {genErr, I}.
-
-%%-----------------------------------------------------------------
-%% Func: get_next_sa/4
-%% Purpose: Loop the list of varbinds for the subagent.
-%%          Call subagent_get_next to retreive
-%%          the next varbinds.
-%% Returns: {ok, ListOfNewVbs, ListOfEndOfMibViewsVbs} |
-%%          {ErrorStatus, ErrorIndex}
-%%-----------------------------------------------------------------
-get_next_sa(SAPid, SAOid, SAVbs, MibView) ->
-    case catch subagent_get_next(SAPid, MibView, SAVbs) of
-	{noError, 0, NewVbs} ->
-	    NewerVbs = transform_sa_next_result(NewVbs,SAOid,next_oid(SAOid)),
-	    split_varbinds(NewerVbs, [], []);
-	{ErrorStatus, ErrorIndex, _} ->
-	    {ErrorStatus, ErrorIndex};
-	{'EXIT', Reason} ->
-	    user_err("Lost contact with subagent (next) ~w. Using genErr",
-		     [Reason]),
-	    {genErr, 0}
-    end.
 
-%%-----------------------------------------------------------------
-%% Check for wrong prefix returned or endOfMibView, and convert
-%% into {endOfMibView, SANextOid}.
-%%-----------------------------------------------------------------
-transform_sa_next_result([Vb | Vbs], SAOid, SANextOid)
-  when Vb#varbind.value =:= endOfMibView ->
-    [Vb#varbind{value = {endOfMibView, SANextOid}} |
-     transform_sa_next_result(Vbs, SAOid, SANextOid)];
-transform_sa_next_result([Vb | Vbs], SAOid, SANextOid) ->
-    case lists:prefix(SAOid, Vb#varbind.oid) of
-	true ->
-	    [Vb | transform_sa_next_result(Vbs, SAOid, SANextOid)];
-	_ ->
-	    [Vb#varbind{oid = SANextOid, value = {endOfMibView, SANextOid}} |
-	     transform_sa_next_result(Vbs, SAOid, SANextOid)]
-    end;
-transform_sa_next_result([], _SAOid, _SANextOid) ->
-    [].
-
-split_varbinds([Vb | Vbs], Res, EndOfs) ->
-    case Vb#varbind.value of
-	{endOfMibView, _} -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
-	{endOfTable, _} -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
-	_ -> split_varbinds(Vbs, [Vb | Res], EndOfs)
-    end;
-split_varbinds([], Res, EndOfs) -> {ok, Res, EndOfs}.
+do_get_next(MibView, UnsortedVarbinds) ->
+    GetModule = get(get_module),
+    GetModule:do_get_next(MibView, UnsortedVarbinds).
 
-next_oid(Oid) ->
-    case lists:reverse(Oid) of
-	[H | T] -> lists:reverse([H+1 | T]);
-	[] -> []
-    end.
 
 
 %%%-----------------------------------------------------------------
@@ -3623,200 +2796,10 @@ next_oid(Oid) ->
 %%%-----------------------------------------------------------------
 
 do_get_bulk(MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs) ->
-    ?vtrace("do_get_bulk -> entry with"
-	    "~n   MibView:        ~p"
-	    "~n   NonRepeaters:   ~p"
-	    "~n   MaxRepetitions: ~p"
-	    "~n   PduMS:          ~p"
-	    "~n   Varbinds:       ~p"
-	    "~n   GbMaxVBs:       ~p",
-	    [MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs]),
-    {NonRepVbs, RestVbs} = split_vbs(NonRepeaters, Varbinds, []),
-    ?vt("do_get_bulk -> split: "
-	"~n   NonRepVbs: ~p"
-	"~n   RestVbs:   ~p", [NonRepVbs, RestVbs]),
-    case do_get_next(MibView, NonRepVbs, GbMaxVBs) of
-	{noError, 0, UResNonRepVbs} ->
-	    ?vt("do_get_bulk -> next noError: "
-		"~n   UResNonRepVbs: ~p", [UResNonRepVbs]),
-	    ResNonRepVbs = lists:keysort(#varbind.org_index, UResNonRepVbs),
-	    %% Decode the first varbinds, produce a reversed list of
-	    %% listOfBytes.
-	    case (catch enc_vbs(PduMS - ?empty_pdu_size, ResNonRepVbs)) of
- 		{error, Idx, Reason} ->
-		    user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
-                    {genErr, Idx, []};
-                {SizeLeft, Res} when is_integer(SizeLeft) and is_list(Res) ->
- 		    ?vtrace("do_get_bulk -> encoded: "
-			    "~n   SizeLeft: ~p"
-			    "~n   Res:      ~w", [SizeLeft, Res]),
-		    case (catch do_get_rep(SizeLeft, MibView, MaxRepetitions,
-					   RestVbs, Res, 
-					   length(UResNonRepVbs), GbMaxVBs)) of
-			{error, Idx, Reason} ->
-			    user_err("failed encoding varbind ~w:~n~p", 
-				     [Idx, Reason]),
-			    {genErr, Idx, []};
-			Res when is_list(Res) ->
-			    ?vtrace("do get bulk -> Res: "
-				    "~n   ~w", [Res]),
-			    {noError, 0, conv_res(Res)};
-			{noError, 0, Data} = OK ->
-			    ?vtrace("do get bulk -> OK: "
-				    "~n   length(Data): ~w", [length(Data)]),
-			    OK;
-			Else ->
-			    ?vtrace("do get bulk -> Else: "
-				    "~n   ~w", [Else]),
-			    Else
-		    end;
-		Res when is_list(Res) ->
-		    {noError, 0, conv_res(Res)}
-	    end;
-
-	{ErrorStatus, Index, _} ->
-	    ?vdebug("do get bulk: "
-		    "~n   ErrorStatus: ~p"
-		    "~n   Index:       ~p",[ErrorStatus, Index]),
-	    {ErrorStatus, Index, []}
-    end.
+    GetModule = get(get_module),
+    GetModule:do_get_bulk(MibView, NonRepeaters, MaxRepetitions,
+                          PduMS, Varbinds, GbMaxVBs).
 
-% sz(L) when list(L) -> length(L);
-% sz(B) when binary(B) -> size(B);
-% sz(_) -> unknown.
-
-split_vbs(N, Varbinds, Res) when N =< 0 -> {Res, Varbinds};
-split_vbs(N, [H | T], Res) -> split_vbs(N-1, T, [H | Res]);
-split_vbs(_N, [], Res) -> {Res, []}.
-     
-enc_vbs(SizeLeft, Vbs) ->
-    ?vt("enc_vbs -> entry with"
-	"~n   SizeLeft: ~w", [SizeLeft]),
-    Fun = fun(Vb, {Sz, Res}) when Sz > 0 ->
-		  ?vt("enc_vbs -> (fun) entry with"
-		      "~n   Vb:  ~p"
-		      "~n   Sz:  ~p"
-		      "~n   Res: ~w", [Vb, Sz, Res]),
-		  case (catch snmp_pdus:enc_varbind(Vb)) of
-		      {'EXIT', Reason} ->
-			  ?vtrace("enc_vbs -> encode failed: "
-				  "~n   Reason: ~p", [Reason]),
-			  throw({error, Vb#varbind.org_index, Reason});
-		      X ->
-			  ?vt("enc_vbs -> X: ~w", [X]),
-			  Lx = length(X),
-			  ?vt("enc_vbs -> Lx: ~w", [Lx]),
-			  if
-			      Lx < Sz ->
-				  {Sz - length(X), [X | Res]};
-			      true ->
-				  throw(Res)
-			  end
-		  end;
-	     (_Vb, {_Sz, [_H | T]}) ->
-		  ?vt("enc_vbs -> (fun) entry with"
-		      "~n   T: ~p", [T]),
-		  throw(T);
-	     (_Vb, {_Sz, []}) ->
-		  ?vt("enc_vbs -> (fun) entry", []),
-		  throw([])
-	  end,
-    lists:foldl(Fun, {SizeLeft, []}, Vbs).
-
-do_get_rep(Sz, MibView, MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) 
-  when MaxRepetitions >= 0 ->
-    do_get_rep(Sz, MibView, 0, MaxRepetitions, Varbinds, Res, 
-	       GbNumVBs, GbMaxVBs);
-do_get_rep(Sz, MibView, _MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) ->
-    do_get_rep(Sz, MibView, 0, 0, Varbinds, Res, GbNumVBs, GbMaxVBs).
-
-conv_res(ResVarbinds) ->
-    conv_res(ResVarbinds, []).
-conv_res([VbListOfBytes | T], Bytes) ->
-    conv_res(T, VbListOfBytes ++ Bytes);
-conv_res([], Bytes) ->
-    Bytes.
-
-%% The only other value, then a positive integer, is infinity.
-do_get_rep(_Sz, _MibView, Count, Max, _, _Res, GbNumVBs, GbMaxVBs) 
-  when (is_integer(GbMaxVBs) andalso (GbNumVBs > GbMaxVBs)) ->
-    ?vinfo("Max Get-BULK VBs limit (~w) exceeded (~w) when:"
-	   "~n   Count: ~p"
-	   "~n   Max:   ~p", [GbMaxVBs, GbNumVBs, Count, Max]),
-    {tooBig, 0, []};
-do_get_rep(_Sz, _MibView, Max, Max, _, Res, _GbNumVBs, _GbMaxVBs) ->
-    ?vt("do_get_rep -> done when: "
-	"~n   Res: ~p", [Res]),
-    {noError, 0, conv_res(Res)};
-do_get_rep(Sz, MibView, Count, Max, Varbinds, Res, GbNumVBs, GbMaxVBs) -> 
-    ?vt("do_get_rep -> entry when: "
-	"~n   Sz:    ~p"
-	"~n   Count: ~p"
-	"~n   Res:   ~w", [Sz, Count, Res]),
-    case try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) of
-	{noError, NextVarbinds, SizeLeft, Res2} -> 
-	    ?vt("do_get_rep -> noError: "
-		"~n   SizeLeft: ~p"
-		"~n   Res2:     ~p", [SizeLeft, Res2]),
-	    do_get_rep(SizeLeft, MibView, Count+1, Max, NextVarbinds,
-		       Res2 ++ Res, 
-		       GbNumVBs + length(Varbinds), GbMaxVBs);
-	{endOfMibView, _NextVarbinds, _SizeLeft, Res2} -> 
-	    ?vt("do_get_rep -> endOfMibView: "
-		"~n   Res2: ~p", [Res2]),
-	    {noError, 0, conv_res(Res2 ++ Res)};
-	{ErrorStatus, Index} ->
-	    ?vtrace("do_get_rep -> done when error: "
-		    "~n   ErrorStatus: ~p"
-		    "~n   Index:       ~p", [ErrorStatus, Index]),
-	    {ErrorStatus, Index, []}
-    end.
-
-org_index_sort_vbs(Vbs) ->
-    lists:keysort(#varbind.org_index, Vbs).
-
-try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) -> 
-    ?vt("try_get_bulk -> entry with"
-	"~n   Sz:       ~w"
-	"~n   MibView:  ~w"
-	"~n   Varbinds: ~w", [Sz, MibView, Varbinds]),
-    case do_get_next(MibView, Varbinds, GbMaxVBs) of
-	{noError, 0, UNextVarbinds} -> 
-	    ?vt("try_get_bulk -> noError: "
-		"~n   UNextVarbinds: ~p", [UNextVarbinds]),
-	    NextVarbinds = org_index_sort_vbs(UNextVarbinds),
-	    case (catch enc_vbs(Sz, NextVarbinds)) of
-		{error, Idx, Reason} ->
-		    user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
-		    ?vtrace("try_get_bulk -> encode error: "
-			    "~n   Idx:    ~p"
-			    "~n   Reason: ~p", [Idx, Reason]),
-		    {genErr, Idx};
-		{SizeLeft, Res} when is_integer(SizeLeft) andalso 
-				     is_list(Res) ->
-		    ?vt("try get bulk -> encode ok: "
-			"~n   SizeLeft: ~w"
-			"~n   Res:      ~w", [SizeLeft, Res]),
-		    {check_end_of_mibview(NextVarbinds),
-		     NextVarbinds, SizeLeft, Res};
-		Res when is_list(Res) ->
-		    ?vt("try get bulk -> Res: "
-			"~n   ~w", [Res]),
-		    {endOfMibView, [], 0, Res}
-	    end;
-	{ErrorStatus, Index, _} ->
-	    ?vt("try_get_bulk -> error: "
-		"~n   ErrorStatus: ~p"
-		"~n   Index:       ~p", [ErrorStatus, Index]),
-	    {ErrorStatus, Index}
-    end.
-
-%% If all variables in this pass are endOfMibView,
-%% there is no reason to continue.
-check_end_of_mibview([#varbind{value = endOfMibView} | T]) ->
-    check_end_of_mibview(T);
-check_end_of_mibview([]) -> endOfMibView;
-check_end_of_mibview(_) -> noError.
 
 
 %%%--------------------------------------------------
@@ -3834,14 +2817,11 @@ do_subagent_set(Arguments) ->
     SetModule = get(set_module),
     apply(SetModule, do_subagent_set, [Arguments]).
 
+
+
 %%%-----------------------------------------------------------------
 %%% 7. Misc functions
 %%%-----------------------------------------------------------------
-sort_varbindlist(Varbinds) ->
-    snmpa_svbl:sort_varbindlist(get(mibserver), Varbinds).
-
-sa_split(SubagentVarbinds) ->
-    snmpa_svbl:sa_split(SubagentVarbinds).
 
 make_response_pdu(ReqId, ErrStatus, ErrIndex, OrgVarbinds, _ResponseVarbinds)
   when ErrIndex =/= 0 ->
@@ -4180,28 +3160,28 @@ mapfoldl(_F, _Eas, Accu, []) -> {Accu,[]}.
 %% Runtime debugging of the agent.
 %%-----------------------------------------------------------------
 
-dbg_apply(M,F,A) ->
-    case get(verbosity) of
-	silence -> 
-	    apply(M,F,A);
-	_ ->
-	    ?vlog("~n   apply: ~w,~w,~p~n", [M,F,A]),
-	    Res = (catch apply(M,F,A)),
-	    case Res of
-		{'EXIT', Reason} ->
-		    ?vinfo("Call to: "
-			   "~n   Module:   ~p"
-			   "~n   Function: ~p"
-			   "~n   Args:     ~p"
-			   "~n"
-			   "~nresulted in an exit"
-			   "~n"
-			   "~n   ~p", [M, F, A, Reason]);
-		_ ->
-		    ?vlog("~n   returned: ~p", [Res])
-	    end,
-	    Res
-    end.
+%% dbg_apply(M,F,A) ->
+%%     case get(verbosity) of
+%% 	silence -> 
+%% 	    apply(M,F,A);
+%% 	_ ->
+%% 	    ?vlog("~n   apply: ~w,~w,~p~n", [M,F,A]),
+%% 	    Res = (catch apply(M,F,A)),
+%% 	    case Res of
+%% 		{'EXIT', Reason} ->
+%% 		    ?vinfo("Call to: "
+%% 			   "~n   Module:   ~p"
+%% 			   "~n   Function: ~p"
+%% 			   "~n   Args:     ~p"
+%% 			   "~n"
+%% 			   "~nresulted in an exit"
+%% 			   "~n"
+%% 			   "~n   ~p", [M, F, A, Reason]);
+%% 		_ ->
+%% 		    ?vlog("~n   returned: ~p", [Res])
+%% 	    end,
+%% 	    Res
+%%     end.
 
 
 short_name(none) -> ma;
@@ -4450,6 +3430,9 @@ get_mib_storage(Opts) ->
 get_set_mechanism(Opts) ->
     get_option(set_mechanism, Opts, snmpa_set).
 
+get_get_mechanism(Opts) ->
+    get_option(get_mechanism, Opts, snmpa_get).
+
 get_authentication_service(Opts) ->
     get_option(authentication_service, Opts, snmpa_acm).
 
diff --git a/lib/snmp/src/agent/snmpa_get.erl b/lib/snmp/src/agent/snmpa_get.erl
new file mode 100644
index 0000000000..be4ecd9a71
--- /dev/null
+++ b/lib/snmp/src/agent/snmpa_get.erl
@@ -0,0 +1,1148 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(snmpa_get).
+
+-behaviour(snmpa_get_mechanism).
+
+
+%%%-----------------------------------------------------------------
+%%% snmpa_get_mechanism exports
+%%%-----------------------------------------------------------------
+
+-export([
+         do_get/2, do_get/3,
+         do_get_next/2,
+         do_get_bulk/6
+        ]).
+
+-include("snmpa_internal.hrl").
+-include("snmp_types.hrl").
+-include("snmp_debug.hrl").
+-include("snmp_verbosity.hrl").
+
+-ifndef(default_verbosity).
+-define(default_verbosity,silence).
+-endif.
+
+-define(empty_pdu_size, 21).
+
+-ifdef(snmp_extended_verbosity).
+-define(vt(F,A), ?vtrace(F, A)).
+-else.
+-define(vt(_F, _A), ok).
+-endif.
+
+
+-define(AGENT, snmpa_agent).
+-define(LIB,   snmpa_get_lib).
+
+
+
+%%%-----------------------------------------------------------------
+%%% 3. GET REQUEST
+%%% --------------
+%%%   According to RFC1157, section 4.1.2 and RFC1905, section 4.2.1.
+%%%   In rfc1157:4.1.2 it isn't specified if noSuchName should be
+%%%   returned even if some other varbind generates a genErr.
+%%%   In rfc1905:4.2.1 this is not a problem since exceptions are
+%%%   used, and thus a genErr will be returned anyway.
+%%%-----------------------------------------------------------------
+
+%%-----------------------------------------------------------------
+%% Func: do_get/2
+%% Purpose: Handles all VBs in a request that is inside the 
+%%          mibview (local).
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get(UnsortedVarbinds, IsNotification) ->
+    {MyVarbinds, SubagentVarbinds} = ?LIB:agent_sort_vbs(UnsortedVarbinds),
+    case do_get_local(MyVarbinds, IsNotification) of
+	{noError, 0, NewMyVarbinds} ->
+	    case do_get_subagents(SubagentVarbinds, IsNotification) of
+		{noError, 0, NewSubagentVarbinds} ->
+		    {noError, 0, NewMyVarbinds ++ NewSubagentVarbinds};
+		{ErrorStatus, ErrorIndex, _} ->
+		    {ErrorStatus, ErrorIndex, []}
+	    end;
+	{ErrorStatus, ErrorIndex, _} -> 
+	    {ErrorStatus, ErrorIndex, []}
+    end.
+
+
+%%-----------------------------------------------------------------
+%% Func: do_get/3
+%% Purpose: do_get handles "getRequests".
+%% Pre: incoming varbinds have type == 'NULL', value == unSpecified
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get(MibView, UnsortedVarbinds, IsNotification) ->
+    ?vtrace("do_get -> entry with"
+	    "~n   MibView:          ~p"
+	    "~n   UnsortedVarbinds: ~p"
+	    "~n   IsNotification:   ~p", 
+	    [MibView, UnsortedVarbinds, IsNotification]),
+    %% This is me, the master, so go ahead
+    {OutSideView, InSideView} = ?LIB:split_vbs_view(UnsortedVarbinds, MibView),
+    {Error, Index, NewVbs}    = do_get(InSideView, IsNotification),
+    {Error, Index, NewVbs ++ OutSideView}.
+
+
+
+%%-----------------------------------------------------------------
+%% Func: do_get_local/2,3
+%% Purpose: Loop the variablebindings list. We know that each varbind
+%%          in that list belongs to us.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get_local(VBs, IsNotification) ->
+    do_get_local(VBs, [], IsNotification).
+
+do_get_local([Vb | Vbs], Res, IsNotification) ->
+    case try_get(Vb, IsNotification) of
+	NewVb when is_record(NewVb, varbind) ->
+	    do_get_local(Vbs, [NewVb | Res], IsNotification);
+	ListOfNewVb when is_list(ListOfNewVb) ->
+	    do_get_local(Vbs, lists:append(ListOfNewVb, Res), IsNotification);
+	{error, Error, OrgIndex} ->
+	    {Error, OrgIndex, []}
+    end;
+do_get_local([], Res, _IsNotification) -> 
+    {noError, 0, Res}.
+
+
+
+%%-----------------------------------------------------------------
+%% Func: do_get_subagents/2
+%% Purpose: Loop the list of varbinds for different subagents.
+%%          For each of them, call sub_agent_get to retreive
+%%          the values for them.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+do_get_subagents(SubagentVarbinds, IsNotification) ->
+    do_get_subagents(SubagentVarbinds, [], IsNotification).
+do_get_subagents([{SubAgentPid, SAVbs} | Tail], Res, IsNotification) ->
+    {_SAOids, Vbs} = ?LIB:sa_split(SAVbs),
+    case catch ?AGENT:subagent_get(SubAgentPid, Vbs, IsNotification) of
+	{noError, 0, NewVbs} ->
+	    do_get_subagents(Tail, lists:append(NewVbs, Res), IsNotification);
+	{ErrorStatus, ErrorIndex, _} ->
+	    {ErrorStatus, ErrorIndex, []};
+	{'EXIT', Reason} ->
+	    ?LIB:user_err("Lost contact with subagent (get) ~w. Using genErr", 
+                          [Reason]),
+	    {genErr, 0, []} 
+    end;
+do_get_subagents([], Res, _IsNotification) ->
+    {noError, 0, Res}.
+
+
+%%-----------------------------------------------------------------
+%% Func: try_get/2
+%% Returns: {error, ErrorStatus, OrgIndex} |
+%%          #varbind |
+%%          List of #varbind
+%%-----------------------------------------------------------------
+try_get(IVb, IsNotification) when is_record(IVb, ivarbind) ->
+    ?vtrace("try_get(ivarbind) -> entry with"
+	    "~n   IVb: ~p", [IVb]),
+    get_var_value_from_ivb(IVb, IsNotification);
+try_get({TableOid, TableVbs}, IsNotification) ->
+    ?vtrace("try_get(table) -> entry with"
+	    "~n   TableOid: ~p"
+	    "~n   TableVbs: ~p", [TableOid, TableVbs]),
+    [#ivarbind{mibentry = MibEntry}|_] = TableVbs,
+    {NoAccessVbs, AccessVbs} =
+	check_all_table_vbs(TableVbs, IsNotification, [], []),
+    case get_tab_value_from_mib(MibEntry, TableOid, AccessVbs) of
+	{error, ErrorStatus, OrgIndex} ->
+	    {error, ErrorStatus, OrgIndex};
+	NVbs ->
+	    NVbs ++ NoAccessVbs
+    end.
+
+%%-----------------------------------------------------------------
+%% Make sure all requested columns are accessible.
+%%-----------------------------------------------------------------
+check_all_table_vbs([IVb| IVbs], IsNotification, NoA, A) ->
+    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
+    case Me#me.access of
+	'not-accessible' -> 
+	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
+	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
+	'accessible-for-notify' when IsNotification =:= false -> 
+	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
+	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
+	'write-only' -> 
+	    NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
+	    check_all_table_vbs(IVbs, IsNotification, NNoA, A);
+	_ ->
+	    check_all_table_vbs(IVbs, IsNotification, NoA, [IVb | A])
+    end;
+check_all_table_vbs([], _IsNotification, NoA, A) -> {NoA, A}.
+
+%%-----------------------------------------------------------------
+%% Returns: {error, ErrorStatus, OrgIndex} |
+%%          #varbind
+%%-----------------------------------------------------------------
+get_var_value_from_ivb(IVb, IsNotification)
+  when IVb#ivarbind.status =:= noError ->
+    ?vtrace("get_var_value_from_ivb(noError) -> entry", []),
+    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
+    #varbind{org_index = OrgIndex, oid = Oid} = Vb,
+    case Me#me.access of
+	'not-accessible' -> 
+	    Vb#varbind{value = noSuchInstance};
+	'accessible-for-notify' when IsNotification =:= false -> 
+	    Vb#varbind{value = noSuchInstance};
+	'write-only' -> 
+	    Vb#varbind{value = noSuchInstance};
+	_ -> 
+	    case get_var_value_from_mib(Me, Oid) of
+		{value, Type, Value} ->
+		    Vb#varbind{variabletype = Type, value = Value};
+		{error, ErrorStatus} ->
+		    {error, ErrorStatus, OrgIndex}
+	    end
+    end;
+get_var_value_from_ivb(#ivarbind{status = Status, varbind = Vb}, _) ->
+    ?vtrace("get_var_value_from_ivb(~p) -> entry", [Status]),
+    Vb#varbind{value = Status}.
+
+%%-----------------------------------------------------------------
+%% Func: get_var_value_from_mib/1
+%% Purpose: 
+%% Returns: {error, ErrorStatus} |
+%%          {value, Type, Value}
+%%-----------------------------------------------------------------
+%% Pre: Oid is a correct instance Oid (lookup checked that).
+%% Returns: A correct return value (see ?AGENT:make_value_a_correct_value)
+get_var_value_from_mib(#me{entrytype = variable,
+			   asn1_type = ASN1Type,
+			   mfa       = {Mod, Func, Args}},
+		       _Oid) ->
+    ?vtrace("get_var_value_from_mib(variable) -> entry when"
+	    "~n   Mod:  ~p"
+	    "~n   Func: ~p"
+	    "~n   Args: ~p", [Mod, Func, Args]),
+    Result = (catch ?LIB:dbg_apply(Mod, Func, [get | Args])),
+    %% mib shall return {value, <a-nice-value-within-range>} |
+    %% {noValue, noSuchName} (v1) | 
+    %% {noValue, noSuchObject | noSuchInstance} (v2, v1)
+    %% everything else (including 'genErr') will generate 'genErr'.
+    ?AGENT:make_value_a_correct_value(Result, ASN1Type, {Mod, Func, Args});
+
+get_var_value_from_mib(#me{entrytype = table_column,
+			   oid       = MeOid,
+			   asn1_type = ASN1Type,
+			   mfa       = {Mod, Func, Args}},
+		       Oid) ->
+    ?vtrace("get_var_value_from_mib(table_column) -> entry when"
+	    "~n   MeOid: ~p"
+	    "~n   Mod:   ~p"
+	    "~n   Func:  ~p"
+	    "~n   Args:  ~p"
+	    "~n   Oid:   ~p", [MeOid, Mod, Func, Args, Oid]),
+    Col = lists:last(MeOid),
+    Indexes = snmp_misc:diff(Oid, MeOid),
+    [Result] = (catch ?LIB:dbg_apply(Mod, Func, [get, Indexes, [Col] | Args])),
+    ?AGENT:make_value_a_correct_value(Result, ASN1Type, 
+                                      {Mod, Func, Args, Indexes, Col}).
+
+
+%% For table operations we need to pass RestOid down to the table-function.
+%% Its up to the table-function to check for noSuchInstance (ex: a 
+%% non-existing row).
+%% Returns: {error, ErrorStatus, OrgIndex} |
+%%          {value, Type, Value}
+get_tab_value_from_mib(#me{mfa = {Mod, Func, Args}}, TableOid, TableVbs) ->
+    ?vtrace("get_tab_value_from_mib -> entry when"
+	    "~n   Mod:  ~p"
+	    "~n   Func: ~p"
+	    "~n   Args: ~p", [Mod, Func, Args]),
+    TableOpsWithShortOids = ?LIB:delete_prefixes(TableOid, TableVbs),
+    SortedVBsRows = snmpa_svbl:sort_varbinds_rows(TableOpsWithShortOids), 
+    case get_value_all_rows(SortedVBsRows, Mod, Func, Args, []) of
+	{Error, Index} ->
+	    #ivarbind{varbind = Vb} = lists:nth(Index, TableVbs),
+	    {error, Error, Vb#varbind.org_index};
+	ListOfValues -> 
+	    merge_varbinds_and_value(TableVbs, ListOfValues)
+    end.
+
+%%-----------------------------------------------------------------
+%% Values is a scrambled list of {CorrectValue, Index}, where Index
+%% is index into the #ivarbind list. So for each Value, we must
+%% find the corresponding #ivarbind, and merge them into a new
+%% #varbind.
+%% The Values list comes from validate_tab_res.
+%%-----------------------------------------------------------------
+merge_varbinds_and_value(IVbs, [{{value, Type, Value}, Index} | Values]) ->
+    #ivarbind{varbind = Vb} = lists:nth(Index, IVbs),
+    [Vb#varbind{variabletype = Type, value = Value} |
+     merge_varbinds_and_value(IVbs, Values)];
+merge_varbinds_and_value(_, []) -> [].
+    
+get_value_all_rows([{[], OrgCols} | Rows], Mod, Func, Args, Res) ->
+    ?vtrace("get_value_all_rows -> entry when"
+	    "~n   OrgCols: ~p", [OrgCols]),
+    Cols   = [{{value, noValue, noSuchInstance}, Index} || 
+		 {_Col, _ASN1Type, Index} <- OrgCols], 
+    NewRes = lists:append(Cols, Res),
+    get_value_all_rows(Rows, Mod, Func, Args, NewRes);
+get_value_all_rows([{RowIndex, OrgCols} | Rows], Mod, Func, Args, Res) ->
+    ?vtrace("get_value_all_rows -> entry when"
+	    "~n   RowIndex: ~p"
+	    "~n   OrgCols:  ~p", [RowIndex, OrgCols]),
+    {DOrgCols, Dup} = remove_duplicates(OrgCols),
+    Cols   = delete_index(DOrgCols),
+    Result = (catch ?LIB:dbg_apply(Mod, Func, [get, RowIndex, Cols | Args])),
+    case validate_tab_res(Result, DOrgCols, {Mod, Func, Args}) of
+	Values when is_list(Values) ->
+	    NVals  = restore_duplicates(Dup, Values),
+	    NewRes = lists:append(NVals, Res),
+	    get_value_all_rows(Rows, Mod, Func, Args, NewRes);
+	{error, ErrorStatus, Index} ->
+	    ?AGENT:validate_err(row_set, {ErrorStatus, Index}, {Mod, Func, Args})
+    end;
+get_value_all_rows([], _Mod, _Func, _Args, Res) -> 
+    ?vtrace("get_value_all_rows -> entry when done"
+	    "~n   Res: ~p", [Res]),
+    Res.
+
+%%-----------------------------------------------------------------
+%% Args: {RowIndex, list of {ShortOid, ASN1Type}}
+%% Returns: list of Col
+%%-----------------------------------------------------------------
+delete_index([{Col, _Val, _OrgIndex} | T]) ->
+    [Col | delete_index(T)];
+delete_index([]) -> [].
+
+%%-----------------------------------------------------------------
+%% This function is called before 'get' on a table, and removes
+%% any duplicate columns.  It returns {Cols, DupInfo}.  The Cols
+%% are the unique columns.  The instrumentation function is
+%% called to get the values.  These values, together with the
+%% DupInfo, is later passed to restore_duplicates, which uses
+%% the retrieved values to reconstruct the original column list,
+%% but with the retrieved value for each column.
+%%-----------------------------------------------------------------
+remove_duplicates(Cols) ->
+    remove_duplicates(Cols, [], []).
+
+
+remove_duplicates([{Col, V1, OrgIdx1}, {Col, V2, OrgIdx2} | T], NCols, Dup) ->
+    remove_duplicates([{Col, V1, OrgIdx1} | T], NCols, 
+		      [{Col, V2, OrgIdx2} | Dup]);
+remove_duplicates([Col | T], NCols, Dup) ->
+    remove_duplicates(T, [Col | NCols], Dup);
+remove_duplicates([], NCols, Dup) ->
+    {lists:reverse(NCols), lists:reverse(Dup)}.
+
+restore_duplicates([], Cols) ->
+    [{Val, OrgIndex} || {_Col, Val, OrgIndex} <- Cols];
+restore_duplicates([{Col, _Val2, OrgIndex2} | Dup],
+		   [{Col, NVal, OrgIndex1} | Cols]) ->
+    [{NVal, OrgIndex2} |
+     restore_duplicates(Dup, [{Col, NVal, OrgIndex1} | Cols])];
+restore_duplicates(Dup, [{_Col, Val, OrgIndex} | T]) ->
+    [{Val, OrgIndex} | restore_duplicates(Dup, T)].
+
+
+
+%%-----------------------------------------------------------------
+%% Three cases:
+%%   1) All values ok
+%%   2) table_func returned {Error, ...}
+%%   3) Some value in Values list is erroneous.
+%% Args: Value is a list of values from table_func(get..)
+%%       OrgCols is a list with {Col, ASN1Type, OrgIndex} 
+%%         each element in Values and OrgCols correspond to each
+%%         other.
+%%-----------------------------------------------------------------
+validate_tab_res(Values, OrgCols, Mfa) when is_list(Values) ->
+    {_Col, _ASN1Type, OneIdx} = hd(OrgCols),
+    validate_tab_res(Values, OrgCols, Mfa, [], OneIdx);
+validate_tab_res({noValue, Error}, OrgCols, Mfa) ->
+    Values = lists:duplicate(length(OrgCols), {noValue, Error}),
+    validate_tab_res(Values, OrgCols, Mfa);
+validate_tab_res({genErr, Col}, OrgCols, Mfa) ->
+    case lists:keysearch(Col, 1, OrgCols) of
+	{value, {_Col, _ASN1Type, Index}} ->
+	    {error, genErr, Index};
+	_ ->
+	    ?LIB:user_err("Invalid column in {genErr, ~w} from ~w (get)",
+                          [Col, Mfa]),
+	    [{_Col, _ASN1Type, Index} | _] = OrgCols,
+	    {error, genErr, Index}
+    end;
+validate_tab_res(genErr, [{_Col, __ASN1Type, Index} | _OrgCols], _Mfa) ->
+    {error, genErr, Index};
+validate_tab_res(Error, [{_Col, _ASN1Type, Index} | _OrgCols], Mfa) ->
+    ?LIB:user_err("Invalid return value ~w from ~w (get)",[Error, Mfa]),
+    {error, genErr, Index}.
+
+validate_tab_res([Value | Values], 
+		 [{Col, ASN1Type, Index} | OrgCols],
+		 Mfa, Res, I) ->
+    %% This one makes it possible to return a list of genErr, which
+    %% is not allowed according to the manual.  But that's ok, as
+    %% everything else will generate a genErr! (the only problem is
+    %% that it won't generate a user_error).
+    case ?AGENT:make_value_a_correct_value(Value, ASN1Type, Mfa) of
+	{error, ErrorStatus} ->
+	    {error, ErrorStatus, Index};
+	CorrectValue ->
+	    NewRes = [{Col, CorrectValue, Index} | Res],
+	    validate_tab_res(Values, OrgCols, Mfa, NewRes, I)
+    end;
+validate_tab_res([], [], _Mfa, Res, _I) -> 
+    lists:reverse(Res);
+validate_tab_res([], [{_Col, _ASN1Type, Index}|_], Mfa, _Res, _I) ->
+    ?LIB:user_err("Too few values returned from ~w (get)", [Mfa]),
+    {error, genErr, Index};
+validate_tab_res(_TooMany, [], Mfa, _Res, I) ->
+    ?LIB:user_err("Too many values returned from ~w (get)", [Mfa]),
+    {error, genErr, I}.
+
+
+
+%%%-----------------------------------------------------------------
+%%% 4. GET-NEXT REQUEST
+%%% --------------
+%%%   According to RFC1157, section 4.1.3 and RFC1905, section 4.2.2.
+%%%-----------------------------------------------------------------
+%%-----------------------------------------------------------------
+%% Func: do_get_next/2
+%% Purpose: do_get_next handles "getNextRequests".
+%% Note: Even if it is SNMPv1, a varbind's value can be
+%%       endOfMibView. This is converted to noSuchName in process_pdu.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%% Note2: ListOfNewVarbinds is not sorted in any order!!!
+%% Alg: First, the variables are sorted in OID order.
+%%
+%%      Second, next in the MIB is performed for each OID, and
+%%      the result is collected as: if next oid is a variable,
+%%      perform a get to retrieve its value; if next oid is in a
+%%      table, save this value and continue until we get an oid
+%%      outside this table. Then perform get_next on the table,
+%%      and continue with all endOfTables and the oid outside the
+%%      table; if next oid is an subagent, save this value and
+%%      continue as in the table case.
+%%
+%%      Third, each response is checked for endOfMibView, or (for
+%%      subagents) that the Oid returned has the correct prefix.
+%%      (This is necessary since an SA can be registered under many
+%%      separated subtrees, and if the last variable in the first
+%%      subtree is requested in a next, the SA will return the first
+%%      variable in the second subtree. This might be working, since
+%%      there may be a variable in between these subtrees.) For each
+%%      of these, a new get-next is performed, one at a time.
+%%      This alg. might be optimised in several ways. The most 
+%%      striking one is that the same SA might be called several
+%%      times, when one time should be enough. But it isn't clear
+%%      that this really matters, since many nexts across the same
+%%      subagent must be considered to be very rare.
+%%-----------------------------------------------------------------
+
+do_get_next(MibView, UnsortedVBs) ->
+    do_get_next(MibView, UnsortedVBs, infinity).
+
+%% The third argument is only used if we are called as result
+%% of a get-bulk request.
+do_get_next(_MibView, UnsortedVarbinds, GbMaxVBs) 
+  when (is_integer(GbMaxVBs) andalso (length(UnsortedVarbinds) > GbMaxVBs)) ->
+    {tooBig, 0, []}; % What is the correct index in this case?
+do_get_next(MibView, UnsortedVBs, GbMaxVBs) ->
+    ?vt("do_get_next -> entry when"
+ 	"~n   MibView:          ~p"
+ 	"~n   UnsortedVBs: ~p", [MibView, UnsortedVBs]),
+    SortedVBs = ?LIB:oid_sort_vbs(UnsortedVBs),
+    ?vt("do_get_next -> "
+ 	"~n   SortedVBs: ~p", [SortedVBs]),
+    next_loop_varbinds([], SortedVBs, MibView, [], [], GbMaxVBs).
+
+next_loop_varbinds(_, Vbs, _MibView, Res, _LAVb, GbMaxVBs) 
+  when (is_integer(GbMaxVBs) andalso 
+	((length(Vbs) + length(Res)) > GbMaxVBs)) ->
+    {tooBig, 0, []}; % What is the correct index in this case?
+
+%% LAVb is Last Accessible Vb
+next_loop_varbinds([], [Vb | Vbs], MibView, Res, LAVb, GbMaxVBs) ->
+    ?vt("next_loop_varbinds -> entry when"
+ 	"~n   Vb:      ~p"
+ 	"~n   MibView: ~p", [Vb, MibView]),
+    case varbind_next(Vb, MibView) of
+	endOfMibView ->
+	    ?vt("next_loop_varbind -> endOfMibView", []),
+	    RVb = if LAVb =:= [] -> Vb;
+		     true -> LAVb
+		  end,
+	    NewVb = RVb#varbind{variabletype = 'NULL', value = endOfMibView},
+	    next_loop_varbinds([], Vbs, MibView, [NewVb | Res], [], GbMaxVBs);
+
+	{variable, ME, VarOid} when ((ME#me.access =/= 'not-accessible') andalso 
+				     (ME#me.access =/= 'write-only') andalso 
+				     (ME#me.access =/= 'accessible-for-notify')) -> 
+	    ?vt("next_loop_varbind -> variable: "
+		"~n   ME:     ~p"
+		"~n   VarOid: ~p", [ME, VarOid]),
+	    case try_get_instance(Vb, ME) of
+		{value, noValue, _NoSuchSomething} ->
+		    ?vt("next_loop_varbind -> noValue", []),
+		    %% Try next one
+		    NewVb = Vb#varbind{oid   = VarOid, 
+				       value = 'NULL'},
+		    next_loop_varbinds([], [NewVb | Vbs], MibView, Res, [], 
+				       GbMaxVBs);
+		{value, Type, Value} ->
+		    ?vt("next_loop_varbind -> value"
+			"~n   Type:  ~p"
+			"~n   Value: ~p", [Type, Value]),
+		    NewVb = Vb#varbind{oid          = VarOid, 
+				       variabletype = Type,
+				       value        = Value},
+		    next_loop_varbinds([], Vbs, MibView, [NewVb | Res], [],
+				       GbMaxVBs);
+		{error, ErrorStatus} ->
+		    ?vdebug("next loop varbinds:"
+			    "~n   ErrorStatus: ~p",[ErrorStatus]),
+		    {ErrorStatus, Vb#varbind.org_index, []}
+	    end;
+	{variable, _ME, VarOid} -> 
+	    ?vt("next_loop_varbind -> variable: "
+		"~n   VarOid: ~p", [VarOid]),
+	    RVb = if LAVb =:= [] -> Vb;
+		     true -> LAVb
+		  end,
+	    NewVb = Vb#varbind{oid = VarOid, value = 'NULL'},
+	    next_loop_varbinds([], [NewVb | Vbs], MibView, Res, RVb, GbMaxVBs);
+	{table, TableOid, TableRestOid, ME} ->
+	    ?vt("next_loop_varbind -> table: "
+		"~n   TableOid:     ~p"
+		"~n   TableRestOid: ~p"
+		"~n   ME:           ~p", [TableOid, TableRestOid, ME]),
+	    next_loop_varbinds({table, TableOid, ME,
+				[{tab_oid(TableRestOid), Vb}]},
+			       Vbs, MibView, Res, [], GbMaxVBs);
+	{subagent, SubAgentPid, SAOid} ->
+	    ?vt("next_loop_varbind -> subagent: "
+		"~n   SubAgentPid: ~p"
+		"~n   SAOid:       ~p", [SubAgentPid, SAOid]),
+	    NewVb = Vb#varbind{variabletype = 'NULL', value = 'NULL'},
+	    next_loop_varbinds({subagent, SubAgentPid, SAOid, [NewVb]},
+			       Vbs, MibView, Res, [], GbMaxVBs)
+    end;
+next_loop_varbinds({table, TableOid, ME, TabOids},
+		   [Vb | Vbs], MibView, Res, _LAVb, GbMaxVBs) ->
+    ?vt("next_loop_varbinds(table) -> entry with"
+ 	"~n   TableOid: ~p"
+ 	"~n   Vb:       ~p", [TableOid, Vb]),
+    case varbind_next(Vb, MibView) of
+	{table, TableOid, TableRestOid, _ME} ->
+	    next_loop_varbinds({table, TableOid, ME,
+				[{tab_oid(TableRestOid), Vb} | TabOids]},
+			       Vbs, MibView, Res, [], GbMaxVBs);
+	_ ->
+	    case get_next_table(ME, TableOid, TabOids, MibView) of
+		{ok, TabRes, TabEndOfTabVbs} ->
+		    NewVbs = lists:append(TabEndOfTabVbs, [Vb | Vbs]),
+		    NewRes = lists:append(TabRes, Res),
+		    next_loop_varbinds([], NewVbs, MibView, NewRes, [], 
+				       GbMaxVBs);
+		{ErrorStatus, OrgIndex} ->
+		    ?vdebug("next loop varbinds: next varbind"
+			    "~n   ErrorStatus: ~p"
+			    "~n   OrgIndex:    ~p",
+			    [ErrorStatus,OrgIndex]),
+		    {ErrorStatus, OrgIndex, []}
+	    end
+    end;
+next_loop_varbinds({table, TableOid, ME, TabOids},
+		   [], MibView, Res, _LAVb, GbMaxVBs) ->
+    ?vt("next_loop_varbinds(table) -> entry with"
+	"~n   TableOid: ~p", [TableOid]),
+    case get_next_table(ME, TableOid, TabOids, MibView) of
+	{ok, TabRes, TabEndOfTabVbs} ->
+ 	    ?vt("next_loop_varbinds(table) -> get_next_table result:"
+		"~n   TabRes:         ~p"
+		"~n   TabEndOfTabVbs: ~p", [TabRes, TabEndOfTabVbs]),
+	    NewRes = lists:append(TabRes, Res),
+	    next_loop_varbinds([], TabEndOfTabVbs, MibView, NewRes, [], 
+			       GbMaxVBs);
+	{ErrorStatus, OrgIndex} ->
+	    ?vdebug("next loop varbinds: next table"
+		    "~n   ErrorStatus: ~p"
+		    "~n   OrgIndex:    ~p",
+		    [ErrorStatus,OrgIndex]),
+	    {ErrorStatus, OrgIndex, []}
+    end;
+next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
+		   [Vb | Vbs], MibView, Res, _LAVb, GbMaxVBs) ->
+    ?vt("next_loop_varbinds(subagent) -> entry with"
+	"~n   SAPid: ~p"
+	"~n   SAOid: ~p"
+ 	"~n   Vb:    ~p", [SAPid, SAOid, Vb]),
+    case varbind_next(Vb, MibView) of
+	{subagent, _SubAgentPid, SAOid} ->
+	    next_loop_varbinds({subagent, SAPid, SAOid,
+				[Vb | SAVbs]},
+			       Vbs, MibView, Res, [], GbMaxVBs);
+	_ ->
+	    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
+		{ok, SARes, SAEndOfMibViewVbs} ->
+		    NewVbs = lists:append(SAEndOfMibViewVbs, [Vb | Vbs]),
+		    NewRes = lists:append(SARes, Res),
+		    next_loop_varbinds([], NewVbs, MibView, NewRes, [], 
+				       GbMaxVBs);
+		{noSuchName, OrgIndex} ->
+		    %% v1 reply, treat this Vb as endOfMibView, and try again
+		    %% for the others.
+		    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
+			{value, EVb} ->
+			    NextOid = next_oid(SAOid),
+			    EndOfVb = 
+				EVb#varbind{oid = NextOid,
+					    value = {endOfMibView, NextOid}},
+			    case lists:delete(EVb, SAVbs) of
+				[] ->
+				    next_loop_varbinds([], [EndOfVb, Vb | Vbs],
+						       MibView, Res, [],
+						       GbMaxVBs);
+				TryAgainVbs ->
+				    next_loop_varbinds({subagent, SAPid, SAOid,
+							TryAgainVbs},
+						       [EndOfVb, Vb | Vbs],
+						       MibView, Res, [],
+						       GbMaxVBs)
+			    end;
+			false ->
+			    %% bad index from subagent
+			    {genErr, (hd(SAVbs))#varbind.org_index, []}
+		    end;
+		{ErrorStatus, OrgIndex} ->
+ 		    ?vdebug("next loop varbinds: next subagent"
+ 			    "~n   Vb:          ~p"
+ 			    "~n   ErrorStatus: ~p"
+ 			    "~n   OrgIndex:    ~p",
+ 			    [Vb,ErrorStatus,OrgIndex]),
+		    {ErrorStatus, OrgIndex, []}
+	    end
+    end;
+next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
+		   [], MibView, Res, _LAVb, GbMaxVBs) ->
+     ?vt("next_loop_varbinds(subagent) -> entry with"
+	 "~n   SAPid: ~p"
+	 "~n   SAOid: ~p", [SAPid, SAOid]),
+    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
+	{ok, SARes, SAEndOfMibViewVbs} ->
+	    NewRes = lists:append(SARes, Res),
+	    next_loop_varbinds([], SAEndOfMibViewVbs, MibView, NewRes, [],
+			       GbMaxVBs);
+	{noSuchName, OrgIndex} ->
+	    %% v1 reply, treat this Vb as endOfMibView, and try again for
+	    %% the others.
+	    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
+		{value, EVb} ->
+		    NextOid = next_oid(SAOid),
+		    EndOfVb = EVb#varbind{oid = NextOid,
+					  value = {endOfMibView, NextOid}},
+		    case lists:delete(EVb, SAVbs) of
+			[] ->
+			    next_loop_varbinds([], [EndOfVb], MibView, Res, [],
+					       GbMaxVBs);
+			TryAgainVbs ->
+			    next_loop_varbinds({subagent, SAPid, SAOid,
+						TryAgainVbs},
+					       [EndOfVb], MibView, Res, [],
+					       GbMaxVBs)
+		    end;
+		false ->
+		    %% bad index from subagent
+		    {genErr, (hd(SAVbs))#varbind.org_index, []}
+	    end;
+	{ErrorStatus, OrgIndex} ->
+ 	    ?vdebug("next loop varbinds: next subagent"
+ 		    "~n   ErrorStatus: ~p"
+ 		    "~n   OrgIndex:    ~p",
+ 		    [ErrorStatus,OrgIndex]),
+ 	    {ErrorStatus, OrgIndex, []}
+    end;
+next_loop_varbinds([], [], _MibView, Res, _LAVb, _GbMaxVBs) ->
+    ?vt("next_loop_varbinds -> entry when done", []),
+    {noError, 0, Res}.
+
+try_get_instance(_Vb, #me{mfa = {M, F, A}, asn1_type = ASN1Type}) ->
+    ?vtrace("try_get_instance -> entry with"
+	    "~n   M: ~p"
+	    "~n   F: ~p"
+	    "~n   A: ~p", [M,F,A]),
+    Result = (catch ?LIB:dbg_apply(M, F, [get | A])),
+    % mib shall return {value, <a-nice-value-within-range>} |
+    % {noValue, noSuchName} (v1) | 
+    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
+    % everything else (including 'genErr') will generate 'genErr'.
+    ?AGENT:make_value_a_correct_value(Result, ASN1Type, {M, F, A}).
+
+tab_oid([]) -> [0];
+tab_oid(X) -> X.
+
+
+%%-----------------------------------------------------------------
+%% Perform a next, using the varbinds Oid if value is simple
+%% value. If value is {endOf<something>, NextOid}, use NextOid.
+%% This case happens when a table has returned endOfTable, or
+%% a subagent has returned endOfMibView.
+%%-----------------------------------------------------------------
+varbind_next(#varbind{value = Value, oid = Oid}, MibView) ->
+    ?vt("varbind_next -> entry with"
+ 	"~n   Value:   ~p"
+ 	"~n   Oid:     ~p"
+ 	"~n   MibView: ~p", [Value, Oid, MibView]),
+    case Value of
+	{endOfTable, NextOid} ->
+	    snmpa_mib:next(get(mibserver), NextOid, MibView);
+	{endOfMibView, NextOid} ->
+	    snmpa_mib:next(get(mibserver), NextOid, MibView);
+	_ ->
+	    snmpa_mib:next(get(mibserver), Oid, MibView)
+    end.
+
+get_next_table(#me{mfa = {M, F, A}}, TableOid, TableOids, MibView) ->
+    % We know that all TableOids have at least a column number as oid
+    ?vt("get_next_table -> entry with"
+	"~n   M:         ~p"
+	"~n   F:         ~p"
+	"~n   A:         ~p"
+	"~n   TableOid:  ~p"
+	"~n   TableOids: ~p"
+	"~n   MibView:   ~p", [M, F, A, TableOid, TableOids, MibView]),
+    Sorted = snmpa_svbl:sort_varbinds_rows(TableOids),
+    case get_next_values_all_rows(Sorted, M,F,A, [], TableOid) of
+	NewVbs when is_list(NewVbs) ->
+ 	    ?vt("get_next_table -> "
+		"~n   NewVbs: ~p", [NewVbs]),
+	    % We must now check each Vb for endOfTable and that it is
+	    % in the MibView. If not, it becomes a endOfTable. We 
+	    % collect all of these together.
+	    transform_tab_next_result(NewVbs, {[], []}, MibView);
+	{ErrorStatus, OrgIndex} ->
+	    {ErrorStatus, OrgIndex}
+    end.
+
+get_next_values_all_rows([Row | Rows], M, F, A, Res, TabOid) ->
+    {RowIndex, TableOids} = Row,
+    Cols = delete_index(TableOids),
+    ?vt("get_next_values_all_rows -> "
+	"~n   Cols: ~p", [Cols]),
+    Result = (catch ?LIB:dbg_apply(M, F, [get_next, RowIndex, Cols | A])),
+    ?vt("get_next_values_all_rows -> "
+ 	"~n   Result: ~p", [Result]),
+    case validate_tab_next_res(Result, TableOids, {M, F, A}, TabOid) of
+	Values when is_list(Values) -> 
+ 	    ?vt("get_next_values_all_rows -> "
+ 		"~n   Values: ~p", [Values]),
+	    NewRes = lists:append(Values, Res),
+	    get_next_values_all_rows(Rows, M, F, A, NewRes, TabOid);
+	{ErrorStatus, OrgIndex} ->
+	    {ErrorStatus, OrgIndex}
+    end;
+get_next_values_all_rows([], _M, _F, _A, Res, _TabOid) ->
+    Res.
+
+transform_tab_next_result([Vb | Vbs], {Res, EndOfs}, MibView) ->
+    case Vb#varbind.value of
+	{endOfTable, _} ->
+	    {ResVBs, EndOfVBs} = ?LIB:split_vbs(Vbs, Res, [Vb | EndOfs]),
+            {ok, ResVBs, EndOfVBs};
+	_ ->
+	    case snmpa_acm:validate_mib_view(Vb#varbind.oid, MibView) of
+		true ->
+		    transform_tab_next_result(Vbs, {[Vb|Res], EndOfs},MibView);
+		_ ->
+		    Oid = Vb#varbind.oid,
+		    NewEndOf = Vb#varbind{value = {endOfTable, Oid}},
+		    transform_tab_next_result(Vbs, {Res, [NewEndOf | EndOfs]},
+					      MibView)
+	    end
+    end;
+transform_tab_next_result([], {Res, EndOfs}, _MibView) ->
+    ?vt("transform_tab_next_result -> entry with: "
+ 	"~n   Res:    ~p"
+ 	"~n   EndIfs: ~p",[Res, EndOfs]),
+    {ok, Res, EndOfs}.
+
+
+
+%%-----------------------------------------------------------------
+%% Three cases:
+%%   1) All values ok
+%%   2) table_func returned {Error, ...}
+%%   3) Some value in Values list is erroneous.
+%% Args: Value is a list of values from table_func(get_next, ...)
+%%       TableOids is a list of {TabRestOid, OrgVb} 
+%%         each element in Values and TableOids correspond to each
+%%         other.
+%% Returns: List of NewVarbinds |
+%%          {ErrorStatus, OrgIndex}
+%%          (In the NewVarbinds list, the value may be endOfTable)
+%%-----------------------------------------------------------------
+validate_tab_next_res(Values, TableOids, Mfa, TabOid) ->
+     ?vt("validate_tab_next_res -> entry with: "
+	 "~n   Values:     ~p"
+	 "~n   TableOids:  ~p"
+	 "~n   Mfa:        ~p"
+	 "~n   TabOid:     ~p", [Values, TableOids, Mfa, TabOid]),
+    {_Col, _ASN1Type, OneIdx} = hd(TableOids),
+    validate_tab_next_res(Values, TableOids, Mfa, [], TabOid,
+			  next_oid(TabOid), OneIdx).
+validate_tab_next_res([{NextOid, Value} | Values],
+		      [{_ColNo, OrgVb, _Index} | TableOids],
+		      Mfa, Res, TabOid, TabNextOid, I) ->
+    ?vt("validate_tab_next_res -> entry with: "
+ 	"~n   NextOid:    ~p"
+ 	"~n   Value:      ~p"
+ 	"~n   Values:     ~p"
+ 	"~n   TableOids:  ~p"
+ 	"~n   Mfa:        ~p"
+ 	"~n   TabOid:     ~p", 
+ 	[NextOid, Value, Values, TableOids, Mfa, TabOid]),
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?vt("validate_tab_next_res -> OrgIndex: ~p", [OrgIndex]),
+    NextCompleteOid = lists:append(TabOid, NextOid),
+    case snmpa_mib:lookup(get(mibserver), NextCompleteOid) of
+	{table_column, #me{asn1_type = ASN1Type}, _TableEntryOid} ->
+  	    ?vt("validate_tab_next_res -> ASN1Type: ~p", [ASN1Type]),
+	    case ?AGENT:make_value_a_correct_value({value, Value}, ASN1Type, Mfa) of
+		{error, ErrorStatus} ->
+ 		    ?vt("validate_tab_next_res -> "
+ 			"~n   ErrorStatus: ~p", [ErrorStatus]),
+		    {ErrorStatus, OrgIndex};
+		{value, Type, NValue} ->
+ 		    ?vt("validate_tab_next_res -> "
+     			"~n   Type:   ~p"
+			"~n   NValue: ~p", [Type, NValue]),
+		    NewVb = OrgVb#varbind{oid = NextCompleteOid,
+					  variabletype = Type, value = NValue},
+		    validate_tab_next_res(Values, TableOids, Mfa,
+					  [NewVb | Res], TabOid, TabNextOid, I)
+	    end;
+	Error ->
+	    ?LIB:user_err("Invalid oid ~w from ~w (get_next). Using genErr => ~p",
+                          [NextOid, Mfa, Error]),
+	    {genErr, OrgIndex}
+    end;
+validate_tab_next_res([endOfTable | Values],
+		      [{_ColNo, OrgVb, _Index} | TableOids],
+		      Mfa, Res, TabOid, TabNextOid, I) ->
+     ?vt("validate_tab_next_res(endOfTable) -> entry with: "
+	 "~n   Values:     ~p"
+	 "~n   OrgVb:      ~p"
+	 "~n   TableOids:  ~p"
+	 "~n   Mfa:        ~p"
+	 "~n   Res:        ~p"
+	 "~n   TabOid:     ~p"
+	 "~n   TabNextOid: ~p"
+	 "~n   I:          ~p",
+	 [Values, OrgVb, TableOids, Mfa, Res, TabOid, TabNextOid, I]),
+    NewVb = OrgVb#varbind{value = {endOfTable, TabNextOid}},
+    validate_tab_next_res(Values, TableOids, Mfa, [NewVb | Res],
+			  TabOid, TabNextOid, I);
+validate_tab_next_res([], [], _Mfa, Res, _TabOid, _TabNextOid, _I) ->
+    Res;
+validate_tab_next_res([], [{_Col, _OrgVb, Index}|_], Mfa, _Res, _, _, _I) ->
+    ?LIB:user_err("Too few values returned from ~w (get_next)", [Mfa]),
+    {genErr, Index};
+validate_tab_next_res({genErr, ColNumber}, OrgCols,
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    OrgIndex = snmpa_svbl:col_to_orgindex(ColNumber, OrgCols),
+    ?AGENT:validate_err(table_next, {genErr, OrgIndex}, Mfa);
+validate_tab_next_res({error, Reason}, [{_ColNo, OrgVb, _Index} | _TableOids],
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?LIB:user_err("Erroneous return value ~w from ~w (get_next)",
+                  [Reason, Mfa]),
+    {genErr, OrgIndex};
+validate_tab_next_res(Error, [{_ColNo, OrgVb, _Index} | _TableOids],
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?LIB:user_err("Invalid return value ~w from ~w (get_next)",
+                  [Error, Mfa]),
+    {genErr, OrgIndex};
+validate_tab_next_res(TooMany, [], Mfa, _Res, _, _, I) ->
+    ?LIB:user_err("Too many values ~w returned from ~w (get_next)",
+                  [TooMany, Mfa]),
+    {genErr, I}.
+
+%%-----------------------------------------------------------------
+%% Func: get_next_sa/4
+%% Purpose: Loop the list of varbinds for the subagent.
+%%          Call subagent_get_next to retreive
+%%          the next varbinds.
+%% Returns: {ok, ListOfNewVbs, ListOfEndOfMibViewsVbs} |
+%%          {ErrorStatus, ErrorIndex}
+%%-----------------------------------------------------------------
+get_next_sa(SAPid, SAOid, SAVbs, MibView) ->
+    case catch ?AGENT:subagent_get_next(SAPid, MibView, SAVbs) of
+	{noError, 0, NewVbs} ->
+	    NewerVbs = transform_sa_next_result(NewVbs,SAOid,next_oid(SAOid)),
+	    {ResVBs, EndOfVBs} = ?LIB:split_vbs(NewerVbs),
+            {ok, ResVBs, EndOfVBs};
+	{ErrorStatus, ErrorIndex, _} ->
+	    {ErrorStatus, ErrorIndex};
+	{'EXIT', Reason} ->
+	    ?LIB:user_err("Lost contact with subagent (next) ~w. Using genErr",
+                          [Reason]),
+	    {genErr, 0}
+    end.
+
+%%-----------------------------------------------------------------
+%% Check for wrong prefix returned or endOfMibView, and convert
+%% into {endOfMibView, SANextOid}.
+%%-----------------------------------------------------------------
+transform_sa_next_result([Vb | Vbs], SAOid, SANextOid)
+  when Vb#varbind.value =:= endOfMibView ->
+    [Vb#varbind{value = {endOfMibView, SANextOid}} |
+     transform_sa_next_result(Vbs, SAOid, SANextOid)];
+transform_sa_next_result([Vb | Vbs], SAOid, SANextOid) ->
+    case lists:prefix(SAOid, Vb#varbind.oid) of
+	true ->
+	    [Vb | transform_sa_next_result(Vbs, SAOid, SANextOid)];
+	_ ->
+	    [Vb#varbind{oid = SANextOid, value = {endOfMibView, SANextOid}} |
+	     transform_sa_next_result(Vbs, SAOid, SANextOid)]
+    end;
+transform_sa_next_result([], _SAOid, _SANextOid) ->
+    [].
+
+
+next_oid(Oid) ->
+    case lists:reverse(Oid) of
+	[H | T] -> lists:reverse([H+1 | T]);
+	[] -> []
+    end.
+
+
+
+%%%-----------------------------------------------------------------
+%%% 5. GET-BULK REQUEST
+%%% 
+%%% In order to prevent excesses in reply sizes there are two 
+%%% preventive methods in place. One is to check that the encode
+%%% size does not exceed Max PDU size (this is mentioned in the
+%%% standard). The other is a simple VBs limit. That is, the 
+%%% resulting response cannot contain more then this number of VBs.
+%%%-----------------------------------------------------------------
+
+do_get_bulk(MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs) ->
+    ?vtrace("do_get_bulk -> entry with"
+	    "~n   MibView:        ~p"
+	    "~n   NonRepeaters:   ~p"
+	    "~n   MaxRepetitions: ~p"
+	    "~n   PduMS:          ~p"
+	    "~n   Varbinds:       ~p"
+	    "~n   GbMaxVBs:       ~p",
+	    [MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs]),
+    {NonRepVbs, RestVbs} = ?LIB:split_vbs_gb(NonRepeaters, Varbinds),
+    ?vt("do_get_bulk -> split: "
+	"~n   NonRepVbs: ~p"
+	"~n   RestVbs:   ~p", [NonRepVbs, RestVbs]),
+    case do_get_next(MibView, NonRepVbs, GbMaxVBs) of
+	{noError, 0, UResNonRepVbs} ->
+	    ?vt("do_get_bulk -> next noError: "
+		"~n   UResNonRepVbs: ~p", [UResNonRepVbs]),
+	    ResNonRepVbs = lists:keysort(#varbind.org_index, UResNonRepVbs),
+	    %% Decode the first varbinds, produce a reversed list of
+	    %% listOfBytes.
+	    case (catch enc_vbs(PduMS - ?empty_pdu_size, ResNonRepVbs)) of
+ 		{error, Idx, Reason} ->
+		    ?LIB:user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
+                    {genErr, Idx, []};
+                {SizeLeft, Res} when is_integer(SizeLeft) and is_list(Res) ->
+ 		    ?vtrace("do_get_bulk -> encoded: "
+			    "~n   SizeLeft: ~p"
+			    "~n   Res:      ~w", [SizeLeft, Res]),
+		    case (catch do_get_rep(SizeLeft, MibView, MaxRepetitions,
+					   RestVbs, Res, 
+					   length(UResNonRepVbs), GbMaxVBs)) of
+			{error, Idx, Reason} ->
+			    ?LIB:user_err("failed encoding varbind ~w:~n~p", 
+                                          [Idx, Reason]),
+			    {genErr, Idx, []};
+			Res when is_list(Res) ->
+			    ?vtrace("do get bulk -> Res: "
+				    "~n   ~w", [Res]),
+			    {noError, 0, conv_res(Res)};
+			{noError, 0, Data} = OK ->
+			    ?vtrace("do get bulk -> OK: "
+				    "~n   length(Data): ~w", [length(Data)]),
+			    OK;
+			Else ->
+			    ?vtrace("do get bulk -> Else: "
+				    "~n   ~w", [Else]),
+			    Else
+		    end;
+		Res when is_list(Res) ->
+		    {noError, 0, conv_res(Res)}
+	    end;
+
+	{ErrorStatus, Index, _} ->
+	    ?vdebug("do get bulk: "
+		    "~n   ErrorStatus: ~p"
+		    "~n   Index:       ~p",[ErrorStatus, Index]),
+	    {ErrorStatus, Index, []}
+    end.
+
+enc_vbs(SizeLeft, Vbs) ->
+    ?vt("enc_vbs -> entry with"
+	"~n   SizeLeft: ~w", [SizeLeft]),
+    Fun = fun(Vb, {Sz, Res}) when Sz > 0 ->
+		  ?vt("enc_vbs -> (fun) entry with"
+		      "~n   Vb:  ~p"
+		      "~n   Sz:  ~p"
+		      "~n   Res: ~w", [Vb, Sz, Res]),
+		  case (catch snmp_pdus:enc_varbind(Vb)) of
+		      {'EXIT', Reason} ->
+			  ?vtrace("enc_vbs -> encode failed: "
+				  "~n   Reason: ~p", [Reason]),
+			  throw({error, Vb#varbind.org_index, Reason});
+		      X ->
+			  ?vt("enc_vbs -> X: ~w", [X]),
+			  Lx = length(X),
+			  ?vt("enc_vbs -> Lx: ~w", [Lx]),
+			  if
+			      Lx < Sz ->
+				  {Sz - length(X), [X | Res]};
+			      true ->
+				  throw(Res)
+			  end
+		  end;
+	     (_Vb, {_Sz, [_H | T]}) ->
+		  ?vt("enc_vbs -> (fun) entry with"
+		      "~n   T: ~p", [T]),
+		  throw(T);
+	     (_Vb, {_Sz, []}) ->
+		  ?vt("enc_vbs -> (fun) entry", []),
+		  throw([])
+	  end,
+    lists:foldl(Fun, {SizeLeft, []}, Vbs).
+
+do_get_rep(Sz, MibView, MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) 
+  when MaxRepetitions >= 0 ->
+    do_get_rep(Sz, MibView, 0, MaxRepetitions, Varbinds, Res, 
+	       GbNumVBs, GbMaxVBs);
+do_get_rep(Sz, MibView, _MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) ->
+    do_get_rep(Sz, MibView, 0, 0, Varbinds, Res, GbNumVBs, GbMaxVBs).
+
+conv_res(ResVarbinds) ->
+    conv_res(ResVarbinds, []).
+conv_res([VbListOfBytes | T], Bytes) ->
+    conv_res(T, VbListOfBytes ++ Bytes);
+conv_res([], Bytes) ->
+    Bytes.
+
+%% The only other value, then a positive integer, is infinity.
+do_get_rep(_Sz, _MibView, Count, Max, _, _Res, GbNumVBs, GbMaxVBs) 
+  when (is_integer(GbMaxVBs) andalso (GbNumVBs > GbMaxVBs)) ->
+    ?vinfo("Max Get-BULK VBs limit (~w) exceeded (~w) when:"
+	   "~n   Count: ~p"
+	   "~n   Max:   ~p", [GbMaxVBs, GbNumVBs, Count, Max]),
+    {tooBig, 0, []};
+do_get_rep(_Sz, _MibView, Max, Max, _, Res, _GbNumVBs, _GbMaxVBs) ->
+    ?vt("do_get_rep -> done when: "
+	"~n   Res: ~p", [Res]),
+    {noError, 0, conv_res(Res)};
+do_get_rep(Sz, MibView, Count, Max, Varbinds, Res, GbNumVBs, GbMaxVBs) -> 
+    ?vt("do_get_rep -> entry when: "
+	"~n   Sz:    ~p"
+	"~n   Count: ~p"
+	"~n   Res:   ~w", [Sz, Count, Res]),
+    case try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) of
+	{noError, NextVarbinds, SizeLeft, Res2} -> 
+	    ?vt("do_get_rep -> noError: "
+		"~n   SizeLeft: ~p"
+		"~n   Res2:     ~p", [SizeLeft, Res2]),
+	    do_get_rep(SizeLeft, MibView, Count+1, Max, NextVarbinds,
+		       Res2 ++ Res, 
+		       GbNumVBs + length(Varbinds), GbMaxVBs);
+	{endOfMibView, _NextVarbinds, _SizeLeft, Res2} -> 
+	    ?vt("do_get_rep -> endOfMibView: "
+		"~n   Res2: ~p", [Res2]),
+	    {noError, 0, conv_res(Res2 ++ Res)};
+	{ErrorStatus, Index} ->
+	    ?vtrace("do_get_rep -> done when error: "
+		    "~n   ErrorStatus: ~p"
+		    "~n   Index:       ~p", [ErrorStatus, Index]),
+	    {ErrorStatus, Index, []}
+    end.
+
+try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) -> 
+    ?vt("try_get_bulk -> entry with"
+	"~n   Sz:       ~w"
+	"~n   MibView:  ~w"
+	"~n   Varbinds: ~w", [Sz, MibView, Varbinds]),
+    case do_get_next(MibView, Varbinds, GbMaxVBs) of
+	{noError, 0, UNextVarbinds} -> 
+	    ?vt("try_get_bulk -> noError: "
+		"~n   UNextVarbinds: ~p", [UNextVarbinds]),
+	    NextVarbinds = ?LIB:org_index_sort_vbs(UNextVarbinds),
+	    case (catch enc_vbs(Sz, NextVarbinds)) of
+		{error, Idx, Reason} ->
+		    ?LIB:user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
+		    ?vtrace("try_get_bulk -> encode error: "
+			    "~n   Idx:    ~p"
+			    "~n   Reason: ~p", [Idx, Reason]),
+		    {genErr, Idx};
+		{SizeLeft, Res} when is_integer(SizeLeft) andalso 
+				     is_list(Res) ->
+		    ?vt("try get bulk -> encode ok: "
+			"~n   SizeLeft: ~w"
+			"~n   Res:      ~w", [SizeLeft, Res]),
+		    {check_end_of_mibview(NextVarbinds),
+		     NextVarbinds, SizeLeft, Res};
+		Res when is_list(Res) ->
+		    ?vt("try get bulk -> Res: "
+			"~n   ~w", [Res]),
+		    {endOfMibView, [], 0, Res}
+	    end;
+	{ErrorStatus, Index, _} ->
+	    ?vt("try_get_bulk -> error: "
+		"~n   ErrorStatus: ~p"
+		"~n   Index:       ~p", [ErrorStatus, Index]),
+	    {ErrorStatus, Index}
+    end.
+
+%% If all variables in this pass are endOfMibView,
+%% there is no reason to continue.
+check_end_of_mibview([#varbind{value = endOfMibView} | T]) ->
+    check_end_of_mibview(T);
+check_end_of_mibview([]) -> endOfMibView;
+check_end_of_mibview(_) -> noError.
+
+
+
diff --git a/lib/snmp/src/agent/snmpa_get_lib.erl b/lib/snmp/src/agent/snmpa_get_lib.erl
new file mode 100644
index 0000000000..7929b10cf3
--- /dev/null
+++ b/lib/snmp/src/agent/snmpa_get_lib.erl
@@ -0,0 +1,253 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%
+%% Note that most of these functions *assume* that they are executed
+%% by the agent. If they are not they may note work as they require
+%% some properties to be set in the process dictionary!
+%%
+
+-module(snmpa_get_lib).
+
+-export([
+         split_vbs/1, split_vbs/3,
+         split_vbs_view/2,
+         split_vbs_gb/2,
+
+         agent_sort_vbs/1,
+         oid_sort_vbs/1, org_index_sort_vbs/1,
+
+         sa_split/1,
+
+         delete_prefixes/2,
+
+         dbg_apply/3,
+
+         user_err/2
+        ]).
+
+-include("snmpa_internal.hrl").
+-include("snmp_types.hrl").
+-include("snmp_debug.hrl").
+-include("snmp_verbosity.hrl").
+
+
+
+
+%%-----------------------------------------------------------------
+%% split_vbs/1,3
+%%
+%% Splits the list of varbinds (basically) into two lists. One
+%% of 'end of'-varbinds (mib view and tables) and then the rest
+%% of the varbinds.
+%%-----------------------------------------------------------------
+
+-spec split_vbs(VBs :: [snmp:varbind()]) ->
+                       {ResVBs   :: [snmp:varbind()], 
+                        EndOfVBs :: [snmp:varbind()]}.
+
+split_vbs(VBs) ->
+    split_vbs(VBs, [], []).
+
+-spec split_vbs(VBs    :: [snmp:varbind()],
+                Res    :: [snmp:varbind()],
+                EndOfs :: [snmp:varbind()]) ->
+                       {ResVBs   :: [snmp:varbind()],
+                        EndOfVBs :: [snmp:varbind()]}.
+
+split_vbs([], ResVBs, EndOfVBs) ->
+    {ResVBs, EndOfVBs};
+split_vbs([VB | VBs], Res, EndOfs) ->
+    case VB#varbind.value of
+        {endOfMibView, _} -> split_vbs(VBs, Res, [VB | EndOfs]);
+        {endOfTable, _}   -> split_vbs(VBs, Res, [VB | EndOfs]);
+        _                 -> split_vbs(VBs, [VB | Res], EndOfs)
+    end.
+
+
+
+%%-----------------------------------------------------------------
+%% split_vbs_view/2
+%%
+%% Splits a list of varbinds into two lists based on the provided
+%% MibView. One list of varbinds inside the MibView and one of
+%% varbinds outside the MibView.
+%%-----------------------------------------------------------------
+
+-spec split_vbs_view(VBs     :: [snmp:varbind()],
+                     MibView :: snmp_view_based_acm_mib:mibview()) ->
+                            {OutSideView :: [snmp:varbind()],
+                             InSideView  :: [snmp:varbind()]}.
+
+split_vbs_view(VBs, MibView) ->
+    ?vtrace("split the varbinds view", []),
+    split_vbs_view(VBs, MibView, [], []).
+
+split_vbs_view([], _MibView, Out, In) ->
+    {Out, In};
+split_vbs_view([VB | VBs], MibView, Out, In) ->
+    case snmpa_acm:validate_mib_view(VB#varbind.oid, MibView) of
+	true ->
+            split_vbs_view(VBs, MibView, Out, [VB | In]);
+	false ->
+            VB2 = VB#varbind{value = noSuchObject},
+            split_vbs_view(VBs, MibView, [VB2 | Out], In)
+    end.
+
+
+
+%%-----------------------------------------------------------------
+%% split_vbs_gb/2
+%%
+%% Performs a get-bulk split of the varbinds
+%%-----------------------------------------------------------------
+
+-spec split_vbs_gb(NonRepeaters :: integer(),
+                   VBs          :: [snmp:varbind()]) ->
+                          {NonRepVBs :: [snmp:varbind()], 
+                           RestVBs   :: [snmp:varbind()]}.
+
+split_vbs_gb(N, VBs) ->
+    split_vbs_gb(N, VBs, []).
+
+split_vbs_gb(N, Varbinds, Res) when N =< 0 ->
+    {Res, Varbinds};
+split_vbs_gb(N, [H | T], Res) ->
+    split_vbs_gb(N-1, T, [H | Res]);
+split_vbs_gb(_N, [], Res) ->
+    {Res, []}.
+
+
+
+%%-----------------------------------------------------------------
+%% agent_sort_vbs/1
+%%
+%% Sorts the varbinds into two categories. The first is varbinds
+%% belonging to "our" agent and the other is varbinds for 
+%% subagents.
+%%-----------------------------------------------------------------
+
+-spec agent_sort_vbs(VBs :: [snmp:varbind()]) ->
+                      {AgentVBs    :: [snmp:varbind()],
+                       SubAgentVBs :: [snmp:varbind()]}.
+
+agent_sort_vbs(VBs) ->
+    snmpa_svbl:sort_varbindlist(get(mibserver), VBs).
+
+
+%%-----------------------------------------------------------------
+%% oid_sort_vbs/1
+%%
+%% Sorts the varbinds based on their oid.
+%%-----------------------------------------------------------------
+
+-spec oid_sort_vbs(VBs :: [snmp:varbind()]) -> SortedVBs :: [snmp:varbind()].
+
+oid_sort_vbs(VBs) ->
+    lists:keysort(#varbind.oid, VBs).
+
+
+%%-----------------------------------------------------------------
+%% org_index_sort_vbs/1
+%%
+%% Sorts the varbinds based on their org_index.
+%%-----------------------------------------------------------------
+
+-spec org_index_sort_vbs(VBs :: [snmp:varbind()]) -> SortedVBs :: [snmp:varbind()].
+
+org_index_sort_vbs(Vbs) ->
+    lists:keysort(#varbind.org_index, Vbs).
+
+
+
+%%-----------------------------------------------------------------
+%% sa_split/1
+%%
+%% Splits a list of {oid(), varbind()} into two lists of oid() 
+%% and varbind. The resulting lists are reversed!
+%%-----------------------------------------------------------------
+
+-spec sa_split(SAVBs :: [{SAOid :: snmp:oid(), snmp:varbind()}]) ->
+                      {Oids :: [snmp:oid()], VBs :: [snmp:varbind()]}.
+
+sa_split(SAVBs) ->
+    snmpa_svbl:sa_split(SAVBs).
+
+
+
+%%-----------------------------------------------------------------
+%% delete_prefixes/2
+%%
+%% Takes an Oid prefix and a list of ivarbinds and produces a list
+%% of {ShortOid, ASN1Type}. The ShortOid is basically the oid with 
+%% the OidPrefix removed.
+%%-----------------------------------------------------------------
+
+-spec delete_prefixes(OidPrefix :: snmp:oid(),
+                      VBs       :: [snmp:ivarbind()]) ->
+                             [{ShortOid :: snmp:oid(),
+                               ASN1Type :: snmp:asn1_type()}].
+
+delete_prefixes(OidPrefix, IVBs) ->
+    [{snmp_misc:diff(Oid, OidPrefix), ME#me.asn1_type} ||
+        #ivarbind{varbind = #varbind{oid = Oid}, mibentry = ME} <- IVBs].
+
+
+
+%%-----------------------------------------------------------------
+%% dbg_apply/3
+%%
+%% Call instrumentation functions, but allow for debug printing
+%% of useful debug info.
+%%-----------------------------------------------------------------
+
+-spec dbg_apply(M :: atom(), F :: atom(), A :: list()) ->
+                       any().
+
+dbg_apply(M, F, A) ->
+    case get(verbosity) of
+	silence -> 
+	    apply(M,F,A);
+	_ ->
+	    ?vlog("~n   apply: ~w,~w,~p~n", [M,F,A]),
+	    Res = (catch apply(M,F,A)),
+	    case Res of
+		{'EXIT', Reason} ->
+		    ?vinfo("Call to: "
+			   "~n   Module:   ~p"
+			   "~n   Function: ~p"
+			   "~n   Args:     ~p"
+			   "~n"
+			   "~nresulted in an exit"
+			   "~n"
+			   "~n   ~p", [M, F, A, Reason]);
+		_ ->
+		    ?vlog("~n   returned: ~p", [Res])
+	    end,
+	    Res
+    end.
+
+
+%% ---------------------------------------------------------------------
+
+user_err(F, A) ->
+    snmpa_error:user_err(F, A).
+
+
diff --git a/lib/snmp/src/agent/snmpa_get_mechanism.erl b/lib/snmp/src/agent/snmpa_get_mechanism.erl
index 1a2133778e..7be4ae79a2 100644
--- a/lib/snmp/src/agent/snmpa_get_mechanism.erl
+++ b/lib/snmp/src/agent/snmpa_get_mechanism.erl
@@ -24,28 +24,45 @@
 %% This module defines the behaviour for the undocumented (hidden)
 %% get-mechanism feature. This allows for implementing your own
 %% handling of get, get-next and get-bulk requests.
-%% Probably only useful for special cases (optimization).
+%% Probably only useful for special cases (e.g. optimization).
 %%
 
 
 
-%% ----------- do_get/3 -----------------------------------------------------
+%% ----------- do_get/2,3 -----------------------------------------------------
+
+%% Purpose: Handles all VBs in a request that is inside the 
+%%          mibview (local).
+
+-callback do_get(UnsortedVBs    :: [snmp:varbind()],
+                 IsNotification :: boolean()) ->
+    {noError, 0, ResVBs :: [snmp:varbind()]} |
+    {ErrStatus :: snmp:error_status(), ErrIndex :: snmp:error_index(), []}.
+
+
+%% Purpose: Handles "get-requests".
 
 -callback do_get(MibView        :: snmp_view_based_acm_mib:mibview(), 
-                 VBs            :: [snmp:varbind()],
+                 UnsortedVBs    :: [snmp:varbind()],
                  IsNotification :: boolean()) ->
     {noError, 0, ResVBs :: [snmp:varbind()]} |
     {ErrStatus :: snmp:error_status(), ErrIndex :: snmp:error_index(), []}.
 
 
+
+
 %% ----------- do_get_next/2 ------------------------------------------------
 
--callback do_get_next(MibView :: snmp_view_based_acm_mib:mibview(),
-                      VBs     :: [snmp:varbind()]) ->
+%% Purpose: Handles "get-next-requests".
+
+-callback do_get_next(MibView     :: snmp_view_based_acm_mib:mibview(),
+                      UnsortedVBs :: [snmp:varbind()]) ->
     {noError, 0, ResVBs :: [snmp:varbind()]} |
     {ErrStatus :: snmp:error_status(), ErrIndex :: snmp:error_index(), []}.
 
 
+
+
 %% ----------- do_get_bulk/6 ------------------------------------------------
 
 -callback do_get_bulk(MibView        :: snmp_view_based_acm_mib:mibview(),
diff --git a/lib/snmp/src/agent/tmp/snmpa_get.erl b/lib/snmp/src/agent/tmp/snmpa_get.erl
new file mode 100644
index 0000000000..d1710f673c
--- /dev/null
+++ b/lib/snmp/src/agent/tmp/snmpa_get.erl
@@ -0,0 +1,859 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(snmpa_get).
+
+-behaviour(snmpa_get_mechanism).
+
+%%%-----------------------------------------------------------------
+%%% snmpa_get_mechanism exports
+%%%-----------------------------------------------------------------
+
+-export([
+         do_get/2, do_get/3,
+         do_get_next/2,
+         do_get_bulk/6
+        ]).
+
+%% Internal exports
+-export([do_get_next/3]).
+
+-include("snmpa_internal.hrl").
+-include("snmp_types.hrl").
+-include("snmp_debug.hrl").
+-include("snmp_verbosity.hrl").
+
+-ifndef(default_verbosity).
+-define(default_verbosity,silence).
+-endif.
+
+-define(empty_pdu_size, 21).
+
+-ifdef(snmp_extended_verbosity).
+-define(vt(F,A), ?vtrace(F, A)).
+-else.
+-define(vt(_F, _A), ok).
+-endif.
+
+
+-define(AGENT, snmpa_agent).
+-define(LIB,   snmpa_get_lib).
+
+
+
+%%% ================ GET ==========================================
+
+%%-----------------------------------------------------------------
+%% Func: do_get/2
+%% Purpose: Handles all VBs in a request that is inside the 
+%%          mibview (local).
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get(UnsortedVBs, IsNotification) ->
+    {MyIVBs, SubagentVBs} = ?LIB:sort_vbs(UnsortedVBs),
+    case do_get_local(MyIVBs, IsNotification) of
+	{noError, 0, NewMyVBs} ->
+	    case do_get_subagents(SubagentVBs, IsNotification) of
+		{noError, 0, NewSubagentVBs} ->
+		    {noError, 0, NewMyVBs ++ NewSubagentVBs};
+		{ErrorStatus, ErrorIndex, _} ->
+		    {ErrorStatus, ErrorIndex, []}
+	    end;
+	{ErrorStatus, ErrorIndex, _} -> 
+	    {ErrorStatus, ErrorIndex, []}
+    end.
+
+
+%%-----------------------------------------------------------------
+%% Func: do_get/3
+%% Purpose: do_get handles "getRequests".
+%% Pre: incoming varbinds have type == 'NULL', value == unSpecified
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get(MibView, UnsortedVBs, IsNotification) ->
+    {OutSideView, InSideView} = ?LIB:split_vbs_view(UnsortedVBs, MibView),
+    {Error, Index, NewVbs}    = do_get(InSideView, IsNotification),
+    {Error, Index, NewVbs ++ OutSideView}.
+        
+
+
+
+%%% ================ GET-NEXT =====================================
+
+%%-----------------------------------------------------------------
+%% Func: do_get_next/2
+%% Purpose: do_get_next handles "getNextRequests".
+%% Note: Even if it is SNMPv1, a varbind's value can be
+%%       endOfMibView. This is later converted to noSuchName.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%% Note2: ListOfNewVarbinds is not sorted in any order!!!
+%% Alg: First, the variables are sorted in OID order.
+%%
+%%      Second, next in the MIB is performed for each OID, and
+%%      the result is collected as: if next oid is a variable,
+%%      perform a get to retrieve its value; if next oid is in a
+%%      table, save this value and continue until we get an oid
+%%      outside this table. Then perform get_next on the table,
+%%      and continue with all endOfTables and the oid outside the
+%%      table; if next oid is an subagent, save this value and
+%%      continue as in the table case.
+%%
+%%      Third, each response is checked for endOfMibView, or (for
+%%      subagents) that the Oid returned has the correct prefix.
+%%      (This is necessary since an SA can be registered under many
+%%      separated subtrees, and if the last variable in the first
+%%      subtree is requested in a next, the SA will return the first
+%%      variable in the second subtree. This might be working, since
+%%      there may be a variable in between these subtrees.) For each
+%%      of these, a new get-next is performed, one at a time.
+%%      This alg. might be optimised in several ways. The most 
+%%      striking one is that the same SA might be called several
+%%      times, when one time should be enough. But it isn't clear
+%%      that this really matters, since many nexts across the same
+%%      subagent must be considered to be very rare.
+%%-----------------------------------------------------------------
+
+do_get_next(MibView, UnsortedVBs) ->
+    do_get_next(MibView, UnsortedVBs, infinity).
+
+%% The third argument is only used if we are called as result
+%% of a get-buld request.
+do_get_next(_MibView, UnsortedVBs, MaxVBs)
+  when (is_list(UnsortedVBs) andalso 
+        is_integer(MaxVBs) andalso
+        (length(UnsortedVBs) > MaxVBs)) ->
+    {tooBig, 0, []};
+do_get_next(MibView, UnsortedVBs, MaxVBs) ->
+    ?vt("do_get_next -> entry when"
+ 	"~n   MibView:          ~p"
+ 	"~n   UnsortedVBs: ~p", [MibView, UnsortedVBs]),
+    SortedVBs = ?LIB:oid_sort_vbs(UnsortedVBs),
+    ?vt("do_get_next -> "
+ 	"~n   SortedVBs: ~p", [SortedVBs]),
+    next_varbinds_loop([], SortedVBs, MibView, MaxVBs, [], []).
+
+
+
+next_varbinds_loop(_, Vbs, _MibView, MaxVBs, Res, _LAVb) 
+  when (is_integer(MaxVBs) andalso 
+	((length(Vbs) + length(Res)) > MaxVBs)) ->
+    {tooBig, 0, []};
+
+%% LAVb is Last Accessible Vb
+next_varbinds_loop([], [Vb | Vbs], MibView, MaxVBs, Res, LAVb) ->
+    ?vt("next_loop_varbinds -> entry when"
+ 	"~n   Vb:      ~p"
+ 	"~n   MibView: ~p", [Vb, MibView]),
+    case varbind_next(Vb, MibView) of
+	endOfMibView ->
+	    ?vt("next_varbinds_loop -> endOfMibView", []),
+	    RVb = if LAVb =:= [] -> Vb;
+		     true -> LAVb
+		  end,
+	    NewVb = RVb#varbind{variabletype = 'NULL', value = endOfMibView},
+	    next_varbinds_loop([], Vbs, MibView, MaxVBs, [NewVb | Res], []);
+
+	{variable, ME, VarOid} when ((ME#me.access =/= 'not-accessible') andalso 
+				     (ME#me.access =/= 'write-only') andalso 
+				     (ME#me.access =/= 'accessible-for-notify')) -> 
+	    ?vt("next_varbinds_loop -> variable: "
+		"~n   ME:     ~p"
+		"~n   VarOid: ~p", [ME, VarOid]),
+	    case ?LIB:try_get_instance(Vb, ME) of
+		{value, noValue, _NoSuchSomething} ->
+		    ?vt("next_varbinds_loop -> noValue", []),
+		    %% Try next one
+		    NewVb = Vb#varbind{oid   = VarOid, 
+				       value = 'NULL'},
+		    next_varbinds_loop([], [NewVb | Vbs], MibView, MaxVBs, Res, []);
+		{value, Type, Value} ->
+		    ?vt("next_varbinds_loop -> value"
+			"~n   Type:  ~p"
+			"~n   Value: ~p", [Type, Value]),
+		    NewVb = Vb#varbind{oid          = VarOid, 
+				       variabletype = Type,
+				       value        = Value},
+		    next_varbinds_loop([], Vbs, MibView, MaxVBs,
+                                       [NewVb | Res], []);
+		{error, ErrorStatus} ->
+		    ?vdebug("next varbinds loop:"
+			    "~n   ErrorStatus: ~p",[ErrorStatus]),
+		    {ErrorStatus, Vb#varbind.org_index, []}
+	    end;
+	{variable, _ME, VarOid} -> 
+	    ?vt("next_varbinds_loop -> variable: "
+		"~n   VarOid: ~p", [VarOid]),
+	    RVb = if LAVb =:= [] -> Vb;
+		     true -> LAVb
+		  end,
+	    NewVb = Vb#varbind{oid = VarOid, value = 'NULL'},
+	    next_varbinds_loop([], [NewVb | Vbs], MibView, MaxVBs, Res, RVb);
+	{table, TableOid, TableRestOid, ME} ->
+	    ?vt("next_varbinds_loop -> table: "
+		"~n   TableOid:     ~p"
+		"~n   TableRestOid: ~p"
+		"~n   ME:           ~p", [TableOid, TableRestOid, ME]),
+	    next_varbinds_loop({table, TableOid, ME,
+				[{?LIB:tab_oid(TableRestOid), Vb}]},
+			       Vbs, MibView, MaxVBs, Res, []);
+	{subagent, SubAgentPid, SAOid} ->
+	    ?vt("next_varbinds_loop -> subagent: "
+		"~n   SubAgentPid: ~p"
+		"~n   SAOid:       ~p", [SubAgentPid, SAOid]),
+	    NewVb = Vb#varbind{variabletype = 'NULL', value = 'NULL'},
+	    next_varbinds_loop({subagent, SubAgentPid, SAOid, [NewVb]},
+			       Vbs, MibView, MaxVBs, Res, [])
+    end;
+
+next_varbinds_loop({table, TableOid, ME, TabOids},
+		   [Vb | Vbs], MibView, MaxVBs, Res, _LAVb) ->
+    ?vt("next_varbinds_loop(table) -> entry with"
+ 	"~n   TableOid: ~p"
+ 	"~n   Vb:       ~p", [TableOid, Vb]),
+    case varbind_next(Vb, MibView) of
+	{table, TableOid, TableRestOid, _ME} ->
+	    next_varbinds_loop({table, TableOid, ME,
+				[{?LIB:tab_oid(TableRestOid), Vb} | TabOids]},
+			       Vbs, MibView, MaxVBs, Res, []);
+	_ ->
+	    case get_next_table(ME, TableOid, TabOids, MibView) of
+		{ok, TabRes, TabEndOfTabVbs} ->
+		    NewVbs = lists:append(TabEndOfTabVbs, [Vb | Vbs]),
+		    NewRes = lists:append(TabRes, Res),
+		    next_varbinds_loop([], NewVbs, MibView, MaxVBs, NewRes, []);
+		{ErrorStatus, OrgIndex} ->
+		    ?vdebug("next varbinds loop: next varbind"
+			    "~n   ErrorStatus: ~p"
+			    "~n   OrgIndex:    ~p",
+			    [ErrorStatus,OrgIndex]),
+		    {ErrorStatus, OrgIndex, []}
+	    end
+    end;
+next_varbinds_loop({table, TableOid, ME, TabOids},
+                   [], MibView, MaxVBs, Res, _LAVb) ->
+    ?vt("next_varbinds_loop(table) -> entry with"
+	"~n   TableOid: ~p", [TableOid]),
+    case get_next_table(ME, TableOid, TabOids, MibView) of
+	{ok, TabRes, TabEndOfTabVbs} ->
+ 	    ?vt("next_varbinds_loop(table) -> get_next_table result:"
+		"~n   TabRes:         ~p"
+		"~n   TabEndOfTabVbs: ~p", [TabRes, TabEndOfTabVbs]),
+	    NewRes = lists:append(TabRes, Res),
+	    next_varbinds_loop([], TabEndOfTabVbs, MibView, MaxVBs, NewRes, []);
+	{ErrorStatus, OrgIndex} ->
+	    ?vdebug("next varbinds loop: next table"
+		    "~n   ErrorStatus: ~p"
+		    "~n   OrgIndex:    ~p",
+		    [ErrorStatus,OrgIndex]),
+	    {ErrorStatus, OrgIndex, []}
+    end;
+
+next_varbinds_loop({subagent, SAPid, SAOid, SAVbs},
+		   [Vb | Vbs], MibView, MaxVBs, Res, _LAVb) ->
+    ?vt("next_varbinds_loop(subagent) -> entry with"
+	"~n   SAPid: ~p"
+	"~n   SAOid: ~p"
+ 	"~n   Vb:    ~p", [SAPid, SAOid, Vb]),
+    case varbind_next(Vb, MibView) of
+	{subagent, _SubAgentPid, SAOid} ->
+	    next_varbinds_loop({subagent, SAPid, SAOid,
+				[Vb | SAVbs]},
+			       Vbs, MibView, MaxVBs, Res, []);
+	_ ->
+	    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
+		{ok, SARes, SAEndOfMibViewVbs} ->
+		    NewVbs = lists:append(SAEndOfMibViewVbs, [Vb | Vbs]),
+		    NewRes = lists:append(SARes, Res),
+		    next_varbinds_loop([], NewVbs, MibView, MaxVBs, NewRes, []);
+		{noSuchName, OrgIndex} ->
+		    %% v1 reply, treat this Vb as endOfMibView, and try again
+		    %% for the others.
+		    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
+			{value, EVb} ->
+			    NextOid = ?LIB:next_oid(SAOid),
+			    EndOfVb = 
+				EVb#varbind{oid = NextOid,
+					    value = {endOfMibView, NextOid}},
+			    case lists:delete(EVb, SAVbs) of
+				[] ->
+				    next_varbinds_loop([], [EndOfVb, Vb | Vbs],
+						       MibView, Res, [],
+						       MaxVBs);
+				TryAgainVbs ->
+				    next_varbinds_loop({subagent, SAPid, SAOid,
+							TryAgainVbs},
+						       [EndOfVb, Vb | Vbs],
+						       MibView, Res, [],
+                                                       MaxVBs)
+			    end;
+			false ->
+			    %% bad index from subagent
+			    {genErr, (hd(SAVbs))#varbind.org_index, []}
+		    end;
+		{ErrorStatus, OrgIndex} ->
+ 		    ?vdebug("next varbinds loop: next subagent"
+ 			    "~n   Vb:          ~p"
+ 			    "~n   ErrorStatus: ~p"
+ 			    "~n   OrgIndex:    ~p",
+ 			    [Vb,ErrorStatus,OrgIndex]),
+		    {ErrorStatus, OrgIndex, []}
+	    end
+    end;
+next_varbinds_loop({subagent, SAPid, SAOid, SAVbs},
+		   [], MibView, GbMaxVBs, Res, _LAVb) ->
+    ?vt("next_varbinds_loop(subagent) -> entry with"
+	 "~n   SAPid: ~p"
+	 "~n   SAOid: ~p", [SAPid, SAOid]),
+    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
+	{ok, SARes, SAEndOfMibViewVbs} ->
+	    NewRes = lists:append(SARes, Res),
+	    next_varbinds_loop([], SAEndOfMibViewVbs, MibView, GbMaxVBs,
+                               NewRes, []);
+	{noSuchName, OrgIndex} ->
+	    %% v1 reply, treat this Vb as endOfMibView, and try again for
+	    %% the others.
+	    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
+		{value, EVb} ->
+		    NextOid = ?LIB:next_oid(SAOid),
+		    EndOfVb = EVb#varbind{oid = NextOid,
+					  value = {endOfMibView, NextOid}},
+		    case lists:delete(EVb, SAVbs) of
+			[] ->
+			    next_varbinds_loop([], [EndOfVb], MibView, 
+                                               GbMaxVBs, Res, []);
+			TryAgainVbs ->
+			    next_varbinds_loop({subagent, SAPid, SAOid,
+						TryAgainVbs},
+					       [EndOfVb], MibView, GbMaxVBs,
+                                               Res, [])
+		    end;
+		false ->
+		    %% bad index from subagent
+		    {genErr, (hd(SAVbs))#varbind.org_index, []}
+	    end;
+	{ErrorStatus, OrgIndex} ->
+ 	    ?vdebug("next varbinds loop: next subagent"
+ 		    "~n   ErrorStatus: ~p"
+ 		    "~n   OrgIndex:    ~p",
+ 		    [ErrorStatus,OrgIndex]),
+ 	    {ErrorStatus, OrgIndex, []}
+    end;
+
+next_varbinds_loop([], [], _MibView, _GbMaxVBs, Res, _LAVb) ->
+    ?vt("next_varbinds_loop -> entry when done", []),
+    {noError, 0, Res}.
+
+
+%%-----------------------------------------------------------------
+%% Perform a next, using the varbinds Oid if value is simple
+%% value. If value is {endOf<something>, NextOid}, use NextOid.
+%% This case happens when a table has returned endOfTable, or
+%% a subagent has returned endOfMibView.
+%%-----------------------------------------------------------------
+varbind_next(#varbind{value = Value, oid = Oid}, MibView) ->
+    ?vt("varbind_next -> entry with"
+ 	"~n   Value:   ~p"
+ 	"~n   Oid:     ~p"
+ 	"~n   MibView: ~p", [Value, Oid, MibView]),
+    case Value of
+	{endOfTable, NextOid} ->
+	    snmpa_mib:next(get(mibserver), NextOid, MibView);
+	{endOfMibView, NextOid} ->
+	    snmpa_mib:next(get(mibserver), NextOid, MibView);
+	_ ->
+	    snmpa_mib:next(get(mibserver), Oid, MibView)
+    end.
+
+
+get_next_table(#me{mfa = {M, F, A}}, TableOid, TableOids, MibView) ->
+    % We know that all TableOids have at least a column number as oid
+    ?vt("get_next_table -> entry with"
+	"~n   M:         ~p"
+	"~n   F:         ~p"
+	"~n   A:         ~p"
+	"~n   TableOid:  ~p"
+	"~n   TableOids: ~p"
+	"~n   MibView:   ~p", [M, F, A, TableOid, TableOids, MibView]),
+    Sorted = snmpa_svbl:sort_varbinds_rows(TableOids),
+    case get_next_values_all_rows(Sorted, M,F,A, [], TableOid) of
+	NewVbs when is_list(NewVbs) ->
+ 	    ?vt("get_next_table -> "
+		"~n   NewVbs: ~p", [NewVbs]),
+	    % We must now check each Vb for endOfTable and that it is
+	    % in the MibView. If not, it becomes a endOfTable. We 
+	    % collect all of these together.
+	    transform_tab_next_result(NewVbs, {[], []}, MibView);
+	{ErrorStatus, OrgIndex} ->
+	    {ErrorStatus, OrgIndex}
+    end.
+
+
+get_next_values_all_rows([], _M, _F, _A, Res, _TabOid) ->
+    Res;
+get_next_values_all_rows([Row | Rows], M, F, A, Res, TabOid) ->
+    {RowIndex, TableOids} = Row,
+    Cols = ?LIB:delete_index(TableOids),
+    ?vt("get_next_values_all_rows -> "
+	"~n   Cols: ~p", [Cols]),
+    Result = (catch ?LIB:dbg_apply(M, F, [get_next, RowIndex, Cols | A])),
+    ?vt("get_next_values_all_rows -> "
+ 	"~n   Result: ~p", [Result]),
+    case validate_tab_next_res(Result, TableOids, {M, F, A}, TabOid) of
+	Values when is_list(Values) -> 
+ 	    ?vt("get_next_values_all_rows -> "
+ 		"~n   Values: ~p", [Values]),
+	    NewRes = lists:append(Values, Res),
+	    get_next_values_all_rows(Rows, M, F, A, NewRes, TabOid);
+	{ErrorStatus, OrgIndex} ->
+	    {ErrorStatus, OrgIndex}
+    end.
+
+transform_tab_next_result([Vb | Vbs], {Res, EndOfs}, MibView) ->
+    case Vb#varbind.value of
+	{endOfTable, _} ->
+	    ?LIB:split_vbs(Vbs, Res, [Vb | EndOfs]);
+	_ ->
+	    case snmpa_acm:validate_mib_view(Vb#varbind.oid, MibView) of
+		true ->
+		    transform_tab_next_result(Vbs, {[Vb|Res], EndOfs},MibView);
+		_ ->
+		    Oid = Vb#varbind.oid,
+		    NewEndOf = Vb#varbind{value = {endOfTable, Oid}},
+		    transform_tab_next_result(Vbs, {Res, [NewEndOf | EndOfs]},
+					      MibView)
+	    end
+    end;
+transform_tab_next_result([], {Res, EndOfs}, _MibView) ->
+    ?vt("transform_tab_next_result -> entry with: "
+ 	"~n   Res:    ~p"
+ 	"~n   EndIfs: ~p",[Res, EndOfs]),
+    {ok, Res, EndOfs}.
+
+
+%%-----------------------------------------------------------------
+%% Three cases:
+%%   1) All values ok
+%%   2) table_func returned {Error, ...}
+%%   3) Some value in Values list is erroneous.
+%% Args: Value is a list of values from table_func(get_next, ...)
+%%       TableOids is a list of {TabRestOid, OrgVb} 
+%%         each element in Values and TableOids correspond to each
+%%         other.
+%% Returns: List of NewVarbinds |
+%%          {ErrorStatus, OrgIndex}
+%%          (In the NewVarbinds list, the value may be endOfTable)
+%%-----------------------------------------------------------------
+validate_tab_next_res(Values, TableOids, Mfa, TabOid) ->
+     ?vt("validate_tab_next_res -> entry with: "
+	 "~n   Values:     ~p"
+	 "~n   TableOids:  ~p"
+	 "~n   Mfa:        ~p"
+	 "~n   TabOid:     ~p", [Values, TableOids, Mfa, TabOid]),
+    {_Col, _ASN1Type, OneIdx} = hd(TableOids),
+    validate_tab_next_res(Values, TableOids, Mfa, [], TabOid,
+			  ?LIB:next_oid(TabOid), OneIdx).
+validate_tab_next_res([{NextOid, Value} | Values],
+		      [{_ColNo, OrgVb, _Index} | TableOids],
+		      Mfa, Res, TabOid, TabNextOid, I) ->
+    ?vt("validate_tab_next_res -> entry with: "
+ 	"~n   NextOid:    ~p"
+ 	"~n   Value:      ~p"
+ 	"~n   Values:     ~p"
+ 	"~n   TableOids:  ~p"
+ 	"~n   Mfa:        ~p"
+ 	"~n   TabOid:     ~p", 
+ 	[NextOid, Value, Values, TableOids, Mfa, TabOid]),
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?vt("validate_tab_next_res -> OrgIndex: ~p", [OrgIndex]),
+    NextCompleteOid = lists:append(TabOid, NextOid),
+    case snmpa_mib:lookup(get(mibserver), NextCompleteOid) of
+	{table_column, #me{asn1_type = ASN1Type}, _TableEntryOid} ->
+  	    ?vt("validate_tab_next_res -> ASN1Type: ~p", [ASN1Type]),
+	    case ?LIB:make_value_a_correct_value({value, Value}, ASN1Type, Mfa) of
+		{error, ErrorStatus} ->
+ 		    ?vt("validate_tab_next_res -> "
+ 			"~n   ErrorStatus: ~p", [ErrorStatus]),
+		    {ErrorStatus, OrgIndex};
+		{value, Type, NValue} ->
+ 		    ?vt("validate_tab_next_res -> "
+     			"~n   Type:   ~p"
+			"~n   NValue: ~p", [Type, NValue]),
+		    NewVb = OrgVb#varbind{oid = NextCompleteOid,
+					  variabletype = Type, value = NValue},
+		    validate_tab_next_res(Values, TableOids, Mfa,
+					  [NewVb | Res], TabOid, TabNextOid, I)
+	    end;
+	Error ->
+	    ?LIB:user_err("Invalid oid ~w from ~w (get_next). Using genErr => ~p",
+		     [NextOid, Mfa, Error]),
+	    {genErr, OrgIndex}
+    end;
+validate_tab_next_res([endOfTable | Values],
+		      [{_ColNo, OrgVb, _Index} | TableOids],
+		      Mfa, Res, TabOid, TabNextOid, I) ->
+     ?vt("validate_tab_next_res(endOfTable) -> entry with: "
+	 "~n   Values:     ~p"
+	 "~n   OrgVb:      ~p"
+	 "~n   TableOids:  ~p"
+	 "~n   Mfa:        ~p"
+	 "~n   Res:        ~p"
+	 "~n   TabOid:     ~p"
+	 "~n   TabNextOid: ~p"
+	 "~n   I:          ~p",
+	 [Values, OrgVb, TableOids, Mfa, Res, TabOid, TabNextOid, I]),
+    NewVb = OrgVb#varbind{value = {endOfTable, TabNextOid}},
+    validate_tab_next_res(Values, TableOids, Mfa, [NewVb | Res],
+			  TabOid, TabNextOid, I);
+validate_tab_next_res([], [], _Mfa, Res, _TabOid, _TabNextOid, _I) ->
+    Res;
+validate_tab_next_res([], [{_Col, _OrgVb, Index}|_], Mfa, _Res, _, _, _I) ->
+    ?LIB:user_err("Too few values returned from ~w (get_next)", [Mfa]),
+    {genErr, Index};
+validate_tab_next_res({genErr, ColNumber}, OrgCols,
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    OrgIndex = snmpa_svbl:col_to_orgindex(ColNumber, OrgCols),
+    ?AGENT:validate_err(table_next, {genErr, OrgIndex}, Mfa);
+validate_tab_next_res({error, Reason}, [{_ColNo, OrgVb, _Index} | _TableOids],
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?LIB:user_err("Erroneous return value ~w from ~w (get_next)",
+	     [Reason, Mfa]),
+    {genErr, OrgIndex};
+validate_tab_next_res(Error, [{_ColNo, OrgVb, _Index} | _TableOids],
+		      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
+    #varbind{org_index = OrgIndex} = OrgVb,
+    ?LIB:user_err("Invalid return value ~w from ~w (get_next)",
+                  [Error, Mfa]),
+    {genErr, OrgIndex};
+validate_tab_next_res(TooMany, [], Mfa, _Res, _, _, I) ->
+    ?LIB:user_err("Too many values ~w returned from ~w (get_next)",
+                  [TooMany, Mfa]),
+    {genErr, I}.
+
+
+%%-----------------------------------------------------------------
+%% Func: get_next_sa/4
+%% Purpose: Loop the list of varbinds for the subagent.
+%%          Call subagent_get_next to retreive
+%%          the next varbinds.
+%% Returns: {ok, ListOfNewVbs, ListOfEndOfMibViewsVbs} |
+%%          {ErrorStatus, ErrorIndex}
+%%-----------------------------------------------------------------
+get_next_sa(SAPid, SAOid, SAVbs, MibView) ->
+    case catch subagent_get_next(SAPid, MibView, SAVbs) of
+	{noError, 0, NewVbs} ->
+	    NewerVbs = transform_sa_next_result(NewVbs, SAOid,
+                                                ?LIB:next_oid(SAOid)),
+	    ?LIB:split_vbs(NewerVbs);
+	{ErrorStatus, ErrorIndex, _} ->
+	    {ErrorStatus, ErrorIndex};
+	{'EXIT', Reason} ->
+	    ?LIB:user_err("Lost contact with subagent (next) ~w. Using genErr",
+                          [Reason]),
+	    {genErr, 0}
+    end.
+
+
+%%-----------------------------------------------------------------
+%% Check for wrong prefix returned or endOfMibView, and convert
+%% into {endOfMibView, SANextOid}.
+%%-----------------------------------------------------------------
+transform_sa_next_result([Vb | Vbs], SAOid, SANextOid)
+  when Vb#varbind.value =:= endOfMibView ->
+    [Vb#varbind{value = {endOfMibView, SANextOid}} |
+     transform_sa_next_result(Vbs, SAOid, SANextOid)];
+transform_sa_next_result([Vb | Vbs], SAOid, SANextOid) ->
+    case lists:prefix(SAOid, Vb#varbind.oid) of
+	true ->
+	    [Vb | transform_sa_next_result(Vbs, SAOid, SANextOid)];
+	_ ->
+	    [Vb#varbind{oid = SANextOid, value = {endOfMibView, SANextOid}} |
+	     transform_sa_next_result(Vbs, SAOid, SANextOid)]
+    end;
+transform_sa_next_result([], _SAOid, _SANextOid) ->
+    [].
+
+
+
+%%% ================ GET-BULK =====================================
+%%%
+%%% In order to prevent excesses in reply sizes there are two 
+%%% preventive methods in place. One is to check that the encode
+%%% size does not exceed Max PDU size (this is mentioned in the
+%%% standard). The other is a simple VBs limit. That is, the 
+%%% resulting response cannot contain more then this number of VBs.
+%%%
+
+do_get_bulk(MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs) ->
+    ?vtrace("do_get_bulk -> entry with"
+	    "~n   MibView:        ~p"
+	    "~n   NonRepeaters:   ~p"
+	    "~n   MaxRepetitions: ~p"
+	    "~n   PduMS:          ~p"
+	    "~n   Varbinds:       ~p"
+	    "~n   GbMaxVBs:       ~p",
+	    [MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs]),
+    {NonRepVbs, RestVbs} = ?LIB:split_gb_vbs(NonRepeaters, Varbinds),
+    ?vt("do_get_bulk -> split: "
+	"~n   NonRepVbs: ~p"
+	"~n   RestVbs:   ~p", [NonRepVbs, RestVbs]),
+    case do_get_next(MibView, NonRepVbs, GbMaxVBs) of
+	{noError, 0, UResNonRepVbs} ->
+	    ?vt("do_get_bulk -> next noError: "
+		"~n   UResNonRepVbs: ~p", [UResNonRepVbs]),
+	    ResNonRepVbs = lists:keysort(#varbind.org_index, UResNonRepVbs),
+	    %% Decode the first varbinds, produce a reversed list of
+	    %% listOfBytes.
+	    case (catch enc_vbs(PduMS - ?empty_pdu_size, ResNonRepVbs)) of
+ 		{error, Idx, Reason} ->
+		    ?LIB:user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
+                    {genErr, Idx, []};
+                {SizeLeft, Res} when is_integer(SizeLeft) and is_list(Res) ->
+ 		    ?vtrace("do_get_bulk -> encoded: "
+			    "~n   SizeLeft: ~p"
+			    "~n   Res:      ~w", [SizeLeft, Res]),
+		    case (catch do_get_rep(SizeLeft, MibView, MaxRepetitions,
+					   RestVbs, Res, 
+					   length(UResNonRepVbs), GbMaxVBs)) of
+			{error, Idx, Reason} ->
+			    ?LIB:user_err("failed encoding varbind ~w:~n~p", 
+                                          [Idx, Reason]),
+			    {genErr, Idx, []};
+			Res when is_list(Res) ->
+			    ?vtrace("do get bulk -> Res: "
+				    "~n   ~w", [Res]),
+			    {noError, 0, conv_res(Res)};
+			{noError, 0, Data} = OK ->
+			    ?vtrace("do get bulk -> OK: "
+				    "~n   length(Data): ~w", [length(Data)]),
+			    OK;
+			Else ->
+			    ?vtrace("do get bulk -> Else: "
+				    "~n   ~w", [Else]),
+			    Else
+		    end;
+		Res when is_list(Res) ->
+		    {noError, 0, conv_res(Res)}
+	    end;
+
+	{ErrorStatus, Index, _} ->
+	    ?vdebug("do get bulk: "
+		    "~n   ErrorStatus: ~p"
+		    "~n   Index:       ~p",[ErrorStatus, Index]),
+	    {ErrorStatus, Index, []}
+    end.
+
+
+enc_vbs(SizeLeft, Vbs) ->
+    ?vt("enc_vbs -> entry with"
+	"~n   SizeLeft: ~w", [SizeLeft]),
+    Fun = fun(Vb, {Sz, Res}) when Sz > 0 ->
+		  ?vt("enc_vbs -> (fun) entry with"
+		      "~n   Vb:  ~p"
+		      "~n   Sz:  ~p"
+		      "~n   Res: ~w", [Vb, Sz, Res]),
+		  case (catch snmp_pdus:enc_varbind(Vb)) of
+		      {'EXIT', Reason} ->
+			  ?vtrace("enc_vbs -> encode failed: "
+				  "~n   Reason: ~p", [Reason]),
+			  throw({error, Vb#varbind.org_index, Reason});
+		      X ->
+			  ?vt("enc_vbs -> X: ~w", [X]),
+			  Lx = length(X),
+			  ?vt("enc_vbs -> Lx: ~w", [Lx]),
+			  if
+			      Lx < Sz ->
+				  {Sz - length(X), [X | Res]};
+			      true ->
+				  throw(Res)
+			  end
+		  end;
+	     (_Vb, {_Sz, [_H | T]}) ->
+		  ?vt("enc_vbs -> (fun) entry with"
+		      "~n   T: ~p", [T]),
+		  throw(T);
+	     (_Vb, {_Sz, []}) ->
+		  ?vt("enc_vbs -> (fun) entry", []),
+		  throw([])
+	  end,
+    lists:foldl(Fun, {SizeLeft, []}, Vbs).
+
+do_get_rep(Sz, MibView, MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) 
+  when MaxRepetitions >= 0 ->
+    do_get_rep(Sz, MibView, 0, MaxRepetitions, Varbinds, Res, 
+	       GbNumVBs, GbMaxVBs);
+do_get_rep(Sz, MibView, _MaxRepetitions, Varbinds, Res, GbNumVBs, GbMaxVBs) ->
+    do_get_rep(Sz, MibView, 0, 0, Varbinds, Res, GbNumVBs, GbMaxVBs).
+
+conv_res(ResVarbinds) ->
+    conv_res(ResVarbinds, []).
+conv_res([VbListOfBytes | T], Bytes) ->
+    conv_res(T, VbListOfBytes ++ Bytes);
+conv_res([], Bytes) ->
+    Bytes.
+
+%% The only other value, then a positive integer, is infinity.
+do_get_rep(_Sz, _MibView, Count, Max, _, _Res, GbNumVBs, GbMaxVBs) 
+  when (is_integer(GbMaxVBs) andalso (GbNumVBs > GbMaxVBs)) ->
+    ?vinfo("Max Get-BULK VBs limit (~w) exceeded (~w) when:"
+	   "~n   Count: ~p"
+	   "~n   Max:   ~p", [GbMaxVBs, GbNumVBs, Count, Max]),
+    {tooBig, 0, []};
+do_get_rep(_Sz, _MibView, Max, Max, _, Res, _GbNumVBs, _GbMaxVBs) ->
+    ?vt("do_get_rep -> done when: "
+	"~n   Res: ~p", [Res]),
+    {noError, 0, conv_res(Res)};
+do_get_rep(Sz, MibView, Count, Max, Varbinds, Res, GbNumVBs, GbMaxVBs) -> 
+    ?vt("do_get_rep -> entry when: "
+	"~n   Sz:    ~p"
+	"~n   Count: ~p"
+	"~n   Res:   ~w", [Sz, Count, Res]),
+    case try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) of
+	{noError, NextVarbinds, SizeLeft, Res2} -> 
+	    ?vt("do_get_rep -> noError: "
+		"~n   SizeLeft: ~p"
+		"~n   Res2:     ~p", [SizeLeft, Res2]),
+	    do_get_rep(SizeLeft, MibView, Count+1, Max, NextVarbinds,
+		       Res2 ++ Res, 
+		       GbNumVBs + length(Varbinds), GbMaxVBs);
+	{endOfMibView, _NextVarbinds, _SizeLeft, Res2} -> 
+	    ?vt("do_get_rep -> endOfMibView: "
+		"~n   Res2: ~p", [Res2]),
+	    {noError, 0, conv_res(Res2 ++ Res)};
+	{ErrorStatus, Index} ->
+	    ?vtrace("do_get_rep -> done when error: "
+		    "~n   ErrorStatus: ~p"
+		    "~n   Index:       ~p", [ErrorStatus, Index]),
+	    {ErrorStatus, Index, []}
+    end.
+
+org_index_sort_vbs(Vbs) ->
+    lists:keysort(#varbind.org_index, Vbs).
+
+try_get_bulk(Sz, MibView, Varbinds, GbMaxVBs) -> 
+    ?vt("try_get_bulk -> entry with"
+	"~n   Sz:       ~w"
+	"~n   MibView:  ~w"
+	"~n   Varbinds: ~w", [Sz, MibView, Varbinds]),
+    case do_get_next(MibView, Varbinds, GbMaxVBs) of
+	{noError, 0, UNextVarbinds} -> 
+	    ?vt("try_get_bulk -> noError: "
+		"~n   UNextVarbinds: ~p", [UNextVarbinds]),
+	    NextVarbinds = org_index_sort_vbs(UNextVarbinds),
+	    case (catch enc_vbs(Sz, NextVarbinds)) of
+		{error, Idx, Reason} ->
+		    ?LIB:user_err("failed encoding varbind ~w:~n~p", [Idx, Reason]),
+		    ?vtrace("try_get_bulk -> encode error: "
+			    "~n   Idx:    ~p"
+			    "~n   Reason: ~p", [Idx, Reason]),
+		    {genErr, Idx};
+		{SizeLeft, Res} when is_integer(SizeLeft) andalso 
+				     is_list(Res) ->
+		    ?vt("try get bulk -> encode ok: "
+			"~n   SizeLeft: ~w"
+			"~n   Res:      ~w", [SizeLeft, Res]),
+		    {check_end_of_mibview(NextVarbinds),
+		     NextVarbinds, SizeLeft, Res};
+		Res when is_list(Res) ->
+		    ?vt("try get bulk -> Res: "
+			"~n   ~w", [Res]),
+		    {endOfMibView, [], 0, Res}
+	    end;
+	{ErrorStatus, Index, _} ->
+	    ?vt("try_get_bulk -> error: "
+		"~n   ErrorStatus: ~p"
+		"~n   Index:       ~p", [ErrorStatus, Index]),
+	    {ErrorStatus, Index}
+    end.
+
+%% If all variables in this pass are endOfMibView,
+%% there is no reason to continue.
+check_end_of_mibview([#varbind{value = endOfMibView} | T]) ->
+    check_end_of_mibview(T);
+check_end_of_mibview([]) ->
+    endOfMibView;
+check_end_of_mibview(_) ->
+    noError.
+
+
+
+%%-----------------------------------------------------------------
+%% Internal
+%%-----------------------------------------------------------------
+
+%%-----------------------------------------------------------------
+%% Func: do_get_local/2
+%% Purpose: Loop the variablebindings list. We know that each varbind
+%%          in that list belongs to us.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get_local(IVBs, IsNotification) ->
+    do_get_local(IVBs, IsNotification, []).
+
+do_get_local([], _IsNotification, Res) -> 
+    {noError, 0, Res};
+do_get_local([IVB | IVBs], IsNotification, Res) ->
+    case ?LIB:try_get(IVB, IsNotification) of
+	NewVB when is_record(NewVB, varbind) ->
+	    do_get_local(IVBs, IsNotification, [NewVB | Res]);
+	NewVBs when is_list(NewVBs) ->
+	    do_get_local(IVBs, IsNotification, lists:append(NewVBs, Res));
+	{error, Error, OrgIndex} ->
+	    {Error, OrgIndex, []}
+    end.
+
+
+%%-----------------------------------------------------------------
+%% Func: do_get_subagents/2
+%% Purpose: Loop the list of varbinds for different subagents.
+%%          For each of them, call subagent_get to retreive
+%%          the values for them.
+%% Returns: {noError, 0, ListOfNewVarbinds} |
+%%          {ErrorStatus, ErrorIndex, []}
+%%-----------------------------------------------------------------
+
+do_get_subagents(SubagentVarbinds, IsNotification) ->
+    do_get_subagents(SubagentVarbinds, IsNotification, []).
+
+do_get_subagents([], _IsNotification, Res) ->
+    {noError, 0, Res};
+do_get_subagents([{SAPid, SAVBs} | Tail], IsNotification, Res) ->
+    {_SAOids, VBs} = ?LIB:sa_split(SAVBs),
+    case (catch subagent_get(SAPid, IsNotification, VBs)) of
+	{noError, 0, NewVBs} ->
+	    do_get_subagents(Tail, IsNotification, lists:append(NewVBs, Res));
+	{ErrorStatus, ErrorIndex, _} ->
+	    {ErrorStatus, ErrorIndex, []};
+	{'EXIT', Reason} ->
+	    ?LIB:user_err("Lost contact with subagent (get) ~w. Using genErr", 
+                          [Reason]),
+	    {genErr, 0, []} 
+    end.
+
+
+
+
diff --git a/lib/snmp/src/agent/tmp/snmpa_get_lib.erl b/lib/snmp/src/agent/tmp/snmpa_get_lib.erl
new file mode 100644
index 0000000000..2bd7e4a1d2
--- /dev/null
+++ b/lib/snmp/src/agent/tmp/snmpa_get_lib.erl
@@ -0,0 +1,507 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(snmpa_get_lib).
+
+-export([
+         try_get/2,
+         try_get_instance/1,
+
+         delete_prefixes/2,
+         delete_index/1,
+
+         sort_vbs/1,
+         split_gb_vbs/2,
+         split_vbs/1, split_vbs/3,
+         split_vbs_view/2,
+
+         make_value_a_correct_value/3,
+
+         dbg_apply/3,
+
+         user_err/2
+        ]).
+
+
+
+%% *** sort_vbs ***
+
+-spec sort_vbs(VBs :: [snmp:varbind()]) -> [snmp:ivarbind()].
+
+sort_vbs(VBs) ->
+    snmpa_svbl:sort_varbindlist(get(mibserver), VBs).
+
+
+%% *** split_vbs ***
+
+-spec split_gb_vbs(NonRepeaters :: integer(),
+                   VBs          :: [varbind()]) ->
+                          {NonRepVBs :: [varbind()], RestVBs :: [varbind()]}.
+
+split_gb_vbs(N, VBs) ->
+    split_gb_vbs(N, VBs, []).
+
+split_gb_vbs(N, Varbinds, Res) when N =< 0 ->
+    {Res, Varbinds};
+split_gb_vbs(N, [H | T], Res) ->
+    split_gb_vbs(N-1, T, [H | Res]);
+split_gb_vbs(_N, [], Res) ->
+    {Res, []}.
+     
+
+
+%% *** split_vbs_view ***
+
+-spec split_vbs_view(VBs     :: [varbind()],
+                     MibView :: snmp_view_based_acm_mib:mibview()) ->
+                            {OutSideView :: [varbind()],
+                             InSideView  :: [varbind()]}.
+
+split_vbs_view(VBs, MibView) ->
+    ?vtrace("split the varbinds view", []),
+    split_vbs_view(VBs, MibView, [], []).
+
+split_vbs_view([], _MibView, Out, In) ->
+    {Out, In};
+split_vbs_view([Vb | Vbs], MibView, Out, In) ->
+    case snmpa_acm:validate_mib_view(Vb#varbind.oid, MibView) of
+	true -> split_vbs_view(Vbs, MibView, Out, [Vb | In]);
+	false -> split_vbs_view(Vbs, MibView,
+				[Vb#varbind{value = noSuchObject} | Out], In)
+    end.
+
+
+
+%% *** split_vbs/1,3 ***
+%%
+%% Sort out the 'end of' things (mib view of tables).
+%%
+
+-spec split_vbs(VBs :: [varbind()]) ->
+                       {ok, Res :: [varbind()], EndOfs :: [varbond()]}.
+
+split_vbs(VBs) ->
+    split_vbs(VBs, [], []).
+
+-spec split_vbs(VBs :: [varbind()],
+                Res :: [varbind()],
+                EndOfs :: [varbond()]) ->
+                       {ok, Res :: [varbind()], EndOfs :: [varbond()]}.
+
+split_vbs([], Res, EndOfs) ->
+    {ok, Res, EndOfs};
+split_vbs([Vb | Vbs], Res, EndOfs) ->
+    case Vb#varbind.value of
+	{endOfMibView, _} -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
+	{endOfTable, _}   -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
+	_                 -> split_varbinds(Vbs, [Vb | Res], EndOfs)
+    end.
+
+
+next_oid(Oid) ->
+    case lists:reverse(Oid) of
+	[H | T] -> lists:reverse([H+1 | T]);
+	[] -> []
+    end.
+
+
+
+%% *** delete_prefixes ***
+
+-spec delete_prefixes(Prefix :: oid(),
+                      IVBs   :: [ivarbind()]) ->
+                             [{ShortOID :: snmp:oid(), 
+                               ASN1Type :: snmp:asn1_type()}].
+
+delete_prefixes(Prefix, IVBs) ->
+    [{snmp_misc:diff(Oid, Prefix), ME#me.asn1_type} ||
+        #ivarbind{varbind = #varbind{oid = Oid}, mibentry = ME} <- IVBs].
+
+
+
+%% *** delete_index ***
+
+-spec delete_index(TableOids :: [{Col :: integer(), 
+                                  Val :: term(), 
+                                  OrgIndex :: integer()}]) ->
+                          [Col :: integer()].
+
+delete_index(TableOids) ->
+    [Col || {Col, _Val, _OrgIndex} <- TableOids].
+
+
+
+%%-----------------------------------------------------------------
+%% transforms a (hopefully correct) return value ((perhaps) from a 
+%% mib-function) to a typed and guaranteed correct return value.
+%% An incorrect return value is transformed to {error, genErr}.
+%% A correct return value is on the form: 
+%% {error, <error-msg>} | {value, <variable-type>, <value>}
+%%-----------------------------------------------------------------
+
+-spec make_value_a_correct_value(Value :: term(),
+                                 ASN1  :: snmp:asn1_type(),
+                                 MFA   :: term()) ->
+                                        {error, Error :: atom()} |
+                                        {value, ValueType :: atom(), 
+                                         Value :: term()}.
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when Asn1#asn1_type.bertype =:= 'INTEGER' ->
+    check_integer(Val, Asn1, Mfa);
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when Asn1#asn1_type.bertype =:= 'Counter32' ->
+    check_integer(Val, Asn1, Mfa);
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when Asn1#asn1_type.bertype =:= 'Unsigned32' ->
+    check_integer(Val, Asn1, Mfa);
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when Asn1#asn1_type.bertype =:= 'TimeTicks' ->
+    check_integer(Val, Asn1, Mfa);
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when Asn1#asn1_type.bertype =:= 'Counter64' ->
+    check_integer(Val, Asn1, Mfa);
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when (Asn1#asn1_type.bertype =:= 'BITS') andalso is_list(Val) ->
+    {value,Kibbles} = snmp_misc:assq(kibbles,Asn1#asn1_type.assocList),
+    case snmp_misc:bits_to_int(Val,Kibbles) of
+	error ->
+	    wrongValue(Val, Mfa);
+	Int ->
+	    make_value_a_correct_value({value,Int},Asn1,Mfa)
+    end;
+
+make_value_a_correct_value({value, Val}, Asn1, Mfa)
+  when (Asn1#asn1_type.bertype =:= 'BITS') andalso is_integer(Val) ->
+    {value,Kibbles} = snmp_misc:assq(kibbles,Asn1#asn1_type.assocList),
+    {_Kibble,BitNo} = lists:last(Kibbles),
+    case (1 bsl (BitNo+1)) of
+	X when Val < X ->
+	    {value,'BITS',Val};
+	_Big ->
+	    wrongValue(Val, Mfa)
+    end;
+
+make_value_a_correct_value({value, String},
+			   #asn1_type{bertype = 'OCTET STRING',
+				      hi = Hi, lo = Lo}, Mfa) ->
+    check_octet_string(String, Hi, Lo, Mfa, 'OCTET STRING');
+
+make_value_a_correct_value({value, String},
+			   #asn1_type{bertype = 'IpAddress',
+				      hi = Hi, lo = Lo}, Mfa) ->
+    check_octet_string(String, Hi, Lo, Mfa, 'IpAddress');
+
+make_value_a_correct_value({value, Oid},
+			   #asn1_type{bertype = 'OBJECT IDENTIFIER'},
+			   _Mfa) ->
+    case snmp_misc:is_oid(Oid) of
+	true  -> {value, 'OBJECT IDENTIFIER', Oid};
+	_Else -> {error, wrongType}
+    end;
+
+make_value_a_correct_value({value, Val}, Asn1, _Mfa)
+  when Asn1#asn1_type.bertype =:= 'Opaque' ->
+    if is_list(Val) -> {value, 'Opaque', Val};
+       true -> {error, wrongType}
+    end;
+
+make_value_a_correct_value({noValue, noSuchObject}, _ASN1Type, _Mfa) ->
+    {value, noValue, noSuchObject};
+make_value_a_correct_value({noValue, noSuchInstance}, _ASN1Type, _Mfa) ->
+    {value, noValue, noSuchInstance};
+make_value_a_correct_value({noValue, noSuchName}, _ASN1Type, _Mfa) ->
+    %% Transform this into a v2 value.  It is converted to noSuchName
+    %% later if it was v1.  If it was v2, we use noSuchInstance.
+    {value, noValue, noSuchInstance};
+%% For backwards compatibility only - we really shouldn't allow this;
+%% it makes no sense to return unSpecified for a variable! But we did
+%% allow it previously. -- We transform unSpecified to noSuchInstance
+%% (OTP-3303).
+make_value_a_correct_value({noValue, unSpecified}, _ASN1Type, _Mfa) ->
+    {value, noValue, noSuchInstance};
+make_value_a_correct_value(genErr, _ASN1Type, _MFA) ->
+    {error, genErr};
+
+make_value_a_correct_value(_WrongVal, _ASN1Type, undef) ->
+    {error, genErr};
+
+make_value_a_correct_value(WrongVal, ASN1Type, Mfa) ->
+    user_err("Got ~w from ~w. (~w) Using genErr",
+	     [WrongVal, Mfa, ASN1Type]),
+    {error, genErr}.
+
+check_integer(Val, Asn1, Mfa) ->
+    case Asn1#asn1_type.assocList of
+	undefined -> check_size(Val, Asn1, Mfa);
+	Alist ->
+	    case snmp_misc:assq(enums, Alist) of
+		{value, Enums} -> check_enums(Val, Asn1, Enums, Mfa);
+		false -> check_size(Val, Asn1, Mfa)
+	    end
+    end.
+
+check_octet_string(String, Hi, Lo, Mfa, Type) ->
+    Len = (catch length(String)), % it might not be a list
+    case snmp_misc:is_string(String) of
+	true when Lo =:= undefined -> {value, Type, String};
+	true when Len =< Hi, Len >= Lo ->
+	    {value, Type, String};
+	true ->
+	    wrongLength(String, Mfa);
+	_Else ->
+	    wrongType(String, Mfa)
+    end.
+
+check_size(Val, #asn1_type{lo = Lo, hi = Hi, bertype = Type}, Mfa) 
+  when is_integer(Val) ->
+    ?vtrace("check size of integer: "
+	    "~n   Value:       ~p"
+	    "~n   Upper limit: ~p"
+	    "~n   Lower limit: ~p"
+	    "~n   BER-type:    ~p",
+	    [Val,Hi,Lo,Type]),
+    if
+	(Lo =:= undefined) andalso (Hi =:= undefined) -> {value, Type, Val};
+	(Lo =:= undefined) andalso is_integer(Hi) andalso (Val =< Hi) ->
+	    {value, Type, Val};
+	is_integer(Lo) andalso (Val >= Lo) andalso (Hi =:= undefined) ->
+	    {value, Type, Val};
+	is_integer(Lo) andalso is_integer(Hi) andalso (Val >= Lo) andalso (Val =< Hi) ->
+	    {value, Type, Val};
+	true ->
+	    wrongValue(Val, Mfa)
+    end;
+check_size(Val, _, Mfa) ->
+    wrongType(Val, Mfa).
+
+check_enums(Val, Asn1, Enums, Mfa) ->
+    Association = 
+	if
+	    is_integer(Val) -> lists:keysearch(Val, 2, Enums);
+	    is_atom(Val)    -> lists:keysearch(Val, 1, Enums);
+	    true            -> {error, wrongType}
+    end,
+    case Association of
+	{value, {_AliasIntName, Val2}} -> 
+	    {value, Asn1#asn1_type.bertype, Val2};
+	false ->
+	    wrongValue(Val, Mfa);
+	{error, wrongType} ->
+	    wrongType(Val, Mfa)
+    end.
+
+wrongLength(Val, Mfa) ->
+    report_err(Val, Mfa, wrongLength).
+
+wrongValue(Val, Mfa) ->
+    report_err(Val, Mfa, wrongValue).
+
+wrongType(Val, Mfa) ->
+    report_err(Val, Mfa, wrongType).
+
+report_err(_Val, undef, Err) ->
+    {error, Err};
+report_err(Val, Mfa, Err) ->
+    user_err("Got ~p from ~w. Using ~w", [Val, Mfa, Err]),
+    {error, Err}.
+
+
+
+
+is_valid_pdu_type('get-request')      -> true;
+is_valid_pdu_type('get-next-request') -> true;
+is_valid_pdu_type('get-bulk-request') -> true;
+is_valid_pdu_type('set-request')      -> true;
+is_valid_pdu_type(_)                  -> false.
+
+
+
+%%-----------------------------------------------------------------
+%% Func: try_get/2
+%% Returns: {error, ErrorStatus, OrgIndex} |
+%%          #varbind |
+%%          List of #varbind
+%%-----------------------------------------------------------------
+
+-spec try_get(IVB            :: ivarbind(),
+              IsNotification :: boolean()) ->
+                     {error, ErrorStatus, OrgIndex} | varbind() | [varbind()].
+
+try_get(IVb, IsNotification) when is_record(IVb, ivarbind) ->
+    ?vtrace("try_get(ivarbind) -> entry with"
+	    "~n   IVb: ~p", [IVb]),
+    get_var_value_from_ivb(IVb, IsNotification);
+try_get({TableOid, TableVbs}, IsNotification) ->
+    ?vtrace("try_get(table) -> entry with"
+	    "~n   TableOid: ~p"
+	    "~n   TableVbs: ~p", [TableOid, TableVbs]),
+    [#ivarbind{mibentry = MibEntry}|_] = TableVbs,
+    {NoAccessVbs, AccessVbs} =
+	check_all_table_vbs(TableVbs, IsNotification, [], []),
+    case get_tab_value_from_mib(MibEntry, TableOid, AccessVbs) of
+	{error, ErrorStatus, OrgIndex} ->
+	    {error, ErrorStatus, OrgIndex};
+	NVbs ->
+	    NVbs ++ NoAccessVbs
+    end.
+
+
+%%-----------------------------------------------------------------
+%% Func: try_get_instance/1
+%% Returns: {value, noValue, term()} |
+%%          {value, Type, Value} |
+%%          {error, ErrorStatus}
+%%-----------------------------------------------------------------
+
+-spec try_get_instance(ME :: snmp:me()) ->
+                              {value, noValue, term()} |
+                              {value, Type :: asn1_type(), Value :: term()} |
+                              {error, error_status()}.
+
+try_get_instance(#me{mfa = {M, F, A}, asn1_type = ASN1Type}) ->
+    ?vtrace("try_get_instance -> entry with"
+	    "~n   M: ~p"
+	    "~n   F: ~p"
+	    "~n   A: ~p", [M,F,A]),
+    Result = (catch dbg_apply(M, F, [get | A])),
+    % mib shall return {value, <a-nice-value-within-range>} |
+    % {noValue, noSuchName} (v1) | 
+    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
+    % everything else (including 'genErr') will generate 'genErr'.
+    make_value_a_correct_value(Result, ASN1Type, {M, F, A}).
+
+
+
+%%-----------------------------------------------------------------
+%% Returns: {error, ErrorStatus, OrgIndex} |
+%%          #varbind
+%%-----------------------------------------------------------------
+
+get_var_value_from_ivb(#ivarbind{status   = noError,
+                                 mibentry = ME,
+                                 varbind  = VB} = IVb, IsNotification) ->
+    ?vtrace("get_var_value_from_ivb(noError) -> entry", []),
+    #varbind{org_index = OrgIndex, oid = Oid} = Vb,
+    case ME#me.access of
+	'not-accessible' -> 
+	    Vb#varbind{value = noSuchInstance};
+	'accessible-for-notify' when (IsNotification =:= false) -> 
+	    Vb#varbind{value = noSuchInstance};
+	'write-only' -> 
+	    Vb#varbind{value = noSuchInstance};
+	_ -> 
+	    case get_var_value_from_mib(Me, Oid) of
+		{value, Type, Value} ->
+		    Vb#varbind{variabletype = Type, value = Value};
+		{error, ErrorStatus} ->
+		    {error, ErrorStatus, OrgIndex}
+	    end
+    end;
+get_var_value_from_ivb(#ivarbind{status = Status, varbind = VB}, _) ->
+    ?vtrace("get_var_value_from_ivb(~p) -> entry", [Status]),
+    VB#varbind{value = Status}.
+
+
+
+%%-----------------------------------------------------------------
+%% Func: get_var_value_from_mib/1
+%% Purpose: 
+%% Pre:     Oid is a correct instance Oid (lookup checked that).
+%% Returns: {error, ErrorStatus} |
+%%          {value, Type, Value}
+%% Returns: A correct return value (see make_value_a_correct_value)
+%%-----------------------------------------------------------------
+get_var_value_from_mib(#me{entrytype = variable,
+			   asn1_type = ASN1Type,
+			   mfa       = {Mod, Func, Args}},
+		       _Oid) ->
+    ?vtrace("get_var_value_from_mib(variable) -> entry when"
+	    "~n   Mod:  ~p"
+	    "~n   Func: ~p"
+	    "~n   Args: ~p", [Mod, Func, Args]),
+    Result = (catch dbg_apply(Mod, Func, [get | Args])),
+    % mib shall return {value, <a-nice-value-within-range>} |
+    % {noValue, noSuchName} (v1) | 
+    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
+    % everything else (including 'genErr') will generate 'genErr'.
+    make_value_a_correct_value(Result, ASN1Type, {Mod, Func, Args});
+
+get_var_value_from_mib(#me{entrytype = table_column,
+			   oid       = MeOid,
+			   asn1_type = ASN1Type,
+			   mfa       = {Mod, Func, Args}},
+		       Oid) ->
+    ?vtrace("get_var_value_from_mib(table_column) -> entry when"
+	    "~n   MeOid: ~p"
+	    "~n   Mod:   ~p"
+	    "~n   Func:  ~p"
+	    "~n   Args:  ~p"
+	    "~n   Oid:   ~p", [MeOid, Mod, Func, Args, Oid]),
+    Col      = lists:last(MeOid),
+    Indexes  = snmp_misc:diff(Oid, MeOid),
+    [Result] = (catch dbg_apply(Mod, Func, [get, Indexes, [Col] | Args])),
+    make_value_a_correct_value(Result, ASN1Type, 
+                               {Mod, Func, Args, Indexes, Col}).
+
+
+
+%%-----------------------------------------------------------------
+%% Runtime debugging of the agent.
+%%-----------------------------------------------------------------
+
+-spec dbg_apply(M :: atom(), F :: atom(), A :: list()) ->
+                       any().
+
+dbg_apply(M, F, A) ->
+    case get(verbosity) of
+	silence -> 
+	    apply(M,F,A);
+	_ ->
+	    ?vlog("~n   apply: ~w,~w,~p~n", [M,F,A]),
+	    Res = (catch apply(M,F,A)),
+	    case Res of
+		{'EXIT', Reason} ->
+		    ?vinfo("Call to: "
+			   "~n   Module:   ~p"
+			   "~n   Function: ~p"
+			   "~n   Args:     ~p"
+			   "~n"
+			   "~nresulted in an exit"
+			   "~n"
+			   "~n   ~p", [M, F, A, Reason]);
+		_ ->
+		    ?vlog("~n   returned: ~p", [Res])
+	    end,
+	    Res
+    end.
+
+
+%% ---------------------------------------------------------------------
+
+user_err(F, A) ->
+    snmpa_error:user_err(F, A).
+
+
diff --git a/lib/snmp/src/app/snmp.app.src b/lib/snmp/src/app/snmp.app.src
index d4bf0de61a..178309b488 100644
--- a/lib/snmp/src/app/snmp.app.src
+++ b/lib/snmp/src/app/snmp.app.src
@@ -49,6 +49,9 @@
              snmpa_error_io,
              snmpa_error_logger,
              snmpa_error_report,
+             snmpa_get,
+             snmpa_get_lib,
+             snmpa_get_mechanism, 
              snmpa_local_db,
              snmpa_mib,
              snmpa_mib_data,
diff --git a/lib/snmp/src/app/snmp.config b/lib/snmp/src/app/snmp.config
index b66ef5d7df..f35a636157 100644
--- a/lib/snmp/src/app/snmp.config
+++ b/lib/snmp/src/app/snmp.config
@@ -8,6 +8,7 @@
 %%                 {agent_verbosity,   verbosity()} |
 %%                 {versions,          versions()} |
 %%                 {priority,          atom()} |
+%%                 {get_mechanism,     module()} |
 %%                 {set_mechanism,     module()} |
 %%                 {authentication_service, module()} |
 %%                 {multi_threaded,    bool()} | 
diff --git a/lib/snmp/test/modules.mk b/lib/snmp/test/modules.mk
index 0f54e67c65..8b6547f9a9 100644
--- a/lib/snmp/test/modules.mk
+++ b/lib/snmp/test/modules.mk
@@ -31,6 +31,7 @@ SUITE_MODULES = \
 	snmp_agent_mibs_test \
 	snmp_agent_nfilter_test \
 	snmp_agent_test \
+	snmp_agent_test_get \
 	snmp_agent_conf_test \
 	snmp_agent_test_lib \
 	snmp_manager_config_test \
diff --git a/lib/snmp/test/snmp_agent_test_get.erl b/lib/snmp/test/snmp_agent_test_get.erl
new file mode 100644
index 0000000000..46436044f5
--- /dev/null
+++ b/lib/snmp/test/snmp_agent_test_get.erl
@@ -0,0 +1,55 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2019. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(snmp_agent_test_get).
+
+-behaviour(snmpa_get_mechanism).
+
+
+%%%-----------------------------------------------------------------
+%%% snmpa_get_mechanism exports
+%%%-----------------------------------------------------------------
+
+-export([
+         do_get/2, do_get/3,
+         do_get_next/2,
+         do_get_bulk/6
+        ]).
+
+
+
+do_get(UnsortedVarbinds, IsNotification) ->
+    snmpa_get:do_get(UnsortedVarbinds, IsNotification).
+
+
+
+do_get(MibView, UnsortedVarbinds, IsNotification) ->
+    snmpa_get:do_get(MibView, UnsortedVarbinds, IsNotification).
+
+
+do_get_next(MibView, UnsortedVBs) ->
+    snmpa_get:do_get_next(MibView, UnsortedVBs).
+
+
+
+
+do_get_bulk(MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds, GbMaxVBs) ->
+    snmpa_get:do_get_bulk(MibView, NonRepeaters, MaxRepetitions,
+                          PduMS, Varbinds, GbMaxVBs).
diff --git a/lib/snmp/test/snmp_agent_test_lib.erl b/lib/snmp/test/snmp_agent_test_lib.erl
index 66211d7105..c19c88528f 100644
--- a/lib/snmp/test/snmp_agent_test_lib.erl
+++ b/lib/snmp/test/snmp_agent_test_lib.erl
@@ -445,6 +445,7 @@ start_agent(Config, Vsns, Opts) ->
 	    [{versions,         Vsns}, 
 	     {agent_type,       master},
 	     {agent_verbosity,  trace},
+             {get_mechanism,    snmp_agent_test_get},
 	     {db_dir,           AgentDbDir},
 	     {audit_trail_log,  [{type, read_write},
 				 {dir,  AgentLogDir},
-- 
2.16.4

openSUSE Build Service is sponsored by