~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/ssl/test/ssl_test_lib.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2008-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
22
22
 
23
23
-include("test_server.hrl").
24
24
-include("test_server_line.hrl").
 
25
-include_lib("public_key/include/public_key.hrl").
25
26
 
26
27
%% Note: This directive should only be used in test suites.
27
28
-compile(export_all).
81
82
        no_result_msg ->
82
83
            ok;
83
84
        Msg ->
84
 
            test_server:format("Msg: ~p ~n", [Msg]),    
 
85
            test_server:format("Server Msg: ~p ~n", [Msg]),
85
86
            Pid ! {self(), Msg}
86
87
    end,
87
 
    receive 
 
88
    receive
88
89
        listen ->
89
90
            run_server(ListenSocket, Opts);
 
91
        {listen, MFA} ->
 
92
            run_server(ListenSocket, [MFA | proplists:delete(mfa, Opts)]);
90
93
        close ->
91
 
            ok = rpc:call(Node, ssl, close, [AcceptSocket])
 
94
            test_server:format("Server closing  ~p ~n", [self()]),
 
95
            Result = rpc:call(Node, ssl, close, [AcceptSocket], 500),
 
96
            test_server:format("Result ~p ~n", [Result]);
 
97
        {ssl_closed, _} ->
 
98
            ok
92
99
    end.
93
100
 
94
101
%%% To enable to test with s_client -reconnect
122
129
           remove_close_msg(ReconnectTimes -1)
123
130
    end.
124
131
            
125
 
 
126
132
start_client(Args) ->
127
 
    Result = spawn_link(?MODULE, run_client, [Args]),
 
133
    Result = spawn_link(?MODULE, run_client, [lists:delete(return_socket, Args)]),
128
134
    receive 
129
 
        connected ->
130
 
            Result
 
135
        { connected, Socket } ->
 
136
        case lists:member(return_socket, Args) of
 
137
            true -> { Result, Socket };
 
138
            false -> Result
 
139
        end
131
140
    end.
132
141
 
133
142
run_client(Opts) ->
139
148
    test_server:format("ssl:connect(~p, ~p, ~p)~n", [Host, Port, Options]),
140
149
    case rpc:call(Node, ssl, connect, [Host, Port, Options]) of
141
150
        {ok, Socket} ->
142
 
            Pid ! connected,
 
151
            Pid ! { connected, Socket },
143
152
            test_server:format("Client: connected~n", []), 
144
153
            %% In specail cases we want to know the client port, it will
145
154
            %% be indicated by sending {port, 0} in options list!
151
160
                no_result_msg ->
152
161
                    ok;
153
162
                Msg ->
 
163
                    test_server:format("Client Msg: ~p ~n", [Msg]),
154
164
                    Pid ! {self(), Msg}
155
165
            end,
156
 
            receive 
 
166
            receive
157
167
                close ->
158
 
                    ok = rpc:call(Node, ssl, close, [Socket])
 
168
                    test_server:format("Client closing~n", []),
 
169
                    rpc:call(Node, ssl, close, [Socket]);
 
170
                {ssl_closed, Socket} ->
 
171
                    ok
159
172
            end;
160
173
        {error, Reason} ->
161
 
            test_server:format("Client: connection failed: ~p ~n", [Reason]), 
 
174
            test_server:format("Client: connection failed: ~p ~n", [Reason]),
162
175
               Pid ! {self(), {error, Reason}}
163
176
    end.
164
177
 
165
178
close(Pid) ->
166
 
    Pid ! close.
 
179
    test_server:format("Close ~p ~n", [Pid]),
 
180
    Monitor = erlang:monitor(process, Pid),
 
181
    Pid ! close,
 
182
    receive
 
183
        {'DOWN', Monitor, process, Pid, Reason} ->
 
184
            erlang:demonitor(Monitor),
 
185
            test_server:format("Pid: ~p down due to:~p ~n", [Pid, Reason])
 
186
    end.
167
187
 
168
188
check_result(Server, ServerMsg, Client, ClientMsg) -> 
169
189
    receive 
208
228
            test_server:fail(Reason)
209
229
    end.
210
230
 
211
 
check_result_ignore_renegotiation_reject(Pid, Msg) -> 
212
 
    receive 
213
 
        {Pid,  fail_session_fatal_alert_during_renegotiation} ->
214
 
            test_server:comment("Server rejected old renegotiation"),
215
 
            ok;
216
 
        {ssl_error, _, esslconnect} ->
217
 
            test_server:comment("Server rejected old renegotiation"),
218
 
            ok;
219
 
        {Pid, Msg} -> 
220
 
            ok;
221
 
        {Port, {data,Debug}} when is_port(Port) ->
222
 
            io:format("openssl ~s~n",[Debug]),
223
 
            check_result(Pid,Msg);
224
 
        Unexpected ->
