~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/crypto/test/crypto_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
-module(crypto_SUITE).
 
20
 
 
21
-include_lib("test_server/include/test_server.hrl").
 
22
 
 
23
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, 
 
24
         init_per_testcase/2,
 
25
         end_per_testcase/2,
 
26
         info/1,
 
27
         link_test/1,
 
28
         md5/1,
 
29
         md5_update/1,
 
30
         md4/1,
 
31
         md4_update/1,
 
32
         sha/1,
 
33
         sha_update/1,
 
34
         sha256/1,
 
35
         sha256_update/1,
 
36
         sha512/1,
 
37
         sha512_update/1,
 
38
         md5_mac/1,
 
39
         md5_mac_io/1,
 
40
         des_cbc/1,
 
41
         des_cbc_iter/1,
 
42
         des_ecb/1,
 
43
         aes_cfb/1,
 
44
         aes_cbc/1,
 
45
         aes_cbc_iter/1,
 
46
         aes_ctr/1,
 
47
         mod_exp_test/1,
 
48
         rand_uniform_test/1,
 
49
         rsa_verify_test/1,
 
50
         dsa_verify_test/1,
 
51
         rsa_sign_test/1,
 
52
         dsa_sign_test/1,        
 
53
         rsa_encrypt_decrypt/1,
 
54
         dh/1,
 
55
         exor_test/1,
 
56
         rc4_test/1,
 
57
         rc4_stream_test/1,
 
58
         blowfish_cfb64/1,
 
59
         smp/1,
 
60
         cleanup/1]).
 
61
 
 
62
-export([hexstr2bin/1]).
 
63
 
 
64
suite() -> [{ct_hooks,[ts_install_cth]}].
 
65
 
 
66
all() -> 
 
67
    [link_test, md5, md5_update, md4, md4_update, md5_mac,
 
68
     md5_mac_io, sha, sha_update, 
 
69
     %% sha256, sha256_update, sha512,sha512_update,
 
70
     des_cbc, aes_cfb, aes_cbc,
 
71
     aes_cbc_iter, aes_ctr, des_cbc_iter, des_ecb, rand_uniform_test,
 
72
     rsa_verify_test, dsa_verify_test, rsa_sign_test,
 
73
     dsa_sign_test, rsa_encrypt_decrypt, dh, exor_test,
 
74
     rc4_test, rc4_stream_test, mod_exp_test, blowfish_cfb64,
 
75
     smp].
 
76
 
 
77
groups() -> 
 
78
    [].
 
79
 
 
80
init_per_suite(Config) ->
 
81
    Config.
 
82
 
 
83
end_per_suite(_Config) ->
 
84
    ok.
 
85
 
 
86
init_per_group(_GroupName, Config) ->
 
87
    Config.
 
88
 
 
89
end_per_group(_GroupName, Config) ->
 
90
    Config.
 
91
 
 
92
init_per_testcase(_Name,Config) ->
 
93
    io:format("init_per_testcase\n"),
 
94
    ?line crypto:start(),
 
95
    Config.
 
96
 
 
97
end_per_testcase(_Name,Config) ->
 
98
    io:format("end_per_testcase\n"),
 
99
    ?line crypto:stop(),
 
100
    Config.
 
101
 
 
102
%%
 
103
%%
 
104
link_test(doc) ->
 
105
    ["Test that the library is statically linked to libcrypto.a."];
 
106
link_test(suite) ->
 
107
    [];
 
108
link_test(Config) when is_list(Config) ->
 
109
    ?line case os:type() of
 
110
              {unix,darwin} -> {skipped,"Darwin cannot link statically"};
 
111
              {unix,_} -> link_test_1();
 
112
              _ -> {skip,"Only runs on Unix"}
 
113
          end.
 
114
 
 
115
link_test_1() ->    
 
116
    ?line CryptoPriv = code:priv_dir(crypto),
 
117
    ?line Wc = filename:join([CryptoPriv,"lib","crypto.*"]),
 
118
    ?line case filelib:wildcard(Wc) of
 
119
              [] -> {skip,"Didn't find the crypto driver"};
 
120
              [Drv] -> link_test_2(Drv)
 
121
          end.
 
122
 
 
123
link_test_2(Drv) ->
 
124
    case ldd_program() of
 
125
        none ->
 
126
            {skip,"No ldd-like program found"};
 
127
        Ldd ->
 
128
            Cmd = Ldd ++ " " ++ Drv,
 
129
            Libs = os:cmd(Cmd),
 
130
            io:format("~p\n", [Libs]),
 
131
            case string:str(Libs, "libcrypto") of
 
132
                0 -> ok;
 
133
                _ ->
 
134
                    case ?t:is_commercial() of
 
135
                        true ->
 
136
                            ?t:fail({libcrypto,not_statically_linked});
 
137
                        false ->
 
138
                            {comment,"Not statically linked (OK for open-source platform)"}
 
139
                    end
 
140
            end
 
141
    end.
 
142
 
 
143
ldd_program() ->
 
144
    case os:find_executable("ldd") of
 
145
        false ->
 
146
            case os:type() of
 
147
                {unix,darwin} ->
 
148
                    case os:find_executable("otool") of
 
149
                        false -> none;
 
150
                        Otool -> Otool ++ " -L"
 
151
                    end
 
152
            end;
 
153
        Ldd when is_list(Ldd) -> Ldd
 
154
    end.
 
155
 
 
156
%%
 
157
%%
 
158
info(doc) ->
 
159
    ["Call the info function."];
 
160
info(suite) ->
 
161
    [];
 
162
info(Config) when is_list(Config) ->
 
163
    case {code:lib_dir(crypto),?t:is_commercial()} of
 
164
        {{error,bad_name},false} ->
 
165
            {skip,"Missing crypto application"};
 
166
        {_,_} ->
 
167
            ?line crypto:start(),
 
168
            ?line crypto:info(),
 
169
            ?line InfoLib = crypto:info_lib(),
 
170
            ?line [_|_] = InfoLib,
 
171
            F = fun([{Name,VerN,VerS}|T],Me) ->
 
172
                        ?line true = is_binary(Name),
 
173
                        ?line true = is_integer(VerN),
 
174
                        ?line true = is_binary(VerS),
 
175
                        Me(T,Me);
 
176
                   ([],_) ->
 
177
                        ok
 
178
                end,        
 
179
            ?line F(InfoLib,F),
 
180
            ?line crypto:stop()
 
181
    end.
 
182
 
 
183
cleanup(doc) ->
 
184
    ["Cleanup (dummy)."];
 
185
cleanup(suite) ->
 
186
    [];
 
187
cleanup(Config) when is_list(Config) ->
 
188
    Config.
 
189
 
 
190
%%
 
191
%%
 
192
md5(doc) ->
 
193
    ["Generate MD5 message digests and check the result. Examples are "
 
194
     "from RFC-1321."];
 
195
md5(suite) ->
 
196
    [];
 
197
md5(Config) when is_list(Config) ->
 
198
    ?line m(crypto:md5(""), 
 
199
                hexstr2bin("d41d8cd98f00b204e9800998ecf8427e")),
 
200
    ?line m(crypto:md5("a"), 
 
201
                hexstr2bin("0cc175b9c0f1b6a831c399e269772661")),
 
202
    ?line m(crypto:md5("abc"), 
 
203
                hexstr2bin("900150983cd24fb0d6963f7d28e17f72")),
 
204
    ?line m(crypto:md5("message digest"),
 
205
                hexstr2bin("f96b697d7cb7938d525a2f31aaf161d0")),
 
206
    ?line m(crypto:md5("abcdefghijklmnopqrstuvwxyz"),
 
207
            hexstr2bin("c3fcd3d76192e4007dfb496cca67e13b")),
 
208
    ?line m(crypto:md5("ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
 
209
                     "0123456789"),  
 
210
            hexstr2bin("d174ab98d277d9f5a5611c2c9f419d9f")),
 
211
    ?line m(crypto:md5("12345678901234567890123456789012345678901234567890"
 
212
                     "123456789012345678901234567890"),
 
213
            hexstr2bin("57edf4a22be3c955ac49da2e2107b67a")).
 
214
 
 
215
%%
 
216
%%
 
217
md5_update(doc) ->
 
218
    ["Generate MD5 message using md5_init, md5_update, and md5_final, and"
 
219
     "check the result. Examples are from RFC-1321."];
 
220
md5_update(suite) ->
 
221
    [];
 
222
md5_update(Config) when is_list(Config) ->
 
223
    ?line Ctx = crypto:md5_init(),
 
224
    ?line Ctx1 = crypto:md5_update(Ctx, "ABCDEFGHIJKLMNOPQRSTUVWXYZ"),
 
225
    ?line Ctx2 = crypto:md5_update(Ctx1, "abcdefghijklmnopqrstuvwxyz"
 
226
                                   "0123456789"),
 
227
    ?line m(crypto:md5_final(Ctx2),  
 
228
            hexstr2bin("d174ab98d277d9f5a5611c2c9f419d9f")).
 
229
 
 
230
%%
 
231
%%
 
232
md4(doc) ->
 
233
    ["Generate MD4 message digests and check the result. Examples are "
 
234
     "from RFC-1321."];
 
235
md4(suite) ->
 
236
    [];
 
237
md4(Config) when is_list(Config) ->
 
