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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_agent.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_agent).
19
 
 
20
 
-include("snmp_types.hrl").
21
 
-include("snmp_debug.hrl").
22
 
-include("snmp_verbosity.hrl").
23
 
 
24
 
%% External exports
25
 
-export([start_link/3, start_link/4, stop/1]).
26
 
-export([subagent_set/2, load_mibs/2, unload_mibs/2, info/1,
27
 
         register_subagent/3, unregister_subagent/2,
28
 
         send_trap/6, get_net_if/1]).
29
 
-export([debug/2, verbosity/2, dump_mibs/1, dump_mibs/2]).
30
 
-export([validate_err/3, make_value_a_correct_value/3, do_get/3, get/2]).
31
 
 
32
 
%% Internal exports
33
 
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
34
 
         terminate/2, code_change/3, tr_var/2, tr_varbind/1,
35
 
         handle_pdu/8, worker/2, worker_loop/1, do_send_trap/6]).
36
 
 
37
 
-ifndef(default_verbosity).
38
 
-define(default_verbosity,silence).
39
 
-endif.
40
 
 
41
 
-define(empty_pdu_size, 21).
42
 
 
43
 
 
44
 
%%-----------------------------------------------------------------
45
 
%% The agent is multi-threaded, i.e. each request is handled
46
 
%% by a separate process.  However, in the normal case, there
47
 
%% is just one request handled at the time.  In order to improve
48
 
%% performance, there is always two worker processes alive.  They are
49
 
%% created at initialization time.  There is always one worker
50
 
%% dedicated to SET-handling.  When a get*-request is received,
51
 
%% it is sent to the worker, and the worker is marked as busy.
52
 
%% If a request is received when the worker is busy, a new temporary
53
 
%% worker is spawned.
54
 
%% Code change
55
 
%% ===========
56
 
%% Note that the worker(s) execute the same module as the master
57
 
%% agent. For code change we have two options - ignore the workers,
58
 
%% or send them a code change message.
59
 
%%-----------------------------------------------------------------
60
 
-record(state, {type, parent, worker, worker_state = ready,
61
 
                set_worker, multi_threaded, ref, misc_sup, vsns}).
62
 
 
63
 
%%%-----------------------------------------------------------------
64
 
%%% This module implements the agent machinery; both for the master
65
 
%%% agent and the subagents.
66
 
%%%-----------------------------------------------------------------
67
 
%%% Table of contents
68
 
%%% =================
69
 
%%% 1. Interface
70
 
%%% 2. Main loop
71
 
%%% 3. GET REQUEST
72
 
%%% 4. GET-NEXT REQUEST
73
 
%%% 5. GET-BULK REQUEST
74
 
%%% 6. SET REQUEST
75
 
%%% 7. Misc functions
76
 
%%%-----------------------------------------------------------------
77
 
 
78
 
%%-----------------------------------------------------------------
79
 
%% Parent is a Pid (of master_agent) or none
80
 
%% Options is a list of Option, where Option is
81
 
%%   {mibs, Mibs}
82
 
%%   {net_if, NetIfModule}
83
 
%%   {priority, Prio}
84
 
%%   {verbosity, Verbosity}
85
 
%%   {multi_threaded, Bool} true means that SETs are serialized,
86
 
%%      while GETs are concurrent, even with a SET.
87
 
%%   {set_mechanism, SetModule}           % undocumented feature
88
 
%%
89
 
%% The following options are now removed - they are not needed
90
 
%% anymore when VACM is standard for authentication, and works
91
 
%% with all versions, and trap sending is standardized too.
92
 
%%   {authentication_service, AuthModule} % undocumented feature
93
 
%%   {trap_mechanism, TrapModule}         % undocumented feature
94
 
%% Note: authentication_service is reintroduced for AXD301 (OTP-3324).
95
 
%%-----------------------------------------------------------------
96
 
start_link(Parent, Ref, Options) ->
97
 
    ?debug("start_link -> ~n"
98
 
           "Parent:  ~p~n"
99
 
           "Ref:     ~p~n"
100
 
           "Options: ~p",
101
 
           [Parent, Ref, Options]),
102
 
    gen_server:start_link(?MODULE, [Parent, Ref, Options], []).
103
 
start_link(Name, Parent, Ref, Options) ->
104
 
    ?debug("start_link -> ~n"
105
 
           "Name:    ~p~n"
106
 
           "Parent:  ~p~n"
107
 
           "Ref:     ~p~n"
108
 
           "Options: ~p",
109
 
           [Name, Parent, Ref, Options]),
110
 
    gen_server:start_link(Name, ?MODULE, [Parent, Ref, Options], []).
111
 
 
112
 
stop(Agent) -> gen_server:call(Agent, stop, infinity).
113
 
 
114
 
init([Parent, Ref, Options]) ->
115
 
    ?debug("init -> ~n"
116
 
           "Parent:  ~p~n"
117
 
           "Ref:     ~p~n"
118
 
           "Options: ~p",
119
 
           [Parent, Ref, Options]),
120
 
    put(sname,short_name(Parent)),
121
 
    put(verbosity,get_verbosity(Parent,Options)),
122
 
    ?vlog("starting",[]),
123
 
    Mibs = get_option(mibs, Options, []),
124
 
    MeOverride = get_option(mibentry_override, Options, false),
125
 
    TeOverride = get_option(trapentry_override, Options, false),
126
 
    MibsVerbosity = get_option(mibserver_verbosity, Options, silence),
127
 
    MibStorage = get_option(mib_storage, Options, ets),
128
 
    SetModule = get_option(set_mechanism, Options, snmp_set),
129
 
    put(set_module, SetModule),
130
 
    %% XXX OTP-3324. For AXD301.
131
 
    AuthModule = get_option(authentication_service, Options, snmp_acm),
132
 
    put(auth_module, AuthModule),
133
 
    Prio = get_option(priority, Options, normal),
134
 
    process_flag(priority, Prio),
135
 
    MultiT = get_option(multi_threaded, Options, false),
136
 
    MiscSup = get_option(misc_sup, Options, undefined),
137
 
    Vsns = snmp_misc:get_option(snmp_vsn, Options, [v1,v2,v3]),
138
 
    {Type, NetIfPid} =
139
 
        case Parent of
140
 
            none -> 
141
 
                NetIf = get_option(net_if, Options, snmp_net_if),
142
 
                NiVerbosity = get_option(net_if_verbosity, Options, silence),
143
 
                NiRecBuf = get_option(net_if_recbuf, Options, use_default),
144
 
                NiReqLimit = get_option(net_if_req_limit, Options, infinity),
145
 
                NiOpts = [{verbosity, NiVerbosity},
146
 
                          {recbuf,    NiRecBuf},
147
 
                          {req_limit, NiReqLimit}],
148
 
                ?vdebug("start net if",[]),
149
 
                case (catch snmp_misc_sup:start_net_if(MiscSup,Ref,self(),
150
 
                                                       NetIf,NiOpts)) of
151
 
                    {ok, Pid} -> 
152
 
                        {master_agent, Pid};
153
 
                    {error, Reason} -> 
154
 
                        ?vinfo("error starting net if: ~n~p",[Reason]),
155
 
                        exit(Reason);
156
 
                    {'EXIT', Reason} ->
157
 
                        ?vinfo("exit starting net if: ~n~p",[Reason]),
158
 
                        exit(Reason);
159
 
                    Error ->
160
 
                        ?vinfo("failed starting net if: ~n~p",[Error]),
161
 
                        exit({failed_starting_net_if, Error})
162
 
                end;
163
 
            Pid when pid(Pid) -> 
164
 
                {subagent, undefined}
165
 
        end,
166
 
    ?vdebug("start mib server (~p,~p,~p,~p)",
167
 
            [MeOverride,TeOverride,MibsVerbosity,MibStorage]),
168
 
    MibsOpts = [{mibentry_override,MeOverride},
169
 
                {trapentry_override,TeOverride},
170
 
                {mibserver_verbosity,MibsVerbosity},
171
 
                {mib_storage,MibStorage}],
172
 
    case snmp_misc_sup:start_mib(MiscSup, Ref, Mibs, Prio, MibsOpts) of
173
 
        {ok, MibPid} ->
174
 
            put(mibserver, MibPid),
175
 
            process_flag(trap_exit, true),
176
 
            put(net_if, NetIfPid),
177
 
            {Worker, SetWorker} =
178
 
                case MultiT of
179
 
                    true ->
180
 
                        ?vdebug("start worker and set-worker",[]),
181
 
                        {proc_lib:spawn_link(?MODULE,worker,[self(),get()]),
182
 
                         proc_lib:spawn_link(?MODULE,worker,[self(),get()])};
183
 
                    _ -> 
184
 
                        {undefined, undefined}
185
 
                end,
186
 
            ?vdebug("mib server started",[]),
187
 
            {ok, #state{type = Type, parent = Parent, worker = Worker,
188
 
                        set_worker = SetWorker,
189
 
                        multi_threaded = MultiT, ref = Ref,
190
 
                        misc_sup = MiscSup, vsns = Vsns}};
191
 
        {error, Reason2} ->
192
 
            ?vlog("~n   failed starting mib: ~p",[Reason2]),
193
 
            {stop, Reason2}
194
 
    end.
195
 
 
196
 
%%-----------------------------------------------------------------
197
 
%% Purpose: We must calculate the length of an empty Pdu.  This
198
 
%%          length is used to calculate the max pdu size allowed
199
 
%%          for each get-bulk-request. This size is 
200
 
%%          dependent on the varbinds. It is calculated
201
 
%%          as EmptySize + 8.  8 comes from the fact that the
202
 
%%          maximum pdu size needs 31 bits which needs 5 * 7 bits to be
203
 
%%          expressed. One 7bit octet is already present in the
204
 
%%          empty pdu, leaving 4 more 7bit octets. The length is
205
 
%%          repeated twice, once for the varbinds, and once for the
206
 
%%          entire pdu; 2 * 4 = 8.
207
 
%% Actually, this function is not used, we use a constant instead.
208
 
%%-----------------------------------------------------------------
209
 
%% Ret: 21
210
 
%empty_pdu() ->
211
 
%    Pdu = #pdu{type = 'get-response', request_id = 1,
212
 
%              error_status = noError, error_index = 0, varbinds = []},
213
 
%    length(snmp_pdus:enc_pdu(Pdu)) + 8.
214
 
 
215
 
 
216
 
%%%--------------------------------------------------
217
 
%%% 1. Interface
218
 
%%%--------------------------------------------------
219
 
%% Called by administrator (not subagent; deadlock could occur)
220
 
register_subagent(Agent, SubTreeOid, SubagentPid) ->
221
 
    gen_server:call(Agent, {register_subagent, SubTreeOid, SubagentPid},
222
 
                    infinity).
223
 
 
224
 
%% Called by administrator (not subagent; deadlock could occur)
225
 
unregister_subagent(Agent, SubagentOidOrPid) ->
226
 
    gen_server:call(Agent, {unregister_subagent, SubagentOidOrPid}, infinity).
227
 
 
228
 
%%-----------------------------------------------------------------
229
 
%% These subagent_ functions either return a value, or exits
230
 
%% with {nodedown, Node} | Reason.
231
 
%%-----------------------------------------------------------------
232
 
subagent_get(SubAgent, Varbinds, IsNotification) ->
233
 
    PduData = get_pdu_data(),
234
 
    gen_server:call(SubAgent, {subagent_get, Varbinds, PduData, IsNotification},
235
 
                    infinity).
236
 
 
237
 
subagent_get_next(SubAgent, MibView, Varbinds) ->
238
 
    PduData = get_pdu_data(),
239
 
    gen_server:call(SubAgent, {subagent_get_next, MibView, Varbinds, PduData},
240
 
                   infinity).
241
 
 
242
 
subagent_set(SubAgent, Arguments) ->
243
 
    PduData = get_pdu_data(),
244
 
    gen_server:call(SubAgent, {subagent_set, Arguments, PduData}, infinity).
245
 
 
246
 
%% Called by administrator (not agent; deadlock would occur)
247
 
load_mibs(Agent, Mibs) ->
248
 
    gen_server:call(Agent, {load_mibs, Mibs}, infinity).
249
 
 
250
 
%% Called by administrator (not agent; deadlock would occur)
251
 
unload_mibs(Agent, Mibs) ->
252
 
    gen_server:call(Agent, {unload_mibs, Mibs}, infinity).
253
 
 
254
 
info(Agent) ->
255
 
    gen_server:call(Agent, info, infinity).
256
 
 
257
 
get_net_if(Agent) ->
258
 
    gen_server:call(Agent, get_net_if, infinity).
259
 
 
260
 
send_trap(Agent, Trap, NotifyName, ContextName, Recv, Varbinds) ->
261
 
    Agent ! {send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}.
262
 
 
263
 
forward_trap(Agent, TrapRecord, NotifyName, ContextName, Recv, Varbinds) ->
264
 
    Agent ! {forward_trap, TrapRecord, NotifyName, ContextName, Recv, Varbinds}.
265
 
 
266
 
%%-----------------------------------------------------------------
267
 
%% Args: Vars = [Oid]
268
 
%% Returns: [Value]
269
 
%% Called from a program to get variables.  Don't call this from
270
 
%% an instrumentation function; deadlock can occur!
271
 
%%-----------------------------------------------------------------
272
 
get(Agent, Vars) -> gen_server:call(Agent, {get, Vars}, infinity).
273
 
 
274
 
%%-----------------------------------------------------------------
275
 
%% Runtime debug support.  When Flag is true, the agent prints info
276
 
%% when a packet is receive/sent, and when a user defined function
277
 
%% is called.
278
 
%%
279
 
%% This is kept for backward compatibillity reasons, see verbosity
280
 
%%-----------------------------------------------------------------
281
 
debug(Agent, Flag) -> gen_server:call(Agent, {debug, Flag}, infinity).
282
 
 
283
 
dump_mibs(Agent) -> 
284
 
    gen_server:call(Agent, dump_mibs, infinity).
285
 
dump_mibs(Agent,File) when list(File) -> 
286
 
    gen_server:call(Agent,{dump_mibs,File}, infinity).
287
 
 
288
 
 
289
 
%%-----------------------------------------------------------------
290
 
%% Runtime debug (verbosity) support.
291
 
%%-----------------------------------------------------------------
292
 
verbosity(snmp_net_if,Verbosity) -> 
293
 
    gen_server:cast(snmp_master_agent,{snmp_net_if_verbosity,Verbosity});
294
 
verbosity(snmp_mib,Verbosity) -> 
295
 
    gen_server:cast(snmp_master_agent,{snmp_mib_verbosity,Verbosity});
296
 
verbosity(snmp_sub_agents,Verbosity) -> 
297
 
    gen_server:cast(snmp_master_agent,{snmp_sub_agents_verbosity,Verbosity});
298
 
verbosity(Agent,{snmp_sub_agents,Verbosity}) -> 
299
 
    gen_server:cast(Agent,{snmp_sub_agents_verbosity,Verbosity});
300
 
verbosity(Agent,Verbosity) -> 
301
 
    gen_server:cast(Agent,{verbosity,Verbosity}).
302
 
 
303
 
%%%--------------------------------------------------
304
 
%%% 2. Main loop
305
 
%%%--------------------------------------------------
306
 
handle_info({snmp_pdu, Vsn, Pdu, PduMS, ACMData, Address, Extra}, S) ->
307
 
    ?vdebug("~n   Received PDU ~p"
308
 
            "~n   from ~p", [Pdu,Address]),
309
 
    %% XXX OTP-3324
310
 
    AuthMod = get(auth_module),
311
 
    case AuthMod:init_check_access(Pdu, ACMData) of
312
 
        {ok, MibView, ContextName} ->
313
 
            AgentData = cheat(ACMData, Address, ContextName),
