~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/snmp/src/misc/snmp_config.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% 
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%% 
19
19
 
22
22
-include_lib("kernel/include/file.hrl").
23
23
-include("snmp_types.hrl").
24
24
 
 
25
%% Avoid warning for local function error/1 clashing with autoimported BIF.
 
26
-compile({no_auto_import,[error/1]}).
25
27
-export([config/0]).
26
28
 
27
29
-export([write_config_file/4, append_config_file/4, read_config_file/3]).
327
329
                            ATLRepair = ask("23f. Audit trail log repair "
328
330
                                            "(true/false/truncate/snmp_repair)?", "true",
329
331
                                            fun verify_atl_repair/1),
 
332
                            ATLSeqNo = ask("23g. Audit trail log "
 
333
                                           "sequence-numbering (true/false)?", 
 
334
                                           "false",
 
335
                                           fun verify_atl_seqno/1),
330
336
                            [{audit_trail_log, [{type,   ATLType},
331
337
                                                {dir,    ATLDir},
332
338
                                                {size,   ATLSize},
333
 
                                                {repair, ATLRepair}]}];
 
339
                                                {repair, ATLRepair},
 
340
                                                {seqno, ATLSeqNo}]}];
334
341
                        no ->
335
342
                            []
336
343
                    end,
400
407
                NetIf = [{module,    NetIfMod},
401
408
                         {verbosity, NetIfVerb},
402
409
                         {options,   NetIfOpts}],
 
410
                TermDiscoEnable = ask("26a. Allow terminating discovery "
 
411
                                      "(true/false)?", "true",
 
412
                                      fun verify_bool/1),
 
413
                TermDiscoConf = 
 
414
                    case TermDiscoEnable of
 
415
                        true ->
 
416
                            TermDiscoStage2 = 
 
417
                                ask("26b. Second stage behaviour "
 
418
                                    "(discovery/plain)?", "discovery",
 
419
                                    fun verify_term_disco_behaviour/1),
 
420
                            TermDiscoTrigger = 
 
421
                                ask("26c. Trigger username "
 
422
                                    "(default/a string)?", "default",
 
423
                                    fun verify_term_disco_trigger_username/1),
 
424
                            [{enable, TermDiscoEnable},
 
425
                             {stage2, TermDiscoStage2},
 
426
                             {trigger_username, TermDiscoTrigger}];
 
427
                        false ->
 
428
                            [{enable, TermDiscoEnable},
 
429
                             {stage2, discovery},
 
430
                             {trigger_username, ""}]
 
431
                    end,
 
432
                OrigDiscoEnable = ask("27a. Allow originating discovery "
 
433
                                      "(true/false)?", "true",
 
434
                                      fun verify_bool/1),
 
435
                OrigDiscoConf = 
 
436
                    [{enable, OrigDiscoEnable}], 
 
437
                DiscoveryConfig = 
 
438
                    [{terminating, TermDiscoConf},
 
439
                     {originating, OrigDiscoConf}], 
403
440
                [{agent_type,      master},
404
441
                 {agent_verbosity, MasterAgentVerb},
 
442
                 {discovery,       DiscoveryConfig}, 
405
443
                 {config,          [{dir,        ConfigDir}, 
406
444
                                    {force_load, ForceLoad},
407
445
                                    {verbosity,  ConfigVerb}]},
644
682
                 "(y/n)?",
645
683
                 "n", fun verify_yes_or_no/1) of
646
684
            yes ->