238
    ?line m(crypto:md4(""), 
 
239
            hexstr2bin("31d6cfe0d16ae931b73c59d7e0c089c0")),
 
240
    ?line m(crypto:md4("a"), 
 
241
            hexstr2bin("bde52cb31de33e46245e05fbdbd6fb24")),
 
242
    ?line m(crypto:md4("abc"), 
 
243
            hexstr2bin("a448017aaf21d8525fc10ae87aa6729d")),
 
244
    ?line m(crypto:md4("message digest"),
 
245
            hexstr2bin("d9130a8164549fe818874806e1c7014b")),
 
246
    ?line m(crypto:md4("abcdefghijklmnopqrstuvwxyz"),
 
247
            hexstr2bin("d79e1c308aa5bbcdeea8ed63df412da9")),
 
248
    ?line m(crypto:md4("ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz"
 
249
                       "0123456789"),  
 
250
            hexstr2bin("043f8582f241db351ce627e153e7f0e4")),
 
251
    ?line m(crypto:md4("12345678901234567890123456789012345678901234567890"
 
252
                       "123456789012345678901234567890"),
 
253
            hexstr2bin("e33b4ddc9c38f2199c3e7b164fcc0536")).
 
254
 
 
255
%%
 
256
%%
 
257
md4_update(doc) ->
 
258
    ["Generate MD5 message using md5_init, md5_update, and md5_final, and"
 
259
     "check the result. Examples are from RFC-1321."];
 
260
md4_update(suite) ->
 
261
    [];
 
262
md4_update(Config) when is_list(Config) ->
 
263
    ?line Ctx = crypto:md4_init(),
 
264
    ?line Ctx1 = crypto:md4_update(Ctx, "ABCDEFGHIJKLMNOPQRSTUVWXYZ"),
 
265
    ?line Ctx2 = crypto:md4_update(Ctx1, "abcdefghijklmnopqrstuvwxyz"
 
266
                                   "0123456789"),
 
267
    ?line m(crypto:md4_final(Ctx2),  
 
268
            hexstr2bin("043f8582f241db351ce627e153e7f0e4")).
 
269
 
 
270
%%
 
271
%%
 
272
sha(doc) ->
 
273
    ["Generate SHA message digests and check the result. Examples are "
 
274
     "from FIPS-180-1."];
 
275
sha(suite) ->
 
276
    [];
 
277
sha(Config) when is_list(Config) ->
 
278
    ?line m(crypto:sha("abc"),
 
279
             hexstr2bin("A9993E364706816ABA3E25717850C26C9CD0D89D")),
 
280
    ?line m(crypto:sha("abcdbcdecdefdefgefghfghighijhijkijkljklmklm"
 
281
                       "nlmnomnopnopq"), 
 
282
                hexstr2bin("84983E441C3BD26EBAAE4AA1F95129E5E54670F1")).
 
283
 
 
284
 
 
285
%%
 
286
%%
 
287
sha_update(doc) ->
 
288
    ["Generate SHA message digests by using sha_init, sha_update, and"
 
289
     "sha_final, and check the result. Examples are from FIPS-180-1."];
 
290
sha_update(suite) ->
 
291
    [];
 
292
sha_update(Config) when is_list(Config) ->
 
293
    ?line Ctx = crypto:sha_init(),
 
294
    ?line Ctx1 = crypto:sha_update(Ctx, "abcdbcdecdefdefgefghfghighi"),
 
295
    ?line Ctx2 = crypto:sha_update(Ctx1, "jhijkijkljklmklmnlmnomnopnopq"),
 
296
    ?line m(crypto:sha_final(Ctx2), 
 
297
            hexstr2bin("84983E441C3BD26EBAAE4AA1F95129E5E54670F1")).
 
298
 
 
299
%%
 
300
%%
 
301
sha256(doc) ->
 
302
    ["Generate SHA-256 message digests and check the result. Examples are "
 
303
     "from rfc-4634."];
 
304
sha256(suite) ->
 
305
    [];
 
306
sha256(Config) when is_list(Config) ->
 
307
    ?line m(crypto:sha256("abc"),
 
308
            hexstr2bin("BA7816BF8F01CFEA4141"
 
309
                       "40DE5DAE2223B00361A396177A9CB410FF61F20015AD")),
 
310
    ?line m(crypto:sha256("abcdbcdecdefdefgefghfghighijhijkijkljklmklm"
 
311
                          "nlmnomnopnopq"), 
 
312
            hexstr2bin("248D6A61D20638B8"
 
313
                       "E5C026930C3E6039A33CE45964FF2167F6ECEDD419DB06C1")).
 
314
 
 
315
%%
 
316
%%
 
317
sha256_update(doc) ->
 
318
    ["Generate SHA256 message digests by using sha256_init, sha256_update, and"
 
319
     "sha256_final, and check the result. Examples are from rfc-4634."];
 
320
sha256_update(suite) ->
 
321
    [];
 
322
sha256_update(Config) when is_list(Config) ->
 
323
    ?line Ctx = crypto:sha256_init(),
 
324
    ?line Ctx1 = crypto:sha256_update(Ctx, "abcdbcdecdefdefgefghfghighi"),
 
325
    ?line Ctx2 = crypto:sha256_update(Ctx1, "jhijkijkljklmklmnlmnomnopnopq"),
 
326
    ?line m(crypto:sha256_final(Ctx2), 
 
327
            hexstr2bin("248D6A61D20638B8"
 
328
                       "E5C026930C3E6039A33CE45964FF2167F6ECEDD419DB06C1")).
 
329
 
 
330
 
 
331
%%
 
332
%%
 
333
sha512(doc) ->
 
334
    ["Generate SHA-512 message digests and check the result. Examples are "
 
335
     "from rfc-4634."];
 
336
sha512(suite) ->
 
337
    [];
 
338
sha512(Config) when is_list(Config) ->
 
339
    ?line m(crypto:sha512("abc"),
 
340
            hexstr2bin("DDAF35A193617ABACC417349AE20413112E6FA4E89A97EA2"
 
341
                       "0A9EEEE64B55D39A2192992A274FC1A836BA3C23A3FEEBBD"
 
342
                       "454D4423643CE80E2A9AC94FA54CA49F")),
 
343
    ?line m(crypto:sha512("abcdefghbcdefghicdefghijdefghijkefghijklfghijklmghijklmn"
 
344
                          "hijklmnoijklmnopjklmnopqklmnopqrlmnopqrsmnopqrstnopqrstu"), 
 
345
            hexstr2bin("8E959B75DAE313DA8CF4F72814FC143F8F7779C6EB9F7FA1"
 
346
                       "7299AEADB6889018501D289E4900F7E4331B99DEC4B5433A"
 
347
                       "C7D329EEB6DD26545E96E55B874BE909")).
 
348
 
 
349
%%
 
350
%%
 
351
sha512_update(doc) ->
 
352
    ["Generate SHA512 message digests by using sha512_init, sha512_update, and"
 
353
     "sha512_final, and check the result. Examples are from rfc=4634."];
 
354
sha512_update(suite) ->
 
355
    [];
 
356
sha512_update(Config) when is_list(Config) ->
 
357
    ?line Ctx = crypto:sha512_init(),
 
358
    ?line Ctx1 = crypto:sha512_update(Ctx, "abcdefghbcdefghicdefghijdefghijkefghijklfghijklmghijklmn"),
 
359
    ?line Ctx2 = crypto:sha512_update(Ctx1, "hijklmnoijklmnopjklmnopqklmnopqrlmnopqrsmnopqrstnopqrstu"),
 
360
    ?line m(crypto:sha512_final(Ctx2), 
 
361
            hexstr2bin("8E959B75DAE313DA8CF4F72814FC143F8F7779C6EB9F7FA1"
 
362
                       "7299AEADB6889018501D289E4900F7E4331B99DEC4B5433A"
 
363
                       "C7D329EEB6DD26545E96E55B874BE909")).
 
364
 
 
365
%%
 
366
%%
 
367
md5_mac(doc) ->
 
368
    ["Generate some HMACs, using MD5, and check the result. Examples are "
 
369
     "from RFC-2104."];
 
370
md5_mac(suite) ->
 
371
    [];
 
372
md5_mac(Config) when is_list(Config) ->
 
373
    ?line m(crypto:md5_mac(hexstr2bin("0b0b0b0b0b0b0b0b0b0b0b0b0b0b0b0b"),
 
374
                           "Hi There"),
 
375
            hexstr2bin("9294727a3638bb1c13f48ef8158bfc9d")),
 
376
    ?line m(crypto:md5_mac(list_to_binary("Jefe"), 
 
377
                                     "what do ya want for nothing?"),
 
378
            hexstr2bin("750c783e6ab0b503eaa86e310a5db738")),
 
379
    ?line m(crypto:md5_mac(hexstr2bin("AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA"),
 
380
                           hexstr2bin("DDDDDDDDDDDDDDDDDDDD"
 
381
                                      "DDDDDDDDDDDDDDDDDDDD"
 
382
                                      "DDDDDDDDDDDDDDDDDDDD"
 
383
                                      "DDDDDDDDDDDDDDDDDDDD"
 
384
                                      "DDDDDDDDDDDDDDDDDDDD")),
 
385
            hexstr2bin("56be34521d144c88dbb8c733f0e8b3f6")).
 
