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

« back to all changes in this revision

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