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

« back to all changes in this revision

Viewing changes to lib/snmp/src/manager/snmpm_usm.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
%%-----------------------------------------------------------------
 
19
%% This module implements the User Based Security Model for SNMP,
 
20
%% as defined in rfc2274.
 
21
%%-----------------------------------------------------------------
 
22
 
 
23
-module(snmpm_usm).
 
24
 
 
25
-export([init/0, 
 
26
         reset/0, 
 
27
         process_incoming_msg/4, generate_outgoing_msg/5]).
 
28
 
 
29
-define(SNMP_USE_V3, true).
 
30
-include("snmp_types.hrl").
 
31
-include("snmpm_usm.hrl").
 
32
-include("SNMP-USER-BASED-SM-MIB.hrl").
 
33
-include("SNMP-USM-AES-MIB.hrl").
 
34
% -include("SNMPv2-TC.hrl").
 
35
 
 
36
-define(VMODULE,"M-USM").
 
37
-include("snmp_verbosity.hrl").
 
38
 
 
39
 
 
40
%%-----------------------------------------------------------------
 
41
 
 
42
-define(i32(Int), (Int bsr 24) band 255, (Int bsr 16) band 255, (Int bsr 8) band 255, Int band 255).
 
43
-define(i64(Int), (Int bsr 56) band 255, (Int bsr 48) band 255, (Int bsr 40) band 255, (Int bsr 32) band 255, (Int bsr 24) band 255, (Int bsr 16) band 255, (Int bsr 8) band 255, Int band 255).
 
44
 
 
45
 
 
46
init() ->
 
47
    init_counters().
 
48
 
 
49
 
 
50
%%-----------------------------------------------------------------
 
51
%% Func: process_incoming_msg(Packet, Data, SecParams, SecLevel) ->
 
52
%%       {ok, {SecEngineID, SecName, ScopedPDUBytes, SecData}} |
 
53
%%       {error, Reason} | {error, Reason, ErrorInfo}
 
54
%%       Return value may be throwed.
 
55
%% Types: Reason -> term()
 
56
%% Purpose: 
 
57
%%-----------------------------------------------------------------
 
58
process_incoming_msg(Packet, Data, SecParams, SecLevel) ->
 
59
    %% 3.2.1
 
60
    ?vtrace("process_incoming_msg -> [3.2.1] check security parms",[]),
 
61
    UsmSecParams =
 
62
        case (catch snmp_pdus:dec_usm_security_parameters(SecParams)) of
 
63
            {'EXIT', Reason} ->
 
64
                inc(snmpInASNParseErrs),
 
65
                error({parseError, Reason}, []);
 
66
            Res ->
 
67
                Res
 
68
        end,
 
69
 
 
70
    %% Part of 3.2.2
 
71
    #usmSecurityParameters{msgAuthoritativeEngineID = MsgAuthEngineID,
 
72
                           msgUserName = MsgUserName} = UsmSecParams,
 
73
    ?vlog("process_incoming_msg -> [3.2.2]"
 
74
          "~n   authEngineID: ~p"
 
75
          "~n   userName:     ~p", [MsgAuthEngineID, MsgUserName]),
 
76
 
 
77
    %% 3.2.3 (b)
 
78
    ?vtrace("process_incoming_msg -> [3.2.3-b] check engine id",[]),
 
79
    case snmpm_config:is_usm_engine_id_known(MsgAuthEngineID) of
 
80
        true ->
 
81
            ok;
 
82
        false ->
 
83
            SecData1 = [MsgUserName],
 
84
            error(usmStatsUnknownEngineIDs, 
 
85
                  ?usmStatsUnknownEngineIDs_instance,
 
86
                  undefined, [{sec_data, SecData1}])
 
87
    end,
 
88
 
 
89
    %% 3.2.4
 
90
    ?vtrace("process_incoming_msg -> [3.2.4] retrieve usm user",[]),
 
91
    SecUser =
 
92
        case snmpm_config:get_usm_user(MsgAuthEngineID, MsgUserName) of
 
93
            {ok, User} ->
 
94
                User;
 
95
            _ -> % undefined user
 
96
                SecData2 = [MsgUserName],
 
97
                error(usmStatsUnknownUserNames, 
 
98
                      ?usmStatsUnknownUserNames_instance, %% OTP-3542
 
99
                      undefined, [{sec_data, SecData2}])
 
100
        end,
 