386
 
 
387
%%
 
388
%%
 
389
md5_mac_io(doc) ->
 
390
    ["Generate some HMACs, using MD5, with Key an IO-list, and check the "
 
391
     "result. Examples are from RFC-2104."];
 
392
md5_mac_io(suite) ->
 
393
    [];
 
394
md5_mac_io(Config) when is_list(Config) ->
 
395
    ?line Key1 = hexstr2bin("0b0b0b0b0b0b0b0b0b0b0b0b0b0b0b0b"),
 
396
    ?line {B11, B12} = split_binary(Key1, 4),
 
397
    ?line Key11 = [B11,binary_to_list(B12)],
 
398
    ?line m(crypto:md5_mac(Key11, "Hi There"),
 
399
            hexstr2bin("9294727a3638bb1c13f48ef8158bfc9d")).
 
400
 
 
401
%%
 
402
%%
 
403
des_cbc(doc) ->
 
404
    "Encrypt and decrypt according to CBC DES. and check the result. "
 
405
        "Example are from FIPS-81.";
 
406
des_cbc(suite) ->
 
407
    [];
 
408
des_cbc(Config) when is_list(Config) ->
 
409
    ?line Key =  hexstr2bin("0123456789abcdef"),
 
410
    ?line IVec = hexstr2bin("1234567890abcdef"),
 
411
    ?line Plain = "Now is the time for all ",
 
412
    ?line Cipher = crypto:des_cbc_encrypt(Key, IVec, Plain),
 
413
    ?line m(Cipher, hexstr2bin("e5c7cdde872bf27c43e934008c389c"
 
414
                               "0f683788499a7c05f6")),
 
415
    ?line m(list_to_binary(Plain), 
 
416
            crypto:des_cbc_decrypt(Key, IVec, Cipher)),
 
417
    ?line Plain2 = "7654321 Now is the time for " ++ [0, 0, 0, 0],
 
418
    ?line Cipher2 = crypto:des_cbc_encrypt(Key, IVec, Plain2),
 
419
    ?line m(Cipher2, hexstr2bin("b9916b8ee4c3da64b4f44e3cbefb9"
 
420
                                "9484521388fa59ae67d58d2e77e86062733")),
 
421
    ?line m(list_to_binary(Plain2), 
 
422
            crypto:des_cbc_decrypt(Key, IVec, Cipher2)).
 
423
 
 
424
%%
 
425
%%
 
426
des_cbc_iter(doc) ->
 
427
        "Encrypt and decrypt according to CBC DES in two steps, and "
 
428
    "check the result. Example are from FIPS-81.";
 
429
des_cbc_iter(suite) ->
 
430
    [];
 
431
des_cbc_iter(Config) when is_list(Config) ->
 
432
    ?line Key =  hexstr2bin("0123456789abcdef"),
 
433
    ?line IVec = hexstr2bin("1234567890abcdef"),
 
434
    ?line Plain1 = "Now is the time ",
 
435
    ?line Plain2 = "for all ",
 
436
    ?line Cipher1 = crypto:des_cbc_encrypt(Key, IVec, Plain1),
 
437
    ?line IVec2 = crypto:des_cbc_ivec(Cipher1),
 
438
    ?line Cipher2 = crypto:des_cbc_encrypt(Key, IVec2, Plain2),
 
439
    ?line Cipher = list_to_binary([Cipher1, Cipher2]),
 
440
    ?line m(Cipher, hexstr2bin("e5c7cdde872bf27c43e934008c389c"
 
441
                                     "0f683788499a7c05f6")).
 
442
 
 
443
%%
 
444
%%
 
445
des_ecb(doc) ->
 
446
    "Encrypt and decrypt according to ECB DES and check the result. "
 
447
    "Example are from FIPS-81.";
 
448
des_ecb(suite) ->
 
449
    [];
 
450
des_ecb(Config) when is_list(Config) ->
 
451
    ?line Key =  hexstr2bin("0123456789abcdef"),
 
452
    ?line Cipher1 = crypto:des_ecb_encrypt(Key, "Now is t"),
 
453
    ?line m(Cipher1, hexstr2bin("3fa40e8a984d4815")),
 
454
    ?line Cipher2 = crypto:des_ecb_encrypt(Key, "he time "),
 
455
    ?line m(Cipher2, hexstr2bin("6a271787ab8883f9")),
 
456
    ?line Cipher3 = crypto:des_ecb_encrypt(Key, "for all "),
 
457
    ?line m(Cipher3, hexstr2bin("893d51ec4b563b53")),
 
458
    ?line Cipher4 = crypto:des_ecb_decrypt(Key, hexstr2bin("3fa40e8a984d4815")),
 
459
    ?line m(Cipher4, <<"Now is t">>),
 
460
    ?line Cipher5 = crypto:des_ecb_decrypt(Key, hexstr2bin("6a271787ab8883f9")),
 
461
    ?line m(Cipher5, <<"he time ">>),
 
462
    ?line Cipher6 = crypto:des_ecb_decrypt(Key, hexstr2bin("893d51ec4b563b53")),
 
463
    ?line m(Cipher6, <<"for all ">>).
 
464
 
 
465
%%
 
466
%%
 
467
aes_cfb(doc) ->
 
468
    "Encrypt and decrypt according to AES CFB 128 bit and check "
 
469
        "the result. Example are from NIST SP 800-38A.";
 
470
 
 
471
aes_cfb(suite) ->
 
472
    [];
 
473
aes_cfb(Config) when is_list(Config) ->
 
474
 
 
475
%% Sample data from NIST Spec.Publ. 800-38A
 
476
%% F.3.13 CFB128-AES128.Encrypt
 
477
%% Key            2b7e151628aed2a6abf7158809cf4f3c
 
478
%% IV             000102030405060708090a0b0c0d0e0f
 
479
%% Segment #1
 
480
%% Input Block    000102030405060708090a0b0c0d0e0f
 
481
%% Output Block   50fe67cc996d32b6da0937e99bafec60
 
482
%% Plaintext      6bc1bee22e409f96e93d7e117393172a
 
483
%% Ciphertext     3b3fd92eb72dad20333449f8e83cfb4a
 
484
%% Segment #2
 
485
%% Input Block    3b3fd92eb72dad20333449f8e83cfb4a
 
486
%% Output Block   668bcf60beb005a35354a201dab36bda
 
487
%% Plaintext      ae2d8a571e03ac9c9eb76fac45af8e51
 
488
%% Ciphertext     c8a64537a0b3a93fcde3cdad9f1ce58b
 
489
%% Segment #3
 
490
%% Input Block    c8a64537a0b3a93fcde3cdad9f1ce58b
 
491
%% Output Block   16bd032100975551547b4de89daea630
 
492
%% Plaintext      30c81c46a35ce411e5fbc1191a0a52ef
 
493
%% Ciphertext     26751f67a3cbb140b1808cf187a4f4df
 
494
%% Segment #4
 
495
%% Input Block    26751f67a3cbb140b1808cf187a4f4df
 
496
%% Output Block   36d42170a312871947ef8714799bc5f6
 
497
%% Plaintext      f69f2445df4f9b17ad2b417be66c3710
 
498
%% Ciphertext     c04b05357c5d1c0eeac4c66f9ff7f2e6
 
499
 
 
500
    ?line Key =  hexstr2bin("2b7e151628aed2a6abf7158809cf4f3c"),
 
501
    ?line IVec = hexstr2bin("000102030405060708090a0b0c0d0e0f"),
 
502
    ?line Plain = hexstr2bin("6bc1bee22e409f96e93d7e117393172a"),
 
503
    ?line Cipher = crypto:aes_cfb_128_encrypt(Key, IVec, Plain),
 
504
    ?line m(Cipher, hexstr2bin("3b3fd92eb72dad20333449f8e83cfb4a")),
 
505
    ?line m(Plain, 
 
506
            crypto:aes_cfb_128_decrypt(Key, IVec, Cipher)).
 
507
 
 
508
%%
 
509
%%
 
510
aes_cbc(doc) ->
 
511
    "Encrypt and decrypt according to AES CBC 128 bit. and check the result. "
 
512
        "Example are from NIST SP 800-38A.";
 
513
 
 
514
aes_cbc(suite) ->
 
515
    [];
 
516
aes_cbc(Config) when is_list(Config) ->
 
517
 
 
518
%% Sample data from NIST Spec.Publ. 800-38A
 
519
%% F.2.1 CBC-AES128.Encrypt
 
520
%% Key 2b7e151628aed2a6abf7158809cf4f3c 
 
521
%% IV 000102030405060708090a0b0c0d0e0f 
 
522
%% Block #1 
 
523
%% Plaintext 6bc1bee22e409f96e93d7e117393172a 
 
524
%% Input Block 6bc0bce12a459991e134741a7f9e1925 
 
525
%% Output Block 7649abac8119b246cee98e9b12e9197d 
 
526
%% Ciphertext 7649abac8119b246cee98e9b12e9197d 
 
527
%% Block #2 
 
528
%% Plaintext ae2d8a571e03ac9c9eb76fac45af8e51 
 
529
%% Input Block d86421fb9f1a1eda505ee1375746972c 
 
530
%% Output Block 5086cb9b507219ee95db113a917678b2 
 
