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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_set.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_set).
19
 
 
20
 
-define(VMODULE,"SET").
21
 
-include("snmp_verbosity.hrl").
22
 
 
23
 
 
24
 
%%%-----------------------------------------------------------------
25
 
%%% This module implements a simple, basic atomic set mechanism.
26
 
%%%-----------------------------------------------------------------
27
 
%%% Table of contents
28
 
%%% =================
29
 
%%% 1. SET REQUEST
30
 
%%% 1.1 SET phase one
31
 
%%% 1.2 SET phase two
32
 
%%% 2. Misc functions
33
 
%%%-----------------------------------------------------------------
34
 
 
35
 
%% External exports
36
 
-export([do_set/2, do_subagent_set/1]).
37
 
 
38
 
%%%-----------------------------------------------------------------
39
 
%%% 1. SET REQUEST
40
 
%%%
41
 
%%% 1) Perform set_phase_one for all own vars
42
 
%%% 2) Perform set_phase_one for all SAs
43
 
%%%    IF nok THEN 2.1 ELSE 3
44
 
%%% 2.1) Perform set_phase_two(undo) for all SAs that have performed
45
 
%%%      set_phase_one.
46
 
%%% 3) Perform set_phase_two for all own vars
47
 
%%% 4) Perform set_phase_two(set) for all SAs
48
 
%%%    IF nok THEN 4.1 ELSE 5
49
 
%%% 4.1) Perform set_phase_two(undo) for all SAs that have performed
50
 
%%%      set_phase_one but not set_phase_two(set).
51
 
%%% 5) noError
52
 
%%%-----------------------------------------------------------------
53
 
%%-----------------------------------------------------------------
54
 
%% First of all - validate MibView for all varbinds. In this way
55
 
%% we don't have to send the MibView to all SAs for validation.
56
 
%%-----------------------------------------------------------------
57
 
do_set(MibView, UnsortedVarbinds) ->
58
 
    ?vtrace("do set with"
59
 
            "~n   MibView: ~p",[MibView]),
60
 
    case snmp_acm:validate_all_mib_view(UnsortedVarbinds, MibView) of
61
 
        true ->
62
 
            {MyVarbinds , SubagentVarbinds} = 
63
 
                sort_varbindlist(UnsortedVarbinds),
64
 
            case set_phase_one(MyVarbinds, SubagentVarbinds) of
65
 
                {noError, 0} -> set_phase_two(MyVarbinds, SubagentVarbinds);
66
 
                {Reason, Index} -> {Reason, Index}
67
 
            end;
68
 
        {false, Index} ->
69
 
            {noAccess, Index}
70
 
    end.
71
 
 
72
 
%%-----------------------------------------------------------------
73
 
%% This function is called when a subagents receives a message
74
 
%% concerning some set_phase.
75
 
%% Mandatory messages for all subagents:
76
 
%%   [phase_one, UnsortedVarbinds]
77
 
%%   [phase_two, set, UnsortedVarbinds]
78
 
%%   [phase_two, undo, UnsortedVarbinds]
79
 
%%-----------------------------------------------------------------
80
 
do_subagent_set([phase_one, UnsortedVarbinds]) ->
81
 
    ?vtrace("do subagent set, phase one",[]),
82
 
    {MyVarbinds, SubagentVarbinds} = sort_varbindlist(UnsortedVarbinds),
83
 
    set_phase_one(MyVarbinds, SubagentVarbinds);
84
 
do_subagent_set([phase_two, State, UnsortedVarbinds]) ->
85
 
    ?vtrace("do subagent set, phase two",[]),
86
 
    {MyVarbinds, SubagentVarbinds} = sort_varbindlist(UnsortedVarbinds),
87
 
    set_phase_two(State, MyVarbinds, SubagentVarbinds).
88
 
    
89
 
%%%-----------------------------------------------------------------
90
 
%%% 1.1 SET phase one
91
 
%%%-----------------------------------------------------------------
92
 
%%-----------------------------------------------------------------
93
 
%% Func: set_phase_one/3
94
 
