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

« back to all changes in this revision

Viewing changes to lib/crypto/src/crypto.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:
27
27
-export([des_cbc_encrypt/3, des_cbc_decrypt/3, des_cbc_ivec/1]).
28
28
-export([des3_cbc_encrypt/5, des3_cbc_decrypt/5]).
29
29
-export([des_ede3_cbc_encrypt/5, des_ede3_cbc_decrypt/5]).
 
30
-export([aes_cfb_128_encrypt/3, aes_cfb_128_decrypt/3]).
 
31
-export([rand_bytes/1,
 
32
         rand_bytes/3,
 
33
         rand_uniform/2,
 
34
         mod_exp/3,
 
35
         dss_verify/3,
 
36
         rsa_verify/3,
 
37
         aes_cbc_128_encrypt/3,
 
38
         aes_cbc_128_decrypt/3,
 
39
         mpint/1, erlint/1]).
 
40
 
30
41
 
31
42
-define(INFO,            0).
32
43
-define(MD5,             1).
45
56
-define(DES_CBC_DECRYPT, 14).
46
57
-define(DES_EDE3_CBC_ENCRYPT, 15).
47
58
-define(DES_EDE3_CBC_DECRYPT, 16).
 
59
-define(AES_CFB_128_ENCRYPT, 17).
 
60
-define(AES_CFB_128_DECRYPT, 18).
 
61
-define(RAND_BYTES,      19).
 
62
-define(RAND_UNIFORM,    20).
 
63
-define(MOD_EXP,         21).
 
64
-define(DSS_VERIFY,      22).
 
65
-define(RSA_VERIFY,      23).
 
66
-define(AES_CBC_128_ENCRYPT, 24).
 
67
-define(AES_CBC_128_DECRYPT, 25).
48
68
 
49
69
-define(FUNC_LIST, [md5,
50
70
                    md5_init,
61
81
                    des_cbc_encrypt,
62
82
                    des_cbc_decrypt,
63
83
                    des_ede3_cbc_encrypt,
64
 
                    des_ede3_cbc_decrypt]).
 
84
                    des_ede3_cbc_decrypt,
 
85
                    aes_cfb_128_encrypt,
 
86
                    aes_cfb_128_decrypt,
 
87
                    rand_bytes,
 
88
                    rand_uniform,
 
89
                    mod_exp,
 
90
                    dss_verify,
 
91
                    rsa_verify,
 
92
                    aes_cbc_128_encrypt,
 
93
                    aes_cbc_128_decrypt]).
65
94
 
66
95
start() ->
67
96
    application:start(crypto).
163
192
des3_cbc_encrypt(Key1, Key2, Key3, IVec, Data) ->
164
193
    des_ede3_cbc_encrypt(Key1, Key2, Key3, IVec, Data).
165
194
des_ede3_cbc_encrypt(Key1, Key2, Key3, IVec, Data) ->
 
195
    %%io:format("des_ede3_cbc_encrypt: size(Data)=~p\n", [size(list_to_binary([Data]))]),
166
196
    control(?DES_EDE3_CBC_ENCRYPT, [Key1, Key2, Key3, IVec, Data]).
167
197
 
168
198
des3_cbc_decrypt(Key1, Key2, Key3, IVec, Data) ->
170
200
des_ede3_cbc_decrypt(Key1, Key2, Key3, IVec, Data) ->
171
201
    control(?DES_EDE3_CBC_DECRYPT, [Key1, Key2, Key3, IVec, Data]).
172
202
 
 
203
%%
 
204
%% AES in cipher feedback mode (CFB)
 
205
%%
 
206
aes_cfb_128_encrypt(Key, IVec, Data) ->
 
207
    control(?AES_CFB_128_ENCRYPT, [Key, IVec, Data]).
 
208
 
 
209
aes_cfb_128_decrypt(Key, IVec, Data) ->
 
210
    control(?AES_CFB_128_DECRYPT, [Key, IVec, Data]).    
 
211
 
 
212
 
 
213
%% 
 
214
%% RAND - pseudo random numbers using RN_ functions in crypto lib
 
215
%%
 
216
 
 
217
rand_bytes(Bytes) ->
 
218
    rand_bytes(Bytes, 0, 0).
 
219
rand_bytes(Bytes, Topmask, Bottommask) ->
 
220
    control(?RAND_BYTES,[<<Bytes:32/integer,
 
221
                          Topmask:8/integer,
 
222
                          Bottommask:8/integer>>]).
 
223
 
 
224
rand_uniform(From,To) when binary(From), binary(To) ->
 
225
    case control(?RAND_UNIFORM,[From,To]) of
 
226
        <<Len:32/integer, MSB, Rest/binary>> when MSB > 127 ->
 
227
            <<(Len + 1):32/integer, 0, MSB, Rest/binary>>;
 
228
        Whatever ->
 
229
            Whatever
 
230
    end;
 
231
rand_uniform(From,To) when integer(From),integer(To) ->
 
232
    BinFrom = mpint(From),
 
233
    BinTo = mpint(To),
 
234
    case rand_uniform(BinFrom, BinTo) of
 
235
        Result when binary(Result) ->
 
236
            erlint(Result);
 
237
        Other ->
 
238
            Other
 
239
    end.
 
240
 
 
241
%%
 
242
%% mod_exp - utility for rsa generation
 