531
%% Ciphertext 5086cb9b507219ee95db113a917678b2 
 
532
%% Block #3 
 
533
%% Plaintext 30c81c46a35ce411e5fbc1191a0a52ef 
 
534
%% Input Block 604ed7ddf32efdff7020d0238b7c2a5d 
 
535
%% Output Block 73bed6b8e3c1743b7116e69e22229516 
 
536
%% Ciphertext 73bed6b8e3c1743b7116e69e22229516 
 
537
%% Block #4 
 
538
%% Plaintext f69f2445df4f9b17ad2b417be66c3710 
 
539
%% Input Block 8521f2fd3c8eef2cdc3da7e5c44ea206 
 
540
%% Output Block 3ff1caa1681fac09120eca307586e1a7 
 
541
%% Ciphertext 3ff1caa1681fac09120eca307586e1a7 
 
542
%%
 
543
%% F.2.2 CBC-AES128.Decrypt 
 
544
%% Key 2b7e151628aed2a6abf7158809cf4f3c 
 
545
%% IV 000102030405060708090a0b0c0d0e0f 
 
546
    %% Block #1 
 
547
%% Ciphertext 7649abac8119b246cee98e9b12e9197d 
 
548
%% Input Block 7649abac8119b246cee98e9b12e9197d 
 
549
%% Output Block 6bc0bce12a459991e134741a7f9e1925 
 
550
%% Plaintext 6bc1bee22e409f96e93d7e117393172a 
 
551
%% Block #2 
 
552
%% Ciphertext 5086cb9b507219ee95db113a917678b2 
 
553
%% Input Block 5086cb9b507219ee95db113a917678b2 
 
554
%% Output Block d86421fb9f1a1eda505ee1375746972c 
 
555
%% Plaintext ae2d8a571e03ac9c9eb76fac45af8e51 
 
556
%% Block #3 
 
557
%% Ciphertext 73bed6b8e3c1743b7116e69e22229516 
 
558
%% Input Block 73bed6b8e3c1743b7116e69e22229516 
 
559
%% Output Block 604ed7ddf32efdff7020d0238b7c2a5d 
 
560
%% Plaintext 30c81c46a35ce411e5fbc1191a0a52ef 
 
561
%% Block #4 
 
562
%% Ciphertext 3ff1caa1681fac09120eca307586e1a7 
 
563
%% Input Block 3ff1caa1681fac09120eca307586e1a7
 
564
%% Output Block 8521f2fd3c8eef2cdc3da7e5c44ea206 
 
565
%% Plaintext f69f2445df4f9b17ad2b417be66c3710
 
566
 
 
567
    ?line Key =  hexstr2bin("2b7e151628aed2a6abf7158809cf4f3c"),
 
568
    ?line IVec = hexstr2bin("000102030405060708090a0b0c0d0e0f"),
 
569
    ?line Plain = hexstr2bin("6bc1bee22e409f96e93d7e117393172a"),
 
570
    ?line Cipher = crypto:aes_cbc_128_encrypt(Key, IVec, Plain),
 
571
    ?line m(Cipher, hexstr2bin("7649abac8119b246cee98e9b12e9197d")),
 
572
    ?line m(Plain, 
 
573
            crypto:aes_cbc_128_decrypt(Key, IVec, Cipher)).
 
574
 
 
575
aes_cbc_iter(doc) ->
 
576
    "Encrypt and decrypt according to CBC AES in steps";
 
577
aes_cbc_iter(suite) -> [];
 
578
aes_cbc_iter(Config) when is_list(Config) ->
 
579
    Key = list_to_binary(lists:seq(255,256-16*17,-17)),
 
580
    IVec = list_to_binary(lists:seq(1,16*7,7)),
 
581
    Plain = <<"One, two, three o'clock, four o'clock, rock"
 
582
             "Five, six, seven o'clock, eight o'clock, rock"
 
583
             "Nine, ten, eleven o'clock, twelve o'clock, rock"
 
584
             "We're gonna rock around the clock tonight">>,
 
585
    ?line 0 = size(Plain) rem 16,
 
586
 
 
587
    ?line Cipher = crypto:aes_cbc_128_encrypt(Key, IVec, Plain),
 
588
    ?line Plain = crypto:aes_cbc_128_decrypt(Key, IVec, Cipher),
 
589
    
 
590
    ?line Cipher = aes_cbc_encrypt_iter(Key,IVec,Plain,<<>>),
 
591
    ?line Plain = aes_cbc_decrypt_iter(Key,IVec,Cipher,<<>>),
 
592
    ok.
 
593
 
 
594
aes_cbc_encrypt_iter(_,_,<<>>, Acc) ->
 
595
    Acc;
 
596
aes_cbc_encrypt_iter(Key,IVec,Data, Acc) ->
 
597
    Bytes = 16 * (1 + size(Data) div (16*3)),
 
598
    <<Chunk:Bytes/binary, Rest/binary>> = Data,
 
599
    %%io:format("encrypt iter Chunk=~p Rest=~p\n",[Chunk,Rest]),
 
600
    ?line Cipher = crypto:aes_cbc_128_encrypt(Key, IVec, Chunk),
 
601
    ?line IVec2 = crypto:aes_cbc_ivec(Cipher),
 
602
    aes_cbc_encrypt_iter(Key,IVec2,Rest, <<Acc/binary, Cipher/binary>>).
 
603
 
 
604
aes_cbc_decrypt_iter(_,_,<<>>, Acc) ->
 
605
    Acc;
 
606
aes_cbc_decrypt_iter(Key,IVec,Data, Acc) ->
 
607
    Bytes = 16 * (1 + size(Data) div (16*5)),
 
608
    <<Chunk:Bytes/binary, Rest/binary>> = Data,
 
609
    %%io:format("decrypt iter Chunk=~p Rest=~p\n",[Chunk,Rest]),
 
610
    ?line Plain = crypto:aes_cbc_128_decrypt(Key, IVec, Chunk),
 
611
    ?line IVec2 = crypto:aes_cbc_ivec(Chunk),
 
612
    aes_cbc_decrypt_iter(Key,IVec2,Rest, <<Acc/binary, Plain/binary>>).
 
613
 
 
614
 
 
615
aes_ctr(doc) -> "CTR";
 
616
aes_ctr(Config) when is_list(Config) ->
 
617
    %% Sample data from NIST Spec.Publ. 800-38A
 
618
    %% F.5.1 CTR-AES128.Encrypt
 
619
    Key128 = hexstr2bin("2b7e151628aed2a6abf7158809cf4f3c"),
 
620
    Samples128 = [{"f0f1f2f3f4f5f6f7f8f9fafbfcfdfeff", % Input Block
 
621
                   "6bc1bee22e409f96e93d7e117393172a", % Plaintext
 
622
                   "874d6191b620e3261bef6864990db6ce"},% Ciphertext
 
623
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff00",
 
624
                   "ae2d8a571e03ac9c9eb76fac45af8e51",
 
625
                   "9806f66b7970fdff8617187bb9fffdff"},
 
626
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff01",
 
627
                   "30c81c46a35ce411e5fbc1191a0a52ef",
 
628
                   "5ae4df3edbd5d35e5b4f09020db03eab"},
 
629
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff02",
 
630
                   "f69f2445df4f9b17ad2b417be66c3710",
 
631
                   "1e031dda2fbe03d1792170a0f3009cee"}],
 
632
    lists:foreach(fun(S) -> aes_ctr_do(Key128,S) end, Samples128),
 
633
 
 
634
    %% F.5.3  CTR-AES192.Encrypt
 
635
    Key192 =  hexstr2bin("8e73b0f7da0e6452c810f32b809079e562f8ead2522c6b7b"),
 
636
    Samples192 = [{"f0f1f2f3f4f5f6f7f8f9fafbfcfdfeff", % Input Block
 
637
                   "6bc1bee22e409f96e93d7e117393172a", % Plaintext
 
638
                   "1abc932417521ca24f2b0459fe7e6e0b"},% Ciphertext
 
639
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff00",
 
640
                   "ae2d8a571e03ac9c9eb76fac45af8e51",
 
641
                   "090339ec0aa6faefd5ccc2c6f4ce8e94"},
 
642
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff01",
 
643
                   "30c81c46a35ce411e5fbc1191a0a52ef",
 
644
                   "1e36b26bd1ebc670d1bd1d665620abf7"},
 
645
                  {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff02",
 
646
                   "f69f2445df4f9b17ad2b417be66c3710",
 
647
                   "4f78a7f6d29809585a97daec58c6b050"}],    
 
648
    lists:foreach(fun(S) -> aes_ctr_do(Key192,S) end, Samples192),
 
649
 
 
650
    %% F.5.5  CTR-AES256.Encrypt
 
651
    Key256 = hexstr2bin("603deb1015ca71be2b73aef0857d77811f352c073b6108d72d9810a30914dff4"),
 
