File 2528-snmp-agent-Truncate-variable-oids-in-a-notification.patch of Package erlang

From b50db97bd9c50961947192cb4662468b5121b742 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 17 Dec 2019 19:16:14 +0100
Subject: [PATCH 1/3] [snmp|agent] Truncate (variable) oids in a notification

When sending a notification (from the agent) its now
possible for each *variable* varbind to specify that
the oid should be "truncated". That is, remove the
trailing ".0". This is done by instead of the normal
oid (or aliasname) specify the tuple:

            {truncate, aliasname() | oid()}

OTP-16360
---
 lib/snmp/src/agent/snmpa_agent.erl |  16 ++-
 lib/snmp/src/agent/snmpa_get.erl   |   4 +-
 lib/snmp/src/agent/snmpa_trap.erl  | 199 +++++++++++++++++++++++++++++--------
 3 files changed, 171 insertions(+), 48 deletions(-)

diff --git a/lib/snmp/src/agent/snmpa_agent.erl b/lib/snmp/src/agent/snmpa_agent.erl
index 7489f74223..cc3bef15af 100644
--- a/lib/snmp/src/agent/snmpa_agent.erl
+++ b/lib/snmp/src/agent/snmpa_agent.erl
@@ -2072,7 +2072,7 @@ handle_send_trap(S, Notification, SendOpts) ->
     handle_send_trap(S, Notification, NotifyName, ContextName, Recv, Varbinds, 
 		     LocalEngineID, ExtraInfo).
 
