Skip to content

Commit

Permalink
Fix bug in handling framework:end_tc timeouts
Browse files Browse the repository at this point in the history
  • Loading branch information
Peter Andersson authored and RaimoNiskanen committed Jun 9, 2010
1 parent e2698f9 commit 4ed3162
Show file tree
Hide file tree
Showing 3 changed files with 84 additions and 2 deletions.
17 changes: 15 additions & 2 deletions lib/common_test/test/ct_error_SUITE.erl
Expand Up @@ -89,7 +89,8 @@ cfg_error(Config) when is_list(Config) ->
Join(DataDir, "cfg_error_8_SUITE"),
Join(DataDir, "cfg_error_9_SUITE"),
Join(DataDir, "cfg_error_10_SUITE"),
Join(DataDir, "cfg_error_11_SUITE")
Join(DataDir, "cfg_error_11_SUITE"),
Join(DataDir, "cfg_error_12_SUITE")
],
{Opts,ERPid} = setup([{suite,Suites}], Config),
ok = ct_test_support:run(Opts, Config),
Expand Down Expand Up @@ -230,7 +231,7 @@ test_events(cfg_error) ->
[
{?eh,start_logging,{'DEF','RUNDIR'}},
{?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
{?eh,start_info,{11,11,36}},
{?eh,start_info,{12,12,39}},

{?eh,tc_start,{cfg_error_1_SUITE,init_per_suite}},
{?eh,tc_done,
Expand Down Expand Up @@ -563,6 +564,18 @@ test_events(cfg_error) ->
{?eh,test_stats,{13,3,{1,19}}},
{?eh,tc_start,{cfg_error_11_SUITE,end_per_suite}},
{?eh,tc_done,{cfg_error_11_SUITE,end_per_suite,ok}},
{?eh,tc_start,{cfg_error_12_SUITE,tc1}},
{?eh,tc_done,{cfg_error_12_SUITE,tc1,{failed,{timetrap_timeout,500}}}},
{?eh,test_stats,{13,4,{1,19}}},
{?eh,tc_start,{cfg_error_12_SUITE,tc2}},
{?eh,tc_done,{cfg_error_12_SUITE,tc2,
{failed,
{cfg_error_12_SUITE,end_per_testcase,
{timetrap_timeout,500}}}}},
{?eh,test_stats,{14,4,{1,19}}},
{?eh,tc_start,{cfg_error_12_SUITE,tc3}},
{?eh,tc_done,{cfg_error_12_SUITE,tc3,ok}},
{?eh,test_stats,{15,4,{1,19}}},

{?eh,test_done,{'DEF','STOP_TIME'}},
{?eh,stop_logging,[]}
Expand Down
@@ -0,0 +1,68 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
%% compliance with the License. You should have received a copy of the
%% Erlang Public License along with this software. If not, it can be
%% retrieved online at http://www.erlang.org/.
%%
%% Software distributed under the License is distributed on an "AS IS"
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
%% the License for the specific language governing rights and limitations
%% under the License.
%%
%% %CopyrightEnd%
%%
-module(cfg_error_12_SUITE).

-compile(export_all).

-include_lib("common_test/include/ct.hrl").

end_per_testcase(tc2, _Config) ->
timer:sleep(2000),
exit(this_should_not_be_printed);
end_per_testcase(_, _) ->
ok.

all() ->
[tc1, tc2, tc3].

%%%-----------------------------------------------------------------
tc1() ->
put('$test_server_framework_test',
fun(init_tc, _Default) ->
ct:pal("init_tc(~p): Night time...",[self()]),
timer:sleep(2000),
ct:pal("init_tc(~p): Day time!",[self()]),
exit(this_should_not_be_printed);
(_, Default) -> Default
end),
[{timetrap,500}].

tc1(_) ->
exit(this_should_not_be_printed).

%%%-----------------------------------------------------------------
tc2() ->
[{timetrap,500}].

tc2(_) ->
ok.

%%%-----------------------------------------------------------------
tc3() ->
[{timetrap,500}].

tc3(_) ->
put('$test_server_framework_test',
fun(end_tc, _Default) ->
ct:pal("end_tc(~p): Night time...",[self()]),
timer:sleep(1000),
ct:pal("end_tc(~p): Day time!",[self()]);
(_, Default) -> Default
end),
{comment,"should succeed since ct_fw cancels timetrap in end_tc"}.
1 change: 1 addition & 0 deletions lib/test_server/src/test_server.erl
Expand Up @@ -1126,6 +1126,7 @@ run_test_case_eval1(Mod, Func, Args, Name, RunInit, TCCallback) ->
_ ->
{FWReturn,TSReturn,EndConf1}
end,
put(test_server_init_or_end_conf,undefined),
case test_server_sup:framework_call(end_tc, [?pl2a(Mod), Func,
{FWReturn1,[EndConf2]}]) of
{fail,Reason} ->
Expand Down

0 comments on commit 4ed3162

Please sign in to comment.