101
 
 
102
    %% 3.2.5 - implicit in following checks
 
103
    %% 3.2.6 - 3.2.7
 
104
    ?vtrace("process_incoming_msg -> "
 
105
            "[3.2.5 - 3.2.7] authenticate incoming",[]),
 
106
    authenticate_incoming(Packet, UsmSecParams, SecUser, SecLevel),
 
107
 
 
108
    %% 3.2.8
 
109
    ?vtrace("process_incoming_msg -> [3.2.8] decrypt scoped data",[]),
 
110
    ScopedPDUBytes = decrypt(Data, SecUser, UsmSecParams, SecLevel),
 
111
 
 
112
    %% 3.2.9
 
113
    %% Means that if AuthKey/PrivKey are changed; the old values
 
114
    %% will be used.
 
115
    CachedSecData = {MsgUserName,
 
116
                     SecUser#usm_user.auth,
 
117
                     SecUser#usm_user.auth_key,
 
118
                     SecUser#usm_user.priv,
 
119
                     SecUser#usm_user.priv_key},
 
120
    SecName = SecUser#usm_user.sec_name,
 
121
    {ok, {MsgAuthEngineID, SecName, ScopedPDUBytes, CachedSecData}}.
 
122
    
 
123
 
 
124
authenticate_incoming(Packet, UsmSecParams, UsmUser, SecLevel) ->
 
125
    %% 3.2.6
 
126
    ?vtrace("authenticate incoming: 3.2.6",[]),
 
127
    #usmSecurityParameters{msgAuthoritativeEngineID    = MsgAuthEngineID,
 
128
                           msgAuthoritativeEngineBoots = MsgAuthEngineBoots,
 
129
                           msgAuthoritativeEngineTime  = MsgAuthEngineTime,
 
130
                           msgAuthenticationParameters = MsgAuthParams} =
 
131
        UsmSecParams,
 
132
    case snmp_misc:is_auth(SecLevel) of
 
133
        true ->
 
134
            SecName = UsmUser#usm_user.sec_name,
 
135
            case is_auth(UsmUser#usm_user.auth, 
 
136
                         UsmUser#usm_user.auth_key,
 
137
                         MsgAuthParams,
 
138
                         Packet,
 
139
                         SecName,
 
140
                         MsgAuthEngineID,
 
141
                         MsgAuthEngineBoots, 
 
142
                         MsgAuthEngineTime) of
 
143
                true -> 
 
144
                    ok;
 
145
                false -> 
 
146
                    error(usmStatsWrongDigests,
 
147
                          ?usmStatsWrongDigests_instance, SecName)
 
148
            end;
 
149
        false ->  % noAuth
 
150
            ok
 
151
    end.
 
152
 
 
153
 
 
154
            
 
155
is_auth(usmNoAuthProtocol, _, _, _, SecName, _, _, _) -> % 3.2.5
 
156
    error(usmStatsUnsupportedSecLevels,
 
157
          ?usmStatsUnsupportedSecLevels_instance, SecName);
 
158
is_auth(AuthProtocol, AuthKey, AuthParams, Packet, SecName,
 
159
        MsgAuthEngineID, MsgAuthEngineBoots, MsgAuthEngineTime) ->
 
160
    case auth_in(AuthProtocol, AuthKey, AuthParams, Packet) of
 
161
        true ->
 
162
            %% 3.2.7
 
163
            ?vtrace("retrieve EngineBoots and EngineTime: 3.2.7",[]),
 
164
            SnmpEngineID = get_engine_id(),
 
165
            ?vtrace("SnmpEngineID: ~p",[SnmpEngineID]),
 
166
            case MsgAuthEngineID of
 
167
                SnmpEngineID -> %% 3.2.7a
 
168
                    ?vtrace("we are authoritative: 3.2.7a",[]),
 
169
                    SnmpEngineBoots = get_engine_boots(),
 
170
                    ?vtrace("SnmpEngineBoots: ~p",[SnmpEngineBoots]),
 
171
                    SnmpEngineTime = get_engine_time(),
 
172
                    ?vtrace("SnmpEngineTime: ~p",[SnmpEngineTime]),
 
173
                    InTimeWindow =
 
174
                        if
 
175
                            SnmpEngineBoots == 2147483647 -> false;
 
176
                            MsgAuthEngineBoots /= SnmpEngineBoots -> false;
 
177
                            MsgAuthEngineTime + 150 < SnmpEngineTime -> false;
 