652
    Samples256 = [{"f0f1f2f3f4f5f6f7f8f9fafbfcfdfeff",  % Input Block
 
653
                    "6bc1bee22e409f96e93d7e117393172a", % Plaintext
 
654
                    "601ec313775789a5b7a7f504bbf3d228"},% Ciphertext
 
655
                   {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff00",
 
656
                    "ae2d8a571e03ac9c9eb76fac45af8e51",
 
657
                    "f443e3ca4d62b59aca84e990cacaf5c5"},
 
658
                   {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff01",
 
659
                    "30c81c46a35ce411e5fbc1191a0a52ef",
 
660
                    "2b0930daa23de94ce87017ba2d84988d"},
 
661
                   {"f0f1f2f3f4f5f6f7f8f9fafbfcfdff02",
 
662
                    "f69f2445df4f9b17ad2b417be66c3710",
 
663
                    "dfc9c58db67aada613c2dd08457941a6"}],
 
664
    lists:foreach(fun(S) -> aes_ctr_do(Key256,S) end, Samples256).
 
665
 
 
666
 
 
667
aes_ctr_do(Key,{IVec, Plain, Cipher}) ->
 
668
    ?line I = hexstr2bin(IVec),
 
669
    ?line P = hexstr2bin(Plain),
 
670
    ?line C = crypto:aes_ctr_encrypt(Key, I, P),
 
671
    ?line m(C, hexstr2bin(Cipher)),
 
672
    ?line m(P, crypto:aes_ctr_decrypt(Key, I, C)).
 
673
 
 
674
%%
 
675
%%
 
676
mod_exp_test(doc) ->
 
677
    "mod_exp testing (A ^ M % P with bignums)";
 
678
mod_exp_test(suite) ->
 
679
    [];
 
680
mod_exp_test(Config) when is_list(Config) ->
 
681
    mod_exp_aux_test(2, 5, 10, 8).
 
682
 
 
683
mod_exp_aux_test(_, _, _, 0) ->
 
684
    ok;
 
685
mod_exp_aux_test(B, E, M, N) ->
 
686
    ?line R1 = crypto:mod_exp(B, E, M),
 
687
    ?line R2 = ipow(B, E, M),
 
688
    ?line m(R1, R2),
 
689
    ?line mod_exp_aux_test(B, E*E+1, M*M+1, N-1).
 
690
 
 
691
%%
 
692
%%
 
693
rand_uniform_test(doc) ->
 
694
    "rand_uniform and random_bytes testing";
 
695
rand_uniform_test(suite) ->
 
696
    [];
 
697
rand_uniform_test(Config) when is_list(Config) ->
 
698
    rand_uniform_aux_test(10),
 
699
    ?line 10 = size(crypto:rand_bytes(10)).
 
700
 
 
701
rand_uniform_aux_test(0) ->
 
702
    ok;
 
703
rand_uniform_aux_test(N) ->
 
704
    ?line L = N*1000,
 
705
    ?line H = N*100000+1,
 
706
    ?line R1 = crypto:rand_uniform(L, H),
 
707
    ?line t(R1 >= L),
 
708
    ?line t(R1 < H),
 
709
    ?line rand_uniform_aux_test(N-1).
 
710
 
 
711
%%
 
712
%%
 
713
%%
 
714
%%
 
715
rsa_verify_test(doc) ->
 
716
    "rsa_verify testing (A ^ M % P with bignums)";
 
717
rsa_verify_test(suite) ->
 
718
    [];
 
719
rsa_verify_test(Config) when is_list(Config) ->
 
720
    ?line H = <<178,28,54,104,36,80,144,66,140,201,135,17,36,97,114,124,
 
721
               194,164,172,147>>,
 
722
    ?line SigBlob = <<153,44,121,71,132,1,192,159,78,33,29,62,153,64,191,70,
 
723
                     208,239,166,208,220,167,49,111,128,67,91,253,24,63,194,241,
 
724
                     97,157,135,226,121,162,150,156,60,49,236,90,151,67,239,23,
 
725
                     92,103,89,254,17,165,78,181,64,128,13,210,86,111,209,76,
 
726
                     115,34,107,227,151,47,80,185,143,85,202,55,245,163,226,26,
 
727
                     139,104,196,6,96,82,108,197,13,0,12,70,153,109,107,180,
 
728
                     130,246,156,182,56,96,31,220,227,218,136,211,252,43,8,14,
 
729
                     145,155,191,206,72,194,80,52,54,206,53,27,6,188,195,29>>,
 
730
    ?line BadSigBlob = <<153,44,121,71,132,1,192,159,78,33,29,62,153,64,191,70,
 
731
                        208,239,166,208,220,167,49,111,128,67,91,253,24,63,194,241,
 
732
                        97,157,135,226,121,162,150,156,60,49,236,90,151,67,239,23,
 
733
                        92,103,89,254,17,165,78,181,64,128,13,210,86,111,209,76,
 
734
                        115,107,34,227,151,47,80,185,143,85,202,55,245,163,226,26,
 
735
                        139,104,196,6,96,82,108,197,13,0,12,70,153,109,107,180,
 
736
                        130,246,156,182,56,96,31,220,227,218,136,211,252,43,8,14,
 
737
                        145,155,191,206,72,194,80,52,54,206,53,27,6,188,195,29>>,
 
738
    ?line E = <<35>>,
 
739
    ?line N = <<0,199,209,142,191,86,92,148,103,37,250,217,175,169,109,10,
 
740
               130,139,34,237,174,90,97,118,7,185,57,137,252,236,177,193,
 
741
               228,16,62,29,153,144,64,207,152,240,152,206,136,89,64,6,
 
742
               3,187,89,57,241,219,88,215,75,70,120,20,145,229,37,1,
 
743
               67,138,204,17,39,231,249,239,116,142,169,99,149,41,65,123,
 
744
               26,225,133,0,41,85,77,181,35,100,162,223,92,220,207,50,
 
745
               63,168,193,171,174,199,23,214,201,63,157,76,125,6,54,73,
 
746
               76,89,40,33,147,208,189,76,98,24,61,8,10,110,165,119,165>>,
 
747
    ?line Nbad = <<0,199,209,142,191,86,92,148,103,37,250,217,175,169,109,10,
 
748
                  130,139,34,237,174,90,97,118,7,185,57,137,252,236,177,193,
 
749
                  228,16,62,29,153,144,64,207,152,240,152,206,136,89,64,6,
 
750
                  3,187,89,57,241,219,88,215,75,70,120,20,145,229,37,1,
 
751
                  67,138,204,17,39,231,249,239,116,142,169,99,149,41,65,123,
 
752
                  26,225,133,0,41,85,77,181,35,100,162,223,92,220,207,50,
 
753
                  63,168,193,171,174,199,23,214,201,63,157,76,125,6,54,73,
 
754
                  76,89,40,33,147,189,208,76,98,24,61,8,10,110,165,119,165>>,
 
755
    ?line Ebad = <<77>>,
 
756
    ?line m(crypto:rsa_verify(sized_binary(H), sized_binary(SigBlob),
 
757
                              [sized_binary(E), sized_binary(N)]), true),
 
758
    ?line m(crypto:rsa_verify(sized_binary(H), sized_binary(SigBlob),
 
759
                              [sized_binary(Ebad), sized_binary(N)]), false),
 
760
    ?line m(crypto:rsa_verify(sized_binary(H), sized_binary(SigBlob),
 
761
                              [sized_binary(E), sized_binary(Nbad)]), false),
 
762
    ?line m(crypto:rsa_verify(sized_binary(H), sized_binary(BadSigBlob),
 
763
                              [sized_binary(E), sized_binary(N)]), false).
 
764
 
 
765
%%
 
766
%%
 
767
dsa_verify_test(doc) ->
 
768
    "dsa_verify testing (A ^ M % P with bignums)";
 
769
dsa_verify_test(suite) ->
 
770
    [];
 
771
dsa_verify_test(Config) when is_list(Config) ->
 
772
    ?line Msg = <<48,130,2,245,160,3,2,1,2,2,1,1,48,9,6,7,42,134,72,206,56,4,3,48,
 
773
                 58,49,11,48,9,6,3,85,4,6,19,2,85,83,49,26,48,24,6,3,85,4,10,19,17,
 
774
                 84,101,115,116,32,67,101,114,116,105,102,105,99,97,116,101,115,49,
 
775
                 15,48,13,6,3,85,4,3,19,6,68,83,65,32,67,65,48,30,23,13,48,49,48,
 
776
                 52,49,57,49,52,53,55,50,48,90,23,13,49,49,48,52,49,57,49,52,53,55,
 
777
                 50,48,90,48,93,49,11,48,9,6,3,85,4,6,19,2,85,83,49,26,48,24,6,3,
 
778
                 85,4,10,19,17,84,101,115,116,32,67,101,114,116,105,102,105,99,97,
 
779
                 116,101,115,49,50,48,48,6,3,85,4,3,19,41,86,97,108,105,100,32,68,
 
780
                 83,65,32,83,105,103,110,97,116,117,114,101,115,32,69,69,32,67,101,
 
781
                 114,116,105,102,105,99,97,116,101,32,84,101,115,116,52,48,130,1,
 
782
                 182,48,130,1,43,6,7,42,134,72,206,56,4,1,48,130,1,30,2,129,129,0,
 
783
                 228,139,175,64,140,21,215,61,124,238,3,150,18,104,193,32,5,232,23,
 
784
                 202,158,116,101,75,154,84,151,42,120,51,218,165,197,114,234,52,
 
785
                 179,148,104,66,213,27,253,119,240,168,66,158,100,147,144,182,194,
 
786
                 2,49,70,19,122,3,105,204,152,45,86,157,94,35,95,40,191,173,127,15,
 
