File 4261-common_test-remove-undocumented-tracer-node-feature.patch of Package erlang

From d5aaefea0571a6dc724e2a96e5e6c1bab346925c Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <maximfca@gmail.com>
Date: Fri, 2 Jul 2021 07:31:47 -0700
Subject: [PATCH] common_test: remove undocumented 'tracer node' feature

Tracer node is one more implementation of "slave" node. It is not
documented and likely to be unused.
---
 lib/common_test/src/test_server_ctrl.erl | 122 +++---------
 lib/common_test/src/test_server_node.erl | 231 +----------------------
 2 files changed, 30 insertions(+), 323 deletions(-)

diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl
index 49ea24cc2e..bf53e1287f 100644
--- a/lib/common_test/src/test_server_ctrl.erl
+++ b/lib/common_test/src/test_server_ctrl.erl
@@ -54,8 +54,7 @@
 -export([multiply_timetraps/1, scale_timetraps/1, get_timetrap_parameters/0]).
 -export([create_priv_dir/1]).
 -export([cover/1, cover/2, cover/3,
-	 cover_compile/7, cover_analyse/2, cross_cover_analyse/2,
-	 trc/1, stop_trace/0]).
+	 cover_compile/7, cover_analyse/2, cross_cover_analyse/2]).
 -export([testcase_callback/1]).
 -export([set_random_seed/1]).
 -export([kill_slavenodes/0]).
@@ -115,7 +114,7 @@
 -record(state,{jobs=[], levels={1,19,10}, reject_io_reqs=false,
 	       multiply_timetraps=1, scale_timetraps=true,
 	       create_priv_dir=auto_per_run, finish=false,
-	       target_info, trc=false, cover=false, wait_for_node=[],
+	       target_info, cover=false, wait_for_node=[],
 	       testcase_callback=undefined, idle_notify=[],
 	       get_totals=false, random_seed=undefined}).
 
@@ -224,55 +223,53 @@ add_tests_with_skip(LogDir, Tests, Skip) ->
 %% COMMAND LINE INTERFACE
 
 parse_cmd_line(Cmds) ->
-    parse_cmd_line(Cmds, [], [], local, false, false, undefined).
+    parse_cmd_line(Cmds, [], [], local, false, undefined).
 
