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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_app.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
%%-----------------------------------------------------------------
 
19
%% This module implements the config conversion for the old SNMP 
 
20
%% application start method
 
21
%% The purpose is to extract all agent app-env and convert to the 
 
22
%% new format
 
23
%% 
 
24
%% ---
 
25
%% 
 
26
%% What about the restart times for the children 
 
27
%% note_store (snmpa_supervisor) and
 
28
%% net_if and mib_server (snmpa_misc_sup)?
 
29
%% 
 
30
%%-----------------------------------------------------------------
 
31
 
 
32
-module(snmpa_app).
 
33
 
 
34
-include("snmp_debug.hrl").
 
35
 
 
36
-export([convert_config/0, convert_config/1]).
 
37
 
 
38
%% Internal (test)
 
39
-export([start/1]).
 
40
 
 
41
 
 
42
convert_config() ->
 
43
    ?d("convert_config -> entry", []),
 
44
    convert_config( application:get_all_env(snmp) ).
 
45
 
 
46
convert_config(Opts) ->
 
47
    ?d("convert_config -> Opts: ~p", [Opts]),
 
48
    Prio           = get_priority(Opts),
 
49
    DbDir          = get_db_dir(Opts),
 
50
    DbInitError    = terminate, 
 
51
    LdbOpts        = get_local_db_opts(Opts),
 
52
    MibStorage     = get_mib_storage(Opts),
 
53
    MibsOpts       = get_mib_server_opts(Opts),
 
54
    SymOpts        = get_symbolic_store_opts(Opts),
 
55
    SetModule      = get_set_mechanism(Opts),
 
56
    AuthModule     = get_authentication_service(Opts),
 
57
    MultiT         = get_multi_threaded(Opts),
 
58
    Vsns           = get_versions(Opts),
 
59
    SupOpts        = get_supervisor_opts(Opts),
 
60
    ErrorReportMod = get_error_report_mod(Opts),
 
61
    AgentType      = get_agent_type(Opts),
 
62
    case AgentType of
 
63
        sub ->
 
64
            ?d("convert_config -> agent type: sub",[]),
 
65
            SaVerb = get_sub_agent_verbosity(Opts),
 
66
            [{agent_type,             AgentType}, 
 
67
             {agent_verbosity,        SaVerb}, 
 
68
             {set_mechanism,          SetModule},
 
69
             {authentication_service, AuthModule},
 
70
             {priority,               Prio},
 
71
             {versions,               Vsns},
 
72
             {db_dir,                 DbDir},
 
73
             {db_init_error,          DbInitError},
 
74
             {multi_threaded,         MultiT},
 
75
             {error_report_mod,       ErrorReportMod},
 
76
             {mib_storage,            MibStorage},
 
77
             {mib_server,             MibsOpts}, 
 
78
             {local_db,               LdbOpts}, 
 
79
             {supervisor,             SupOpts}, 
 
80
             {symbolic_store,         SymOpts}];
 
81
        
 
82
        master ->
 
83
            ?d("convert_config -> agent type: master",[]),
 
84
            MaVerb    = get_master_agent_verbosity(Opts),
 
85
            NoteOpts  = get_note_store_opts(Opts),
 
86
            NiOptions = get_net_if_options(Opts),
 
87
            NiOpts    = [{options, NiOptions}|get_net_if_opts(Opts)],
 
88
            AtlOpts   = get_audit_trail_log_opts(Opts),
 
89
            Mibs      = get_master_agent_mibs(Opts),
 
90
            ForceLoad = get_force_config_load(Opts),
 
91
            ConfVerb  = get_opt(verbosity, SupOpts, silence),
 
92
            ConfDir   = get_config_dir(Opts),
 
93
            ConfOpts  = [{dir,        ConfDir}, 
 
94
                         {force_load, ForceLoad},
 
95
                         {verbosity,  ConfVerb}],
 
96
            [{agent_type,             AgentType}, 
 
97
             {agent_verbosity,        MaVerb}, 
 
98
             {set_mechanism,          SetModule},
 
99
             {authentication_service, AuthModule},
 
100
             {db_dir,                 DbDir},
 
101
             {db_init_error,          DbInitError},
 
102
             {config,                 ConfOpts}, 
 
103
             {priority,               Prio},
 
104
             {versions,               Vsns},
 
105
             {multi_threaded,         MultiT},
 
106
             {error_report_mod,       ErrorReportMod},
 
107
             {supervisor,             SupOpts}, 
 
108
             {mibs,                   Mibs},
 
109
             {mib_storage,            MibStorage},
 
110
             {symbolic_store,         SymOpts}, 
 
111
             {note_store,             NoteOpts}, 
 
112
             {net_if,                 NiOpts}, 
 
113
             {mib_server,             MibsOpts}, 
 
114
             {local_db,               LdbOpts}] ++ AtlOpts
 