178
                            MsgAuthEngineTime - 150 > SnmpEngineTime -> false;
 
179
                            true -> true
 
180
                        end,
 
181
                    case InTimeWindow of
 
182
                        true -> 
 
183
                            true;
 
184
                        %% OTP-4090 (OTP-3542)
 
185
                        false -> 
 
186
                            error(usmStatsNotInTimeWindows,
 
187
                                  ?usmStatsNotInTimeWindows_instance,
 
188
                                  SecName,
 
189
                                  [{securityLevel, 1}]) % authNoPriv
 
190
                    end;
 
191
                _ -> %% 3.2.7b - we're non-authoritative
 
192
                    ?vtrace("we are non-authoritative: 3.2.7b",[]),
 
193
                    SnmpEngineBoots = get_engine_boots(MsgAuthEngineID),
 
194
                    ?vtrace("SnmpEngineBoots: ~p",[SnmpEngineBoots]),
 
195
                    SnmpEngineTime = get_engine_time(MsgAuthEngineID),
 
196
                    ?vtrace("SnmpEngineTime: ~p",[SnmpEngineTime]),
 
197
                    LatestRecvTime = get_engine_latest_time(MsgAuthEngineID),
 
198
                    ?vtrace("LatestRecvTime: ~p",[LatestRecvTime]),
 
199
                    UpdateLCD =
 
200
                        if
 
201
                            MsgAuthEngineBoots > SnmpEngineBoots -> true;
 
202
                            MsgAuthEngineBoots == SnmpEngineBoots,
 
203
                            MsgAuthEngineTime > LatestRecvTime -> true;
 
204
                            true -> false
 
205
                        end,
 
206
                    case UpdateLCD of
 
207
                        true -> %% 3.2.7b1
 
208
                            ?vtrace("update msgAuthoritativeEngineID: 3.2.7b1",
 
209
                                    []),
 
210
                            set_engine_boots(MsgAuthEngineID,
 
211
                                             MsgAuthEngineBoots),
 
212
                            set_engine_time(MsgAuthEngineID,
 
213
                                            MsgAuthEngineTime),
 
214
                            set_engine_latest_time(MsgAuthEngineID,
 
215
                                                   MsgAuthEngineTime);
 
216
                        false ->
 
217
                            ok
 
218
                    end,
 
219
                    %% 3.2.7.b2
 
220
                    ?vtrace("check if message is outside time window: 3.2.7b2",
 
221
                            []),
 
222
                    InTimeWindow =
 
223
                        if
 
224
                            SnmpEngineBoots == 2147483647 ->
 
225
                                {false, [{engine, SnmpEngineID}, 
 
226
                                         {boots,  at_max}]};
 
227
                            MsgAuthEngineBoots < SnmpEngineBoots ->
 
228
                                {false, [{engine, MsgAuthEngineID},
 
229
                                         {boots,  MsgAuthEngineBoots}]};
 
230
                            MsgAuthEngineBoots == SnmpEngineBoots,
 
231
                            MsgAuthEngineTime < (SnmpEngineTime - 150) ->
 
232
                                {false, [{engine, MsgAuthEngineID},
 
233
                                         {time,   MsgAuthEngineTime}]};
 
234
                            true -> true
 
235
                        end,
 
236
                    case InTimeWindow of
 
237
                        {false, Reason} ->
 
238
                            ?vinfo("not in time window[3.2.7b2]: ~p", 
 
239
                                   [Reason]),
 
240
                            error(notInTimeWindow, Reason);
 
241
                        true ->
 
242
                            ok
 
243
                    end,
 
244
                    true
 
245
            end;
 
246
        false -> 
 
247
            false
 
248
    end.
 
249
                                
 
250
                            
 
251
decrypt(Data, UsmUser, UsmSecParams, SecLevel) ->
 
252
    case snmp_misc:is_priv(SecLevel) of
 
253
        true ->
 
254
            do_decrypt(Data, UsmUser, UsmSecParams);
 
255
        false ->
 
256
            Data
 
257
    end.
 
258
 
 
259
do_decrypt(Data, #usm_user{sec_name = SecName,
 
260
                           priv     = PrivP,
 
261
                           priv_key = PrivKey}, 
 
262
           #usmSecurityParameters{msgPrivacyParameters = PrivParms}) ->
 
263
    EncryptedPDU = snmp_pdus:dec_scoped_pdu_data(Data),
 