%% Purpose: First, do set_phase_one for my own variables (i.e. 
95
 
%%          variables handled by this agent). Then, do set_phase_one
96
 
%%          for all subagents. If any SA failed, do set_phase_two
97
 
%%          (undo) for all SA that have done set_phase_one.
98
 
%% Returns: {noError, 0} | {ErrorStatus, Index}
99
 
%%-----------------------------------------------------------------
100
 
set_phase_one(MyVarbinds, SubagentVarbinds) ->
101
 
    ?vtrace("set phase one: "
102
 
            "~n   MyVarbinds:       ~p"
103
 
            "~n   SubagentVarbinds: ~p",
104
 
            [MyVarbinds, SubagentVarbinds]),
105
 
    case set_phase_one_my_variables(MyVarbinds) of
106
 
        {noError, 0} ->
107
 
            case set_phase_one_subagents(SubagentVarbinds, []) of
108
 
                {noError, 0} ->
109
 
                    {noError, 0};
110
 
                {{ErrorStatus, Index}, PerformedSubagents} ->
111
 
                    case set_phase_two_undo(MyVarbinds, PerformedSubagents) of
112
 
                        {noError, 0} ->
113
 
                            {ErrorStatus, Index};
114
 
                        {WorseErrorStatus, WorseIndex} ->
115
 
                            {WorseErrorStatus, WorseIndex}
116
 
                    end
117
 
            end;
118
 
        {ErrorStatus, Index} ->
119
 
            {ErrorStatus, Index}
120
 
    end.
121
 
 
122
 
set_phase_one_my_variables(MyVarbinds) ->
123
 
    ?vtrace("my variables set, phase one:"
124
 
            "~n   ~p",[MyVarbinds]),
125
 
    case snmp_set_lib:is_varbinds_ok(MyVarbinds) of
126
 
        {noError, 0} ->
127
 
            snmp_set_lib:consistency_check(MyVarbinds);
128
 
        {ErrorStatus, Index} ->
129
 
            {ErrorStatus, Index}
130
 
    end.
131
 
 
132
 
%%-----------------------------------------------------------------
133
 
%% Loop all subagents, and perform set_phase_one for them.
134
 
%%-----------------------------------------------------------------
135
 
set_phase_one_subagents([{SubAgentPid, SAVbs}|SubagentVarbinds], Done) ->
136
 
    {_SAOids, Vbs} = sa_split(SAVbs),
137
 
    case catch snmp_agent:subagent_set(SubAgentPid, [phase_one, Vbs]) of
138
 
        {noError, 0} ->
139
 
            set_phase_one_subagents(SubagentVarbinds, 
140
 
                                    [{SubAgentPid, SAVbs} | Done]);
141
 
        {ErrorStatus, ErrorIndex} ->
142
 
            {{ErrorStatus, ErrorIndex}, Done};
143
 
        {'EXIT', Reason} ->
144
 
            user_err("Lost contact with subagent (set phase_one)"
145
 
                     "~n~w. Using genErr", [Reason]),
146
 
            {{genErr, 0}, Done}
147
 
    end;
148
 
set_phase_one_subagents([], _Done) ->
149
 
    {noError, 0}.
150
 
 
151
 
%%%-----------------------------------------------------------------
152
 
%%% 1.2 SET phase two
153
 
%%%-----------------------------------------------------------------
154
 
%% returns:  {ErrStatus, ErrIndex}
155
 
set_phase_two(MyVarbinds, SubagentVarbinds) ->
156
 
    ?vtrace("set phase two: "
157
 
            "~n   MyVarbinds:       ~p"
158
 
            "~n   SubagentVarbinds: ~p",
159
 
            [MyVarbinds, SubagentVarbinds]),
160
 
    case snmp_set_lib:try_set(MyVarbinds) of
161
 
        {noError, 0} ->
162
 
            set_phase_two_subagents(SubagentVarbinds);
163
 
        {ErrorStatus, Index} ->
164
 
            set_phase_two_undo_subagents(SubagentVarbinds),
165
 
            {ErrorStatus, Index}
166
 
    end.
167
 
 
168
 