115
    end.
 
116
 
 
117
 
 
118
start(Type) ->
 
119
    snmp_app_sup:start_agent(Type, convert_config()).
 
120
 
 
121
    
 
122
%% ------------------------------------------------------------------
 
123
 
 
124
get_db_dir(Opts) ->
 
125
    case get_opt(snmp_db_dir, Opts) of
 
126
        {value, Dir} when list(Dir) ->
 
127
            Dir;
 
128
        {value, Bad} ->
 
129
            exit({bad_config, {db_dir, Bad}});
 
130
        false ->
 
131
            exit({undefined_config, db_dir})
 
132
    end.
 
133
            
 
134
 
 
135
%% --
 
136
 
 
137
get_priority(Opts) ->
 
138
    case get_opt(snmp_priority, Opts) of
 
139
        {value, Prio} when atom(Prio) ->
 
140
            Prio;
 
141
        _ ->
 
142
            normal
 
143
    end.
 
144
 
 
145
 
 
146
%% --
 
147
 
 
148
get_mib_storage(Opts) ->
 
149
    get_opt(snmp_mib_storage, Opts, ets).
 
150
 
 
151
get_mib_server_opts(Opts) ->
 
152
    Options = [{snmp_mibserver_verbosity, verbosity, silence},
 
153
               {mibentry_override, mibentry_override, false},
 
154
               {trapentry_override, trapentry_override, false}],
 
155
    get_opts(Options, Opts, []).
 
156
 
 
157
 
 
158
%% --
 
159
 
 
160
get_audit_trail_log_opts(Opts) ->
 
161
    case get_audit_trail_log(Opts) of
 
162
        false ->
 
163
            [];
 
164
        Type ->
 
165
            Dir  = get_audit_trail_log_dir(Opts),
 
166
            Size = get_audit_trail_log_size(Opts),
 
167
            AtlOpts0 = [{type,   Type},
 
168
                        {dir,    Dir},
 
169
                        {size,   Size},
 
170
                        {repair, true}],
 
171
            [{audit_trail_log, AtlOpts0}]
 
172
    end.
 
173
 
 
174
    
 
175
get_audit_trail_log(Opts) ->
 
176
    case get_opt(audit_trail_log, Opts) of
 
177
        {value, write_log}      -> write;
 
178
        {value, read_log}       -> read;
 
179
        {value, read_write_log} -> read_write;
 
180
        _                       -> false
 
181
    end.
 
182
 
 
183
get_audit_trail_log_dir(Opts) ->
 
184
    case get_opt(audit_trail_log_dir, Opts) of
 
185
        {value, Dir} when list(Dir) ->
 
186
            Dir;
 
187
        {value, Bad} -> 
 
188
            exit({bad_config, {audit_trail_log_dir, Bad}});
 
189
        _ -> 
 
190
            exit({undefined_config, audit_trail_log_dir})
 
191
    end.
 
192
 
 
193
get_audit_trail_log_size(Opts) ->
 
194
    case get_opt(audit_trail_log_size, Opts) of
 
195
        {value, {MB, MF} = Sz} when integer(MB), integer(MF) ->
 
196
            Sz;
 
197
        {value, Bad} -> 
 
198
            exit({bad_config, {audit_trail_log_size, Bad}});
 
199
        _ -> 
 
200
            exit({undefined_config, audit_trail_log_size})
 
201
    end.
 
202
 
 
203
 
 
204
%% --
 
205
 
 
206
get_master_agent_verbosity(Opts) ->
 
207
    get_opt(snmp_master_agent_verbosity, Opts, silence).
 
208
 
 
209
 
 
210
%% --
 
211
 
 
212
get_sub_agent_verbosity(Opts) ->
 
213
    get_opt(snmp_subagent_verbosity, Opts, silence).
 
214
 
 
215
 
 
216
%% --
 
217
 
 
218
get_supervisor_opts(Opts) ->
 
219
    Options = [{snmp_supervisor_verbosity, verbosity, silence}],
 
220
    get_opts(Options, Opts, []).
 
221
 
 
222
 
 
223
%% --
 
224
 
 
225
get_symbolic_store_opts(Opts) ->
 
226
    Options = [{snmp_symbolic_store_verbosity, verbosity, silence}],
 
227
    get_opts(Options, Opts, []).
 
228
 
 
229
 
 
230
%% --
 
231
 
 
232
get_note_store_opts(Opts) ->
 
233
    Options = [{snmp_note_store_verbosity, verbosity, silence}],
 
234
    get_opts(Options, Opts, []).
 
235
 
 
236
 
 
237
%% --
 
238
 
 
239
get_local_db_opts(Opts) ->
 
240
    Options = [{snmp_local_db_auto_repair, repair,    true}, 
 
241
               {snmp_local_db_verbosity,   verbosity, silence}],
 