787
                 208,105,149,98,92,26,7,42,94,140,115,73,126,253,18,34,142,85,229,
 
788
                 86,233,174,114,41,150,135,8,39,215,119,67,240,134,184,9,10,27,20,
 
789
                 165,230,3,230,69,121,77,233,250,83,95,193,9,189,126,197,195,2,21,
 
790
                 0,128,63,228,252,243,76,229,62,203,15,23,10,42,84,108,208,103,108,
 
791
                 13,59,2,129,128,102,212,22,138,32,173,254,209,50,159,165,127,167,
 
792
                 179,208,234,119,63,235,108,162,228,41,216,216,188,33,221,154,247,
 
793
                 204,229,180,119,77,223,236,218,162,140,156,117,18,90,31,254,102,
 
794
                 211,17,194,239,132,67,236,169,136,110,76,186,76,63,53,150,199,103,
 
795
                 252,153,189,15,153,41,19,145,78,216,2,174,254,107,175,80,86,170,
 
796
                 47,30,181,42,200,238,34,71,37,120,107,33,221,20,63,206,240,16,129,
 
797
                 247,150,29,156,65,187,94,68,146,93,46,198,30,184,205,105,200,143,
 
798
                 63,59,62,208,79,162,206,217,3,129,132,0,2,129,128,15,83,40,172,56,
 
799
                 47,61,243,17,97,65,195,61,167,214,122,247,246,1,50,211,33,113,16,
 
800
                 20,213,195,62,77,235,25,162,140,175,158,8,61,65,10,255,204,162,71,
 
801
                 130,122,86,161,163,253,236,178,139,183,57,181,202,160,25,133,130,
 
802
                 155,150,104,168,187,107,186,144,164,225,173,101,182,68,49,210,30,
 
803
                 34,47,83,65,79,250,156,248,47,232,44,67,36,22,126,43,216,100,247,
 
804
                 100,250,240,121,72,29,185,2,109,144,54,204,235,54,15,242,57,171,
 
805
                 125,39,236,247,71,111,221,51,196,126,77,238,36,87,163,107,48,105,
 
806
                 48,29,6,3,85,29,14,4,22,4,20,179,51,215,81,162,4,13,68,251,157,64,
 
807
                 241,18,98,113,176,83,246,105,13,48,31,6,3,85,29,35,4,24,48,22,128,
 
808
                 20,116,21,213,36,28,189,94,101,136,31,225,139,9,126,127,234,25,72,
 
809
                 78,97,48,23,6,3,85,29,32,4,16,48,14,48,12,6,10,96,134,72,1,101,3,
 
810
                 2,1,48,1,48,14,6,3,85,29,15,1,1,255,4,4,3,2,6,192>>,
 
811
 
 
812
    ?line SigBlob = <<48,45,2,21,0,140,167,200,210,153,212,64,155,249,33,146,104,243,
 
813
                     39,38,9,115,162,89,24,2,20,76,254,31,128,187,48,128,215,216,
 
814
                     112,198,78,118,160,217,157,180,246,64,234>>,
 
815
    ?line P_p = 157224271412839155721795253728878055347359513988016145491388196653004661857517720927482198111104095793441029858267073789634147217022008635826863307553453131345099940951090826856271796188522037524757740796268675508118348391218066949174594918958269259937813776150149068811425194955973128428675945283593831134219,
 
816
    ?line Q_p = 1181895316321540581845959276009400765315408342791,
 
817
    ?line G_p = 143872196713149000950547166575757355261637863805587906227228163275557375159769599033632918292482002186641475268486598023281100659643528846513898847919251032731261718358900479488287933293278745715922865499005559197328388506945134386346185262919258658109015074718441639029135304654725637911172671711310801418648,
 
818
    
 
819
    ?line Key = 12603618348903387232593303690286336220738319446775939686476278478034365380027994899970214309288018488811754534229198764622077544117034174589418477472887827980332636062691833965078594576024299807057520016043084384987871640003684704483975314128362610573625803532737054022545217931847268776098203204571431581966,
 
820
    
 
821
    ValidKey = [crypto:mpint(P_p), 
 
822
                crypto:mpint(Q_p), 
 
823
                crypto:mpint(G_p),
 
824
                crypto:mpint(Key)
 
825
               ],
 
826
    
 
827
    ?line m(my_dss_verify(sized_binary(Msg), sized_binary(SigBlob),
 
828
                              ValidKey), true),
 
829
 
 
830
    BadMsg  = one_bit_wrong(Msg),
 
831
    ?line m(my_dss_verify(sized_binary(BadMsg), sized_binary(SigBlob),
 
832
                              ValidKey), false),
 
833
    BadSig = one_bit_wrong(SigBlob),
 
834
    ?line m(my_dss_verify(sized_binary(Msg), sized_binary(BadSig),
 
835
                              ValidKey), false),
 
836
    SizeErr = size(SigBlob) - 13,
 
837
    
 
838
    BadArg = (catch my_dss_verify(sized_binary(Msg), <<SizeErr:32, SigBlob/binary>>,
 
839
                                      ValidKey)),
 
840
    ?line m(element(1,element(2,BadArg)), badarg),
 
841
    
 
842
    InValidKey = [crypto:mpint(P_p), 
 
843
                  crypto:mpint(Q_p), 
 
844
                  crypto:mpint(G_p),
 
845
                  crypto:mpint(Key+17)
 
846
                 ],
 
847
    
 
848
    ?line m(my_dss_verify(sized_binary(Msg), sized_binary(SigBlob),
 
849
                              InValidKey), false).
 
850
 
 
851
 
 
852
one_bit_wrong(List) when is_list(List) ->
 
853
    lists:map(fun(Bin) -> one_bit_wrong(Bin) end, List);
 
854
one_bit_wrong(Bin) ->
 
855
    Half = size(Bin) div 2,
 
856
    <<First:Half/binary, Byte:8, Last/binary>> = Bin,
 
857
    <<First/binary, (Byte+1):8, Last/binary>>.
 
858
 
 
859
 
 
860
%%
 
861
%%  Sign tests
 
862
 
 
863
rsa_sign_test(doc) ->
 
864
    "rsa_sign testing";
 
865
rsa_sign_test(suite) ->
 
866
    [];
 
867
rsa_sign_test(Config) when is_list(Config) ->
 
868
    PubEx  = 65537,
 
869
    PrivEx = 7531712708607620783801185371644749935066152052780368689827275932079815492940396744378735701395659435842364793962992309884847527234216715366607660219930945,
 
870
    Mod = 7919488123861148172698919999061127847747888703039837999377650217570191053151807772962118671509138346758471459464133273114654252861270845708312601272799123,
 
871
    Msg = <<"7896345786348756234 Hejsan Svejsan, erlang crypto debugger"
 
872
           "09812312908312378623487263487623412039812 huagasd">>,
 
873
    
 
874
    PrivKey = [crypto:mpint(PubEx), crypto:mpint(Mod), crypto:mpint(PrivEx)],
 
875
    PubKey  = [crypto:mpint(PubEx), crypto:mpint(Mod)],
 
876
    ?line Sig1 = crypto:rsa_sign(sized_binary(Msg), PrivKey),
 
877
    ?line m(crypto:rsa_verify(sized_binary(Msg), sized_binary(Sig1),PubKey), true),
 
878
    
 
879
    ?line Sig2 = crypto:rsa_sign(md5, sized_binary(Msg), PrivKey),
 
880
    ?line m(crypto:rsa_verify(md5, sized_binary(Msg), sized_binary(Sig2),PubKey), true),
 
881
    
 
882
    ?line m(Sig1 =:= Sig2, false),
 
883
    ?line m(crypto:rsa_verify(md5, sized_binary(Msg), sized_binary(Sig1),PubKey), false),
 
884
    ?line m(crypto:rsa_verify(sha, sized_binary(Msg), sized_binary(Sig1),PubKey), true),
 
885
  
 
886
    ok.
 
887
    
 
888
dsa_sign_test(doc) ->
 
889
    "dsa_sign testing";
 
890
dsa_sign_test(suite) ->
 
891
    [];
 
892
dsa_sign_test(Config) when is_list(Config) ->
 
893
    Msg = <<"7896345786348756234 Hejsan Svejsan, erlang crypto debugger"
 
894
           "09812312908312378623487263487623412039812 huagasd">>,
 
895
 
 
896
    PubKey = _Y = 25854665488880835237281628794585130313500176551981812527054397586638455298000483144002221850980183404910190346416063318160497344811383498859129095184158800144312512447497510551471331451396405348497845813002058423110442376886564659959543650802132345311573634832461635601376738282831340827591903548964194832978,
 
897
    PrivKey = _X = 441502407453038284293378221372000880210588566361,
 
898
    ParamP = 109799869232806890760655301608454668257695818999841877165019612946154359052535682480084145133201304812979481136659521529774182959764860329095546511521488413513097576425638476458000255392402120367876345280670101492199681798674053929238558140260669578407351853803102625390950534052428162468100618240968893110797,
 
899
    ParamQ = 1349199015905534965792122312016505075413456283393,
 
900
    ParamG = 18320614775012672475365915366944922415598782131828709277168615511695849821411624805195787607930033958243224786899641459701930253094446221381818858674389863050420226114787005820357372837321561754462061849169568607689530279303056075793886577588606958623645901271866346406773590024901668622321064384483571751669,
 