264
    try_decrypt(PrivP, PrivKey, PrivParms, EncryptedPDU, SecName).
 
265
 
 
266
try_decrypt(usmNoPrivProtocol, _, _, _, SecName) -> % 3.2.5
 
267
    error(usmStatsUnsupportedSecLevels, 
 
268
          ?usmStatsUnsupportedSecLevels_instance, SecName);
 
269
try_decrypt(usmDESPrivProtocol, 
 
270
            PrivKey, MsgPrivParams, EncryptedPDU, SecName) ->
 
271
    case (catch des_decrypt(PrivKey, MsgPrivParams, EncryptedPDU)) of
 
272
        {ok, DecryptedData} ->
 
273
            DecryptedData;
 
274
        _ ->
 
275
            error(usmStatsDecryptionErrors, 
 
276
                  ?usmStatsDecryptionErrors, SecName)
 
277
    end;
 
278
try_decrypt(usmAesCfb128Protocol, 
 
279
            PrivKey, UsmSecParams,  EncryptedPDU, SecName) ->
 
280
    case (catch aes_decrypt(PrivKey, UsmSecParams, EncryptedPDU)) of
 
281
        {ok, DecryptedData} ->
 
282
            DecryptedData;
 
283
        _ ->
 
284
            error(usmStatsDecryptionErrors, 
 
285
                  ?usmStatsDecryptionErrors, SecName)
 
286
    end.
 
287
    
 
288
 
 
289
%%-----------------------------------------------------------------
 
290
%% Func: process_outgoing_msg(Message, SecEngineID, SecName, 
 
291
%%                            SecData, SecLevel) ->
 
292
%%       {ok, {SecEngineID, SecName, ScopedPDUBytes, SecData}} |
 
293
%%       {error, Reason} | {error, Reason, ErrorInfo}
 
294
%%       Return value may be throwed.
 
295
%% Types: Reason -> term()
 
296
%% Purpose: 
 
297
%%-----------------------------------------------------------------
 
298
generate_outgoing_msg(Message, SecEngineID, SecName, SecData, SecLevel) ->
 
299
    %% 3.1.1
 
300
    ?vtrace("generate_outgoing_msg -> entry (3.1.1)",[]),
 
301
    {UserName, AuthProtocol, PrivProtocol, AuthKey, PrivKey} = 
 
302
        case SecData of
 
303
            [] -> % 3.1.1b
 
304
                %% Not a response - read from LCD
 
305
                case snmpm_config:get_usm_user_from_sec_name(SecEngineID, 
 
306
                                                             SecName) of
 
307
                    {ok, User} ->
 
308
                        {User#usm_user.name, 
 
309
                         User#usm_user.auth,
 
310
                         User#usm_user.priv,
 
311
                         User#usm_user.auth_key,
 
312
                         User#usm_user.priv_key};
 
313
                    _ ->
 
314
                        error(unknownSecurityName)
 
315
                end;
 
316
            [MsgUserName] ->
 
317
                %% This means the user at the engine is unknown
 
318
                {MsgUserName, usmNoAuthProtocol, usmNoPrivProtocol, "", ""};
 
319
            _ -> % 3.1.1a
 
320
                SecData
 
321
        end,
 
322
    %% 3.1.4
 
323
    ?vtrace("generate_outgoing_msg -> (3.1.4)",[]),
 
324
    ScopedPduBytes = Message#message.data,
 
325
    {ScopedPduData, MsgPrivParams} =
 
326
        encrypt(ScopedPduBytes, PrivProtocol, PrivKey, SecLevel),
 
327
    SnmpEngineID = get_engine_id(),
 
328
    ?vtrace("SnmpEngineID: ~p (3.1.6)",[SnmpEngineID]),
 
329
    %% 3.1.6
 
330
    {MsgAuthEngineBoots, MsgAuthEngineTime} =
 
331
        case snmp_misc:is_auth(SecLevel) of
 
332
            false when SecData == [] -> % not a response
 
333
                {0, 0}; 
 
334
            true when SecEngineID /= SnmpEngineID ->
 
335
                {get_engine_boots(SecEngineID), get_engine_time(SecEngineID)};
 
336
            _ ->
 
337
                {get_engine_boots(), get_engine_time()}
 
338
        end,
 
339
    %% 3.1.5 - 3.1.7
 
340
    ?vtrace("generate_outgoing_msg -> (3.1.5 - 3.1.7)",[]),
 
341
    UsmSecParams =
 
342
        #usmSecurityParameters{msgAuthoritativeEngineID = SecEngineID,
 
343
                               msgAuthoritativeEngineBoots = MsgAuthEngineBoots,
 
344
                               msgAuthoritativeEngineTime = MsgAuthEngineTime,
 
345
                               msgUserName = UserName,
 
346
                               msgPrivacyParameters = MsgPrivParams},
 
