aboutsummaryrefslogtreecommitdiffstats
path: root/lib/test_server/src
diff options
context:
space:
mode:
Diffstat (limited to 'lib/test_server/src')
-rw-r--r--lib/test_server/src/erl2html2.erl5
-rw-r--r--lib/test_server/src/test_server.erl37
-rw-r--r--lib/test_server/src/test_server_ctrl.erl138
-rw-r--r--lib/test_server/src/test_server_gl.erl4
-rw-r--r--lib/test_server/src/test_server_internal.hrl10
-rw-r--r--lib/test_server/src/test_server_io.erl28
-rw-r--r--lib/test_server/src/test_server_node.erl67
-rw-r--r--lib/test_server/src/ts_erl_config.erl22
8 files changed, 118 insertions, 193 deletions
diff --git a/lib/test_server/src/erl2html2.erl b/lib/test_server/src/erl2html2.erl
index 9c0ca64173..d0f40c47a7 100644
--- a/lib/test_server/src/erl2html2.erl
+++ b/lib/test_server/src/erl2html2.erl
@@ -1,3 +1,4 @@
+%% -*- coding: utf-8 -*-
%%
%% %CopyrightBegin%
%%
@@ -126,7 +127,7 @@ build_html(SFd,DFd,Encoding,Functions) ->
build_html(SFd,DFd,Encoding,file:read_line(SFd),1,Functions,false).
build_html(SFd,DFd,Encoding,{ok,Str},L,[{F,A,L}|Functions],_IsFuncDef) ->
- FALink = http_uri:encode(F++"-"++integer_to_list(A)),
+ FALink = test_server_ctrl:uri_encode(F++"-"++integer_to_list(A),utf8),
file:write(DFd,["<a name=\"",to_raw_list(FALink,Encoding),"\"/>"]),
build_html(SFd,DFd,Encoding,{ok,Str},L,Functions,true);
build_html(SFd,DFd,Encoding,{ok,Str},L,[{clause,L}|Functions],_IsFuncDef) ->
@@ -214,7 +215,7 @@ html_encoding(utf8) ->
%%% from the source.
%%%
%%% Example: if the encoding of the file is utf8, and we have a string
-%%% containing "�" = [229], then we need to convert this to [195,165]
+%%% containing "å" = [229], then we need to convert this to [195,165]
%%% before writing. Note that this conversion is only necessary
%%% because the destination file is not (necessarily) opened with utf8
%%% encoding - it is opened with default encoding in order to allow
diff --git a/lib/test_server/src/test_server.erl b/lib/test_server/src/test_server.erl
index 4c39c604a2..8b0be51be3 100644
--- a/lib/test_server/src/test_server.erl
+++ b/lib/test_server/src/test_server.erl
@@ -218,17 +218,14 @@ do_cover_compile1([]) ->
%% Analyse = {details,Dir} | details | {overview,void()} | overview
%% Modules = [atom()], the modules to analyse
%%
-%% Cover analysis. If this is a remote target, analyse_to_file can not be used.
-%% In that case the analyse level 'line' is used instead if Analyse==details.
+%% Cover analysis. If Analyse=={details,Dir} analyse_to_file is used.
%%
-%% If this is a local target, the test directory is given
-%% (Analyse=={details,Dir}) and analyse_to_file can be used directly.
+%% If Analyse=={overview,Dir} analyse_to_file is not used, only an
+%% overview containing the number of covered/not covered lines in each
+%% module.
%%
-%% If Analyse==overview | {overview,Dir} analyse_to_file is not used, only
-%% an overview containing the number of covered/not covered lines in each module.
-%%
-%% Also, if a Dir exists, cover data will be exported to a file called
-%% all.coverdata in that directory.
+%% Also, cover data will be exported to a file called all.coverdata in
+%% the given directory.
%%
%% Finally, if Stop==true, then cover will be stopped after the
%% analysis is completed. Stopping cover causes the original (non
@@ -261,24 +258,13 @@ cover_analyse(Analyse,Modules,Stop) ->
Error ->
fun(_) -> Error end
end;
- details ->
- fun(M) ->
- case cover:analyse(M,line) of
- {ok,Lines} ->
- {lines,Lines};
- Error ->
- Error
- end
- end;
{overview,Dir} ->
case cover:export(filename:join(Dir,"all.coverdata")) of
ok ->
fun(_) -> undefined end;
Error ->
fun(_) -> Error end
- end;
- overview ->
- fun(_) -> undefined end
+ end
end,
R = pmap(
fun(M) ->
@@ -512,10 +498,10 @@ run_test_case_msgloop(#st{ref=Ref,pid=Pid,end_conf_pid=EndConfPid0}=St0) ->
end,
run_test_case_msgloop(St);
{sync_apply,From,MFA} ->
- sync_local_or_remote_apply(false,From,MFA),
+ do_sync_apply(false,From,MFA),
run_test_case_msgloop(St0);
{sync_apply_proxy,Proxy,From,MFA} ->
- sync_local_or_remote_apply(Proxy,From,MFA),
+ do_sync_apply(Proxy,From,MFA),
run_test_case_msgloop(St0);
{comment,NewComment0} ->
NewComment1 = test_server_ctrl:to_string(NewComment0),
@@ -2599,10 +2585,9 @@ purify_format(Format, Args) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
-%% Generic send functions for communication with host
+%% Apply given function and reply to caller or proxy.
%%
-sync_local_or_remote_apply(Proxy, From, {M,F,A}) ->
- %% i'm a local target
+do_sync_apply(Proxy, From, {M,F,A}) ->
Result = apply(M, F, A),
if is_pid(Proxy) -> Proxy ! {sync_result_proxy,From,Result};
true -> From ! {sync_result,Result}
diff --git a/lib/test_server/src/test_server_ctrl.erl b/lib/test_server/src/test_server_ctrl.erl
index 5d4d392166..ffa21d054c 100644
--- a/lib/test_server/src/test_server_ctrl.erl
+++ b/lib/test_server/src/test_server_ctrl.erl
@@ -251,8 +251,6 @@ parse_cmd_line(['MODULE',Mod|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
parse_cmd_line(['CASE',Mod,Case|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
parse_cmd_line(Cmds,[{topcase,{Mod,Case}}|SpecList],[atom_to_list(Mod)|Names],
Param, Trc, Cov, TCCB);
-parse_cmd_line(['PARAMETERS',Param|Cmds], SpecList, Names, _Param, Trc, Cov, TCCB) ->
- parse_cmd_line(Cmds, SpecList, Names, Param, Trc, Cov, TCCB);
parse_cmd_line(['TRACE',Trc|Cmds], SpecList, Names, Param, _Trc, Cov, TCCB) ->
parse_cmd_line(Cmds, SpecList, Names, Param, Trc, Cov, TCCB);
parse_cmd_line(['COVER',App,CF,Analyse|Cmds], SpecList, Names, Param, Trc, _Cov, TCCB) ->
@@ -284,19 +282,23 @@ cast_to_list(X) -> lists:flatten(io_lib:format("~w", [X])).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% START INTERFACE
-start() ->
- start(local).
+%% Kept for backwards compatibility
+start(_) ->
+ start().
+start_link(_) ->
+ start_link().
-start(Param) ->
- case gen_server:start({local,?MODULE}, ?MODULE, [Param], []) of
+
+start() ->
+ case gen_server:start({local,?MODULE}, ?MODULE, [], []) of
{ok, Pid} ->
{ok, Pid};
Other ->
Other
end.
-start_link(Param) ->
- case gen_server:start_link({local,?MODULE}, ?MODULE, [Param], []) of
+start_link() ->
+ case gen_server:start_link({local,?MODULE}, ?MODULE, [], []) of
{ok, Pid} ->
{ok, Pid};
Other ->
@@ -463,24 +465,11 @@ controller_call(Arg, Timeout) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% init([Mode])
-%% Mode = lazy | error_logger
-%% StateFile = string()
-%% ReadMode = ignore_errors | halt_on_errors
+%% init([])
%%
%% init() is the init function of the test_server's gen_server.
-%% When Mode=error_logger: The init function of the test_server's gen_event
-%% event handler used as a replacement error_logger when running test_suites.
%%
-%% The init function reads the test server state file, to see what test
-%% suites were running when the test server was last running, and which
-%% flags that were in effect. If no state file is found, or there are
-%% errors in it, defaults are used.
-%%
-%% Mode 'lazy' ignores (and resets to []) any jobs in the state file
-%%
-
-init([_]) ->
+init([]) ->
case os:getenv("TEST_SERVER_CALL_TRACE") of
false ->
ok;
@@ -505,7 +494,6 @@ init([_]) ->
end,
test_server_sup:cleanup_crash_dumps(),
State = #state{jobs=[],finish=false},
- put(test_server_free_targets,[]),
TI0 = test_server:init_target_info(),
TargetHost = test_server_sup:hoststr(),
TI = TI0#target_info{host=TargetHost,
@@ -529,7 +517,7 @@ naming() ->
%% is completed.
%%
handle_call(kill_slavenodes, _From, State) ->
- Nodes = test_server_node:kill_nodes(State#state.target_info),
+ Nodes = test_server_node:kill_nodes(),
{reply, Nodes, State};
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -950,11 +938,11 @@ handle_call({wait_for_node, Node}, From, State) ->
%% - the node is really stopped by test_server when this returns.
handle_call({stop_node, Name}, _From, State) ->
- R = test_server_node:stop_node(Name, State#state.target_info),
+ R = test_server_node:stop_node(Name),
{reply, R, State};
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% handle_call({stop_node,Name}, _, State) -> ok | {error,Reason}
+%% handle_call({is_release_available,Name}, _, State) -> ok | {error,Reason}
%%
%% Tests if the release is available.
@@ -993,9 +981,7 @@ handle_cast({node_started,Node}, State) ->
%%
%% Handles exit messages from linked processes. Only test suites are
%% expected to be linked. When a test suite terminates, it is removed
-%% from the job queue. If a target client terminates it means that we
-%% lost contact with target. The test_server_ctrl process is
-%% terminated, and teminate/2 will do the cleanup
+%% from the job queue.
handle_info(report_idle, State) ->
Finish = State#state.finish,
@@ -1047,35 +1033,12 @@ handle_info({'EXIT',Pid,Reason}, State) ->
end
end;
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% handle_info({tcp,Sock,Bin}, State)
-%%
-%% Message from remote main target process
-%% Only valid message is 'job_proc_killed', which indicates
-%% that a process running a test suite was killed
-
-handle_info({tcp,_MainSock,<<1,Request/binary>>}, State) ->
- case binary_to_term(Request) of
- {job_proc_killed,Name,Reason} ->
- %% The only purpose of this is to inform the user about what
- %% happened on target.
- %% The local job proc will soon be killed by the closed socket or
- %% because the job is finished. Then the above clause ('EXIT') will
- %% handle the problem.
- io:format("Suite ~ts was killed on remote target with reason"
- " ~p\n", [Name,Reason]);
- _ ->
- ignore
- end,
- {noreply,State};
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% handle_info({tcp_closed,Sock}, State)
%%
%% A Socket was closed. This indicates that a node died.
%% This can be
-%% *Target node (if remote)
%% *Slave or peer node started by a test suite
%% *Trace controll node
@@ -1084,7 +1047,7 @@ handle_info({tcp_closed,Sock}, State=#state{trc=Sock}) ->
%%! Maybe print something???
{noreply,State#state{trc=false}};
handle_info({tcp_closed,Sock}, State) ->
- test_server_node:nodedown(Sock, State#state.target_info),
+ test_server_node:nodedown(Sock),
{noreply,State};
handle_info(_, State) ->
%% dummy; accept all, do nothing.
@@ -1095,7 +1058,7 @@ handle_info(_, State) ->
%% Reason = term()
%%
%% Cleans up when the test_server is terminating. Kills the running
-%% test suites (if any) and terminates the remote target (if is exists)
+%% test suites (if any) and any possible remainting slave node
terminate(_Reason, State) ->
case State#state.trc of
@@ -1103,7 +1066,7 @@ terminate(_Reason, State) ->
Sock -> test_server_node:stop_tracer_node(Sock)
end,
kill_all_jobs(State#state.jobs),
- test_server_node:stop(State#state.target_info),
+ test_server_node:kill_nodes(),
case lists:keysearch(sasl, 1, application:which_applications()) of
{value,_} ->
test_server_h:restore();
@@ -1220,7 +1183,7 @@ init_tester(Mod, Func, Args, Dir, Name, {_,_,MinLev}=Levels,
"<td>~.3fs</td><td><b>~ts</b></td><td>~w Ok, ~w Failed~ts of ~w</td></tr>\n"
"</tfoot>\n",
[Time,SuccessStr,OkN,FailedN,SkipStr,OkN+FailedN+SkippedN]),
- test_server_io:stop().
+ test_server_io:stop([major,html,unexpected_io]).
report_severe_error(Reason) ->
test_server_sup:framework_call(report, [severe_error,Reason]).
@@ -1625,7 +1588,7 @@ do_test_cases(TopCases, SkipCases,
print(major, "=started ~s",
[lists:flatten(timestamp_get(""))]),
- put(test_server_html_footer, Footer),
+ test_server_io:set_footer(Footer),
run_test_cases(TestSpec, Config, TimetrapData)
end;
@@ -2071,7 +2034,6 @@ do_add_end_per_suite_and_skip(LastMod, LastRef, Mod, FwMod) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% run_test_cases(TestSpec, Config, TimetrapData) -> exit(Result)
%%
-%% If remote target, a socket connection is established.
%% Runs the specified tests, then displays/logs the summary.
run_test_cases(TestSpec, Config, TimetrapData) ->
@@ -2137,8 +2099,7 @@ run_test_cases(TestSpec, Config, TimetrapData) ->
%% return a new configuration.
%%
%% {make,Ref,{Mod,Func,Args}} Mod:Func is a make function, and it is called
-%% with the given arguments. This function will *always* be called on the host
-%% - not on target.
+%% with the given arguments.
%%
%% {Mod,Case} This is a normal test case. Determine the correct
%% configuration, and insert {Mod,Case,Config} as head of the list,
@@ -3462,20 +3423,16 @@ handle_io_and_exits(Main, CurrPid, CaseNum, Mod, Func, Cases) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% run_test_case(Ref, Num, Mod, Func, Args, RunInit,
-%% Where, TimetrapData, Mode) -> RetVal
+%% TimetrapData, Mode) -> RetVal
%%
%% Creates the minor log file and inserts some test case specific headers
-%% and footers into the log files. If a remote target is used, the test
-%% suite (binary) and the content of data_dir is sent. Then the test case
-%% is executed and the result is printed to the log files (also info
-%% about lingering processes & slave nodes in the system is presented).
+%% and footers into the log files. Then the test case is executed and the
+%% result is printed to the log files (also info about lingering processes
+%% & slave nodes in the system is presented).
%%
%% RunInit decides if the per test case init is to be run (true for all
%% but conf cases).
%%
-%% Where specifies if the test case should run on target or on the host.
-%% (Note that 'make' test cases always run on host).
-%%
%% Mode specifies if the test case should be executed by a dedicated,
%% parallel, process rather than sequentially by the main process. If
%% the former, the new process is spawned and the dictionary of the main
@@ -4110,11 +4067,6 @@ do_format_exception(Reason={Error,Stack}) ->
%% DetectedFail = [{File,Line}]
%% ProcessesBefore = ProcessesAfter = integer()
%%
-%% Where indicates if the test should run on target or always on the host.
-%%
-%% If test is to be run on target, and target is remote the request is
-%% sent over socket to target, and test_server runs the case and sends the
-%% result back over the socket. Else test_server runs the case directly on host.
run_test_case_apply(CaseNum, Mod, Func, Args, Name, RunInit,
TimetrapData) ->
@@ -4351,8 +4303,7 @@ update_config(Config, []) ->
%% Cases is treated according to this table, then
%% FinMFA is placed in the BasicCaseList. InitMFA
%% and FinMFA are make/unmake functions. If InitMFA
-%% fails, Cases are not run. InitMFA and FinMFA are
-%% always run on the host - not on target.
+%% fails, Cases are not run.
%%
%% When a function is called, above, it means that the function is invoked
%% and the return is expected to be:
@@ -4702,7 +4653,7 @@ keep_name(Props) ->
(_) -> false end, Props).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% Target node handling functions %%
+%% Node handling functions %%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -5375,31 +5326,28 @@ uri_encode(File,Encoding) ->
Components = filename:split(File),
filename:join([uri_encode_comp(C,Encoding) || C <- Components]).
-uri_encode_comp("/",_) ->
- "/";
-uri_encode_comp(Chars,utf8) ->
- http_uri:encode(Chars);
-uri_encode_comp(Chars,latin1) ->
- do_uri_encode(Chars).
-
-%% Encode a file reference to a latin1 filename so it can be inserted
-%% in a utf8 encoded HTML file.
-%% This does the same as http_uri:encode/1, except it also encodes all
-%% characters >127 - i.e. latin1 but not ASCII.
-do_uri_encode([Char|Chars]) ->
- case Char>127 orelse sets:is_element(Char, reserved()) of
+%% Encode the reference to a "filename of the given encoding" so it
+%% can be inserted in a utf8 encoded HTML file.
+%% This does almost the same as http_uri:encode/1, except
+%% 1. it does not convert @, : and / (in order to preserve nodename and c:/)
+%% 2. if the file name is in latin1, it also encodes all
+%% characters >127 - i.e. latin1 but not ASCII.
+uri_encode_comp([Char|Chars],Encoding) ->
+ Reserved = sets:is_element(Char, reserved()),
+ case (Char>127 andalso Encoding==latin1) orelse Reserved of
true ->
- [ $% | http_util:integer_to_hexlist(Char)] ++ do_uri_encode(Chars);
+ [ $% | http_util:integer_to_hexlist(Char)] ++
+ uri_encode_comp(Chars,Encoding);
false ->
- [Char | do_uri_encode(Chars)]
+ [Char | uri_encode_comp(Chars,Encoding)]
end;
-do_uri_encode([]) ->
+uri_encode_comp([],_) ->
[].
%% Copied from http_uri.erl, but slightly modified
-%% (not converting @ and :)
+%% (not converting @, : and /)
reserved() ->
- sets:from_list([$;, $&, $=, $+, $,, $/, $?,
+ sets:from_list([$;, $&, $=, $+, $,, $?,
$#, $[, $], $<, $>, $\", ${, $}, $|,
$\\, $', $^, $%, $ ]).
diff --git a/lib/test_server/src/test_server_gl.erl b/lib/test_server/src/test_server_gl.erl
index 766a4537a2..1f7317c51d 100644
--- a/lib/test_server/src/test_server_gl.erl
+++ b/lib/test_server/src/test_server_gl.erl
@@ -166,7 +166,7 @@ handle_info({'DOWN',Ref,process,_,Reason}=D, #st{minor_monitor=Ref}=St) ->
Data = io_lib:format("=== WARNING === TC: ~w\n"
"Got down from minor Fd ~w: ~w\n\n",
[St#st.tc,St#st.minor,D]),
- test_server_io:print(xxxFrom, unexpected_io, Data)
+ test_server_io:print_unexpected(Data)
end,
{noreply,St#st{minor=none,minor_monitor=none}};
handle_info({permit_io,Pid}, #st{permit_io=P}=St) ->
@@ -197,7 +197,7 @@ handle_info({io_request,From,ReplyAs,Req}=IoReq, St) ->
From ! {io_reply,ReplyAs,ok}
catch
_:_ ->
- {io_reply,ReplyAs,{error,arguments}}
+ From ! {io_reply,ReplyAs,{error,arguments}}
end,
{noreply,St};
handle_info({structured_io,ClientPid,{Detail,Str}}, St) ->
diff --git a/lib/test_server/src/test_server_internal.hrl b/lib/test_server/src/test_server_internal.hrl
index 9a11182725..4e734a330b 100644
--- a/lib/test_server/src/test_server_internal.hrl
+++ b/lib/test_server/src/test_server_internal.hrl
@@ -21,8 +21,7 @@
-define(MAIN_PORT,3289).
-define(ACCEPT_TIMEOUT,20000).
-%% Target information generated by test_server:init_target_info/0 and
-%% test_server_ctrl:contact_main_target/2
+%% Target information generated by test_server:init_target_info/0
%% Once initiated, this information will never change!!
-record(target_info, {os_family, % atom(); win32 | unix
os_type, % result of os:type()
@@ -36,21 +35,16 @@
username, % string()
cookie, % string(); Cookie for target node
naming, % string(); "-name" | "-sname"
- master, % string(); Was used for OSE's master
+ master}). % string(); Was used for OSE's master
% node for main target and slave nodes.
% For other platforms the target node
% itself is master for slave nodes
- %% The following are only used for remote targets
- slave_targets=[]}).% list() of atom(); all available
- % targets for starting slavenodes
-
%% Temporary information generated by test_server_ctrl:read_parameters/X
%% This information is used when starting the main target, and for
%% initiating the #target_info record.
-record(par, {type,
target,
- slave_targets=[],
naming,
master,
cookie}).
diff --git a/lib/test_server/src/test_server_io.erl b/lib/test_server/src/test_server_io.erl
index 242c08f765..73d4468bda 100644
--- a/lib/test_server/src/test_server_io.erl
+++ b/lib/test_server/src/test_server_io.erl
@@ -29,8 +29,9 @@
%%
-module(test_server_io).
--export([start_link/0,stop/0,get_gl/1,set_fd/2,
- start_transaction/0,end_transaction/0,print_buffered/1,print/3,
+-export([start_link/0,stop/1,get_gl/1,set_fd/2,
+ start_transaction/0,end_transaction/0,
+ print_buffered/1,print/3,print_unexpected/1,
set_footer/1,set_job_name/1,set_gl_props/1]).
-export([init/1,handle_call/3,handle_info/2,terminate/2]).
@@ -54,10 +55,10 @@ start_link() ->
Other
end.
-stop() ->
+stop(FilesToClose) ->
OldGL = group_leader(),
group_leader(self(), self()),
- req(stop),
+ req({stop,FilesToClose}),
group_leader(OldGL, self()),
ok.
@@ -124,6 +125,14 @@ print(From, Tag, Msg) ->
print_buffered(Pid) ->
req({print_buffered,Pid}).
+%% print_unexpected(Msg)
+%% Msg = string or iolist
+%%
+%% Print the given string in the unexpected_io log.
+
+print_unexpected(Msg) ->
+ print(xxxFrom,unexpected_io,Msg).
+
%% set_footer(IoData)
%%
%% Set a footer for the file associated with the 'html' tag.
@@ -204,12 +213,21 @@ handle_call({set_job_name,Name}, _From, St) ->
handle_call({set_gl_props,Props}, _From, #st{shared_gl=Shared}=St) ->
test_server_gl:set_props(Shared, Props),
{reply,ok,St#st{gl_props=Props}};
-handle_call(stop, From, #st{shared_gl=SGL,gls=Gls0}=St0) ->
+handle_call({stop,FdTags}, From, #st{fds=Fds,shared_gl=SGL,gls=Gls0}=St0) ->
St = St0#st{gls=gb_sets:insert(SGL, Gls0),stopping=From},
gc(St),
%% Give the users of the surviving group leaders some
%% time to finish.
erlang:send_after(2000, self(), stop_group_leaders),
+ %% close open log files
+ lists:foreach(fun(Tag) ->
+ case gb_trees:lookup(Tag, Fds) of
+ none ->
+ ok;
+ {value,Fd} ->
+ file:close(Fd)
+ end
+ end, FdTags),
{noreply,St}.
handle_info({'EXIT',Pid,normal}, #st{gls=Gls0,stopping=From}=St) ->
diff --git a/lib/test_server/src/test_server_node.erl b/lib/test_server/src/test_server_node.erl
index 54a49b31ca..619fd463de 100644
--- a/lib/test_server/src/test_server_node.erl
+++ b/lib/test_server/src/test_server_node.erl
@@ -26,10 +26,9 @@
%% Test Controller interface
-export([is_release_available/1]).
--export([stop/1]).
-export([start_tracer_node/2,trace_nodes/2,stop_tracer_node/1]).
--export([start_node/5, stop_node/2]).
--export([kill_nodes/1, nodedown/2]).
+-export([start_node/5, stop_node/1]).
+-export([kill_nodes/0, nodedown/1]).
%% Internal export
-export([node_started/1,trc/1,handle_debug/4]).
@@ -57,23 +56,12 @@ is_release_available(Rel) ->
false
end.
-stop(TI) ->
- kill_nodes(TI).
-
-nodedown(Sock, TI) ->
+nodedown(Sock) ->
Match = #slave_info{name='$1',socket=Sock,client='$2',_='_'},
case ets:match(slave_tab,Match) of
- [[Node,Client]] -> % Slave node died
+ [[Node,_Client]] -> % Slave node died
gen_tcp:close(Sock),
ets:delete(slave_tab,Node),
- close_target_client(Client),
- HostAtom = test_server_sup:hostatom(Node),
- case lists:member(HostAtom,TI#target_info.slave_targets) of
- true ->
- put(test_server_free_targets,
- get(test_server_free_targets) ++ [HostAtom]);
- false -> ok
- end,
slave_died;
[] ->
ok
@@ -300,9 +288,11 @@ start_node(_SlaveName, _Type, _Options, _From, _TI) ->
%%
%% Peer nodes are always started on the same host as test_server_ctrl
-%% Socket communication is used in case target and controller is
-%% not the same node (target must not know the controller node
-%% via erlang distribution)
+%%
+%% (Socket communication is used since in early days the test target
+%% and the test server controller node could be on different hosts and
+%% the target could not know the controller node via erlang
+%% distribution)
%%
start_node_peer(SlaveName, OptList, From, TI) ->
SuppliedArgs = start_node_get_option_value(args, OptList, []),
@@ -403,8 +393,6 @@ do_start_node_slave(Host0, SlaveName, Args, Prog, Cleanup) ->
_ -> cast_to_list(Host0)
end,
Cmd = Prog ++ " " ++ Args,
- %% Can use slave.erl here because I'm both controller and target
- %% so I will ping the new node anyway
case slave:start(Host, SlaveName, Args, no_link, Prog) of
{ok,Nodename} ->
case Cleanup of
@@ -545,62 +533,37 @@ start_node_get_option_value(Key, List, Default) ->
%% stop_node(Name) -> ok | {error,Reason}
%%
%% Clean up - test_server will stop this node
-stop_node(Name, TI) ->
+stop_node(Name) ->
case ets:lookup(slave_tab,Name) of
- [#slave_info{client=Client}] ->
+ [#slave_info{}] ->
ets:delete(slave_tab,Name),
- HostAtom = test_server_sup:hostatom(Name),
- case lists:member(HostAtom,TI#target_info.slave_targets) of
- true ->
- put(test_server_free_targets,
- get(test_server_free_targets) ++ [HostAtom]);
- false -> ok
- end,
- close_target_client(Client),
ok;
[] ->
{error, not_a_slavenode}
end.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% kill_nodes(TI) -> ok
+%% kill_nodes() -> ok
%%
%% Brutally kill all slavenodes that were not stopped by test_server
-kill_nodes(TI) ->
+kill_nodes() ->
case ets:match_object(slave_tab,'_') of
[] -> [];
List ->
- lists:map(fun(SI) -> kill_node(SI,TI) end, List)
+ lists:map(fun(SI) -> kill_node(SI) end, List)
end.
-kill_node(SI,TI) ->
+kill_node(SI) ->
Name = SI#slave_info.name,
ets:delete(slave_tab,Name),
- HostAtom = test_server_sup:hostatom(Name),
- case lists:member(HostAtom,TI#target_info.slave_targets) of
- true ->
- put(test_server_free_targets,
- get(test_server_free_targets) ++ [HostAtom]);
- false -> ok
- end,
case SI#slave_info.socket of
undefined ->
catch rpc:call(Name,erlang,halt,[]);
Sock ->
gen_tcp:close(Sock)
end,
- close_target_client(SI#slave_info.client),
Name.
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% Platform specific code
-
-close_target_client(undefined) ->
- ok.
-
-
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%% cast_to_list(X) -> string()
%%% X = list() | atom() | void()
diff --git a/lib/test_server/src/ts_erl_config.erl b/lib/test_server/src/ts_erl_config.erl
index 73abe86e11..a0fab4e2d2 100644
--- a/lib/test_server/src/ts_erl_config.erl
+++ b/lib/test_server/src/ts_erl_config.erl
@@ -32,7 +32,7 @@ variables(Base0, OsType) ->
Base2 = get_app_vars(fun erl_interface/2, Base1, OsType),
Base3 = get_app_vars(fun ic/2, Base2, OsType),
Base4 = get_app_vars(fun jinterface/2, Base3, OsType),
- Base5 = dl_vars(Base4, OsType),
+ Base5 = dl_vars(Base4, Base3, OsType),
Base6 = emu_vars(Base5),
Base7 = get_app_vars(fun ssl/2, Base6, OsType),
Base8 = erts_lib(Base7, OsType),
@@ -60,7 +60,7 @@ get_app_vars(AppFun, Vars, OsType) ->
exit({unexpected_internal_error, Garbage})
end.
-dl_vars(Vars, _) ->
+dl_vars(Vars, Base3, OsType) ->
ShlibRules0 = ".SUFFIXES:\n" ++
".SUFFIXES: @dll@ @obj@ .c\n\n" ++
".c@dll@:\n" ++
@@ -68,7 +68,23 @@ dl_vars(Vars, _) ->
"\t@SHLIB_LD@ @CROSSLDFLAGS@ @SHLIB_LDFLAGS@ $(SHLIB_EXTRA_LDFLAGS) -o $@ $*@obj@ @SHLIB_LDLIBS@ $(SHLIB_EXTRA_LDLIBS)",
ShlibRules = ts_lib:subst(ShlibRules0, Vars),
- [{'SHLIB_RULES', ShlibRules}|Vars].
+ case get_app_vars2(fun jinterface/2, Base3, OsType) of
+ {App, not_found} ->
+ [{'SHLIB_RULES', ShlibRules}, {App, "not_found"}|Vars];
+ _ ->
+ [{'SHLIB_RULES', ShlibRules}|Vars]
+ end.
+get_app_vars2(AppFun, Vars, OsType) ->
+ case catch AppFun(Vars,OsType) of
+ Res when is_list(Res) ->
+ {jinterface, ok};
+ {cannot_find_app, App} ->
+ {App, not_found};
+ {'EXIT', Reason} ->
+ exit(Reason);
+ Garbage ->
+ exit({unexpected_internal_error, Garbage})
+ end.
erts_lib_name(multi_threaded, {win32, V}) ->
link_library("erts_MD" ++ case is_debug_build() of