225
 
            Reason = {{expected, {Pid, Msg}}, 
226
 
                      {got, Unexpected}},
227
 
            test_server:fail(Reason)
228
 
    end.
229
 
 
230
 
 
231
231
wait_for_result(Server, ServerMsg, Client, ClientMsg) -> 
232
232
    receive 
233
233
        {Server, ServerMsg} -> 
234
234
            receive 
235
235
                {Client, ClientMsg} ->
236
 
                    ok;
237
 
                Unexpected ->
238
 
                    Unexpected
 
236
                    ok
 
237
                %% Unexpected ->
 
238
                %%     Unexpected
239
239
            end;
240
240
        {Client, ClientMsg} -> 
241
241
            receive 
242
242
                {Server, ServerMsg} ->
243
 
                    ok;
244
 
                Unexpected ->
245
 
                    Unexpected
 
243
                    ok
 
244
                %% Unexpected ->
 
245
                %%     Unexpected
246
246
            end;
247
247
        {Port, {data,Debug}} when is_port(Port) ->
248
248
            io:format("openssl ~s~n",[Debug]),
249
 
            wait_for_result(Server, ServerMsg, Client, ClientMsg);
250
 
        Unexpected ->
251
 
            Unexpected
 
249
            wait_for_result(Server, ServerMsg, Client, ClientMsg)
 
250
        %% Unexpected ->
 
251
        %%     Unexpected
252
252
    end.
253
253
 
254
254
 
258
258
            ok;
259
259
        {Port, {data,Debug}} when is_port(Port) ->
260
260
            io:format("openssl ~s~n",[Debug]),
261
 
            wait_for_result(Pid,Msg);
262
 
        Unexpected ->
263
 
            Unexpected
 
261
            wait_for_result(Pid,Msg)
 
262
        %% Unexpected ->
 
263
        %%     Unexpected
264
264
    end.
265
265
 
266
266
cert_options(Config) ->
327
327
 
328
328
make_dsa_cert(Config) ->
329
329
    
330
 
    {ServerCaCertFile, ServerCertFile, ServerKeyFile} = make_dsa_cert_files("server", Config),
331
 
    {ClientCaCertFile, ClientCertFile, ClientKeyFile} = make_dsa_cert_files("client", Config),
 
330
    {ServerCaCertFile, ServerCertFile, ServerKeyFile} = make_cert_files("server", Config, dsa, dsa, ""),
 
331
    {ClientCaCertFile, ClientCertFile, ClientKeyFile} = make_cert_files("client", Config, dsa, dsa, ""),
332
332
    [{server_dsa_opts, [{ssl_imp, new},{reuseaddr, true}, 
333
333
                                 {cacertfile, ServerCaCertFile},
334
334
                                 {certfile, ServerCertFile}, {keyfile, ServerKeyFile}]},
342
342
     | Config].
343
343
 
344
344
 
345
 
    
346
 
make_dsa_cert_files(RoleStr, Config) ->    
347
 
    CaInfo = {CaCert, _} = erl_make_certs:make_cert([{key, dsa}]),
348
 
    {Cert, CertKey} = erl_make_certs:make_cert([{key, dsa}, {issuer, CaInfo}]),
 
345
make_mix_cert(Config) ->
 
346
    {ServerCaCertFile, ServerCertFile, ServerKeyFile} = make_cert_files("server", Config, dsa,
 
347
                                                                        rsa, "mix"),
 
348
    {ClientCaCertFile, ClientCertFile, ClientKeyFile} = make_cert_files("client", Config, dsa,
 
349
                                                                        rsa, "mix"),
 
350
    [{server_mix_opts, [{ssl_imp, new},{reuseaddr, true},
 
351
                                 {cacertfile, ServerCaCertFile},
 
352
                                 {certfile, ServerCertFile}, {keyfile, ServerKeyFile}]},
 
353
     {server_mix_verify_opts, [{ssl_imp, new},{reuseaddr, true},
 
354
                               {cacertfile, ClientCaCertFile},
 
355
                               {certfile, ServerCertFile}, {keyfile, ServerKeyFile},
 
356
                               {verify, verify_peer}]},
 
357
     {client_mix_opts, [{ssl_imp, new},{reuseaddr, true},
 
358
                        {cacertfile, ClientCaCertFile},
 
359
                        {certfile, ClientCertFile}, {keyfile, ClientKeyFile}]}
 
360
     | Config].
 
361
 
 
362
make_cert_files(RoleStr, Config, Alg1, Alg2, Prefix) ->
 
363
    Alg1Str = atom_to_list(Alg1),
 
364
    Alg2Str = atom_to_list(Alg2),
 
365
    CaInfo = {CaCert, _} = erl_make_certs:make_cert([{key, Alg1}]),
 
