~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2007-2009. 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
 
 
20
%%
 
21
 
 
22
 
 
23
%%%-------------------------------------------------------------------
 
24
%%% File    : ssl_dist_SUITE.erl
 
25
%%% Author  : Rickard Green
 
26
%%% Description : Test that the Erlang distribution works over ssl.
 
27
%%%
 
28
%%% Created : 15 Nov 2007 by Rickard Green
 
29
%%%-------------------------------------------------------------------
 
30
-module(old_ssl_dist_SUITE).
 
31
 
 
32
-include("test_server.hrl").
 
33
 
 
34
-define(DEFAULT_TIMETRAP_SECS, 240).
 
35
 
 
36
-define(AWAIT_SLL_NODE_UP_TIMEOUT, 30000).
 
37
 
 
38
-export([all/1]).
 
39
-export([init_per_suite/1,
 
40
         end_per_suite/1,
 
41
         init_per_testcase/2,
 
42
         fin_per_testcase/2]).
 
43
-export([cnct2tstsrvr/1]).
 
44
 
 
45
-export([basic/1]).
 
46
 
 
47
-record(node_handle, {connection_handler, socket, name, nodename}).
 
48
 
 
49
all(doc) ->
 
50
    [];
 
51
all(suite) ->
 
52
    [basic].
 
53
 
 
54
init_per_suite(Config) ->
 
55
    add_ssl_opts_config(Config).
 
56
 
 
57
end_per_suite(Config) ->
 
58
    Config.
 
59
 
 
60
init_per_testcase(Case, Config) when list(Config) ->
 
61
    Dog = ?t:timetrap(?t:seconds(?DEFAULT_TIMETRAP_SECS)),
 
62
    [{watchdog, Dog},{testcase, Case}|Config].
 
63
 
 
64
fin_per_testcase(_Case, Config) when list(Config) ->
 
65
    Dog = ?config(watchdog, Config),
 
66
    ?t:timetrap_cancel(Dog),
 
67
    ok.
 
68
 
 
69
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
70
%%                                                                       %%
 
71
%% Testcases                                                             %%
 
72
%%                                                                       %%
 
73
 
 
74
basic(doc) ->
 
75
    ["Test that two nodes can connect via ssl distribution"];
 
76
basic(suite) ->
 
77
    [];
 
78
basic(Config) when is_list(Config) ->
 
79
    ?line NH1 = start_ssl_node(Config),
 
80
    ?line Node1 = NH1#node_handle.nodename,
 
81
    ?line NH2 = start_ssl_node(Config),
 
82
    ?line Node2 = NH2#node_handle.nodename,
 
83
 
 
84
    ?line pong = apply_on_ssl_node(NH1, fun () -> net_adm:ping(Node2) end),
 
85
 
 
86
    ?line [Node2] = apply_on_ssl_node(NH1, fun () -> nodes() end),
 
87
    ?line [Node1] = apply_on_ssl_node(NH2, fun () -> nodes() end),
 
88
 
 
89
    %% The test_server node has the same cookie as the ssl nodes
 
90
    %% but it should not be able to communicate with the ssl nodes
 
91
    %% via the erlang distribution.
 
92
    ?line pang = net_adm:ping(Node1),
 
93
    ?line pang = net_adm:ping(Node2),
 
94
 
 
95
 
 
96
    %%
 
97
    %% Check that we are able to communicate over the erlang
 
98
    %% distribution between the ssl nodes.
 
99
    %%
 
100
    ?line Ref = make_ref(),
 
101
    ?line spawn(fun () ->
 
102
                        apply_on_ssl_node(
 
103
                          NH1,
 
104
                          fun () -> 
 
105
                                  tstsrvr_format("Hi from ~p!~n",
 
106
                                                 [node()]),
 
107
                                  send_to_tstcntrl({Ref, self()}),
 
108
                                  receive
 
109
                                      {From, ping} ->
 
110
                                          From ! {self(), pong}
 
111
                                  end
 
112
                          end)
 
113
                end),
 
114
    ?line receive
 
115
              {Ref, SslPid} ->
 
116
                  ?line ok = apply_on_ssl_node(
 
117
                               NH2,
 
118
                               fun () ->
 
119
                                       tstsrvr_format("Hi from ~p!~n",
 
120
                                                      [node()]),
 
121
                                       SslPid ! {self(), ping},
 
122
                                       receive
 
123
                                           {SslPid, pong} ->
 
124
                                               ok
 
125
                                       end
 
126
                               end)
 
