~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/crypto/src/crypto.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
21
21
-module(crypto).
22
22
 
23
23
-export([start/0, stop/0, info/0, info_lib/0]).
 
24
-export([md4/1, md4_init/0, md4_update/2, md4_final/1]).
24
25
-export([md5/1, md5_init/0, md5_update/2, md5_final/1]).
25
26
-export([sha/1, sha_init/0, sha_update/2, sha_final/1]).
 
27
%-export([sha256/1, sha256_init/0, sha256_update/2, sha256_final/1]).
 
28
%-export([sha512/1, sha512_init/0, sha512_update/2, sha512_final/1]).
26
29
-export([md5_mac/2, md5_mac_96/2, sha_mac/2, sha_mac_96/2]).
27
30
-export([des_cbc_encrypt/3, des_cbc_decrypt/3, des_cbc_ivec/1]).
28
31
-export([des3_cbc_encrypt/5, des3_cbc_decrypt/5]).
31
34
-export([exor/2]).
32
35
-export([rc4_encrypt/2, rc4_set_key/1, rc4_encrypt_with_state/2]).
33
36
-export([rc2_40_cbc_encrypt/3, rc2_40_cbc_decrypt/3]).
34
 
-export([dss_verify/3, rsa_verify/3]).
 
37
-export([dss_verify/3, rsa_verify/3, rsa_verify/4]).
 
38
-export([dss_sign/2, rsa_sign/2, rsa_sign/3]).
 
39
-export([rsa_public_encrypt/3, rsa_private_decrypt/3]).
 
40
-export([rsa_private_encrypt/3, rsa_public_decrypt/3]).
 
41
-export([dh_generate_key/1, dh_generate_key/2, dh_compute_key/3]).
35
42
-export([rand_bytes/1, rand_bytes/3, rand_uniform/2]).
36
43
-export([mod_exp/3, mpint/1, erlint/1]).
37
44
%% -export([idea_cbc_encrypt/3, idea_cbc_decrypt/3]).
38
45
-export([aes_cbc_128_encrypt/3, aes_cbc_128_decrypt/3]).
39
46
-export([aes_cbc_256_encrypt/3, aes_cbc_256_decrypt/3]).
40
47
 
 
48
-export([dh_generate_parameters/2, dh_check/1]). %% Testing see below
41
49
 
42
50
-define(INFO,            0).
43
51
-define(MD5,             1).
62
70
-define(RAND_UNIFORM,    20).
63
71
-define(MOD_EXP,         21).
64
72
-define(DSS_VERIFY,      22).
65
 
-define(RSA_VERIFY,      23).
 
73
-define(RSA_VERIFY_SHA,  23).
 
74
%-define(RSA_VERIFY_MD5,         35).
66
75
-define(AES_CBC_128_ENCRYPT, 24).
67
76
-define(AES_CBC_128_DECRYPT, 25).
68
77
-define(XOR,             26).
74
83
-define(AES_CBC_256_ENCRYPT, 32).
75
84
-define(AES_CBC_256_DECRYPT, 33).
76
85
-define(INFO_LIB,34).
 
86
%-define(RSA_VERIFY_SHA,         23).
 
87
-define(RSA_VERIFY_MD5,  35).
 
88
-define(RSA_SIGN_SHA,    36).
 
89
-define(RSA_SIGN_MD5,    37).
 
90
-define(DSS_SIGN,        38).
 
91
-define(RSA_PUBLIC_ENCRYPT,  39).
 
92
-define(RSA_PRIVATE_DECRYPT, 40).
 
93
-define(RSA_PRIVATE_ENCRYPT, 41).
 
94
-define(RSA_PUBLIC_DECRYPT,  42).
 
95
-define(DH_GENERATE_PARAMS,  43).
 
96
-define(DH_CHECK,            44).
 
97
-define(DH_GENERATE_KEY,     45).
 
98
-define(DH_COMPUTE_KEY,      46).
 
99
-define(MD4,             47).
 
100
-define(MD4_INIT,        48).
 
101
-define(MD4_UPDATE,      49).
 
102
-define(MD4_FINAL,       50).
 
103
 
 
104
%% -define(SHA256,               51).
 
105
%% -define(SHA256_INIT,  52).
 
106
%% -define(SHA256_UPDATE,        53).
 
107
%% -define(SHA256_FINAL,         54).
 
108
%% -define(SHA512,               55).
 
109
%% -define(SHA512_INIT,  56).
 
110
%% -define(SHA512_UPDATE,        57).
 
111
%% -define(SHA512_FINAL,         58).
 
112
 
 
113
 
77
114
%% -define(IDEA_CBC_ENCRYPT, 34).
78
115
%% -define(IDEA_CBC_DECRYPT, 35).
79
116
 
