~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/snmp/doc/src/snmp_generic.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1996</year><year>2009</year>
 
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
 
9
    </copyright>
 
10
    <legalnotice>
 
11
      The contents of this file are subject to the Erlang Public License,
 
12
      Version 1.1, (the "License"); you may not use this file except in
 
13
      compliance with the License. You should have received a copy of the
 
14
      Erlang Public License along with this software. If not, it can be
 
15
      retrieved online at http://www.erlang.org/.
 
16
    
 
17
      Software distributed under the License is distributed on an "AS IS"
 
18
      basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
19
      the License for the specific language governing rights and limitations
 
20
      under the License.
 
21
    
 
22
    </legalnotice>
 
23
 
 
24
    <title>snmp_generic</title>
 
25
    <prepared></prepared>
 
26
    <responsible></responsible>
 
27
    <docno></docno>
 
28
    <approved></approved>
 
29
    <checked></checked>
 
30
    <date></date>
 
31
    <rev></rev>
 
32
    <file>snmp_generic.xml</file>
 
33
  </header>
 
34
  <module>snmp_generic</module>
 
35
  <modulesummary>Generic Functions for Implementing SNMP Objects in a Database</modulesummary>
 
36
  <description>
 
37
    <p>The module <c>snmp_generic</c> contains generic functions for implementing tables
 
38
      (and variables) using the SNMP built-in database or Mnesia. These
 
39
      default functions are used if no instrumentation function is
 
40
      provided for a managed object in a MIB. Sometimes, it might be
 
41
      necessary to customize the behaviour of the default functions. For
 
42
      example, in some situations a trap should be sent if a row is
 
43
      deleted or modified, or some hardware is to be informed, when
 
44
      information is changed.
 
45
      </p>
 
46
    <p>The overall structure is shown in the following figure:</p>
 
47
    <pre>
 
48
         +---------------+
 
49
         |   SNMP Agent  |
 
50
         +- - - - - - - -+
 
51
         |      MIB      |
 
52
         +---------------+
 
53
                 |
 
54
         Association file       (associates a MIB object with
 
55
                 |               snmp_generic:table_funct
 
56
                 |               snmp_generic:variable_func)
 
57
+--------------------------------------+
 
58
|           snmp_generic               |  Support for get-next,
 
59
|                                      |  RowStatus operations
 
60
+----------------------+---------------+
 
61
|    snmpa_local_db    |    Mnesia     |  Database
 
62
+--------------+-------+---------------+
 
63
|     dets     |  ets  | 
 
64
| (persistent) |       | 
 
65
+--------------+-------+     </pre>
 
66
    <p>Each function takes the argument <c>NameDb</c>, which is a
 
67
      tuple <c>{Name, Db}</c>, to identify which database the
 
68
      functions should use. <c>Name</c> is the symbolic name of the
 
69
      managed object as defined in the MIB, and <c>Db</c> is either
 
70
      <c>volatile</c>, <c>persistent</c>, or <c>mnesia</c>. If it is
 
71
      <c>mnesia</c>, all variables are stored in the Mnesia table
 
72
      <c>snmp_variables</c> which must be a table with two attributes
 
73
      (not a Mnesia SNMP table). The SNMP tables are stored in Mnesia
 
74
      tables with the same names as the SNMP tables.  All functions
 
75
      assume that a Mnesia table exists with the correct name and
 
76
      attributes. It is the programmer's responsibility to ensure
 
77
      this. Specifically, if variables are stored in Mnesia, the table
 
78
      <c>snmp_variables</c> must be created by the programmer.  The
 
79
      record definition for this table is defined in the file
 
80
      <c>snmp/include/snmp_types.hrl</c>.
 
81
      </p>
 
82
    <p>If an instrumentation function in the association file for a
 
83
      variable <c>myVar</c> does not have a name when compiling an
 
84
      MIB, the compiler generates an entry.
 
85
      </p>
 
86
    <pre>
 