127
          end,
 
128
 
 
129
    ?line stop_ssl_node(NH1),
 
130
    ?line stop_ssl_node(NH2),
 
131
    ?line success(Config).
 
132
 
 
133
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
134
%%                                                                       %%
 
135
%% Internal functions                                                    %%
 
136
%%                                                                       %%
 
137
 
 
138
%%
 
139
%% ssl_node side api
 
140
%%
 
141
 
 
142
tstsrvr_format(Fmt, ArgList) ->
 
143
    send_to_tstsrvr({format, Fmt, ArgList}).
 
144
 
 
145
send_to_tstcntrl(Message) ->
 
146
    send_to_tstsrvr({message, Message}).
 
147
 
 
148
 
 
149
%%
 
150
%% test_server side api
 
151
%%
 
152
 
 
153
apply_on_ssl_node(Node, M, F, A) when atom(M), atom(F), list(A) ->
 
154
    Ref = make_ref(),
 
155
    send_to_ssl_node(Node, {apply, self(), Ref, M, F, A}),
 
156
    receive
 
157
        {Ref, Result} ->
 
158
            Result
 
159
    end.
 
160
 
 
161
apply_on_ssl_node(Node, Fun) when is_function(Fun, 0) ->
 
162
    Ref = make_ref(),
 
163
    send_to_ssl_node(Node, {apply, self(), Ref, Fun}),
 
164
    receive
 
165
        {Ref, Result} ->
 
166
            Result
 
167
    end.
 
168
 
 
169
stop_ssl_node(#node_handle{connection_handler = Handler,
 
170
                           socket = Socket,
 
171
                           name = Name}) ->
 
172
    ?t:format("Trying to stop ssl node ~s.~n", [Name]),
 
173
    Mon = erlang:monitor(process, Handler),
 
174
    unlink(Handler),
 
175
    case gen_tcp:send(Socket, term_to_binary(stop)) of
 
176
        ok ->
 
177
            receive
 
178
                {'DOWN', Mon, process, Handler, Reason} ->
 
179
                    case Reason of
 
180
                        normal -> ok;
 
181
                        _ -> exit(Reason)
 
182
                    end
 
183
            end;
 
184
        Error ->
 
185
            erlang:demonitor(Mon, [flush]),
 
186
            exit(Error)
 
187
    end.
 
188
 
 
189
start_ssl_node(Config) ->
 
190
    start_ssl_node(Config, "").
 
191
 
 
192
start_ssl_node(Config, XArgs) ->
 
193
    Name = mk_node_name(Config),
 
194
    SSL = ?config(ssl_opts, Config),
 
195
    SSLDistOpts = setup_dist_opts(Name, ?config(priv_dir, Config)),
 
196
    start_ssl_node_raw(Name, SSL ++ " " ++ SSLDistOpts ++ XArgs).
 
197
 
 
198
start_ssl_node_raw(Name, Args) ->
 
199
    {ok, LSock} = gen_tcp:listen(0,
 
200
                                 [binary, {packet, 4}, {active, false}]),
 
201
    {ok, ListenPort} = inet:port(LSock),
 
202
    CmdLine = mk_node_cmdline(ListenPort, Name, Args),
 
203
    ?t:format("Attempting to start ssl node ~s: ~s~n", [Name, CmdLine]),
 
204
    case open_port({spawn, CmdLine}, []) of
 
205
        Port when port(Port) ->
 
206
            unlink(Port),
 
207
            erlang:port_close(Port),
 
208
            case await_ssl_node_up(Name, LSock) of
 
209
                #node_handle{} = NodeHandle ->
 
210
                    ?t:format("Ssl node ~s started.~n", [Name]),
 
211
                    NodeName = list_to_atom(Name ++ "@" ++ host_name()),
 
212
                    NodeHandle#node_handle{nodename = NodeName};
 
213
                Error ->
 
214
                    exit({failed_to_start_node, Name, Error})
 
215
            end;
 
216
        Error ->
 
217
            exit({failed_to_start_node, Name, Error})
 
218
    end.
 
219
 
 
220
%%
 
221
%% command line creation
 
222
%%
 
223
 
 
224
host_name() ->
 