347
    Message2 = Message#message{data = ScopedPduData},
 
348
    %% 3.1.8
 
349
    ?vtrace("generate_outgoing_msg -> (3.1.8)",[]),
 
350
    authenticate_outgoing(Message2, UsmSecParams,
 
351
                          AuthKey, AuthProtocol, SecLevel).
 
352
 
 
353
 
 
354
%% Ret: {ScopedPDU, MsgPrivParams} - both are already encoded as OCTET STRINGs
 
355
encrypt(Data, PrivProtocol, PrivKey, SecLevel) ->
 
356
    case snmp_misc:is_priv(SecLevel) of
 
357
        false -> % 3.1.4b
 
358
            {Data, []};
 
359
        true -> % 3.1.4a
 
360
            case try_encrypt(PrivProtocol, PrivKey, Data) of
 
361
                {ok, ScopedPduData, MsgPrivParams} ->
 
362
                    {snmp_pdus:enc_oct_str_tag(ScopedPduData), MsgPrivParams};
 
363
                {error, Reason} ->
 
364
                    error(Reason);
 
365
                _ ->
 
366
                    error(encryptionError)
 
367
            end
 
368
    end.
 
369
 
 
370
try_encrypt(usmNoPrivProtocol, _PrivKey, _Data) -> % 3.1.2
 
371
    error(unsupportedSecurityLevel);
 
372
try_encrypt(usmDESPrivProtocol, PrivKey, Data) ->
 
373
    des_encrypt(PrivKey, Data);
 
374
try_encrypt(usmAesCfb128Protocol, PrivKey, Data) ->
 
375
    aes_encrypt(PrivKey, Data).
 
376
 
 
377
authenticate_outgoing(Message, UsmSecParams, 
 
378
                      AuthKey, AuthProtocol, SecLevel) ->
 
379
    Message2 = 
 
380
        case snmp_misc:is_auth(SecLevel) of
 
381
            true ->
 
382
                auth_out(AuthProtocol, AuthKey, Message, UsmSecParams);
 
383
            false ->
 
384
                set_msg_auth_params(Message, UsmSecParams)
 
385
        end,
 
386
    snmp_pdus:enc_message_only(Message2).
 
387
    
 
388
            
 
389
 
 
390
%%-----------------------------------------------------------------
 
391
%% Auth and priv algorithms
 
392
%%-----------------------------------------------------------------
 
393
auth_in(AuthProtocol, AuthKey, AuthParams, Packet) ->
 
394
    snmp_usm:auth_in(AuthProtocol, AuthKey, AuthParams, Packet).
 
395
 
 
396
auth_out(AuthProtocol, AuthKey, Message, UsmSecParams) ->
 
397
    snmp_usm:auth_out(AuthProtocol, AuthKey, Message, UsmSecParams).
 
398
 
 
399
set_msg_auth_params(Message, UsmSecParams) ->
 
400
    snmp_usm:set_msg_auth_params(Message, UsmSecParams, []).
 
401
 
 
402
des_encrypt(PrivKey, Data) ->
 
403
    snmp_usm:des_encrypt(PrivKey, Data, fun get_des_salt/0).
 
404
 
 
405
des_decrypt(PrivKey, MsgPrivParams, EncData) ->
 
406
    snmp_usm:des_decrypt(PrivKey, MsgPrivParams, EncData).
 
407
 
 
408
get_des_salt() ->
 
409
    SaltInt     = snmpm_config:incr_counter(usm_des_salt, 1),
 
410
    EngineBoots = get_engine_boots(),
 
411
    [?i32(EngineBoots), ?i32(SaltInt)].
 
412
 
 
413
aes_encrypt(PrivKey, Data) ->
 
414
    snmp_usm:aes_encrypt(PrivKey, Data, fun get_aes_salt/0).
 
415
 
 
416
aes_decrypt(PrivKey, UsmSecParams, EncData) ->
 