647
 
                ATLDir = ask("19b. Where to store the "
 
685
                ATLType = ask("19b. Audit trail log type "
 
686
                              "(write/read_write)?",
 
687
                              "read_write", fun verify_atl_type/1),
 
688
                ATLDir = ask("19c. Where to store the "
648
689
                             "audit trail log?",
649
690
                             DefDir, fun verify_dir/1),
650
 
                ATLMaxFiles = ask("19c. Max number of files?", 
 
691
                ATLMaxFiles = ask("19d. Max number of files?", 
651
692
                                  "10", 
652
693
                                  fun verify_pos_integer/1),
653
 
                ATLMaxBytes = ask("19d. Max size (in bytes) "
 
694
                ATLMaxBytes = ask("19e. Max size (in bytes) "
654
695
                                  "of each file?", 
655
696
                                  "10240", 
656
697
                                  fun verify_pos_integer/1),
657
698
                ATLSize = {ATLMaxBytes, ATLMaxFiles},
658
 
                ATLRepair = ask("19e. Audit trail log repair "
 
699
                ATLRepair = ask("19f. Audit trail log repair "
659
700
                                "(true/false/truncate/snmp_repair)?", "true",
660
701
                                fun verify_atl_repair/1),
661
 
                [{audit_trail_log, [{dir,    ATLDir},
 
702
                ATLSeqNo = ask("19g. Audit trail log sequence-numbering "
 
703
                               "(true/false)?", "false",
 
704
                               fun verify_atl_seqno/1),
 
705
                [{audit_trail_log, [{type,   ATLType},
 
706
                                    {dir,    ATLDir},
662
707
                                    {size,   ATLSize},
663
 
                                    {repair, ATLRepair}]}];
 
708
                                    {repair, ATLRepair},
 
709
                                    {seqno,  ATLSeqNo}]}];
664
710
            no ->
665
711
                []
666
712
        end,
1180
1226
verify_atl_repair(R) ->
1181
1227
    {error, "invalid audit trail log repair: " ++ R}.
1182
1228
 
 
1229
verify_atl_seqno("true") ->
 
1230
    {ok, true};
 
1231
verify_atl_seqno("false") ->
 
1232
    {ok, false};
 
1233
verify_atl_seqno(SN) ->
 
1234
    {error, "invalid audit trail log seqno: " ++ SN}.
 
1235
 
1183
1236
 
1184
1237
verify_pos_integer(I0) ->
1185
1238
    case (catch list_to_integer(I0)) of
1237
1290
    end.
1238
1291
    
1239
1292
 
 
1293
verify_term_disco_behaviour("discovery") ->
 
1294
    {ok, discovery};
 
1295
verify_term_disco_behaviour("plain") ->
 
1296
    {ok, plain};
 
1297
verify_term_disco_behaviour(B) ->
 
1298
    {error, "invalid terminating discovery behaviour: " ++ B}.
 
1299
 
 
1300
verify_term_disco_trigger_username("default") ->
 
1301
    {ok, ""};
 
1302
verify_term_disco_trigger_username(Trigger) ->
 
1303
    {ok, Trigger}.
 
1304
 
1240
1305
 
1241
1306
verify_user_id(UserId) when is_list(UserId) ->
1242
1307
    case (catch list_to_atom(UserId)) of
1743
1808
"%% {\"standard inform\", \"std_inform\", inform}.\n"
1744
1809
"%%\n\n",
1745
1810
    Hdr = header() ++ Comment, 
1746
 
    Conf = [{"stadard_trap", "std_trap", NotifyType}],
 
1811
    Conf = [{"standard trap", "std_trap", NotifyType}],
1747
1812
    write_agent_notify_config(Dir, Hdr, Conf).
1748
1813
 
1749
1814
write_agent_notify_config(Dir, Hdr, Conf) ->
2096
2161
    ok = io:format(Fid, "     {audit_trail_log, [", []),
2097
2162
    write_sys_config_file_agent_atl_opts(Fid, Opts),
2098
2163
    ok = io:format(Fid, "}", []);
 
2164
write_sys_config_file_agent_opt(Fid, {discovery, Opts}) ->
 
2165
    ok = io:format(Fid, "     {discovery, [", []),
 
2166
    write_sys_config_file_agent_disco_opts(Fid, Opts),
 
2167
    ok = io:format(Fid, "}", []);
2099
2168
write_sys_config_file_agent_opt(Fid, {net_if, Opts}) ->
2100
2169
    ok = io:format(Fid, "     {net_if, ~w}", [Opts]);
2101
2170
write_sys_config_file_agent_opt(Fid, {mib_server, Opts}) ->
2139
2208
write_sys_config_file_agent_atl_opt(Fid, {size, Size}) ->
2140
2209
    ok = io:format(Fid, "{size, ~w}", [Size]);
2141
2210
write_sys_config_file_agent_atl_opt(Fid, {repair, Rep}) ->
2142
 
    ok = io:format(Fid, "{repair, ~w}", [Rep]).
 
2211
    ok = io:format(Fid, "{repair, ~w}", [Rep]);
 
2212
write_sys_config_file_agent_atl_opt(Fid, {seqno, SeqNo}) ->
 
2213
    ok = io:format(Fid, "{seqno, ~w}", [SeqNo]).
 
2214
 
 
2215
 
 
2216
%% These options are allways there
 
2217
write_sys_config_file_agent_disco_opts(Fid, [Opt]) ->
 
2218
    write_sys_config_file_agent_disco_opt(Fid, Opt),
 
2219
    ok = io:format(Fid, "]", []),
 
2220
    ok;
 
2221
write_sys_config_file_agent_disco_opts(Fid, [Opt|Opts]) ->
 
2222
    write_sys_config_file_agent_disco_opt(Fid, Opt),
 
2223
    ok = io:format(Fid, ", ", []),
 
2224
    write_sys_config_file_agent_disco_opts(Fid, Opts).
 
2225
    
 
2226
write_sys_config_file_agent_disco_opt(Fid, {terminating, Opts}) ->
 
2227
    ok = io:format(Fid, "{terminating, [", []),
 
2228
    write_sys_config_file_agent_term_disco_opts(Fid, Opts),
 
2229
    ok = io:format(Fid, "}", []);
 
2230
write_sys_config_file_agent_disco_opt(Fid, {originating, Opts}) ->
 
2231
    ok = io:format(Fid, "{originating, [", []),
 
2232
    write_sys_config_file_agent_orig_disco_opts(Fid, Opts),
 
2233
    ok = io:format(Fid, "}", []).
 
2234
 
 
2235
write_sys_config_file_agent_term_disco_opts(Fid, [Opt]) ->
 
2236
    write_sys_config_file_agent_term_disco_opt(Fid, Opt),
 
2237
    ok = io:format(Fid, "]", []),
 
2238
    ok;
 
2239
write_sys_config_file_agent_term_disco_opts(Fid, [Opt|Opts]) ->
 
2240
    write_sys_config_file_agent_term_disco_opt(Fid, Opt),
 
2241
    ok = io:format(Fid, ", ", []),
 
2242
    write_sys_config_file_agent_term_disco_opts(Fid, Opts).
 
2243
    
 
2244
write_sys_config_file_agent_term_disco_opt(Fid, {enable, Enable}) ->
 
2245
    ok = io:format(Fid, "{enable, ~w}", [Enable]);
 
2246
write_sys_config_file_agent_term_disco_opt(Fid, {stage2, Stage2}) ->
 
2247
    ok = io:format(Fid, "{stage2, ~w}", [Stage2]);
 
2248
write_sys_config_file_agent_term_disco_opt(Fid, {trigger_username, Trigger}) ->
 
2249
    ok = io:format(Fid, "{trigger_username, \"~s\"}", [Trigger]).
 
2250
 
 
2251
write_sys_config_file_agent_orig_disco_opts(Fid, [Opt]) ->
 
2252
    write_sys_config_file_agent_orig_disco_opt(Fid, Opt),
 
2253
    ok = io:format(Fid, "]", []),
 
2254
    ok;
 
2255
write_sys_config_file_agent_orig_disco_opts(Fid, [Opt|Opts]) ->
 
2256
    write_sys_config_file_agent_orig_disco_opt(Fid, Opt),
 
2257
    ok = io:format(Fid, ", ", []),
 
2258
    write_sys_config_file_agent_orig_disco_opts(Fid, Opts).
 
2259
    
 
2260
write_sys_config_file_agent_orig_disco_opt(Fid, {enable, Enable}) ->
 
2261
    ok = io:format(Fid, "{enable, ~w}", [Enable]).
 
2262
 
2143
2263
 
2144
2264
 
2145
2265
write_sys_config_file_manager_opts(Fid, [Opt]) ->