Skip to content

Commit

Permalink
Make absolute paths in log files relative
Browse files Browse the repository at this point in the history
  • Loading branch information
Peter Andersson committed Nov 18, 2011
1 parent 196a453 commit fd55862
Show file tree
Hide file tree
Showing 5 changed files with 77 additions and 30 deletions.
8 changes: 4 additions & 4 deletions lib/common_test/src/ct_framework.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@
-export([init_tc/3, end_tc/3, end_tc/4, get_suite/2, get_all_cases/1]).
-export([report/2, warn/1, error_notification/4]).

-export([get_logopts/0, format_comment/1, get_html_wrapper/2]).
-export([get_logopts/0, format_comment/1, get_html_wrapper/3]).

-export([error_in_suite/1, ct_init_per_group/2, ct_end_per_group/2]).

Expand Down Expand Up @@ -1411,6 +1411,6 @@ format_comment(Comment) ->
"<font color=\"green\">" ++ Comment ++ "</font>".

%%%-----------------------------------------------------------------
%%% @spec get_html_wrapper(TestName, PrintLabel) -> Header
get_html_wrapper(TestName, PrintLabel) ->
ct_logs:get_ts_html_wrapper(TestName, PrintLabel).
%%% @spec get_html_wrapper(TestName, PrintLabel, Cwd) -> Header
get_html_wrapper(TestName, PrintLabel, Cwd) ->
ct_logs:get_ts_html_wrapper(TestName, PrintLabel, Cwd).
62 changes: 52 additions & 10 deletions lib/common_test/src/ct_logs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@
-export([add_external_logs/1,add_link/3]).
-export([make_last_run_index/0]).
-export([make_all_suites_index/1,make_all_runs_index/1]).
-export([get_ts_html_wrapper/2]).
-export([get_ts_html_wrapper/3]).

