File 1503-snmp-Add-callback-attributes-to-snmp-filters.patch of Package erlang

From c7677c57f6d551992a31da284092fa85aadce330 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 27 Sep 2023 21:25:27 +0200
Subject: [PATCH 3/5] snmp: Add callback attributes to snmp filters

---
 lib/snmp/src/agent/snmpa.erl                  |  6 +-
 lib/snmp/src/agent/snmpa_conf.erl             | 59 ++++++++++++++++++-
 .../agent/snmpa_network_interface_filter.erl  | 46 ++++++++-------
 .../src/agent/snmpa_notification_filter.erl   | 14 +++--
 lib/snmp/src/app/snmp.erl                     |  4 ++
 lib/snmp/src/manager/snmpm.erl                |  5 +-
 .../snmpm_network_interface_filter.erl        | 42 ++++++-------
 7 files changed, 126 insertions(+), 50 deletions(-)

diff --git a/lib/snmp/src/agent/snmpa.erl b/lib/snmp/src/agent/snmpa.erl
index 74205e5716..c0193438fb 100644
--- a/lib/snmp/src/agent/snmpa.erl
+++ b/lib/snmp/src/agent/snmpa.erl
@@ -116,7 +116,9 @@
 -export([print_mib_info/0, print_mib_tables/0, print_mib_variables/0]).
 
 -export_type([
-              me/0, 
+              me/0,
+
+              pdu_type/0,
 
 	      %% Agent config types
 	      mib_storage/0, 
@@ -153,7 +155,7 @@
 -type table_name()    :: atom().
 -type variable_name() :: atom().
 -type mib_info()      :: {mib_module(), [table_name()], [variable_name()]}.
-
+-type pdu_type()      :: snmp:pdu_type().
 
 %%-----------------------------------------------------------------
 %% This utility function is used to convert an old SNMP application
diff --git a/lib/snmp/src/agent/snmpa_conf.erl b/lib/snmp/src/agent/snmpa_conf.erl
index f5c9c3a87f..4b0bc2e7f3 100644
--- a/lib/snmp/src/agent/snmpa_conf.erl
+++ b/lib/snmp/src/agent/snmpa_conf.erl
@@ -84,9 +84,66 @@
 
 
 -export_type([
-              usm_entry/0
+              usm_entry/0,
+              transportDomain/0,
+              transportAddress/0,
+              transportAddressWithPort/0,
+              transportAddressWithoutPort/0,
+              transportAddressMask/0
              ]).
 
+-type transportDomain() :: snmp:tdomain().
+
+-type transportAddress() ::
+    transportAddressIPv4() | transportAddressIPv6().
+
+-type transportAddressWithPort() ::
+        transportAddressIPv4WithPort() | transportAddressIPv6WithPort().
+
+-type transportAddressWithoutPort() ::
+        transportAddressIPv4WithoutPort() | transportAddressIPv6WithoutPort().
+
+-type transportAddressIPv4() ::
+        transportAddressIPv4WithPort() | transportAddressIPv4WithoutPort().
+
+-type transportAddressIPv4WithPort() ::
+   {transportAddressIPv4WithoutPort(), inet:port_number()} |
+   [IPA :: byte() | IPB :: byte() | IPC :: byte() | IPD :: byte() |
+    PortA :: byte() |  PortB :: byte()].
+
+-type transportAddressIPv4WithoutPort() ::
+   inet:ip4_address() | [IPA :: byte() | IPB :: byte() | IPC :: byte() | IPD :: byte()].
+
+-type transportAddressIPv6() ::
+    transportAddressIPv6WithPort() | transportAddressIPv6WithoutPort().
+
+-type transportAddressIPv6WithPort() ::
+   {transportAddressIPv6WithoutPort(), inet:port_number()} |
+   [IPA :: word() | IPB :: word() | IPC :: word() | IPD :: word() |
+    IPE :: word() | IPF :: word() | IPG :: word() | IPH :: word() |
+    inet:port_number()] |
+   [IPA :: word() | IPB :: word() | IPC :: word() | IPD :: word() |
+    IPE :: word() | IPF :: word() | IPG :: word() | IPH :: word() |
+    PortA :: byte() |  PortB :: byte()] |
+   {IPA :: byte(),IPB :: byte(),IPC :: byte(),IPD :: byte(),
+    IPE :: byte(),IPF :: byte(),IPG :: byte(),IPH :: byte(),
+    IPI :: byte(),IPJ :: byte(),IPK :: byte(),IPL :: byte(),
+    IPM :: byte(),IPN :: byte(),IPO :: byte(),IPP :: byte(),
+    PortA :: byte(), PortB :: byte()}.
+-type transportAddressIPv6WithoutPort() ::
+   inet:ip6_address() |
+   [IPA :: word() | IPB :: word() | IPC :: word() | IPD :: word() |
+    IPE :: word() | IPF :: word() | IPG :: word() | IPH :: word()] |
+   [IPA :: byte() | IPB :: byte() | IPC :: byte() | IPD :: byte() |
+    IPE :: byte() | IPF :: byte() | IPG :: byte() | IPH :: byte() |
+    IPI :: byte() | IPJ :: byte() | IPK :: byte() | IPL :: byte() |
+    IPM :: byte() | IPN :: byte() | IPO :: byte() | IPP :: byte()].
+
+-type transportAddressMask() ::
+    [] | transportAddressWithPort().
+
+-type word() :: 0..65535.
+
 -type usm_entry() :: {
                       EngineID    :: string(),
                       UserName    :: string(),
diff --git a/lib/snmp/src/agent/snmpa_network_interface_filter.erl b/lib/snmp/src/agent/snmpa_network_interface_filter.erl
index d67d945b8a..961975f237 100644
--- a/lib/snmp/src/agent/snmpa_network_interface_filter.erl
+++ b/lib/snmp/src/agent/snmpa_network_interface_filter.erl
@@ -19,38 +19,44 @@
 %%
 -module(snmpa_network_interface_filter).
 
--export([behaviour_info/1]).
 -export([verify/1]).
 
-
-behaviour_info(callbacks) ->
-    [{accept_recv,     2},
-     {accept_send,     2},
-     {accept_recv_pdu, 3},
-     {accept_send_pdu, 2}];
-behaviour_info(_) ->
-    undefined.
-
+-type transportDomain() :: snmpa_conf:transportDomain().
+-type transportAddressWithPort() :: snmpa_conf:transportAddressWithPort().
+-type pdu_type() :: snmpa:pdu_type().
 
 %% accept_recv({domain(), address()}) -> boolean()
-%% Called at the reception of a message 
+%% Called at the reception of a message
 %% (before *any* processing has been done).
-%% 
+-callback accept_recv(Domain, Addr) -> boolean() when
+      Domain :: transportDomain(),
+      Addr :: transportAddressWithPort().
 %% accept_send({domain(), address()}) -> boolean()
-%% Called before the sending of a message 
+%% Called before the sending of a message
 %% (after *all* processing has been done).
-%% 
+-callback accept_send(Domain, Addr) -> boolean() when
+      Domain :: transportDomain(),
+      Addr :: transportAddressWithPort().
 %% accept_recv_pdu({domain(), address()}, pdu_type()) -> boolean()
-%% Called after the basic message processing (MPD) has been done, 
-%% but before the pdu is handed over to the master-agent for 
+%% Called after the basic message processing (MPD) has been done,
+%% but before the pdu is handed over to the master-agent for
 %% primary processing.
-%% 
+-callback accept_recv_pdu(Domain, Addr, PduType) -> boolean() when
+      Domain :: transportDomain(),
+      Addr :: transportAddressWithPort(),
+      PduType :: pdu_type().
 %% accept_send_pdu([{domain(), address()}, ...] = Targets, pdu_type()) ->
 %%     boolean() | NewTargets
-%% Called before the basic message processing (MPD) is done, 
+%% Called before the basic message processing (MPD) is done,
 %% when a pdu has been received from the master-agent.
-%% 
-
+-callback accept_send_pdu(Targets, PduType) -> Reply when
+      Targets :: [Target],
+      Target :: {Domain, Addr},
+      Domain :: transportDomain(),
+      Addr :: transportAddressWithPort(),
+      PduType :: pdu_type(),
+      Reply :: boolean() | NewTargets,
+      NewTargets :: Targets.
 
 verify(Module) ->
     snmp_misc:verify_behaviour(?MODULE, Module).
diff --git a/lib/snmp/src/agent/snmpa_notification_filter.erl b/lib/snmp/src/agent/snmpa_notification_filter.erl
index 6300d450c7..b1729c1b7e 100644
--- a/lib/snmp/src/agent/snmpa_notification_filter.erl
+++ b/lib/snmp/src/agent/snmpa_notification_filter.erl
@@ -19,12 +19,9 @@
 %%
 -module(snmpa_notification_filter).
 
--export([behaviour_info/1]).
 
-behaviour_info(callbacks) ->
-    [{handle_notification, 2}];
-behaviour_info(_) ->
-    undefined.
+-type notification() :: term().
+-type trap() :: term().
 
 %% handle_notification(Notification, Data) -> Reply
 %% Notification -> notification() | trap()
@@ -35,3 +32,10 @@ behaviour_info(_) ->
 %% send -> This means it is ok for this filter to send the notification as is
 %% {send, NewNotif} -> Send this notification instead
 %% dont_sent -> Dont send this notification. 
+-callback handle_notification(Notif, Data) -> Reply when
+      Reply :: send |
+               {send, NewNotif} |
+               dont_send,
+      Notif :: notification() | trap(),
+      NewNotif :: notification() | trap(),
+      Data :: term().
diff --git a/lib/snmp/src/app/snmp.erl b/lib/snmp/src/app/snmp.erl
index c1f1c12acd..3392a8c2ac 100644
--- a/lib/snmp/src/app/snmp.erl
+++ b/lib/snmp/src/app/snmp.erl
@@ -89,6 +89,7 @@
 	      trappdu/0, 
 	      mib/0, 
 	      mib_name/0,
+              pdu_type/0,
 
               error_status/0,
               error_index/0,
@@ -141,6 +142,9 @@
 -type mib_name()      :: string().
 -type pdu()           :: #pdu{}.
 -type trappdu()       :: #trappdu{}.
+-type pdu_type()      :: 'get-request' | 'get-next-request' | 'get-response' |
+                         'set-request' | 'trap' | 'get-bulk-request' | 'inform-request' |
+                         'report'.
 
 %% We should really specify all of these, but they are so numerous...
 %% See the validate_err/1 function in the snmpa_agent.
diff --git a/lib/snmp/src/manager/snmpm.erl b/lib/snmp/src/manager/snmpm.erl
index 6c6a22e1f1..9df289b2e4 100644
--- a/lib/snmp/src/manager/snmpm.erl
+++ b/lib/snmp/src/manager/snmpm.erl
@@ -103,10 +103,10 @@
 -export_type([
 	      register_timeout/0, 
 	      agent_config/0, 
-	      target_name/0
+	      target_name/0,
+              pdu_type/0
 	     ]).
 
-
 -include_lib("snmp/src/misc/snmp_debug.hrl").
 -include_lib("snmp/include/snmp_types.hrl").
 -include("snmpm_atl.hrl").
@@ -134,6 +134,7 @@
 			{sec_name,         snmp:sec_name()}    | % Optional
 			{sec_level,        snmp:sec_level()}.    % Optional
 -type target_name() :: string().
+-type pdu_type() :: snmp:pdu_type() | 'trappdu'.
 
 
 %% This function is called when the snmp application
diff --git a/lib/snmp/src/manager/snmpm_network_interface_filter.erl b/lib/snmp/src/manager/snmpm_network_interface_filter.erl
index 54fa8645df..8a0bc9b405 100644
--- a/lib/snmp/src/manager/snmpm_network_interface_filter.erl
+++ b/lib/snmp/src/manager/snmpm_network_interface_filter.erl
@@ -19,37 +19,39 @@
 %%
 -module(snmpm_network_interface_filter).
 
--export([behaviour_info/1]).
 -export([verify/1]).
 
+-type transportDomain() :: snmpa_conf:transportDomain().
+-type transportAddressWithPort() :: snmpa_conf:transportAddressWithPort().
+-type pdu_type() :: snmpm:pdu_type().
 
-behaviour_info(callbacks) ->
-    [{accept_recv,     2}, 
-     {accept_send,     2},
-     {accept_recv_pdu, 3},
-     {accept_send_pdu, 3}];
-behaviour_info(_) ->
-    undefined.
-
-
-%% accept_recv(address(), port()) -> boolean() 
-%% Called at the reception of a message 
+%% accept_recv(address(), port()) -> boolean()
+%% Called at the reception of a message
 %% (before *any* processing has been done).
-%% 
+-callback accept_recv(Domain, Addr) -> boolean() when
+                             Domain :: transportDomain(),
+                             Addr :: transportAddressWithPort().
 %% accept_send(address(), port()) -> boolean()
-%% Called before the sending of a message 
+%% Called before the sending of a message
 %% (after *all* processing has been done).
-%% 
+-callback accept_send(Domain, Addr) -> boolean() when
+                             Domain :: transportDomain(),
+                             Addr :: transportAddressWithPort().
 %% accept_recv_pdu(Addr, Port, pdu_type()) -> boolean()
-%% Called after the basic message processing (MPD) has been done, 
-%% but before the pdu is handed over to the master-agent for 
+%% Called after the basic message processing (MPD) has been done,
+%% but before the pdu is handed over to the master-agent for
 %% primary processing.
-%% 
+-callback accept_recv_pdu(Domain, Addr, PduType) -> boolean() when
+                                 Domain :: transportDomain(),
+                                 Addr :: transportAddressWithPort(),
+                                 PduType :: pdu_type().
 %% accept_send_pdu(Addr, Port, pdu_type()) -> boolean()
 %% Called before the basic message processing (MPD) is done, 
 %% when a pdu has been received from the master-agent.
-%% 
-
+-callback accept_send_pdu(Domain, Addr, PduType) -> boolean() when
+                                 Domain :: transportDomain(),
+                                 Addr :: transportAddressWithPort(),
+                                 PduType :: pdu_type().
 
 verify(Module) ->
     snmp_misc:verify_behaviour(?MODULE, Module).
-- 
2.35.3

openSUSE Build Service is sponsored by