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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmpa_mib_lib.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
3
%% 
4
 
%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2004-2011. All Rights Reserved.
5
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
19
19
-module(snmpa_mib_lib).
20
20
 
21
21
-export([table_cre_row/3, table_del_row/2]).
22
 
-export([get_table/2, print_table/3, print_table/4, print_tables/1]).
 
22
-export([get_table/2]).
 
23
-export([print_variables/1, print_table/3, print_table/4, print_tables/1]).
23
24
-export([gc_tab/3, gc_tab/5]).
24
25
 
25
26
-include("SNMPv2-TC.hrl").
81
82
    end.
82
83
    
83
84
 
 
85
print_variables(Variables) when is_list(Variables) ->
 
86
    Variables2 = print_variables_prefixify(Variables), 
 
87
    lists:foreach(fun({Variable, ValueResult, Prefix}) ->
 
88
                          print_variable(Variable, ValueResult, Prefix)
 
89
                  end, Variables2),
 
90
    ok.
 
91
 
 
92
print_variable(Variable, {value, Val}, Prefix) when is_atom(Variable) ->
 
93
    io:format("~w~s=> ~p~n", [Variable, Prefix, Val]);
 
94
print_variable(Variable, Error, Prefix) when is_atom(Variable) ->
 
95
    io:format("~w~s=> [e] ~p~n", [Variable, Prefix, Error]).
 
96
 
 
97
print_variables_prefixify(Variables) ->
 
98
    MaxVarLength = print_variables_maxlength(Variables),
 
99
    print_variables_prefixify(Variables, MaxVarLength, []).
 
100
 
 
101
print_variables_prefixify([], _MaxVarLength, Acc) ->
 
102
    lists:reverse(Acc);
 
103
print_variables_prefixify([{Var, Res}|Variables], MaxVarLength, Acc) ->
 
104
    Prefix = make_variable_print_prefix(Var, MaxVarLength),
 
105
    print_variables_prefixify(Variables, MaxVarLength, 
 
106
                              [{Var, Res, Prefix}|Acc]).
 
107
    
 
108
make_variable_print_prefix(Var, MaxVarLength) ->
 
109
    lists:duplicate(MaxVarLength - length(atom_to_list(Var)) + 1, $ ).
 
110
 
 
111
print_variables_maxlength(Variables) ->
 
112
    print_variables_maxlength(Variables, 0).
 
113
 
 
114
print_variables_maxlength([], MaxLength) ->
 
115
    MaxLength;
 
116
print_variables_maxlength([{Var, _}|Variables], MaxLength) when is_atom(Var) ->
 
117
    VarLen = length(atom_to_list(Var)),
 
118
    if 
 
119
        VarLen > MaxLength ->
 
120
            print_variables_maxlength(Variables, VarLen);
 
121
        true ->
 
122
            print_variables_maxlength(Variables, MaxLength)
 
123
    end.
 
124
 
 
125
 
84
126
print_tables(Tables) when is_list(Tables) ->
85
127
    lists:foreach(fun({Table, DB, FOI, PrintRow}) ->
86
128
                          print_table(Table, DB, FOI, PrintRow)
87
129
                  end, Tables),
88
130
    ok.
89
131
 
90
 
%% print_table(Table, DB, FOI, PrintRow) ->
91
 
%%     TableInfo = get_table(DB(Table), FOI(Table)),
92
 
%%     print_table(Table, TableInfo, PrintRow),
93
 
%%     ok.
94
 
 
95
132
print_table(Table, DB, FOI, PrintRow) ->
96
133
    TableInfo = get_table(DB, FOI),
97
134
    print_table(Table, TableInfo, PrintRow).
98
135
 
99
136
print_table(Table, TableInfo, PrintRow) when is_function(PrintRow, 2) ->
100
 
    io:format("~w => ~n", [Table]),
 
137
    io:format("~w =>", [Table]),
101
138
    do_print_table(TableInfo, PrintRow).
102
139
 
 
140
do_print_table({ok, [] = _TableInfo}, _PrintRow) ->
 
141
    io:format(" -~n", []);
103
142
do_print_table({ok, TableInfo}, PrintRow) when is_function(PrintRow, 2) ->
 
143
    io:format("~n", []),
104
144
    lists:foreach(fun({RowIdx, Row}) ->
105
145
                          io:format("   ~w => ~n~s~n", 
106
146
                                    [RowIdx, PrintRow("      ", Row)])
107
 
                  end, TableInfo),
108
 
    io:format("~n", []);
 
147
                  end, TableInfo);
109
148
do_print_table({error, {invalid_rowindex, BadRowIndex, []}}, _PrintRow) ->
110
149
    io:format("Error: Bad rowindex ~w~n", [BadRowIndex]);
111
150
do_print_table({error, {invalid_rowindex, BadRowIndex, TableInfo}}, PrintRow) ->