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

« back to all changes in this revision

Viewing changes to lib/snmp/src/snmp_svbl.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_svbl).
19
 
 
20
 
-include("snmp_types.hrl").
21
 
 
22
 
-export([sort_varbindlist/2, sort_varbinds_rows/1, sa_split/1,
23
 
         delete_org_index/1, col_to_orgindex/2]).
24
 
 
25
 
%%-----------------------------------------------------------------
26
 
%% Func: sort_varbindlist/2
27
 
%% Args: Varbinds is a list of #varbind
28
 
%% Purpose: Group all variablebindings that corresponds to logically
29
 
%%          the same entity, i.e. group all plain variables, all
30
 
%%          table operations for each table, all varbinds to each
31
 
%%          subagent.
32
 
%% Returns: {VarbindsForThisAgent
33
 
%%           VarbindsForSubAgents}   where
34
 
%%             VarbindsForThisAgent  = List of {TableOid, List of #ivarbinds} |
35
 
%%                                              #ivarbinds
36
 
%%             VarbindsForSubAgents = List of {SubAgentPid,
37
 
%%                                             List of {SAOid, #varbinds}}
38
 
%%-----------------------------------------------------------------
39
 
sort_varbindlist(Mib, Varbinds) ->
40
 
    {Vars, Tabs, Subagents} = partition(Mib, Varbinds),
41
 
    {lists:append(Tabs, Vars), Subagents}.
42
 
 
43
 
partition(Mib, Vbs) ->
44
 
    partition(Mib, Vbs, [], [], []).
45
 
partition(Mib, [Varbind | Vbs], Vars, Tabs, Subs) ->
46
 
    #varbind{oid = Oid} = Varbind,
47
 
    case snmp_mib:lookup(Mib, Oid) of
48
 
        {table_column, MibEntry, TableOid} ->
49
 
            IVarbind = #ivarbind{varbind = fix_bits(Varbind, MibEntry),
50
 
                                 mibentry = MibEntry},
51
 
            NewTabs = insert_key(TableOid, IVarbind, Tabs),
52
 
            partition(Mib, Vbs, Vars, NewTabs, Subs);
53
 
        {subagent, SubagentPid, SAOid} ->
54
 
            NewSubs = insert_key(SubagentPid, {SAOid, Varbind}, Subs),
55
 
            partition(Mib, Vbs, Vars, Tabs, NewSubs);
56
 
        {variable, MibEntry} ->
57
 
            IVarbind = #ivarbind{varbind = fix_bits(Varbind, MibEntry),
58
 
                                 mibentry = MibEntry},
59
 
            partition(Mib, Vbs, [IVarbind | Vars], Tabs, Subs);
60
 
        {false, ErrorCode} -> % ErrorCode = noSuchObject | noSuchInstance
61
 
            IVarbind = #ivarbind{status = ErrorCode, varbind = Varbind},
62
 
            partition(Mib, Vbs, [IVarbind | Vars], Tabs, Subs)
63
 
    end;
64
 
partition(_Mib, [], Vars, Subs, Tabs) ->
65
 
    {Vars, Subs, Tabs}.
66
 
 
67
 
fix_bits(VarBind, #me{asn1_type=A})
68
 
  when A#asn1_type.bertype == 'BITS',
69
 
       VarBind#varbind.variabletype == 'OCTET STRING',
70
 
       list(VarBind#varbind.value) ->
71
 
    VarBind#varbind{variabletype = 'BITS',
72
 
                    value = snmp_pdus:octet_str_to_bits(VarBind#varbind.value)};
73
 
fix_bits(Vb,_me) -> Vb.
74
 
 
75
 
insert_key(Key, Value, [{Key, Values} | Rest]) ->
76
 
    [{Key, [Value | Values]} | Rest];
77
 
insert_key(Key, Value, [{KeyX, Values} | Rest]) ->
78
 
    [{KeyX, Values} | insert_key(Key, Value, Rest)];
79
 
insert_key(Key, Value, []) ->
80
 
    [{Key, [Value]}].
81
 
 
82
 
%%-----------------------------------------------------------------
83
 
%% Tranforms a list of {Oid, Vb} to a 2-tuple with all
84
 
%% Oids and all Vbs. These lists will be reversed.
85
 
%%-----------------------------------------------------------------
86
 
sa_split(Vbs) -> sa_split(Vbs, [], []).
87
 
sa_split([{SAOid, Vb} | T], Oids, Vbs) ->
88
 
    sa_split(T, [SAOid | Oids], [Vb | Vbs]);
89
 
sa_split([], Oids, Vbs) ->
90
 
    {Oids, Vbs}.
91
 
 
92
 
%%-----------------------------------------------------------------
93
 
%% Func: sort_varbinds_rows/1
94
 
%% Args: Varbinds is a list of {Oid, Value}.
95
 
%% Pre: Varbinds is for one table.
96
 
%% Purpose: Sorts all varbinds in Oid order, and in row order.
97
 
%% Returns: list of Row where
98
 
%%          Row = {Indexes, List of Col} and
99
 
%%          Col = {ColNo, Value, OrgIndex} and
100
 
%%          OrgIndex is index in original varbind list.
101
 
%%-----------------------------------------------------------------
102
 
sort_varbinds_rows(Varbinds) ->
103
 
    P = pack(Varbinds),
104
 
    S = lists:keysort(1, P),
105
 
    unpack(S).
106
 
 
107
 
%% In: list of {Oid, Value}
108
 
%% Out: list of {{Indexes_for_row, Col}, Val, Index}
109
 
pack(V) -> pack(1, V).
110
 
pack(Index, [{[Col | Rest], Val} | T]) -> 
111
 
    [{{Rest, Col}, Val, Index} | pack(Index+1, T)];
112
 
pack(_, []) -> [].
113
 
 
114
 
unpack([{{Rest, Col}, Val, Index} | T]) ->
115
 
    unpack(Rest, [[{Col, Val, Index}]], T);
116
 
unpack([]) -> [].
117
 
 
118
 
unpack(Rest, [Row | Rows], [{{Rest, Col}, Val, Index} | T]) ->
119
 
    unpack(Rest, [[{Col, Val, Index} | Row] | Rows], T);
120
 
unpack(Rest, [Row | Rows], [{{Rest2, Col}, Val, Index} | T]) ->
121
 
    unpack(Rest2, [[{Col, Val, Index}], 
122
 
                   {Rest, lists:reverse(Row)} | Rows], T);
123
 
unpack(Rest, [Row | Rows], []) ->
124
 
    NewRow = {Rest, lists:reverse(Row)},
125
 
    lists:reverse([NewRow | Rows]).
126
 
 
127
 
%% OrgIndex should not be present when we call the is_set_ok/set/undo
128
 
%% table functions. They just see the list of cols, and if an error
129
 
%% occurs, they return the column nunber.
130
 
%% Also, delete duplicate columns.  If a SET is performed with duplicate
131
 
%% columns, it is undefined which column to use.  We just pick one.
132
 
delete_org_index([{RowIndex, Cols} | Rows]) ->
133
 
    [{RowIndex, doi(Cols)} | delete_org_index(Rows)];
134
 
delete_org_index([]) -> [].
135
 
 
136
 
doi([{Col, Val, OrgIndex}, {Col, _Val, _OrgIndex} | T]) ->
137
 
    doi([{Col, Val, OrgIndex} | T]);
138
 
doi([{Col, Val, _OrgIndex} | T]) ->
139
 
    [{Col, Val} | doi(T)];
140
 
doi([]) -> [].
141
 
 
142
 
%% Maps the column number to OrgIndex.
143
 
col_to_orgindex(0, _) -> 0;
144
 
col_to_orgindex(Col, [{Col, _Val, OrgIndex}|_]) ->
145
 
    OrgIndex;
146
 
col_to_orgindex(Col, [_|Cols]) ->
147
 
    col_to_orgindex(Col, Cols);
148
 
col_to_orgindex(BadCol, _) ->
149
 
    {false, BadCol}.