901
 
 
902
    Params = [crypto:mpint(ParamP), crypto:mpint(ParamQ), crypto:mpint(ParamG)],
 
903
    ?line Sig1 = my_dss_sign(sized_binary(Msg), Params ++ [crypto:mpint(PrivKey)]),
 
904
    
 
905
    ?line m(my_dss_verify(sized_binary(Msg), Sig1, 
 
906
                              Params ++ [crypto:mpint(PubKey)]), true),
 
907
    
 
908
    ?line m(my_dss_verify(sized_binary(one_bit_wrong(Msg)), Sig1, 
 
909
                              Params ++ [crypto:mpint(PubKey)]), false),
 
910
    
 
911
    ?line m(my_dss_verify(sized_binary(Msg), one_bit_wrong(Sig1), 
 
912
                              Params ++ [crypto:mpint(PubKey)]), false),
 
913
 
 
914
    %%?line Bad = crypto:dss_sign(sized_binary(Msg), [Params, crypto:mpint(PubKey)]),
 
915
    
 
916
    ok.
 
917
 
 
918
 
 
919
rsa_encrypt_decrypt(doc) ->
 
920
    ["Test rsa_public_encrypt and rsa_private_decrypt functions."];
 
921
rsa_encrypt_decrypt(suite) -> [];
 
922
rsa_encrypt_decrypt(Config) when is_list(Config) ->
 
923
    PubEx  = 65537,
 
924
    PrivEx = 7531712708607620783801185371644749935066152052780368689827275932079815492940396744378735701395659435842364793962992309884847527234216715366607660219930945,
 
925
    Mod = 7919488123861148172698919999061127847747888703039837999377650217570191053151807772962118671509138346758471459464133273114654252861270845708312601272799123,
 
926
    
 
927
    PrivKey = [crypto:mpint(PubEx), crypto:mpint(Mod), crypto:mpint(PrivEx)],
 
928
    PubKey  = [crypto:mpint(PubEx), crypto:mpint(Mod)],
 
929
 
 
930
    Msg = <<"7896345786348 Asldi">>,
 
931
 
 
932
    ?line PKCS1 = crypto:rsa_public_encrypt(Msg, PubKey, rsa_pkcs1_padding),
 
933
    ?line PKCS1Dec = crypto:rsa_private_decrypt(PKCS1, PrivKey, rsa_pkcs1_padding),
 
934
    io:format("PKCS1Dec ~p~n",[PKCS1Dec]),
 
935
    ?line Msg = PKCS1Dec,
 
936
    
 
937
    ?line OAEP = crypto:rsa_public_encrypt(Msg, PubKey, rsa_pkcs1_oaep_padding),
 
938
    ?line Msg = crypto:rsa_private_decrypt(OAEP, PrivKey, rsa_pkcs1_oaep_padding),
 
939
 
 
940
    <<Msg2Len:32,_/binary>> = crypto:mpint(Mod),
 
941
    Msg2 = list_to_binary(lists:duplicate(Msg2Len-1, $X)),
 
942
    ?line NoPad = crypto:rsa_public_encrypt(Msg2, PubKey, rsa_no_padding),
 
943
    ?line NoPadDec = crypto:rsa_private_decrypt(NoPad, PrivKey, rsa_no_padding),
 
944
    ?line NoPadDec = Msg2,
 
945
    
 
946
    ShouldBeError = (catch crypto:rsa_public_encrypt(Msg, PubKey, rsa_no_padding)),
 
947
    ?line {'EXIT', {encrypt_failed,_}} = ShouldBeError,
 
948
    
 
949
%%     ?line SSL = crypto:rsa_public_encrypt(Msg, PubKey, rsa_sslv23_padding),
 
950
%%     ?line Msg = crypto:rsa_private_decrypt(SSL, PrivKey, rsa_sslv23_padding),
 
951
 
 
952
    ?line PKCS1_2 = crypto:rsa_private_encrypt(Msg, PrivKey, rsa_pkcs1_padding),
 
953
    ?line PKCS1_2Dec = crypto:rsa_public_decrypt(PKCS1_2, PubKey, rsa_pkcs1_padding),
 
954
    io:format("PKCS2Dec ~p~n",[PKCS1_2Dec]),
 
955
    ?line Msg = PKCS1_2Dec,
 
956
 
 
957
    ?line PKCS1_3 = crypto:rsa_private_encrypt(Msg2, PrivKey, rsa_no_padding),
 
958
    ?line PKCS1_3Dec = crypto:rsa_public_decrypt(PKCS1_3, PubKey, rsa_no_padding),
 
959
    io:format("PKCS2Dec ~p~n",[PKCS1_3Dec]),
 
960
    ?line Msg2 = PKCS1_3Dec,
 
961
    
 
962
    ?line {'EXIT', {encrypt_failed,_}} = 
 
963
        (catch crypto:rsa_private_encrypt(Msg, PrivKey, rsa_no_padding)),
 
964
    
 
965
    ok.
 
966
 
 
967
 
 
968
dh(doc) ->
 
969
    ["Test dh (Diffie-Hellman) functions."];
 
970
dh(suite) -> [];
 
971
dh(Config) when is_list(Config) ->
 
972
    Self = self(),
 
973
    GenP = fun() ->
 
974
                   %% Gen Param may take arbitrary long time to finish 
 
975
                   %% That's not a bug in erlang crypto application.
 
976
                   ?line DHPs = crypto:dh_generate_parameters(512,2),
 
977
                   ?line ok = crypto:dh_check(DHPs),
 
978
                   Self ! {param, DHPs}
 
979
           end,
 
980
    Pid = spawn(GenP),
 
981
    receive 
 
982
        {param, DHPs} ->
 
983
            timer:sleep(100), 
 
984
            io:format("DHP ~p~n", [DHPs]),
 
985
            ?line {Pub1,Priv1} = crypto:dh_generate_key(DHPs),
 
986
            io:format("Key1:~n~p~n~p~n~n", [Pub1,Priv1]),
 
987
            ?line {Pub2,Priv2} = crypto:dh_generate_key(DHPs),
 
988
            io:format("Key2:~n~p~n~p~n~n", [Pub2,Priv2]),
 
989
            ?line A = crypto:dh_compute_key(Pub1, Priv2, DHPs),
 
990
            timer:sleep(100),  %% Get another thread see if that triggers problem
 
991
            ?line B = crypto:dh_compute_key(Pub2, Priv1, DHPs),
 
992
            io:format("A ~p~n",[A]),
 
993
            io:format("B ~p~n",[B]),
 
994
            ?line A = B
 
995
    after 50000 ->
 
996
            io:format("Killing Param generation which took to long ~p~n",[Pid]),
 
997
            exit(Pid, kill)
 
998
    end.
 
999
 
 
1000
%%
 
1001
%%
 
1002
exor_test(doc) ->
 
1003
    ["Test the exor function."];
 
1004
exor_test(suite) ->
 
1005
    [];
 
1006
exor_test(Config) when is_list(Config) ->
 
1007
    B = <<1, 2, 3, 4, 5, 6, 7, 8, 9, 10>>,
 
1008
    Z1 = zero_bin(B),
 
1009
    Z1 = crypto:exor(B, B),
 
1010
    B1 = crypto:rand_bytes(100),
 
1011
    B2 = crypto:rand_bytes(100),
 
1012
    Z2 = zero_bin(B1),
 
1013
    Z2 = crypto:exor(B1, B1),
 
1014
    Z2 = crypto:exor(B2, B2),
 
1015
    R = xor_bytes(B1, B2),
 
1016
    R = crypto:exor(B1, B2),
 
1017
    ok.
 
1018
 
 
1019
%%
 
1020
%%
 
1021
rc4_test(doc) ->
 
1022
    ["Test rc4 encryption ."];
 
1023
rc4_test(suite) ->
 
1024
    [];
 
1025
rc4_test(Config) when is_list(Config) ->
 
1026
    CT1 = <<"hej p� dig">>,
 
1027
    R1 = <<71,112,14,44,140,33,212,144,155,47>>,
 
1028
    K = "apaapa",
 
1029
    R1 = crypto:rc4_encrypt(K, CT1),
 
1030
    CT1 = crypto:rc4_encrypt(K, R1),
 
1031
    CT2 = lists:seq(0, 255),
 
1032
    R2 = crypto:rc4_encrypt(K, CT2),
 
1033
    CT2 = binary_to_list(crypto:rc4_encrypt(K, R2)),
 
1034
    ok.
 
1035
 
 
1036
rc4_stream_test(doc) ->
 
1037
    ["Test rc4 stream encryption ."];
 
1038
rc4_stream_test(suite) ->
 
1039
    [];
 
1040
rc4_stream_test(Config) when is_list(Config) ->
 
1041
    CT1 = <<"hej">>,
 
1042
    CT2 = <<" p� dig">>,
 
1043
    K = "apaapa",
 
1044
    State0 = crypto:rc4_set_key(K),
 
1045
    {State1, R1} = crypto:rc4_encrypt_with_state(State0, CT1),
 
1046
    {_State2, R2} = crypto:rc4_encrypt_with_state(State1, CT2),
 
1047
    R = list_to_binary([R1, R2]),
 