417
    #usmSecurityParameters{msgPrivacyParameters = MsgPrivParams,
 
418
                           msgAuthoritativeEngineTime = EngineTime,
 
419
                           msgAuthoritativeEngineBoots = EngineBoots} =
 
420
        UsmSecParams,
 
421
    snmp_usm:aes_decrypt(PrivKey, MsgPrivParams, EncData, 
 
422
                         EngineBoots, EngineTime).
 
423
 
 
424
get_aes_salt() ->
 
425
    SaltInt     = snmpm_config:incr_counter(usm_aes_salt, 1),
 
426
    [?i64(SaltInt)].
 
427
 
 
428
%%-----------------------------------------------------------------
 
429
 
 
430
get_engine_id() ->
 
431
    {ok, EngineID} = snmpm_config:get_engine_id(),
 
432
    EngineID.
 
433
 
 
434
get_engine_boots() ->
 
435
    {ok, Boots} = snmpm_config:get_engine_boots(),
 
436
    Boots.
 
437
 
 
438
get_engine_time() ->
 
439
    {ok, Diff} = snmpm_config:get_engine_time(),
 
440
    Diff.
 
441
 
 
442
 
 
443
%%-----------------------------------------------------------------
 
444
%% We cache the local values of all non-auth engines we know.
 
445
%% See section 2.3 (Time Synchronization) of the RFC.
 
446
%%-----------------------------------------------------------------
 
447
get_engine_boots(SnmpEngineID) ->
 
448
    {ok, Boots} = snmpm_config:get_usm_eboots(SnmpEngineID),
 
449
    Boots.
 
450
 
 
451
get_engine_time(SnmpEngineID) ->
 
452
    {ok, Diff} = snmpm_config:get_usm_etime(SnmpEngineID),
 
453
    Diff.
 
454
            
 
455
get_engine_latest_time(SnmpEngineID) ->
 
456
    {ok, Time} = snmpm_config:get_usm_eltime(SnmpEngineID),
 
457
    Time.
 
458
            
 
459
 
 
460
set_engine_boots(SnmpEngineID, EngineBoots) ->
 
461
    snmpm_config:set_usm_eboots(SnmpEngineID, EngineBoots).
 
462
 
 
463
set_engine_time(SnmpEngineID, EngineTime) ->
 
464
    Diff = snmp_misc:now(sec) - EngineTime,
 
465
    snmpm_config:set_usm_etime(SnmpEngineID, Diff).
 
466
 
 
467
set_engine_latest_time(SnmpEngineID, EngineTime) ->
 
468
    snmpm_config:set_usm_eltime(SnmpEngineID, EngineTime).
 
469
 
 
470
 
 
471
%%-----------------------------------------------------------------
 
472
%% Utility functions
 
473
%%-----------------------------------------------------------------
 
474
error(Reason) ->
 
475
    throw({error, Reason}).
 
476
 
 
477
error(Reason, ErrorInfo) ->
 
478
    throw({error, Reason, ErrorInfo}).
 
479
 
 
480
error(Variable, Oid, SecName) ->
 
481
    error(Variable, Oid, SecName, []).
 
482
error(Variable, Oid, SecName, Opts) ->
 
483
    Val = inc(Variable),
 
484
    ErrorInfo = {#varbind{oid          = Oid,
 
485
                          variabletype = 'Counter32',
 
486
                          value        = Val},
 
487
                 SecName,
 
488
                 Opts},
 
489
    throw({error, Variable, ErrorInfo}).
 
490
 
 
491
 
 
492
%%-----------------------------------------------------------------
 
493
 
 
494
init_counters() ->
 
495
    F = fun(Counter) -> snmpm_config:maybe_cre_stats_counter(Counter, 0) end,
 
496
    lists:map(F, counters()).
 
497
 
 
498
reset() ->
 
499
    F = fun(Counter) -> snmpm_config:reset_stats_counter(Counter) end,
 
500
    lists:map(F, counters()).
 
501
 
 
502
counters() ->
 
503
    [usmStatsUnsupportedSecLevels,
 
504
     usmStatsNotInTimeWindows,
 
505
     usmStatsUnknownUserNames,
 
506
     usmStatsUnknownEngineIDs,
 
507
     usmStatsWrongDigests,
 
508
     usmStatsDecryptionErrors].
 
509
 
 
510
inc(Name) -> snmpm_config:incr_stats_counter(Name, 1).
 
511