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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmp_shadow_table.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_shadow_table).
 
19
 
 
20
-export([table_func/2, table_func/4]).
 
21
 
 
22
-include("snmpa_internal.hrl").
 
23
 
 
24
-record(time_stamp, {key, data}).
 
25
 
 
26
-define(verify(Expr, Error), verify(catch Expr, Error, ?FILE, ?LINE)).
 
27
 
 
28
verify(Res, Error, File, Line) ->
 
29
    case Res of
 
30
        {atomic, _} ->
 
31
            Res;
 
32
        ok ->
 
33
            Res;
 
34
        _ ->
 
35
            error_msg("~s(~w): crashed ~p -> ~p ~p~n",
 
36
                      [File, Line, Error, Res, process_info(self())]),
 
37
            Res
 
38
    end.
 
39
 
 
40
 
 
41
%%%-----------------------------------------------------------------
 
42
%%% This module contains generic functions for implementing an SNMP
 
43
%%% table as a 'shadow'-table in Mnesia.  This means that for the
 
44
%%% SNMP table, there exists one Mnesia table with all information
 
45
%%% of the table.
 
46
%%% The Mnesia table is updated whenever an SNMP request is issued
 
47
%%% for the table and a specified amount of time has past since the
 
48
%%% last update.
 
49
%%% This is implemented as instrumentation functions to be used
 
50
%%% for the table.
 
51
%%%-----------------------------------------------------------------
 
52
 
 
53
create_time_stamp_table() ->
 
54
    Props = [{type, set},
 
55
             {attributes, record_info(fields, time_stamp)}],
 
56
    create_table(time_stamp, Props, ram_copies, false),
 
57
    NRef = 
 
58
        case mnesia:dirty_read({time_stamp, ref_count}) of
 
59
            [] -> 1;
 
