1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%%-------------------------------------------------------------------
22%%% File    : ts.erl
23%%% Purpose : Frontend for running tests.
24%%%-------------------------------------------------------------------
25
26-module(ts).
27
28-export([cl_run/1,
29	 run/0, run/1, run/2, run/3, run/4, run/5,
30	 run_category/1, run_category/2, run_category/3,
31	 tests/0, tests/1, suites/1, categories/1,
32	 install/0, install/1,
33	 estone/0, estone/1,
34	 cross_cover_analyse/1,
35	 compile_testcases/0, compile_testcases/1,
36	 help/0]).
37
38%% Functions kept for backwards compatibility
39-export([bench/0, bench/1, bench/2, benchmarks/0,
40	 smoke_test/0, smoke_test/1,smoke_test/2, smoke_tests/0]).
41
42-export([i/0, l/1, r/0, r/1, r/2, r/3]).
43
44%%%----------------------------------------------------------------------
45%%% This module, ts, is the interface to all of the functionality of
46%%% the TS framework.  The picture below shows the relationship of
47%%% the modules:
48%%%
49%%%       +-- ts_install --+------  ts_autoconf_win32
50%%%       |
51%%% ts ---+                +------  ts_erl_config
52%%%       |                |				     ts_lib
53%%%       +-- ts_run  -----+------  ts_make
54%%%       |                |	    			     ts_filelib
55%%%       |                +------  ts_make_erl
56%%%       |
57%%%       +-- ts_benchmark
58%%%
59%%% The modules ts_lib and ts_filelib contains utilities used by
60%%% the other modules.
61%%%
62%%% Module		 Description
63%%% ------		 -----------
64%%% ts			 Frontend to the test server framework.  Contains all
65%%%			 interface functions.
66%%% ts_install		 Installs the test suite.  On Unix, `autoconf' is
67%%%			 is used; on Windows, ts_autoconf_win32 is used.
68%%%			 The result is written to the file `variables'.
69%%% ts_run		 Supervises running of the tests.
70%%% ts_autconf_win32	 An `autoconf' for Windows.
71%%% ts_autconf_cross_env `autoconf' for other platforms (cross environment)
72%%% ts_erl_config	 Finds out information about the Erlang system,
73%%%			 for instance the location of erl_interface.
74%%%			 This works for either an installed OTP or an Erlang
75%%%			 system running in a git repository/source tree.
76%%% ts_make		 Interface to run the `make' program on Unix
77%%%			 and other platforms.
78%%% ts_make_erl		 A corrected version of the standar Erlang module
79%%%			 make (used for rebuilding test suites).
80%%% ts_lib		 Miscellanous utility functions, each used by several
81%%%			 other modules.
82%%% ts_benchmark         Supervises otp benchmarks and collects results.
83%%%----------------------------------------------------------------------
84
85-include_lib("kernel/include/file.hrl").
86-include("ts.hrl").
87
88-define(
89   install_help,
90   [
91    "  ts:install()\n",
92    "    Install ts with no options.\n",
93    "\n",
94    "  ts:install(Options)\n",
95    "    Install ts with a list of options, see below.\n",
96    "\n",
97    "Installation options supported:\n\n",
98    "  {longnames, true} - Use fully qualified hostnames\n",
99    "  {verbose, Level}  - Sets verbosity level for TS output (0,1,2), 0 is\n"
100    "                      quiet(default).\n"
101    "  {crossroot, ErlTop}\n"
102    "                    - Erlang root directory on build host, ~n"
103    "                      normally same value as $ERL_TOP\n"
104    "  {crossenv, [{Key,Val}]}\n"
105    "                    - Environmentals used by test configure on build host\n"
106    "  {crossflags, FlagsString}\n"
107    "                    - Flags used by test configure on build host\n"
108    "  {xcomp, XCompFile}\n"
109    "                    - The xcomp file to use for cross compiling the~n"
110    "                      testcases. Using this option will override any~n"
111    "                      cross* configurations given to ts. Note that you~n"
112    "                      have to have a correct ERL_TOP as well.~n"
113   ]).
114
115help() ->
116    case filelib:is_file(?variables) of
117	false -> help(uninstalled);
118	true  -> help(installed)
119    end.
120
121help(uninstalled) ->
122    H = ["ts is not yet installed. To install use:\n\n"],
123    show_help([H,?install_help]);
124help(installed) ->
125    H = ["\n",
126	 "Run functions:\n\n",
127	 "  ts:run()\n",
128	 "    Run the tests for all apps. The tests are defined by the\n",
129	 "    main test specification for each app: ../App_test/App.spec.\n",
130	 "\n",
131	 "  ts:run(Apps)\n",
132	 "    Apps = atom() | [atom()]\n",
133	 "    Run the tests for an app, or set of apps. The tests are\n",
134	 "    defined by the main test specification for each app:\n",
135	 "    ../App_test/App.spec.\n",
136	 "\n",
137	 "  ts:run(App, Suites)\n",
138	 "    App = atom(), Suites = atom() | [atom()]\n",
139	 "    Run one or more test suites for App (i.e. modules named\n",
140	 "    *_SUITE.erl, located in ../App_test/).\n",
141	 "\n",
142	 "  ts:run(App, Suite, TestCases)\n",
143	 "    App = atom(), Suite = atom(),\n",
144	 "    TestCases = TCs | {testcase,TCs}, TCs = atom() | [atom()]\n",
145	 "    Run one or more test cases (functions) in Suite.\n",
146	 "\n",
147	 "  ts:run(App, Suite, {group,Groups})\n",
148	 "    App = atom(), Suite = atom(), Groups = atom() | [atom()]\n",
149	 "    Run one or more test case groups in Suite.\n",
150	 "\n",
151	 "  ts:run(App, Suite, {group,Group}, {testcase,TestCases})\n",
152	 "    App = atom(), Suite = atom(), Group = atom(),\n",
153	 "    TestCases = atom() | [atom()]\n",
154 	 "    Run one or more test cases in a test case group in Suite.\n",
155	 "\n",
156	 "  ts:run_category(TestCategory)\n",
157	 "    TestCategory = smoke | essential | bench | atom()\n",
158	 "    Run the specified category of tests for all apps.\n",
159	 "    For each app, the tests are defined by the specification:\n",
160	 "    ../App_test/App_TestCategory.spec.\n",
161	 "\n",
162	 "  ts:run_category(Apps, TestCategory)\n",
163	 "    Apps = atom() | [atom()],\n",
164	 "    TestCategory = smoke | essential | bench | atom()\n",
165	 "    Run the specified category of tests for the given app or apps.\n",
166	 "\n",
167	 "    Note that the test category parameter may have arbitrary value,\n",
168	 "    but should correspond to an existing test specification with file\n",
169	 "    name: ../App_test/App_TestCategory.spec.\n",
170	 "    Predefined categories exist for smoke tests, essential tests and\n",
171	 "    benchmark tests. The corresponding specs are:\n",
172	 "    ../*_test/Spec_smoke.spec, ../*_test/Spec_essential.spec and\n",
173	 "    ../*_test/Spec_bench.spec.\n",
174	 "\n",
175	 "  All above run functions can take an additional last argument,\n",
176	 "  Options, which is a list of options (e.g. ts:run(App, Options),\n",
177	 "  or ts:run_category(Apps, TestCategory, Options)).\n",
178	 "\n",
179	 "Run options supported:\n\n",
180	 "  batch             - Do not start a new xterm\n",
181	 "  {verbose, Level}  - Same as the verbosity option for install\n",
182	 "  verbose           - Same as {verbose, 1}\n",
183	 "  {vars, Vars}      - Variables in addition to the 'variables' file\n",
184	 "                      Can be any of the install options\n",
185	 "  {trace, TraceSpec}- Start call trace on target and slave nodes\n",
186	 "                      TraceSpec is the name of a file containing\n",
187	 "                      trace specifications or a list of trace\n",
188	 "                      specification elements.\n",
189	 "  {config, Path}    - Specify which directory ts should get it's \n"
190	 "                      config files from. The files should follow\n"
191	 "                      the convention lib/test_server/src/ts*.config.\n"
192	 "                      These config files can also be specified by\n"
193	 "                      setting the TEST_CONFIG_PATH environment\n"
194	 "                      variable to the directory where the config\n"
195	 "                      files are. The default location is\n"
196	 "                      tests/test_server/.\n"
197	 "\n",
198	 "Supported trace information elements:\n\n",
199	 "  {tp | tpl, Mod, [] | match_spec()}\n",
200	 "  {tp | tpl, Mod, Func, [] | match_spec()}\n",
201	 "  {tp | tpl, Mod, Func, Arity, [] | match_spec()}\n",
202	 "  {ctp | ctpl, Mod}\n",
203	 "  {ctp | ctpl, Mod, Func}\n",
204	 "  {ctp | ctpl, Mod, Func, Arity}\n",
205	 "\n\n",
206	 "Support functions:\n\n",
207	 "  ts:tests()\n",
208	 "    Returns all apps available for testing.\n",
209	 "\n",
210	 "  ts:tests(TestCategory)\n",
211	 "    Returns all apps that provide tests in the given category.\n",
212	 "\n",
213	 "  ts:suites(App)\n",
214	 "    Returns all available test suites for App,\n",
215	 "    i.e. ../App_test/*_SUITE.erl\n",
216	 "\n",
217	 "  ts:categories(App)\n",
218	 "    Returns all test categories available for App.\n",
219	 "\n",
220	 "  ts:estone()\n",
221	 "    Runs estone_SUITE in the kernel application with no run options\n",
222	 "\n",
223	 "  ts:estone(Opts)\n",
224	 "    Runs estone_SUITE in the kernel application with the given\n",
225	 "    run options\n",
226	 "\n",
227	 "  ts:cross_cover_analyse(Level)\n",
228	 "    Use after ts:run with option cover or cover_details. Analyses\n",
229	 "    modules specified with a 'cross' statement in the cover spec file.\n",
230	 "    Level can be 'overview' or 'details'.\n",
231	 "\n",
232	 "  ts:compile_testcases()\n",
233	 "  ts:compile_testcases(Apps)\n",
234	 "    Compiles all test cases for the given apps, for usage in a\n",
235	 "    cross compilation environment.\n",
236	 "\n\n",
237	 "Installation (already done):\n\n"
238	],
239    show_help([H,?install_help]).
240
241show_help(H) ->
242    io:format(lists:flatten(H)).
243
244
245%% Installs tests.
246install() ->
247    ts_install:install(install_local,[]).
248install(Options) when is_list(Options) ->
249    ts_install:install(install_local,Options).
250
251%% run/0
252%%  Runs all specs found by ts:tests(), if any, or returns
253%%  {error, no_tests_available}. (batch)
254run() ->
255    case ts:tests() of
256	[] ->
257	    {error, no_tests_available};
258	_ ->
259	    check_and_run(fun(Vars) -> run_all(Vars) end)
260    end.
261run_all(_Vars) ->
262    run_some(tests(), [batch]).
263
264run_some([], _Opts) ->
265    ok;
266run_some(Apps, Opts) ->
267    case proplists:get_value(test_category, Opts) of
268	bench ->
269	    check_and_run(fun(Vars) -> ts_benchmark:run(Apps, Opts, Vars) end);
270	_Other ->
271	    run_some1(Apps, Opts)
272    end.
273
274run_some1([], _Opts) ->
275    ok;
276run_some1([{App,Mod}|Apps], Opts) ->
277    case run(App, Mod, Opts) of
278	ok -> ok;
279	Error -> io:format("~p: ~p~n",[{App,Mod},Error])
280    end,
281    run_some1(Apps, Opts);
282run_some1([App|Apps], Opts) ->
283    case run(App, Opts) of
284	ok -> ok;
285	Error -> io:format("~p: ~p~n",[App,Error])
286    end,
287    run_some1(Apps, Opts).
288
289%% This can be used from command line. Both App and
290%% TestCategory must be specified. App may be 'all'
291%% and TestCategory may be 'main'. Examples:
292%% erl -s ts cl_run kernel smoke <options>
293%% erl -s ts cl_run kernel main <options>
294%% erl -s ts cl_run all essential <options>
295%% erl -s ts cl_run all main <options>
296%% When using the 'main' category and running with cover,
297%% one can also use the cross_cover_analysis flag.
298cl_run([App,Cat|Options0]) when is_atom(App) ->
299
300    AllAtomsFun = fun(X) when is_atom(X) -> true;
301		     (_) -> false
302		  end,
303    Options1 =
304	case lists:all(AllAtomsFun, Options0) of
305	    true ->
306		%% Could be from command line
307		lists:map(fun(Opt) ->
308				  to_erlang_term(Opt)
309			  end, Options0) -- [batch];
310	    false ->
311		Options0 -- [batch]
312	end,
313    %% Make sure there is exactly one occurence of 'batch'
314    Options2 = [batch|Options1],
315
316    Result =
317	case {App,Cat} of
318	    {all,main} ->
319		run(tests(), Options2);
320	    {all,Cat} ->
321		run_category(Cat, Options2);
322	    {_,main} ->
323		run(App, Options2);
324	    {_,Cat} ->
325		run_category(App, Cat, Options2)
326	end,
327    case check_for_cross_cover_analysis_flag(Options2) of
328	false ->
329	    ok;
330	Level ->
331	    cross_cover_analyse(Level)
332    end,
333    Result.
334
335%% run/1
336%% Runs tests for one app (interactive).
337run(App) when is_atom(App) ->
338    Options = check_test_get_opts(App, []),
339    File = atom_to_list(App),
340    run_test(File, [{spec,[File++".spec"]},{allow_user_terms,true}], Options);
341
342%% This can be used from command line, e.g.
343%% erl -s ts run all <options>
344%% erl -s ts run main <options>
345run([all,main|Opts]) ->
346    cl_run([all,main|Opts]);
347run([all|Opts]) ->
348    cl_run([all,main|Opts]);
349run([main|Opts]) ->
350    cl_run([all,main|Opts]);
351%% Backwards compatible
352run([all_tests|Opts]) ->
353    cl_run([all,main|Opts]);
354
355%% run/1
356%% Runs the main tests for all available apps
357run(Apps) when is_list(Apps) ->
358    run(Apps, [batch]).
359
360%% run/2
361%% Runs the main tests for all available apps
362run(Apps, Opts) when is_list(Apps), is_list(Opts) ->
363    run_some(Apps, Opts);
364
365%% Runs tests for one app with list of suites or with options
366run(App, ModsOrOpts) when is_atom(App),
367			  is_list(ModsOrOpts) ->
368    case is_list_of_suites(ModsOrOpts) of
369	false ->
370	    run(App, {opts_list,ModsOrOpts});
371	true ->
372	    run_some([{App,M} || M <- ModsOrOpts],
373		     [batch])
374    end;
375
376run(App, {opts_list,Opts}) ->
377    Options = check_test_get_opts(App, Opts),
378    File = atom_to_list(App),
379
380    %% check if other test category than main has been specified
381    {CatSpecName,TestCat} =
382	case proplists:get_value(test_category, Opts) of
383	    undefined ->
384		{"",main};
385	    Cat ->
386		{"_" ++ atom_to_list(Cat),Cat}
387	end,
388
389    WhatToDo =
390	case App of
391	    %% Known to exist but fails generic tests below
392	    emulator -> test;
393	    system -> test;
394	    erl_interface -> test;
395	    epmd -> test;
396	    _ ->
397		case code:lib_dir(App) of
398		    {error,bad_name} ->
399			%% Application does not exist
400			skip;
401		    Path ->
402			case file:read_file_info(filename:join(Path,"ebin")) of
403			    {ok,#file_info{type=directory}} ->
404				%% Erlang application is built
405				test;
406			    _ ->
407				case filelib:wildcard(
408				       filename:join([Path,"priv","*.jar"])) of
409				    [] ->
410					%% The application is not built
411					skip;
412				    [_|_] ->
413					%% Java application is built
414					test
415				end
416			end
417		end
418	end,
419    case WhatToDo of
420	skip ->
421	    SkipSpec = create_skip_spec(App, suites(App)),
422	    run_test(File, [{spec,[SkipSpec]}], Options);
423	test when TestCat == bench ->
424	    check_and_run(fun(Vars) ->
425				  ts_benchmark:run([App], Options, Vars)
426			  end);
427	test ->
428	    Spec = File ++ CatSpecName ++ ".spec",
429	    run_test(File, [{spec,[Spec]},{allow_user_terms,true}], Options)
430	end;
431
432%% Runs one module for an app (interactive)
433run(App, Mod) when is_atom(App), is_atom(Mod) ->
434    run_test({atom_to_list(App),Mod},
435	     [{suite,Mod}],
436	     [interactive]).
437
438%% run/3
439%% Run one module for an app with Opts
440run(App, Mod, Opts) when is_atom(App),
441			 is_atom(Mod),
442			 is_list(Opts) ->
443    Options = check_test_get_opts(App, Opts),
444    run_test({atom_to_list(App),Mod},
445	     [{suite,Mod}], Options);
446
447%% Run multiple modules with Opts
448run(App, Mods, Opts) when is_atom(App),
449			  is_list(Mods),
450			  is_list(Opts) ->
451    run_some([{App,M} || M <- Mods], Opts);
452
453%% Runs one test case in a module.
454run(App, Mod, Case) when is_atom(App),
455			 is_atom(Mod),
456			 is_atom(Case) ->
457    Options = check_test_get_opts(App, []),
458    Args = [{suite,Mod},{testcase,Case}],
459    run_test(atom_to_list(App), Args, Options);
460
461%% Runs one or more groups in a module.
462run(App, Mod, Grs={group,_Groups}) when is_atom(App),
463					is_atom(Mod) ->
464    Options = check_test_get_opts(App, []),
465    Args = [{suite,Mod},Grs],
466    run_test(atom_to_list(App), Args, Options);
467
468%% Runs one or more test cases in a module.
469run(App, Mod, TCs={testcase,_Cases}) when is_atom(App),
470					  is_atom(Mod) ->
471    Options = check_test_get_opts(App, []),
472    Args = [{suite,Mod},TCs],
473    run_test(atom_to_list(App), Args, Options).
474
475%% run/4
476%% Run one test case in a module with Options.
477run(App, Mod, Case, Opts) when is_atom(App),
478			       is_atom(Mod),
479			       is_atom(Case),
480			       is_list(Opts) ->
481    Options = check_test_get_opts(App, Opts),
482    Args = [{suite,Mod},{testcase,Case}],
483    run_test(atom_to_list(App), Args, Options);
484
485%% Run one or more test cases in a module with Options.
486run(App, Mod, {testcase,Cases}, Opts) when is_atom(App),
487					   is_atom(Mod) ->
488    run(App, Mod, Cases, Opts);
489run(App, Mod, Cases, Opts) when is_atom(App),
490				is_atom(Mod),
491				is_list(Cases),
492				is_list(Opts) ->
493    Options = check_test_get_opts(App, Opts),
494    Args = [{suite,Mod},Cases],
495    run_test(atom_to_list(App), Args, Options);
496
497%% Run one or more test cases in a group.
498run(App, Mod, Gr={group,_Group}, {testcase,Cases}) when is_atom(App),
499							is_atom(Mod) ->
500    run(App, Mod, Gr, Cases, [batch]);
501
502
503%% Run one or more groups in a module with Options.
504run(App, Mod, Grs={group,_Groups}, Opts) when is_atom(App),
505					      is_atom(Mod),
506					      is_list(Opts) ->
507    Options = check_test_get_opts(App, Opts),
508    Args = [{suite,Mod},Grs],
509    run_test(atom_to_list(App), Args, Options).
510
511%% run/5
512%% Run one or more test cases in a group with Options.
513run(App, Mod, Group, Cases, Opts) when is_atom(App),
514				       is_atom(Mod),
515				       is_list(Opts) ->
516    Group1 = if is_tuple(Group) -> Group; true -> {group,Group} end,
517    Cases1 = if is_tuple(Cases) -> Cases; true -> {testcase,Cases} end,
518    Options = check_test_get_opts(App, Opts),
519    Args = [{suite,Mod},Group1,Cases1],
520    run_test(atom_to_list(App), Args, Options).
521
522%% run_category/1
523run_category(TestCategory) when is_atom(TestCategory) ->
524    run_category(TestCategory, [batch]).
525
526%% run_category/2
527run_category(TestCategory, Opts) when is_atom(TestCategory),
528				      is_list(Opts) ->
529    case ts:tests(TestCategory) of
530	[] ->
531	    {error, no_tests_available};
532	Apps ->
533	    Opts1 = [{test_category,TestCategory} | Opts],
534	    run_some(Apps, Opts1)
535    end;
536
537run_category(Apps, TestCategory) when is_atom(TestCategory) ->
538    run_category(Apps, TestCategory, [batch]).
539
540%% run_category/3
541run_category(App, TestCategory, Opts) ->
542    Apps = if is_atom(App) -> [App];
543	      is_list(App) -> App
544	   end,
545    Opts1 = [{test_category,TestCategory} | Opts],
546    run_some(Apps, Opts1).
547
548%%-----------------------------------------------------------------
549%% Functions kept for backwards compatibility
550
551bench() ->
552    run_category(bench, []).
553bench(Opts) when is_list(Opts) ->
554    run_category(bench, Opts);
555bench(App) ->
556    run_category(App, bench, []).
557bench(App, Opts) when is_atom(App) ->
558    run_category(App, bench, Opts);
559bench(Apps, Opts) when is_list(Apps) ->
560    run_category(Apps, bench, Opts).
561
562benchmarks() ->
563    tests(bench).
564
565smoke_test() ->
566    run_category(smoke, []).
567smoke_test(Opts) when is_list(Opts) ->
568    run_category(smoke, Opts);
569smoke_test(App) ->
570    run_category(App, smoke, []).
571smoke_test(App, Opts) when is_atom(App) ->
572    run_category(App, smoke, Opts);
573smoke_test(Apps, Opts) when is_list(Apps) ->
574    run_category(Apps, smoke, Opts).
575
576smoke_tests() ->
577    tests(smoke).
578
579%%-----------------------------------------------------------------
580
581is_list_of_suites(List) ->
582    lists:all(fun(Suite) ->
583		      S = if is_atom(Suite) -> atom_to_list(Suite);
584			     true -> Suite
585			  end,
586		      try lists:last(string:lexemes(S,"_")) of
587			  "SUITE" -> true;
588			  "suite" -> true;
589			  _ -> false
590		      catch
591			  _:_ -> false
592		      end
593	      end, List).
594
595%% Create a spec to skip all SUITES, this is used when the application
596%% to be tested is not part of the OTP release to be tested.
597create_skip_spec(App, SuitesToSkip) ->
598    {ok,Cwd} = file:get_cwd(),
599    AppString = atom_to_list(App),
600    Specname = AppString++"_skip.spec",
601    {ok,D} = file:open(filename:join([filename:dirname(Cwd),
602				      AppString++"_test",Specname]),
603		       [write]),
604    TestDir = "\"../"++AppString++"_test\"",
605    io:format(D,"{suites, "++TestDir++", all}.~n",[]),
606    io:format(D,"{skip_suites, "++TestDir++", ~w, \"Skipped as application"
607	      " is not in path!\"}.",[SuitesToSkip]),
608    Specname.
609
610%% Check testspec for App to be valid and get possible options
611%% from the list.
612check_test_get_opts(App, Opts) ->
613    validate_test(App),
614    Mode = configmember(batch, {batch, interactive}, Opts),
615    Vars = configvars(Opts),
616    Trace = get_config(trace,Opts),
617    ConfigPath = get_config(config,Opts),
618    KeepTopcase = configmember(keep_topcase, {keep_topcase,[]}, Opts),
619    Cover = configcover(App,Opts),
620    lists:flatten([Vars,Mode,Trace,KeepTopcase,Cover,ConfigPath]).
621
622to_erlang_term(Atom) ->
623    String = atom_to_list(Atom),
624    {ok, Tokens, _} = erl_scan:string(lists:append([String, ". "])),
625    {ok, Term} = erl_parse:parse_term(Tokens),
626    Term.
627
628%% Validate that Testspec really is a testspec,
629%% and exit if not.
630validate_test(Testspec) ->
631    case lists:member(Testspec, tests()) of
632	true ->
633	    ok;
634	false ->
635	    io:format("This testspec does not seem to be "
636		      "available.~n Please try ts:tests() "
637		      "to see available tests.~n"),
638	    exit(self(), {error, test_not_available})
639    end.
640
641configvars(Opts) ->
642    case lists:keysearch(vars, 1, Opts) of
643	{value, {vars, List}} ->
644	    List0 = special_vars(Opts),
645	    Key = fun(T) -> element(1,T) end,
646	    DelDupList =
647		lists:filter(fun(V) ->
648				     case lists:keysearch(Key(V),1,List0) of
649					 {value,_} -> false;
650					 _ -> true
651				     end
652			     end, List),
653	    {vars, [List0|DelDupList]};
654	_ ->
655	    {vars, special_vars(Opts)}
656    end.
657
658%% Allow some shortcuts in the options...
659special_vars(Opts) ->
660    SpecVars =
661	case lists:member(verbose, Opts) of
662	    true ->
663		[{verbose, 1}];
664	    false ->
665		case lists:keysearch(verbose, 1, Opts) of
666		    {value, {verbose, Lvl}} ->
667			[{verbose, Lvl}];
668		    _ ->
669			[{verbose, 0}]
670		end
671	end,
672    SpecVars1 =
673	case lists:keysearch(diskless, 1, Opts) of
674	    {value,{diskless, true}} ->
675		[{diskless, true} | SpecVars];
676	    _ ->
677		SpecVars
678	end,
679    case lists:keysearch(testcase_callback, 1, Opts) of
680	{value,{testcase_callback, CBM, CBF}} ->
681	    [{ts_testcase_callback, {CBM,CBF}} | SpecVars1];
682	{value,{testcase_callback, CB}} ->
683	    [{ts_testcase_callback, CB} | SpecVars1];
684	_ ->
685	    SpecVars1
686    end.
687
688get_config(Key,Config) ->
689    case lists:keysearch(Key,1,Config) of
690	{value,Value} -> Value;
691	false -> []
692    end.
693
694configcover(Testspec,[cover|_]) ->
695    {cover,Testspec,default_coverfile(Testspec),overview};
696configcover(Testspec,[cover_details|_]) ->
697    {cover,Testspec,default_coverfile(Testspec),details};
698configcover(Testspec,[{cover,File}|_]) ->
699    {cover,Testspec,File,overview};
700configcover(Testspec,[{cover_details,File}|_]) ->
701    {cover,Testspec,File,details};
702configcover(Testspec,[_H|T]) ->
703    configcover(Testspec,T);
704configcover(_Testspec,[]) ->
705    [].
706
707default_coverfile(Testspec) ->
708    {ok,Cwd} = file:get_cwd(),
709    CoverFile = filename:join([filename:dirname(Cwd),
710			       atom_to_list(Testspec)++"_test",
711			       atom_to_list(Testspec)++".cover"]),
712    case filelib:is_file(CoverFile) of
713	true ->
714	    CoverFile;
715	false ->
716	    none
717    end.
718
719configmember(Member, {True, False}, Config) ->
720    case lists:member(Member, Config) of
721	true ->
722	    True;
723	false ->
724	    False
725    end.
726
727
728check_for_cross_cover_analysis_flag(Config) ->
729    check_for_cross_cover_analysis_flag(Config,false,false).
730check_for_cross_cover_analysis_flag([cover|Config],false,false) ->
731    check_for_cross_cover_analysis_flag(Config,overview,false);
732check_for_cross_cover_analysis_flag([cover|_Config],false,true) ->
733    overview;
734check_for_cross_cover_analysis_flag([cover_details|Config],false,false) ->
735    check_for_cross_cover_analysis_flag(Config,details,false);
736check_for_cross_cover_analysis_flag([cover_details|_Config],false,true) ->
737    details;
738check_for_cross_cover_analysis_flag([cross_cover_analysis|Config],false,_) ->
739    check_for_cross_cover_analysis_flag(Config,false,true);
740check_for_cross_cover_analysis_flag([cross_cover_analysis|_Config],Level,_) ->
741    Level;
742check_for_cross_cover_analysis_flag([_|Config],Level,CrossFlag) ->
743    check_for_cross_cover_analysis_flag(Config,Level,CrossFlag);
744check_for_cross_cover_analysis_flag([],_,_) ->
745    false.
746
747
748%% Returns all available apps.
749tests() ->
750    {ok, Cwd} = file:get_cwd(),
751    ts_lib:specs(Cwd).
752
753%% Returns all apps that provide tests in the given test category
754tests(main) ->
755    {ok, Cwd} = file:get_cwd(),
756    ts_lib:specs(Cwd);
757tests(bench) ->
758    ts_benchmark:benchmarks();
759tests(TestCategory) ->
760    {ok, Cwd} = file:get_cwd(),
761    ts_lib:specialized_specs(Cwd, atom_to_list(TestCategory)).
762
763%% Returns a list of available test suites for App.
764suites(App) ->
765    {ok, Cwd} = file:get_cwd(),
766    ts_lib:suites(Cwd, atom_to_list(App)).
767
768%% Returns all available test categories for App
769categories(App) ->
770    {ok, Cwd} = file:get_cwd(),
771    ts_lib:test_categories(Cwd, atom_to_list(App)).
772
773%%
774%% estone/0, estone/1
775%% Opts = same as Opts or Config for the run(...) function,
776%% e.g. [batch]
777%%
778estone() -> run(emulator,estone_SUITE).
779estone(Opts) when is_list(Opts) -> run(emulator,estone_SUITE,Opts).
780
781%%
782%% cross_cover_analyse/1
783%% Level = details | overview
784%% Can be called on any node after a test (with cover) is
785%% completed. The node's current directory must be the same as when
786%% the tests were run.
787%%
788cross_cover_analyse([Level]) ->
789    cross_cover_analyse(Level);
790cross_cover_analyse(Level) ->
791    Apps = get_last_app_tests(),
792    test_server_ctrl:cross_cover_analyse(Level,Apps).
793
794get_last_app_tests() ->
795    AllTests = filelib:wildcard(filename:join(["*","*_test.logs"])),
796    {ok,RE} = re:compile("^[^/]*/[^\.]*\.(.*)_test\.logs$"),
797    get_last_app_tests(AllTests,RE,[]).
798
799get_last_app_tests([Dir|Dirs],RE,Acc) ->
800    NewAcc =
801	case re:run(Dir,RE,[{capture,all,list}]) of
802	    {match,[Dir,AppStr]} ->
803		Dir1 = filename:dirname(Dir), % cover logs in ct_run.<t> dir
804		App = list_to_atom(AppStr),
805		case lists:keytake(App,1,Acc) of
806		    {value,{App,LastDir},Rest} ->
807			if Dir1 > LastDir ->
808				[{App,Dir1}|Rest];
809			   true ->
810				Acc
811			end;
812		    false ->
813			[{App,Dir1} | Acc]
814		end;
815	    _ ->
816		Acc
817	end,
818    get_last_app_tests(Dirs,RE,NewAcc);
819get_last_app_tests([],_,Acc) ->
820    Acc.
821
822%%% Implementation.
823
824check_and_run(Fun) ->
825    case file:consult(?variables) of
826	{ok, Vars} ->
827	    check_and_run(Fun, Vars);
828	{error, Error} when is_atom(Error) ->
829	    {error, not_installed};
830	{error, Reason} ->
831	    {error, {bad_installation, file:format_error(Reason)}}
832    end.
833
834check_and_run(Fun, Vars) ->
835    Platform = ts_install:platform_id(Vars),
836    case lists:keysearch(platform_id, 1, Vars) of
837	{value, {_, Platform}} ->
838	    case catch apply(Fun, [Vars]) of
839		{'EXIT', Reason} ->
840		    exit(Reason);
841		Other ->
842		    Other
843	    end;
844	{value, {_, OriginalPlatform}} ->
845	    io:format("These test suites were installed for '~s'.\n",
846		      [OriginalPlatform]),
847	    io:format("But the current platform is '~s'.\nPlease "
848		      "install for this platform before running "
849		      "any tests.\n", [Platform]),
850	    {error, inconsistent_platforms};
851	false ->
852	    {error, {bad_installation, no_platform}}
853    end.
854
855run_test(File, Args, Options) ->
856    check_and_run(fun(Vars) -> run_test(File, Args, Options, Vars) end).
857
858run_test(File, Args, Options, Vars) ->
859    ts_run:run(File, Args, Options, Vars).
860
861
862%% This module provides some convenient shortcuts to running
863%% the test server from within a started Erlang shell.
864%% (This are here for backwards compatibility.)
865%%
866%% r()
867%% r(Opts)
868%% r(SpecOrMod)
869%% r(SpecOrMod, Opts)
870%% r(Mod, Case)
871%% r(Mod, Case, Opts)
872%%	Each of these functions starts the test server if it
873%%	isn't already running, then runs the test case(s) selected
874%%	by the aguments.
875%%      SpecOrMod can be a module name or the name of a test spec file,
876%%      with the extension .spec or .spec.OsType. The module Mod will
877%%	be reloaded before running the test cases.
878%%      Opts = [Opt],
879%%      Opt = {Cover,AppOrCoverFile} | {Cover,App,CoverFile}
880%%      Cover = cover | cover_details
881%%      AppOrCoverFile = App | CoverFile
882%%      App = atom(), an application name
883%%      CoverFile = string(), name of a cover file
884%%                  (see doc of test_server_ctrl:cover/2/3)
885%%
886%% i()
887%%	Shows information about the jobs being run, by dumping
888%%	the process information for the test_server.
889%%
890%% l(Mod)
891%%	This function reloads a module just like c:l/1, but works
892%%	even for a module in one of the sticky library directories
893%%	(for instance, lists can be reloaded).
894
895%% Runs all tests cases in the current directory.
896
897r() ->
898    r([]).
899r(Opts) when is_list(Opts), is_atom(hd(Opts)) ->
900    ensure_ts_started(Opts),
901    test_server_ctrl:add_dir("current_dir", ".");
902
903%% Checks if argument is a spec file or a module
904%% (spec file must be named "*.spec" or "*.spec.OsType")
905%% If module, reloads module and runs all test cases in it.
906%% If spec, runs all test cases in it.
907
908r(SpecOrMod) ->
909    r(SpecOrMod,[]).
910r(SpecOrMod,Opts) when is_list(Opts) ->
911    ensure_ts_started(Opts),
912    case filename:extension(SpecOrMod) of
913	[] ->
914	    l(SpecOrMod),
915	    test_server_ctrl:add_module(SpecOrMod);
916	".spec" ->
917	    test_server_ctrl:add_spec(SpecOrMod);
918	_ ->
919	    Spec2 = filename:rootname(SpecOrMod),
920	    case filename:extension(Spec2) of
921		".spec" ->
922		    %% *.spec.Type
923		    test_server_ctrl:add_spec(SpecOrMod);
924		_ ->
925		    {error, unknown_filetype}
926	    end
927    end;
928
929%% Reloads the given module and runs the given test case in it.
930
931r(Mod, Case) ->
932    r(Mod,Case,[]).
933r(Mod, Case, Opts) ->
934    ensure_ts_started(Opts),
935    l(Mod),
936    test_server_ctrl:add_case(Mod, Case).
937
938%% Shows information about the jobs being run.
939
940i() ->
941    ensure_ts_started([]),
942    hformat("Job", "Current", "Total", "Success", "Failed", "Skipped"),
943    i(test_server_ctrl:jobs()).
944
945i([{Name, Pid}|Rest]) when is_pid(Pid) ->
946    {dictionary, PI} = process_info(Pid, dictionary),
947    {value, {_, CaseNum}} = lists:keysearch(test_server_case_num, 1, PI),
948    {value, {_, Cases}} = lists:keysearch(test_server_cases, 1, PI),
949    {value, {_, Failed}} = lists:keysearch(test_server_failed, 1, PI),
950    {value, {_, {UserSkipped,AutoSkipped}}} = lists:keysearch(test_server_skipped, 1, PI),
951    {value, {_, Ok}} = lists:keysearch(test_server_ok, 1, PI),
952    nformat(Name, CaseNum, Cases, Ok, Failed, UserSkipped+AutoSkipped),
953    i(Rest);
954i([]) ->
955    ok.
956
957hformat(A1, A2, A3, A4, A5, A6) ->
958    io:format("~-20s ~8s ~8s ~8s ~8s ~8s~n", [A1,A2,A3,A4,A5,A6]).
959
960nformat(A1, A2, A3, A4, A5, A6) ->
961    io:format("~-20s ~8w ~8w ~8w ~8w ~8w~n", [A1,A2,A3,A4,A5,A6]).
962
963%% Force load of a module even if it is in a sticky directory.
964
965l(Mod) ->
966    case do_load(Mod) of
967	{error, sticky_directory} ->
968	    Dir = filename:dirname(code:which(Mod)),
969	    code:unstick_dir(Dir),
970	    do_load(Mod),
971	    code:stick_dir(Dir);
972	X ->
973	    X
974    end.
975
976
977ensure_ts_started(Opts) ->
978    Pid = case whereis(test_server_ctrl) of
979	      undefined ->
980		  test_server_ctrl:start();
981	      P when is_pid(P) ->
982		  P
983	  end,
984    case Opts of
985	[{Cover,AppOrCoverFile}] when Cover==cover; Cover==cover_details ->
986	    test_server_ctrl:cover(AppOrCoverFile,cover_type(Cover));
987	[{Cover,App,CoverFile}]  when Cover==cover; Cover==cover_details ->
988	    test_server_ctrl:cover(App,CoverFile,cover_type(Cover));
989	_ ->
990	    ok
991    end,
992    Pid.
993
994cover_type(cover) -> overview;
995cover_type(cover_details) -> details.
996
997do_load(Mod) ->
998    code:purge(Mod),
999    code:load_file(Mod).
1000
1001
1002compile_testcases() ->
1003    compile_datadirs("../*/*_data").
1004
1005compile_testcases(App) when is_atom(App) ->
1006    compile_testcases([App]);
1007compile_testcases([App | T]) ->
1008    compile_datadirs(io_lib:format("../~s_test/*_data", [App])),
1009    compile_testcases(T);
1010compile_testcases([]) ->
1011    ok.
1012
1013compile_datadirs(DataDirs) ->
1014    {ok,Variables} = file:consult("variables"),
1015
1016    lists:foreach(fun(Dir) ->
1017			  ts_lib:make_non_erlang(Dir, Variables)
1018		  end,
1019		  filelib:wildcard(DataDirs)).
1020