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

« back to all changes in this revision

Viewing changes to lib/test_server/src/ts_run.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2011. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
28
28
 
29
29
-include("ts.hrl").
30
30
 
31
 
-import(lists, [map/2,member/2,filter/2,reverse/1]).
 
31
-import(lists, [member/2,filter/2]).
32
32
 
33
33
-record(state,
34
34
        {file,                                  % File given.
63
63
            _ ->
64
64
                {false, fun run_interactive/3}
65
65
        end,
66
 
    HandleTopcase = case member(keep_topcase, Options) of
67
 
                        true -> [fun copy_topcase/3];
68
 
                        false -> [fun remove_original_topcase/3,
69
 
                                  fun init_topcase/3]
70
 
                    end,
71
 
    MakefileHooks = [fun make_make/3,
72
 
                     fun add_make_testcase/3],
73
 
    MakeLoop = fun(V, Sp, St) -> make_loop(MakefileHooks, V, Sp, St) end,
74
66
    Hooks = [fun init_state/3,
75
 
             fun read_spec_file/3] ++
76
 
             HandleTopcase ++
77
 
             [fun run_preinits/3,
78
 
             fun find_makefiles/3,
79
 
             MakeLoop,
80
 
             fun make_test_suite/3,
81
 
             fun add_topcase_to_spec/3,
82
 
             fun write_spec_file/3,
 
67
             fun run_preinits/3,
83
68
             fun make_command/3,
84
69
             Runner],
85
 
    Args = make_test_server_args(Args0,Options,Vars),
 
70
    Args = make_common_test_args(Args0,Options,Vars),
86
71
    St = #state{file=File,test_server_args=Args,batch=Batch},
87
72
    R = execute(Hooks, Vars, [], St),
88
 
    case Batch of
89
 
        true -> ts_reports:make_index();
90
 
        false -> ok % ts_reports:make_index() is run on the test_server node
91
 
    end,
92
73
    case R of
93
74
        {ok,_,_,_} -> ok;
94
75
        Error -> Error
95
76
    end.
96
77
 
97
 
make_loop(Hooks, Vars0, Spec0, St0) ->
98
 
    case St0#state.makefiles of
99
 
        [Makefile|Rest] ->
100
 
            case execute(Hooks, Vars0, Spec0, St0#state{makefile=Makefile}) of
101
 
                {error, Reason} ->
102
 
                    {error, Reason};
103
 
                {ok, Vars, Spec, St} ->
104
 
                    make_loop(Hooks, Vars, Spec, St#state{makefiles=Rest})
105
 
            end;
106
 
        [] ->
107
 
            {ok, Vars0, Spec0, St0}
108
 
    end.
109
 
 
110
78
execute([Hook|Rest], Vars0, Spec0, St0) ->
111
79
    case Hook(Vars0, Spec0, St0) of
112
80
        ok ->
156
124
        false ->
157
125
            {error,{no_test_directory,TestDir}}
158
126
    end.
159
 
    
160
 
%% Read the spec file for the test suite.
161
 
 
162
 
read_spec_file(Vars, _, St) ->
163
 
    TestDir = St#state.test_dir,
164
 
    File = St#state.file,
165
 
    {SpecFile,Res} = get_spec_filename(Vars, TestDir, File),
166
 
    case Res of
167
 
        {ok,Spec} ->
168
 
            {ok,Vars,Spec,St};
169
 
        {error,Atom} when is_atom(Atom) ->
170
 
            {error,{no_spec,SpecFile}};
171
 
        {error,Reason} ->
172
 
            {error,{bad_spec,lists:flatten(file:format_error(Reason))}}
173
 
    end.
174
 
 
175
 
get_spec_filename(Vars, TestDir, File) ->
176
 
    DynSpec = filename:join(TestDir, File ++ ".dynspec"),
177
 
    case filelib:is_file(DynSpec) of
178
 
        true ->
179
 
            Bs0 = erl_eval:new_bindings(),
180
 
            Bs1 = erl_eval:add_binding('Target', ts_lib:var(target, Vars), Bs0),
181
 
            Bs2 = erl_eval:add_binding('Os', ts_lib:var(os, Vars), Bs1),
182
 
            TCCStr = ts_lib:var(test_c_compiler, Vars),
183
 
            TCC = try
184
 
                      {ok, Toks, _} = erl_scan:string(TCCStr ++ "."),
185
 
                      {ok, Tcc} = erl_parse:parse_term(Toks),
186
 
                      Tcc
187
 
                  catch
188
 
                      _:_ -> undefined
189
 
                  end,
190
 
            Bs = erl_eval:add_binding('TestCCompiler', TCC, Bs2),
191
 
            {DynSpec,file:script(DynSpec, Bs)};
192
 
        false ->
193
 
            SpecFile = get_spec_filename_1(Vars, TestDir, File),
194
 
            {SpecFile,file:consult(SpecFile)}
195
 
    end.
196
 
 
197
 
get_spec_filename_1(Vars, TestDir, File) ->
198
 
    case ts_lib:var(os, Vars) of
199
 
        "VxWorks" ->
200
 
            check_spec_filename(TestDir, File, ".spec.vxworks");
201
 
        "OSE" ->
202
 
            check_spec_filename(TestDir, File, ".spec.ose");
203
 
        "Windows"++_ ->
204
 
            check_spec_filename(TestDir, File, ".spec.win");
205
 
        _Other ->
206
 
            filename:join(TestDir, File ++ ".spec")
207
 
    end.
208
 
 
209
 
check_spec_filename(TestDir, File, Ext) ->
210
 
    Spec = filename:join(TestDir, File ++ Ext),
211
 
    case filelib:is_file(Spec) of
212
 
        true -> Spec;
213
 
        false -> filename:join(TestDir, File ++ ".spec")
214
 
    end.
215
 
 
216
 
%% Remove the top case from the spec file. We will add our own
217
 
%% top case later.
218
 
 
219
 
remove_original_topcase(Vars, Spec, St) ->
220
 
    {ok,Vars,filter(fun ({topcase,_}) -> false;
221
 
                        (_Other) -> true end, Spec),St}.
222
 
 
223
 
%% Initialize our new top case. We'll keep in it the state to be
224
 
%%  able to add more to it.
225
 
 
226
 
init_topcase(Vars, Spec, St) ->
227
 
    TestDir = St#state.test_dir,
228
 
    TopCase = 
229
 
        case St#state.mod of
230
 
            Mod when is_atom(Mod) ->
231
 
                ModStr = atom_to_list(Mod),
232
 
                case filelib:is_file(filename:join(TestDir,ModStr++".erl")) of
233
 
                    true -> [{Mod,all}];
234
 
                    false ->
235
 
                        Wc = filename:join(TestDir, ModStr ++ "*_SUITE.erl"),
236
 
                        [{list_to_atom(filename:basename(M, ".erl")),all} ||
237
 
                            M <- filelib:wildcard(Wc)]
238
 
                end;
239
 
            _Other ->
240
 
                %% Here we used to return {dir,TestDir}. Now we instead
241
 
                %% list all suites in TestDir, so we can add make testcases
242
 
                %% around it later (see add_make_testcase) without getting
243
 
                %% duplicates of the suite. (test_server_ctrl does no longer
244
 
                %% check for duplicates of testcases)
245
 
                Wc = filename:join(TestDir, "*_SUITE.erl"),
246
 
                [{list_to_atom(filename:basename(M, ".erl")),all} ||
247
 
                    M <- filelib:wildcard(Wc)]
248
 
        end,
249
 
    {ok,Vars,Spec,St#state{topcase=TopCase}}.
250
 
 
251
 
%% Or if option keep_topcase was given, eh... keep the topcase
252
 
copy_topcase(Vars, Spec, St) ->
253
 
    {value,{topcase,Tc}} = lists:keysearch(topcase,1,Spec),
254
 
    {ok, Vars, lists:keydelete(topcase,1,Spec),St#state{topcase=Tc}}.
255
 
 
256
127
 
257
128
%% Run any "Makefile.first" files first.
258
129
%%  XXX We should fake a failing test case if the make fails.
281
152
        {error,_Reason}=Error -> Error
282
153
    end.
283
154
 
284
 
%% Search for `Makefile.src' in each *_SUITE_data directory.
285
 
 
286
 
find_makefiles(Vars, Spec, St) ->
287
 
    Wc = filename:join(St#state.data_wc, "Makefile.src"),
288
 
    Makefiles = reverse(del_skipped_suite_data_dir(filelib:wildcard(Wc), Spec)),
289
 
    {ok,Vars,Spec,St#state{makefiles=Makefiles}}.
290
 
    
291
 
%% Create "Makefile" from "Makefile.src".
292
 
 
293
 
make_make(Vars, Spec, State) ->
294
 
    Src = State#state.makefile,
295
 
    Dest = filename:rootname(Src),
296
 
    ts_lib:progress(Vars, 1, "Making ~s...\n", [Dest]),
297
 
    case ts_lib:subst_file(Src, Dest, Vars) of
298
 
        ok ->
299
 
            {ok, Vars, Spec, State#state{makefile=Dest}};
300
 
        {error, Reason} ->
301
 
            {error, {Src, Reason}}
302
 
    end.
303
 
 
304
 
%% Add a testcase which will do the making of the stuff in the data directory.
305
 
 
306
 
add_make_testcase(Vars, Spec, St) ->
307
 
    Makefile = St#state.makefile,
308
 
    Dir = filename:dirname(Makefile),
309
 
    case ts_lib:var(os, Vars) of
310
 
        "OSE" ->
311
 
            %% For OSE, C code in datadir must be linked in the image file,
312
 
            %% and erlang code is sent as binaries from test_server_ctrl
313
 
            %% Making erlang code here because the Makefile.src probably won't
314
 
            %% work.
315
 
            Erl_flags=[{i, "../../test_server"}|ts_lib:var(erl_flags,Vars)],
316
 
            {ok, Cwd} = file:get_cwd(),
317
 
            ok = file:set_cwd(Dir),
318
 
            Result = (catch make:all(Erl_flags)),
319
 
            ok = file:set_cwd(Cwd),
320
 
            case Result of
321
 
                up_to_date -> {ok, Vars, Spec, St};
322
 
                _error -> {error, {erlang_make_failed,Dir}}
323
 
            end;
324
 
        _ ->
325
 
            Shortname = filename:basename(Makefile),
326
 
            Suite = filename:basename(Dir, "_data"),
327
 
            Config = [{data_dir,Dir},{makefile,Shortname}],
328
 
            MakeModule = Suite ++ "_make",
329
 
            MakeModuleSrc = filename:join(filename:dirname(Dir), 
330
 
                                          MakeModule ++ ".erl"),
331
 
            MakeMod = list_to_atom(MakeModule),
332
 
            case filelib:is_file(MakeModuleSrc) of
333
 
                true -> ok;
334
 
                false -> generate_make_module(ts_lib:var(make_command, Vars),
335
 
                                              MakeModuleSrc, 
336
 
                                              MakeModule)
337
 
            end,
338
 
            case Suite of
339
 
                "all_SUITE" ->
340
 
                    {ok,Vars,Spec,St#state{all={MakeMod,Config}}};
341
 
                _ ->
342
 
                    %% Avoid duplicates of testcases. There is no longer
343
 
                    %% a check for this in test_server_ctrl.
344
 
                    TestCase = {list_to_atom(Suite),all},
345
 
                    TopCase0 = case St#state.topcase of
346
 
                                   List when is_list(List) ->
347
 
                                       List -- [TestCase];
348
 
                                   Top ->
349
 
                                       [Top] -- [TestCase]
350
 
                               end,
351
 
                    TopCase = [{make,{MakeMod,make,[Config]},
352
 
                                TestCase,
353
 
                                {MakeMod,unmake,[Config]}}|TopCase0],
354
 
                    {ok,Vars,Spec,St#state{topcase=TopCase}}
355
 
            end
356
 
    end.
357
 
 
358
 
generate_make_module(MakeCmd, Name, ModuleString) ->
359
 
    {ok,Host} = inet:gethostname(),
360
 
    file:write_file(Name,
361
 
                    ["-module(",ModuleString,").\n",
362
 
                     "\n",
363
 
                     "-export([make/1,unmake/1]).\n",
364
 
                     "\n",
365
 
                     "make(Config) when is_list(Config) ->\n",
366
 
                     "    Mins = " ++ integer_to_list(?DEFAULT_MAKE_TIMETRAP_MINUTES) ++ ",\n"
367
 
                     "    test_server:format(\"=== Setting timetrap to ~p minutes ===~n\", [Mins]),\n"
368
 
                     "    TimeTrap = test_server:timetrap(test_server:minutes(Mins)),\n"
369
 
                     "    Res = ts_make:make([{make_command, \""++MakeCmd++"\"},{cross_node,\'ts@" ++ Host ++ "\'}|Config]),\n",
370
 
                     "    test_server:timetrap_cancel(TimeTrap),\n"
371
 
                     "    Res.\n"
372
 
                     "\n",
373
 
                     "unmake(Config) when is_list(Config) ->\n",
374
 
                     "    Mins = " ++ integer_to_list(?DEFAULT_UNMAKE_TIMETRAP_MINUTES) ++ ",\n"
375
 
                     "    test_server:format(\"=== Setting timetrap to ~p minutes ===~n\", [Mins]),\n"
376
 
                     "    TimeTrap = test_server:timetrap(test_server:minutes(Mins)),\n"
377
 
                     "    Res = ts_make:unmake([{make_command, \""++MakeCmd++"\"}|Config]),\n"
378
 
                     "    test_server:timetrap_cancel(TimeTrap),\n"
379
 
                     "    Res.\n"
380
 
                     "\n"]).
381
 
                           
382
 
 
383
 
make_test_suite(Vars, _Spec, State) ->
384
 
    TestDir = State#state.test_dir,
385
 
 
386
 
    Erl_flags=[{i, "../test_server"}|ts_lib:var(erl_flags,Vars)],
387
 
 
388
 
    case code:is_loaded(test_server_line) of
389
 
        false -> code:load_file(test_server_line);
390
 
        _ -> ok
391
 
    end,
392
 
 
393
 
    {ok, Cwd} = file:get_cwd(),
394
 
    ok = file:set_cwd(TestDir),
395
 
    Result = (catch make:all(Erl_flags)),
396
 
    ok = file:set_cwd(Cwd),
397
 
    case Result of
398
 
        up_to_date ->
399
 
            ok;
400
 
        {'EXIT', Reason} ->
401
 
            %% If I return an error here, the test will be stopped
402
 
            %% and it will not show up in the top index page. Instead
403
 
            %% I return ok - the test will run for all existing suites.
404
 
            %% It might be that there are old suites that are run, but
405
 
            %% at least one suite is missing, and that is reported on the
406
 
            %% top index page.
407
 
            io:format("~s: {error,{make_crashed,~p}\n",
408
 
                      [State#state.file,Reason]),
409
 
            ok;
410
 
        error ->
411
 
            %% See comment above
412
 
            io:format("~s: {error,make_of_test_suite_failed}\n",
413
 
                      [State#state.file]),
414
 
            ok
415
 
    end.
416
 
 
417
 
%% Add topcase to spec.
418
 
 
419
 
add_topcase_to_spec(Vars, Spec, St) ->
420
 
    Tc = case St#state.all of
421
 
             {MakeMod,Config} ->
422
 
                 [{make,{MakeMod,make,[Config]},
423
 
                   St#state.topcase,
424
 
                   {MakeMod,unmake,[Config]}}];
425
 
             undefined -> St#state.topcase
426
 
         end,
427
 
    {ok,Vars,Spec++[{topcase,Tc}],St}.
428
 
 
429
 
%% Writes the (possibly transformed) spec file.
430
 
 
431
 
write_spec_file(Vars, Spec, _State) ->
432
 
    F = fun(Term) -> io_lib:format("~p.~n", [Term]) end,
433
 
    SpecFile = map(F, Spec),
434
 
    Hosts = 
435
 
        case lists:keysearch(hosts, 1, Vars) of
436
 
            false ->
437
 
                [];
438
 
            {value, {hosts, HostList}} ->
439
 
                io_lib:format("{hosts,~p}.~n",[HostList])
440
 
        end,
441
 
    DiskLess =
442
 
        case lists:keysearch(diskless, 1, Vars) of
443
 
            false ->
444
 
                [];
445
 
            {value, {diskless, How}} ->
446
 
                io_lib:format("{diskless, ~p}.~n",[How])
447
 
        end,
448
 
    Conf = consult_config(),
449
 
    MoreConfig = io_lib:format("~p.\n", [{config,Conf}]),
450
 
    file:write_file("current.spec", [DiskLess,Hosts,MoreConfig,SpecFile]).
451
 
 
452
 
consult_config() ->
453
 
    {ok,Conf} = file:consult("ts.config"),
454
 
    case os:type() of
455
 
        {unix,_} -> consult_config("ts.unix.config", Conf);
456
 
        {win32,_} -> consult_config("ts.win32.config", Conf);
457
 
        vxworks -> consult_config("ts.vxworks.config", Conf);
458
 
        _ -> Conf
459
 
    end.
460
 
 
461
 
consult_config(File, Conf0) ->
462
 
    case file:consult(File) of
463
 
        {ok,Conf} -> Conf++Conf0;
464
 
        {error,enoent} -> Conf0
465
 
    end.
 
155
get_config_files() ->
 
156
    TSConfig = "ts.config",
 
157
    [TSConfig | case os:type() of
 
158
                    {unix,_} -> ["ts.unix.config"];
 
159
                    {win32,_} -> ["ts.win32.config"];
 
160
                    vxworks -> ["ts.vxworks.config"];
 
161
                    _ -> []
 
162
                end].
466
163
 
467
164
%% Makes the command to start up the Erlang node to run the tests.
468
165
 
476
173
    [].
477
174
 
478
175
make_command(Vars, Spec, State) ->
 
176
    {ok,Cwd} = file:get_cwd(),
479
177
    TestDir = State#state.test_dir,
480
178
    TestPath = filename:nativename(TestDir),
481
179
    Erl = case os:getenv("TS_RUN_VALGRIND") of
506
204
            {value,{erl_start_args,Args}} -> Args;
507
205
            false -> ""
508
206
        end,
509
 
    CrashFile = State#state.file ++ "_erl_crash.dump",
 
207
    CrashFile = filename:join(Cwd,State#state.file ++ "_erl_crash.dump"),
510
208
    case filelib:is_file(CrashFile) of
511
209
        true -> 
512
210
            io:format("ts_run: Deleting dump: ~s\n",[CrashFile]),
514
212
        false -> 
515
213
            ok
516
214
    end,
517
 
    Cmd = [Erl, Naming, "test_server -pa ", $", TestPath, $",
 
215
    %% NOTE: Do not use ' in these commands as it wont work on windows
 
216
    Cmd = [Erl, Naming, "test_server"
518
217
           " -rsh ", ts_lib:var(rsh_name, Vars),
519
218
           " -env PATH \"",
520
219
           backslashify(lists:flatten([TestPath, path_separator(),
524
223
           %% uncomment the line below to disable exception formatting 
525
224
           %%      " -test_server_format_exception false",
526
225
           " -boot start_sasl -sasl errlog_type error",
527
 
           " -s test_server_ctrl run_test ", State#state.test_server_args,
 
226
           " -pz ",Cwd,
 
227
           " -eval \"file:set_cwd(\\\"",TestDir,"\\\")\" "
 
228
           " -eval \"ct:run_test(", 
 
229
           backslashify(lists:flatten(State#state.test_server_args)),")\""
528
230
           " ",
529
231
           ExtraArgs],
530
232
    {ok, Vars, Spec, State#state{command=lists:flatten(Cmd)}}.
 
233
    
531
234
 
532
235
run_batch(Vars, _Spec, State) ->
533
236
    process_flag(trap_exit, true),
534
237
    Command = State#state.command ++ " -noinput -s erlang halt",
535
238
    ts_lib:progress(Vars, 1, "Command: ~s~n", [Command]),
 
239
    io:format(user, "Command: ~s~n",[Command]),
536
240
    Port = open_port({spawn, Command}, [stream, in, eof]),
537
241
    tricky_print_data(Port).
538
242
 
573
277
is_testnode_dead([_|T]) -> is_testnode_dead(T).
574
278
 
575
279
run_interactive(Vars, _Spec, State) ->
576
 
    Command = State#state.command ++ " -s ts_reports make_index",
 
280
    Command = State#state.command,
577
281
    ts_lib:progress(Vars, 1, "Command: ~s~n", [Command]),
578
282
    case ts_lib:var(os, Vars) of
579
283
        "Windows 95" ->
623
327
    end.
624
328
 
625
329
 
626
 
make_test_server_args(Args0,Options,Vars) ->
627
 
    Parameters = 
628
 
        case ts_lib:var(os, Vars) of
629
 
            "VxWorks" ->
630
 
                F = write_parameterfile(vxworks,Vars),
631
 
                " PARAMETERS " ++ F;
632
 
            "OSE" ->
633
 
                F = write_parameterfile(ose,Vars),
634
 
                " PARAMETERS " ++ F;
635
 
            _ ->
636
 
                ""
637
 
        end,
 
330
make_common_test_args(Args0, Options, _Vars) ->
638
331
    Trace = 
639
332
        case lists:keysearch(trace,1,Options) of
640
333
            {value,{trace,TI}} when is_tuple(TI); is_tuple(hd(TI)) ->
641
334
                ok = file:write_file(?tracefile,io_lib:format("~p.~n",[TI])),
642
 
                " TRACE " ++ ?tracefile;
 
335
                [{ct_trace,?tracefile}];
643
336
            {value,{trace,TIFile}} when is_atom(TIFile) ->
644
 
                " TRACE " ++ atom_to_list(TIFile);
 
337
                [{ct_trace,atom_to_list(TIFile)}];
645
338
            {value,{trace,TIFile}} ->
646
 
                " TRACE " ++ TIFile;
 
339
                [{ct_trace,TIFile}];
647
340
            false ->
648
 
                ""
 
341
                []
649
342
        end,
650
343
    Cover = 
651
344
        case lists:keysearch(cover,1,Options) of
652
 
            {value,{cover,App,File,Analyse}} -> 
653
 
                " COVER " ++ to_list(App) ++ " " ++ to_list(File) ++ " " ++ 
654
 
                    to_list(Analyse);
 
345
            {value,{cover, App, none, _Analyse}} ->
 
346
                io:format("No cover file found for ~p~n",[App]),
 
347
                [];
 
348
            {value,{cover,_App,File,_Analyse}} -> 
 
349
                [{cover,to_list(File)}];
655
350
            false -> 
656
 
                ""
657
 
        end,
658
 
    TCCallback =
659
 
        case ts_lib:var(ts_testcase_callback, Vars) of
660
 
            "" -> 
661
 
                "";
662
 
            {Mod,Func} ->
663
 
                io:format("Function ~w:~w/4 will be called before and "
664
 
                          "after each test case.\n", [Mod,Func]),
665
 
                " TESTCASE_CALLBACK " ++ to_list(Mod) ++ " " ++ to_list(Func);      
666
 
            ModFunc when is_list(ModFunc) ->
667
 
                [Mod,Func]=string:tokens(ModFunc," "),
668
 
                io:format("Function ~s:~s/4 will be called before and "
669
 
                          "after each test case.\n", [Mod,Func]),                       
670
 
                " TESTCASE_CALLBACK " ++ ModFunc;                   
671
 
            _ ->
672
 
                ""
673
 
        end,
674
 
    Args0 ++ Parameters ++ Trace ++ Cover ++ TCCallback.
 
351
                []
 
352
        end,
 
353
 
 
354
    Logdir = case lists:keysearch(logdir, 1, Options) of
 
355
                  {value,{logdir, _}} ->
 
356
                      [];
 
357
                  false ->
 
358
                      [{logdir,"../test_server"}]
 
359
             end,
 
360
 
 
361
    ConfigPath = case {os:getenv("TEST_CONFIG_PATH"),
 
362
                       lists:keysearch(config, 1, Options)} of
 
363
                     {false,{value, {config, Path}}} ->
 
364
                         Path;
 
365
                     {false,false} ->
 
366
                         "../test_server";
 
367
                     {Path,_} ->
 
368
                         Path
 
369
                 end,
 
370
    ConfigFiles = [{config,[filename:join(ConfigPath,File)
 
371
                            || File <- get_config_files()]}],
 
372
 
 
373
    io_lib:format("~100000p",[Args0++Trace++Cover++Logdir++
 
374
                                  ConfigFiles++Options]).
675
375
 
676
376
to_list(X) when is_atom(X) ->
677
377
    atom_to_list(X);
678
378
to_list(X) when is_list(X) ->
679
379
    X.
680
380
 
681
 
write_parameterfile(Type,Vars) ->
682
 
    Cross_host = ts_lib:var(target_host, Vars),
683
 
    SlaveTargets = case lists:keysearch(slavetargets,1,Vars) of
684
 
                       {value, ST} ->
685
 
                           [ST];
686
 
                       _ ->
687
 
                           []
688
 
                   end,
689
 
    Master = case lists:keysearch(master,1,Vars) of
690
 
                 {value,M} -> [M];
691
 
                 false -> []
692
 
             end,
693
 
    ToWrite = [{type,Type},
694
 
               {target, list_to_atom(Cross_host)}] ++ SlaveTargets ++ Master,
695
 
 
696
 
    Crossfile = atom_to_list(Type) ++ "parameters" ++ os:getpid(),
697
 
    ok = file:write_file(Crossfile,io_lib:format("~p.~n", [ToWrite])),
698
 
    Crossfile.
699
 
 
700
381
%%
701
382
%% Paths and spaces handling for w2k and XP
702
383
%%
742
423
 
743
424
split_path(Path) ->
744
425
    string:tokens(Path,";").
745
 
 
746