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

« back to all changes in this revision

Viewing changes to lib/snmp/src/misc/snmp_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(snmp_usm).
 
19
 
 
20
-export([passwd2localized_key/3, localize_key/3]).
 
21
-export([auth_in/4, auth_out/4, set_msg_auth_params/3]).
 
22
-export([des_encrypt/3, des_decrypt/3]).
 
23
-export([aes_encrypt/3, aes_decrypt/5]).
 
24
 
 
25
 
 
26
-define(SNMP_USE_V3, true).
 
27
-include("snmp_types.hrl").
 
28
-include("SNMP-USER-BASED-SM-MIB.hrl").
 
29
-include("SNMP-USM-AES-MIB.hrl").
 
30
 
 
31
-define(VMODULE,"USM").
 
32
-include("snmp_verbosity.hrl").
 
33
 
 
34
 
 
35
%%-----------------------------------------------------------------
 
36
 
 
37
-define(twelwe_zeros, [0,0,0,0,0,0,0,0,0,0,0,0]).
 
38
 
 
39
-define(i32(Int), (Int bsr 24) band 255, (Int bsr 16) band 255, (Int bsr 8) band 255, Int band 255).
 
40
 
 
41
 
 
42
%%-----------------------------------------------------------------
 
43
%% Func: passwd2localized_key/3
 
44
%% Types: Alg      = md5 | sha
 
45
%%        Passwd   = string()
 
46
%%        EngineID = string()
 
47
%% Purpose: Generates a key that can be used as an authentication
 
48
%%          or privacy key using MD5 och SHA.  The key is
 
49
%%          localized for EngineID.
 
50
%%          The algorithm is described in appendix A.1 2) of
 
51
%%          rfc2274.
 
52
%%-----------------------------------------------------------------
 
53
passwd2localized_key(Alg, Passwd, EngineID) when length(Passwd) > 0 ->
 
54
    Key = mk_digest(Alg, Passwd),
 
55
    localize_key(Alg, Key, EngineID).
 
56
 
 
57
    
 
58
%%-----------------------------------------------------------------
 
59
%% Func: localize_key/3
 
60
%% Types: Alg      = md5 | sha
 
61
%%        Passwd   = string()
 
62
%%        EngineID = string()
 
63
%% Purpose: Localizes an unlocalized key for EngineID.  See rfc2274
 
64
%%          section 2.6 for a definition of localized keys.
 
65
%%-----------------------------------------------------------------
 
66
localize_key(Alg, Key, EngineID) ->
 
67
    Str = [Key, EngineID, Key],
 
68
    binary_to_list(crypto:Alg(Str)).
 
69
 
 
70
 
 
71
mk_digest(md5, Passwd) ->
 
72
    mk_md5_digest(Passwd);
 
73
mk_digest(sha, Passwd) ->
 
74
    mk_sha_digest(Passwd).
 
75
 
 
76
mk_md5_digest(Passwd) ->
 
77
    Ctx = crypto:md5_init(),
 
78
    Ctx2 = md5_loop(0, [], Ctx, Passwd, length(Passwd)),
 
79
    crypto:md5_final(Ctx2).
 
80
 
 
81
md5_loop(Count, Buf, Ctx, Passwd, PasswdLen) when Count < 1048576 ->
 
82
    {Buf64, NBuf} = mk_buf64(length(Buf), Buf, Passwd, PasswdLen),
 
83
    NCtx = crypto:md5_update(Ctx, Buf64),
 
84
    md5_loop(Count+64, NBuf, NCtx, Passwd, PasswdLen);
 
85
md5_loop(_Count, _Buf, Ctx, _Passwd, _PasswdLen) ->
 
86
    Ctx.
 
87
 
 
88
mk_sha_digest(Passwd) ->
 
89
    Ctx = crypto:sha_init(),
 
90
    Ctx2 = sha_loop(0, [], Ctx, Passwd, length(Passwd)),
 
91
    crypto:sha_final(Ctx2).
 
92
 
 
93
sha_loop(Count, Buf, Ctx, Passwd, PasswdLen) when Count < 1048576 ->
 
94
    {Buf64, NBuf} = mk_buf64(length(Buf), Buf, Passwd, PasswdLen),
 
95
    NCtx = crypto:sha_update(Ctx, Buf64),
 
96
    sha_loop(Count+64, NBuf, NCtx, Passwd, PasswdLen);
 
97
sha_loop(_Count, _Buf, Ctx, _Passwd, _PasswdLen) ->
 
98
    Ctx.
 
99
 
 
100
%% Create a 64 bytes long string, by repeating Passwd as many times 
 
101
%% as necessary. Output is the 64 byte string, and the rest of the 
 
102
%% last repetition of the Passwd. This is used as input in the next
 
103
%% invocation.
 
