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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmp_standard_mib.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
-module(snmp_standard_mib).
 
19
 
 
20
%%%-----------------------------------------------------------------
 
21
%%% This module implements the configure- and reinit-functions
 
22
%%% for the STANDARD-MIB and SNMPv2-MIB.
 
23
%%%-----------------------------------------------------------------
 
24
 
 
25
-include("snmp_types.hrl").
 
26
-include("STANDARD-MIB.hrl").
 
27
 
 
28
-define(VMODULE,"STANDARD-MIB").
 
29
-include("snmp_verbosity.hrl").
 
30
 
 
31
-define(enabled, 1).
 
32
-define(disabled, 2).
 
33
 
 
34
%% External exports
 
35
-export([configure/1, reconfigure/1, reset/0, sys_up_time/0, sys_up_time/1,
 
36
         snmp_enable_authen_traps/1, snmp_enable_authen_traps/2,
 
37
         sys_object_id/1, sys_object_id/2, sys_or_table/3,
 
38
         variable_func/1, variable_func/2,
 
39
         inc/1, inc/2]).
 
40
-export([dummy/1, snmp_set_serial_no/1, snmp_set_serial_no/2]).
 
41
-export([add_agent_caps/2, del_agent_caps/1, get_agent_caps/0]).
 
42
-export([check_standard/1]).
 
43
 
 
44
 
 
45
%%-----------------------------------------------------------------
 
46
%% Func: configure/1
 
47
%% Args: Dir is the directory with trailing dir_separator where
 
48
%%       the configuration files can be found.
 
49
%% Purpose: Reads the config-files for the standard mib, and
 
50
%%          inserts the data.  Persistent data that is already
 
51
%%          present is *not* changed!  (use reconfigure for that)
 
52
%% Returns: ok
 
53
%% Fails: exit(configuration_error)
 
54
%%-----------------------------------------------------------------
 
55
configure(Dir) ->
 
56
    case (catch do_configure(Dir)) of
 
57
        ok ->
 
58
            ok;
 
59
        {error, Reason} ->
 
60
            ?vinfo("configure error: ~p", [Reason]),
 
61
            config_err("configure failed: ~p", [Reason]),
 
62
            exit(configuration_error);
 
63
        Error ->
 
64
            ?vinfo("configure failed: ~p", [Error]),
 
65
            config_err("configure failed: ~p", [Error]),
 
66
            exit(configuration_error)
 
67
    end.
 
68
 
 
69
do_configure(Dir) ->
 
70
    case snmpa_agent:get_agent_mib_storage() of
 
71
        mnesia ->
 
72
            ok;
 
73
        _ ->
 
74
            Standard = read_standard(Dir),
 
75
            lists:map(fun maybe_create_persistent_var/1, Standard)
 
76
    end,
 
77
    snmpa_local_db:variable_set({next_sys_or_index, volatile}, 1),
 
78
    %% sysORTable is always volatile
 
79
    snmp_generic:table_func(new, {sysORTable, volatile}),
 
80
    ok.
 
81
 
 
82
 
 
83
%%-----------------------------------------------------------------
 
84
%% Func: reconfigure/1
 
85
%% Args: Dir is the directory with trailing dir_separator where
 
86
%%       the configuration files can be found.
 
87
%% Purpose: Reads the config-files for the standard mib, and
 
88
%%          inserts the data.  Persistent data that is already
 
89
%%          present is deleted.  Makes sure the config file
 
90
%%          data is used.
 
91
%% Returns: ok
 
92
%% Fails: exit(configuration_error)
 
93
%%-----------------------------------------------------------------
 
94
reconfigure(Dir) ->
 
95
    set_sname(),
 
96
    case (catch do_reconfigure(Dir)) of
 
97
        ok ->
 
98
            ok;
 
99
        {error, Reason} ->
 
100
            ?vinfo("reconfigure error: ~p", [Reason]),
 
101
            config_err("reconfigure failed: ~p", [Reason]),
 
102
            exit(configuration_error);
 
103
        Error ->
 
104
            ?vinfo("reconfigure failed: ~p", [Error]),
 
105
            config_err("reconfigure failed: ~p", [Error]),
 
106
            exit(configuration_error)
 
107
    end.
 
108
 
 
109
do_reconfigure(Dir) ->
 
110
    Standard = read_standard(Dir),
 
111
    lists:map(fun create_persistent_var/1, Standard),
 
112
    snmpa_local_db:variable_set({next_sys_or_index, volatile}, 1),
 
113
    snmp_generic:table_func(new, {sysORTable, volatile}),
 
114
    ok.
 
115
 
 
116
 
 
117
%%-----------------------------------------------------------------
 
118
%% Func: read_standard/1
 
119
%% Args: Dir is the directory with trailing dir_separator where
 
120
%%       the configuration files can be found.
 
121
%% Purpose: Reads th standard configuration file.
 