87
{myVar, {snmp_generic, variable_func, [{myVar, Db]}}.
 
88
    </pre>
 
89
    <p>And for a table:</p>
 
90
    <pre>
 
91
{myTable, {snmp_generic, table_func, [{myTable, Db]}}.
 
92
    </pre>
 
93
  </description>
 
94
 
 
95
  <section>
 
96
    <title>DATA TYPES</title>
 
97
    <p>In the functions defined below, the following types are used:</p>
 
98
    <code type="none">
 
99
name_db() = {name(), db()} 
 
100
name() = atom()
 
101
db() = volatile | persistent | mnesia
 
102
row_index() = [int()]
 
103
columns() = [column()] | [{column(), value()}]
 
104
column() = int()
 
105
value() = term()
 
106
    </code>
 
107
    <taglist>
 
108
      <tag><c>row_index()</c></tag>
 
109
      <item>
 
110
        <p>Denotes the last part of the OID which specifies the 
 
111
          index of the row in the table (see RFC1212, 4.1.6 for 
 
112
          more information about INDEX).  </p>
 
113
      </item>
 
114
      <tag><c>columns()</c></tag>
 
115
      <item>
 
116
        <p>Is a list of column numbers in the case of a <c>get</c> 
 
117
          operation, and a list of column numbers and values in the 
 
118
          case of a <c>set</c> operation. </p>
 
119
      </item>
 
120
    </taglist>
 
121
  </section>
 
122
  <funcs>
 
123
    <func>
 
124
      <name>get_status_col(Name, Cols)</name>
 
125
      <name>get_status_col(NameDb, Cols) -> {ok, StatusVal} | false</name>
 
126
      <fsummary>Get the value of the status column from <c>Cols</c></fsummary>
 
127
      <type>
 
128
        <v>Name = name()</v>
 
129
        <v>NameDb = name_db()</v>
 
130
        <v>Cols = columns()</v>
 
131
        <v>StatusVal = term()</v>
 
132
      </type>
 
133
      <desc>
 
134
        <p>Gets the value of the status column from <c>Cols</c>.
 
135
          </p>
 
136
        <p>This function can be used in instrumentation functions for
 
137
          <c>is_set_ok</c>, <c>undo</c> or <c>set</c> to check if the
 
138
          status column of a table is modified.</p>
 
139
      </desc>
 
140
    </func>
 
141
    <func>
 
142
      <name>get_index_types(Name)</name>
 
143
      <fsummary>Get the index types of <c>Name</c></fsummary>
 
144
      <type>
 
145
        <v>Name = name()</v>
 
146
      </type>
 
147
      <desc>
 
148
        <p>Gets the index types of <c>Name</c></p>
 
149
        <p>This function can be used in instrumentation functions to
 
150
          retrieve the index types part of the table info.</p>
 
151
      </desc>
 
152
    </func>
 
153
    <func>
 
154
      <name>table_func(Op1, NameDb)</name>
 
155
      <name>table_func(Op2, RowIndex, Cols, NameDb) -> Ret</name>
 
156
      <fsummary>Default instrumentation function for tables</fsummary>
 
157
      <type>
 
158
        <v>Op1 = new | delete </v>
 
159
        <v>Op2 = get | next | is_set_ok | set | undo</v>
 
160
        <v>NameDb = name_db()</v>
 
161
        <v>RowIndex = row_index()</v>
 
162
        <v>Cols = columns()</v>
 
163
        <v>Ret = term()</v>
 
164
      </type>
 
165
      <desc>
 
166
        <p>This is the default instrumentation function for tables.
 
167
          </p>
 
168
        <list type="bulleted">
 
169
          <item>The <c>new</c> function creates the table if it does
 
170
           not exist, but only if the database is the SNMP internal db.</item>
 
171
          <item>The <c>delete</c> function does not delete the table
 
172
           from the database since unloading an MIB does not
 
173
           necessarily mean that the table should be destroyed.</item>
 
174
          <item>The <c>is_set_ok</c> function checks that a row which
 
175
           is to be modified or deleted exists, and that a row which
 
176
           is to be created does not exist.</item>
 
177
          <item>The <c>undo</c> function does nothing.</item>
 
178
          <item>The <c>set</c> function checks if it has enough
 
179
           information to make the row change its status from
 
180
          <c>notReady</c> to <c>notInService</c> (when a row has
 
181
           been been set to <c>createAndWait</c>). If a row is set to
 
182
          <c>createAndWait</c>, columns without a value are set to
 
183
          <c>noinit</c>. If Mnesia is used, the set functionality is
 
184
           handled within a transaction.</item>
 
185
        </list>
 
186
        <p>If it is possible for a manager to create or delete rows in
 
187
          the table, there must be a <c>RowStatus</c> column for
 
188
          <c>is_set_ok</c>, <c>set</c> and <c>undo</c> to work properly.
 
189
          </p>
 
190
        <p>The function returns according to the specification of an
 
191
          instrumentation function.
 
192
          </p>
 
193
      </desc>
 
194
    </func>
 
195
    <func>
 
196
      <name>table_get_elements(NameDb, RowIndex, Cols) -> Values</name>
 
197
      <fsummary>Get elements in a table row</fsummary>
 
198
      <type>
 
199
        <v>NameDb = name_db()</v>
 
200
        <v>RowIndex = row_index()</v>
 
201
        <v>Cols = columns()</v>
 
202
        <v>Values = [value() | noinit]</v>
 
203
      </type>
 
204
      <desc>
 
205
        <p>Returns a list with values for all columns in <c>Cols</c>.
 
206
          If a column is undefined, its value is <c>noinit</c>.</p>
 
207
      </desc>
 
208
    </func>
 
209
    <func>
 
210
      <name>table_next(NameDb, RestOid) -> RowIndex | endOfTable</name>
 
211
      <fsummary>Find the next row in the table</fsummary>
 
212
      <type>
 
213
        <v>NameDb = name_db()</v>
 
214
        <v>RestOid = [int()]</v>
 
215
        <v>RowIndex = row_index()</v>
 
216
      </type>
 
217
      <desc>
 
218
        <p>Finds the indices of the next row in the table.  <c>RestOid</c>
 
219
          does not have to specify an existing row.</p>
 
220
      </desc>
 
221
    </func>
 
222
    <func>
 
223
      <name>table_row_exists(NameDb, RowIndex) -> bool()</name>
 
224
      <fsummary>Check if a row in a table exists</fsummary>
 
225
      <type>
 
226
        <v>NameDb = name_db()</v>
 
227
        <v>RowIndex = row_index()</v>
 
228
      </type>
 
229
      <desc>
 
230
        <p>Checks if a row in a table exists.</p>
 
231
      </desc>
 
232
    </func>
 
233
    <func>
 
234
      <name>table_set_elements(NameDb, RowIndex, Cols) -> bool()</name>
 
235
      <fsummary>Set elements in a table row</fsummary>
 
236
      <type>
 
237
        <v>NameDb = name_db()</v>
 
238
        <v>RowIndex = row_index()</v>
 
239
        <v>Cols = columns()</v>
 
240
      </type>
 
241
      <desc>
 
242
        <p>Sets the elements in <c>Cols</c> to the row specified by
 
243
          <c>RowIndex</c>.  No checks are performed on the new values.
 
244
          </p>
 
245
        <p>If the Mnesia database is used, this function calls
 
246
          <c>mnesia:write</c> to store the values.  This means that
 
247
          this function must be called from within a transaction
 
248
          (<c>mnesia:transaction/1</c> or <c>mnesia:dirty/1</c>).</p>
 
249
      </desc>
 
250
    </func>
 
251
    <func>
 
252
      <name>variable_func(Op1, NameDb)</name>
 
253
      <name>variable_func(Op2, Val, NameDb) -> Ret</name>
 
254
      <fsummary>Default instrumentation function for tables</fsummary>
 
255
      <type>
 
256
        <v>Op1 = new | delete | get</v>
 
257
        <v>Op2 = is_set_ok | set | undo</v>
 
258
        <v>NameDb = name_db()</v>
 
259
        <v>Val = value()</v>
 
260
        <v>Ret = term()</v>
 
261
      </type>
 
262
      <desc>
 
263
        <p>This is the default instrumentation function for variables.</p>
 
264
        <p>The <c>new</c> function creates a new variable in the
 
265
          database with a default value as defined in the MIB, or a zero
 
266
          value (depending on the type).  </p>
 
267
        <p>The <c>delete</c> function does not delete the variable from 
 
268
          the database. </p>
 
269
        <p>The function returns according to the specification of an 
 
270
          instrumentation function. </p>
 
271
      </desc>
 
272
    </func>
 
273
    <func>
 
274
      <name>variable_get(NameDb) -> {value, Value} | undefined</name>
 
275
      <fsummary>Get the value of a variable</fsummary>
 
276
      <type>
 
277
        <v>NameDb = name_db()</v>
 
278
        <v>Value = value()</v>
 
279
      </type>
 
280
      <desc>
 
281
        <p>Gets the value of a variable.</p>
 
282
      </desc>
 
283
    </func>
 
284
    <func>
 
285
      <name>variable_set(NameDb, NewVal) -> true | false</name>
 
286
      <fsummary>Set a value for a variable</fsummary>
 
287
      <type>
 
288
        <v>NameDb = name_db()</v>
 
289
        <v>NewVal = value()</v>
 
290
      </type>
 
291
      <desc>
 
292
        <p>Sets a new value to a variable.  The variable is created if
 
293
          it does not exist.  No checks are made on the type of the
 
294
          new value.  </p>
 
295
        <p>Returns <c>false</c> if the <c>NameDb</c> argument
 
296
          is incorrectly specified, otherwise <c>true</c>.</p>
 
297
      </desc>
 
298
    </func>
 
299
  </funcs>
 
300
 
 
301
  <section>
 
302
    <title>Example</title>
 
303
    <p>The following example shows an implementation of a table which is
 
304
      stored in Mnesia, but with some checks performed at set-request
 
305
      operations.
 
306
      </p>
 
307
    <pre>
 
308
myTable_func(new, NameDb) ->   % pass unchanged
 
309
  snmp_generic:table_func(new, NameDb).
 
310
 
 
311
myTable_func(delete, NameDb) ->   % pass unchanged
 
312
  snmp_generic:table_func(delete, NameDb).
 
313
 
 
314
%% change row
 
315
myTable_func(is_set_ok, RowIndex, Cols, NameDb) ->
 
316
  case snmp_generic:table_func(is_set_ok, RowIndex,
 
317
                               Cols, NameDb) of
 
318
    {noError, 0} -> 
 
319
      myApplication:is_set_ok(RowIndex, Cols);
 
320
    Err ->
 
321
      Err
 
322
  end;
 
323
 
 
324
myTable_func(set, RowIndex, Cols, NameDb) ->
 
325
  case snmp_generic:table_func(set, RowIndex, Cols,
 
326
                               NameDb),
 
327
    {noError, 0} ->
 
328
      % Now the row is updated, tell the application
 
329
      myApplication:update(RowIndex, Cols);
 
330
    Err ->
 
331
      Err
 
332
  end;
 
333
 
 
334
myTable_func(Op, RowIndex, Cols, NameDb) ->   % pass unchanged
 
335
  snmp_generic:table_func(Op, RowIndex, Cols, NameDb).
 
336
    </pre>
 
337
    <p>The <c>.funcs</c> file would look like:
 
338
      </p>
 
339
    <pre>
 
340
{myTable, {myModule, myTable_func, [{myTable, mnesia}]}}.
 
341
    </pre>
 
342
  </section>
 
343
  
 
344
</erlref>
 
345