80
 
 
81
 
-define(FUNC_LIST, [md5,
82
 
                    md5_init,
83
 
                    md5_update,
84
 
                    md5_final,
85
 
                    sha,
86
 
                    sha_init,
87
 
                    sha_update,
88
 
                    sha_final,
89
 
                    md5_mac,
90
 
                    md5_mac_96,
91
 
                    sha_mac,
92
 
                    sha_mac_96,
 
117
-define(FUNC_LIST, [md4, md4_init, md4_update, md4_final,
 
118
                    md5, md5_init, md5_update, md5_final,
 
119
                    sha, sha_init, sha_update, sha_final,
 
120
%%                  sha256, sha256_init, sha256_update, sha256_final,
 
121
%%                  sha512, sha512_init, sha512_update, sha512_final,
 
122
                    md5_mac,  md5_mac_96,
 
123
                    sha_mac,  sha_mac_96,
93
124
                    des_cbc_encrypt, des_cbc_decrypt,
94
125
                    des_ede3_cbc_encrypt, des_ede3_cbc_decrypt,
95
126
                    aes_cfb_128_encrypt, aes_cfb_128_decrypt,
96
127
                    rand_bytes,
97
128
                    rand_uniform,
98
129
                    mod_exp,
99
 
                    dss_verify,
100
 
                    rsa_verify,
 
130
                    dss_verify,dss_sign,
 
131
                    rsa_verify,rsa_sign,
 
132
                    rsa_public_encrypt,rsa_private_decrypt, 
 
133
                    rsa_private_encrypt,rsa_public_decrypt, 
 
134
                    dh_generate_key, dh_compute_key,
101
135
                    aes_cbc_128_encrypt, aes_cbc_128_decrypt,
102
136
                    exor,
103
137
                    rc4_encrypt, rc4_set_key, rc4_encrypt_with_state,
113
147
    application:stop(crypto).
114
148
 
115
149
info() ->
116
 
    lists:map(fun(I) -> lists:nth(I, ?FUNC_LIST) end, 
117
 
              binary_to_list(control(?INFO, []))).
 
150
    lists:map(fun(I) -> 
 
151
                      lists:nth(I, ?FUNC_LIST) 
 
152
              end, binary_to_list(control(?INFO, []))).
118
153
 
119
154
info_lib() ->
120
155
    <<_DrvVer:8, NameSize:8, Name:NameSize/binary,
144
179
    control(?MD5_FINAL, Context).
145
180
 
146
181
%%
 
182
%%  MD4
 
183
%%
 
184
md4(Data) ->
 
185
    control(?MD4, Data).
 
186
 
 
187
md4_init() ->
 
188
    control(?MD4_INIT, []).
 
189
 
 
190
md4_update(Context, Data) ->
 
191
    control(?MD4_UPDATE, [Context, Data]).
 
192
 
 
193
md4_final(Context) ->
 
194
    control(?MD4_FINAL, Context).
 
195
 
 
196
%%
147
197
%% SHA
148
198
%%
149
199
sha(Data) ->
158
208
sha_final(Context) ->
159
209
    control(?SHA_FINAL, Context).
160
210
 
 
211
%% sha256 and sha512 requires openssl-0.9.8 removed for now
 
212
 
 
213
%% sha256(Data) ->
 
214
%%     control(?SHA256, Data).
 
215
 
 
216
%% sha256_init() ->
 
217
%%     control(?SHA256_INIT, []).
 
218
 
 
219
%% sha256_update(Context, Data) ->
 
220
%%     control(?SHA256_UPDATE, [Context, Data]).
 
221
 
 
222
%% sha256_final(Context) ->
 
223
%%         control(?SHA256_FINAL, Context).
 
224
 
 
225
%% sha512(Data) ->
 
226
%%     control(?SHA512, Data).
 
227
 
 
228
%% sha512_init() ->
 
229
%%     control(?SHA512_INIT, []).
 
230
 
 
231
%% sha512_update(Context, Data) ->
 
232
%%     control(?SHA512_UPDATE, [Context, Data]).
 
233
 
 
234
%% sha512_final(Context) ->
 
235
%%     control(?SHA512_FINAL, Context).
 
236
 
161
237
%%
162
238
%%  MESSAGE AUTHENTICATION CODES
163
239
%%
286
362
%% DSS, RSA - verify
287
363
%%
288
364
 
289
 
dss_verify(Dgst,Signature,Key) ->
290
 
    control(?DSS_VERIFY, [Dgst,Signature,Key]) == <<1>>.
291
 
 
292
 
rsa_verify(Dgst,Signature,Key) ->
293
 
    control(?RSA_VERIFY, [Dgst,Signature,Key]) == <<1>>.
294
 
 
 
365
%% Key = [P,Q,G,Y]   P,Q,G=DSSParams  Y=PublicKey
 
366
dss_verify(Data,Signature,Key) ->
 
367
    control(?DSS_VERIFY, [Data,Signature,Key]) == <<1>>.
 
368
 
 
369
% Key = [E,N]  E=PublicExponent N=PublicModulus
 
370
rsa_verify(Data,Signature,Key) ->
 
371
    rsa_verify(sha, Data,Signature,Key).
 
372
rsa_verify(Type,Data,Signature,Key) ->
 
373
    control(rsa_verify_digest_type(Type), [Data,Signature,Key]) == <<1>>.
 
374
 
 
375
rsa_verify_digest_type(md5) -> ?RSA_VERIFY_MD5;
 
376
rsa_verify_digest_type(sha) -> ?RSA_VERIFY_SHA;
 
377
rsa_verify_digest_type(Bad) -> erlang:error(badarg, [Bad]).
 
378
 
 
379
%%
 
380
%% DSS, RSA - sign
 
381
%%
 
382
%% Key = [P,Q,G,X]   P,Q,G=DSSParams  X=PrivateKey
 
383
dss_sign(Data, Key) ->
 
384
    <<Ret:8, Signature/binary>> = control(?DSS_SIGN, [Data,Key]),
 
385
    case Ret of
 
386
        1 -> Signature;
 
387
        0 -> erlang:error(badkey, [Data, Key])
 
388
    end.
 
389
 
 
390
%% Key = [E,N,D]  E=PublicExponent N=PublicModulus  D=PrivateExponent
 
391
rsa_sign(Data,Key) ->
 
392
    rsa_sign(sha, Data, Key).
 
393
rsa_sign(Type, Data, Key) ->
 
394
    <<Ret:8, Signature/binary>> = control(rsa_sign_digest_type(Type), [Data,Key]),
 
395
    case Ret of
 
396
        1 -> Signature;
 
397
        0 -> erlang:error(badkey, [Type,Data,Key])
 
398
    end.
 
399
 
 
400
rsa_sign_digest_type(md5) -> ?RSA_SIGN_MD5;
 
401
rsa_sign_digest_type(sha) -> ?RSA_SIGN_SHA;
 
402
rsa_sign_digest_type(Bad) -> erlang:error(badarg, [Bad]).
 
403
 
 
404
%%
 
405
%%  rsa_public_encrypt
 
406
%%  rsa_private_decrypt
 
407
 
 
408
%% Binary, Key = [E,N]
 
409
rsa_public_encrypt(BinMesg, Key, Padding) ->
 
410
    Size = iolist_size(BinMesg),
 
411
    <<Ret:8, Signature/binary>> = 
 
412
        control(?RSA_PUBLIC_ENCRYPT, [<<Size:32>>,BinMesg,Key,rsa_pad(Padding)]),
 
413
    case Ret of
 
414
        1 -> Signature;
 
415
        0 -> erlang:error(encrypt_failed, [BinMesg,Key, Padding])
 
416
    end.    
 
417
 
 
418
%% Binary, Key = [E,N,D]
 
419
rsa_private_decrypt(BinMesg, Key, Padding) ->
 
420
    Size = iolist_size(BinMesg),
 
421
    <<Ret:8, Signature/binary>> = 
 
422
        control(?RSA_PRIVATE_DECRYPT, [<<Size:32>>,BinMesg,Key,rsa_pad(Padding)]),
 
423
    case Ret of
 
424
        1 -> Signature;
 
425
        0 -> erlang:error(decrypt_failed, [BinMesg,Key, Padding])
 
426
    end.    
 
427
 
 
428
rsa_pad(rsa_pkcs1_padding) -> 1;
 
429
rsa_pad(rsa_pkcs1_oaep_padding) -> 2;
 
430
%% rsa_pad(rsa_sslv23_padding) -> 3;
 
431
rsa_pad(rsa_no_padding) -> 0;
 
432
rsa_pad(Bad) -> erlang:error(badarg, [Bad]).
 
433
    
 
434
%% Binary, Key = [E,N,D]
 
435
rsa_private_encrypt(BinMesg, Key, Padding) ->
 
436
    Size = iolist_size(BinMesg),
 
437
    <<Ret:8, Signature/binary>> = 
 
438
        control(?RSA_PRIVATE_ENCRYPT, [<<Size:32>>,BinMesg,Key,rsa_pad(Padding)]),
 
439
    case Ret of
 
440
        1 -> Signature;
 
441
        0 -> erlang:error(encrypt_failed, [BinMesg,Key, Padding])
 
442
    end.    
 
443
 
 
444
%% Binary, Key = [E,N]
 
445
rsa_public_decrypt(BinMesg, Key, Padding) ->
 
446
    Size = iolist_size(BinMesg),
 
447
    <<Ret:8, Signature/binary>> = 
 
448
        control(?RSA_PUBLIC_DECRYPT, [<<Size:32>>,BinMesg,Key,rsa_pad(Padding)]),
 
449
    case Ret of
 
450
        1 -> Signature;
 
451
        0 -> erlang:error(decrypt_failed, [BinMesg,Key, Padding])
 
452
    end.
 
453
    
295
454
%%
296
455
%% AES - with 128 or 256 bit key in cipher block chaining mode (CBC)
297
456
%%
340
499
    control(?RC2_40_CBC_DECRYPT, [Key, IVec, Data]).
341
500
 
342
501
%%
 
502
%% DH Diffie-Hellman functions
 
503
%% 
 
504
 
 
505
%% Generate (and check) Parameters is not documented because they are implemented
 
506
%% for testing (and offline parameter generation) only.
 
507
%% From the openssl doc: 
 
508
%%  DH_generate_parameters() may run for several hours before finding a suitable prime.
 
509
%% Thus dh_generate_parameters may in this implementation block 
 
510
%% the emulator for several hours.
 
511
%%
 
512
%% usage: dh_generate_parameters(1024, 2 or 5) -> 
 
513
%%    [Prime=mpint(), SharedGenerator=mpint()]
 
514
dh_generate_parameters(PrimeLen, Generator) 
 
515
  when is_integer(PrimeLen), is_integer(Generator) ->
 
516
    case control(?DH_GENERATE_PARAMS, <<PrimeLen:32, Generator:32>>) of
 
517
        <<0:8, _/binary>> ->
 
518
            erlang:error(generation_failed, [PrimeLen,Generator]);
 
519
        <<1:8, PLen0:32, _:PLen0/binary, GLen0:32,_:GLen0/binary>> = Bin -> 
 
520
            PLen = PLen0+4, 
 
521
            GLen = GLen0+4,
 
522
            <<_:8, PBin:PLen/binary,GBin:GLen/binary>> = Bin,
 
523
            [PBin, GBin]
 
524
    end.
 
525
 
 
526
%% Checks that the DHParameters are ok.
 
527
%% DHParameters = [P (Prime)= mpint(), G(Generator) = mpint()]
 
528
dh_check(DHParameters) ->
 
529
    case control(?DH_CHECK, DHParameters) of
 
530
        <<0:32>>  -> ok;
 
531
        <<_:24,_:1,_:1,_:1,1:1>> -> not_prime;
 
532
        <<_:24,_:1,_:1,1:1,0:1>> -> not_strong_prime;
 
533
        <<_:24,_:1,1:1,0:1,0:1>> -> unable_to_check_generator;
 
534
        <<_:24,1:1,0:1,0:1,0:1>> -> not_suitable_generator;
 
535
        <<16#FFFF:32>> -> {error, check_failed};
 
536
        <<X:32>>  -> {unknown, X}
 
537
    end.
 
538
 
 
539
%% DHParameters = [P (Prime)= mpint(), G(Generator) = mpint()]
 
540
%% PrivKey = mpint()
 
541
dh_generate_key(DHParameters) ->
 
542
    dh_generate_key(<<0:32>>, DHParameters).
 
543
dh_generate_key(PrivateKey, DHParameters) ->
 
544
    case control(?DH_GENERATE_KEY, [PrivateKey, DHParameters]) of
 
545
        <<0:8, _/binary>> ->
 
546
            erlang:error(generation_failed, [PrivateKey,DHParameters]);
 
547
        Bin = <<1:8, PubLen0:32, _:PubLen0/binary, PrivLen0:32, _:PrivLen0/binary>> -> 
 
548
            PubLen = PubLen0+4, 
 
549
            PrivLen = PrivLen0+4,
 
550
            <<_:8, PubBin:PubLen/binary,PrivBin:PrivLen/binary>> = Bin,
 
551
            {PubBin, PrivBin}
 
552
    end.
 
553
 
 
554
%% DHParameters = [P (Prime)= mpint(), G(Generator) = mpint()]
 
555
%% MyPrivKey, OthersPublicKey = mpint() 
 
556
dh_compute_key(OthersPublicKey, MyPrivateKey, DHParameters) ->
 
557
    case control(?DH_COMPUTE_KEY, [OthersPublicKey, MyPrivateKey, DHParameters]) of
 
558
        <<0:8, _/binary>> ->
 
559
            erlang:error(computation_failed, [OthersPublicKey,MyPrivateKey,DHParameters]);
 
560
        <<1:8, Binary/binary>> -> Binary
 
561
    end.
 
562
 
 
563
%%
343
564
%%  LOCAL FUNCTIONS
344
565
%%
345
566
control_bin(Cmd, Key, Data) ->