Skip to content

Commit f228601

Browse files
author
Niclas Eklund
committed
Merge branch 'maint-r14' into dev
2 parents 4dd5d2a + 459bde5 commit f228601

File tree

11 files changed

+213
-68
lines changed

11 files changed

+213
-68
lines changed

lib/crypto/c_src/crypto.c

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -134,7 +134,9 @@ static ERL_NIF_TERM des_ede3_cbc_crypt(ErlNifEnv* env, int argc, const ERL_NIF_T
134134
static ERL_NIF_TERM aes_cfb_128_crypt(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
135135
static ERL_NIF_TERM aes_ctr_encrypt(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
136136
static ERL_NIF_TERM rand_bytes_1(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
137+
static ERL_NIF_TERM strong_rand_bytes_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
137138
static ERL_NIF_TERM rand_bytes_3(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
139+
static ERL_NIF_TERM strong_rand_mpint_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
138140
static ERL_NIF_TERM rand_uniform_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
139141
static ERL_NIF_TERM mod_exp_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
140142
static ERL_NIF_TERM dss_verify(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
@@ -204,7 +206,9 @@ static ErlNifFunc nif_funcs[] = {
204206
{"aes_ctr_encrypt", 3, aes_ctr_encrypt},
205207
{"aes_ctr_decrypt", 3, aes_ctr_encrypt},
206208
{"rand_bytes", 1, rand_bytes_1},
209+
{"strong_rand_bytes_nif", 1, strong_rand_bytes_nif},
207210
{"rand_bytes", 3, rand_bytes_3},
211+
{"strong_rand_mpint_nif", 3, strong_rand_mpint_nif},
208212
{"rand_uniform_nif", 2, rand_uniform_nif},
209213
{"mod_exp_nif", 3, mod_exp_nif},
210214
{"dss_verify", 4, dss_verify},
@@ -704,6 +708,22 @@ static ERL_NIF_TERM rand_bytes_1(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
704708
ERL_VALGRIND_MAKE_MEM_DEFINED(data, bytes);
705709
return ret;
706710
}
711+
static ERL_NIF_TERM strong_rand_bytes_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
712+
{/* (Bytes) */
713+
unsigned bytes;
714+
unsigned char* data;
715+
ERL_NIF_TERM ret;
716+
if (!enif_get_uint(env, argv[0], &bytes)) {
717+
return enif_make_badarg(env);
718+
}
719+
data = enif_make_new_binary(env, bytes, &ret);
720+
if ( RAND_bytes(data, bytes) != 1) {
721+
return atom_false;
722+
}
723+
ERL_VALGRIND_MAKE_MEM_DEFINED(data, bytes);
724+
return ret;
725+
}
726+
707727
static ERL_NIF_TERM rand_bytes_3(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
708728
{/* (Bytes, TopMask, BottomMask) */
709729
unsigned bytes;
@@ -724,6 +744,47 @@ static ERL_NIF_TERM rand_bytes_3(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
724744
}
725745
return ret;
726746
}
747+
static ERL_NIF_TERM strong_rand_mpint_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
748+
{/* (Bytes, TopMask, BottomMask) */
749+
unsigned bits;
750+
BIGNUM *bn_rand;
751+
int top, bottom;
752+
unsigned char* data;
753+
unsigned dlen;
754+
ERL_NIF_TERM ret;
755+
if (!enif_get_uint(env, argv[0], &bits)
756+
|| !enif_get_int(env, argv[1], &top)
757+
|| !enif_get_int(env, argv[2], &bottom)) {
758+
return enif_make_badarg(env);
759+
}
760+
if (! (top == -1 || top == 0 || top == 1) ) {
761+
return enif_make_badarg(env);
762+
}
763+
if (! (bottom == 0 || bottom == 1) ) {
764+
return enif_make_badarg(env);
765+
}
766+
767+
bn_rand = BN_new();
768+
if (! bn_rand ) {
769+
return enif_make_badarg(env);
770+
}
771+
772+
/* Get a (bits) bit random number */
773+
if (!BN_rand(bn_rand, bits, top, bottom)) {
774+
ret = atom_false;
775+
}
776+
else {
777+
/* Copy the bignum into an erlang mpint binary. */
778+
dlen = BN_num_bytes(bn_rand);
779+
data = enif_make_new_binary(env, dlen+4, &ret);
780+
put_int32(data, dlen);
781+
BN_bn2bin(bn_rand, data+4);
782+
ERL_VALGRIND_MAKE_MEM_DEFINED(data+4, dlen);
783+
}
784+
BN_free(bn_rand);
785+
786+
return ret;
787+
}
727788

728789
static int get_bn_from_mpint(ErlNifEnv* env, ERL_NIF_TERM term, BIGNUM** bnp)
729790
{

lib/crypto/doc/src/crypto.xml

Lines changed: 41 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
<erlref>
55
<header>
66
<copyright>
7-
<year>1999</year><year>2010</year>
7+
<year>1999</year><year>2011</year>
88
<holder>Ericsson AB. All Rights Reserved.</holder>
99
</copyright>
1010
<legalnotice>
@@ -618,6 +618,21 @@ Mpint() = <![CDATA[<<ByteLen:32/integer-big, Bytes:ByteLen/binary>>]]>
618618
number generator.</p>
619619
</desc>
620620
</func>
621+
<func>
622+
<name>strong_rand_bytes(N) -> binary()</name>
623+
<fsummary>Generate a binary of random bytes</fsummary>
624+
<type>
625+
<v>N = integer()</v>
626+
</type>
627+
<desc>
628+
<p>Generates N bytes randomly uniform 0..255, and returns the
629+
result in a binary. Uses a cryptographically secure prng seeded and
630+
periodically mixed with operating system provided entropy. By default
631+
this is the <c>RAND_bytes</c> method from OpenSSL.</p>
632+
<p>May throw exception <c>low_entropy</c> in case the random generator
633+
failed due to lack of secure "randomness".</p>
634+
</desc>
635+
</func>
621636
<func>
622637
<name>rand_uniform(Lo, Hi) -> N</name>
623638
<fsummary>Generate a random number</fsummary>
@@ -632,6 +647,31 @@ Mpint() = <![CDATA[<<ByteLen:32/integer-big, Bytes:ByteLen/binary>>]]>
632647
multi-precision integers.</p>
633648
</desc>
634649
</func>
650+
<func>
651+
<name>strong_rand_mpint(N, Top, Bottom) -> Mpint</name>
652+
<fsummary>Generate an N bit random number</fsummary>
653+
<type>
654+
<v>N = non_neg_integer()</v>
655+
<v>Top = -1 | 0 | 1</v>
656+
<v>Bottom = 0 | 1</v>
657+
<v>Mpint = binary()</v>
658+
</type>
659+
<desc>
660+
<p>Generate an N bit random number using OpenSSL's
661+
cryptographically strong pseudo random number generator
662+
<c>BN_rand</c>.</p>
663+
<p>The parameter <c>Top</c> places constraints on the most
664+
significant bits of the generated number. If <c>Top</c> is 1, then the
665+
two most significant bits will be set to 1, if <c>Top</c> is 0, the
666+
most significant bit will be 1, and if <c>Top</c> is -1 then no
667+
constraints are applied and thus the generated number may be less than
668+
N bits long.</p>
669+
<p>If <c>Bottom</c> is 1, then the generated number is
670+
constrained to be odd.</p>
671+
<p>May throw exception <c>low_entropy</c> in case the random generator
672+
failed due to lack of secure "randomness".</p>
673+
</desc>
674+
</func>
635675
<func>
636676
<name>mod_exp(N, P, M) -> Result</name>
637677
<fsummary>Perform N ^ P mod M</fsummary>

lib/crypto/doc/src/notes.xml

Lines changed: 16 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
<chapter>
55
<header>
66
<copyright>
7-
<year>1999</year><year>2010</year>
7+
<year>1999</year><year>2011</year>
88
<holder>Ericsson AB. All Rights Reserved.</holder>
99
</copyright>
1010
<legalnotice>
@@ -30,6 +30,21 @@
3030
</header>
3131
<p>This document describes the changes made to the Crypto application.</p>
3232

33+
<section><title>Crypto 2.0.2.2</title>
34+
35+
<section><title>Improvements and New Features</title>
36+
<list>
37+
<item>
38+
<p>
39+
Strengthened random number generation. (Thanks to Geoff Cant)</p>
40+
<p>
41+
Own Id: OTP-9225</p>
42+
</item>
43+
</list>
44+
</section>
45+
46+
</section>
47+
3348
<section><title>Crypto 2.0.2.1</title>
3449

3550
<section><title>Improvements and New Features</title>

lib/crypto/src/crypto.erl

Lines changed: 24 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
%%
22
%% %CopyrightBegin%
33
%%
4-
%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
4+
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
55
%%
66
%% The contents of this file are subject to the Erlang Public License,
77
%% Version 1.1, (the "License"); you may not use this file except in
@@ -46,6 +46,7 @@
4646
-export([rsa_private_encrypt/3, rsa_public_decrypt/3]).
4747
-export([dh_generate_key/1, dh_generate_key/2, dh_compute_key/3]).
4848
-export([rand_bytes/1, rand_bytes/3, rand_uniform/2]).
49+
-export([strong_rand_bytes/1, strong_rand_mpint/3]).
4950
-export([mod_exp/3, mpint/1, erlint/1]).
5051
%% -export([idea_cbc_encrypt/3, idea_cbc_decrypt/3]).
5152
-export([aes_cbc_128_encrypt/3, aes_cbc_128_decrypt/3]).
@@ -68,6 +69,8 @@
6869
des_ede3_cbc_encrypt, des_ede3_cbc_decrypt,
6970
aes_cfb_128_encrypt, aes_cfb_128_decrypt,
7071
rand_bytes,
72+
strong_rand_bytes,
73+
strong_rand_mpint,
7174
rand_uniform,
7275
mod_exp,
7376
dss_verify,dss_sign,
@@ -361,12 +364,32 @@ aes_cfb_128_crypt(_Key, _IVec, _Data, _IsEncrypt) -> ?nif_stub.
361364
%% RAND - pseudo random numbers using RN_ functions in crypto lib
362365
%%
363366
-spec rand_bytes(non_neg_integer()) -> binary().
367+
-spec strong_rand_bytes(non_neg_integer()) -> binary().
364368
-spec rand_uniform(crypto_integer(), crypto_integer()) ->
365369
crypto_integer().
370+
-spec strong_rand_mpint(Bits::non_neg_integer(),
371+
Top::-1..1,
372+
Bottom::0..1) -> binary().
366373

367374
rand_bytes(_Bytes) -> ?nif_stub.
375+
376+
strong_rand_bytes(Bytes) ->
377+
case strong_rand_bytes_nif(Bytes) of
378+
false -> erlang:error(low_entropy);
379+
Bin -> Bin
380+
end.
381+
strong_rand_bytes_nif(_Bytes) -> ?nif_stub.
382+
368383
rand_bytes(_Bytes, _Topmask, _Bottommask) -> ?nif_stub.
369384

385+
strong_rand_mpint(Bits, Top, Bottom) ->
386+
case strong_rand_mpint_nif(Bits,Top,Bottom) of
387+
false -> erlang:error(low_entropy);
388+
Bin -> Bin
389+
end.
390+
strong_rand_mpint_nif(_Bits, _Top, _Bottom) -> ?nif_stub.
391+
392+
370393
rand_uniform(From,To) when is_binary(From), is_binary(To) ->
371394
case rand_uniform_nif(From,To) of
372395
<<Len:32/integer, MSB, Rest/binary>> when MSB > 127 ->

lib/crypto/test/crypto_SUITE.erl

Lines changed: 31 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@
4646
aes_ctr/1,
4747
mod_exp_test/1,
4848
rand_uniform_test/1,
49+
strong_rand_test/1,
4950
rsa_verify_test/1,
5051
dsa_verify_test/1,
5152
rsa_sign_test/1,
@@ -68,7 +69,8 @@ all() ->
6869
md5_mac_io, sha, sha_update,
6970
%% sha256, sha256_update, sha512,sha512_update,
7071
des_cbc, aes_cfb, aes_cbc,
71-
aes_cbc_iter, aes_ctr, des_cbc_iter, des_ecb, rand_uniform_test,
72+
aes_cbc_iter, aes_ctr, des_cbc_iter, des_ecb,
73+
rand_uniform_test, strong_rand_test,
7274
rsa_verify_test, dsa_verify_test, rsa_sign_test,
7375
dsa_sign_test, rsa_encrypt_decrypt, dh, exor_test,
7476
rc4_test, rc4_stream_test, mod_exp_test, blowfish_cfb64,
@@ -708,6 +710,33 @@ rand_uniform_aux_test(N) ->
708710
?line t(R1 < H),
709711
?line rand_uniform_aux_test(N-1).
710712

713+
%%
714+
%%
715+
strong_rand_test(doc) ->
716+
"strong_rand_mpint and strong_random_bytes testing";
717+
strong_rand_test(suite) ->
718+
[];
719+
strong_rand_test(Config) when is_list(Config) ->
720+
strong_rand_aux_test(180),
721+
?line 10 = byte_size(crypto:strong_rand_bytes(10)).
722+
723+
strong_rand_aux_test(0) ->
724+
?line t(crypto:strong_rand_mpint(0,0,0) =:= <<0,0,0,0>>),
725+
ok;
726+
strong_rand_aux_test(1) ->
727+
?line t(crypto:erlint(crypto:strong_rand_mpint(1,0,1)) =:= 1),
728+
?line strong_rand_aux_test(0);
729+
strong_rand_aux_test(N) ->
730+
?line t(sru_length(crypto:strong_rand_mpint(N,-1,0)) =< N),
731+
?line t(sru_length(crypto:strong_rand_mpint(N,0,0)) =:= N),
732+
?line t(crypto:erlint(crypto:strong_rand_mpint(N,0,1)) band 1 =:= 1),
733+
?line t(crypto:erlint(crypto:strong_rand_mpint(N,1,0)) bsr (N - 2) =:= 2#11),
734+
?line strong_rand_aux_test(N-1).
735+
736+
sru_length(Mpint) ->
737+
I = crypto:erlint(Mpint),
738+
length(erlang:integer_to_list(I, 2)).
739+
711740
%%
712741
%%
713742
%%
@@ -1097,7 +1126,7 @@ worker_loop(0, _) ->
10971126
ok;
10981127
worker_loop(N, Config) ->
10991128
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,
1129+
aes_cfb, aes_cbc, des_cbc_iter, rand_uniform_test, strong_rand_test,
11011130
rsa_verify_test, exor_test, rc4_test, rc4_stream_test, mod_exp_test },
11021131

11031132
F = element(random:uniform(size(Funcs)),Funcs),

lib/crypto/vsn.mk

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
CRYPTO_VSN = 2.0.2.1
1+
CRYPTO_VSN = 2.0.2.2

lib/ssh/doc/src/notes.xml

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,19 @@
2929
<file>notes.xml</file>
3030
</header>
3131

32+
<section><title>Ssh 2.0.5</title>
33+
<section><title>Improvements and New Features</title>
34+
<list>
35+
<item>
36+
<p>
37+
Strengthened random number generation. (Thanks to Geoff Cant)</p>
38+
<p>
39+
Own Id: OTP-9225</p>
40+
</item>
41+
</list>
42+
</section>
43+
</section>
44+
3245
<section><title>Ssh 2.0.4</title>
3346
<section><title>Fixed Bugs and Malfunctions</title>
3447
<list>

lib/ssh/src/ssh.appup.src

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -19,34 +19,44 @@
1919

2020
{"%VSN%",
2121
[
22-
{"2.0.3", [{load_module, ssh_file, soft_purge, soft_purge, []},
22+
{"2.0.4", [{load_module, ssh_bits, soft_purge, soft_purge, []},
23+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []}]},
24+
{"2.0.3", [{load_module, ssh_bits, soft_purge, soft_purge, []},
25+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []},
26+
{load_module, ssh_file, soft_purge, soft_purge, []},
2327
{load_module, ssh, soft_purge, soft_purge, []},
2428
{load_module, ssh_rsa, soft_purge, soft_purge, []},
2529
{load_module, ssh_acceptor, soft_purge, soft_purge, []},
2630
{load_module, ssh_transport, soft_purge, soft_purge, []},
2731
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]},
28-
{"2.0.2", [{load_module, ssh_file, soft_purge, soft_purge, []},
32+
{"2.0.2", [{load_module, ssh_bits, soft_purge, soft_purge, []},
33+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []},
34+
{load_module, ssh_file, soft_purge, soft_purge, []},
2935
{load_module, ssh, soft_purge, soft_purge, []},
3036
{load_module, ssh_rsa, soft_purge, soft_purge, []},
3137
{load_module, ssh_acceptor, soft_purge, soft_purge, []},
3238
{load_module, ssh_transport, soft_purge, soft_purge, []},
33-
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]},
34-
{"2.0.1", [{restart_application, ssh}]}
39+
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]}
3540
],
3641
[
37-
{"2.0.3", [{load_module, ssh_file, soft_purge, soft_purge, []},
42+
{"2.0.4", [{load_module, ssh_bits, soft_purge, soft_purge, []},
43+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []}]},
44+
{"2.0.3", [{load_module, ssh_bits, soft_purge, soft_purge, []},
45+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []},
46+
{load_module, ssh_file, soft_purge, soft_purge, []},
3847
{load_module, ssh, soft_purge, soft_purge, []},
3948
{load_module, ssh_rsa, soft_purge, soft_purge, []},
4049
{load_module, ssh_acceptor, soft_purge, soft_purge, []},
4150
{load_module, ssh_transport, soft_purge, soft_purge, []},
4251
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]},
43-
{"2.0.2", [{load_module, ssh_file, soft_purge, soft_purge, []},
52+
{"2.0.2", [{load_module, ssh_bits, soft_purge, soft_purge, []},
53+
{load_module, ssh_connection_handler, soft_purge, soft_purge, []},
54+
{load_module, ssh_file, soft_purge, soft_purge, []},
4455
{load_module, ssh, soft_purge, soft_purge, []},
4556
{load_module, ssh_rsa, soft_purge, soft_purge, []},
4657
{load_module, ssh_acceptor, soft_purge, soft_purge, []},
4758
{load_module, ssh_transport, soft_purge, soft_purge, []},
48-
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]},
49-
{"2.0.1", [{restart_application, ssh}]}
59+
{load_module, ssh_connection_manager, soft_purge, soft_purge, []}]}
5060
]
5161
}.
5262

0 commit comments

Comments
 (0)