60
            [#time_stamp{data = Ref}] -> Ref + 1
 
61
        end,
 
62
    ok = mnesia:dirty_write(#time_stamp{key = ref_count, data = NRef}).
 
63
 
 
64
delete_time_stamp_table() ->
 
65
    Tab = time_stamp,
 
66
    case catch mnesia:dirty_read({Tab, ref_count}) of
 
67
        {'EXIT', _Reason} ->
 
68
            delete_table(Tab);
 
69
        [] ->
 
70
            delete_table(Tab);
 
71
        [#time_stamp{data = 1}] ->
 
72
            delete_table(Tab);
 
73
        [#time_stamp{data = Ref}] ->
 
74
            ok = mnesia:dirty_write(#time_stamp{key = ref_count, data = Ref - 1})
 
75
    end.
 
76
 
 
77
update(Name, UpdateFunc, Interval) ->
 
78
    CurrentTime = get_time(),
 
79
    case mnesia:dirty_read({time_stamp, Name}) of
 
80
        [#time_stamp{data = Expire}] when CurrentTime =< Expire -> ok;
 
81
        _ ->
 
82
            UpdateFunc(),
 
83
            ok = mnesia:dirty_write(#time_stamp{key = Name,
 
84
                                                data = CurrentTime + Interval})
 
85
    end.
 
86
          
 
87
 
 
88
%%-----------------------------------------------------------------
 
89
%% Func: table_func(Op, Extra)
 
90
%%       table_func(Op, RowIndex, Cols, Extra)
 
91
%% Args: Extra = {Name, SnmpKey, Attributes, Interval, UpdateFunc}
 
92
%% Purpose: Instrumentation function for the table.
 
93
%%          Name is the name of the table
 
94
%%          SnmpKey is the snmpkey as it should be specifed in order
 
95
%%            to create the Mnesia table as an SNMP table
 
96
%%          Attributes is the attributes as it should be specifed in order
 
97
%%            to create the Mnesia table as an SNMP table
 
98
%%          Interval is the minimum time in milliseconds between two
 
99
%%            updates of the table
 
100
%%          UpdateFunc is a function with no arguments that is called
 
101
%%            whenever the table must be updated
 
102
%% Returns: As specified for an SNMP table instrumentation function.
 
103
%%-----------------------------------------------------------------
 
104
table_func(new, {Name, SnmpKey, Attribs, _Interval, _UpdateFunc}) ->
 
105
    create_time_stamp_table(),
 
106
    Props = [{type, set},
 
107
             {snmp, [{key, SnmpKey}]},
 
108
             {attributes, Attribs}],
 
109
    create_table(Name, Props, ram_copies, true);
 
110
table_func(delete, {Name, _SnmpKey, _Attribs, _Interval, _UpdateFunc}) ->
 
111
    delete_time_stamp_table(),
 
112
    delete_table(Name).
 
113
 
 
114
table_func(Op, RowIndex, Cols, 
 
115
           {Name, _SnmpKey, _Attribs, Interval, UpdateFunc}) ->
 
116
    update(Name, UpdateFunc, Interval),
 
117
    snmp_generic:table_func(Op, RowIndex, Cols, {Name, mnesia}).
 
118
 
 
119
get_time() ->
 
120
    {M,S,U} = erlang:now(),
 
121
    1000000000 * M + 1000 * S + (U div 1000).
 
122
 
 
123
%%-----------------------------------------------------------------
 
124
%% Urrk.
 
125
%% We want named tables, without schema info; the tables should
 
126
%% be locally named, but if the node crashes, info about the
 
127
%% table shouldn't be kept.  We could use ets tables for this.
 
128
%% BUT, we also want the snmp functionality, therefore we must
 
129
%% use mnesia.
 
130
%% The problem arises when the node that implements these tables
 
131
%% crashes, and another node takes over the MIB-implementations.
 
132
%% That node cannot create the shadow tables again, because they
 
133
%% already exist (according to mnesia...).  Therefore, we must
 
134
%% check if we maybe must delete the table first, and then create
 
135
%% it again.
 
136
%%-----------------------------------------------------------------
 
137
create_table(Tab, Props, Storage, DeleteAll) ->
 
138
    case lists:member(Tab, mnesia:system_info(tables)) of
 
139
        true ->
 
140
            case mnesia:table_info(Tab, storage_type) of
 
141
                unknown ->
 
142
                    ?verify(mnesia:add_table_copy(Tab, node(), Storage),
 
143
                            [add_table_copy, Tab, node(), Storage]);
 
144
                Storage when DeleteAll == true ->
 
145
                    delete_all(Tab);
 
146
                _ ->
 
147
                    ignore
 
148
            end;
 
149
        false ->
 
150
            Nodes = [node()],
 
151
            Props2 = [{local_content, true}, {Storage, Nodes}] ++ Props,
 
152
            ?verify(mnesia:create_table(Tab, Props2),
 
153
                    [create_table, Tab, Props2])
 
154
    end.
 
155
 
 
156
delete_all(Tab) ->
 
157
    delete_all(mnesia:dirty_first(Tab), Tab).
 
158
 
 
159
delete_all('$end_of_table', _Tab) ->
 
160
    ok;
 
161
delete_all(Key, Tab) ->
 
162
    ok = mnesia:dirty_delete({Tab, Key}),
 
163
    delete_all(mnesia:dirty_next(Tab, Key), Tab).
 
164
 
 
165
delete_table(Tab) ->
 
166
    case lists:member(Tab, mnesia:system_info(tables)) of
 
167
        true ->
 
168
            case ?verify(mnesia:del_table_copy(Tab, node()),
 
169
                         [del_table_copy, Tab, node()]) of
 
170
                {atomic, ok} ->
 
171
                    ok;
 
172
                {aborted, _Reason} ->
 
173
                    catch delete_all(Tab),
 
174
                    ok
 
175
            end;
 
176
        false ->
 
177
            ok
 
178
    end.
 
179
 
 
180
 
 
181
%%-----------------------------------------------------------------
 
182
 
 
183
error_msg(F, A) ->
 
184
    ?snmpa_error(F, A).
 
185
 
 
186