366
    {Cert, CertKey} = erl_make_certs:make_cert([{key, Alg2}, {issuer, CaInfo}]),
349
367
    CaCertFile = filename:join([?config(priv_dir, Config), 
350
 
                                RoleStr, "dsa_cacerts.pem"]),
 
368
                                RoleStr, Prefix ++ Alg1Str ++ "_cacerts.pem"]),
351
369
    CertFile = filename:join([?config(priv_dir, Config), 
352
 
                              RoleStr, "dsa_cert.pem"]),
 
370
                              RoleStr, Prefix ++ Alg2Str ++ "_cert.pem"]),
353
371
    KeyFile = filename:join([?config(priv_dir, Config), 
354
 
                                   RoleStr, "dsa_key.pem"]),
 
372
                                   RoleStr, Prefix ++ Alg2Str ++ "_key.pem"]),
355
373
    
356
374
    der_to_pem(CaCertFile, [{'Certificate', CaCert, not_encrypted}]),
357
375
    der_to_pem(CertFile, [{'Certificate', Cert, not_encrypted}]),
358
376
    der_to_pem(KeyFile, [CertKey]),
359
377
    {CaCertFile, CertFile, KeyFile}.
360
378
 
 
379
 
361
380
start_upgrade_server(Args) ->
362
381
    Result = spawn_link(?MODULE, run_upgrade_server, [Args]),
363
382
    receive
395
414
                                end,
396
415
        {Module, Function, Args} = proplists:get_value(mfa, Opts),
397
416
        Msg = rpc:call(Node, Module, Function, [SslAcceptSocket | Args]),
 
417
        test_server:format("Upgrade Server Msg: ~p ~n", [Msg]),
398
418
        Pid ! {self(), Msg},
399
419
        receive
400
420
            close ->
401
 
                ok = rpc:call(Node, ssl, close, [SslAcceptSocket])
 
421
                test_server:format("Upgrade Server closing~n", []),
 
422
                rpc:call(Node, ssl, close, [SslAcceptSocket])
402
423
        end
403
424
    catch error:{badmatch, Error} ->
404
425
            Pid ! {self(), Error}
428
449
    test_server:format("apply(~p, ~p, ~p)~n", 
429
450
                       [Module, Function, [SslSocket | Args]]),
430
451
    Msg = rpc:call(Node, Module, Function, [SslSocket | Args]),
 
452
    test_server:format("Upgrade Client Msg: ~p ~n", [Msg]),
431
453
    Pid ! {self(), Msg},
432
454
    receive 
433
455
        close ->
434
 
            ok = rpc:call(Node, ssl, close, [SslSocket])
 
456
            test_server:format("Upgrade Client closing~n", []),
 
457
            rpc:call(Node, ssl, close, [SslSocket])
435
458
    end.
436
459
 
437
460
start_upgrade_server_error(Args) ->
639
662
    %% to properly test "cipher state" handling
640
663
    ssl:send(Socket, "Hello\n"),
641
664
    receive 
 
665
        {ssl, Socket, "H"} ->
 
666
            ssl:send(Socket, " world\n"),
 
667
            receive_rizzo_duong_beast();
642
668
        {ssl, Socket, "Hello\n"} ->
643
669
            ssl:send(Socket, " world\n"),
644
670
            receive
648
674
        Other ->
649
675
            {unexpected, Other}
650
676
    end.
 
677
 
 
678
session_info_result(Socket) ->
 
679
    ssl:session_info(Socket).
 
680
 
 
681
 
 
682
public_key(#'PrivateKeyInfo'{privateKeyAlgorithm =
 
683
                                 #'PrivateKeyInfo_privateKeyAlgorithm'{algorithm = ?rsaEncryption},
 
684
                             privateKey = Key}) ->
 
685
    public_key:der_decode('RSAPrivateKey', iolist_to_binary(Key));
 
686
 
 
687
public_key(#'PrivateKeyInfo'{privateKeyAlgorithm =
 
688
                                 #'PrivateKeyInfo_privateKeyAlgorithm'{algorithm = ?'id-dsa'},
 
689
                             privateKey = Key}) ->
 
690
    public_key:der_decode('DSAPrivateKey', iolist_to_binary(Key));
 
691
public_key(Key) ->
 
692
    Key.
 
693
receive_rizzo_duong_beast() ->
 
694
    receive 
 
695
        {ssl, _, "ello\n"} ->
 
696
            receive 
 
697
                {ssl, _, " "} ->
 
698
                    receive
 
699
                        {ssl, _, "world\n"} ->
 
700
                            ok
 
701
                    end
 
702
            end
 
703
    end.
 
704
 
 
705
state([{data,[{"State", State}]} | _]) ->
 
706
    State;
 
707
state([{data,[{"StateData", State}]} | _]) ->
 
708
    State;
 
709
state([_ | Rest]) ->
 
710
    state(Rest).