~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/common_test/src/ct_snmp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
20
 
%%% @doc Common Test specific layer on top of the OTPs snmp
 
20
%%% @doc Common Test user interface module for the OTP snmp application
21
21
%%%
22
 
%%% Application to make snmp configuration easier for the test case
23
 
%%% writer. Many test cases can use default values for everything and
24
 
%%% then no snmp-configuration files needs to be supplied at all. When
25
 
%%% it is necessary to change some configuration it can be done for
26
 
%%% the subset of snmp-configuration files that are relevant, and
27
 
%%% still all this can be put in to the common-test configuration file
28
 
%%% or for the more specialized configuration parameters a "simple
29
 
%%% snmp-configuration file" can be placed in the test suites data
30
 
%%% directory. ct_snmp will also perform a type check on all supplied
31
 
%%% configuration. In the manager case the common_test application
32
 
%%% also will keep track of some manager information so that the
33
 
%%% test case write does not have to keep track of as much input
34
 
%%% parameters as if using the OTPs snmp manager directly.
35
 
%%%   
 
22
%%% The purpose of this module is to make snmp configuration easier for 
 
23
%%% the test case writer. Many test cases can use default values for common
 
24
%%% operations and then no snmp configuration files need to be supplied. When
 
25
%%% it is necessary to change particular configuration parameters, a subset
 
26
%%% of the relevant snmp configuration files may be passed to <code>ct_snmp</code>
 
27
%%% by means of Common Test configuration files.
 
28
%%% For more specialized configuration parameters, it is possible to place a 
 
29
%%% "simple snmp configuration file" in the test suite data directory. 
 
30
%%% To simplify the test suite, Common Test keeps track
 
31
%%% of some of the snmp manager information. This way the test suite doesn't
 
32
%%% have to handle as many input parameters as it would if it had to interface the
 
33
%%% OTP snmp manager directly.
36
34
%%% 
37
 
%%% <p> The following parameters are configurable </p>
 
35
%%% <p> The following snmp manager and agent parameters are configurable: </p>
38
36
%%%
39
37
%%% <pre>
40
38
%%% {snmp,
82
80
%%%       ]}.
83
81
%%% </pre>
84
82
%%%
85
 
%%% <p>The <code>ConfName</code> parameter in the functions 
86
 
%%%    should be the name you allocated in your test suite using
87
 
%%%  <code>require</code> statement. Example:</p>
88
 
%%% <pre> suite() -> [{require, ConfName,{snmp,[users, managed_agents]}}].</pre>
 
83
%%% <p>The <code>MgrAgentConfName</code> parameter in the functions 
 
84
%%% should be a name you allocate in your test suite using a
 
85
%%% <code>require</code> statement. 
 
86
%%% Example (where <code>MgrAgentConfName = snmp_mgr_agent</code>):</p>
 
87
%%% <pre> suite() -> [{require, snmp_mgr_agent, snmp}].</pre>
89
88
%%% <p>or</p>
90
 
%%% <pre>  ct:require(ConfName,{snmp,[users, managed_agents]}).</pre>
 
89
%%% <pre>  ct:require(snmp_mgr_agent, snmp).</pre>
91
90
%%%
92
91
%%% <p> Note that Usm users are needed for snmp v3 configuration and are
93
92
%%% not to be confused with users.</p>
97
96
%%% the snmp application. </p> 
98
97
%%% <p> Note: It is recommended to use the .hrl-files created by the 
99
98
%%% Erlang/OTP mib-compiler to define the oids.  
100
 
%%% Ex for the getting the erlang node name from the erlNodeTable 
101
 
%%% in the OTP-MIB </p> 
 
99
%%% Example for the getting the erlang node name from the erlNodeTable 
 
100
%%% in the OTP-MIB:</p> 
102
101
%%% <pre>Oid = ?erlNodeEntry ++ [?erlNodeName, 1] </pre>
 
102
%%%
 
103
%%% <p>It is also possible to set values for snmp application configuration 
 