%%-----------------------------------------------------------------
169
 
%% This function is called for each phase_two state in the
170
 
%% subagents. The undo state just pass undo along to each of its
171
 
%% subagents.
172
 
%%-----------------------------------------------------------------
173
 
set_phase_two(set, MyVarbinds, SubagentVarbinds) ->
174
 
    set_phase_two(MyVarbinds, SubagentVarbinds);
175
 
set_phase_two(undo, MyVarbinds, SubagentVarbinds) ->
176
 
    set_phase_two_undo(MyVarbinds, SubagentVarbinds).
177
 
 
178
 
%%-----------------------------------------------------------------
179
 
%% Loop all subagents, and perform set_phase_two(set) for them.
180
 
%% If any fails, perform set_phase_two(undo) for the not yet
181
 
%% called SAs.
182
 
%%-----------------------------------------------------------------
183
 
set_phase_two_subagents([{SubAgentPid, SAVbs} | SubagentVarbinds]) ->
184
 
    {_SAOids, Vbs} = sa_split(SAVbs),
185
 
    case catch snmp_agent:subagent_set(SubAgentPid, [phase_two, set, Vbs]) of
186
 
        {noError, 0} ->
187
 
            set_phase_two_subagents(SubagentVarbinds);
188
 
        {ErrorStatus, ErrorIndex} ->
189
 
            set_phase_two_undo_subagents(SubagentVarbinds),
190
 
            {ErrorStatus, ErrorIndex};
191
 
        {'EXIT', Reason} ->
192
 
            user_err("Lost contact with subagent (set)~n~w. Using genErr", 
193
 
                     [Reason]),
194
 
            set_phase_two_undo_subagents(SubagentVarbinds),
195
 
            {genErr, 0}
196
 
    end;
197
 
set_phase_two_subagents([]) ->
198
 
    {noError, 0}.
199
 
 
200
 
%%-----------------------------------------------------------------
201
 
%% This function undos phase_one, own and subagent.
202
 
%%-----------------------------------------------------------------
203
 
set_phase_two_undo(MyVarbinds, SubagentVarbinds) ->
204
 
    case set_phase_two_undo_my_variables(MyVarbinds) of
205
 
        {noError, 0} ->
206
 
            set_phase_two_undo_subagents(SubagentVarbinds);
207
 
        {ErrorStatus, Index} ->
208
 
            set_phase_two_undo_subagents(SubagentVarbinds),
209
 
            {ErrorStatus, Index}
210
 
    end.
211
 
 
212
 
set_phase_two_undo_my_variables(MyVarbinds) ->
213
 
    snmp_set_lib:undo_varbinds(MyVarbinds).
214
 
 
215
 
set_phase_two_undo_subagents([{SubAgentPid, SAVbs} | SubagentVarbinds]) ->
216
 
    {_SAOids, Vbs} = sa_split(SAVbs),
217
 
    case catch snmp_agent:subagent_set(SubAgentPid, [phase_two, undo, Vbs]) of
218
 
        {noError, 0} ->
219
 
            set_phase_two_undo_subagents(SubagentVarbinds);
220
 
        {ErrorStatus, ErrorIndex} ->
221
 
            {ErrorStatus, ErrorIndex};
222
 
        {'EXIT', Reason} ->
223
 
            user_err("Lost contact with subagent (undo)~n~w. Using genErr", 
224
 
                     [Reason]),
225
 
            {genErr, 0}
226
 
    end;
227
 
set_phase_two_undo_subagents([]) ->
228
 
    {noError, 0}.
229
 
 
230
 
%%%-----------------------------------------------------------------
231
 
%%% 2. Misc functions
232
 
%%%-----------------------------------------------------------------
233
 
sort_varbindlist(Varbinds) ->
234
 
    snmp_svbl:sort_varbindlist(get(mibserver), Varbinds).
235
 
 
236
 
sa_split(SubagentVarbinds) ->
237
 
    snmp_svbl:sa_split(SubagentVarbinds).
238
 
 
239
 
 
240
 
user_err(F, A) ->
241
 
    snmp_error_report:user_err(F, A).