-handle_send_trap(#state{type = Type} = S, 
+handle_send_trap(#state{type = Type} = S,
 		 Notification, NotifyName, ContextName, Recv, Varbinds, 
 		 LocalEngineID, ExtraInfo) ->
     ?vtrace("handle_send_trap -> entry with"
@@ -2082,7 +2082,7 @@ handle_send_trap(#state{type = Type} = S,
 	    "~n   ContextName:   ~p"
 	    "~n   LocalEngineID: ~p", 
 	    [Type, Notification, NotifyName, ContextName, LocalEngineID]),
-    case snmpa_trap:construct_trap(Notification, Varbinds) of
+    try snmpa_trap:construct_trap(Notification, Varbinds) of
 	{ok, TrapRecord, VarList} ->
 	    ?vtrace("handle_send_trap -> construction complete: "
 		    "~n   TrapRecord: ~p"
@@ -2102,7 +2102,10 @@ handle_send_trap(#state{type = Type} = S,
 				    LocalEngineID, ExtraInfo)
 	    end;
 	error ->
-	    error
+	    {error, failed_constructing_trap}
+    catch
+        C:E:Stack ->
+            {error, {failed_constructing_trap, C, E, Stack}}
     end.
 				
 
@@ -2178,7 +2181,7 @@ do_handle_send_trap(S, TrapRec, NotifyName, ContextName, Recv, Varbinds,
 	    {ok, S};
 	master_agent when S#state.multi_threaded =:= false ->
 	    ?vtrace("do_handle_send_trap -> send trap:"
-		    "~n   ~p", [TrapRec]),
+		    "~n   TrapRec: ~p", [TrapRec]),
 	    snmpa_trap:send_trap(TrapRec, NotifyName, ContextName,
 				 Recv, Vbs, LocalEngineID, ExtraInfo, 
 				 get(net_if)),
@@ -2272,7 +2275,7 @@ handle_discovery(#state{type = master_agent} = S, From,
 	    "~n   ContextName:  ~p" 
 	    "~n   Varbinds:     ~p", 
 	    [TargetName, Notification, ContextName, Varbinds]),
-    case snmpa_trap:construct_trap(Notification, Varbinds) of
+    try snmpa_trap:construct_trap(Notification, Varbinds) of
 	{ok, Record, InitVars} ->
 	    ?vtrace("handle_discovery -> trap construction complete: "
 		    "~n   Record:   ~p"
@@ -2282,6 +2285,9 @@ handle_discovery(#state{type = master_agent} = S, From,
 			   DiscoHandler, ExtraInfo);
 	error ->
 	    {error, failed_constructing_notification}
+    catch
+        C:E:Stack ->
+            {error, {failed_constructing_trap, C, E, Stack}}
     end;
 handle_discovery(_S, _From, 
 		 _TargetName, _Notification, _ContextName, _Varbinds, 
diff --git a/lib/snmp/src/agent/snmpa_get.erl b/lib/snmp/src/agent/snmpa_get.erl
index 8b16016d84..c4f4f44095 100644
--- a/lib/snmp/src/agent/snmpa_get.erl
+++ b/lib/snmp/src/agent/snmpa_get.erl
@@ -75,8 +75,8 @@
 %%          {ErrorStatus, ErrorIndex, []}
 %%-----------------------------------------------------------------
 
-%% There is now to properly spec the behaviour of the ?AGENT:subagent_get/3
-%% function (it *can* exit).
+%% There is no way to properly spec the behaviour of the
+%% ?AGENT:subagent_get/3 function (it *can* exit).
 -dialyzer({nowarn_function, do_get/3}).
 do_get(UnsortedVarbinds, IsNotification, _Extra) ->
     {MyVarbinds, SubagentVarbinds} = ?LIB:agent_sort_vbs(UnsortedVarbinds),
diff --git a/lib/snmp/src/agent/snmpa_trap.erl b/lib/snmp/src/agent/snmpa_trap.erl
index 2d00441e2a..4416508ec0 100644
--- a/lib/snmp/src/agent/snmpa_trap.erl
+++ b/lib/snmp/src/agent/snmpa_trap.erl
@@ -155,25 +155,56 @@ construct_trap(Trap, Varbinds) ->
 	    {ok, NRec, InitiatedVars}
     end.
 
+%% Variable value (without oid processing)
 alias_to_oid({Alias, Val}) when is_atom(Alias) ->
-    case snmpa_symbolic_store:aliasname_to_oid(Alias) of
-	{value, Oid} -> {lists:append(Oid, [0]), {value, Val}};
-	_ ->   	     {Alias, {value, Val}}
+    case alias2oid(Alias) of
+	Alias ->
+            {{keep, Alias}, {value, Val}};
+	Oid ->
+            {{keep, Oid}, {value, Val}}
+    end;
+alias_to_oid({Oid, Val}) when is_list(Oid) ->
+    {{keep, Oid}, {value, Val}};
+
+%% Variable value (with oid processing)
+alias_to_oid({{Process, Alias}, Val}) when is_atom(Alias) ->
+    case alias2oid(Alias) of
+	Alias ->
+            {{Process, Alias}, {value, Val}};
+	Oid ->
+            {{Process, Oid}, {value, Val}}
     end;
+alias_to_oid({{Process, Oid}, Val}) when is_list(Oid) ->
+    {{Process, Oid}, {value, Val}};
+
+%% Table Column value
 alias_to_oid({Alias, RowIndex, Val}) when is_atom(Alias) ->
+    case alias2oid(Alias, RowIndex) of
+        Alias ->
+            {Alias, RowIndex, {value, Val}};
+	Oid ->
+            {{keep, Oid}, {value, Val}}
+
+    end.
+
+alias2oid(Alias) ->
+    alias2oid(Alias, [0]).
+
+alias2oid(Alias, Append) ->
     case snmpa_symbolic_store:aliasname_to_oid(Alias) of
-	{value, Oid} -> {lists:append(Oid, RowIndex), {value, Val}};
-	_ ->   	     {Alias, RowIndex, {value, Val}}
-    end;
-alias_to_oid({Oid, Val}) -> {Oid, {value, Val}}.
+	{value, Oid} ->
+            lists:append(Oid, Append);
+	_ ->
+            Alias
+    end.
 
 
 %%-----------------------------------------------------------------
 %% Func: initiate_vars/2
 %% Args: ListOfVars is a list of {Oid, #asn1_type}
 %%       Varbinds is a list of 
-%%          {VariableOid, Value} | 
-%%          {VariableAtom, Value} |
+%%          {{Process, VariableOid}, Value} | 
+%%          {{Process, VariableAtom}, Value} |
 %%          {TableColAtom, RowIndex, Value}
 %% Purpose: For each variable specified in the TRAP-TYPE macro
 %%          (each in ListOfVars), check if it's got a value given
@@ -182,17 +213,17 @@ alias_to_oid({Oid, Val}) -> {Oid, {value, Val}}.
 %%            1) It has corresponding VariableOid. Use Value.
 %%            2) No corresponding VariableOid. No value.
 %% Returns: A list of
-%%            {VariableOid, #asn1_type, Value} |
-%%            {VariableOid, #asn1_type} |
-%%            {VariableOid, Value} |
-%%            {VariableAtom, Value} |
+%%            {{Process, VariableOid}, #asn1_type, Value} |
+%%            {{Process, VariableOid}, #asn1_type} |
+%%            {{Process, VariableOid}, Value} |
+%%            {{Process, VariableAtom}, Value} |
 %%            {TableColAtom, RowIndex, Value}
 %% NOTE: Executed at the initial SA
 %%-----------------------------------------------------------------
 initiate_vars([{Oid, Asn1Type} | T], Varbinds) ->
     case delete_oid_from_varbinds(Oid, Varbinds) of
 	{undefined, _, _} ->
-	    [{Oid, Asn1Type} | initiate_vars(T, Varbinds)];
+	    [{{keep, Oid}, Asn1Type} | initiate_vars(T, Varbinds)];
         %% Skip this oid!
 	{{value, ?NOTIFICATION_IGNORE_VB_VALUE}, _VarOid, RestOfVarbinds} ->
 	    initiate_vars(T, RestOfVarbinds);
@@ -202,18 +233,19 @@ initiate_vars([{Oid, Asn1Type} | T], Varbinds) ->
 initiate_vars([], Varbinds) ->
     Varbinds.
     
-delete_oid_from_varbinds(Oid, [{VarOid, Value} | T]) ->
+delete_oid_from_varbinds(Oid, [{{_Process, VarOid} = VOid, Value} | T]) ->
     case lists:prefix(Oid, VarOid) of
 	true -> 
-	    {Value, VarOid, T};
+	    {Value, VOid, T};
 	_ -> 
-	    {Value2, VarOid2, T2} = delete_oid_from_varbinds(Oid, T),
-	    {Value2, VarOid2, [{VarOid, Value} | T2]}
+	    {Value2, VOid2, T2} = delete_oid_from_varbinds(Oid, T),
+	    {Value2, VOid2, [{VOid, Value} | T2]}
     end;
 delete_oid_from_varbinds(Oid, [H | T]) ->
-    {Value, VarOid, T2} = delete_oid_from_varbinds(Oid, T),
-    {Value, VarOid, [H | T2]};
-delete_oid_from_varbinds(_Oid, []) -> {undefined, undefined, []}.
+    {Value, VOid, T2} = delete_oid_from_varbinds(Oid, T),
+    {Value, VOid, [H | T2]};
+delete_oid_from_varbinds(_Oid, []) ->
+    {undefined, undefined, []}.
 
 
 %%-----------------------------------------------------------------
@@ -228,6 +260,7 @@ try_initialise_vars(Mib, Varbinds) ->
     V = try_map_symbolic(Varbinds),
     try_find_type(V, Mib).
 
+
 %%-----------------------------------------------------------------
 %% Func: try_map_symbolic/1
 %% Args: Varbinds is a list returned from initiate_vars.
@@ -240,11 +273,13 @@ try_map_symbolic([Varbind | Varbinds]) ->
     [localise_oid(Varbind) | try_map_symbolic(Varbinds)];
 try_map_symbolic([]) -> [].
 
-localise_oid({VariableName, Value}) when is_atom(VariableName) ->
-    alias_to_oid({VariableName, Value});
-localise_oid({VariableName, RowIndex, Value}) when is_atom(VariableName) ->
-    alias_to_oid({VariableName, RowIndex, Value});
-localise_oid(X) -> X.
+localise_oid({{_Process, Alias}, _Value} = VB) when is_atom(Alias) ->
+    alias_to_oid(VB);
+localise_oid({Alias, _RowIndex, _Value} = VB) when is_atom(Alias) ->
+    alias_to_oid(VB);
+localise_oid(X) ->
+    X.
+
 
 %%-----------------------------------------------------------------
 %% Func: try_find_type/2
@@ -262,17 +297,32 @@ try_find_type([], _) -> [].
 
 localise_type({VariableOid, Type}, _Mib) 
   when is_list(VariableOid) andalso is_record(Type, asn1_type) ->
-    {VariableOid, Type};
+    {{keep, VariableOid}, Type};
+localise_type({{_Process, VariableOid} = VOid, Type}, _Mib) 
+  when is_list(VariableOid) andalso is_record(Type, asn1_type) ->
+    {VOid, Type};
 localise_type({VariableOid, Value}, Mib) when is_list(VariableOid) ->
     case snmpa_mib:lookup(Mib, VariableOid) of
 	{variable, ME} ->
-	    {VariableOid, ME#me.asn1_type, Value};
+	    {{keep, VariableOid}, ME#me.asn1_type, Value};
+	{table_column, ME, _} ->
+	    {{keep, VariableOid}, ME#me.asn1_type, Value};
+	_ ->
+	    {{keep, VariableOid}, Value}
+    end;
+localise_type({{_Process, VariableOid} = VOid, Value}, Mib)
+  when is_list(VariableOid) ->
+    case snmpa_mib:lookup(Mib, VariableOid) of
+	{variable, ME} ->
+	    {VOid, ME#me.asn1_type, Value};
 	{table_column, ME, _} ->
-	    {VariableOid, ME#me.asn1_type, Value};
+	    {VOid, ME#me.asn1_type, Value};
 	_ ->
-	    {VariableOid, Value}
+	    {VOid, Value}
     end;
-localise_type(X, _) -> X.
+localise_type(X, _) ->
+    X.
+
 
 %%-----------------------------------------------------------------
 %% Func: make_v1_trap_pdu/5
@@ -320,10 +370,22 @@ make_v2_notif_pdu(Vbs, Type) ->
 	 varbinds     = Vbs}.
 
 make_varbind_list(Varbinds) ->
-    {VariablesWithValueAndType, VariablesWithType} =
-	split_variables( order(Varbinds) ),
+    %% ?vtrace("make_varbind_list -> entry with"
+    %%         "~n      Varbinds: ~p", [Varbinds]),
+    OVarbinds = order(Varbinds),
+    %% ?vtrace("make_varbind_list -> order:"
+    %%         "~n      OVarbinds: ~p", [OVarbinds]),
+    {VariablesWithValueAndType, VariablesWithType} = split_variables(OVarbinds),
+    %% ?vtrace("make_varbind_list -> split:"
+    %%         "~n      VariablesWithValueAndType: ~p"
+    %%         "~n      VariablesWithType:         ~p",
+    %%         [VariablesWithValueAndType, VariablesWithType]),
     V    = get_values(VariablesWithType),
+    %% ?vtrace("make_varbind_list -> get-values:"
+    %%         "~n      V: ~p", [V]),
     Vars = lists:append([V, VariablesWithValueAndType]),
+    %% ?vtrace("make_varbind_list -> combined:"
+    %%         "~n      Vars: ~p", [Vars]),
     [make_varbind(Var) || Var <- unorder(lists:keysort(1, Vars))].
 
 
@@ -362,7 +424,7 @@ send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, ExtraInfo, NetIf) ->
 %% some info when we fail to send the trap(s).
 send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, LocalEngineID, 
 	  ExtraInfo, NetIf) ->
-    try 
+    try
 	begin
 	    do_send_trap(TrapRec, NotifyName, ContextName, Recv, Vbs, 
 			 LocalEngineID, ExtraInfo, NetIf)
@@ -425,10 +487,28 @@ get_values(VariablesWithType) ->
     
 make_varbind(Varbind) when is_record(Varbind, varbind) ->
     Varbind;
+make_varbind({Process, #varbind{oid = Oid} = VB}) ->
+    VB#varbind{oid = process_oid(Process, Oid)};
+make_varbind({Process, {VarOid, ASN1Type, Value}}) ->
+    case snmpa_agent:make_value_a_correct_value(Value, ASN1Type, undef) of
+	{value, Type, Val} ->
+	    #varbind{oid          = process_oid(Process, VarOid),
+                     variabletype = Type,
+                     value        = Val};
+	{error, Reason} -> 
+	    user_err("snmpa_trap: Invalid value: ~w"
+		     "~n   Oid:  ~w"
+		     "~n   Val:  ~w"
+		     "~n   Type: ~w",
+		     [Reason, VarOid, Value, ASN1Type]),
+	    throw(error)
+    end;
 make_varbind({VarOid, ASN1Type, Value}) ->
     case snmpa_agent:make_value_a_correct_value(Value, ASN1Type, undef) of
 	{value, Type, Val} ->
-	    #varbind{oid = VarOid, variabletype = Type, value = Val};
+	    #varbind{oid          = VarOid,
+                     variabletype = Type,
+                     value        = Val};
 	{error, Reason} -> 
 	    user_err("snmpa_trap: Invalid value: ~w"
 		     "~n   Oid:  ~w"
@@ -438,25 +518,59 @@ make_varbind({VarOid, ASN1Type, Value}) ->
 	    throw(error)
     end.
 
+process_oid(truncate, Oid) ->
+    case lists:reverse(Oid) of
+        [0 | RevRestOid] ->
+            lists:revse(RevRestOid);
+        _ ->
+            Oid
+    end;
+process_oid(_, Oid) ->
+    Oid.
+
+
+
+%% Order does two things:
+%% 1) Add an index to each element indicating where in the 
+%%    list it was found.
+%% 2) Extract the 'process oid' information (and add it to the index => ID)
+%% We can add whatever we want to the second element since the first,
+%% the integer (No) is unique.
+
 order(Varbinds) -> 
     order(Varbinds, 1).
 
-order([H | T], No) -> [{No, H} | order(T, No + 1)];
-order([], _) -> [].
+order([{{Process, OidOrAlias}, Type, Value} | T], No) ->
+    VB = {OidOrAlias, Type, Value},
+    ID = {No, Process},
+    [{ID, VB} | order(T, No + 1)];
+order([{{Process, OidOrAlias}, Type} | T], No) ->
+    VB = {OidOrAlias, Type},
+    ID = {No, Process},
+    [{ID, VB} | order(T, No + 1)];
+order([H | T], No) ->
+    ID = {No, keep},
+    [{ID, H} | order(T, No + 1)];
+order([], _) ->
+    [].
+
+
+unorder(OVbs) ->
+    [{Process, VB} || {{_No, Process}, VB} <- OVbs].
 
-unorder([{_No, H} | T]) -> [H | unorder(T)];
-unorder([]) -> [].
 
 extract_order([{No, {VarOid, _Type}} | T], Index) ->
     {Order, V} = extract_order(T, Index+1),
     {[No | Order], [#varbind{oid = VarOid, org_index = Index} | V]};
-extract_order([], _) -> {[], []}.
+extract_order([], _) ->
+    {[], []}.
 
 contract_order([No | Order], [Varbind | T]) ->
     [{No, Varbind} | contract_order(Order, T)];
 contract_order([], []) -> 
     [].
 
+
 split_variables([{No, {VarOid, Type, Val}} | T]) when is_list(VarOid) ->
     {A, B} = split_variables(T),
     {[{No, {VarOid, Type, Val}} | A], B};
@@ -464,6 +578,7 @@ split_variables([{No, {VarOid, Type}} | T])
   when is_list(VarOid) andalso is_record(Type, asn1_type) ->
     {A, B} = split_variables(T),
     {A, [{No, {VarOid, Type}} | B]};
+
 split_variables([{_No, {VarName, Value}} | _T]) ->
     user_err("snmpa_trap: Undefined variable ~w (~w)", [VarName, Value]),
     throw(error);
@@ -471,7 +586,9 @@ split_variables([{_No, {VarName, RowIndex, Value}} | _T]) ->
     user_err("snmpa_trap: Undefined variable ~w ~w (~w)",
 	     [VarName, RowIndex, Value]),
     throw(error);
-split_variables([]) -> {[], []}.
+
+split_variables([]) ->
+    {[], []}.
 
 
 %%-----------------------------------------------------------------
-- 
2.16.4

openSUSE Build Service is sponsored by