104
%%% parameters, such as <code>config</code>, <code>server</code>, 
 
105
%%% <code>net_if</code>, etc (see the "Configuring the application" chapter in
 
106
%%% the OTP snmp User's Guide for a list of valid parameters and types). This is 
 
107
%%% done by defining a configuration data variable on the following form:</p>
 
108
%%% <pre>
 
109
%%% {snmp_app, [{manager, [snmp_app_manager_params()]},
 
110
%%%             {agent, [snmp_app_agent_params()]}]}.</pre>
 
111
%%% 
 
112
%%% <p>A name for the data needs to be allocated in the suite using 
 
113
%%% <code>require</code> (see example above), and this name passed as 
 
114
%%% the <code>SnmpAppConfName</code> argument to <code>start/3</code>.
 
115
%%% <code>ct_snmp</code> specifies default values for some snmp application
 
116
%%% configuration parameters (such as <code>{verbosity,trace}</code> for the
 
117
%%% <code>config</code> parameter). This set of defaults will be
 
118
%%% merged with the parameters specified by the user, and user values
 
119
%%% override <code>ct_snmp</code> defaults.</p>
103
120
 
104
121
-module(ct_snmp).
105
122
 
129
146
%%% @type var_and_val() = {oid(), value_type(), value()}
130
147
%%% @type sec_type() = none | minimum | semi
131
148
%%% @type rel_path() = string() 
 
149
%%% @type snmp_app_manager_params() = term()
 
150
%%% @type snmp_app_agent_params() = term()
132
151
 
133
152
 
134
153
-include("snmp_types.hrl").
136
155
-include("ct.hrl").
137
156
 
138
157
%%% API
139
 
-export([start/2, stop/1, get_values/3, get_next_values/3, set_values/4, 
 
158
-export([start/2, start/3, stop/1, get_values/3, get_next_values/3, set_values/4, 
140
159
         set_info/1, register_users/2, register_agents/2, register_usm_users/2,
141
160
         unregister_users/1, unregister_agents/1, update_usm_users/2, 
142
161
         load_mibs/1]).
160
179
%%%  API
161
180
%%%=========================================================================
162
181
 
163
 
%%% @spec start(Config, ConfName) -> ok
 
182
%%%-----------------------------------------------------------------
 
183
%%% @spec start(Config, MgrAgentConfName) -> ok
 
184
%%% @equiv start(Config, MgrAgentConfName, undefined)
 
185
start(Config, MgrAgentConfName) ->
 
186
    start(Config, MgrAgentConfName, undefined).
 
187
 
 
188
%%% @spec start(Config, MgrAgentConfName, SnmpAppConfName) -> ok
164
189
%%%      Config = [{Key, Value}] 
165
190
%%%      Key = atom()
166
191
%%%      Value = term()
167
 
%%%      ConfName = atom()
 
192
%%%      MgrAgentConfName = atom()
 
193
%%%      SnmpConfName = atom()
168
194
%%%
169
 
%%% @doc Starts an snmp manager and/or agent. In the manager case also
170
 
%%% registrations of users and agents as specified by the
171
 
%%% configuration &lt;ConfName&gt; will be performed. When using snmp
 
195
%%% @doc Starts an snmp manager and/or agent. In the manager case,
 
196
%%% registrations of users and agents as specified by the configuration 
 
197
%%% <code>MgrAgentConfName</code> will be performed. When using snmp
172
198
%%% v3 also so called usm users will be registered. Note that users,
173
 
%%% usm_users and managed agents may also be registerd at a later time
 
199
%%% usm_users and managed agents may also be registered at a later time
174
200
%%% using ct_snmp:register_users/2, ct_snmp:register_agents/2, and
175
201
%%% ct_snmp:register_usm_users/2. The agent started will be
176
 
%%% called snmp_master_agent. Use ct_snmp:load_mibs to load mibs into the
177
 
%%% agent.
178
 
start(Config, ConfName) ->
179
 
    
180
 
    StartManager= ct:get_config({ConfName, start_manager}, true),
181
 
    StartAgent = ct:get_config({ConfName, start_agent}, false),
 
202
%%% called <code>snmp_master_agent</code>. Use ct_snmp:load_mibs/1 to load 
 
203
%%% mibs into the agent. With <code>SnmpAppConfName</code> it's possible 
 
204
%%% to configure the snmp application with parameters such as <code>config</code>,
 
205
%%% <code>mibs</code>, <code>net_if</code>, etc. The values will be merged
 
206
%%% with (and possibly override) default values set by <code>ct_snmp</code>.
 
207
start(Config, MgrAgentConfName, SnmpAppConfName) ->
 
208
    StartManager= ct:get_config({MgrAgentConfName, start_manager}, true),
 
209
    StartAgent = ct:get_config({MgrAgentConfName, start_agent}, false),
182
210
   
183
 
    SysName = ct:get_config({ConfName, agent_sysname}, "ct_test"),
 
211
    SysName = ct:get_config({MgrAgentConfName, agent_sysname}, "ct_test"),
184
212
    {ok, HostName} = inet:gethostname(),
185
213
    {ok, Addr} = inet:getaddr(HostName, inet),
186
214
    IP = tuple_to_list(Addr),
187
 
    AgentManagerIP = ct:get_config({ConfName, agent_manager_ip},
188
 
                                   IP),
 
215
    AgentManagerIP = ct:get_config({MgrAgentConfName, agent_manager_ip}, IP),
189
216
    
190
217
    prepare_snmp_env(),
191
 
    setup_agent(StartAgent, ConfName, Config, SysName, AgentManagerIP, IP),
192
 
    setup_manager(StartManager, ConfName, Config, AgentManagerIP),
 
218
    setup_agent(StartAgent, MgrAgentConfName, SnmpAppConfName, 
 
219
                Config, SysName, AgentManagerIP, IP),
 
220
    setup_manager(StartManager, MgrAgentConfName, SnmpAppConfName, 
 
221
                  Config, AgentManagerIP),
193
222
    application:start(snmp),
194
223
 
195
 
    manager_register(StartManager, ConfName).
 
224
    manager_register(StartManager, MgrAgentConfName).
196
225
 
197
226
%%% @spec stop(Config) -> ok
198
227
%%%      Config = [{Key, Value}]
199
228
%%%      Key = atom()
200
229
%%%      Value = term()
201
 
%%%      ConfName = atom()
202
230
%%%
203
231
%%% @doc Stops the snmp manager and/or agent removes all files created.
204
232
stop(Config) ->
213
241
    catch del_dir(DbDir).
214
242
    
215
243
    
216
 
%%% @spec get_values(Agent, Oids, ConfName) -> SnmpReply
 
244
%%% @spec get_values(Agent, Oids, MgrAgentConfName) -> SnmpReply
217
245
%%%
218
246
%%%      Agent = agent_name()
219
247
%%%      Oids = oids()
220
 
%%%      ConfName = atom()
 
248
%%%      MgrAgentConfName = atom()
221
249
%%%      SnmpReply = snmpreply()  
222
250
%%%
223
251
%%% @doc Issues a synchronous snmp get request. 
224
 
get_values(Agent, Oids, ConfName) ->
 
252
get_values(Agent, Oids, MgrAgentConfName) ->
225
253
    [Uid, AgentIp, AgentUdpPort | _] = 
226
 
        agent_conf(Agent, ConfName),
 
254
        agent_conf(Agent, MgrAgentConfName),
227
255
    {ok, SnmpReply, _} =
228
256
        snmpm:g(Uid, AgentIp, AgentUdpPort, Oids),
229
257
    SnmpReply.
230
258
 
231
 
%%% @spec get_next_values(Agent, Oids, ConfName) -> SnmpReply 
 
259
%%% @spec get_next_values(Agent, Oids, MgrAgentConfName) -> SnmpReply 
232
260
%%%
233
261
%%%      Agent = agent_name()
234
262
%%%      Oids = oids()
235
 
%%%      ConfName = atom()
 
263
%%%      MgrAgentConfName = atom()
236
264
%%%      SnmpReply = snmpreply()  
237
265
%%%
238
266
%%% @doc Issues a synchronous snmp get next request. 
239
 
get_next_values(Agent, Oids, ConfName) ->
 
267
get_next_values(Agent, Oids, MgrAgentConfName) ->
240
268
    [Uid, AgentIp, AgentUdpPort | _] = 
241
 
        agent_conf(Agent, ConfName),
 
269
        agent_conf(Agent, MgrAgentConfName),
242
270
    {ok, SnmpReply, _} =
243
271
        snmpm:gn(Uid, AgentIp, AgentUdpPort, Oids),
244
272
    SnmpReply.
245
273
 
246
 
%%% @spec set_values(Agent, VarsAndVals, ConfName, Config) -> SnmpReply
 
274
%%% @spec set_values(Agent, VarsAndVals, MgrAgentConfName, Config) -> SnmpReply
247
275
%%%
248
276
%%%      Agent = agent_name()
249
277
%%%      Oids = oids()
250
 
%%%      ConfName = atom()
 
278
%%%      MgrAgentConfName = atom()
251
279
%%%      Config = [{Key, Value}] 
252
280
%%%      SnmpReply = snmpreply()  
253
281
%%%
254
282
%%% @doc Issues a synchronous snmp set request. 
255
 
set_values(Agent, VarsAndVals, ConfName, Config) ->
 
283
set_values(Agent, VarsAndVals, MgrAgentConfName, Config) ->
256
284
    PrivDir = ?config(priv_dir, Config),
257
285
    [Uid, AgentIp, AgentUdpPort | _] = 
258
 
        agent_conf(Agent, ConfName),
 
286
        agent_conf(Agent, MgrAgentConfName),
259
287
    Oids = lists:map(fun({Oid, _, _}) -> Oid end, VarsAndVals),
260
288
    {ok, SnmpGetReply, _} =
261
289
        snmpm:g(Uid, AgentIp, AgentUdpPort, Oids),
293
321
            []
294
322
    end.
295
323
 
296
 
%%% @spec register_users(ConfName, Users) -> ok | {error, Reason}
 
324
%%% @spec register_users(MgrAgentConfName, Users) -> ok | {error, Reason}
297
325
%%%
298
 
%%%      ConfName = atom()
 
326
%%%      MgrAgentConfName = atom()
299
327
%%%      Users =  [user()]
300
328
%%%      Reason = term()    
301
329
%%%
302
330
%%% @doc Register the manager entity (=user) responsible for specific agent(s).
303
331
%%% Corresponds to making an entry in users.conf
304
 
register_users(ConfName, Users) ->
305
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
332
register_users(MgrAgentConfName, Users) ->
 
333
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
306
334
    NewSnmpVals = lists:keyreplace(users, 1, SnmpVals, {users, Users}),
307
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
 
335
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
308
336
    setup_users(Users).
309
337
 
310
 
%%% @spec register_agents(ConfName, ManagedAgents) -> ok | {error, Reason}
 
338
%%% @spec register_agents(MgrAgentConfName, ManagedAgents) -> ok | {error, Reason}
311
339
%%%
312
 
%%%      ConfName = atom()
 
340
%%%      MgrAgentConfName = atom()
313
341
%%%      ManagedAgents = [agent()]
314
342
%%%      Reason = term()    
315
343
%%%
316
344
%%% @doc Explicitly instruct the manager to handle this agent.
317
345
%%% Corresponds to making an entry in agents.conf 
318
 
register_agents(ConfName, ManagedAgents) ->
319
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
346
register_agents(MgrAgentConfName, ManagedAgents) ->
 
347
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
320
348
    NewSnmpVals = lists:keyreplace(managed_agents, 1, SnmpVals,
321
349
                                   {managed_agents, ManagedAgents}),
322
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
 
350
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
323
351
    setup_managed_agents(ManagedAgents).
324
352
 
325
 
%%% @spec register_usm_users(ConfName, UsmUsers) ->  ok | {error, Reason}
 
353
%%% @spec register_usm_users(MgrAgentConfName, UsmUsers) ->  ok | {error, Reason}
326
354
%%%
327
 
%%%      ConfName = atom()
 
355
%%%      MgrAgentConfName = atom()
328
356
%%%      UsmUsers = [usm_user()]
329
357
%%%      Reason = term()    
330
358
%%%
331
359
%%% @doc Explicitly instruct the manager to handle this USM user.
332
360
%%% Corresponds to making an entry in usm.conf 
333
 
register_usm_users(ConfName, UsmUsers) ->
334
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
361
register_usm_users(MgrAgentConfName, UsmUsers) ->
 
362
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
335
363
    NewSnmpVals = lists:keyreplace(users, 1, SnmpVals, {usm_users, UsmUsers}),
336
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
337
 
    EngineID = ct:get_config({ConfName, engine_id}, ?ENGINE_ID),
 
364
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
 
365
    EngineID = ct:get_config({MgrAgentConfName, engine_id}, ?ENGINE_ID),
338
366
    setup_usm_users(UsmUsers, EngineID).
339
367
 
340
 
%%% @spec unregister_users(ConfName) ->  ok | {error, Reason}
 
368
%%% @spec unregister_users(MgrAgentConfName) ->  ok | {error, Reason}
341
369
%%%
342
 
%%%      ConfName = atom()
 
370
%%%      MgrAgentConfName = atom()
343
371
%%%      Reason = term()
344
372
%%%
345
373
%%% @doc Removes information added when calling register_users/2. 
346
 
unregister_users(ConfName) ->
 
374
unregister_users(MgrAgentConfName) ->
347
375
    Users = lists:map(fun({UserName, _}) -> UserName end,
348
 
                      ct:get_config({ConfName, users})),
349
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
376
                      ct:get_config({MgrAgentConfName, users})),
 
377
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
350
378
    NewSnmpVals = lists:keyreplace(users, 1, SnmpVals, {users, []}),
351
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
 
379
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
352
380
    takedown_users(Users).
353
381
 
354
 
%%% @spec unregister_agents(ConfName) ->  ok | {error, Reason}
 
382
%%% @spec unregister_agents(MgrAgentConfName) ->  ok | {error, Reason}
355
383
%%%
356
 
%%%      ConfName = atom()
 
384
%%%      MgrAgentConfName = atom()
357
385
%%%      Reason = term()
358
386
%%%
359
387
%%% @doc  Removes information added when calling register_agents/2. 
360
 
unregister_agents(ConfName) ->    
 
388
unregister_agents(MgrAgentConfName) ->    
361
389
    ManagedAgents = lists:map(fun({_, [Uid, AgentIP, AgentPort, _]}) -> 
362
390
                                      {Uid, AgentIP, AgentPort} 
363
391
                              end,
364
 
                              ct:get_config({ConfName, managed_agents})),
365
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
392
                              ct:get_config({MgrAgentConfName, managed_agents})),
 
393
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
366
394
    NewSnmpVals = lists:keyreplace(managed_agents, 1, SnmpVals, 
367
395
                                   {managed_agents, []}),
368
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
 
396
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
369
397
    takedown_managed_agents(ManagedAgents).
370
398
 
371
399
 
372
 
%%% @spec update_usm_users(ConfName, UsmUsers) -> ok | {error, Reason}
 
400
%%% @spec update_usm_users(MgrAgentConfName, UsmUsers) -> ok | {error, Reason}
373
401
%%%
374
 
%%%      ConfName = atom()
 
402
%%%      MgrAgentConfName = atom()
375
403
%%%      UsmUsers = usm_users()
376
404
%%%      Reason = term()
377
405
%%%
378
406
%%% @doc  Alters information added when calling register_usm_users/2. 
379
 
update_usm_users(ConfName, UsmUsers) ->    
 
407
update_usm_users(MgrAgentConfName, UsmUsers) ->    
380
408
   
381
 
    {snmp, SnmpVals} = ct:get_config(ConfName),
 
409
    {snmp, SnmpVals} = ct:get_config(MgrAgentConfName),
382
410
    NewSnmpVals = lists:keyreplace(usm_users, 1, SnmpVals, 
383
411
                                   {usm_users, UsmUsers}),
384
 
    ct_util:update_config(ConfName, {snmp, NewSnmpVals}),
385
 
    EngineID = ct:get_config({ConfName, engine_id}, ?ENGINE_ID),
 
412
    ct_util:update_config(MgrAgentConfName, {snmp, NewSnmpVals}),
 
413
    EngineID = ct:get_config({MgrAgentConfName, engine_id}, ?ENGINE_ID),
386
414
    do_update_usm_users(UsmUsers, EngineID). 
387
415
 
388
416
%%% @spec load_mibs(Mibs) -> ok | {error, Reason}
409
437
    %% agent.
410
438
    application:unset_env(snmp, agent).
411
439
%%%---------------------------------------------------------------------------
412
 
setup_manager(false, _, _, _) ->
 
440
setup_manager(false, _, _, _, _) ->
413
441
    ok;
414
 
setup_manager(true, ConfName, Config, IP) ->
415
 
    
 
442
setup_manager(true, MgrConfName, SnmpConfName, Config, IP) ->    
416
443
    PrivDir = ?config(priv_dir, Config),
417
 
    MaxMsgSize = ct:get_config({ConfName, max_msg_size}, ?MAX_MSG_SIZE),
418
 
    Port = ct:get_config({ConfName, mgr_port}, ?MGR_PORT),
419
 
    EngineID = ct:get_config({ConfName, engine_id}, ?ENGINE_ID),
 
444
    MaxMsgSize = ct:get_config({MgrConfName,max_msg_size}, ?MAX_MSG_SIZE),
 
445
    Port = ct:get_config({MgrConfName,mgr_port}, ?MGR_PORT),
 
446
    EngineID = ct:get_config({MgrConfName,engine_id}, ?ENGINE_ID),
420
447
    MgrDir =  filename:join(PrivDir,"mgr"),
421
448
    %%% Users, Agents and Usms are in test suites register after the
422
449
    %%% snmp application is started.
427
454
   
428
455
    snmp_config:write_manager_snmp_files(MgrDir, IP, Port, MaxMsgSize, 
429
456
                                         EngineID, Users, Agents, Usms),
430
 
    application:set_env(snmp, manager, [{config, [{dir, MgrDir},
431
 
                                                  {db_dir, MgrDir},
432
 
                                                  {verbosity, trace}]},
433
 
                                        {server, [{verbosity, trace}]},
434
 
                                        {net_if, [{verbosity, trace}]},
435
 
                                        {versions, [v1, v2, v3]}]).
 
457
    SnmpEnv = merge_snmp_conf([{config, [{dir, MgrDir},{db_dir, MgrDir},
 
458
                                         {verbosity, trace}]},
 
459
                               {server, [{verbosity, trace}]},
 
460
                               {net_if, [{verbosity, trace}]},
 
461
                               {versions, [v1, v2, v3]}],
 
462
                              ct:get_config({SnmpConfName,manager})),
 
463
    application:set_env(snmp, manager, SnmpEnv).
436
464
%%%---------------------------------------------------------------------------
437
 
setup_agent(false,_, _, _, _, _) ->
 
465
setup_agent(false,_, _, _, _, _, _) ->
438
466
    ok;
439
 
setup_agent(true, ConfName, Config, SysName, ManagerIP, AgentIP) ->
 
467
setup_agent(true, AgentConfName, SnmpConfName, 
 
468
            Config, SysName, ManagerIP, AgentIP) ->
440
469
    application:start(mnesia),
441
470
    PrivDir = ?config(priv_dir, Config),
442
 
    Vsns = ct:get_config({ConfName, agent_vsns}, ?CONF_FILE_VER),
443
 
    TrapUdp = ct:get_config({ConfName, agent_trap_udp}, ?TRAP_UDP),
444
 
    AgentUdp = ct:get_config({ConfName, agent_udp}, ?AGENT_UDP),
445
 
    NotifType = ct:get_config({ConfName, agent_notify_type},
 
471
    Vsns = ct:get_config({AgentConfName, agent_vsns}, ?CONF_FILE_VER),
 
472
    TrapUdp = ct:get_config({AgentConfName, agent_trap_udp}, ?TRAP_UDP),
 
473
    AgentUdp = ct:get_config({AgentConfName, agent_udp}, ?AGENT_UDP),
 
474
    NotifType = ct:get_config({AgentConfName, agent_notify_type},
446
475
                              ?AGENT_NOTIFY_TYPE),
447
 
    SecType = ct:get_config({ConfName, agent_sec_type}, ?AGENT_SEC_TYPE),
448
 
    Passwd  = ct:get_config({ConfName, agent_passwd}, ?AGENT_PASSWD),
449
 
    AgentEngineID = ct:get_config({ConfName, agent_engine_id}, 
 
476
    SecType = ct:get_config({AgentConfName, agent_sec_type}, ?AGENT_SEC_TYPE),
 
477
    Passwd  = ct:get_config({AgentConfName, agent_passwd}, ?AGENT_PASSWD),
 
478
    AgentEngineID = ct:get_config({AgentConfName, agent_engine_id}, 
450
479
                                  ?AGENT_ENGINE_ID),
451
 
    AgentMaxMsgSize = ct:get_config({ConfName, agent_max_msg_size},
 
480
    AgentMaxMsgSize = ct:get_config({AgentConfName, agent_max_msg_size},
452
481
                                    ?MAX_MSG_SIZE),
453
482
    
454
483
    ConfDir = filename:join(PrivDir, "conf"),
461
490
                                       SecType, Passwd, AgentEngineID, 
462
491
                                       AgentMaxMsgSize),
463
492
 
464
 
    override_default_configuration(Config, ConfName),
465
 
   
466
 
    application:set_env(snmp, agent, [{db_dir, DbDir},
467
 
                                      {config, [{dir, ConfDir},
468
 
                                                {verbosity, trace}]},
469
 
                                      {agent_type, master},
470
 
                                      {agent_verbosity, trace},
471
 
                                      {net_if, [{verbosity, trace}]}]).
 
493
    override_default_configuration(Config, AgentConfName),
 
494
    
 
495
    SnmpEnv = merge_snmp_conf([{db_dir, DbDir},
 
496
                               {config, [{dir, ConfDir},
 
497
                                         {verbosity, trace}]},
 
498
                               {agent_type, master},
 
499
                               {agent_verbosity, trace},
 
500
                               {net_if, [{verbosity, trace}]}],
 
501
                              ct:get_config({SnmpConfName,agent})),
 
502
    application:set_env(snmp, agent, SnmpEnv).
 
503
%%%---------------------------------------------------------------------------
 
504
merge_snmp_conf(Defaults, undefined) ->
 
505
    Defaults;
 
506
merge_snmp_conf([Def={Key,DefList=[P|_]}|DefParams], UserParams) when is_tuple(P) ->
 
507
    case lists:keysearch(Key, 1, UserParams) of
 
508
        false ->
 
509
            [Def | merge_snmp_conf(DefParams, UserParams)];
 
510
        {value,{Key,UserList}} ->
 
511
            DefList1 = [{SubKey,Val} || {SubKey,Val} <- DefList, 
 
512
                                        lists:keysearch(SubKey, 1, UserList) == false],
 
513
            [{Key,DefList1++UserList} | merge_snmp_conf(DefParams, 
 
514
                                                        lists:keydelete(Key, 1, UserParams))]
 
515
    end;
 
516
merge_snmp_conf([Def={Key,_}|DefParams], UserParams) ->
 
517
    case lists:keysearch(Key, 1, UserParams) of
 
518
        false ->
 
519
            [Def | merge_snmp_conf(DefParams, UserParams)];
 
520
        {value,_} ->
 
521
            merge_snmp_conf(DefParams, UserParams)
 
522
    end;
 
523
merge_snmp_conf([], UserParams) ->
 
524
    UserParams.
 
525
                              
 
526
 
472
527
%%%---------------------------------------------------------------------------
473
528
manager_register(false, _) ->
474
529
    ok;
475
 
manager_register(true, ConfName) ->
476
 
    Agents = ct:get_config({ConfName, managed_agents}, []),
477
 
    Users = ct:get_config({ConfName, users}, []),
478
 
    UsmUsers = ct:get_config({ConfName, usm_users}, []),
479
 
    EngineID = ct:get_config({ConfName, engine_id}, ?ENGINE_ID),
 
530
manager_register(true, MgrAgentConfName) ->
 
531
    Agents = ct:get_config({MgrAgentConfName, managed_agents}, []),
 
532
    Users = ct:get_config({MgrAgentConfName, users}, []),
 
533
    UsmUsers = ct:get_config({MgrAgentConfName, usm_users}, []),
 
534
    EngineID = ct:get_config({MgrAgentConfName, engine_id}, ?ENGINE_ID),
480
535
 
481
536
    setup_usm_users(UsmUsers, EngineID),
482
537
    setup_users(Users),
561
616
    file:del_dir(Dir),
562
617
    ok.
563
618
%%%---------------------------------------------------------------------------
564
 
agent_conf(Agent, ConfName) ->
565
 
    Agents = ct:get_config({ConfName, managed_agents}),
 
619
agent_conf(Agent, MgrAgentConfName) ->
 
620
    Agents = ct:get_config({MgrAgentConfName, managed_agents}),
566
621
    case lists:keysearch(Agent, 1, Agents) of
567
622
        {value, {Agent, AgentConf}} ->
568
623
            AgentConf;
570
625
            exit({error, {unknown_agent, Agent, Agents}})
571
626
    end.
572
627
%%%---------------------------------------------------------------------------
573
 
override_default_configuration(Config, ConfName) ->
 
628
override_default_configuration(Config, MgrAgentConfName) ->
574
629
    override_contexts(Config,
575
 
                      ct:get_config({ConfName, agent_contexts}, undefined)),
 
630
                      ct:get_config({MgrAgentConfName, agent_contexts}, undefined)),
576
631
    override_community(Config,
577
 
                       ct:get_config({ConfName, agent_community}, undefined)),
 
632
                       ct:get_config({MgrAgentConfName, agent_community}, undefined)),
578
633
    override_sysinfo(Config,
579
 
                     ct:get_config({ConfName, agent_sysinfo}, undefined)),
 
634
                     ct:get_config({MgrAgentConfName, agent_sysinfo}, undefined)),
580
635
    override_vacm(Config,
581
 
                  ct:get_config({ConfName, agent_vacm}, undefined)),
 
636
                  ct:get_config({MgrAgentConfName, agent_vacm}, undefined)),
582
637
    override_usm(Config,
583
 
                 ct:get_config({ConfName, agent_usm}, undefined)),
 
638
                 ct:get_config({MgrAgentConfName, agent_usm}, undefined)),
584
639
    override_notify(Config,
585
 
                    ct:get_config({ConfName, agent_notify_def}, undefined)),
 
640
                    ct:get_config({MgrAgentConfName, agent_notify_def}, undefined)),
586
641
    override_target_address(Config,
587
 
                            ct:get_config({ConfName, 
 
642
                            ct:get_config({MgrAgentConfName, 
588
643
                                           agent_target_address_def}, 
589
644
                                          undefined)),
590
645
    override_target_params(Config, 
591
 
                           ct:get_config({ConfName, agent_target_param_def},
 
646
                           ct:get_config({MgrAgentConfName, agent_target_param_def},
592
647
                                         undefined)).
593
648
 
594
649
%%%---------------------------------------------------------------------------