snmp_generic
Generic Functions for Implementing SNMP Objects in a Database
The module snmp_generic
contains generic functions for
implementing tables (and variables) using the SNMP built-in database
or Mnesia. These default functions are used if no instrumentation
function is provided for a managed object in a MIB. Sometimes,
it might be necessary to customize the behaviour of the default
functions. For example, in some situations a trap should be sent
if a row is deleted or modified, or some hardware is to be informed,
when information is changed.
The overall structure is shown in the following figure:
+---------------+ | SNMP Agent | +- - - - - - - -+ | MIB | +---------------+ | Association file (associates a MIB object with | snmp_generic:table_funct | snmp_generic:variable_func) +--------------------------------------+ | snmp_generic | Support for get-next, | | RowStatus operations +----------------------+---------------+ | snmpa_local_db | Mnesia | Database +--------------+-------+---------------+ | dets | ets | | (persistent) | | +--------------+-------+
Each function takes the argument NameDb
, which is a
tuple {Name, Db}
, to identify which database the
functions should use. Name
is the symbolic name of the
managed object as defined in the MIB, and Db
is either
volatile
, persistent
, or mnesia
. If it is
mnesia
, all variables are stored in the Mnesia table
snmp_variables
which must be a table with two attributes
(not a Mnesia SNMP table). The SNMP tables are stored in Mnesia
tables with the same names as the SNMP tables. All functions
assume that a Mnesia table exists with the correct name and
attributes. It is the programmer's responsibility to ensure
this. Specifically, if variables are stored in Mnesia, the table
snmp_variables
must be created by the programmer. The
record definition for this table is defined in the file
snmp/include/snmp_types.hrl
.
If an instrumentation function in the association file for a
variable myVar
does not have a name when compiling an
MIB, the compiler generates an entry.
{myVar, {snmp_generic, variable_func, [{myVar, Db]}}.
And for a table:
{myTable, {snmp_generic, table_func, [{myTable, Db]}}.
DATA TYPES
In the functions defined below, the following types are used:
name_db() = {name(), db()} name() = atom() db() = volatile | persistent | mnesia row_index() = [int()] columns() = [column()] | [{column(), value()}] column() = int() value() = term()
row_index()
Denotes the last part of the OID which specifies the index of the row in the table (see RFC1212, 4.1.6 for more information about INDEX).
columns()
Is a list of column numbers in the case of a get
operation, and a list of column numbers and values in the
case of a set
operation.
Functions
get_status_col(Name, Cols)
get_status_col(NameDb, Cols) -> {ok, StatusVal} | false
Name = name()
NameDb = name_db()
Cols = columns()
StatusVal = term()
Gets the value of the status column from Cols
.
This function can be used in instrumentation functions for
is_set_ok
, undo
or set
to check if the
status column of a table is modified.
get_index_types(Name)
Name = name()
Gets the index types of Name
This function can be used in instrumentation functions to retrieve the index types part of the table info.
get_table_info(Name, Item) -> table_info_result()
Name = name()
Item = table_item() | all
table_item() = nbr_of_cols | defvals | status_col | not_accessible | index_types | first_accessible | first_own_index
table_info_result() = Value | [{table_item(), Value}]
Value = term()
Get a specific table info item or, if Item
has the
value all
, a two tuple list (property list) is instead
returned with all the items and their respctive values of the
given table.
This function can be used in instrumentation functions to retrieve a given part of the table info.
table_func(Op1, NameDb)
table_func(Op2, RowIndex, Cols, NameDb) -> Ret
Op1 = new | delete
Op2 = get | next | is_set_ok | set | undo
NameDb = name_db()
RowIndex = row_index()
Cols = columns()
Ret = term()
This is the default instrumentation function for tables.
- The
new
function creates the table if it does not exist, but only if the database is the SNMP internal db. - The
delete
function does not delete the table from the database since unloading an MIB does not necessarily mean that the table should be destroyed. - The
is_set_ok
function checks that a row which is to be modified or deleted exists, and that a row which is to be created does not exist. - The
undo
function does nothing. - The
set
function checks if it has enough information to make the row change its status fromnotReady
tonotInService
(when a row has been been set tocreateAndWait
). If a row is set tocreateAndWait
, columns without a value are set tonoinit
. If Mnesia is used, the set functionality is handled within a transaction.
If it is possible for a manager to create or delete rows in
the table, there must be a RowStatus
column for
is_set_ok
, set
and undo
to work properly.
The function returns according to the specification of an instrumentation function.
table_get_elements(NameDb, RowIndex, Cols) -> Values
NameDb = name_db()
RowIndex = row_index()
Cols = columns()
Values = [value() | noinit]
Returns a list with values for all columns in Cols
.
If a column is undefined, its value is noinit
.
table_next(NameDb, RestOid) -> RowIndex | endOfTable
NameDb = name_db()
RestOid = [int()]
RowIndex = row_index()
Finds the indices of the next row in the table. RestOid
does not have to specify an existing row.
table_row_exists(NameDb, RowIndex) -> bool()
NameDb = name_db()
RowIndex = row_index()
Checks if a row in a table exists.
table_set_elements(NameDb, RowIndex, Cols) -> bool()
NameDb = name_db()
RowIndex = row_index()
Cols = columns()
Sets the elements in Cols
to the row specified by
RowIndex
. No checks are performed on the new values.
If the Mnesia database is used, this function calls
mnesia:write
to store the values. This means that
this function must be called from within a transaction
(mnesia:transaction/1
or mnesia:dirty/1
).
variable_func(Op1, NameDb)
variable_func(Op2, Val, NameDb) -> Ret
Op1 = new | delete | get
Op2 = is_set_ok | set | undo
NameDb = name_db()
Val = value()
Ret = term()
This is the default instrumentation function for variables.
The new
function creates a new variable in the
database with a default value as defined in the MIB, or a zero
value (depending on the type).
The delete
function does not delete the variable from
the database.
The function returns according to the specification of an instrumentation function.
variable_get(NameDb) -> {value, Value} | undefined
NameDb = name_db()
Value = value()
Gets the value of a variable.
variable_set(NameDb, NewVal) -> true | false
NameDb = name_db()
NewVal = value()
Sets a new value to a variable. The variable is created if it does not exist. No checks are made on the type of the new value.
Returns false
if the NameDb
argument
is incorrectly specified, otherwise true
.
Example
The following example shows an implementation of a table which is stored in Mnesia, but with some checks performed at set-request operations.
myTable_func(new, NameDb) -> % pass unchanged snmp_generic:table_func(new, NameDb). myTable_func(delete, NameDb) -> % pass unchanged snmp_generic:table_func(delete, NameDb). %% change row myTable_func(is_set_ok, RowIndex, Cols, NameDb) -> case snmp_generic:table_func(is_set_ok, RowIndex, Cols, NameDb) of {noError, 0} -> myApplication:is_set_ok(RowIndex, Cols); Err -> Err end; myTable_func(set, RowIndex, Cols, NameDb) -> case snmp_generic:table_func(set, RowIndex, Cols, NameDb), {noError, 0} -> % Now the row is updated, tell the application myApplication:update(RowIndex, Cols); Err -> Err end; myTable_func(Op, RowIndex, Cols, NameDb) -> % pass unchanged snmp_generic:table_func(Op, RowIndex, Cols, NameDb).
The .funcs
file would look like:
{myTable, {myModule, myTable_func, [{myTable, mnesia}]}}.