242
    get_opts(Options, Opts, []).
 
243
 
 
244
 
 
245
%% --
 
246
 
 
247
get_multi_threaded(Opts) ->
 
248
    case get_opt(snmp_multi_threaded, Opts) of
 
249
        {value, true} ->
 
250
            true;
 
251
        {value, false} ->
 
252
            false;
 
253
        _ ->
 
254
            false
 
255
    end.
 
256
 
 
257
get_versions(Opts) ->
 
258
    F = fun(Ver) ->
 
259
                case get_opt(Ver, Opts) of
 
260
                    {value, true} ->
 
261
                        [Ver];
 
262
                    {value, false} ->
 
263
                        [];
 
264
                    _ ->
 
265
                        [Ver] % Default is true
 
266
                end
 
267
        end,
 
268
    V1 = F(v1),
 
269
    V2 = F(v2),
 
270
    V3 = F(v3),
 
271
    V1 ++ V2 ++ V3.
 
272
 
 
273
get_set_mechanism(Opts) ->
 
274
    get_opt(set_mechanism, Opts, snmpa_set).
 
275
 
 
276
get_authentication_service(Opts) ->
 
277
    get_opt(authentication_service, Opts, snmpa_acm).
 
278
 
 
279
get_error_report_mod(Opts) ->
 
280
    get_opt(snmp_error_report_mod, Opts, snmpa_error_logger).
 
281
 
 
282
 
 
283
%% --
 
284
 
 
285
get_net_if_opts(Opts) ->
 
286
    Options = [{snmp_net_if_module,    module,    snmpa_net_if},
 
287
               {snmp_net_if_verbosity, verbosity, silence}],
 
288
    get_opts(Options, Opts, []).
 
289
 
 
290
get_net_if_options(Opts) ->
 
291
    Options = [recbuf, 
 
292
               {req_limit,          req_limit, infinity}, 
 
293
               {bind_to_ip_address, bind_to,   false},
 
294
               {no_reuse_address,   no_reuse,  false}],
 
295
    get_opts(Options, Opts, []).
 
296
 
 
297
 
 
298
%% --
 
299
 
 
300
get_agent_type(Opts) ->
 
301
    get_opt(snmp_agent_type, Opts, master).
 
302
 
 
303
 
 
304
%% --
 
305
 
 
306
get_config_dir(Opts) ->
 
307
    case get_opt(snmp_config_dir, Opts) of
 
308
        {value, Dir} when list(Dir) -> Dir;
 
309
        {value, Bad} ->
 
310
            exit({bad_config, {config_dir, Bad}});
 
311
        _ -> 
 
312
            exit({undefined_config, config_dir})
 
313
    end.
 
314
 
 
315
get_master_agent_mibs(Opts) ->
 
316
    get_opt(snmp_master_agent_mibs, Opts, []).
 
317
 
 
318
get_force_config_load(Opts) ->
 
319
    case get_opt(force_config_load, Opts) of
 
320
        {value, true}  -> true;
 
321
        {value, false} -> false;
 
322
        _              -> false
 
323
    end.
 
324
 
 
325
 
 
326
%% --
 
327
 
 
328
get_opts([], _Options, Opts) ->
 
329
    Opts;
 
330
get_opts([{Key1, Key2, Def}|KeyVals], Options, Opts) ->
 
331
    %% If not found among Options, then use default value
 
332
    case lists:keysearch(Key1, 1, Options) of
 
333
        {value, {Key1, Val}} ->
 
334
            get_opts(KeyVals, Options, [{Key2, Val}|Opts]);
 
335
        false ->
 
336
            get_opts(KeyVals, Options, [{Key2, Def}|Opts])
 
337
    end;
 
338
get_opts([Key|KeyVals], Options, Opts) ->
 
339
    %% If not found among Options, then ignore
 
340
    case lists:keysearch(Key, 1, Options) of
 
341
        {value, KeyVal} ->
 
342
            get_opts(KeyVals, Options, [KeyVal|Opts]);
 
343
        false ->
 
344
            get_opts(KeyVals, Options, Opts)
 
345
    end.
 
346
    
 
347
 
 
348
%% --
 
349
 
 
350
 
 
351
get_opt(Key, Opts, Def) ->
 
352
    case get_opt(Key, Opts) of
 
353
        {value, Val} ->
 
354
            Val;
 
355
        false ->
 
356
            Def
 
357
    end.
 
358
 
 
359
get_opt(Key, Opts) ->
 
360
    case lists:keysearch(Key, 1, Opts) of
 
361
        {value, {_, Val}} ->
 
362
            {value, Val};
 
363
        false ->
 
364
            false
 
365
    end.
 
366
 
 
367
% i(F) ->
 
368
%     i(F, []).
 
369
 
 
370
% i(F, A) ->
 
371
%     io:format("~p: " ++ F ++ "~n", [?MODULE|A]).