1048
    <<71,112,14,44,140,33,212,144,155,47>> = R,
 
1049
    ok.
 
1050
 
 
1051
blowfish_cfb64(doc) -> ["Test Blowfish encrypt/decrypt."];
 
1052
blowfish_cfb64(suite) -> [];
 
1053
blowfish_cfb64(Config) when is_list(Config) ->                          
 
1054
    Key = <<1,35,69,103,137,171,205,239,240,225,210,195,180,165,150,135>>,
 
1055
 
 
1056
    IVec = <<254,220,186,152,118,84,50,16>>,
 
1057
    Plain = <<"7654321 Now is the time for ">>,
 
1058
    Enc = <<231,50,20,162,130,33,57,202,242,110,207,109,46,185,231,110,61,163,222,4,209,81,114,0,81,157,87,166>>,
 
1059
 
 
1060
    Enc = crypto:blowfish_cfb64_encrypt(Key, IVec, Plain),
 
1061
    Plain = crypto:blowfish_cfb64_decrypt(Key, IVec, Enc),
 
1062
 
 
1063
    Key2 = <<"A2B4C">>,
 
1064
    IVec2 = <<"12345678">>,
 
1065
    Plain2 = <<"badger at my table....!">>,
 
1066
    Enc2 = <<173,76,128,155,70,81,79,228,4,162,188,92,119,53,144,89,93,236,28,164,176,16,138>>,
 
1067
 
 
1068
    Enc2 = crypto:blowfish_cfb64_encrypt(Key2, IVec2, Plain2),
 
1069
    Plain2 = crypto:blowfish_cfb64_decrypt(Key2, IVec2, Enc2).
 
1070
 
 
1071
 
 
1072
smp(doc) -> "Check concurrent access to crypto driver";
 
1073
smp(suite) -> [];
 
1074
smp(Config) ->
 
1075
    case erlang:system_info(smp_support) of
 
1076
        true ->
 
1077
            NumOfProcs = erlang:system_info(schedulers),
 
1078
            io:format("smp starting ~p workers\n",[NumOfProcs]),
 
1079
            Seeds = [random:uniform(9999) || _ <- lists:seq(1,NumOfProcs)],
 
1080
            Parent = self(),
 
1081
            Pids = [spawn_link(fun()-> worker(Seed,Config,Parent) end)
 
1082
                    || Seed <- Seeds],
 
1083
            wait_pids(Pids);
 
1084
 
 
1085
        false ->
 
1086
            {skipped,"No smp support"}
 
1087
    end.
 
1088
            
 
1089
worker(Seed, Config, Parent) ->
 
1090
    io:format("smp worker ~p, seed=~p~n",[self(),Seed]),
 
1091
    random:seed(Seed,Seed,Seed),
 
1092
    worker_loop(100, Config),
 
1093
    %%io:format("worker ~p done\n",[self()]),
 
1094
    Parent ! self().
 
1095
 
 
1096
worker_loop(0, _) ->
 
1097
    ok;
 
1098
worker_loop(N, Config) ->
 
1099
    Funcs = { md5, md5_update, md5_mac, md5_mac_io, sha, sha_update, des_cbc,
 
1100
              aes_cfb, aes_cbc, des_cbc_iter, rand_uniform_test, 
 
1101
              rsa_verify_test, exor_test, rc4_test, rc4_stream_test, mod_exp_test },
 
1102
 
 
1103
    F = element(random:uniform(size(Funcs)),Funcs),
 
1104
    %%io:format("worker ~p calling ~p\n",[self(),F]),
 
1105
    ?MODULE:F(Config),
 
1106
    worker_loop(N-1,Config).
 
1107
    
 
1108
wait_pids([]) -> 
 
1109
    ok;
 
1110
wait_pids(Pids) ->
 
1111
    receive
 
1112
        Pid ->
 
1113
            ?line true = lists:member(Pid,Pids),
 
1114
            Others = lists:delete(Pid,Pids),
 
1115
            io:format("wait_pid got ~p, still waiting for ~p\n",[Pid,Others]),
 
1116
            wait_pids(Others)
 
1117
    end.
 
1118
 
 
1119
%%
 
1120
%% Help functions
 
1121
%%
 
1122
 
 
1123
% match
 
1124
m(X, X) ->
 
1125
    ?line true.
 
1126
t(true) ->
 
1127
    true.
 
1128
 
 
1129
% hexstr2bin
 
1130
hexstr2bin(S) ->
 
1131
    list_to_binary(hexstr2list(S)).
 
1132
 
 
1133
hexstr2list([X,Y|T]) ->
 
1134
    [mkint(X)*16 + mkint(Y) | hexstr2list(T)];
 
1135
hexstr2list([]) ->
 
1136
    [].
 
1137
 
 
1138
mkint(C) when $0 =< C, C =< $9 ->
 
1139
    C - $0;
 
1140
mkint(C) when $A =< C, C =< $F ->
 
1141
    C - $A + 10;
 
1142
mkint(C) when $a =< C, C =< $f ->
 
1143
    C - $a + 10.
 
1144
 
 
1145
%% mod_exp in erlang (copied from jungerl's ssh_math.erl)
 
1146
ipow(A, B, M) when M > 0, B >= 0 ->
 
1147
    if A == 1 -> 
 
1148
            1;
 
1149
       true -> 
 
1150
            ipow(A, B, M, 1)
 
1151
    end.
 
1152
 
 
1153
ipow(A, 1, M, Prod) ->
 
1154
    (A*Prod) rem M;
 
1155
ipow(_A, 0, _M, Prod) ->
 
1156
    Prod;
 
1157
ipow(A, B, M, Prod)  ->
 
1158
    B1 = B bsr 1,
 
1159
    A1 = (A*A) rem M,
 
1160
    if B - B1 == B1 ->
 
1161
            ipow(A1, B1, M, Prod);
 
1162
       true ->
 
1163
            ipow(A1, B1, M, (A*Prod) rem M)
 
1164
    end.
 
1165
 
 
1166
%%
 
1167
%% Invert an element X mod P
 
1168
%% Calculated as {1, {A,B}} = egcd(X,P),
 
1169
%%   1 == P*A + X*B == X*B (mod P) i.e B is the inverse element
 
1170
%%
 
1171
%% X > 0, P > 0, X < P   (P should be prime)
 
1172
%%
 
1173
%% invert(X,P) when X > 0, P > 0, X < P ->
 
1174
%%     I = inv(X,P,1,0),
 
1175
%%     if 
 
1176
%%         I < 0 -> P + I;
 
1177
%%         true -> I
 
1178
%%     end.
 
1179
 
 
1180
%% inv(0,_,_,Q) -> Q;
 
1181
%% inv(X,P,R1,Q1) ->
 
1182
%%     D = P div X,
 
1183
%%     inv(P rem X, X, Q1 - D*R1, R1).    
 
1184
 
 
1185
sized_binary(Binary) when is_binary(Binary) ->
 
1186
    <<(size(Binary)):32/integer, Binary/binary>>;
 
1187
sized_binary(List) ->
 
1188
    sized_binary(list_to_binary(List)).
 
1189
 
 
1190
xor_bytes(Bin1, Bin2) when is_binary(Bin1), is_binary(Bin2) ->
 
1191
    L1 = binary_to_list(Bin1),
 
1192
    L2 = binary_to_list(Bin2),
 
1193
    list_to_binary(xor_bytes(L1, L2));
 
1194
xor_bytes(L1, L2) ->
 
1195
    xor_bytes(L1, L2, []).
 
1196
 
 
1197
xor_bytes([], [], Acc) ->
 
1198
    lists:reverse(Acc);
 
1199
xor_bytes([N1 | Tl1], [N2 | Tl2], Acc) ->
 
1200
    xor_bytes(Tl1, Tl2, [N1 bxor N2 | Acc]).
 
1201
 
 
1202
zero_bin(N) when is_integer(N) ->
 
1203
    N8 = N * 8,
 
1204
    <<0:N8/integer>>;
 
1205
zero_bin(B) when is_binary(B) ->
 
1206
    zero_bin(size(B)).
 
1207
 
 
1208
my_dss_verify(Data,[Sign|Tail],Key) ->
 
1209
    Res = my_dss_verify(Data,sized_binary(Sign),Key),
 
1210
    case Tail of
 
1211
        [] ->  Res;
 
1212
        _ -> ?line Res = my_dss_verify(Data,Tail,Key)
 
1213
    end;       
 
1214
my_dss_verify(Data,Sign,Key) ->
 
1215
    ?line Res = crypto:dss_verify(Data, Sign, Key),
 
1216
    ?line Res = crypto:dss_verify(sha, Data, Sign, Key),
 
1217
    ?line <<_:32,Raw/binary>> = Data,
 
1218
    ?line Res = crypto:dss_verify(none, crypto:sha(Raw), Sign, Key),
 
1219
    Res.
 
1220
 
 
1221
my_dss_sign(Data,Key) ->
 
1222
    ?line S1 = crypto:dss_sign(Data, Key),
 
1223
    ?line S2 = crypto:dss_sign(sha, Data, Key),
 
1224
    ?line <<_:32,Raw/binary>> = Data,
 
1225
    ?line S3 = crypto:dss_sign(none, crypto:sha(Raw), Key),
 
1226
    [S1,S2,S3].
 
1227