%% Logging stuff directly from testcase
-export([tc_log/3,tc_print/3,tc_pal/3,ct_log/3,
Expand Down Expand Up @@ -213,6 +213,7 @@ cast(Msg) ->
%%% <p>This function is called by ct_framework:init_tc/3</p>
init_tc(RefreshLog) ->
call({init_tc,self(),group_leader(),RefreshLog}),
io:format(xhtml("", "<br />")),
ok.

%%%-----------------------------------------------------------------
Expand All @@ -222,6 +223,7 @@ init_tc(RefreshLog) ->
%%%
%%% <p>This function is called by ct_framework:end_tc/3</p>
end_tc(TCPid) ->
io:format(xhtml("<br>", "<br />")),
%% use call here so that the TC process will wait and receive
%% possible exit signals from ct_logs before end_tc returns ok
call({end_tc,TCPid}).
Expand Down Expand Up @@ -1159,7 +1161,8 @@ header1(Title, SubTitle) ->
xhtml("</center>\n<br>\n", "</center>\n<br />\n")];
true -> xhtml("<br>\n", "<br />\n")
end,
CSSFile = locate_default_css_file(),
CSSFile = xhtml(fun() -> "" end,
fun() -> make_relative(locate_default_css_file()) end),
[xhtml(["<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 3.2 Final//EN\">\n",
"<html>\n"],
["<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Transitional//EN\"\n",
Expand All @@ -1170,7 +1173,7 @@ header1(Title, SubTitle) ->
"<title>" ++ Title ++ " " ++ SubTitle ++ "</title>\n",
"<meta http-equiv=\"cache-control\" content=\"no-cache\">\n",
xhtml("",
["<link rel=\"stylesheet\" href=\"file:///",CSSFile,"\" type=\"text/css\">"]),
["<link rel=\"stylesheet\" href=\"",CSSFile,"\" type=\"text/css\">"]),
"</head>\n",
body_tag(),
"<center>\n",
Expand Down Expand Up @@ -1953,10 +1956,16 @@ last_test([], Latest) ->
%%%
%%% @doc
%%%
xhtml(HTML, XHTML) when is_function(HTML),
is_function(XHTML) ->
case get(basic_html) of
true -> HTML();
_ -> XHTML()
end;
xhtml(HTML, XHTML) ->
case get(basic_html) of
true -> HTML;
_ -> XHTML
_ -> XHTML
end.

%%%-----------------------------------------------------------------
Expand Down Expand Up @@ -2020,11 +2029,41 @@ locate_default_css_file() ->
end.

%%%-----------------------------------------------------------------
%%% @spec get_ts_html_wrapper(TestName, PrintLabel) -> {Mode,Header,Footer}
%%% @spec make_relative(AbsDir, Cwd) -> RelDir
%%%
%%% @doc Return directory path to File (last element of AbsDir), which
%%% is the path relative to Cwd. Examples when Cwd == "/ldisk/test/logs":
%%% make_relative("/ldisk/test/logs/run/trace.log") -> "run/trace.log"
%%% make_relative("/ldisk/test/trace.log") -> "../trace.log"
%%% make_relative("/ldisk/test/logs/trace.log") -> "trace.log"
make_relative(AbsDir) ->
{ok,Cwd} = file:get_cwd(),
make_relative(AbsDir, Cwd).

make_relative(AbsDir, Cwd) ->
DirTokens = filename:split(AbsDir),
CwdTokens = filename:split(Cwd),
filename:join(make_relative1(DirTokens, CwdTokens)).

make_relative1([T | DirTs], [T | CwdTs]) ->
make_relative1(DirTs, CwdTs);
make_relative1(Last = [_File], []) ->
Last;
make_relative1(Last = [_File], CwdTs) ->
Ups = ["../" || _ <- CwdTs],
Ups ++ Last;
make_relative1(DirTs, []) ->
DirTs;
make_relative1(DirTs, CwdTs) ->
Ups = ["../" || _ <- CwdTs],
Ups ++ DirTs.

%%%-----------------------------------------------------------------
%%% @spec get_ts_html_wrapper(TestName, PrintLabel, Cwd) -> {Mode,Header,Footer}
%%%
%%% @doc
%%%
get_ts_html_wrapper(TestName, PrintLabel) ->
get_ts_html_wrapper(TestName, PrintLabel, Cwd) ->
TestName1 = if is_list(TestName) ->
lists:flatten(TestName);
true ->
Expand All @@ -2046,8 +2085,10 @@ get_ts_html_wrapper(TestName, PrintLabel) ->
end,
CTPath = code:lib_dir(common_test),
{ok,CtLogdir} = get_log_dir(true),
AllRuns = filename:join(filename:dirname(CtLogdir), ?all_runs_name),
TestIndex = filename:join(filename:dirname(CtLogdir), ?index_name),
AllRuns = make_relative(filename:join(filename:dirname(CtLogdir),
?all_runs_name), Cwd),
TestIndex = make_relative(filename:join(filename:dirname(CtLogdir),
?index_name), Cwd),
case Basic of
true ->
TileFile = filename:join(filename:join(CTPath,"priv"),"tile1.jpg"),
Expand Down Expand Up @@ -2082,14 +2123,15 @@ get_ts_html_wrapper(TestName, PrintLabel) ->
"Open Telecom Platform</a><br />\n",
"Updated: <!date>", current_time(), "<!/date>",
"<br />\n</div>\n"],
CSSFile = locate_default_css_file(),
CSSFile = xhtml(fun() -> "" end,
fun() -> make_relative(locate_default_css_file(), Cwd) end),
{xhtml,
["<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Transitional//EN\"\n",
"\"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd\">\n",
"<html xmlns=\"http://www.w3.org/1999/xhtml\" xml:lang=\"en\" lang=\"en\">\n",
"<head>\n<title>", TestName1, "</title>\n",
"<meta http-equiv=\"cache-control\" content=\"no-cache\">\n",
"<link rel=\"stylesheet\" href=\"file:///", CSSFile, "\" type=\"text/css\">",
"<link rel=\"stylesheet\" href=\"", CSSFile, "\" type=\"text/css\">",
"</head>\n","<body>\n",
LabelStr, "\n"],
["<center>\n<br /><hr /><p>\n",
Expand Down
2 changes: 1 addition & 1 deletion lib/test_server/src/erl2html2.erl
Original file line number Diff line number Diff line change
Expand Up @@ -175,7 +175,7 @@ linenum(Line) ->
end,
[A,Pred,integer_to_list(Line),":"].

footer(Lines) ->
footer(_Lines) ->
"".
%% {_, Time} = statistics(runtime),
%% io:format("Converted ~p lines in ~.2f Seconds.~n",
Expand Down
2 changes: 1 addition & 1 deletion lib/test_server/src/test_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -611,7 +611,7 @@ do_run_test_case_apply(Mod, Func, Args, Name, RunInit, TimetrapData) ->
print(minor, "Test case started with:\n~s:~s(~p)\n", [Mod,Func,Args2Print]),
print(minor, "Current directory is ~p\n", [Cwd]),
print_timestamp(minor,"Started at "),
print(minor, "\n", []),
print(minor, "", []),
TCCallback = get(test_server_testcase_callback),
LogOpts = get(test_server_logopts),
Ref = make_ref(),
Expand Down
33 changes: 19 additions & 14 deletions lib/test_server/src/test_server_ctrl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -214,6 +214,9 @@
X == auto_skip -> skipped;
true -> X end).

-define(auto_skip_color, "#FFA64D").
-define(user_skip_color, "#FF8000").

-record(state,{jobs=[],levels={1,19,10},
multiply_timetraps=1,scale_timetraps=true,
finish=false,
Expand Down Expand Up @@ -1668,7 +1671,7 @@ do_test_cases(TopCases, SkipCases,
do_test_cases(TopCases, SkipCases,
Config, TimetrapData) when is_list(TopCases),
is_tuple(TimetrapData) ->
start_log_file(),
{ok,TestDir} = start_log_file(),
FwMod =
case os:getenv("TEST_SERVER_FRAMEWORK") of
FW when FW =:= false; FW =:= "undefined" -> ?MODULE;
Expand Down Expand Up @@ -1700,10 +1703,9 @@ do_test_cases(TopCases, SkipCases,
TestDescr = "Test " ++ TestName ++ " results",

test_server_sup:framework_call(report, [tests_start,{Test,N}]),

{Header,Footer} =
case test_server_sup:framework_call(get_html_wrapper,
[TestDescr,true], "") of
[TestDescr,true,TestDir], "") of
Empty when (Empty == "") ; (element(2,Empty) == "") ->
put(basic_html, true),
{["<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 3.2 Final//EN\">\n",
Expand Down Expand Up @@ -1769,7 +1771,7 @@ do_test_cases(TopCases, SkipCases,
"<table>") ++
"<tr><th>Num</th><th>Module</th><th>Case</th><th>Log</th>"
"<th>Time</th><th>Result</th><th>Comment</th></tr>\n",
[print_if_known(N, {"Executing ~p test cases...\n",[N]},
[print_if_known(N, {"<i>Executing <b>~p</b> test cases...</i>\n",[N]},
{"",[]})]),
print(html, xhtml("<br>", "<br />")),

Expand Down Expand Up @@ -1803,7 +1805,7 @@ do_test_cases(TopCase, SkipCases, Config, TimetrapSpec) ->


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% start_log_file() -> ok | exit({Error,Reason})
%% start_log_file() -> {ok,TestDirName} | exit({Error,Reason})
%% Stem = string()
%%
%% Creates the log directories, the major log file and the html log file.
Expand Down Expand Up @@ -1854,7 +1856,7 @@ start_log_file() ->

LogInfo = [{topdir,Dir},{rundir,lists:flatten(TestDir)}],
test_server_sup:framework_call(report, [loginfo,LogInfo]),
ok.
{ok,TestDir}.

make_html_link(LinkName, Target, Explanation) ->
%% if possible use a relative reference to Target.
Expand Down Expand Up @@ -1915,7 +1917,8 @@ start_minor_log_file1(Mod, Func, LogDir, AbsName) ->
TestDescr = io_lib:format("Test ~p:~p result", [Mod,Func]),
{Header,Footer} =
case test_server_sup:framework_call(get_html_wrapper,
[TestDescr,false], "") of
[TestDescr,false,
filename:dirname(AbsName)], "") of
Empty when (Empty == "") ; (element(2,Empty) == "") ->
put(basic_html, true),
{["<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 3.2 Final//EN\">\n",
Expand Down Expand Up @@ -2041,10 +2044,11 @@ html_possibly_convert(Src, SrcInfo, Dest) ->
{ok,DestInfo} when DestInfo#file_info.mtime >= SrcInfo#file_info.mtime ->
ok; % dest file up to date
_ ->
OutDir = get(test_server_log_dir_base),
Header =
case test_server_sup:framework_call(get_html_wrapper,
["Module "++Src,false],
"") of
["Module "++Src,false,
OutDir], "") of
Empty when (Empty == "") ; (element(2,Empty) == "") ->
["<!DOCTYPE HTML PUBLIC",
"\"-//W3C//DTD HTML 3.2 Final//EN\">\n",
Expand Down Expand Up @@ -3215,8 +3219,8 @@ skip_case(Type, Ref, CaseNum, Case, Comment, SendSync, Mode) ->

skip_case1(Type, CaseNum, Mod, Func, Comment, Mode) ->
{{Col0,Col1},_} = get_font_style((CaseNum > 0), Mode),
ResultCol = if Type == auto -> "#ffcc99";
Type == user -> "#ff9933"
ResultCol = if Type == auto -> ?auto_skip_color;
Type == user -> ?user_skip_color
end,

Comment1 = reason_to_string(Comment),
Expand Down Expand Up @@ -3901,9 +3905,10 @@ check_new_crash_dumps(Where) ->

progress(skip, CaseNum, Mod, Func, Loc, Reason, Time,
Comment, {St0,St1}) ->
{Reason1,{Color,Ret}} = if_auto_skip(Reason,
fun() -> {"#ffcc99",auto_skip} end,
fun() -> {"#ff9933",skip} end),
{Reason1,{Color,Ret}} =
if_auto_skip(Reason,
fun() -> {?auto_skip_color,auto_skip} end,
fun() -> {?user_skip_color,skip} end),
print(major, "=result skipped", []),
print(1, "*** SKIPPED *** ~s",
[get_info_str(Func, CaseNum, get(test_server_cases))]),
Expand Down

0 comments on commit fd55862

Please sign in to comment.