-parse_cmd_line(['SPEC',Spec|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+parse_cmd_line(['SPEC',Spec|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     case file:consult(Spec) of
 	{ok, TermList} ->
 	    Name = filename:rootname(Spec),
 	    parse_cmd_line(Cmds, TermList++SpecList, [Name|Names], Param,
-			   Trc, Cov, TCCB);
+			   Cov, TCCB);
 	{error,Reason} ->
 	    io:format("Can't open ~tw: ~tp\n",[Spec, file:format_error(Reason)]),
-	    parse_cmd_line(Cmds, SpecList, Names, Param, Trc, Cov, TCCB)
+	    parse_cmd_line(Cmds, SpecList, Names, Param, Cov, TCCB)
     end;
-parse_cmd_line(['NAME',Name|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+parse_cmd_line(['NAME',Name|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     parse_cmd_line(Cmds, SpecList, [{name,atom_to_list(Name)}|Names],
-		   Param, Trc, Cov, TCCB);
-parse_cmd_line(['SKIPMOD',Mod|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['SKIPMOD',Mod|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     parse_cmd_line(Cmds, [{skip,{Mod,"by command line"}}|SpecList], Names,
-		   Param, Trc, Cov, TCCB);
-parse_cmd_line(['SKIPCASE',Mod,Case|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['SKIPCASE',Mod,Case|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     parse_cmd_line(Cmds, [{skip,{Mod,Case,"by command line"}}|SpecList], Names,
-		   Param, Trc, Cov, TCCB);
-parse_cmd_line(['DIR',Dir|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['DIR',Dir|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     Name = filename:basename(Dir),
     parse_cmd_line(Cmds, [{topcase,{dir,Name}}|SpecList], [Name|Names],
-		   Param, Trc, Cov, TCCB);
-parse_cmd_line(['MODULE',Mod|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['MODULE',Mod|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     parse_cmd_line(Cmds,[{topcase,{Mod,all}}|SpecList],[atom_to_list(Mod)|Names],
-		   Param, Trc, Cov, TCCB);
-parse_cmd_line(['CASE',Mod,Case|Cmds], SpecList, Names, Param, Trc, Cov, TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['CASE',Mod,Case|Cmds], SpecList, Names, Param, Cov, TCCB) ->
     parse_cmd_line(Cmds,[{topcase,{Mod,Case}}|SpecList],[atom_to_list(Mod)|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) ->
-    parse_cmd_line(Cmds, SpecList, Names, Param, Trc, {{App,CF}, Analyse}, TCCB);
-parse_cmd_line(['TESTCASE_CALLBACK',Mod,Func|Cmds], SpecList, Names, Param, Trc, Cov, _) ->
-    parse_cmd_line(Cmds, SpecList, Names, Param, Trc, Cov, {Mod,Func});
-parse_cmd_line([Obj|_Cmds], _SpecList, _Names, _Param, _Trc, _Cov, _TCCB) ->
+		   Param, Cov, TCCB);
+parse_cmd_line(['COVER',App,CF,Analyse|Cmds], SpecList, Names, Param, _Cov, TCCB) ->
+    parse_cmd_line(Cmds, SpecList, Names, Param, {{App,CF}, Analyse}, TCCB);
+parse_cmd_line(['TESTCASE_CALLBACK',Mod,Func|Cmds], SpecList, Names, Param, Cov, _) ->
+    parse_cmd_line(Cmds, SpecList, Names, Param, Cov, {Mod,Func});
+parse_cmd_line([Obj|_Cmds], _SpecList, _Names, _Param, __Cov, _TCCB) ->
     io:format("~w: Bad argument: ~tw\n", [?MODULE,Obj]),
     io:format(" Use the `ts' module to start tests.\n", []),
     io:format(" (If you ARE using `ts', there is a bug in `ts'.)\n", []),
     halt(1);
-parse_cmd_line([], SpecList, Names, Param, Trc, Cov, TCCB) ->
+parse_cmd_line([], SpecList, Names, Param, Cov, TCCB) ->
     NameList = lists:reverse(Names, ["suite"]),
     Name = case lists:keysearch(name, 1, NameList) of
 	       {value,{name,N}} -> N;
 	       false -> hd(NameList)
 	   end,
-    {lists:reverse(SpecList), Name, Param, Trc, Cov, TCCB}.
+    {lists:reverse(SpecList), Name, Param, Cov, TCCB}.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% cast_to_list(X) -> string()
@@ -311,12 +308,8 @@ start_link() ->
 
 run_test(CommandLine) ->
     process_flag(trap_exit,true),
-    {SpecList,Name,Param,Trc,Cov,TCCB} = parse_cmd_line(CommandLine),
+    {SpecList,Name,Param,Cov,TCCB} = parse_cmd_line(CommandLine),
     {ok,_TSPid} = start_link(Param),
-    case Trc of
-	false -> ok;
-	File -> trc(File)
-    end,
     case Cov of
 	false -> ok;
 	{{App,CoverFile},Analyse} -> cover(App, maybe_file(CoverFile), Analyse)
@@ -399,12 +392,6 @@ get_timetrap_parameters() ->
 create_priv_dir(Value) ->
     controller_call({create_priv_dir,Value}).
 
-trc(TraceFile) ->
-    controller_call({trace,TraceFile}, 2*?ACCEPT_TIMEOUT).
-
-stop_trace() ->
-    controller_call(stop_trace).
-
 node_started(Node) ->
     gen_server:cast(?MODULE, {node_started,Node}).
 
@@ -795,45 +782,6 @@ handle_call({scale_timetraps,Bool}, _From, State) ->
 handle_call(get_timetrap_parameters, _From, State) ->
     {reply,{State#state.multiply_timetraps,State#state.scale_timetraps},State};
 
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% handle_call({trace,TraceFile}, _, State) -> ok | {error,Reason}
-%%
-%% Starts a separate node (trace control node) which
-%% starts tracing on target and all slave nodes
-%%
-%% TraceFile is a text file with elements of type
-%% {Trace,Mod,TracePattern}.
-%% {Trace,Mod,Func,TracePattern}.
-%% {Trace,Mod,Func,Arity,TracePattern}.
-%%
-%% Trace = tp | tpl;  local or global call trace
-%% Mod,Func = atom(), Arity=integer(); defines what to trace
-%% TracePattern = [] | match_spec()
-%%
-%% The 'call' trace flag is set on all processes, and then
-%% the given trace patterns are set.
-
-handle_call({trace,TraceFile}, _From, State=#state{trc=false}) ->
-    TI = State#state.target_info,
-    case test_server_node:start_tracer_node(TraceFile, TI) of
-	{ok,Tracer} -> {reply,ok,State#state{trc=Tracer}};
-	Error -> {reply,Error,State}
-    end;
-handle_call({trace,_TraceFile}, _From, State) ->
-    {reply,{error,already_tracing},State};
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% handle_call(stop_trace, _, State) -> ok | {error,Reason}
-%%
-%% Stops tracing on target and all slave nodes and
-%% terminates trace control node
-
-handle_call(stop_trace, _From, State=#state{trc=false}) ->
-    {reply,{error,not_tracing},State};
-handle_call(stop_trace, _From, State) ->
-    R = test_server_node:stop_tracer_node(State#state.trc),
-    {reply,R,State#state{trc=false}};
-
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% handle_call({cover,CoverInfo}, _, State) -> ok | {error,Reason}
 %%
@@ -987,10 +935,6 @@ set_hosts(Hosts) ->
 %% Called by test_server_node when a slave/peer node is fully started.
 
 handle_cast({node_started,Node}, State) ->
-    case State#state.trc of
-	false -> ok;
-	Trc -> test_server_node:trace_nodes(Trc, [Node])
-    end,
     NewWaitList =
 	case lists:keysearch(Node,1,State#state.wait_for_node) of
 	    {value,{Node,From}} ->
@@ -1065,14 +1009,8 @@ handle_info({'EXIT',Pid,Reason}, State) ->
 %% handle_info({tcp_closed,Sock}, State)
 %%
 %% A Socket was closed. This indicates that a node died.
-%% This can be
-%% *Slave or peer node started by a test suite
-%% *Trace controll node
-
-handle_info({tcp_closed,Sock}, State=#state{trc=Sock}) ->
-    %% Tracer node died - can't really do anything
-    %%! Maybe print something???
-    {noreply,State#state{trc=false}};
+%% This can be a slave or peer node started by a test suite
+
 handle_info({tcp_closed,Sock}, State) ->
     test_server_node:nodedown(Sock),
     {noreply,State};
@@ -1089,10 +1027,6 @@ handle_info(_, State) ->
 
 terminate(_Reason, State) ->
     test_server_sup:util_stop(),
-    case State#state.trc of
-	false -> ok;
-	Sock -> test_server_node:stop_tracer_node(Sock)
-    end,
     ok = kill_all_jobs(State#state.jobs),
     _ = test_server_node:kill_nodes(),
     ok.
diff --git a/lib/common_test/src/test_server_node.erl b/lib/common_test/src/test_server_node.erl
index 052824b4bd..349402fcca 100644
--- a/lib/common_test/src/test_server_node.erl
+++ b/lib/common_test/src/test_server_node.erl
@@ -22,11 +22,10 @@
 
 %% Test Controller interface
 -export([is_release_available/1, find_release/1]).
--export([start_tracer_node/2,trace_nodes/2,stop_tracer_node/1]).
 -export([start_node/5, stop_node/1]).
 -export([kill_nodes/0, nodedown/1]).
 %% Internal export
--export([node_started/1,trc/1,handle_debug/4]).
+-export([node_started/1]).
 
 -include("test_server_internal.hrl").
 -record(slave_info, {name,socket,client}).
@@ -34,7 +33,7 @@
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%%                                                                  %%%
 %%% All code in this module executes on the test_server_ctrl process %%%
-%%% except for node_started/1 and trc/1 which execute on a new node. %%%
+%%% except for node_started/1  which execute on a new node.          %%%
 %%%                                                                  %%%
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
@@ -67,212 +67,6 @@ nodedown(Sock) ->
 	    ok
     end.
 
-
-
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% Start trace node
-%%%
-start_tracer_node(TraceFile,TI) ->
-    Match = #slave_info{name='$1',_='_'},
-    SlaveNodes = lists:map(fun([N]) -> [" ",N] end,
-			   ets:match(slave_tab,Match)),
-    TargetNode = node(),
-    Cookie = TI#target_info.cookie,
-    {ok,LSock} = gen_tcp:listen(0,[binary,{reuseaddr,true},{packet,2}]),
-    {ok,TracePort} = inet:port(LSock),
-    {false, Prog0} = pick_erl_program(default),
-    Prog = quote_progname(Prog0),
-    Cmd = lists:concat([Prog, " -sname tracer -hidden -setcookie ", Cookie, 
-			" -s ", ?MODULE, " trc ", TraceFile, " ", 
-			TracePort, " ", TI#target_info.os_family]),
-    spawn(fun() -> print_data(open_port({spawn,Cmd},[stream])) end),
-%!    open_port({spawn,Cmd},[stream]),
-    case gen_tcp:accept(LSock,?ACCEPT_TIMEOUT) of
-	{ok,Sock} -> 
-	    gen_tcp:close(LSock),
-	    receive 
-		{tcp,Sock,Result} when is_binary(Result) ->
-		    case unpack(Result) of
-			error ->
-			    gen_tcp:close(Sock),
-			    {error,timeout};
-			{ok,started} ->
-			    trace_nodes(Sock,[TargetNode | SlaveNodes]),
-			    {ok,Sock};
-			{ok,Error} -> Error
-		    end;
-		{tcp_closed,Sock} ->
-		    gen_tcp:close(Sock),
-		    {error,could_not_start_tracernode}
-	    after ?ACCEPT_TIMEOUT ->
-		    gen_tcp:close(Sock),
-		    {error,timeout}
-	    end;
-	Error -> 
-	    gen_tcp:close(LSock),
-	    {error,{could_not_start_tracernode,Error}}
-    end.
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% Start a tracer on each of these nodes and set flags and patterns
-%%%
-trace_nodes(Sock,Nodes) ->
-    Bin = term_to_binary({add_nodes,Nodes}),
-    ok = gen_tcp:send(Sock, tag_trace_message(Bin)),
-    receive_ack(Sock).
-
-
-receive_ack(Sock) ->
-    receive
-	{tcp,Sock,Bin} when is_binary(Bin) ->
-	    case unpack(Bin) of
-		error -> receive_ack(Sock);
-		{ok,_} -> ok
-	    end;
-	_ ->
-	    receive_ack(Sock)
-    end.
-    
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%% Stop trace node
-%%%
-stop_tracer_node(Sock) ->
-    Bin = term_to_binary(id(stop)),
-    ok = gen_tcp:send(Sock, tag_trace_message(Bin)),
-    receive {tcp_closed,Sock} -> gen_tcp:close(Sock) end,
-    ok.
-    
-
-
-
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%% trc([TraceFile,Nodes]) -> ok
-%%
-%% Start tracing on the given nodes
-%%
-%% This function executes on the new node
-%%
-trc([TraceFile, PortAtom, Type]) ->
-    {Result,Patterns} = 
-	case file:consult(TraceFile) of
-	    {ok,TI} ->
-		Pat = parse_trace_info(lists:flatten(TI)),
-		{started,Pat};
-	    Error ->
-		{Error,[]}
-	end,
-    Port = list_to_integer(atom_to_list(PortAtom)),
-    case catch gen_tcp:connect("localhost", Port, [binary, 
-						   {reuseaddr,true}, 
-						   {packet,2}]) of
-	{ok,Sock} -> 
-	    BinResult = term_to_binary(Result),
-	    ok = gen_tcp:send(Sock,tag_trace_message(BinResult)),
-	    trc_loop(Sock,Patterns,Type);
-	_else ->
-	    ok
-    end,
-    erlang:halt().
-trc_loop(Sock,Patterns,Type) ->
-    receive
-	{tcp,Sock,Bin} ->
-	    case unpack(Bin) of
-		error ->
-		    ttb:stop(),
-		    gen_tcp:close(Sock);
-		{ok,{add_nodes,Nodes}} -> 
-		    add_nodes(Nodes,Patterns,Type),
-		    Bin = term_to_binary(id(ok)),
-		    ok = gen_tcp:send(Sock, tag_trace_message(Bin)),
-		    trc_loop(Sock,Patterns,Type);
-		{ok,stop} -> 
-		    ttb:stop(),
-		    gen_tcp:close(Sock)
-	    end;
-	{tcp_closed,Sock} ->
-	    ttb:stop(),
-	    gen_tcp:close(Sock)
-    end.
-add_nodes(Nodes,Patterns,_Type) ->
-    {ok, _} = ttb:tracer(Nodes,[{file,{local, test_server}},
-			        {handler, {{?MODULE,handle_debug},initial}}]),
-    {ok, _} = ttb:p(all,[call,timestamp]),
-    lists:foreach(fun({TP,M,F,A,Pat}) -> ttb:TP(M,F,A,Pat);
-		     ({CTP,M,F,A}) -> ttb:CTP(M,F,A) 
-		  end,
-		  Patterns).
-
-parse_trace_info([{TP,M,Pat}|Pats]) when TP=:=tp; TP=:=tpl ->
-    [{TP,M,'_','_',Pat}|parse_trace_info(Pats)];
-parse_trace_info([{TP,M,F,Pat}|Pats]) when TP=:=tp; TP=:=tpl ->
-    [{TP,M,F,'_',Pat}|parse_trace_info(Pats)];
-parse_trace_info([{TP,M,F,A,Pat}|Pats]) when TP=:=tp; TP=:=tpl ->
-    [{TP,M,F,A,Pat}|parse_trace_info(Pats)];
-parse_trace_info([CTP|Pats]) when CTP=:=ctp; CTP=:=ctpl; CTP=:=ctpg ->
-    [{CTP,'_','_','_'}|parse_trace_info(Pats)];
-parse_trace_info([{CTP,M}|Pats]) when CTP=:=ctp; CTP=:=ctpl; CTP=:=ctpg ->
-    [{CTP,M,'_','_'}|parse_trace_info(Pats)];
-parse_trace_info([{CTP,M,F}|Pats]) when CTP=:=ctp; CTP=:=ctpl; CTP=:=ctpg ->
-    [{CTP,M,F,'_'}|parse_trace_info(Pats)];
-parse_trace_info([{CTP,M,F,A}|Pats]) when CTP=:=ctp; CTP=:=ctpl; CTP=:=ctpg ->
-    [{CTP,M,F,A}|parse_trace_info(Pats)];
-parse_trace_info([]) ->
-    [];
-parse_trace_info([_other|Pats]) -> % ignore
-    parse_trace_info(Pats).
-
-handle_debug(Out,Trace,TI,initial) ->
-    handle_debug(Out,Trace,TI,0);
-handle_debug(_Out,end_of_trace,_TI,N) ->
-    N;
-handle_debug(Out,Trace,_TI,N) ->
-    print_trc(Out,Trace,N),
-    N+1.
-
-print_trc(Out,{trace_ts,P,call,{M,F,A},C,Ts},N) ->
-    io:format(Out,
-	      "~w: ~s~n"
-	      "Process   : ~w~n"
-	      "Call      : ~w:~tw/~w~n"
-	      "Arguments : ~tp~n"
-	      "Caller    : ~tw~n~n",
-	      [N,ts(Ts),P,M,F,length(A),A,C]);
-print_trc(Out,{trace_ts,P,call,{M,F,A},Ts},N) ->
-    io:format(Out,
-	      "~w: ~s~n"
-	      "Process   : ~w~n"
-	      "Call      : ~w:~tw/~w~n"
-	      "Arguments : ~tp~n~n",
-	      [N,ts(Ts),P,M,F,length(A),A]);
-print_trc(Out,{trace_ts,P,return_from,{M,F,A},R,Ts},N) ->
-    io:format(Out,
-	      "~w: ~s~n"
-	      "Process      : ~w~n"
-	      "Return from  : ~w:~tw/~w~n"
-	      "Return value : ~tp~n~n",
-	      [N,ts(Ts),P,M,F,A,R]);
-print_trc(Out,{drop,X},N) ->
-    io:format(Out,
-	      "~w: Tracer dropped ~w messages - too busy~n~n",
-	      [N,X]);
-print_trc(Out,Trace,N) ->
-    Ts = element(size(Trace),Trace),
-    io:format(Out,
-	      "~w: ~s~n"
-	      "Trace        : ~tp~n~n",
-	      [N,ts(Ts),Trace]).
-ts({_, _, Micro} = Now) ->
-    {{Y,M,D},{H,Min,S}} = calendar:now_to_local_time(Now),
-    io_lib:format("~4.4.0w-~2.2.0w-~2.2.0w ~2.2.0w:~2.2.0w:~2.2.0w,~6.6.0w",
-		  [Y,M,D,H,Min,S,Micro]).
-
-
-
-
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%% Start slave/peer nodes (initiated by test_server:start_node/5)
 %%%
@@ -878,24 +672,3 @@ unpack(Bin) ->
 	_ -> error
     end.
 
-id(I) -> I.
-   
-print_data(Port) ->
-    ct_util:mark_process(),
-    receive
-	{Port, {data, Bytes}} ->
-	    io:put_chars(Bytes),
-	    print_data(Port);
-	{Port, eof} ->
-	    Port ! {self(), close}, 
-	    receive
-		{Port, closed} ->
-		    true
-	    end, 
-	    receive
-		{'EXIT',  Port,  _} -> 
-		    ok
-	    after 1 ->				% force context switch
-		    ok
-	    end
-    end.
-- 
2.31.1

openSUSE Build Service is sponsored by