225
    [$@ | Host] = lists:dropwhile(fun ($@) -> false; (_) -> true end,
 
226
                                  atom_to_list(node())),
 
227
    Host.
 
228
 
 
229
mk_node_name(Config) ->
 
230
    {A, B, C} = erlang:now(),
 
231
    Case = ?config(testcase, Config),
 
232
    atom_to_list(?MODULE)
 
233
        ++ "_"
 
234
        ++ atom_to_list(Case)
 
235
        ++ "_"
 
236
        ++ integer_to_list(A)
 
237
        ++ "-"
 
238
        ++ integer_to_list(B)
 
239
        ++ "-"
 
240
        ++ integer_to_list(C).
 
241
 
 
242
mk_node_cmdline(ListenPort, Name, Args) ->
 
243
    Static = "-detached -noinput",
 
244
    Pa = filename:dirname(code:which(?MODULE)),
 
245
    Prog = case catch init:get_argument(progname) of
 
246
               {ok,[[P]]} -> P;
 
247
               _ -> exit(no_progname_argument_found)
 
248
           end,
 
249
    NameSw = case net_kernel:longnames() of
 
250
                 false -> "-sname ";
 
251
                 _ -> "-name "
 
252
             end,
 
253
    {ok, Pwd} = file:get_cwd(),
 
254
    Prog ++ " "
 
255
        ++ Static ++ " "
 
256
        ++ NameSw ++ " " ++ Name ++ " "
 
257
        ++ "-pa " ++ Pa ++ " "
 
258
        ++ "-run " ++ atom_to_list(?MODULE) ++ " cnct2tstsrvr "
 
259
        ++ host_name() ++ " "
 
260
        ++ integer_to_list(ListenPort) ++ " "
 
261
        ++ Args ++ " "
 
262
        ++ "-env ERL_CRASH_DUMP " ++ Pwd ++ "/erl_crash_dump." ++ Name ++ " "
 
263
        ++ "-setcookie " ++ atom_to_list(erlang:get_cookie()).
 
264
 
 
265
%%
 
266
%% Connection handler test_server side
 
267
%%
 
268
 
 
269
await_ssl_node_up(Name, LSock) ->
 
270
    case gen_tcp:accept(LSock, ?AWAIT_SLL_NODE_UP_TIMEOUT) of
 
271
        timeout ->
 
272
            gen_tcp:close(LSock),
 
273
            ?t:format("Timeout waiting for ssl node ~s to come up~n",
 
274
                      [Name]),
 
275
            timeout;
 
276
        {ok, Socket} ->
 
277
            gen_tcp:close(LSock),
 
278
            case gen_tcp:recv(Socket, 0) of
 
279
                {ok, Bin} ->
 
280
                    check_ssl_node_up(Socket, Name, Bin);
 
281
                {error, closed} ->
 
282
                    gen_tcp:close(Socket),
 
283
                    exit({lost_connection_with_ssl_node_before_up, Name})
 
284
            end;
 
285
        {error, Error} ->
 
286
            gen_tcp:close(LSock),
 
287
            exit({accept_failed, Error})
 
288
    end.
 
289
 
 
290
check_ssl_node_up(Socket, Name, Bin) ->
 
291
    case catch binary_to_term(Bin) of
 
292
        {'EXIT', _} ->
 
293
            gen_tcp:close(Socket),
 
294
            exit({bad_data_received_from_ssl_node, Name, Bin});
 
295
        {ssl_node_up, NodeName} ->
 
296
            case list_to_atom(Name++"@"++host_name()) of
 
297
                NodeName ->
 
298
                    Parent = self(),
 
299
                    Go = make_ref(),
 
300
                    %% Spawn connection handler on test server side
 
301
                    Pid = spawn_link(
 
302
                            fun () ->
 
303
                                    receive Go -> ok end,
 
304
                                    tstsrvr_con_loop(Name, Socket, Parent)
 
305
                            end),
 
306
                    ok = gen_tcp:controlling_process(Socket, Pid),
 
307
                    Pid ! Go,
 
308
                    #node_handle{connection_handler = Pid,
 
309
                                 socket = Socket,
 
310
                                 name = Name};
 
311
                _ ->
 
312
                    exit({unexpected_ssl_node_connected, NodeName})
 
313
            end;
 
314
        Msg ->
 
315
            exit({unexpected_msg_instead_of_ssl_node_up, Name, Msg})
 