104
mk_buf64(BufLen, Buf, Passwd, PasswdLen) ->
 
105
    case BufLen + PasswdLen of
 
106
        TotLen when TotLen > 64 ->
 
107
            {[Buf, lists:sublist(Passwd, 64-BufLen)],
 
108
             lists:sublist(Passwd, 65-BufLen, PasswdLen)};
 
109
        TotLen ->
 
110
            mk_buf64(TotLen, [Buf, Passwd], Passwd, PasswdLen)
 
111
    end.
 
112
 
 
113
 
 
114
%%-----------------------------------------------------------------
 
115
%% Auth and priv algorithms
 
116
%%-----------------------------------------------------------------
 
117
 
 
118
auth_in(usmHMACMD5AuthProtocol, AuthKey, AuthParams, Packet) ->
 
119
    md5_auth_in(AuthKey, AuthParams, Packet);
 
120
auth_in(?usmHMACMD5AuthProtocol, AuthKey, AuthParams, Packet) ->
 
121
    md5_auth_in(AuthKey, AuthParams, Packet);
 
122
auth_in(usmHMACSHAAuthProtocol, AuthKey, AuthParams, Packet) ->
 
123
    sha_auth_in(AuthKey, AuthParams, Packet);
 
124
auth_in(?usmHMACSHAAuthProtocol, AuthKey, AuthParams, Packet) ->
 
125
    sha_auth_in(AuthKey, AuthParams, Packet).
 
126
 
 
127
auth_out(usmNoAuthProtocol, _AuthKey, _Message, _UsmSecParams) -> % 3.1.3
 
128
    error(unSupportedSecurityLevel);
 
129
auth_out(?usmNoAuthProtocol, _AuthKey, _Message, _UsmSecParams) -> % 3.1.3
 
130
    error(unSupportedSecurityLevel);
 
131
auth_out(usmHMACMD5AuthProtocol, AuthKey, Message, UsmSecParams) ->
 
132
    md5_auth_out(AuthKey, Message, UsmSecParams);
 
133
auth_out(?usmHMACMD5AuthProtocol, AuthKey, Message, UsmSecParams) ->
 
134
    md5_auth_out(AuthKey, Message, UsmSecParams);
 
135
auth_out(usmHMACSHAAuthProtocol, AuthKey, Message, UsmSecParams) ->
 
136
    sha_auth_out(AuthKey, Message, UsmSecParams);
 
137
auth_out(?usmHMACSHAAuthProtocol, AuthKey, Message, UsmSecParams) ->
 
138
    sha_auth_out(AuthKey, Message, UsmSecParams).
 
139
 
 
140
md5_auth_out(AuthKey, Message, UsmSecParams) ->
 
141
    %% 6.3.1.1
 
142
    Message2 = set_msg_auth_params(Message, UsmSecParams, ?twelwe_zeros),
 
143
    Packet = snmp_pdus:enc_message_only(Message2),
 
144
    %% 6.3.1.2-4 is done by the crypto function
 
145
    %% 6.3.1.4
 
146
    MAC = binary_to_list(crypto:md5_mac_96(AuthKey, Packet)),
 
147
    %% 6.3.1.5
 
148
    set_msg_auth_params(Message, UsmSecParams, MAC).
 
149
 
 
150
md5_auth_in(AuthKey, AuthParams, Packet) when length(AuthParams) == 12 ->
 
151
    %% 6.3.2.3
 
152
    Packet2 = patch_packet(binary_to_list(Packet)),
 
153
    %% 6.3.2.5
 
154
    MAC = binary_to_list(crypto:md5_mac_96(AuthKey, Packet2)),
 
155
    %% 6.3.2.6
 
156
    MAC == AuthParams;
 
157
md5_auth_in(_AuthKey, _AuthParams, _Packet) ->
 
158
    %% 6.3.2.1
 
159
    ?vtrace("md5_auth_in -> entry with"
 
160
            "~n   _AuthKey:    ~p"
 
161
            "~n   _AuthParams: ~p", [_AuthKey, _AuthParams]),
 
162
    false.
 
163
 
 
164
 
 
165
sha_auth_out(AuthKey, Message, UsmSecParams) ->
 
166
    %% 7.3.1.1
 
167
    Message2 = set_msg_auth_params(Message, UsmSecParams, ?twelwe_zeros),
 
168
    Packet = snmp_pdus:enc_message_only(Message2),
 
169
    %% 7.3.1.2-4 is done by the crypto function
 
170
    %% 7.3.1.4
 
171
    MAC = binary_to_list(crypto:sha_mac_96(AuthKey, Packet)),
 
172
    %% 7.3.1.5
 
173
    set_msg_auth_params(Message, UsmSecParams, MAC).
 
174
 
 
175
sha_auth_in(AuthKey, AuthParams, Packet) when length(AuthParams) == 12 ->
 
