ct_snmp
Common Test user interface module for the OTP snmp application.
Common Test user interface module for the OTP snmp application
The purpose of this module is to make snmp configuration easier for
the test case writer. Many test cases can use default values for common
operations and then no snmp configuration files need to be supplied. When
it is necessary to change particular configuration parameters, a subset
of the relevant snmp configuration files may be passed to ct_snmp
by means of Common Test configuration files.
For more specialized configuration parameters, it is possible to place a
"simple snmp configuration file" in the test suite data directory.
To simplify the test suite, Common Test keeps track
of some of the snmp manager information. This way the test suite doesn't
have to handle as many input parameters as it would if it had to interface the
OTP snmp manager directly.
The following snmp manager and agent parameters are configurable:
{snmp, %%% Manager config [{start_manager, boolean()} % Optional - default is true {users, [{user_name(), [call_back_module(), user_data()]}]}, %% Optional {usm_users, [{usm_user_name(), [usm_config()]}]},%% Optional - snmp v3 only % managed_agents is optional {managed_agents,[{agent_name(), [user_name(), agent_ip(), agent_port(), [agent_config()]]}]}, {max_msg_size, integer()}, % Optional - default is 484 {mgr_port, integer()}, % Optional - default is 5000 {engine _id, string()}, % Optional - default is "mgrEngine" %%% Agent config {start_agent, boolean()}, % Optional - default is false {agent_sysname, string()}, % Optional - default is "ct_test" {agent_manager_ip, manager_ip()}, % Optional - default is localhost {agent_vsns, list()}, % Optional - default is [v2] {agent_trap_udp, integer()}, % Optional - default is 5000 {agent_udp, integer()}, % Optional - default is 4000 {agent_notify_type, atom()}, % Optional - default is trap {agent_sec_type, sec_type()}, % Optional - default is none {agent_passwd, string()}, % Optional - default is "" {agent_engine_id, string()}, % Optional - default is "agentEngine" {agent_max_msg_size, string()},% Optional - default is 484 %% The following parameters represents the snmp configuration files %% context.conf, standard.conf, community.conf, vacm.conf, %% usm.conf, notify.conf, target_addr.conf and target_params.conf. %% Note all values in agent.conf can be altered by the parametes %% above. All these configuration files have default values set %% up by the snmp application. These values can be overridden by %% suppling a list of valid configuration values or a file located %% in the test suites data dir that can produce a list %% of valid configuration values if you apply file:consult/1 to the %% file. {agent_contexts, [term()] | {data_dir_file, rel_path()}}, % Optional {agent_community, [term()] | {data_dir_file, rel_path()}},% Optional {agent_sysinfo, [term()] | {data_dir_file, rel_path()}}, % Optional {agent_vacm, [term()] | {data_dir_file, rel_path()}}, % Optional {agent_usm, [term()] | {data_dir_file, rel_path()}}, % Optional {agent_notify_def, [term()] | {data_dir_file, rel_path()}},% Optional {agent_target_address_def, [term()] | {data_dir_file, rel_path()}},% Optional {agent_target_param_def, [term()] | {data_dir_file, rel_path()}},% Optional ]}.
The MgrAgentConfName
parameter in the functions
should be a name you allocate in your test suite using a
require
statement.
Example (where MgrAgentConfName = snmp_mgr_agent
):
suite() -> [{require, snmp_mgr_agent, snmp}].
or
ct:require(snmp_mgr_agent, snmp).
Note that Usm users are needed for snmp v3 configuration and are not to be confused with users.
Snmp traps, inform and report messages are handled by the user callback module. For more information about this see the snmp application.
Note: It is recommended to use the .hrl-files created by the Erlang/OTP mib-compiler to define the oids. Example for the getting the erlang node name from the erlNodeTable in the OTP-MIB:
Oid = ?erlNodeEntry ++ [?erlNodeName, 1]
It is also possible to set values for snmp application configuration
parameters, such as config
, server
,
net_if
, etc (see the "Configuring the application" chapter in
the OTP snmp User's Guide for a list of valid parameters and types). This is
done by defining a configuration data variable on the following form:
{snmp_app, [{manager, [snmp_app_manager_params()]}, {agent, [snmp_app_agent_params()]}]}.
A name for the data needs to be allocated in the suite using
require
(see example above), and this name passed as
the SnmpAppConfName
argument to start/3
.
ct_snmp
specifies default values for some snmp application
configuration parameters (such as {verbosity,trace}
for the
config
parameter). This set of defaults will be
merged with the parameters specified by the user, and user values
override ct_snmp
defaults.
DATA TYPES
agent_config() = {Item, Value}
agent_ip() = ip()
agent_name() = atom()
agent_port() = integer()
call_back_module() = atom()
error_index() = integer()
error_status() = noError | atom()
ip() = string() | {integer(), integer(), integer(), integer()}
manager_ip() = ip()
oid() = [byte()]
oids() = [oid()]
rel_path() = string()
sec_type() = none | minimum | semi
snmp_app_agent_params() = term()
snmp_app_manager_params() = term()
snmpreply() = {error_status(), error_index(), varbinds()}
user_data() = term()
user_name() = atom()
usm_config() = {Item, Value}
usm_user_name() = string()
value_type() = o('OBJECT IDENTIFIER') | i('INTEGER') | u('Unsigned32') | g('Unsigned32') | s('OCTET STRING')
var_and_val() = {oid(), value_type(), value()}
varbind() = term()
varbinds() = [varbind()]
varsandvals() = [var_and_val()]
Functions
start(Config, MgrAgentConfName) -> ok
Equivalent to start(Config, MgrAgentConfName, undefined).
start(Config, MgrAgentConfName, SnmpAppConfName) -> ok
Config = [{Key, Value}]
Key = atom()
Value = term()
MgrAgentConfName = atom()
SnmpConfName = atom()
Starts an snmp manager and/or agent. In the manager case,
registrations of users and agents as specified by the configuration
MgrAgentConfName
will be performed. When using snmp
v3 also so called usm users will be registered. Note that users,
usm_users and managed agents may also be registered at a later time
using ct_snmp:register_users/2, ct_snmp:register_agents/2, and
ct_snmp:register_usm_users/2. The agent started will be
called snmp_master_agent
. Use ct_snmp:load_mibs/1 to load
mibs into the agent. With SnmpAppConfName
it's possible
to configure the snmp application with parameters such as config
,
mibs
, net_if
, etc. The values will be merged
with (and possibly override) default values set by ct_snmp
.
stop(Config) -> ok
Config = [{Key, Value}]
Key = atom()
Value = term()
Stops the snmp manager and/or agent removes all files created.
get_values(Agent, Oids, MgrAgentConfName) -> SnmpReply
Agent = agent_name()
Oids = oids()
MgrAgentConfName = atom()
SnmpReply = snmpreply()
Issues a synchronous snmp get request.
get_next_values(Agent, Oids, MgrAgentConfName) -> SnmpReply
Agent = agent_name()
Oids = oids()
MgrAgentConfName = atom()
SnmpReply = snmpreply()
Issues a synchronous snmp get next request.
set_values(Agent, VarsAndVals, MgrAgentConfName, Config) -> SnmpReply
Agent = agent_name()
Oids = oids()
MgrAgentConfName = atom()
Config = [{Key, Value}]
SnmpReply = snmpreply()
Issues a synchronous snmp set request.
set_info(Config) -> [{Agent, OldVarsAndVals, NewVarsAndVals}]
Config = [{Key, Value}]
Agent = agent_name()
OldVarsAndVals = varsandvals()
NewVarsAndVals = varsandvals()
Returns a list of all successful set requests performed in the test case in reverse order. The list contains the involved user and agent, the value prior to the set and the new value. This is intended to facilitate the clean up in the end_per_testcase function i.e. the undoing of the set requests and its possible side-effects.
register_users(MgrAgentConfName, Users) -> ok | {error, Reason}
MgrAgentConfName = atom()
Users = [user()]
Reason = term()
Register the manager entity (=user) responsible for specific agent(s). Corresponds to making an entry in users.conf.
This function will try to register the given users, without checking if any of them already exist. In order to change an already registered user, the user must first be unregistered.register_agents(MgrAgentConfName, ManagedAgents) -> ok | {error, Reason}
MgrAgentConfName = atom()
ManagedAgents = [agent()]
Reason = term()
Explicitly instruct the manager to handle this agent. Corresponds to making an entry in agents.conf
This function will try to register the given managed agents, without checking if any of them already exist. In order to change an already registered managed agent, the agent must first be unregistered.register_usm_users(MgrAgentConfName, UsmUsers) -> ok | {error, Reason}
MgrAgentConfName = atom()
UsmUsers = [usm_user()]
Reason = term()
Explicitly instruct the manager to handle this USM user. Corresponds to making an entry in usm.conf
This function will try to register the given users, without checking if any of them already exist. In order to change an already registered user, the user must first be unregistered.unregister_users(MgrAgentConfName) -> ok
MgrAgentConfName = atom()
Reason = term()
Unregister all users.
unregister_users(MgrAgentConfName, Users) -> ok
MgrAgentConfName = atom()
Users = [user_name()]
Reason = term()
Unregister the given users.
unregister_agents(MgrAgentConfName) -> ok
MgrAgentConfName = atom()
Reason = term()
Unregister all managed agents.
unregister_agents(MgrAgentConfName, ManagedAgents) -> ok
MgrAgentConfName = atom()
ManagedAgents = [agent_name()]
Reason = term()
Unregister the given managed agents.
unregister_usm_users(MgrAgentConfName) -> ok
MgrAgentConfName = atom()
Reason = term()
Unregister all usm users.
unregister_usm_users(MgrAgentConfName, UsmUsers) -> ok
MgrAgentConfName = atom()
UsmUsers = [usm_user_name()]
Reason = term()
Unregister the given usm users.
load_mibs(Mibs) -> ok | {error, Reason}
Mibs = [MibName]
MibName = string()
Reason = term()
Load the mibs into the agent 'snmp_master_agent'.
unload_mibs(Mibs) -> ok | {error, Reason}
Mibs = [MibName]
MibName = string()
Reason = term()
Unload the mibs from the agent 'snmp_master_agent'.