122
%% Returns: A list of standard variables
 
123
%% Fails: If an error occurs, the process will die with Reason
 
124
%%        configuration_error.
 
125
%%-----------------------------------------------------------------
 
126
read_standard(Dir) ->
 
127
    ?vdebug("check standard config file",[]),
 
128
    Gen    = fun(_) -> ok end,
 
129
    Filter = fun(Standard) -> sort_standard(Standard) end,
 
130
    Check  = fun(Entry) -> check_standard(Entry) end,
 
131
    [Standard] = 
 
132
        snmp_conf:read_files(Dir, [{Gen, Filter, Check, "standard.conf"}]), 
 
133
    Standard.
 
134
 
 
135
 
 
136
%%-----------------------------------------------------------------
 
137
%% Make sure that each mandatory standard attribute is present, and
 
138
%% provide default values for the other non-present attributes.
 
139
%%-----------------------------------------------------------------
 
140
sort_standard(L) ->
 
141
    Mand = [{sysContact, {value, ""}},
 
142
            {sysDescr, {value, ""}},
 
143
            {sysLocation, {value, ""}},
 
144
            {sysName, {value, ""}},
 
145
            {sysObjectID, mandatory},
 
146
            {sysServices, mandatory},
 
147
            {snmpEnableAuthenTraps, mandatory}],
 
148
    {ok, L2} = snmp_conf:check_mandatory(L, Mand),
 
149
    lists:keysort(1, L2).
 
150
 
 
151
 
 
152
%%-----------------------------------------------------------------
 
153
%%  Standard
 
154
%%  {Name, Value}.
 
155
%%-----------------------------------------------------------------
 
156
check_standard({sysDescr,    Value}) -> snmp_conf:check_string(Value);
 
157
check_standard({sysObjectID, Value}) -> snmp_conf:check_oid(Value);
 
158
check_standard({sysContact,  Value}) -> snmp_conf:check_string(Value);
 
159
check_standard({sysName,     Value}) -> snmp_conf:check_string(Value);
 
160
check_standard({sysLocation, Value}) -> snmp_conf:check_string(Value);
 
161
check_standard({sysServices, Value}) -> snmp_conf:check_integer(Value);
 
162
check_standard({snmpEnableAuthenTraps, Value}) ->
 
163
    Atoms = [{enabled,  ?snmpEnableAuthenTraps_enabled},
 
164
             {disabled, ?snmpEnableAuthenTraps_disabled}],
 
165
    {ok, Val} = snmp_conf:check_atom(Value, Atoms),
 
166
    {ok, {snmpEnableAuthenTraps, Val}};
 
167
check_standard({Attrib, _Value}) -> error({unknown_attribute, Attrib});
 
168
check_standard(X) -> error({invalid_standard_specification, X}).
 
169
 
 
170
 
 
171
%%-----------------------------------------------------------------
 
172
%% Func: reset/0
 
173
%% Purpose: Resets all counters (sets them to 0).
 
174
%%-----------------------------------------------------------------
 
175
reset() ->
 
176
    snmpa_mpd:reset().
 
177
 
 
178
maybe_create_persistent_var({Var, Val}) ->
 
179
    case snmp_generic:variable_get({Var, persistent}) of
 
180
        {value, _} -> ok;
 
181
        _ -> snmp_generic:variable_set({Var, persistent}, Val)
 
182
    end.
 
183
 
 
184
create_persistent_var({Var, Val}) ->
 
185
    snmp_generic:variable_set({Var, persistent}, Val).
 
186
 
 
187
variable_func(_Op) -> ok.
 
188
 
 
189
variable_func(get, Name) ->
 
190
    [{_, Val}] = ets:lookup(snmp_agent_table, Name),
 
191
    {value, Val}.
 
192
    
 
193
 
 
194
%%-----------------------------------------------------------------
 
195
%%  inc(VariableName) increments the variable (Counter) in
 
196
%%  the local mib. (e.g. snmpInPkts)
 
197
%%-----------------------------------------------------------------
 
198
inc(Name) -> inc(Name, 1).
 
199
inc(Name, N) -> ets:update_counter(snmp_agent_table, Name, N).
 
200
 
 
201
%%-----------------------------------------------------------------
 
202
%% This is the instrumentation function for sysUpTime.
 
203
%%-----------------------------------------------------------------
 
204
sys_up_time() ->
 
205
    snmpa:sys_up_time().
 
206
 
 
207
sys_up_time(get) ->
 
208
    {value, snmpa:sys_up_time()}.
 
209
 
 
210
%%-----------------------------------------------------------------
 
211
%% This is the instrumentation function for snmpEnableAuthenTraps
 
212
%%-----------------------------------------------------------------
 
213
snmp_enable_authen_traps(new) ->
 
214
    snmp_generic:variable_func(new, db(snmpEnableAuthenTraps));
 
215
 
 
216
snmp_enable_authen_traps(delete) ->
 