176
    %% 7.3.2.3
 
177
    Packet2 = patch_packet(binary_to_list(Packet)),
 
178
    %% 7.3.2.5
 
179
    MAC = binary_to_list(crypto:sha_mac_96(AuthKey, Packet2)),
 
180
    %% 7.3.2.6
 
181
    MAC == AuthParams;
 
182
sha_auth_in(_AuthKey, _AuthParams, _Packet) ->
 
183
    %% 7.3.2.1
 
184
    ?vtrace("sha_auth_in -> entry with"
 
185
            "~n   _AuthKey:    ~p"
 
186
            "~n   _AuthParams: ~p", [_AuthKey, _AuthParams]),
 
187
    false.
 
188
 
 
189
 
 
190
des_encrypt(PrivKey, Data, SaltFun) ->
 
191
    [A,B,C,D,E,F,G,H | PreIV] = PrivKey,
 
192
    DesKey = [A,B,C,D,E,F,G,H],
 
193
    Salt = SaltFun(),
 
194
    IV = snmp_misc:str_xor(PreIV, Salt),
 
195
    TailLen = (8 - (length(Data) rem 8)) rem 8,
 
196
    Tail = mk_tail(TailLen),
 
197
    EncData = crypto:des_cbc_encrypt(DesKey, IV, [Data,Tail]),
 
198
    {ok, binary_to_list(EncData), Salt}.
 
199
 
 
200
des_decrypt(PrivKey, MsgPrivParams, EncData) when length(MsgPrivParams) == 8 ->
 
201
    [A,B,C,D,E,F,G,H | PreIV] = PrivKey,
 
202
    DesKey = [A,B,C,D,E,F,G,H],
 
203
    Salt = MsgPrivParams,
 
204
    IV = snmp_misc:str_xor(PreIV, Salt),
 
205
    %% Whatabout errors here???  E.g. not a mulitple of 8!
 
206
    Data = binary_to_list(crypto:des_cbc_decrypt(DesKey, IV, EncData)),
 
207
    Data2 = snmp_pdus:strip_encrypted_scoped_pdu_data(Data),
 
208
    {ok, Data2}.
 
209
 
 
210
aes_encrypt(PrivKey, Data, SaltFun) ->
 
211
    AesKey = PrivKey,
 
212
    Salt = SaltFun(),
 
213
    EngineBoots = snmp_framework_mib:get_engine_boots(),
 
214
    EngineTime = snmp_framework_mib:get_engine_time(),
 
215
    IV = [?i32(EngineBoots), ?i32(EngineTime) | Salt],
 
216
    EncData = crypto:aes_cfb_128_encrypt(AesKey, IV, Data),
 
217
    {ok, binary_to_list(EncData), Salt}.
 
218
 
 
219
aes_decrypt(PrivKey, MsgPrivParams, EncData, EngineBoots, EngineTime)
 
220
  when length(MsgPrivParams) == 8 ->
 
221
    AesKey = PrivKey,
 
222
    Salt = MsgPrivParams,
 
223
    IV = [?i32(EngineBoots), ?i32(EngineTime) | Salt],
 
224
    %% Whatabout errors here???  E.g. not a mulitple of 8!
 
225
    Data = binary_to_list(crypto:aes_cfb_128_decrypt(AesKey, IV, EncData)),
 
226
    Data2 = snmp_pdus:strip_encrypted_scoped_pdu_data(Data),
 
227
    {ok, Data2}.
 
228
 
 
229
 
 
230
%%-----------------------------------------------------------------
 
231
%% Utility functions
 
232
%%-----------------------------------------------------------------
 
233
mk_tail(N) when N > 0 ->
 
234
    [0 | mk_tail(N-1)];
 
235
mk_tail(0) ->
 
236
    [].
 
237
 
 
238
set_msg_auth_params(Message, UsmSecParams, AuthParams) ->
 
239
    NUsmSecParams = 
 
240
        UsmSecParams#usmSecurityParameters{msgAuthenticationParameters =
 
241
                                           AuthParams},
 
242
    SecBytes = snmp_pdus:enc_usm_security_parameters(NUsmSecParams),
 
243
    VsnHdr   = Message#message.vsn_hdr,
 
244
    NVsnHdr  = VsnHdr#v3_hdr{msgSecurityParameters = SecBytes},
 
245
    Message#message{vsn_hdr = NVsnHdr}.
 
246
 
 
247
 
 
248
%% Not very nice...
 
249
%% This function patches the asn.1 encoded message. It changes the
 
250
%% AuthenticationParameters to 12 zeros.
 
251
%% NOTE: returns a deep list of bytes
 
252
patch_packet([48 | T]) ->
 
253
    %% Length for whole packet - 2 is tag for version
 