314
 
            case valid_pdu_type(Pdu#pdu.type) of
315
 
                true when S#state.multi_threaded == false ->
316
 
                    % Execute in same process
317
 
                    ?vtrace("execute in the same process",[]),
318
 
                    handle_pdu(MibView, Vsn, Pdu, PduMS, 
319
 
                               ACMData, AgentData, Extra),
320
 
                    {noreply, S};
321
 
                true when Pdu#pdu.type == 'set-request' ->
322
 
                    % Always send to main worker, in order to serialize
323
 
                    % the SETs
324
 
                    ?vtrace("send set-request to main worker",[]),
325
 
                    S#state.set_worker !
326
 
                        {MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra},
327
 
                    {noreply, S#state{worker_state = busy}};
328
 
                true when S#state.worker_state == busy ->
329
 
                    % Main worker busy => create new worker
330
 
                    ?vtrace("main worker busy -> crete new worker",[]),
331
 
                    spawn_thread(MibView, Vsn, Pdu, PduMS,
332
 
                                 ACMData, AgentData, Extra),
333
 
                    {noreply, S};
334
 
                true ->
335
 
                    % Send to main worker
336
 
                    ?vtrace("send to main worker",[]),
337
 
                    S#state.worker !
338
 
                        {MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra},
339
 
                    {noreply, S#state{worker_state = busy}};
340
 
                _ -> 
341
 
                    {noreply, S}
342
 
            end;
343
 
        {error, Reason} ->
344
 
            ?vlog("~n   auth init check failed: ~p", [Reason]),
345
 
            handle_acm_error(Vsn, Reason, Pdu, ACMData, Address, Extra),
346
 
            {noreply, S};
347
 
        {discarded, Variable, Reason} ->
348
 
            ?vlog("~n   PDU discarded for reason: ~p", [Reason]),
349
 
            get(net_if) ! {discarded_pdu, Vsn, Pdu#pdu.request_id,
350
 
                           ACMData, Variable, Extra},
351
 
            {noreply, S}
352
 
    end;
353
 
 
354
 
handle_info(worker_available, S) ->
355
 
    ?vdebug("worker available",[]),
356
 
    {noreply, S#state{worker_state = ready}};
357
 
 
358
 
handle_info({send_trap, Trap, NotifyName, ContextName, Recv, Varbinds}, S) ->
359
 
    ?vlog("send trap request:"
360
 
          "~n   Trap:        ~p"
361
 
          "~n   NotifyName:  ~p"
362
 
          "~n   ContextName: ~p"
363
 
          "~n   Recv:        ~p" 
364
 
          "~n   Varbinds:    ~p", 
365
 
          [Trap,NotifyName,ContextName,Recv,Varbinds]),
366
 
    case catch handle_send_trap(S, Trap, NotifyName, ContextName,
367
 
                                Recv, Varbinds) of
368
 
        {ok, NewS} ->
369
 
            {noreply, NewS};
370
 
        {'EXIT', R} ->
371
 
            ?vinfo("Trap not sent:~n   ~p", [R]),
372
 
            {noreply, S};
373
 
        _ ->
374
 
            {noreply, S}
375
 
    end;
376
 
 
377
 
handle_info({forward_trap, TrapRecord, NotifyName, ContextName,
378
 
             Recv, Varbinds},S) ->
379
 
    ?vlog("forward trap request:"
380
 
          "~n   TrapRecord:  ~p"
381
 
          "~n   NotifyName:  ~p"
382
 
          "~n   ContextName: ~p"
383
 
          "~n   Recv:        ~p"
384
 
          "~n   Varbinds:    ~p", 
385
 
          [TrapRecord,NotifyName,ContextName,Recv,Varbinds]),
386
 
    case catch handle_forward_trap(S, TrapRecord, NotifyName, ContextName,
387
 
                                   Recv, Varbinds) of
388
 
        {ok, NewS} ->
389
 
            {noreply, NewS};
390
 
        {'EXIT', R} ->
391
 
            ?vinfo("Trap not sent:~n   ~p", [R]),
392
 
            {noreply, S};
393
 
        _ ->
394
 
            {noreply, S}
395
 
    end;
396
 
 
397
 
%%-----------------------------------------------------------------
398
 
%% If a process crashes, we first check to see if it was the mib.
399
 
%% Otherwise, we check to see if it was a subagent. In this case
400
 
%% we unregister the sa, and unlink us from the sa.
401
 
%%-----------------------------------------------------------------
402
 
handle_info({'EXIT', Pid, Reason}, S) ->
403
 
    ?vlog("~p exited for reason ~p", [Pid,Reason]),
404
 
    Mib = get(mibserver),
405
 
    NetIf = get(net_if),
406
 
    case Pid of
407
 
        Mib ->
408
 
            exit(Reason);
409
 
        NetIf ->
410
 
            exit(Reason);
411
 
        Worker when S#state.worker == Worker -> 
412
 
            ?vtrace("was a worker -> create new", []),
413
 
            NewWorker =
414
 
                proc_lib:spawn_link(?MODULE, worker, [self(), get()]),
415
 
            {noreply, S#state{worker = NewWorker, worker_state = ready}};
416
 
        Worker when S#state.set_worker == Worker -> 
417
 
            ?vtrace("was a set-worker -> create new", []),
418
 
            NewWorker =
419
 
                proc_lib:spawn_link(?MODULE, worker, [self(), get()]),
420
 
            {noreply, S#state{set_worker = NewWorker}};
421
 
        Parent when Parent == S#state.parent ->
422
 
            ?vlog("parent died", []),
423
 
            {stop, {parent_died, Reason}, S};
424
 
        _ ->
425
 
            SAs = snmp_mib:info(Mib, subagents),
426
 
            case lists:keysearch(Pid, 1, SAs) of
427
 
                {value, _} ->
428
 
                    ?vlog("subagent", []),
429
 
                    snmp_mib:unregister_subagent(Mib, Pid),
430
 
                    unlink(Pid);
431
 
                _ -> 
432
 
                    %% Otherwise it was a probably a worker thread - ignore
433
 
                    ok
434
 
            end,
435
 
            {noreply, S}
436
 
    end;
437
 
handle_info(_, S) ->
438
 
    {noreply, S}.
439
 
 
440
 
handle_call({subagent_get, Varbinds, PduData, IsNotification}, _From, S) ->
441
 
    ?vlog("subagent get:"
442
 
          "~n   Varbinds: ~p"
443
 
          "~n   PduData:  ~p", 
444
 
          [Varbinds,PduData]),
445
 
    put_pdu_data(PduData),
446
 
    {reply, do_get(Varbinds, IsNotification), S};
447
 
handle_call({subagent_get_next, MibView, Varbinds, PduData}, _From, S) ->
448
 
    ?vlog("subagent get-next:"
449
 
          "~n   MibView:  ~p"
450
 
          "~n   Varbinds: ~p"
451
 
          "~n   PduData:  ~p", 
452
 
          [MibView,Varbinds,PduData]),
453
 
    put_pdu_data(PduData),
454
 
    {reply, do_get_next(MibView, Varbinds), S};
455
 
handle_call({subagent_set, Arguments, PduData}, _From, S) ->
456
 
    ?vlog("subagent set:"
457
 
          "~n   Arguments: ~p"
458
 
          "~n   PduData:   ~p", 
459
 
          [Arguments,PduData]),
460
 
    put_pdu_data(PduData),
461
 
    {reply, do_subagent_set(Arguments), S};
462
 
 
463
 
handle_call({get, Vars}, _From, S) ->
464
 
    ?vlog("get:"
465
 
          "~n   Vars: ~p",[Vars]),
466
 
    case catch mapfoldl({?MODULE, tr_var}, [], 1, Vars) of
467
 
        {error, Reason} -> {reply, {error, Reason}, S};
468
 
        {_, Varbinds} ->
469
 
            ?vdebug("Varbinds: ~p",[Varbinds]),
470
 
            Reply =
471
 
                case do_get(Varbinds, false) of
472
 
                    {noError, 0, NewVarbinds} ->
473
 
                        ResVarbinds = lists:keysort(#varbind.org_index,
474
 
                                                    NewVarbinds),
475
 
                        snmp_misc:map({?MODULE, tr_varbind}, [], ResVarbinds);
476
 
                    {ErrorStatus, ErrIndex, _} ->
477
 
                        N = lists:nth(ErrIndex, Vars),
478
 
                        {error, {ErrorStatus, N}}
479
 
                end,
480
 
            {reply, Reply, S}
481
 
    end;
482
 
 
483
 
handle_call({register_subagent, SubTreeOid, SubagentPid}, _From, S) ->
484
 
    Reply = 
485
 
        case snmp_mib:register_subagent(get(mibserver),
486
 
                                        SubTreeOid, SubagentPid) of
487
 
            ok -> link(SubagentPid), ok;
488
 
            Error -> Error
489
 
        end,
490
 
    {reply, Reply, S};
491
 
 
492
 
handle_call({unregister_subagent, SubagentPid}, _From, S) 
493
 
  when pid(SubagentPid) ->
494
 
    ?vlog("unregister subagent ~p", [SubagentPid]),
495
 
    Reply = snmp_mib:unregister_subagent(get(mibserver), SubagentPid),
496
 
    unlink(SubagentPid),
497
 
    {reply, Reply, S};
498
 
 
499
 
handle_call({unregister_subagent, SubTreeOid}, _From, S) ->
500
 
    ?vlog("unregister subagent ~p", [SubTreeOid]),
501
 
    Reply = 
502
 
        case snmp_mib:unregister_subagent(get(mibserver), SubTreeOid) of
503
 
            {ok, DeletedSubagentPid} ->
504
 
                SAs = snmp_mib:info(get(mibserver), subagents),
505
 
                case lists:keysearch(DeletedSubagentPid, 1, SAs) of
506
 
                    {value, _} -> ok;
507
 
                    _ -> unlink(DeletedSubagentPid)
508
 
                end,
509
 
                ok;
510
 
            Error ->
511
 
                Error
512
 
        end,
513
 
    {reply, Reply, S};
514
 
 
515
 
handle_call({load_mibs, Mibs}, _From, S) ->
516
 
    ?vlog("load mibs ~p", [Mibs]),
517
 
    {reply, snmp_mib:load_mibs(get(mibserver), Mibs), S};
518
 
 
519
 
handle_call({unload_mibs, Mibs}, _From, S) ->
520
 
    ?vlog("unload mibs ~p", [Mibs]),
521
 
    {reply, snmp_mib:unload_mibs(get(mibserver), Mibs), S};
522
 
 
523
 
handle_call(info, _From, S) ->
524
 
    {reply, [{vsns, S#state.vsns} | snmp_mib:info(get(mibserver))], S};
525
 
 
526
 
handle_call(get_net_if, _From, S) ->
527
 
    {reply, get(net_if), S};
528
 
 
529
 
handle_call({debug, Flag}, _From, S) ->
530
 
    V = d2v(Flag),
531
 
    put(verbosity,V),
532
 
    net_if_verbosity(get(net_if),V),
533
 
    case S#state.worker of
534
 
        Pid when pid(Pid) -> Pid ! {verbosity,V};
535
 
        _ -> ok
536
 
    end,
537
 
    case S#state.set_worker of
538
 
        Pid2 when pid(Pid2) -> Pid2 ! {verbosity,V};
539
 
        _ -> ok
540
 
    end,
541
 
    {reply, ok, S};
542
 
 
543
 
handle_call(dump_mibs, _From, S) ->
544
 
    Reply = snmp_mib:dump(get(mibserver)),
545
 
    {reply, Reply, S};
546
 
    
547
 
handle_call({dump_mibs,File}, _From, S) ->
548
 
    Reply = snmp_mib:dump(get(mibserver),File),
549
 
    {reply, Reply, S};
550
 
    
551
 
handle_call(stop, _From, S) ->
552
 
    {stop, normal, ok, S}.
553
 
 
554
 
handle_cast({verbosity,Verbosity}, S) ->
555
 
    ?vlog("verbosity: ~p -> ~p",[get(verbosity),Verbosity]),
556
 
    put(verbosity,snmp_verbosity:validate(Verbosity)),
557
 
    case S#state.worker of
558
 
        Pid when pid(Pid) -> Pid ! {verbosity,Verbosity};
559
 
        _ -> ok
560
 
    end,
561
 
    case S#state.set_worker of
562
 
        Pid2 when pid(Pid2) -> Pid2 ! {verbosity,Verbosity};
563
 
        _ -> ok
564
 
    end,
565
 
    {noreply, S};
566
 
    
567
 
handle_cast({snmp_sub_agents_verbosity,Verbosity}, S) ->
568
 
    ?vlog("subagent verbosity: ~p",[Verbosity]),
569
 
    subagents_verbosity(Verbosity),
570
 
    {noreply, S};
571
 
    
572
 
%% This should only happen if we are a master_agent
573
 
handle_cast({snmp_net_if_verbosity,Verbosity}, S) ->
574
 
    net_if_verbosity(get(net_if),Verbosity),
575
 
    {noreply, S};
576
 
    
577
 
handle_cast({snmp_mib_verbosity,Verbosity}, S) ->
578
 
    mib_verbosity(get(mibserver),Verbosity),
579
 
    {noreply, S};
580
 
    
581
 
handle_cast(_, S) ->
582
 
    {noreply, S}.
583
 
    
584
 
terminate(shutdown, #state{ref = Ref, misc_sup = MiscSup}) ->
585
 
    %% Ordered shutdown - stop mib and net_if.
586
 
    snmp_misc_sup:stop_mib(MiscSup, Ref),
587
 
    snmp_misc_sup:stop_net_if(MiscSup, Ref);
588
 
terminate(_Reason, _S) ->
589
 
    %% We crashed!  We will reuse net_if and mib if we get restarted.
590
 
    ok.
591
 
 
592
 
%%-----------------------------------------------------------------
593
 
%% Code replacement
594
 
%% 
595
 
%%-----------------------------------------------------------------
596
 
 
597
 
%% Upgrade
598
 
%%
599
 
code_change(_Vsn, S, _Extra) ->
600
 
    NS = worker_restart(S),
601
 
    {ok, NS};
602
 
 
603
 
%% Downgrade
604
 
%%
605
 
code_change({down, _Vsn}, S, _Extra) ->
606
 
    NS = worker_restart(S),
607
 
    {ok, NS}.
608
 
 
609
 
 
610
 
worker_restart(S) ->
611
 
    Worker    = restart_worker(S#state.worker),
612
 
    SetWorker = restart_worker(S#state.set_worker),
613
 
    S#state{worker = Worker, set_worker = SetWorker}.
614
 
 
615
 
restart_worker(Pid) when pid(Pid) -> 
616
 
    Pid ! terminate, 
617
 
    receive 
618
 
        {'EXIT', Pid, normal} ->
619
 
            ok
620
 
    end,
621
 
    proc_lib:spawn_link(?MODULE,worker,[self(),get()]);
622
 
restart_worker(Any) ->
623
 
    Any.
624
 
 
625
 
%%-----------------------------------------------------------------
626
 
%% We must cheat to get the community string out of the ACM data,
627
 
%% because we (for some reason) support the function
628
 
%% snmp:current_community().
629
 
%%-----------------------------------------------------------------
630
 
cheat({community, _SecModel, Community, _IpUdp}, Address, ContextName) ->
631
 
    {Community, Address, ContextName};
632
 
cheat(_, Address, ContextName) ->
633
 
    {"", Address, ContextName}.
634
 
 
635
 
%%-----------------------------------------------------------------
636
 
%% Threads and workers
637
 
%% 
638
 
%%-----------------------------------------------------------------
639
 
 
640
 
spawn_thread(MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra) ->
641
 
    Dict = get(),
642
 
    proc_lib:spawn_link(?MODULE, handle_pdu,
643
 
                        [MibView, Vsn, Pdu, PduMS, ACMData,
644
 
                         AgentData, Extra, Dict]).
645
 
 
646
 
spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, V) ->
647
 
    Dict = get(),
648
 
    proc_lib:spawn_link(?MODULE, do_send_trap,
649
 
                        [TrapRec, NotifyName, ContextName, Recv, V, Dict]).
650
 
 
651
 
do_send_trap(TrapRec, NotifyName, ContextName, Recv, V, Dict) ->
652
 
    lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
653
 
    put(sname,trap_sender_short_name(get(sname))),
654
 
    ?vlog("starting",[]),
655
 
    snmp_trap:send_trap(TrapRec, NotifyName, ContextName, Recv, V, get(net_if)).
656
 
 
657
 
 
658
 
worker(Master, Dict) ->
659
 
    lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
660
 
    put(sname,worker_short_name(get(sname))),
661
 
    ?vlog("starting",[]),
662
 
    worker_loop(Master).
663
 
 
664
 
worker_loop(Master) ->
665
 
    receive
666
 
        {MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra} ->
667
 
            handle_pdu(MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra),
668
 
            Master ! worker_available;
669
 
        {TrapRec, NotifyName, ContextName, Recv, V} -> % We don't trap exits!
670
 
            ?vtrace("send trap:~n   ~p",[TrapRec]),
671
 
            snmp_trap:send_trap(TrapRec, NotifyName, 
672
 
                                ContextName, Recv, V, get(net_if)),
673
 
            Master ! worker_available;
674
 
        {verbosity, Verbosity} ->
675
 
            put(verbosity,snmp_verbosity:validate(Verbosity));
676
 
        terminate ->
677
 
            exit(normal);
678
 
        _X ->
679
 
            %% ignore
680
 
            ok
681
 
    after 30000 ->
682
 
            %% This is to assure that the worker process leaves a
683
 
            %% possibly old version of this module.
684
 
            ok
685
 
    end,
686
 
    ?MODULE:worker_loop(Master).
687
 
 
688
 
 
689
 
handle_pdu(MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra, Dict) ->
690
 
    lists:foreach(fun({Key, Val}) -> put(Key, Val) end, Dict),
691
 
    put(sname,pdu_handler_short_name(get(sname))),
692
 
    ?vlog("starting",[]),
693
 
    handle_pdu(MibView, Vsn, Pdu, PduMS, ACMData, AgentData, Extra).
694
 
 
695
 
handle_pdu(MibView, Vsn, Pdu, PduMS, ACMData,
696
 
           {Community, Address, ContextName}, Extra) ->
697
 
    put(snmp_net_if_data, Extra),
698
 
    RePdu = process_msg(MibView, Vsn, Pdu, PduMS, Community, 
699
 
                        Address, ContextName),
700
 
    ?vtrace("reply PDU:~n   ~p",[RePdu]),
701
 
    get(net_if) ! {snmp_response, Vsn, RePdu, 
702
 
                   RePdu#pdu.type, ACMData, Address, Extra}.
703
 
 
704
 
 
705
 
handle_acm_error(Vsn, Reason, Pdu, ACMData, Address, Extra) ->
706
 
    #pdu{type = Type, request_id = ReqId, varbinds = Vbs} = Pdu,
707
 
    RawErrStatus = snmp_acm:error2status(Reason),
708
 
    case valid_pdu_type(Type) of
709
 
        true ->
710
 
            %% RawErrStatus can be authorizationError or genErr.  If it is
711
 
            %% authorizationError, we'll have to do different things, 
712
 
            %% depending on which SNMP version is used.
713
 
            %% v1 - noSuchName error
714
 
            %% v2 - GET: all variables 'noSuchObject'
715
 
            %%      NEXT/BULK: all variables 'endOfMibView'
716
 
            %%      SET: noAccess error
717
 
            %% v3 - authorizationError error
718
 
            %%
719
 
            %% NOTE: this procedure is not yet defined in the coex document!
720
 
            ?vdebug("~n   Raw error status: ~w",[RawErrStatus]),
721
 
            Idx = case Vbs of
722
 
                      [] -> 0;
723
 
                      _ -> 1
724
 
                  end,
725
 
            RePdu =
726
 
                if
727
 
                    Vsn == 'version-1' ->
728
 
                        ErrStatus = v2err_to_v1err(RawErrStatus),
729
 
                        make_response_pdu(ReqId, ErrStatus, Idx, Vbs, Vbs);
730
 
                    Vsn == 'version-3' ->
731
 
                        make_response_pdu(ReqId, RawErrStatus, Idx, Vbs, Vbs);
732
 
                    Type == 'get-request' ->  % this is v2
733
 
                        ReVbs = lists:map(
734
 
                                  fun(Vb) -> Vb#varbind{value=noSuchObject} end,
735
 
                                  Vbs),
736
 
                        make_response_pdu(ReqId, noError, 0, Vbs, ReVbs);
737
 
                    Type == 'set-request' ->
738
 
                        make_response_pdu(ReqId, noAccess, Idx, Vbs, Vbs);
739
 
                    true -> % next or bulk
740
 
                        ReVbs = lists:map(
741
 
                                  fun(Vb) -> Vb#varbind{value=endOfMibView} end,
742
 
                                  Vbs),
743
 
                        make_response_pdu(ReqId, noError, 0, Vbs, ReVbs)
744
 
                end,
745
 
            get(net_if) ! {snmp_response, Vsn, RePdu, 
746
 
                           'get-response', ACMData, Address, Extra};
747
 
        false ->
748
 
            ?vdebug("~n   Raw error status: ~w"
749
 
                    "~n   invalid pdu type: ~w", 
750
 
                    [RawErrStatus,Type]),
751
 
            ok
752
 
    end.
753
 
 
754
 
 
755
 
handle_send_trap(S, TrapName, NotifyName, ContextName, Recv, Varbinds) ->
756
 
    case snmp_trap:construct_trap(TrapName, Varbinds) of
757
 
        {ok, TrapRecord, VarList} ->
758
 
            case S#state.type of
759
 
                subagent ->
760
 
                    forward_trap(S#state.parent, TrapRecord, NotifyName,
761
 
                                 ContextName, Recv, VarList),
762
 
                    {ok, S};
763
 
                master_agent ->
764
 
                    handle_forward_trap(S, TrapRecord, NotifyName,
765
 
                                        ContextName, Recv, VarList)
766
 
            end;
767
 
        error ->
768
 
            error
769
 
    end.
770
 
                                
771
 
handle_forward_trap(S, TrapRec, NotifyName, ContextName, Recv, Varbinds) ->
772
 
    V = snmp_trap:try_initialise_vars(get(mibserver), Varbinds),
773
 
    case S#state.type of
774
 
        subagent ->
775
 
            forward_trap(S#state.parent, TrapRec, NotifyName, ContextName,
776
 
                         Recv, V),
777
 
            {ok, S};
778
 
        master_agent when S#state.multi_threaded == false ->
779
 
            ?vtrace("send trap:~n   ~p",[TrapRec]),
780
 
            snmp_trap:send_trap(TrapRec, NotifyName, ContextName,
781
 
                                Recv, V, get(net_if)),
782
 
            {ok, S};
783
 
        master_agent when S#state.worker_state == busy ->
784
 
            %% Main worker busy => create new worker
785
 
            ?vtrace("~n   main worker busy -> spawn a trap sender",[]),
786
 
            spawn_trap_thread(TrapRec, NotifyName, ContextName, Recv, V),
787
 
            {ok, S};
788
 
        master_agent ->
789
 
            %% Send to main worker
790
 
            ?vtrace("~n   send to main worker",[]),
791
 
            S#state.worker ! {TrapRec, NotifyName, ContextName, Recv, V},
792
 
            {ok, S#state{worker_state = busy}}
793
 
    end.
794
 
    
795
 
%%-----------------------------------------------------------------
796
 
%% Func: process_msg/7
797
 
%% Returns: RePdu
798
 
%%-----------------------------------------------------------------
799
 
process_msg(MibView, Vsn, Pdu, PduMS, Community, {Ip, Udp}, ContextName) ->
800
 
    #pdu{request_id = ReqId} = Pdu,
801
 
    put(snmp_address, {tuple_to_list(Ip), Udp}),
802
 
    put(snmp_request_id, ReqId),
803
 
    put(snmp_community, Community),
804
 
    put(snmp_context, ContextName),
805
 
    ?vtrace("process ~p",[Pdu#pdu.type]),
806
 
    process_pdu(Pdu, PduMS, Vsn, MibView).
807
 
 
808
 
process_pdu(#pdu{type='get-request', request_id = ReqId, varbinds=Vbs},
809
 
            _PduMS, Vsn, MibView) ->
810
 
    ?vtrace("get ~p",[ReqId]),
811
 
    Res = get_err(do_get(MibView, Vbs, false)),
812
 
    ?vtrace("get result: "
813
 
            "~n   ~p",[Res]),
814
 
    {ErrStatus, ErrIndex, ResVarbinds} =
815
 
        if
816
 
            Vsn == 'version-1' -> validate_get_v1(Res);
817
 
            true -> Res
818
 
        end,
819
 
    ?vtrace("get final result: "
820
 
            "~n   Error status: ~p"
821
 
            "~n   Error index:  ~p"
822
 
            "~n   Varbinds:     ~p",
823
 
            [ErrStatus,ErrIndex,ResVarbinds]),
824
 
    ResponseVarbinds = lists:keysort(#varbind.org_index, ResVarbinds),
825
 
    ?vtrace("response varbinds: "
826
 
            "~n   ~p",[ResponseVarbinds]),
827
 
    make_response_pdu(ReqId, ErrStatus, ErrIndex, Vbs, ResponseVarbinds);
828
 
 
829
 
process_pdu(#pdu{type = 'get-next-request', request_id = ReqId, varbinds = Vbs},
830
 
            _PduMS, Vsn, MibView) ->
831
 
    ?vtrace("process get-next-request -> entry with"
832
 
            "~n   ReqId:   ~p"
833
 
            "~n   Vbs:     ~p"
834
 
            "~n   MibView: ~p",[ReqId, Vbs, MibView]),
835
 
    Res = get_err(do_get_next(MibView, Vbs)),
836
 
    ?vtrace("get-next result: "
837
 
            "~n   ~p",[Res]),
838
 
    {ErrStatus, ErrIndex, ResVarbinds} = 
839
 
        if
840
 
            Vsn == 'version-1' -> validate_next_v1(Res, MibView);
841
 
            true -> Res
842
 
        end,
843
 
    ?vtrace("get-next final result -> validation result:"
844
 
            "~n   Error status: ~p"
845
 
            "~n   Error index:  ~p"
846
 
            "~n   Varbinds:     ~p",[ErrStatus,ErrIndex,ResVarbinds]),
847
 
    ResponseVarbinds = lists:keysort(#varbind.org_index, ResVarbinds),
848
 
    ?vtrace("get-next final result -> response varbinds: "
849
 
            "~n   ~p",[ResponseVarbinds]),
850
 
    make_response_pdu(ReqId, ErrStatus, ErrIndex, Vbs, ResponseVarbinds);
851
 
 
852
 
process_pdu(#pdu{type = 'get-bulk-request',request_id = ReqId,varbinds = Vbs,
853
 
                 error_status = NonRepeaters, error_index = MaxRepetitions},
854
 
            PduMS, _Vsn, MibView)->
855
 
    {ErrStatus, ErrIndex, ResponseVarbinds} = 
856
 
        get_err(do_get_bulk(MibView,NonRepeaters,MaxRepetitions,PduMS,Vbs)),
857
 
    ?vtrace("get-bulk final result: "
858
 
            "~n   Error status:     ~p"
859
 
            "~n   Error index:      ~p"
860
 
            "~n   Respons varbinds: ~p",
861
 
            [ErrStatus,ErrIndex,ResponseVarbinds]),
862
 
    make_response_pdu(ReqId, ErrStatus, ErrIndex, Vbs, ResponseVarbinds);
863
 
 
864
 
process_pdu(#pdu{type = 'set-request', request_id = ReqId, varbinds = Vbs},
865
 
            _PduMS, Vsn, MibView)->
866
 
    Res = do_set(MibView, Vbs),
867
 
    ?vtrace("set result: "
868
 
            "~n   ~p",[Res]),
869
 
    {ErrStatus, ErrIndex} =
870
 
        if 
871
 
            Vsn == 'version-1' -> validate_err(v2_to_v1, Res);
872
 
            true -> Res
873
 
        end,
874
 
    ?vtrace("set final result: "
875
 
            "~n   Error status: ~p"
876
 
            "~n   Error index:  ~p",[ErrStatus,ErrIndex]),
877
 
    make_response_pdu(ReqId, ErrStatus, ErrIndex, Vbs, Vbs).
878
 
 
879
 
%%-----------------------------------------------------------------
880
 
%% Transform a value == noSuchInstance | noSuchObject or a 
881
 
%% Counter64 type to a noSuchName error for the whole pdu.
882
 
%% Args: {Error, Index, Vbs}
883
 
%% Returns: {NewError, NewIndex, NewVbs}
884
 
%%-----------------------------------------------------------------
885
 
validate_get_v1({noError, _, ResponseVarbinds}) ->
886
 
    case validate_get_v1_2(ResponseVarbinds) of
887
 
        true -> {noError, 0, ResponseVarbinds};
888
 
        {Error, Index} -> {Error, Index, []} % dummy vbs
889
 
    end;
890
 
validate_get_v1({ErrStatus, ErrIndex, ResponseVarbinds}) ->
891
 
    {v2err_to_v1err(ErrStatus), ErrIndex, ResponseVarbinds}.
892
 
 
893
 
validate_get_v1_2([Vb | Vbs]) when Vb#varbind.value /= noSuchInstance,
894
 
                                   Vb#varbind.value /= noSuchObject,
895
 
                                   Vb#varbind.variabletype /= 'Counter64' ->
896
 
    validate_get_v1_2(Vbs);
897
 
validate_get_v1_2([Vb | _Vbs]) ->
898
 
    {noSuchName, Vb#varbind.org_index};
899
 
validate_get_v1_2([]) ->
900
 
    true.
901
 
 
902
 
%%-----------------------------------------------------------------
903
 
%% Transform a value == endOfMibView to a noSuchName for the
904
 
%% whole pdu, and do another get-next for any Counter64 value.
905
 
%% Args: {Error, Index, Vbs}
906
 
%% Returns: {NewError, NewIndex, NewVbs}
907
 
%%-----------------------------------------------------------------
908
 
validate_next_v1({noError, _, ResponseVarbinds}, MibView) ->
909
 
    case validate_next_v1_2(ResponseVarbinds, MibView, []) of
910
 
        {true, NVbs} -> {noError, 0, NVbs};
911
 
        {Error, Index} -> {Error, Index, []} % dummy vbs
912
 
    end;
913
 
validate_next_v1({ErrStatus, ErrIndex, ResponseVarbinds}, _MibView) ->
914
 
    {v2err_to_v1err(ErrStatus), ErrIndex, ResponseVarbinds}.
915
 
 
916
 
validate_next_v1_2([Vb | _Vbs], _MibView, _Res)
917
 
  when Vb#varbind.value == endOfMibView ->
918
 
    {noSuchName, Vb#varbind.org_index};
919
 
validate_next_v1_2([Vb | Vbs], MibView, Res)
920
 
  when Vb#varbind.variabletype == 'Counter64' ->
921
 
    case validate_next_v1(do_get_next(MibView, [mk_next_oid(Vb)]), MibView) of
922
 
        {noError, 0, [NVb]} ->
923
 
            validate_next_v1_2(Vbs, MibView, [NVb | Res]);
924
 
        {Error, Index, _OrgVb} ->
925
 
            {Error, Index}
926
 
    end;
927
 
validate_next_v1_2([Vb | Vbs], MibView, Res) ->
928
 
    validate_next_v1_2(Vbs, MibView, [Vb | Res]);
929
 
validate_next_v1_2([], _MibView, Res) ->
930
 
    {true, Res}.
931
 
 
932
 
%%-----------------------------------------------------------------
933
 
%% Optimization. When we get to a Counter64 object that is a table
934
 
%% column, we'll try to find the next instance. This will be the
935
 
%% next row in the table, which is a Counter64 value as well. This
936
 
%% means that we will loop through the entire table, until we find
937
 
%% a column that isn't a Counter64 column. We can optimze this by
938
 
%% adding 1 to the column-no in the oid of this instance.
939
 
%% If the table is implemented by a subagent this does not help,
940
 
%% we'll call that subagent many times. But it shouldn't be any
941
 
%% problems.
942
 
%%-----------------------------------------------------------------
943
 
mk_next_oid(Vb) ->
944
 
    case snmp_mib:lookup(get(mibserver), Oid = Vb#varbind.oid) of
945
 
        {table_column, _MibEntry, TableEntryOid} ->
946
 
            [Col | _] = Oid -- TableEntryOid,
947
 
            Vb#varbind{oid = TableEntryOid ++ [Col+1]};
948
 
        _ ->
949
 
            Vb
950
 
    end.
951
 
 
952
 
%%%-----------------------------------------------------------------
953
 
%%% 3. GET REQUEST
954
 
%%% --------------
955
 
%%%   According to RFC1157, section 4.1.2 and RFC1905, section 4.2.1.
956
 
%%%   In rfc1157:4.1.2 it isn't specified if noSuchName should be
957
 
%%%   returned even if some other varbind generates a genErr.
958
 
%%%   In rfc1905:4.2.1 this is not a problem since exceptions are
959
 
%%%   used, and thus a genErr will be returned anyway.
960
 
%%%-----------------------------------------------------------------
961
 
%%-----------------------------------------------------------------
962
 
%% Func: do_get/3
963
 
%% Purpose: do_get handles "getRequests".
964
 
%% Pre: incoming varbinds have type == 'NULL', value == unSpecified
965
 
%% Returns: {noError, 0, ListOfNewVarbinds} |
966
 
%%          {ErrorStatus, ErrorIndex, []}
967
 
%%-----------------------------------------------------------------
968
 
do_get(MibView, UnsortedVarbinds, IsNotification) ->
969
 
    {OutSideView, InSideView} = split_vbs_view(UnsortedVarbinds, MibView),
970
 
    {Error, Index, NewVbs} = do_get(InSideView, IsNotification),
971
 
    {Error, Index, NewVbs ++ OutSideView}.
972
 
 
973
 
split_vbs_view(Vbs, MibView) ->
974
 
    split_vbs_view(Vbs, MibView, [], []).
975
 
 
976
 
split_vbs_view([Vb | Vbs], MibView, Out, In) ->
977
 
    case snmp_acm:validate_mib_view(Vb#varbind.oid, MibView) of
978
 
        true -> split_vbs_view(Vbs, MibView, Out, [Vb | In]);
979
 
        false -> split_vbs_view(Vbs, MibView,
980
 
                                [Vb#varbind{value = noSuchObject} | Out], In)
981
 
    end;
982
 
split_vbs_view([], _MibView, Out, In) ->
983
 
    {Out, In}.
984
 
            
985
 
do_get(UnsortedVarbinds, IsNotification) ->
986
 
    {MyVarbinds, SubagentVarbinds} = sort_varbindlist(UnsortedVarbinds),
987
 
    case do_get_local(MyVarbinds, [], IsNotification) of
988
 
        {noError, 0, NewMyVarbinds} ->
989
 
            case do_get_subagents(SubagentVarbinds, IsNotification) of
990
 
                {noError, 0, NewSubagentVarbinds} ->
991
 
                    {noError, 0, NewMyVarbinds ++ NewSubagentVarbinds};
992
 
                {ErrorStatus, ErrorIndex, _} ->
993
 
                    {ErrorStatus, ErrorIndex, []}
994
 
            end;
995
 
        {ErrorStatus, ErrorIndex, _} -> 
996
 
            {ErrorStatus, ErrorIndex, []}
997
 
    end.
998
 
 
999
 
%%-----------------------------------------------------------------
1000
 
%% Func: do_get_local/3
1001
 
%% Purpose: Loop the variablebindings list. We know that each varbind
1002
 
%%          in that list belongs to us.
1003
 
%% Returns: {noError, 0, ListOfNewVarbinds} |
1004
 
%%          {ErrorStatus, ErrorIndex, []}
1005
 
%%-----------------------------------------------------------------
1006
 
do_get_local([Vb | Vbs], Res, IsNotification) ->
1007
 
    case try_get(Vb, IsNotification) of
1008
 
        NewVb when record(NewVb, varbind) ->
1009
 
            do_get_local(Vbs, [NewVb | Res], IsNotification);
1010
 
        ListOfNewVb when list(ListOfNewVb) ->
1011
 
            do_get_local(Vbs, lists:append(ListOfNewVb, Res), IsNotification);
1012
 
        {error, Error, OrgIndex} ->
1013
 
            {Error, OrgIndex, []}
1014
 
    end;
1015
 
do_get_local([], Res, _IsNotification) -> 
1016
 
    {noError, 0, Res}.
1017
 
 
1018
 
%%-----------------------------------------------------------------
1019
 
%% Func: do_get_subagents/2
1020
 
%% Purpose: Loop the list of varbinds for different subagents.
1021
 
%%          For each of them, call sub_agent_get to retreive
1022
 
%%          the values for them.
1023
 
%% Returns: {noError, 0, ListOfNewVarbinds} |
1024
 
%%          {ErrorStatus, ErrorIndex, []}
1025
 
%%-----------------------------------------------------------------
1026
 
do_get_subagents(SubagentVarbinds, IsNotification) ->
1027
 
    do_get_subagents(SubagentVarbinds, [], IsNotification).
1028
 
do_get_subagents([{SubAgentPid, SAVbs} | Tail], Res, IsNotification) ->
1029
 
    {_SAOids, Vbs} = sa_split(SAVbs),
1030
 
    case catch subagent_get(SubAgentPid, Vbs, IsNotification) of
1031
 
        {noError, 0, NewVbs} ->
1032
 
            do_get_subagents(Tail, lists:append(NewVbs, Res), IsNotification);
1033
 
        {ErrorStatus, ErrorIndex, _} ->
1034
 
            {ErrorStatus, ErrorIndex, []};
1035
 
        {'EXIT', Reason} ->
1036
 
            user_err("Lost contact with subagent (get) ~w. Using genErr", 
1037
 
                     [Reason]),
1038
 
            {genErr, 0, []} 
1039
 
    end;
1040
 
do_get_subagents([], Res, _IsNotification) ->
1041
 
    {noError, 0, Res}.
1042
 
 
1043
 
 
1044
 
%%-----------------------------------------------------------------
1045
 
%% Func: try_get/2
1046
 
%% Returns: {error, ErrorStatus, OrgIndex} |
1047
 
%%          #varbind |
1048
 
%%          List of #varbind
1049
 
%%-----------------------------------------------------------------
1050
 
try_get(IVb, IsNotification) when record(IVb, ivarbind) ->
1051
 
    get_var_value_from_ivb(IVb, IsNotification);
1052
 
try_get({TableOid, TableVbs}, IsNotification) ->
1053
 
    [#ivarbind{mibentry = MibEntry}|_] = TableVbs,
1054
 
    {NoAccessVbs, AccessVbs} =
1055
 
        check_all_table_vbs(TableVbs, IsNotification, [], []),
1056
 
    case get_tab_value_from_mib(MibEntry, TableOid, AccessVbs) of
1057
 
        {error, ErrorStatus, OrgIndex} ->
1058
 
            {error, ErrorStatus, OrgIndex};
1059
 
        NVbs ->
1060
 
            NVbs ++ NoAccessVbs
1061
 
    end.
1062
 
 
1063
 
%%-----------------------------------------------------------------
1064
 
%% Make sure all requested columns are accessible.
1065
 
%%-----------------------------------------------------------------
1066
 
check_all_table_vbs([IVb| IVbs], IsNotification, NoA, A) ->
1067
 
    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
1068
 
    case Me#me.access of
1069
 
        'not-accessible' -> 
1070
 
            NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
1071
 
            check_all_table_vbs(IVbs, IsNotification, NNoA, A);
1072
 
        'accessible-for-notify' when IsNotification == false -> 
1073
 
            NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
1074
 
            check_all_table_vbs(IVbs, IsNotification, NNoA, A);
1075
 
        'write-only' -> 
1076
 
            NNoA = [Vb#varbind{value = noSuchInstance} | NoA],
1077
 
            check_all_table_vbs(IVbs, IsNotification, NNoA, A);
1078
 
        _ ->
1079
 
            check_all_table_vbs(IVbs, IsNotification, NoA, [IVb | A])
1080
 
    end;
1081
 
check_all_table_vbs([], _IsNotification, NoA, A) -> {NoA, A}.
1082
 
 
1083
 
%%-----------------------------------------------------------------
1084
 
%% Returns: {error, ErrorStatus, OrgIndex} |
1085
 
%%          #varbind
1086
 
%%-----------------------------------------------------------------
1087
 
get_var_value_from_ivb(IVb, IsNotification)
1088
 
  when IVb#ivarbind.status == noError ->
1089
 
    #ivarbind{mibentry = Me, varbind = Vb} = IVb,
1090
 
    #varbind{org_index = OrgIndex, oid = Oid} = Vb,
1091
 
    case Me#me.access of
1092
 
        'not-accessible' -> 
1093
 
            Vb#varbind{value = noSuchInstance};
1094
 
        'accessible-for-notify' when IsNotification == false -> 
1095
 
            Vb#varbind{value = noSuchInstance};
1096
 
        'write-only' -> 
1097
 
            Vb#varbind{value = noSuchInstance};
1098
 
        _ -> 
1099
 
            case get_var_value_from_mib(Me, Oid) of
1100
 
                {value, Type, Value} ->
1101
 
                    Vb#varbind{variabletype = Type, value = Value};
1102
 
                {error, ErrorStatus} ->
1103
 
                    {error, ErrorStatus, OrgIndex}
1104
 
            end
1105
 
    end;
1106
 
get_var_value_from_ivb(#ivarbind{status = Status, varbind = Vb}, _) ->
1107
 
    Vb#varbind{value = Status}.
1108
 
 
1109
 
%%-----------------------------------------------------------------
1110
 
%% Func: get_var_value_from_mib/1
1111
 
%% Purpose: 
1112
 
%% Returns: {error, ErrorStatus} |
1113
 
%%          {value, Type, Value}
1114
 
%%-----------------------------------------------------------------
1115
 
%% Pre: Oid is a correct instance Oid (lookup checked that).
1116
 
%% Returns: A correct return value (see make_value_a_correct_value)
1117
 
get_var_value_from_mib(#me{entrytype = variable,
1118
 
                           asn1_type = ASN1Type,
1119
 
                           mfa = {Module, Func, Args}},
1120
 
                       _Oid) ->
1121
 
    Result = (catch dbg_apply(Module, Func, [get | Args])),
1122
 
    % mib shall return {value, <a-nice-value-within-range>} |
1123
 
    % {noValue, noSuchName} (v1) | 
1124
 
    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
1125
 
    % everything else (including 'genErr') will generate 'genErr'.
1126
 
    make_value_a_correct_value(Result, ASN1Type, {Module, Func, Args});
1127
 
 
1128
 
get_var_value_from_mib(#me{entrytype = table_column,
1129
 
                           oid = MeOid,
1130
 
                           asn1_type = ASN1Type,
1131
 
                           mfa = {Module, Func, Args}},
1132
 
                       Oid) ->
1133
 
    Col = lists:last(MeOid),
1134
 
    Indexes = snmp_misc:diff(Oid, MeOid),
1135
 
    [Result] = (catch dbg_apply(Module, Func, [get, Indexes, [Col] | Args])),
1136
 
    make_value_a_correct_value(Result, ASN1Type, {Module, Func, Args, 
1137
 
                                                  Indexes, Col}).
1138
 
 
1139
 
 
1140
 
%% For table operations we need to pass RestOid down to the table-function.
1141
 
%% Its up to the table-function to check for noSuchInstance (ex: a 
1142
 
%% non-existing row).
1143
 
%% Returns: {error, ErrorStatus, OrgIndex} |
1144
 
%%          {value, Type, Value}
1145
 
get_tab_value_from_mib(#me{mfa = {Module,Func,Args}}, TableOid, TableVbs) ->
1146
 
    TableOpsWithShortOids = deletePrefixes(TableOid, TableVbs),
1147
 
    case get_value_all_rows(snmp_svbl:sort_varbinds_rows(TableOpsWithShortOids),
1148
 
                            Module, Func, Args, []) of
1149
 
        {Error, Index} ->
1150
 
            #ivarbind{varbind = Vb} = lists:nth(Index, TableVbs),
1151
 
            {error, Error, Vb#varbind.org_index};
1152
 
        ListOfValues -> 
1153
 
            merge_varbinds_and_value(TableVbs, ListOfValues)
1154
 
    end.
1155
 
 
1156
 
%%-----------------------------------------------------------------
1157
 
%% Values is a scrambled list of {CorrectValue, Index}, where Index
1158
 
%% is index into the #ivarbind list. So for each Value, we must
1159
 
%% find the corresponding #ivarbind, and merge them into a new
1160
 
%% #varbind.
1161
 
%% The Values list comes from validate_tab_res.
1162
 
%%-----------------------------------------------------------------
1163
 
merge_varbinds_and_value(IVbs, [{{value, Type, Value}, Index} | Values]) ->
1164
 
    #ivarbind{varbind = Vb} = lists:nth(Index, IVbs),
1165
 
    [Vb#varbind{variabletype = Type, value = Value} |
1166
 
     merge_varbinds_and_value(IVbs, Values)];
1167
 
merge_varbinds_and_value(_, []) -> [].
1168
 
    
1169
 
get_value_all_rows([{RowIndex, OrgCols} | Rows], Module, Func, Args, Res) 
1170
 
  when RowIndex == [] ->
1171
 
    Cols = lists:map(fun({_Col, _ASN1Type, Index}) ->
1172
 
                             {{value, noValue, noSuchInstance}, Index}
1173
 
                     end, OrgCols),
1174
 
    NewRes = lists:append(Cols, Res),
1175
 
    get_value_all_rows(Rows, Module, Func, Args, NewRes);
1176
 
get_value_all_rows([Row | Rows], Module, Func, Args, Res) ->
1177
 
    {RowIndex, OrgCols} = Row,
1178
 
    {DOrgCols, Dup} = remove_duplicates(OrgCols),
1179
 
    Cols = delete_index(DOrgCols),
1180
 
    Result = (catch dbg_apply(Module, Func, [get, RowIndex, Cols | Args])),
1181
 
    case validate_tab_res(Result, DOrgCols, {Module, Func, Args}) of
1182
 
        Values when list(Values) ->
1183
 
            NVals = restore_duplicates(Dup, Values),
1184
 
            NewRes = lists:append(NVals, Res),
1185
 
            get_value_all_rows(Rows, Module, Func, Args, NewRes);
1186
 
        {error, ErrorStatus, Index} ->
1187
 
            validate_err(row_set, {ErrorStatus, Index}, {Module, Func, Args})
1188
 
%% Remove these lines!
1189
 
%       {ErrorStatus, ColNumber} ->
1190
 
%           Index = col_to_index(ColNumber, OrgCols),
1191
 
%           validate_err(row_set, {ErrorStatus, Index}, {Module,Func,Args})
1192
 
    end;
1193
 
get_value_all_rows([], _Module, _Func, _Args, Res) -> Res.
1194
 
 
1195
 
%%-----------------------------------------------------------------
1196
 
%% Returns: list of {ShortOid, ASN1TYpe}
1197
 
%%-----------------------------------------------------------------
1198
 
deletePrefixes(Prefix, [#ivarbind{varbind = Varbind, mibentry = ME} | Vbs]) ->
1199
 
    #varbind{oid = Oid} = Varbind,
1200
 
    [{snmp_misc:diff(Oid, Prefix), ME#me.asn1_type} |
1201
 
     deletePrefixes(Prefix, Vbs)];
1202
 
deletePrefixes(_Prefix, []) -> [].
1203
 
 
1204
 
%%-----------------------------------------------------------------
1205
 
%% Args: {RowIndex, list of {ShortOid, ASN1Type}}
1206
 
%% Returns: list of Col
1207
 
%%-----------------------------------------------------------------
1208
 
delete_index([{Col, _Val, _OrgIndex} | T]) ->
1209
 
    [Col | delete_index(T)];
1210
 
delete_index([]) -> [].
1211
 
 
1212
 
%%-----------------------------------------------------------------
1213
 
%% This function is called before 'get' on a table, and removes
1214
 
%% any duplicate columns.  It returns {Cols, DupInfo}.  The Cols
1215
 
%% are the unique columns.  The instrumentation function is
1216
 
%% called to get the values.  These values, together with the
1217
 
%% DupInfo, is later passed to restore_duplicates, which uses
1218
 
%% the retrieved values to reconstruct the original column list,
1219
 
%% but with the retrieved value for each column.
1220
 
%%-----------------------------------------------------------------
1221
 
remove_duplicates(Cols) ->
1222
 
    remove_duplicates(Cols, [], []).
1223
 
 
1224
 
 
1225
 
remove_duplicates([{Col, V1, OrgIdx1}, {Col, V2, OrgIdx2} | T], NCols, Dup) ->
1226
 
    remove_duplicates([{Col, V1, OrgIdx1} | T], NCols, 
1227
 
                      [{Col, V2, OrgIdx2} | Dup]);
1228
 
remove_duplicates([Col | T], NCols, Dup) ->
1229
 
    remove_duplicates(T, [Col | NCols], Dup);
1230
 
remove_duplicates([], NCols, Dup) ->
1231
 
    {lists:reverse(NCols), lists:reverse(Dup)}.
1232
 
 
1233
 
restore_duplicates([], Cols) ->
1234
 
    lists:map(fun({_Col, Val, OrgIndex}) -> {Val, OrgIndex} end, Cols);
1235
 
restore_duplicates([{Col, _Val2, OrgIndex2} | Dup],
1236
 
                   [{Col, NVal, OrgIndex1} | Cols]) ->
1237
 
    [{NVal, OrgIndex2} |
1238
 
     restore_duplicates(Dup, [{Col, NVal, OrgIndex1} | Cols])];
1239
 
restore_duplicates(Dup, [{_Col, Val, OrgIndex} | T]) ->
1240
 
    [{Val, OrgIndex} | restore_duplicates(Dup, T)].
1241
 
 
1242
 
%% Maps the column number to Index.
1243
 
% col_to_index(0, _) -> 0;
1244
 
% col_to_index(Col, [{Col, _, Index}|_]) ->
1245
 
%     Index;
1246
 
% col_to_index(Col, [_|Cols]) ->
1247
 
%     col_to_index(Col, Cols).
1248
 
 
1249
 
%%-----------------------------------------------------------------
1250
 
%% Three cases:
1251
 
%%   1) All values ok
1252
 
%%   2) table_func returned {Error, ...}
1253
 
%%   3) Some value in Values list is erroneous.
1254
 
%% Args: Value is a list of values from table_func(get..)
1255
 
%%       OrgCols is a list with {Col, ASN1Type, OrgIndex} 
1256
 
%%         each element in Values and OrgCols correspond to each
1257
 
%%         other.
1258
 
%%-----------------------------------------------------------------
1259
 
validate_tab_res(Values, OrgCols, Mfa) when list(Values) ->
1260
 
    {_Col, _ASN1Type, OneIdx} = hd(OrgCols),
1261
 
    validate_tab_res(Values, OrgCols, Mfa, [], OneIdx);
1262
 
validate_tab_res({noValue, Error}, OrgCols, Mfa) ->
1263
 
    Values = lists:duplicate(length(OrgCols), {noValue, Error}),
1264
 
    validate_tab_res(Values, OrgCols, Mfa);
1265
 
validate_tab_res({genErr, Col}, OrgCols, Mfa) ->
1266
 
    case lists:keysearch(Col, 1, OrgCols) of
1267
 
        {value, {_Col, _ASN1Type, Index}} ->
1268
 
            {error, genErr, Index};
1269
 
        _ ->
1270
 
            user_err("Invalid column in {genErr, ~w} from ~w (get)",
1271
 
                     [Col, Mfa]),
1272
 
            [{_Col, _ASN1Type, Index} | _] = OrgCols,
1273
 
            {error, genErr, Index}
1274
 
    end;
1275
 
validate_tab_res(genErr, [{_Col, __ASN1Type, Index} | _OrgCols], _Mfa) ->
1276
 
    {error, genErr, Index};
1277
 
validate_tab_res(Error, [{_Col, _ASN1Type, Index} | _OrgCols], Mfa) ->
1278
 
    user_err("Invalid return value ~w from ~w (get)",[Error, Mfa]),
1279
 
    {error, genErr, Index}.
1280
 
 
1281
 
validate_tab_res([Value | Values], [{Col, ASN1Type, Index} | OrgCols],
1282
 
                 Mfa, Res, I) ->
1283
 
    %% This one makes it possible to return a list of genErr, which
1284
 
    %% is not allowed according to the manual.  But that's ok, as
1285
 
    %% everything else will generate a genErr! (the only problem is
1286
 
    %% that it won't generate a user_error).
1287
 
    case make_value_a_correct_value(Value, ASN1Type, Mfa) of
1288
 
        {error, ErrorStatus} ->
1289
 
            {error, ErrorStatus, Index};
1290
 
        CorrectValue ->
1291
 
            NewRes = [{Col, CorrectValue, Index} | Res],
1292
 
            validate_tab_res(Values, OrgCols, Mfa, NewRes, I)
1293
 
    end;
1294
 
validate_tab_res([], [], _Mfa, Res, _I) -> Res;
1295
 
validate_tab_res([], [{_Col, _ASN1Type, Index}|_], Mfa, _Res, _I) ->
1296
 
    user_err("Too few values returned from ~w (get)", [Mfa]),
1297
 
    {error, genErr, Index};
1298
 
validate_tab_res(_TooMany, [], Mfa, _Res, I) ->
1299
 
    user_err("Too many values returned from ~w (get)", [Mfa]),
1300
 
    {error, genErr, I}.
1301
 
 
1302
 
 
1303
 
%%%-----------------------------------------------------------------
1304
 
%%% 4. GET-NEXT REQUEST
1305
 
%%% --------------
1306
 
%%%   According to RFC1157, section 4.1.3 and RFC1905, section 4.2.2.
1307
 
%%%-----------------------------------------------------------------
1308
 
%%-----------------------------------------------------------------
1309
 
%% Func: do_get_next/2
1310
 
%% Purpose: do_get_next handles "getNextRequests".
1311
 
%% Note: Even if it is SNMPv1, a varbind's value can be
1312
 
%%       endOfMibView. This is converted to noSuchName in process_pdu.
1313
 
%% Returns: {noError, 0, ListOfNewVarbinds} |
1314
 
%%          {ErrorStatus, ErrorIndex, []}
1315
 
%% Note2: ListOfNewVarbinds is not sorted in any order!!!
1316
 
%% Alg: First, the variables are sorted in OID order.
1317
 
%%
1318
 
%%      Second, next in the MIB is performed for each OID, and
1319
 
%%      the result is collected as: if next oid is a variable,
1320
 
%%      perform a get to retrieve its value; if next oid is in a
1321
 
%%      table, save this value and continue until we get an oid
1322
 
%%      outside this table. Then perform get_next on the table,
1323
 
%%      and continue with all endOfTables and the oid outside the
1324
 
%%      table; if next oid is an subagent, save this value and
1325
 
%%      continue as in the table case.
1326
 
%%
1327
 
%%      Third, each response is checked for endOfMibView, or (for
1328
 
%%      subagents) that the Oid returned has the correct prefix.
1329
 
%%      (This is necessary since an SA can be registered under many
1330
 
%%      separated subtrees, and if the last variable in the first
1331
 
%%      subtree is requested in a next, the SA will return the first
1332
 
%%      variable in the second subtree. This might be working, since
1333
 
%%      there may be a variable in between these subtrees.) For each
1334
 
%%      of these, a new get-next is performed, one at a time.
1335
 
%%      This alg. might be optimised in several ways. The most 
1336
 
%%      striking one is that the same SA might be called several
1337
 
%%      times, when one time should be enough. But it isn't clear
1338
 
%%      that this really matters, since many nexts across the same
1339
 
%%      subagent must be considered to be very rare.
1340
 
%%-----------------------------------------------------------------
1341
 
do_get_next(MibView, UnsortedVarbinds) ->
1342
 
    SortedVarbinds = oid_sort_varbindlist(UnsortedVarbinds),
1343
 
    next_loop_varbinds([], SortedVarbinds, MibView, [], []).
1344
 
 
1345
 
oid_sort_varbindlist(Vbs) ->
1346
 
    lists:keysort(#varbind.oid, Vbs).
1347
 
 
1348
 
%% LAVb is Last Accessible Vb
1349
 
next_loop_varbinds([], [Vb | Vbs], MibView, Res, LAVb) ->
1350
 
%%     ?vtrace("next_loop_varbins -> entry when"
1351
 
%%      "~n   Vb:      ~p"
1352
 
%%      "~n   MibView: ~p", [Vb, MibView]),
1353
 
    case varbind_next(Vb, MibView) of
1354
 
        endOfMibView ->
1355
 
            RVb = if LAVb == [] -> Vb;
1356
 
                     true -> LAVb
1357
 
                  end,
1358
 
            NewVb = RVb#varbind{variabletype = 'NULL', value = endOfMibView},
1359
 
            next_loop_varbinds([], Vbs, MibView, [NewVb | Res], []);
1360
 
        {variable, ME, VarOid} when ME#me.access /= 'not-accessible',
1361
 
                                    ME#me.access /= 'write-only',
1362
 
                                    ME#me.access /= 'accessible-for-notify' -> 
1363
 
            case try_get_instance(Vb, ME) of
1364
 
                {value, noValue, _NoSuchSomething} ->
1365
 
                    %% Try next one
1366
 
                    NewVb = Vb#varbind{oid = VarOid, value = 'NULL'},
1367
 
                    next_loop_varbinds([], [NewVb | Vbs], MibView, Res, []);
1368
 
                {value, Type, Value} ->
1369
 
                    NewVb = Vb#varbind{oid = VarOid, variabletype = Type,
1370
 
                                       value = Value},
1371
 
                    next_loop_varbinds([], Vbs, MibView, [NewVb | Res], []);
1372
 
                {error, ErrorStatus} ->
1373
 
                    ?vdebug("next loop varbinds:"
1374
 
                            "~n   ErrorStatus: ~p",[ErrorStatus]),
1375
 
                    {ErrorStatus, Vb#varbind.org_index, []}
1376
 
            end;
1377
 
        {variable, _ME, VarOid} -> 
1378
 
            RVb = if LAVb == [] -> Vb;
1379
 
                     true -> LAVb
1380
 
                  end,
1381
 
            NewVb = Vb#varbind{oid = VarOid, value = 'NULL'},
1382
 
            next_loop_varbinds([], [NewVb | Vbs], MibView, Res, RVb);
1383
 
        {table, TableOid, TableRestOid, ME} ->
1384
 
            next_loop_varbinds({table, TableOid, ME,
1385
 
                                [{tab_oid(TableRestOid), Vb}]},
1386
 
                               Vbs, MibView, Res, []);
1387
 
        {subagent, SubAgentPid, SAOid} ->
1388
 
            NewVb = Vb#varbind{variabletype = 'NULL', value = 'NULL'},
1389
 
            next_loop_varbinds({subagent, SubAgentPid, SAOid, [NewVb]},
1390
 
                               Vbs, MibView, Res, [])
1391
 
    end;
1392
 
next_loop_varbinds({table, TableOid, ME, TabOids},
1393
 
                   [Vb | Vbs], MibView, Res, _LAVb) ->
1394
 
%%     ?vtrace("next_loop_varbins(table) -> entry with"
1395
 
%%      "~n   TableOid: ~p"
1396
 
%%      "~n   Vb:       ~p", [TableOid, Vb]),
1397
 
    case varbind_next(Vb, MibView) of
1398
 
        {table, TableOid, TableRestOid, _ME} ->
1399
 
            next_loop_varbinds({table, TableOid, ME,
1400
 
                                [{tab_oid(TableRestOid), Vb} | TabOids]},
1401
 
                               Vbs, MibView, Res, []);
1402
 
        _ ->
1403
 
            case get_next_table(ME, TableOid, TabOids, MibView) of
1404
 
                {ok, TabRes, TabEndOfTabVbs} ->
1405
 
                    NewVbs = lists:append(TabEndOfTabVbs, [Vb | Vbs]),
1406
 
                    NewRes = lists:append(TabRes, Res),
1407
 
                    next_loop_varbinds([], NewVbs, MibView, NewRes, []);
1408
 
                {ErrorStatus, OrgIndex} ->
1409
 
                    ?vdebug("next loop varbinds: next varbind"
1410
 
                            "~n   ErrorStatus: ~p"
1411
 
                            "~n   OrgIndex:    ~p",
1412
 
                            [ErrorStatus,OrgIndex]),
1413
 
                    {ErrorStatus, OrgIndex, []}
1414
 
            end
1415
 
    end;
1416
 
next_loop_varbinds({table, TableOid, ME, TabOids},
1417
 
                   [], MibView, Res, _LAVb) ->
1418
 
%%     ?vtrace("next_loop_varbins(table) -> entry with"
1419
 
%%      "~n   TableOid: ~p", [TableOid]),
1420
 
    case get_next_table(ME, TableOid, TabOids, MibView) of
1421
 
        {ok, TabRes, TabEndOfTabVbs} ->
1422
 
%%          ?vtrace("next_loop_varbins(table) -> get_next_table result:"
1423
 
%%              "~n   TabRes:         ~p"
1424
 
%%              "~n   TabEndOfTabVbs: ~p", [TabRes, TabEndOfTabVbs]),
1425
 
            NewRes = lists:append(TabRes, Res),
1426
 
            next_loop_varbinds([], TabEndOfTabVbs, MibView, NewRes, []);
1427
 
        {ErrorStatus, OrgIndex} ->
1428
 
            ?vdebug("next loop varbinds: next table"
1429
 
                    "~n   ErrorStatus: ~p"
1430
 
                    "~n   OrgIndex:    ~p",
1431
 
                    [ErrorStatus,OrgIndex]),
1432
 
            {ErrorStatus, OrgIndex, []}
1433
 
    end;
1434
 
next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
1435
 
                   [Vb | Vbs], MibView, Res, _LAVb) ->
1436
 
%%     ?vtrace("next_loop_varbins(subagent) -> entry with"
1437
 
%%      "~n   SAPid: ~p"
1438
 
%%      "~n   SAOid: ~p"
1439
 
%%      "~n   Vb:    ~p", [SAPid, SAOid, Vb]),
1440
 
    case varbind_next(Vb, MibView) of
1441
 
        {subagent, _SubAgentPid, SAOid} ->
1442
 
            next_loop_varbinds({subagent, SAPid, SAOid,
1443
 
                                [Vb | SAVbs]},
1444
 
                               Vbs, MibView, Res, []);
1445
 
        _ ->
1446
 
            case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
1447
 
                {ok, SARes, SAEndOfMibViewVbs} ->
1448
 
                    NewVbs = lists:append(SAEndOfMibViewVbs, [Vb | Vbs]),
1449
 
                    NewRes = lists:append(SARes, Res),
1450
 
                    next_loop_varbinds([], NewVbs, MibView, NewRes, []);
1451
 
                {noSuchName, OrgIndex} ->
1452
 
                    %% v1 reply, treat this Vb as endOfMibView, and try again
1453
 
                    %% for the others.
1454
 
                    case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
1455
 
                        {value, EVb} ->
1456
 
                            NextOid = next_oid(SAOid),
1457
 
                            EndOfVb = 
1458
 
                                EVb#varbind{oid = NextOid,
1459
 
                                            value = {endOfMibView, NextOid}},
1460
 
                            case lists:delete(EVb, SAVbs) of
1461
 
                                [] ->
1462
 
                                    next_loop_varbinds([], [EndOfVb, Vb | Vbs],
1463
 
                                                       MibView, Res, []);
1464
 
                                TryAgainVbs ->
1465
 
                                    next_loop_varbinds({subagent, SAPid, SAOid,
1466
 
                                                        TryAgainVbs},
1467
 
                                                       [EndOfVb, Vb | Vbs],
1468
 
                                                       MibView, Res, [])
1469
 
                            end;
1470
 
                        false ->
1471
 
                            %% bad index from subagent
1472
 
                            {genErr, (hd(SAVbs))#varbind.org_index, []}
1473
 
                    end;
1474
 
                {ErrorStatus, OrgIndex} ->
1475
 
                    ?vdebug("next loop varbinds: next subagent"
1476
 
                            "~n   Vb:          ~p"
1477
 
                            "~n   ErrorStatus: ~p"
1478
 
                            "~n   OrgIndex:    ~p",
1479
 
                            [Vb,ErrorStatus,OrgIndex]),
1480
 
                    {ErrorStatus, OrgIndex, []}
1481
 
            end
1482
 
    end;
1483
 
next_loop_varbinds({subagent, SAPid, SAOid, SAVbs},
1484
 
                   [], MibView, Res, _LAVb) ->
1485
 
%%     ?vtrace("next_loop_varbins(subagent) -> entry with"
1486
 
%%      "~n   SAPid: ~p"
1487
 
%%      "~n   SAOid: ~p", [SAPid, SAOid]),
1488
 
    case get_next_sa(SAPid, SAOid, SAVbs, MibView) of
1489
 
        {ok, SARes, SAEndOfMibViewVbs} ->
1490
 
            NewRes = lists:append(SARes, Res),
1491
 
            next_loop_varbinds([], SAEndOfMibViewVbs, MibView, NewRes, []);
1492
 
        {noSuchName, OrgIndex} ->
1493
 
            %% v1 reply, treat this Vb as endOfMibView, and try again for
1494
 
            %% the others.
1495
 
            case lists:keysearch(OrgIndex, #varbind.org_index, SAVbs) of
1496
 
                {value, EVb} ->
1497
 
                    NextOid = next_oid(SAOid),
1498
 
                    EndOfVb = EVb#varbind{oid = NextOid,
1499
 
                                          value = {endOfMibView, NextOid}},
1500
 
                    case lists:delete(EVb, SAVbs) of
1501
 
                        [] ->
1502
 
                            next_loop_varbinds([], [EndOfVb], MibView, Res, []);
1503
 
                        TryAgainVbs ->
1504
 
                            next_loop_varbinds({subagent, SAPid, SAOid,
1505
 
                                                TryAgainVbs},
1506
 
                                               [EndOfVb], MibView, Res, [])
1507
 
                    end;
1508
 
                false ->
1509
 
                    %% bad index from subagent
1510
 
                    {genErr, (hd(SAVbs))#varbind.org_index, []}
1511
 
            end;
1512
 
        {ErrorStatus, OrgIndex} ->
1513
 
            ?vdebug("next loop varbinds: next subagent"
1514
 
                    "~n   ErrorStatus: ~p"
1515
 
                    "~n   OrgIndex:    ~p",
1516
 
                    [ErrorStatus,OrgIndex]),
1517
 
            {ErrorStatus, OrgIndex, []}
1518
 
    end;
1519
 
next_loop_varbinds([], [], _MibView, Res, _LAVb) ->
1520
 
%%     ?vtrace("next_loop_varbins -> entry when done", []),
1521
 
    {noError, 0, Res}.
1522
 
 
1523
 
try_get_instance(_Vb, #me{mfa = {M, F, A}, asn1_type = ASN1Type}) ->
1524
 
    ?vtrace("try get instance from <~p,~p,~p>",[M,F,A]),
1525
 
    Result = (catch dbg_apply(M, F, [get | A])),
1526
 
    % mib shall return {value, <a-nice-value-within-range>} |
1527
 
    % {noValue, noSuchName} (v1) | 
1528
 
    % {noValue, noSuchObject | noSuchInstance} (v2, v1)
1529
 
    % everything else (including 'genErr') will generate 'genErr'.
1530
 
    make_value_a_correct_value(Result, ASN1Type, {M, F, A}).
1531
 
 
1532
 
tab_oid([]) -> [0];
1533
 
tab_oid(X) -> X.
1534
 
 
1535
 
%%-----------------------------------------------------------------
1536
 
%% Perform a next, using the varbinds Oid if value is simple
1537
 
%% value. If value is {endOf<something>, NextOid}, use NextOid.
1538
 
%% This case happens when a table has returned endOfTable, or
1539
 
%% a subagent has returned endOfMibView.
1540
 
%%-----------------------------------------------------------------
1541
 
varbind_next(#varbind{value = Value, oid = Oid}, MibView) ->
1542
 
%%     ?vtrace("varbind_next -> entry with"
1543
 
%%      "~n   Value:   ~p"
1544
 
%%      "~n   Oid:     ~p"
1545
 
%%      "~n   MibView: ~p", [Value, Oid, MibView]),
1546
 
    case Value of
1547
 
        {endOfTable, NextOid} ->
1548
 
            snmp_mib:next(get(mibserver), NextOid, MibView);
1549
 
        {endOfMibView, NextOid} ->
1550
 
            snmp_mib:next(get(mibserver), NextOid, MibView);
1551
 
        _ ->
1552
 
            snmp_mib:next(get(mibserver), Oid, MibView)
1553
 
    end.
1554
 
 
1555
 
get_next_table(#me{mfa = {M, F, A}}, TableOid, TableOids, MibView) ->
1556
 
    % We know that all TableOids have at least a column number as oid
1557
 
%%     ?vtrace("get_next_table -> entry with"
1558
 
%%      "~n   M:         ~p"
1559
 
%%      "~n   F:         ~p"
1560
 
%%      "~n   A:         ~p"
1561
 
%%      "~n   TableOid:  ~p"
1562
 
%%      "~n   TableOids: ~p"
1563
 
%%      "~n   MibView:   ~p", [M, F, A, TableOid, TableOids, MibView]),
1564
 
    Sorted = snmp_svbl:sort_varbinds_rows(TableOids),
1565
 
    case get_next_values_all_rows(Sorted, M,F,A, [], TableOid) of
1566
 
        NewVbs when list(NewVbs) ->
1567
 
%%          ?vtrace("get_next_table -> "
1568
 
%%              "~n   NewVbs: ~p", [NewVbs]),
1569
 
            % We must now check each Vb for endOfTable and that it is
1570
 
            % in the MibView. If not, it becomes a endOfTable. We 
1571
 
            % collect all of these together.
1572
 
            transform_tab_next_result(NewVbs, {[], []}, MibView);
1573
 
        {ErrorStatus, OrgIndex} ->
1574
 
            {ErrorStatus, OrgIndex}
1575
 
    end.
1576
 
 
1577
 
get_next_values_all_rows([Row | Rows], M, F, A, Res, TabOid) ->
1578
 
    {RowIndex, TableOids} = Row,
1579
 
    Cols = delete_index(TableOids),
1580
 
%%     ?vtrace("get_next_values_all_rows -> "
1581
 
%%      "~n   Cols: ~p", [Cols]),
1582
 
    Result = (catch dbg_apply(M, F, [get_next, RowIndex, Cols | A])),
1583
 
%%     ?vtrace("get_next_values_all_rows -> "
1584
 
%%      "~n   Result: ~p", [Result]),
1585
 
    case validate_tab_next_res(Result, TableOids, {M, F, A}, TabOid) of
1586
 
        Values when list(Values) -> 
1587
 
%%          ?vtrace("get_next_values_all_rows -> "
1588
 
%%              "~n   Values: ~p", [Values]),
1589
 
            NewRes = lists:append(Values, Res),
1590
 
            get_next_values_all_rows(Rows, M, F, A, NewRes, TabOid);
1591
 
        {ErrorStatus, OrgIndex} ->
1592
 
            {ErrorStatus, OrgIndex}
1593
 
    end;
1594
 
get_next_values_all_rows([], _M, _F, _A, Res, _TabOid) ->
1595
 
    Res.
1596
 
 
1597
 
transform_tab_next_result([Vb | Vbs], {Res, EndOfs}, MibView) ->
1598
 
    case Vb#varbind.value of
1599
 
        {endOfTable, _} ->
1600
 
%%          ?vtrace("transform_tab_next_result -> endOfTable: "
1601
 
%%              "split varbinds",[]),
1602
 
%%          R = split_varbinds(Vbs, Res, [Vb | EndOfs]),
1603
 
%%          ?vtrace("transform_tab_next_result -> "
1604
 
%%              "~n   R: ~p", [R]),
1605
 
%%          R;
1606
 
            split_varbinds(Vbs, Res, [Vb | EndOfs]);
1607
 
        _ ->
1608
 
            case snmp_acm:validate_mib_view(Vb#varbind.oid, MibView) of
1609
 
                true ->
1610
 
                    transform_tab_next_result(Vbs, {[Vb|Res], EndOfs},MibView);
1611
 
                _ ->
1612
 
                    Oid = Vb#varbind.oid,
1613
 
                    NewEndOf = Vb#varbind{value = {endOfTable, Oid}},
1614
 
                    transform_tab_next_result(Vbs, {Res, [NewEndOf | EndOfs]},
1615
 
                                              MibView)
1616
 
            end
1617
 
    end;
1618
 
transform_tab_next_result([], {Res, EndOfs}, _MibView) ->
1619
 
%%     ?vtrace("transform_tab_next_result -> entry with: "
1620
 
%%      "~n   Res:    ~p"
1621
 
%%      "~n   EndIfs: ~p",[Res, EndOfs]),
1622
 
    {ok, Res, EndOfs}.
1623
 
 
1624
 
%%-----------------------------------------------------------------
1625
 
%% Three cases:
1626
 
%%   1) All values ok
1627
 
%%   2) table_func returned {Error, ...}
1628
 
%%   3) Some value in Values list is erroneous.
1629
 
%% Args: Value is a list of values from table_func(get_next, ...)
1630
 
%%       TableOids is a list of {TabRestOid, OrgVb} 
1631
 
%%         each element in Values and TableOids correspond to each
1632
 
%%         other.
1633
 
%% Returns: List of NewVarbinds |
1634
 
%%          {ErrorStatus, OrgIndex}
1635
 
%%          (In the NewVarbinds list, the value may be endOfTable)
1636
 
%%-----------------------------------------------------------------
1637
 
validate_tab_next_res(Values, TableOids, Mfa, TabOid) ->
1638
 
%%     ?vtrace("validate_tab_next_res -> entry with: "
1639
 
%%      "~n   Values:     ~p"
1640
 
%%      "~n   TableOids:  ~p"
1641
 
%%      "~n   Mfa:        ~p"
1642
 
%%      "~n   TabOid:     ~p", [Values, TableOids, Mfa, TabOid]),
1643
 
    {_Col, _ASN1Type, OneIdx} = hd(TableOids),
1644
 
    validate_tab_next_res(Values, TableOids, Mfa, [], TabOid,
1645
 
                          next_oid(TabOid), OneIdx).
1646
 
validate_tab_next_res([{NextOid, Value} | Values],
1647
 
                      [{_ColNo, OrgVb, _Index} | TableOids],
1648
 
                      Mfa, Res, TabOid, TabNextOid, I) ->
1649
 
%%     ?vtrace("validate_tab_next_res -> entry with: "
1650
 
%%      "~n   NextOid:    ~p"
1651
 
%%      "~n   Value:      ~p"
1652
 
%%      "~n   Values:     ~p"
1653
 
%%      "~n   TableOids:  ~p"
1654
 
%%      "~n   Mfa:        ~p"
1655
 
%%      "~n   TabOid:     ~p", 
1656
 
%%      [NextOid, Value, Values, TableOids, Mfa, TabOid]),
1657
 
    #varbind{org_index = OrgIndex} = OrgVb,
1658
 
%%     ?vtrace("validate_tab_next_res -> OrgIndex: ~p", [OrgIndex]),
1659
 
    NextCompleteOid = lists:append(TabOid, NextOid),
1660
 
    case snmp_mib:lookup(get(mibserver), NextCompleteOid) of
1661
 
        {table_column, #me{asn1_type = ASN1Type}, _TableEntryOid} ->
1662
 
%%          ?vtrace("validate_tab_next_res -> ASN1Type: ~p", [ASN1Type]),
1663
 
            case make_value_a_correct_value({value, Value}, ASN1Type, Mfa) of
1664
 
                {error, ErrorStatus} ->
1665
 
%%                  ?vtrace("validate_tab_next_res -> "
1666
 
%%                      "~n   ErrorStatus: ~p", [ErrorStatus]),
1667
 
                    {ErrorStatus, OrgIndex};
1668
 
                {value, Type, NValue} ->
1669
 
%%                  ?vtrace("validate_tab_next_res -> "
1670
 
%%                      "~n   Type:   ~p"
1671
 
%%                      "~n   NValue: ~p", [Type, NValue]),
1672
 
                    NewVb = OrgVb#varbind{oid = NextCompleteOid,
1673
 
                                          variabletype = Type, value = NValue},
1674
 
                    validate_tab_next_res(Values, TableOids, Mfa,
1675
 
                                          [NewVb | Res], TabOid, TabNextOid, I)
1676
 
            end;
1677
 
        Error ->
1678
 
            user_err("Invalid oid ~w from ~w (get_next). Using genErr => ~p",
1679
 
                     [NextOid, Mfa, Error]),
1680
 
            {genErr, OrgIndex}
1681
 
    end;
1682
 
validate_tab_next_res([endOfTable | Values],
1683
 
                      [{_ColNo, OrgVb, _Index} | TableOids],
1684
 
                      Mfa, Res, TabOid, TabNextOid, I) ->
1685
 
%%     ?vtrace("validate_tab_next_res(endOfTable) -> entry with: "
1686
 
%%      "~n   Values:     ~p"
1687
 
%%      "~n   OrgVb:      ~p"
1688
 
%%      "~n   TableOids:  ~p"
1689
 
%%      "~n   Mfa:        ~p"
1690
 
%%      "~n   Res:        ~p"
1691
 
%%      "~n   TabOid:     ~p"
1692
 
%%      "~n   TabNextOid: ~p"
1693
 
%%      "~n   I:          ~p",
1694
 
%%      [Values, OrgVb, TableOids, Mfa, Res, TabOid, TabNextOid, I]),
1695
 
    NewVb = OrgVb#varbind{value = {endOfTable, TabNextOid}},
1696
 
    validate_tab_next_res(Values, TableOids, Mfa, [NewVb | Res],
1697
 
                          TabOid, TabNextOid, I);
1698
 
validate_tab_next_res([], [], _Mfa, Res, _TabOid, _TabNextOid, _I) ->
1699
 
    Res;
1700
 
validate_tab_next_res([], [{_Col, _OrgVb, Index}|_], Mfa, _Res, _, _, _I) ->
1701
 
    user_err("Too few values returned from ~w (get_next)", [Mfa]),
1702
 
    {genErr, Index};
1703
 
validate_tab_next_res({genErr, ColNumber}, OrgCols,
1704
 
                      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
1705
 
    OrgIndex = snmp_svbl:col_to_orgindex(ColNumber, OrgCols),
1706
 
    validate_err(table_next, {genErr, OrgIndex}, Mfa);
1707
 
validate_tab_next_res(Error, [{_ColNo, OrgVb, _Index} | _TableOids],
1708
 
                      Mfa, _Res, _TabOid, _TabNextOid, _I) ->
1709
 
    #varbind{org_index = OrgIndex} = OrgVb,
1710
 
    user_err("Invalid return value ~w from ~w (get_next)",
1711
 
             [Error, Mfa]),
1712
 
    {genErr, OrgIndex};
1713
 
validate_tab_next_res(TooMany, [], Mfa, _Res, _, _, I) ->
1714
 
    user_err("Too many values ~w returned from ~w (get_next)",
1715
 
             [TooMany, Mfa]),
1716
 
    {genErr, I}.
1717
 
 
1718
 
%%-----------------------------------------------------------------
1719
 
%% Func: get_next_sa/4
1720
 
%% Purpose: Loop the list of varbinds for the subagent.
1721
 
%%          Call subagent_get_next to retreive
1722
 
%%          the next varbinds.
1723
 
%% Returns: {ok, ListOfNewVbs, ListOfEndOfMibViewsVbs} |
1724
 
%%          {ErrorStatus, ErrorIndex}
1725
 
%%-----------------------------------------------------------------
1726
 
get_next_sa(SAPid, SAOid, SAVbs, MibView) ->
1727
 
    case catch subagent_get_next(SAPid, MibView, SAVbs) of
1728
 
        {noError, 0, NewVbs} ->
1729
 
            NewerVbs = transform_sa_next_result(NewVbs,SAOid,next_oid(SAOid)),
1730
 
            split_varbinds(NewerVbs, [], []);
1731
 
        {ErrorStatus, ErrorIndex, _} ->
1732
 
            {ErrorStatus, ErrorIndex};
1733
 
        {'EXIT', Reason} ->
1734
 
            user_err("Lost contact with subagent (next) ~w. Using genErr",
1735
 
                     [Reason]),
1736
 
            {genErr, 0}
1737
 
    end.
1738
 
 
1739
 
%%-----------------------------------------------------------------
1740
 
%% Check for wrong prefix returned or endOfMibView, and convert
1741
 
%% into {endOfMibView, SANextOid}.
1742
 
%%-----------------------------------------------------------------
1743
 
transform_sa_next_result([Vb | Vbs], SAOid, SANextOid)
1744
 
  when Vb#varbind.value == endOfMibView ->
1745
 
    [Vb#varbind{value = {endOfMibView, SANextOid}} |
1746
 
     transform_sa_next_result(Vbs, SAOid, SANextOid)];
1747
 
transform_sa_next_result([Vb | Vbs], SAOid, SANextOid) ->
1748
 
    case lists:prefix(SAOid, Vb#varbind.oid) of
1749
 
        true ->
1750
 
            [Vb | transform_sa_next_result(Vbs, SAOid, SANextOid)];
1751
 
        _ ->
1752
 
            [Vb#varbind{oid = SANextOid, value = {endOfMibView, SANextOid}} |
1753
 
             transform_sa_next_result(Vbs, SAOid, SANextOid)]
1754
 
    end;
1755
 
transform_sa_next_result([], _SAOid, _SANextOid) ->
1756
 
    [].
1757
 
 
1758
 
split_varbinds([Vb | Vbs], Res, EndOfs) ->
1759
 
    case Vb#varbind.value of
1760
 
        {endOfMibView, _} -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
1761
 
        {endOfTable, _} -> split_varbinds(Vbs, Res, [Vb | EndOfs]);
1762
 
        _ -> split_varbinds(Vbs, [Vb | Res], EndOfs)
1763
 
    end;
1764
 
split_varbinds([], Res, EndOfs) -> {ok, Res, EndOfs}.
1765
 
 
1766
 
next_oid(Oid) ->
1767
 
    case lists:reverse(Oid) of
1768
 
        [H | T] -> lists:reverse([H+1 | T]);
1769
 
        [] -> []
1770
 
    end.
1771
 
 
1772
 
%%%-----------------------------------------------------------------
1773
 
%%% 5. GET-BULK REQUEST
1774
 
%%%-----------------------------------------------------------------
1775
 
do_get_bulk(MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds) ->
1776
 
    ?vtrace("do get bulk: start with"
1777
 
            "~n   MibView:        ~p"
1778
 
            "~n   NonRepeaters:   ~p"
1779
 
            "~n   MaxRepetitions: ~p"
1780
 
            "~n   PduMS:          ~p"
1781
 
            "~n   Varbinds:       ~p",
1782
 
            [MibView, NonRepeaters, MaxRepetitions, PduMS, Varbinds]),
1783
 
    {NonRepVbs, RestVbs} = split_vbs(NonRepeaters, Varbinds, []),
1784
 
    case do_get_next(MibView, NonRepVbs) of
1785
 
        {noError, 0, UResNonRepVbs} -> 
1786
 
            ResNonRepVbs = lists:keysort(#varbind.org_index, UResNonRepVbs),
1787
 
            % Decode the first varbinds, produce a reversed list of
1788
 
            % listOfBytes.
1789
 
            case enc_vbs(PduMS - ?empty_pdu_size, ResNonRepVbs) of
1790
 
                {SizeLeft, Res} ->
1791
 
                    do_get_rep(SizeLeft, MibView, MaxRepetitions,
1792
 
                               RestVbs, Res);
1793
 
                Res ->
1794
 
                    {noError, 0, conv_res(Res)}
1795
 
            end;
1796
 
        {ErrorStatus, Index, _} ->
1797
 
            ?vdebug("do get bulk: "
1798
 
                    "~n   ErrorStatus: ~p"
1799
 
                    "~n   Index:       ~p",[ErrorStatus, Index]),
1800
 
            {ErrorStatus, Index, []}
1801
 
    end.
1802
 
 
1803
 
% sz(L) when list(L) -> length(L);
1804
 
% sz(B) when binary(B) -> size(B);
1805
 
% sz(_) -> unknown.
1806
 
 
1807
 
split_vbs(N, Varbinds, Res) when N =< 0 -> {Res, Varbinds};
1808
 
split_vbs(N, [H | T], Res) -> split_vbs(N-1, T, [H | Res]);
1809
 
split_vbs(_N, [], Res) -> {Res, []}.
1810
 
     
1811
 
enc_vbs(SizeLeft, Vbs) ->
1812
 
    catch lists:foldl(fun(Vb, {Sz, Res}) when Sz > 0 ->
1813
 
                              X = snmp_pdus:enc_varbind(Vb),
1814
 
                              Lx = length(X),
1815
 
                              if
1816
 
                                  Lx < Sz ->
1817
 
                                      {Sz - length(X), [X | Res]};
1818
 
                                  true ->
1819
 
                                      throw(Res)
1820
 
                              end;
1821
 
                         (_Vb, {_Sz, [_H | T]}) ->
1822
 
                              throw(T);
1823
 
                         (_Vb, {_Sz, []}) ->
1824
 
                              throw([])
1825
 
                      end,
1826
 
                      {SizeLeft, []},
1827
 
                      Vbs).
1828
 
 
1829
 
do_get_rep(Sz, MibView, MaxRepetitions, Varbinds, Res) when MaxRepetitions>=0 ->
1830
 
    do_get_rep(Sz, MibView, 0, MaxRepetitions, Varbinds, Res);
1831
 
do_get_rep(Sz, MibView, _MaxRepetitions, Varbinds, Res) ->
1832
 
    do_get_rep(Sz, MibView, 0, 0, Varbinds, Res).
1833
 
 
1834
 
conv_res(ResVarbinds) ->
1835
 
    conv_res(ResVarbinds, []).
1836
 
conv_res([VbListOfBytes | T], Bytes) ->
1837
 
    conv_res(T, VbListOfBytes ++ Bytes);
1838
 
conv_res([], Bytes) ->
1839
 
    Bytes.
1840
 
 
1841
 
do_get_rep(_Sz, _MibView, Max, Max, _, Res) ->
1842
 
    {noError, 0, conv_res(Res)};
1843
 
do_get_rep(Sz, MibView, Count, Max, Varbinds, Res) -> 
1844
 
    case try_get_bulk(Sz, MibView, Varbinds) of
1845
 
        {noError, NextVarbinds, SizeLeft, Res2} -> 
1846
 
            do_get_rep(SizeLeft, MibView, Count+1, Max, NextVarbinds,
1847
 
                       Res2 ++ Res);
1848
 
        {endOfMibView, _NextVarbinds, _SizeLeft, Res2} -> 
1849
 
            {noError, 0, conv_res(Res2 ++ Res)};
1850
 
        {ErrorStatus, Index} ->
1851
 
            {ErrorStatus, Index, []}
1852
 
    end.
1853
 
 
1854
 
try_get_bulk(Sz, MibView, Varbinds) -> 
1855
 
    case do_get_next(MibView, Varbinds) of
1856
 
        {noError, 0, UNextVarbinds} -> 
1857
 
            NextVarbinds = lists:keysort(#varbind.org_index, UNextVarbinds),
1858
 
            case enc_vbs(Sz, NextVarbinds) of
1859
 
                {SizeLeft, Res} when list(Res) ->
1860
 
                    {check_end_of_mibview(NextVarbinds),
1861
 
                     NextVarbinds, SizeLeft, Res};
1862
 
                Res when list(Res) ->
1863
 
                    {endOfMibView, [], 0, Res};
1864
 
                Else ->
1865
 
                    exit(Else)
1866
 
            end;
1867
 
        {ErrorStatus, Index, _} ->
1868
 
            {ErrorStatus, Index}
1869
 
    end.
1870
 
 
1871
 
%% If all variables in this pass are endOfMibView,
1872
 
%% there is no reason to continue.
1873
 
check_end_of_mibview([#varbind{value = endOfMibView} | T]) ->
1874
 
    check_end_of_mibview(T);
1875
 
check_end_of_mibview([]) -> endOfMibView;
1876
 
check_end_of_mibview(_) -> noError.
1877
 
 
1878
 
 
1879
 
%%%--------------------------------------------------
1880
 
%%% 6. SET REQUEST
1881
 
%%%--------------------------------------------------
1882
 
%% return:  {ErrStatus, ErrIndex}
1883
 
%% where ErrIndex is an index in Varbinds list (not org_index (user-functions
1884
 
%% doesn't see org_index)).
1885
 
do_set(MibView, UnsortedVarbinds) ->
1886
 
    SetModule = get(set_module),
1887
 
    ?vtrace("set module: ~p",[SetModule]),
1888
 
    apply(SetModule, do_set, [MibView, UnsortedVarbinds]).
1889
 
 
1890
 
do_subagent_set(Arguments) ->
1891
 
    SetModule = get(set_module),
1892
 
    apply(SetModule, do_subagent_set, [Arguments]).
1893
 
 
1894
 
%%%-----------------------------------------------------------------
1895
 
%%% 7. Misc functions
1896
 
%%%-----------------------------------------------------------------
1897
 
sort_varbindlist(Varbinds) ->
1898
 
    snmp_svbl:sort_varbindlist(get(mibserver), Varbinds).
1899
 
 
1900
 
sa_split(SubagentVarbinds) ->
1901
 
    snmp_svbl:sa_split(SubagentVarbinds).
1902
 
 
1903
 
make_response_pdu(ReqId, ErrStatus, ErrIndex, OrgVarbinds, _ResponseVarbinds)
1904
 
  when ErrIndex /= 0 ->
1905
 
    #pdu{type = 'get-response', request_id = ReqId, error_status = ErrStatus,
1906
 
         error_index = ErrIndex, varbinds = OrgVarbinds};
1907
 
make_response_pdu(ReqId, ErrStatus, ErrIndex, _OrgVarbinds, ResponseVarbinds) ->
1908
 
    #pdu{type = 'get-response', request_id = ReqId, error_status = ErrStatus,
1909
 
         error_index = ErrIndex, varbinds = ResponseVarbinds}.
1910
 
 
1911
 
%% Valid errormsgs for different operations.
1912
 
validate_err(consistency_check, {'EXIT', _Reason}, _) ->
1913
 
    {genErr, 0};
1914
 
validate_err(consistency_check, X, _) ->
1915
 
    X;
1916
 
 
1917
 
validate_err(is_set_ok, noError, _) -> noError;
1918
 
validate_err(is_set_ok, noCreation, _) -> noCreation;
1919
 
validate_err(is_set_ok, inconsistentValue, _) -> inconsistentValue;
1920
 
validate_err(is_set_ok, resourceUnavailable, _) -> resourceUnavailable;
1921
 
validate_err(is_set_ok, inconsistentName, _) -> inconsistentName;
1922
 
validate_err(is_set_ok, badValue, _) -> badValue;
1923
 
validate_err(is_set_ok, wrongValue, _) -> wrongValue;
1924
 
validate_err(is_set_ok, noSuchName, _) -> noSuchName;
1925
 
validate_err(is_set_ok, noAccess, _) -> noAccess;
1926
 
validate_err(is_set_ok, notWritable, _) -> notWritable;
1927
 
validate_err(is_set_ok, genErr, _) -> genErr;
1928
 
validate_err(is_set_ok, X, Mfa) -> 
1929
 
    user_err("~w with is_set_ok, returned: ~w. Using genErr.",
1930
 
             [Mfa, X]),
1931
 
    genErr;
1932
 
 
1933
 
validate_err(set, commitFailed, _) -> commitFailed;
1934
 
validate_err(set, undoFailed, _) -> undoFailed;
1935
 
validate_err(set, noError, _) -> noError;
1936
 
validate_err(set, genErr, _) -> genErr;
1937
 
validate_err(set, X, Mfa) -> 
1938
 
    user_err("~w with set, returned: ~w. Using genErr.",
1939
 
             [Mfa, X]),
1940
 
    genErr;
1941
 
 
1942
 
validate_err(undo, undoFailed, _) -> undoFailed;
1943
 
validate_err(undo, noError, _) -> noError;
1944
 
validate_err(undo, genErr, _) -> genErr;
1945
 
validate_err(undo, X, Mfa) -> 
1946
 
    user_err("~w with undo, returned: ~w. Using genErr.",
1947
 
             [Mfa, X]),
1948
 
    genErr;
1949
 
 
1950
 
validate_err(table_is_set_ok, {Err, Idx}, Mfa) when integer(Idx) ->
1951
 
    {validate_err(is_set_ok, Err, Mfa), Idx};
1952
 
validate_err(table_is_set_ok, X, Mfa) ->
1953
 
    user_err("~w with is_set_ok (table), returned: ~w. Using genErr.",
1954
 
             [Mfa, X]),
1955
 
    {genErr, 0};
1956
 
 
1957
 
validate_err(row_is_set_ok, {Err, Idx}, _) when integer(Idx) ->
1958
 
    {Err, Idx};
1959
 
validate_err(row_is_set_ok, {_Err, {false, BadCol}}, Mfa) ->
1960
 
    user_err("~w with is_set_ok (table), returned bad column: "
1961
 
             "~w. Using genErr.", [Mfa, BadCol]),
1962
 
    {genErr, 0};
1963
 
 
1964
 
validate_err(table_undo, {Err, Idx}, Mfa) when integer(Idx) ->
1965
 
    {validate_err(undo, Err, Mfa), Idx};
1966
 
validate_err(table_undo, X, Mfa) ->
1967
 
    user_err("~w with undo (table), returned: ~w. Using genErr.",
1968
 
             [Mfa, X]),
1969
 
    {genErr, 0};
1970
 
 
1971
 
validate_err(row_undo, {Err, Idx}, _) when integer(Idx) ->
1972
 
    {Err, Idx};
1973
 
validate_err(row_undo, {_Err, {false, BadCol}}, Mfa) ->
1974
 
    user_err("~w with undo (table), returned bad column: "
1975
 
             "~w. Using genErr.", [Mfa, BadCol]),
1976
 
    {genErr, 0};
1977
 
 
1978
 
validate_err(table_set, {Err, Idx}, Mfa) when integer(Idx) ->
1979
 
    {validate_err(set, Err, Mfa), Idx};
1980
 
validate_err(table_set, X, Mfa) ->
1981
 
    user_err("~w with set (table), returned: ~w. Using genErr.",
1982
 
             [Mfa, X]),
1983
 
    {genErr, 0};
1984
 
 
1985
 
validate_err(row_set, {Err, Idx}, _) when integer(Idx) ->
1986
 
    {Err, Idx};
1987
 
validate_err(row_set, {_Err, {false, BadCol}}, Mfa) ->
1988
 
    user_err("~w with set (table), returned bad column: "
1989
 
             "~w. Using genErr.", [Mfa, BadCol]),
1990
 
    {genErr, 0};
1991
 
 
1992
 
validate_err(table_next, {Err, Idx}, _Mfa) when integer(Idx) ->
1993
 
    {Err, Idx};
1994
 
validate_err(table_next, {_Err, {false, BadCol}}, Mfa) ->
1995
 
    user_err("~w with get_next, returned bad column: "
1996
 
             "~w. Using genErr.", [Mfa, BadCol]),
1997
 
    {genErr, 0}.
1998
 
 
1999
 
validate_err(v2_to_v1, {V2Err, Index}) ->
2000
 
    {v2err_to_v1err(V2Err), Index};
2001
 
validate_err(v2_to_v1, _) ->
2002
 
    {genErr, 0}.
2003
 
 
2004
 
get_err({ErrC, ErrI, Vbs}) ->
2005
 
    {get_err_i(ErrC), ErrI, Vbs}.
2006
 
 
2007
 
get_err_i(noError) -> noError;
2008
 
get_err_i(S) -> 
2009
 
    ?vtrace("convert '~p' to 'genErr'",[S]),
2010
 
    genErr.
2011
 
 
2012
 
v2err_to_v1err(noError) ->            noError;
2013
 
v2err_to_v1err(noAccess) ->           noSuchName;
2014
 
v2err_to_v1err(noCreation) ->         noSuchName;
2015
 
v2err_to_v1err(notWritable) ->        noSuchName;
2016
 
v2err_to_v1err(wrongLength) ->        badValue;
2017
 
v2err_to_v1err(wrongEncoding) ->      badValue;
2018
 
v2err_to_v1err(wrongType) ->          badValue;
2019
 
v2err_to_v1err(wrongValue) ->         badValue;
2020
 
v2err_to_v1err(inconsistentValue) ->  badValue;
2021
 
v2err_to_v1err(inconsistentName) ->   noSuchName;
2022
 
v2err_to_v1err(noSuchName) ->         noSuchName;
2023
 
v2err_to_v1err(badValue) ->           badValue;
2024
 
v2err_to_v1err(authorizationError) -> noSuchName;
2025
 
%% genErr | resourceUnavailable | undoFailed | commitFailed -> genErr
2026
 
v2err_to_v1err(_Error) ->             genErr.
2027
 
 
2028
 
%%-----------------------------------------------------------------
2029
 
%% transforms a (hopefully correct) return value ((perhaps) from a 
2030
 
%% mib-function) to a typed and guaranteed correct return value.
2031
 
%% An incorrect return value is transformed to {error, genErr}.
2032
 
%% A correct return value is on the form: 
2033
 
%% {error, <error-msg>} | {value, <variable-type>, <value>}
2034
 
%%-----------------------------------------------------------------
2035
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2036
 
  when Asn1#asn1_type.bertype == 'INTEGER' ->
2037
 
    check_integer(Val, Asn1, Mfa);
2038
 
 
2039
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2040
 
  when Asn1#asn1_type.bertype == 'Counter32' ->
2041
 
    check_integer(Val, Asn1, Mfa);
2042
 
 
2043
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2044
 
  when Asn1#asn1_type.bertype == 'Unsigned32' ->
2045
 
    check_integer(Val, Asn1, Mfa);
2046
 
 
2047
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2048
 
  when Asn1#asn1_type.bertype == 'TimeTicks' ->
2049
 
    check_integer(Val, Asn1, Mfa);
2050
 
 
2051
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2052
 
  when Asn1#asn1_type.bertype == 'Counter64' ->
2053
 
    check_integer(Val, Asn1, Mfa);
2054
 
 
2055
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2056
 
  when Asn1#asn1_type.bertype == 'BITS', list(Val) ->
2057
 
    {value,Kibbles} = snmp_misc:assq(kibbles,Asn1#asn1_type.assocList),
2058
 
    case snmp_misc:bits_to_int(Val,Kibbles) of
2059
 
        error ->
2060
 
            report_err(Val, Mfa, wrongValue);
2061
 
        Int ->
2062
 
            make_value_a_correct_value({value,Int},Asn1,Mfa)
2063
 
    end;
2064
 
 
2065
 
make_value_a_correct_value({value, Val}, Asn1, Mfa)
2066
 
  when Asn1#asn1_type.bertype == 'BITS', integer(Val) ->
2067
 
    {value,Kibbles} = snmp_misc:assq(kibbles,Asn1#asn1_type.assocList),
2068
 
    {_Kibble,BitNo} = lists:last(Kibbles),
2069
 
    case round(math:pow(2,BitNo+1)) of
2070
 
        X when Val < X ->
2071
 
            {value,'BITS',Val};
2072
 
        _Big ->
2073
 
            report_err(Val,Mfa,wrongValue)
2074
 
    end;
2075
 
 
2076
 
make_value_a_correct_value({value, String},
2077
 
                           #asn1_type{bertype = 'OCTET STRING',
2078
 
                                      hi = Hi, lo = Lo}, Mfa) ->
2079
 
    check_octet_string(String, Hi, Lo, Mfa, 'OCTET STRING');
2080
 
 
2081
 
make_value_a_correct_value({value, String},
2082
 
                           #asn1_type{bertype = 'IpAddress',
2083
 
                                      hi = Hi, lo = Lo}, Mfa) ->
2084
 
    check_octet_string(String, Hi, Lo, Mfa, 'IpAddress');
2085
 
 
2086
 
make_value_a_correct_value({value, Oid},
2087
 
                           #asn1_type{bertype = 'OBJECT IDENTIFIER'},
2088
 
                           _Mfa) ->
2089
 
    case snmp_misc:is_oid(Oid) of
2090
 
        true  -> {value, 'OBJECT IDENTIFIER', Oid};
2091
 
        _Else -> {error, wrongType}
2092
 
    end;
2093
 
 
2094
 
make_value_a_correct_value({value, Val}, Asn1, _Mfa)
2095
 
  when Asn1#asn1_type.bertype == 'Opaque' ->
2096
 
    if list(Val) -> {value, 'Opaque', Val};
2097
 
       true -> {error, wrongType}
2098
 
    end;
2099
 
 
2100
 
make_value_a_correct_value({noValue, noSuchObject}, _ASN1Type, _Mfa) ->
2101
 
    {value, noValue, noSuchObject};
2102
 
make_value_a_correct_value({noValue, noSuchInstance}, _ASN1Type, _Mfa) ->
2103
 
    {value, noValue, noSuchInstance};
2104
 
make_value_a_correct_value({noValue, noSuchName}, _ASN1Type, _Mfa) ->
2105
 
    %% Transform this into a v2 value.  It is converted to noSuchName
2106
 
    %% later if it was v1.  If it was v2, we use noSuchInstance.
2107
 
    {value, noValue, noSuchInstance};
2108
 
%% For backwards compatibility only - we really shouldn't allow this;
2109
 
%% it makes no sense to return unSpecified for a variable! But we did
2110
 
%% allow it previously. -- We transform unSpecified to noSuchInstance
2111
 
%% (OTP-3303).
2112
 
make_value_a_correct_value({noValue, unSpecified}, _ASN1Type, _Mfa) ->
2113
 
    {value, noValue, noSuchInstance};
2114
 
make_value_a_correct_value(genErr, _ASN1Type, _MFA) ->
2115
 
    {error, genErr};
2116
 
 
2117
 
make_value_a_correct_value(_WrongVal, _ASN1Type, undef) ->
2118
 
    {error, genErr};
2119
 
 
2120
 
make_value_a_correct_value(WrongVal, ASN1Type, Mfa) ->
2121
 
    user_err("Got ~w from ~w. (~w) Using genErr",
2122
 
             [WrongVal, Mfa, ASN1Type]),
2123
 
    {error, genErr}.
2124
 
 
2125
 
check_integer(Val, Asn1, Mfa) ->
2126
 
    case Asn1#asn1_type.assocList of
2127
 
        undefined -> check_size(Val, Asn1, Mfa);
2128
 
        Alist ->
2129
 
            case snmp_misc:assq(enums, Alist) of
2130
 
                {value, Enums} -> check_enums(Val, Asn1, Enums, Mfa);
2131
 
                false -> check_size(Val, Asn1, Mfa)
2132
 
            end
2133
 
    end.
2134
 
 
2135
 
check_octet_string(String, Hi, Lo, Mfa, Type) ->
2136
 
    Len = (catch length(String)), % it might not be a list
2137
 
    case snmp_misc:is_string(String) of
2138
 
        true when Lo == undefined -> {value, Type, String};
2139
 
        true when Len =< Hi, Len >= Lo ->
2140
 
            {value, Type, String};
2141
 
        true ->
2142
 
            report_err(String, Mfa, wrongLength);
2143
 
        _Else ->
2144
 
            report_err(String, Mfa, wrongType)
2145
 
    end.
2146
 
 
2147
 
check_size(Val, #asn1_type{lo = Lo, hi = Hi, bertype = Type}, Mfa) 
2148
 
  when integer(Val) ->
2149
 
    ?vtrace("check size of integer: "
2150
 
            "~n   Value:       ~p"
2151
 
            "~n   Upper limit: ~p"
2152
 
            "~n   Lower limit: ~p"
2153
 
            "~n   BER-type:    ~p",
2154
 
            [Val,Hi,Lo,Type]),
2155
 
    if
2156
 
        Lo == undefined, Hi == undefined -> {value, Type, Val};
2157
 
        Lo == undefined, integer(Hi), Val =< Hi ->
2158
 
            {value, Type, Val};
2159
 
        integer(Lo), Val >= Lo, Hi == undefined ->
2160
 
            {value, Type, Val};
2161
 
        integer(Lo), integer(Hi), Val >= Lo, Val =< Hi ->
2162
 
            {value, Type, Val};
2163
 
        true ->
2164
 
            report_err(Val, Mfa, wrongValue)
2165
 
    end;
2166
 
check_size(Val, _, Mfa) ->
2167
 
    report_err(Val, Mfa, wrongType).
2168
 
 
2169
 
check_enums(Val, Asn1, Enums, Mfa) ->
2170
 
    Association = 
2171
 
        if
2172
 
            integer(Val) -> lists:keysearch(Val, 2, Enums);
2173
 
            atom(Val)    -> lists:keysearch(Val, 1, Enums);
2174
 
            true         -> {error, wrongType}
2175
 
    end,
2176
 
    case Association of
2177
 
        {value, {_AliasIntName, Val2}} -> 
2178
 
            {value, Asn1#asn1_type.bertype, Val2};
2179
 
        false ->
2180
 
            report_err(Val, Mfa, wrongValue);
2181
 
        {error, wrongType} ->
2182
 
            report_err(Val, Mfa, wrongType)
2183
 
    end.
2184
 
 
2185
 
report_err(_Val, undef, Err) ->
2186
 
    {error, Err};
2187
 
report_err(Val, Mfa, Err) ->
2188
 
    user_err("Got ~p from ~w. Using ~w", [Val, Mfa, Err]),
2189
 
    {error, Err}.
2190
 
 
2191
 
get_option(Key, Options, Default) ->
2192
 
    case lists:keysearch(Key, 1, Options) of
2193
 
        {value, {_Key, Value}} -> Value;
2194
 
        _ -> Default
2195
 
    end.
2196
 
 
2197
 
valid_pdu_type('get-request') -> true;
2198
 
valid_pdu_type('get-next-request') -> true;
2199
 
valid_pdu_type('get-bulk-request') -> true;
2200
 
valid_pdu_type('set-request') -> true;
2201
 
valid_pdu_type(_) -> false.
2202
 
 
2203
 
get_pdu_data() ->
2204
 
    {get(snmp_net_if_data), get(snmp_request_id),
2205
 
     get(snmp_address), get(snmp_community), get(snmp_context)}.
2206
 
 
2207
 
put_pdu_data({Extra, ReqId, Address, Community, ContextName}) -> 
2208
 
    put(snmp_net_if_data, Extra),
2209
 
    put(snmp_address, Address),
2210
 
    put(snmp_request_id, ReqId),
2211
 
    put(snmp_community, Community),
2212
 
    put(snmp_context, ContextName).
2213
 
 
2214
 
tr_var(Oid, Idx) ->
2215
 
    case snmp_misc:is_oid(Oid) of
2216
 
        true ->
2217
 
            {#varbind{oid = Oid, value = unSpecified, org_index = Idx},
2218
 
             Idx+1};
2219
 
        false -> throw({error, {bad_oid, Oid}})
2220
 
    end.
2221
 
 
2222
 
tr_varbind(#varbind{value = Value}) -> Value.
2223
 
 
2224
 
mapfoldl(F, Eas, Accu0, [Hd|Tail]) ->
2225
 
    {R,Accu1} = apply(F, [Hd,Accu0|Eas]),
2226
 
    {Accu2,Rs} = mapfoldl(F, Eas, Accu1, Tail),
2227
 
    {Accu2,[R|Rs]};
2228
 
mapfoldl(_F, _Eas, Accu, []) -> {Accu,[]}.
2229
 
 
2230
 
%%-----------------------------------------------------------------
2231
 
%% Runtime debugging of the agent.
2232
 
%%-----------------------------------------------------------------
2233
 
 
2234
 
dbg_apply(M,F,A) ->
2235
 
    case get(verbosity) of
2236
 
        silence -> apply(M,F,A);
2237
 
        _ ->
2238
 
            ?vlog("~n   apply: ~w,~w,~p~n", [M,F,A]),
2239
 
            Res = (catch apply(M,F,A)),
2240
 
            ?vlog("~n   returned: ~p", [Res]),
2241
 
            Res
2242
 
    end.
2243
 
 
2244
 
 
2245
 
short_name(none) -> ma;
2246
 
short_name(_Pid) -> sa.
2247
 
 
2248
 
worker_short_name(ma) -> maw;
2249
 
worker_short_name(_)  -> saw.
2250
 
 
2251
 
trap_sender_short_name(ma) -> mats;
2252
 
trap_sender_short_name(_)  -> sats.
2253
 
 
2254
 
pdu_handler_short_name(ma) -> maph;
2255
 
pdu_handler_short_name(_)  -> saph.
2256
 
 
2257
 
get_verbosity(_,[]) ->
2258
 
    ?default_verbosity;
2259
 
get_verbosity(none,L) ->
2260
 
    snmp_misc:get_option(master_agent_verbosity,L,?default_verbosity);
2261
 
get_verbosity(_,L) ->
2262
 
    snmp_misc:get_option(subagent_verbosity,L,?default_verbosity).
2263
 
 
2264
 
 
2265
 
net_if_verbosity(Pid,Verbosity) when pid(Pid) ->
2266
 
    Pid ! {verbosity,Verbosity};
2267
 
net_if_verbosity(_Pid,_Verbosity) ->
2268
 
    ok.
2269
 
 
2270
 
 
2271
 
mib_verbosity(Pid,Verbosity) when pid(Pid) ->
2272
 
    snmp_mib:verbosity(Pid,Verbosity);
2273
 
mib_verbosity(_Pid,_Verbosity) ->
2274
 
    ok.
2275
 
 
2276
 
d2v(true) -> log;
2277
 
d2v(_)    -> silence.
2278
 
 
2279
 
 
2280
 
subagents_verbosity(V) ->
2281
 
    subagents_verbosity(catch snmp_mib:info(get(mibserver),subagents),V).
2282
 
 
2283
 
subagents_verbosity([],_V) ->
2284
 
    ok;
2285
 
subagents_verbosity([{Pid,_Oid}|T],V) ->
2286
 
    catch snmp_agent:verbosity(Pid,V),             %% On the agent
2287
 
    catch snmp_agent:verbosity(Pid,{subagents,V}), %% and it's subagents
2288
 
    subagents_verbosity(T,V);
2289
 
subagents_verbosity(_,_V) ->
2290
 
    ok.
2291
 
 
2292
 
 
2293
 
user_err(F, A) ->
2294
 
    snmp_error_report:user_err(F, A).