217
    ok;
 
218
 
 
219
snmp_enable_authen_traps(get) ->
 
220
    snmp_generic:variable_func(get, db(snmpEnableAuthenTraps)).
 
221
 
 
222
snmp_enable_authen_traps(set, NewVal) ->
 
223
    snmp_generic:variable_func(set, NewVal, db(snmpEnableAuthenTraps)).
 
224
 
 
225
%%-----------------------------------------------------------------
 
226
%% This is the instrumentation function for sysObjectId
 
227
%%-----------------------------------------------------------------
 
228
sys_object_id(new) ->
 
229
    snmp_generic:variable_func(new, db(sysObjectID));
 
230
 
 
231
sys_object_id(delete) ->
 
232
    ok;
 
233
 
 
234
sys_object_id(get) ->
 
235
    snmp_generic:variable_func(get, db(sysObjectID)).
 
236
 
 
237
sys_object_id(set, NewVal) ->
 
238
    snmp_generic:variable_func(set, NewVal, db(sysObjectID)).
 
239
 
 
240
%%-----------------------------------------------------------------
 
241
%% This is a dummy instrumentation function for objects like
 
242
%% snmpTrapOID, that is accessible-for-notify, with different
 
243
%% values each time.  This function will only be called with
 
244
%% new/delete.
 
245
%%-----------------------------------------------------------------
 
246
dummy(_Op) -> ok.
 
247
 
 
248
%%-----------------------------------------------------------------
 
249
%% This is the instrumentation function for snmpSetSerialNo.
 
250
%% It is always volatile.
 
251
%%-----------------------------------------------------------------
 
252
snmp_set_serial_no(new) ->
 
253
    snmp_generic:variable_func(new, {snmpSetSerialNo, volatile}),
 
254
    {A1,A2,A3} = erlang:now(),
 
255
    random:seed(A1,A2,A3),
 
256
    Val = random:uniform(2147483648) - 1,
 
257
    snmp_generic:variable_func(set, Val, {snmpSetSerialNo, volatile});
 
258
 
 
259
snmp_set_serial_no(delete) ->
 
260
    ok;
 
261
 
 
262
snmp_set_serial_no(get) ->
 
263
    snmp_generic:variable_func(get, {snmpSetSerialNo, volatile}).
 
264
 
 
265
snmp_set_serial_no(is_set_ok, NewVal) ->
 
266
    case snmp_generic:variable_func(get, {snmpSetSerialNo, volatile}) of
 
267
        {value, NewVal} -> noError;
 
268
        _ -> inconsistentValue
 
269
    end;
 
270
snmp_set_serial_no(set, NewVal) ->
 
271
    snmp_generic:variable_func(set, (NewVal + 1) rem 2147483648,
 
272
                               {snmpSetSerialNo, volatile}).
 
273
 
 
274
%%-----------------------------------------------------------------
 
275
%% This is the instrumentation function for sysOrTable
 
276
%%-----------------------------------------------------------------
 
277
sys_or_table(Op, RowIndex, Cols) ->
 
278
    snmp_generic:table_func(Op, RowIndex, Cols, {sysORTable, volatile}).
 
279
 
 
280
add_agent_caps(Oid, Descr) when list(Oid), list(Descr) ->
 
281
    {value, Next} = snmpa_local_db:variable_get({next_sys_or_index, volatile}),
 
282
    snmpa_local_db:variable_set({next_sys_or_index, volatile}, Next+1),
 
283
    SysUpTime = sys_up_time(),
 
284
    Row = {Next, Oid, Descr, SysUpTime},
 
285
    snmpa_local_db:table_create_row({sysORTable, volatile}, [Next], Row),
 
286
    snmpa_local_db:variable_set({sysORLastChange, volatile}, SysUpTime),
 
287
    Next.
 
288
 
 
289
del_agent_caps(Index) ->
 
290
    snmpa_local_db:table_delete_row({sysORTable, volatile}, [Index]),
 
291
    snmpa_local_db:variable_set({sysORLastChange, volatile}, sys_up_time()).
 
292
 
 
293
get_agent_caps() ->
 
294
    snmpa_local_db:match({sysORTable, volatile}, {'$1', '$2', '$3', '$4'}).
 
295
 
 
296
 
 
297
db(Var) -> snmpa_agent:db(Var).
 
298
 
 
299
 
 
300
%% -----
 
301
 
 
302
set_sname() ->
 
303
    set_sname(get(sname)).
 
304
 
 
305
set_sname(undefined) ->
 
306
    put(sname,conf);
 
307
set_sname(_) -> %% Keep it, if already set.
 
308
    ok.
 
309
 
 
310
error(Reason) ->
 
311
    throw({error, Reason}).
 
312
 
 
313
config_err(F, A) ->
 
314
    snmpa_error:config_err("[STANDARD-MIB]: " ++ F, A).