254
    {Len1, [2 | T1]} = split_len(T),
 
255
    %% Length for version - 48 is tag for header data
 
256
    {Len2, [Vsn,48|T2]} = split_len(T1),
 
257
    %% Length for header data
 
258
    {Len3, T3} = split_len(T2),
 
259
    [48,Len1,2,Len2,Vsn,48,Len3|pp2(dec_len(Len3),T3)].
 
260
 
 
261
%% Skip HeaderData - 4 is tag for SecurityParameters
 
262
pp2(0,[4|T]) ->
 
263
    %% 48 is tag for UsmSecParams
 
264
    {Len1,[48|T1]} = split_len(T),
 
265
    %% 4 is tag for EngineID
 
266
    {Len2,[4|T2]} = split_len(T1),
 
267
    %% Len 3 is length for EngineID
 
268
    {Len3,T3} = split_len(T2),
 
269
    [4,Len1,48,Len2,4,Len3|pp3(dec_len(Len3),T3)];
 
270
pp2(N,[H|T]) ->
 
271
    [H|pp2(N-1,T)].
 
272
 
 
273
%% Skip EngineID - 2 is tag for EngineBoots
 
274
pp3(0,[2|T]) ->
 
275
    {Len1,T1} = split_len(T),
 
276
    [2,Len1|pp4(dec_len(Len1),T1)];
 
277
pp3(N,[H|T]) ->
 
278
    [H|pp3(N-1,T)].
 
279
 
 
280
%% Skip EngineBoots - 2 is tag for EngineTime
 
281
pp4(0,[2|T]) ->
 
282
    {Len1,T1} = split_len(T),
 
283
    [2,Len1|pp5(dec_len(Len1),T1)];
 
284
pp4(N,[H|T]) ->
 
285
    [H|pp4(N-1,T)].
 
286
 
 
287
%% Skip EngineTime - 4 is tag for UserName 
 
288
pp5(0,[4|T]) ->
 
289
    {Len1,T1} = split_len(T),
 
290
    [4,Len1|pp6(dec_len(Len1),T1)];
 
291
pp5(N,[H|T]) ->
 
292
    [H|pp5(N-1,T)].
 
293
 
 
294
%% Skip UserName - 4 is tag for AuthenticationParameters
 
295
%% This is what we're looking for!
 
296
pp6(0,[4|T]) ->
 
297
    {Len1,[_,_,_,_,_,_,_,_,_,_,_,_|T1]} = split_len(T),
 
298
    12 == dec_len(Len1),
 
299
    [4,Len1,?twelwe_zeros|T1];
 
300
pp6(N,[H|T]) ->
 
301
    [H|pp6(N-1,T)].
 
302
 
 
303
 
 
304
%% Returns {LengthOctets, Rest}
 
305
split_len([Hd|Tl]) ->
 
306
    %% definite form
 
307
    case is8set(Hd) of
 
308
        0 -> % Short form
 
309
            {Hd,Tl};
 
310
        1 -> % Long form - at least one more octet
 
311
            No = clear(Hd,8),
 
312
            {DigList,Rest} = head(No,Tl),
 
313
            {[Hd | DigList], Rest}
 
314
    end.
 
315
 
 
316
dec_len(D) when integer(D) ->
 
317
    D;
 
318
dec_len([_LongOctet|T]) ->
 
319
    dl(T).
 
320
dl([D]) ->
 
321
    D;
 
322
dl([A,B]) ->
 
323
    (A bsl 8) bor B;
 
324
dl([A,B,C]) ->
 
325
    (A bsl 16) bor (B bsl 8) bor C;
 
326
dl([0 | T]) ->
 
327
    dl(T).
 
328
 
 
329
head(L,List) when length(List) == L -> {List,[]};
 
330
head(L,List) ->
 
331
    head(L,List,[]).
 
332
 
 
333
head(0,L,Res) ->
 
334
    {lists:reverse(Res),L};
 
335
 
 
336
head(Int,[H|Tail],Res) ->
 
337
    head(Int-1,Tail,[H|Res]).
 
338
 
 
339
clear(Byte,8) -> 
 
340
    Byte band 127;
 
341
clear(Byte,Pos) when Pos < 9 ->
 
342
    Mask = bnot set(0,Pos),
 
343
    Mask band Byte.
 
344
 
 
345
is8set(Byte) ->
 
346
    if
 
347
        Byte > 127 -> 1;
 
348
        true -> 0
 
349
    end.
 
350
 
 
351
set(Byte,8) -> 
 
352
    Byte bor 2#10000000;
 
353
set(Byte,Pos)  when Pos < 9 ->
 
354
    Mask = 1  bsl (Pos-1),
 
355
    Byte bor Mask.
 
356
 
 
357
error(Reason) ->
 
358
    throw({error, Reason}).
 
359