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

« back to all changes in this revision

Viewing changes to lib/snmp/src/agent/snmp_index.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_index).
 
19
 
 
20
-export([new/1 ,new/2, insert/3, delete/2, delete/1, get/2, get_next/2,
 
21
         get_last/1, key_to_oid/2]).
 
22
 
 
23
%%%-----------------------------------------------------------------
 
24
%%% This module implements an SNMP index structure as an ADT.
 
25
%%% It is supposed to be used as a separate structure which implements
 
26
%%% the SNMP ordering of the keys in the SNMP table.  The advantage
 
27
%%% with this is that the get-next operation is automatically
 
28
%%% taken care of.
 
29
%%%-----------------------------------------------------------------
 
30
 
 
31
%%-----------------------------------------------------------------
 
32
%% Args: KeyTypes = key() | {key(), ...}
 
33
%%       key() = integer | string | fix_string
 
34
%% Returns: handle()
 
35
%%-----------------------------------------------------------------
 
36
 
 
37
new(KeyTypes) ->
 
38
    new(KeyTypes,[]).
 
39
 
 
40
new(KeyTypes, Name) ->
 
41
    case is_snmp_type(to_list(KeyTypes)) of
 
42
        true ->
 
43
            {EtsName,EtsOpts} = case Name of
 
44
                                    N when atom(N) ->
 
45
                                        {N,[public,
 
46
                                            ordered_set,
 
47
                                            named_table]};
 
48
                                    [] ->
 
49
                                        {snmp_index, [public,
 
50
                                                     ordered_set]};
 
51
                                    _ ->
 
52
                                        exit({badarg, 
 
53
                                              {?MODULE, new, [KeyTypes,Name]}})
 
54
                                end,
 
55
            {ets:new(EtsName,EtsOpts), KeyTypes};
 
56
        false ->
 
57
            exit({badarg, {?MODULE, new, [KeyTypes,Name]}})
 
58
    end.
 
59
 
 
60
get({OrdSet, _KeyTypes}, KeyOid) ->
 
61
    case ets:lookup(OrdSet, KeyOid) of
 
62
        [X] ->
 
63
            {ok,X};
 
64
        _ ->
 
65
            undefined
 
66
    end.
 
67
 
 
68
get_next({OrdSet, KeyTypes}, KeyOid) ->
 
69
    case ets:next(OrdSet, KeyOid) of
 
70
        '$end_of_table' ->
 
71
            undefined;
 
72
        Key ->
 
73
            get({OrdSet, KeyTypes}, Key)
 
74
    end.
 
75
 
 
76
get_last({OrdSet, KeyTypes}) ->
 
77
    case ets:last(OrdSet) of
 
78
        '$end_of_table' ->
 
79
            undefined;
 
80
        Key ->
 
81
            get({OrdSet, KeyTypes}, Key)
 
82
    end.
 
83
 
 
84
insert({OrdSet, KeyTypes}, Key, Val) ->
 
85
    ets:insert(OrdSet, {key_to_oid_i(Key, KeyTypes), Val}),
 
86
    {OrdSet, KeyTypes}.
 
87
 
 
88
delete({OrdSet, KeyTypes}, Key) ->
 
89
    ets:delete(OrdSet, key_to_oid_i(Key, KeyTypes)),
 
90
    {OrdSet, KeyTypes}.
 
91
 
 
92
delete({OrdSet, _KeyTypes}) ->
 
93
    ets:delete(OrdSet).
 
94
 
 
95
key_to_oid({_OrdSet, KeyTypes}, Key) ->
 
96
    key_to_oid_i(Key, KeyTypes).
 
97
 
 
98
to_list(Tuple) when tuple(Tuple) -> tuple_to_list(Tuple);
 
99
to_list(X) -> [X].
 
100
 
 
101
is_snmp_type([integer | T]) -> is_snmp_type(T);
 
102
is_snmp_type([string | T]) -> is_snmp_type(T);
 
103
is_snmp_type([fix_string | T]) -> is_snmp_type(T);
 
104
is_snmp_type([]) -> true;
 
105
is_snmp_type(_) -> false.
 
106
 
 
107
%%-----------------------------------------------------------------
 
108
%% Args: Key = key()
 
109
%%       key() = int() | string() | {int() | string(), ...}
 
110
%%       Type = {fix_string | term()}
 
111
%% Make an OBJECT IDENTIFIER out of it.
 
112
%% Variable length objects are prepended by their length.
 
113
%% Ex. Key = {"pelle", 42} AND Type = {string, integer} =>
 
114
%%        OID [5, $p, $e, $l, $l, $e, 42]
 
115
%%     Key = {"pelle", 42} AND Type = {fix_string, integer} =>
 
116
%%        OID [$p, $e, $l, $l, $e, 42]
 
117
%%-----------------------------------------------------------------
 
118
key_to_oid_i(Key, _Type) when integer(Key) -> [Key];
 
119
key_to_oid_i(Key, fix_string) -> Key;
 
120
key_to_oid_i(Key, _Type) when list(Key) -> [length(Key) | Key];
 
121
key_to_oid_i(Key, Types) -> keys_to_oid(size(Key), Key, [], Types).
 
122
 
 
123
keys_to_oid(0, _Key, Oid, _Types) -> Oid;
 
124
keys_to_oid(N, Key, Oid, Types) ->
 
125
    Oid2 = lists:append(key_to_oid_i(element(N, Key), element(N, Types)), Oid),
 
126
    keys_to_oid(N-1, Key, Oid2, Types).