243
%%
 
244
mod_exp(Base, Exponent, Modulo)
 
245
  when integer(Base), integer(Exponent), integer(Modulo) ->
 
246
    erlint(mod_exp(mpint(Base), mpint(Exponent), mpint(Modulo)));
 
247
 
 
248
mod_exp(Base, Exponent, Modulo) ->
 
249
    case control(?MOD_EXP,[Base,Exponent,Modulo]) of
 
250
        <<Len:32/integer, MSB, Rest/binary>> when MSB > 127 ->
 
251
            <<(Len + 1):32/integer, 0, MSB, Rest/binary>>;
 
252
        Whatever ->
 
253
            Whatever
 
254
    end.
 
255
 
 
256
%%
 
257
%% DSS, RSA - verify
 
258
%%
 
259
 
 
260
dss_verify(Dgst,Signature,Key) ->
 
261
    control(?DSS_VERIFY, [Dgst,Signature,Key]) == <<1>>.
 
262
 
 
263
rsa_verify(Dgst,Signature,Key) ->
 
264
    control(?RSA_VERIFY, [Dgst,Signature,Key]) == <<1>>.
 
265
 
 
266
%%
 
267
%% AES - with 128 bit key in cipher block chaining mode (CBC)
 
268
%%
 
269
 
 
270
aes_cbc_128_encrypt(Key, IVec, Data) ->
 
271
    control(?AES_CBC_128_ENCRYPT, [Key, IVec, Data]).
 
272
 
 
273
aes_cbc_128_decrypt(Key, IVec, Data) ->
 
274
    control(?AES_CBC_128_DECRYPT, [Key, IVec, Data]).
 
275
 
 
276
 
173
277
 
174
278
%%
175
279
%%  LOCAL FUNCTIONS
176
280
%%
177
 
control_bin(Cmd, Key, Data) when binary(Key) ->
178
 
    control(Cmd, [sizehdr(size(Key)), Key, Data]);
179
 
control_bin(Cmd, Key, Data) when list(Key) ->
180
 
    control(Cmd, [sizehdr(flen(Key)), Key, Data]).
 
281
control_bin(Cmd, Key, Data) ->
 
282
    Sz = flen(Key),
 
283
    control(Cmd, [<<Sz:32/integer-unsigned>>, Key, Data]).
181
284
 
182
285
control(Cmd, Data) ->
183
286
    [{port, Port}| _] = ets:lookup(crypto_server_table, port),
184
287
    erlang:port_control(Port, Cmd, Data).
185
288
 
186
 
sizehdr(N) ->
187
 
    [(N bsr 24) band 255,
188
 
     (N bsr 16) band 255,
189
 
     (N bsr  8) band 255,
190
 
     N band 255].
 
289
%% sizehdr(N) ->
 
290
%%     [(N bsr 24) band 255,
 
291
%%      (N bsr 16) band 255,
 
292
%%      (N bsr  8) band 255,
 
293
%%      N band 255].
191
294
 
192
 
%% Flat length of IOlist
 
295
%% Flat length of IOlist (or binary)
 
296
flen(L) when binary(L) ->
 
297
    size(L);
193
298
flen(L) ->
194
299
    flen(L, 0).
195
300
 
201
306
    flen(T, N + 1);
202
307
flen([], N) ->
203
308
    N.
 
309
 
 
310
%% large integer in a binary with 32bit length
 
311
%% MP representaion  (SSH2)
 
312
mpint(X) when X < 0 ->
 
313
    case X of
 
314
        -1 ->
 
315
            <<0,0,0,1,16#ff>>;      
 
316
       _ ->
 
317
            mpint_neg(X,0,[])
 
318
    end;
 
319
mpint(X) ->
 
320
    case X of 
 
321
        0 ->
 
322
            <<0,0,0,0>>;
 
323
        _ ->
 
324
            mpint_pos(X,0,[])
 
325
    end.
 
326
 
 
327
-define(UINT32(X),   X:32/unsigned-big-integer).
 
328
 
 
329
mpint_neg(-1,I,Ds=[MSB|_]) ->
 
330
    if MSB band 16#80 =/= 16#80 ->
 
331
            <<?UINT32((I+1)), (list_to_binary([255|Ds]))/binary>>;
 
332
       true ->
 
333
            (<<?UINT32(I), (list_to_binary(Ds))/binary>>)
 
334
    end;
 
335
mpint_neg(X,I,Ds)  ->
 
336
    mpint_neg(X bsr 8,I+1,[(X band 255)|Ds]).
 
337
    
 
338
mpint_pos(0,I,Ds=[MSB|_]) ->
 
339
    if MSB band 16#80 == 16#80 ->
 
340
            <<?UINT32((I+1)), (list_to_binary([0|Ds]))/binary>>;
 
341
       true ->
 
342
            (<<?UINT32(I), (list_to_binary(Ds))/binary>>)
 
343
    end;
 
344
mpint_pos(X,I,Ds) ->
 
345
    mpint_pos(X bsr 8,I+1,[(X band 255)|Ds]).
 
346
 
 
347
%% int from integer in a binary with 32bit length
 
348
erlint(<<MPIntSize:32/integer,MPIntValue/binary>>) ->
 
349
    Bits= MPIntSize * 8,
 
350
    <<Integer:Bits/integer>> = MPIntValue,
 
351
    Integer.