316
    end.
 
317
 
 
318
send_to_ssl_node(#node_handle{connection_handler = Hndlr}, Term) ->
 
319
    Hndlr ! {relay_to_ssl_node, term_to_binary(Term)},
 
320
    ok.
 
321
 
 
322
tstsrvr_con_loop(Name, Socket, Parent) ->
 
323
    inet:setopts(Socket,[{active,once}]),
 
324
    receive
 
325
        {relay_to_ssl_node, Data} when is_binary(Data) ->
 
326
            case gen_tcp:send(Socket, Data) of
 
327
                ok ->
 
328
                    ok;
 
329
                _Error ->
 
330
                    gen_tcp:close(Socket),
 
331
                    exit({failed_to_relay_data_to_ssl_node, Name, Data})
 
332
            end;
 
333
        {tcp, Socket, Bin} ->
 
334
            case catch binary_to_term(Bin) of
 
335
                {'EXIT', _} ->
 
336
                    gen_tcp:close(Socket),
 
337
                    exit({bad_data_received_from_ssl_node, Name, Bin});
 
338
                {format, FmtStr, ArgList} ->
 
339
                    ?t:format(FmtStr, ArgList);
 
340
                {message, Msg} ->
 
341
                    Parent ! Msg;
 
342
                {apply_res, To, Ref, Res} ->
 
343
                    To ! {Ref, Res};
 
344
                bye ->
 
345
                    ?t:format("Ssl node ~s stopped.~n", [Name]),
 
346
                    gen_tcp:close(Socket),
 
347
                    exit(normal);
 
348
                Unknown ->
 
349
                    exit({unexpected_message_from_ssl_node, Name, Unknown})
 
350
            end;
 
351
        {tcp_closed, Socket} ->
 
352
            gen_tcp:close(Socket),
 
353
            exit({lost_connection_with_ssl_node, Name})
 
354
    end,
 
355
    tstsrvr_con_loop(Name, Socket, Parent).
 
356
 
 
357
%%
 
358
%% Connection handler ssl_node side
 
359
%%
 
360
 
 
361
% cnct2tstsrvr() is called via command line arg -run ...
 
362
cnct2tstsrvr([Host, Port]) when list(Host), list(Port) ->
 
363
    %% Spawn connection handler on ssl node side
 
364
    ConnHandler
 
365
        = spawn(fun () ->
 
366
                        case catch gen_tcp:connect(Host,
 
367
                                                   list_to_integer(Port),
 
368
                                                   [binary,
 
369
                                                    {packet, 4},
 
370
                                                    {active, false}]) of
 
371
                            {ok, Socket} ->
 
372
                                notify_ssl_node_up(Socket),
 
373
                                ets:new(test_server_info,
 
374
                                        [set,
 
375
                                         public,
 
376
                                         named_table,
 
377
                                         {keypos, 1}]),
 
378
                                ets:insert(test_server_info,
 
379
                                           {test_server_handler, self()}),
 
380
                                ssl_node_con_loop(Socket);
 
381
                            _Error ->
 
382
                                halt("Failed to connect to test server")
 
383
                        end
 
384
                end),
 
385
    spawn(fun () ->
 
386
                  Mon = erlang:monitor(process, ConnHandler),
 
387
                  receive
 
388
                      {'DOWN', Mon, process, ConnHandler, Reason} ->
 
389
                          receive after 1000 -> ok end,
 
390
                          halt("test server connection handler terminated: "
 
391
                               ++
 
392
                               lists:flatten(io_lib:format("~p", [Reason])))
 
393
                  end
 
394
          end).
 
395
 
 
396
notify_ssl_node_up(Socket) ->
 
397
    case catch gen_tcp:send(Socket,
 
398
                            term_to_binary({ssl_node_up, node()})) of
 
399
        ok -> ok;
 
400
        _ -> halt("Failed to notify test server that I'm up")
 
401
    end.
 
402
 
 
403
send_to_tstsrvr(Term) ->
 
404
    case catch ets:lookup_element(test_server_info, test_server_handler, 2) of
 
405
        Hndlr when pid(Hndlr) ->
 
406
            Hndlr ! {relay_to_test_server, term_to_binary(Term)}, ok;
 
407
        _ ->
 
408
            receive after 200 -> ok end,
 
409
            send_to_tstsrvr(Term)
 
410
    end.
 
411
 
 
412
ssl_node_con_loop(Socket) ->
 
413
    inet:setopts(Socket,[{active,once}]),
 
414
    receive
 
415
        {relay_to_test_server, Data} when is_binary(Data) ->
 
416
            case gen_tcp:send(Socket, Data) of
 
417
                ok ->
 
418
                    ok;
 
419
                _Error ->
 
420
                    gen_tcp:close(Socket),
 
421
                    halt("Failed to relay data to test server")
 
422
            end;
 
423
        {tcp, Socket, Bin} ->
 
424
            case catch binary_to_term(Bin) of
 
425
                {'EXIT', _} ->
 
426
                    gen_tcp:close(Socket),
 
427
                    halt("test server sent me bad data");
 
428
                {apply, From, Ref, M, F, A} ->
 
429
                    spawn_link(
 
430
                      fun () ->
 
431
                              send_to_tstsrvr({apply_res,
 
432
                                               From,
 
433
                                               Ref,
 
434
                                               (catch apply(M, F, A))})
 
435
                          end);
 
436
                {apply, From, Ref, Fun} ->
 
437
                    spawn_link(fun () ->
 
438
                                       send_to_tstsrvr({apply_res,
 
439
                                                        From,
 
440
                                                        Ref,
 
441
                                                        (catch Fun())})
 
442
                               end);
 
443
                stop ->
 
444
                    gen_tcp:send(Socket, term_to_binary(bye)),
 
445
                    gen_tcp:close(Socket),
 
446
                    init:stop(),
 
447
                    receive after infinity -> ok end;
 
448
                _Unknown ->
 
449
                    halt("test server sent me an unexpected message")
 
450
            end;
 
451
        {tcp_closed, Socket} ->
 
452
            halt("Lost connection to test server")
 
453
    end,
 
454
    ssl_node_con_loop(Socket).
 
455
 
 
456
%%
 
457
%% Setup ssl dist info
 
458
%%
 
459
 
 
460
rand_bin(N) ->
 
461
    rand_bin(N, []).
 
462
 
 
463
rand_bin(0, Acc) ->
 
464
    Acc;
 
465
rand_bin(N, Acc) ->
 
466
    rand_bin(N-1, [random:uniform(256)-1|Acc]).
 
467
 
 
468
make_randfile(Dir) ->
 
469
    {ok, IoDev} = file:open(filename:join([Dir, "RAND"]), [write]),
 
470
    {A, B, C} = erlang:now(),
 
471
    random:seed(A, B, C),
 
472
    ok = file:write(IoDev, rand_bin(1024)),
 
473
    file:close(IoDev).
 
474
 
 
475
append_files(FileNames, ResultFileName) ->
 
476
    {ok, ResultFile} = file:open(ResultFileName, [write]),
 
477
    do_append_files(FileNames, ResultFile).
 
478
 
 
479
do_append_files([], RF) ->
 
480
    ok = file:close(RF);
 
481
do_append_files([F|Fs], RF) ->
 
482
    {ok, Data} = file:read_file(F),
 
483
    ok = file:write(RF, Data),
 
484
    do_append_files(Fs, RF).
 
485
                            
 
486
setup_dist_opts(Name, PrivDir) ->
 
487
    NodeDir = filename:join([PrivDir, Name]),
 
488
    RGenDir = filename:join([NodeDir, "rand_gen"]),
 
489
    ok = file:make_dir(NodeDir),
 
490
    ok = file:make_dir(RGenDir),
 
491
    make_randfile(RGenDir),
 
492
    make_certs:all(RGenDir, NodeDir),
 
493
    SDir = filename:join([NodeDir, "server"]),
 
494
    SC = filename:join([SDir, "cert.pem"]),
 
495
    SK = filename:join([SDir, "key.pem"]),
 
496
    SKC = filename:join([SDir, "keycert.pem"]),
 
497
    append_files([SK, SC], SKC),
 
498
    CDir = filename:join([NodeDir, "client"]),
 
499
    CC = filename:join([CDir, "cert.pem"]),
 
500
    CK = filename:join([CDir, "key.pem"]),
 
501
    CKC = filename:join([CDir, "keycert.pem"]),
 
502
    append_files([CK, CC], CKC),
 
503
    "-proto_dist inet_ssl "
 
504
        ++ "-ssl_dist_opt server_certfile " ++ SKC ++ " "
 
505
        ++ "-ssl_dist_opt client_certfile " ++ CKC ++ " "
 
506
.%      ++ "-ssl_dist_opt verify 1 depth 1".
 
507
 
 
508
%%
 
509
%% Start scripts etc...
 
510
%%
 
511
 
 
512
add_ssl_opts_config(Config) ->
 
513
    %%
 
514
    %% Start with boot scripts if on an installed system; otherwise,
 
515
    %% just point out ssl ebin with -pa.
 
516
    %%
 
517
    try
 
518
        Dir = ?config(priv_dir, Config),
 
519
        LibDir = code:lib_dir(),
 
520
        Apps = application:which_applications(),
 
521
        {value, {stdlib, _, STDL_VSN}} = lists:keysearch(stdlib, 1, Apps),
 
522
        {value, {kernel, _, KRNL_VSN}} = lists:keysearch(kernel, 1, Apps),
 
523
        StdlDir = filename:join([LibDir, "stdlib-" ++ STDL_VSN]),
 
524
        KrnlDir = filename:join([LibDir, "kernel-" ++ KRNL_VSN]),
 
525
        {ok, _} = file:read_file_info(StdlDir),
 
526
        {ok, _} = file:read_file_info(KrnlDir),
 
527
        SSL_VSN = case lists:keysearch(ssl, 1, Apps) of
 
528
                      {value, {ssl, _, VSN}} ->
 
529
                          VSN;
 
530
                      _ ->
 
531
                          application:start(ssl),
 
532
                          try
 
533
                              {value,
 
534
                               {ssl,
 
535
                                _,
 
536
                                VSN}} = lists:keysearch(ssl,
 
537
                                                        1,
 
538
                                                        application:which_applications()),
 
539
                              VSN
 
540
                          after
 
541
                              application:stop(ssl)
 
542
                          end
 
543
                  end,
 
544
        SslDir = filename:join([LibDir, "ssl-" ++ SSL_VSN]),
 
545
        {ok, _} = file:read_file_info(SslDir),
 
546
        %% We are using an installed otp system, create the boot script.
 
547
        Script = filename:join(Dir, atom_to_list(?MODULE)),
 
548
        {ok, RelFile} = file:open(Script ++ ".rel", [write]),
 
549
        io:format(RelFile,
 
550
                  "{release, ~n"
 
551
                  " {\"SSL distribution test release\", \"~s\"},~n"
 
552
                  " {erts, \"~s\"},~n"
 
553
                  " [{kernel, \"~s\"},~n"
 
554
                  "  {stdlib, \"~s\"},~n"
 
555
                  "  {ssl, \"~s\"}]}.~n",
 
556
                  [case catch erlang:system_info(otp_release) of
 
557
                       {'EXIT', _} -> "R11B";
 
558
                       Rel -> Rel
 
559
                   end,
 
560
                   erlang:system_info(version),
 
561
                   KRNL_VSN,
 
562
                   STDL_VSN,
 
563
                   SSL_VSN]),
 
564
        ok = file:close(RelFile),
 
565
        ok = systools:make_script(Script, []),
 
566
        [{ssl_opts, "-boot " ++ Script} | Config]
 
567
    catch
 
568
        _:_ ->
 
569
            [{ssl_opts, "-pa " ++ filename:dirname(code:which(ssl))}
 
570
             | add_comment_config(
 
571
                 "Bootscript wasn't used since the test wasn't run on an "
 
572
                 "installed OTP system.",
 
573
                 Config)]
 
574
    end.
 
575
 
 
576
%%
 
577
%% Add common comments to config
 
578
%%
 
579
 
 
580
add_comment_config(Comment, []) ->
 
581
    [{comment, Comment}];
 
582
add_comment_config(Comment, [{comment, OldComment} | Cs]) ->
 
583
    [{comment, Comment ++ " " ++ OldComment} | Cs];
 
584
add_comment_config(Comment, [C|Cs]) ->
 
585
    [C|add_comment_config(Comment, Cs)].
 
586
 
 
587
%%
 
588
%% Call when test case success
 
589
%%
 
590
 
 
591
success(Config) ->
 
592
    case lists:keysearch(comment, 1, Config) of
 
593
        {value, {comment, _} = Res} -> Res;
 
594
        _ -> ok
 
595
    end.