components/erlang/patches/ssh.patch
changeset 1119 8acf1591784d
parent 1118 6359871f13db
child 1120 87d4e3f1bdb4
equal deleted inserted replaced
1118:6359871f13db 1119:8acf1591784d
     1 --- otp_src_R12B-5/lib/ssh/src/ssh_connection_handler.erl	Mon Sep  1 14:51:52 2008
       
     2 +++ otp_src_R12B-5-patch/lib/ssh/src/ssh_connection_handler.erl	Thu Jun 23 10:56:21 2011
       
     3 @@ -94,8 +94,6 @@
       
     4  %% initialize. 
       
     5  %%--------------------------------------------------------------------
       
     6  init([Role, Manager, Socket, SshOpts]) ->
       
     7 -    {A,B,C} = erlang:now(),
       
     8 -    random:seed(A, B, C),
       
     9      {NumVsn, StrVsn} = ssh_transport:versions(Role, SshOpts),
       
    10      ssh_bits:install_messages(ssh_transport:transport_messages(NumVsn)),
       
    11      {Protocol, Callback, CloseTag} = 
       
    12 --- otp_src_R12B-5/lib/crypto/c_src/crypto_drv.c	Tue Nov  4 11:52:34 2008
       
    13 +++ otp_src_R12B-5-patch/lib/crypto/c_src/crypto_drv.c	Thu Jun 23 11:33:31 2011
       
    14 @@ -208,6 +208,9 @@
       
    15  #define DRV_SHA512_FINAL        58
       
    16  #endif
       
    17  
       
    18 +#define DRV_STRONG_RAND_BYTES   59
       
    19 +#define DRV_STRONG_RAND_MPINT   60
       
    20 +
       
    21  /* #define DRV_CBC_IDEA_ENCRYPT    34 */
       
    22  /* #define DRV_CBC_IDEA_DECRYPT    35 */
       
    23  
       
    24 @@ -604,7 +607,39 @@
       
    25          bin->orig_bytes[0] |= or_mask; /* bottommask */
       
    26          return rlen;
       
    27          break;
       
    28 -      
       
    29 +
       
    30 +    case DRV_STRONG_RAND_BYTES:
       
    31 +	/* buf = <<rlen:32/integer>> */
       
    32 +        if (len != 4)
       
    33 +            return -1;
       
    34 +	rlen = get_int32(buf);
       
    35 +        *rbuf = (char *)(bin = driver_alloc_binary(rlen));
       
    36 +	if (bin==NULL)
       
    37 +            return -1;
       
    38 +        if (RAND_bytes(bin->orig_bytes,rlen) != 1)
       
    39 +            return -1;
       
    40 +	return rlen;
       
    41 +
       
    42 +    case DRV_STRONG_RAND_MPINT:
       
    43 +        /* buf = <<rlen:32/integer,topmask:8/integer,bottommask:8/integer>> */
       
    44 +        if (len != 6)
       
    45 +            return -1;
       
    46 +        bn_rand = BN_new();
       
    47 +        if (! bn_rand )
       
    48 +            return -1;
       
    49 +
       
    50 +        if (!BN_rand(bn_rand, get_int32(buf), buf[4], buf[5])) {
       
    51 +            BN_free(bn_rand);
       
    52 +            return -1;
       
    53 +        }
       
    54 +
       
    55 +        dlen = BN_num_bytes(bn_rand);
       
    56 +        *rbuf = (char *)(bin = driver_alloc_binary(dlen));
       
    57 +        put_int32(bin->orig_bytes, dlen);
       
    58 +        BN_bn2bin(bn_rand, bin->orig_bytes+4);
       
    59 +        BN_free(bn_rand);
       
    60 +        return 1;
       
    61 +
       
    62      case DRV_RAND_UNIFORM:
       
    63        /* buf = <<from_len:32/integer,bn_from:from_len/binary,   *
       
    64         *         to_len:32/integer,bn_to:to_len/binary>>        */
       
    65 --- otp_src_R12B-5/lib/crypto/src/crypto.erl	Tue Nov  4 11:52:34 2008
       
    66 +++ otp_src_R12B-5-patch/lib/crypto/src/crypto.erl	Thu Jun 23 11:35:29 2011
       
    67 @@ -40,6 +40,7 @@
       
    68  -export([rsa_private_encrypt/3, rsa_public_decrypt/3]).
       
    69  -export([dh_generate_key/1, dh_generate_key/2, dh_compute_key/3]).
       
    70  -export([rand_bytes/1, rand_bytes/3, rand_uniform/2]).
       
    71 +-export([strong_rand_bytes/1, strong_rand_mpint/3]).
       
    72  -export([mod_exp/3, mpint/1, erlint/1]).
       
    73  %% -export([idea_cbc_encrypt/3, idea_cbc_decrypt/3]).
       
    74  -export([aes_cbc_128_encrypt/3, aes_cbc_128_decrypt/3]).
       
    75 @@ -110,6 +111,8 @@
       
    76  %% -define(SHA512_UPDATE,	 57).
       
    77  %% -define(SHA512_FINAL,	 58).
       
    78  
       
    79 +-define(STRONG_RAND_BYTES,	 59).
       
    80 +-define(STRONG_RAND_MPINT,	 60).
       
    81  
       
    82  %% -define(IDEA_CBC_ENCRYPT, 34).
       
    83  %% -define(IDEA_CBC_DECRYPT, 35).
       
    84 @@ -125,6 +128,8 @@
       
    85  		    des_ede3_cbc_encrypt, des_ede3_cbc_decrypt,
       
    86  		    aes_cfb_128_encrypt, aes_cfb_128_decrypt,
       
    87  		    rand_bytes,
       
    88 +		    strong_rand_bytes,
       
    89 +		    strong_rand_mpint,
       
    90  		    rand_uniform,
       
    91  		    mod_exp,
       
    92  		    dss_verify,dss_sign,
       
    93 @@ -321,10 +326,19 @@
       
    94  
       
    95  rand_bytes(Bytes) ->
       
    96      rand_bytes(Bytes, 0, 0).
       
    97 +
       
    98 +strong_rand_bytes(Bytes) ->
       
    99 +    control(?STRONG_RAND_BYTES,[<<Bytes:32/integer>>]).
       
   100 +
       
   101  rand_bytes(Bytes, Topmask, Bottommask) ->
       
   102      control(?RAND_BYTES,[<<Bytes:32/integer,
       
   103  			  Topmask:8/integer,
       
   104  			  Bottommask:8/integer>>]).
       
   105 +
       
   106 +strong_rand_mpint(Bits, Top, Bottom) ->
       
   107 +    control(?STRONG_RAND_MPINT,[<<Bits:32/integer,
       
   108 +			  Top:8/integer,
       
   109 +			  Bottom:8/integer>>]).
       
   110  
       
   111  rand_uniform(From,To) when is_binary(From), is_binary(To) ->
       
   112      case control(?RAND_UNIFORM,[From,To]) of
       
   113 --- otp_src_R12B-5/lib/ssh/src/ssh_bits.erl	Mon Sep  1 14:51:49 2008
       
   114 +++ otp_src_R12B-5-patch/lib/ssh/src/ssh_bits.erl	Thu Jun 23 10:56:25 2011
       
   115 @@ -33,7 +33,7 @@
       
   116  %% integer utils
       
   117  -export([isize/1]).
       
   118  -export([irandom/1, irandom/3]).
       
   119 --export([random/1, random/3]).
       
   120 +-export([random/1]).
       
   121  -export([xor_bits/2, fill_bits/2]).
       
   122  -export([i2bin/2, bin2i/1]).
       
   123  
       
   124 @@ -400,9 +400,6 @@
       
   125  irandom(Bits) ->
       
   126      irandom(Bits, 1, 0).
       
   127  
       
   128 -%% irandom_odd(Bits) ->
       
   129 -%%     irandom(Bits, 1, 1).
       
   130 -
       
   131  %%
       
   132  %% irandom(N, Top, Bottom)
       
   133  %%
       
   134 @@ -413,22 +410,8 @@
       
   135  %%       Bot = 0 - do not set the least signifcant bit
       
   136  %%       Bot = 1 - set the least signifcant bit (i.e always odd)
       
   137  %%
       
   138 -irandom(0, _Top, _Bottom) -> 
       
   139 -    0;
       
   140 -irandom(Bits, Top, Bottom) ->
       
   141 -    Bytes = (Bits+7) div 8,
       
   142 -    Skip  = (8-(Bits rem 8)) rem 8,
       
   143 -    TMask = case Top of
       
   144 -		  0 -> 0;
       
   145 -		  1 -> 16#80;
       
   146 -		  2 -> 16#c0
       
   147 -	      end,
       
   148 -    BMask = case Bottom of
       
   149 -		0 -> 0;
       
   150 -		1 -> (1 bsl Skip)
       
   151 -	    end,
       
   152 -    <<X:Bits/big-unsigned-integer, _:Skip>> = random(Bytes, TMask, BMask),
       
   153 -    X.
       
   154 +irandom(Bits, Top, Bottom) -> 
       
   155 +    crypto:erlint(crypto:strong_rand_mpint(Bits, Top - 1, Bottom)).
       
   156  
       
   157  %%
       
   158  %% random/1
       
   159 @@ -435,37 +419,9 @@
       
   160  %%   Generate N random bytes
       
   161  %%
       
   162  random(N) ->
       
   163 -    random(N, 0, 0).
       
   164 +    crypto:strong_rand_bytes(N).
       
   165  
       
   166 -random(N, TMask, BMask) ->
       
   167 -    list_to_binary(rnd(N, TMask, BMask)).
       
   168 -
       
   169 -%% random/3
       
   170 -%%   random(Bytes, TopMask, BotMask)
       
   171 -%% where 
       
   172 -%% Bytes is the number of bytes to generate
       
   173 -%% TopMask is bitwised or'ed to the first byte
       
   174 -%% BotMask is bitwised or'ed to the last byte
       
   175  %%
       
   176 -rnd(0, _TMask, _BMask) ->
       
   177 -    [];
       
   178 -rnd(1, TMask, BMask) ->
       
   179 -    [(rand8() bor TMask) bor BMask];
       
   180 -rnd(N, TMask, BMask) ->
       
   181 -    [(rand8() bor TMask) | rnd_n(N-1, BMask)].
       
   182 -
       
   183 -rnd_n(1, BMask) ->
       
   184 -    [rand8() bor BMask];
       
   185 -rnd_n(I, BMask) ->
       
   186 -    [rand8() | rnd_n(I-1, BMask)].
       
   187 -
       
   188 -rand8() ->
       
   189 -    (rand32() bsr 8) band 16#ff.
       
   190 -
       
   191 -rand32() ->
       
   192 -    random:uniform(16#100000000) -1.
       
   193 -
       
   194 -%%
       
   195  %% Base 64 encode/decode
       
   196  %%
       
   197