Skip to content

Commit

Permalink
common_test: header option for cth_conn_log hook module
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Oct 11, 2024
1 parent 928d03e commit 042ddc7
Show file tree
Hide file tree
Showing 4 changed files with 55 additions and 24 deletions.
7 changes: 7 additions & 0 deletions lib/common_test/doc/src/ct_telnet.xml
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,13 @@
is set to <c>html</c>, all Telnet communication is printed to the test
case HTML log instead.</p>

<p>For raw logs, <c>prefix</c> option can be used for adjusting
prefix data added to connection log. The default value of this
option is <c>disabled</c>, which results with no prefix data. If
the value is set to <c>full</c> prefix contains timestamp and
additonal information. If the value is set to <c>short</c>
prefix includes only human readable timestamp.</p>

<p>All <c>cth_conn_log</c> hook options described can also be
specified in a configuration file with configuration variable
<c>ct_conn_log</c>.</p>
Expand Down
58 changes: 41 additions & 17 deletions lib/common_test/src/ct_conn_log_h.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,17 +30,18 @@
-export([init/1,
handle_event/2, handle_call/2, handle_info/2,
terminate/2]).

-record(state, {logs=[], default_gl}).
-record(state, {logs=[], default_gl, prefix=disabled}).

-define(WIDTH,80).

-define(now, os:timestamp()).

%%%-----------------------------------------------------------------
%%% Callbacks
init({GL,ConnLogs}) ->
open_files(GL,ConnLogs,#state{default_gl=GL}).
init({GL,ConnLogs,Opts}) ->
open_files(GL,ConnLogs,
#state{default_gl = GL,
prefix = proplists:get_value(prefix, Opts, disabled)}).

open_files(GL,[{ConnMod,{LogType,LogFiles}}|T],State=#state{logs=Logs}) ->
case do_open_files(LogFiles,[]) of
Expand Down Expand Up @@ -103,6 +104,10 @@ terminate(_,#state{logs=Logs}) ->

%%%-----------------------------------------------------------------
%%% Writing reports
write_report(Time,#conn_log{header=false,module=ConnMod}=Info,Data,GL,
#state{prefix=PrefixType}=State)
when PrefixType==full;PrefixType==short ->
write_report_with_header(Info, GL, State, ConnMod, Data, Time);
write_report(_Time,#conn_log{header=false,module=ConnMod}=Info,Data,GL,State) ->
case get_log(Info,GL,State) of
{silent,_,_} ->
Expand All @@ -113,8 +118,14 @@ write_report(_Time,#conn_log{header=false,module=ConnMod}=Info,Data,GL,State) ->
end,
io:format(Fd,Str,[format_data(ConnMod,LogType,Data)])
end;

write_report(Time,#conn_log{module=ConnMod}=Info,Data,GL,State) ->
write_report(Time,#conn_log{module=ConnMod}=Info,Data,GL,State0) ->
%% setting to full so output matches with legacy behavior when
%% header field is set to true
State = State0#state{prefix=full},
write_report_with_header(Info, GL, State, ConnMod, Data, Time).

write_report_with_header(Info, GL,#state{prefix=PrefixType}=State,
ConnMod, Data, Time) ->
case get_log(Info,GL,State) of
{silent,_,_} ->
ok;
Expand All @@ -128,13 +139,17 @@ write_report(Time,#conn_log{module=ConnMod}=Info,Data,GL,State) ->
true ->
"~n~ts~ts~ts"
end,
io:format(Fd,Str,[format_head(ConnMod,LogType,Time),
format_title(LogType,Info),
FormattedData])
io:format(Fd,Str,
[format_head(ConnMod,LogType,PrefixType,Time),
format_title(LogType,PrefixType,Info),
FormattedData])
end
end.

write_error(Time,#conn_log{module=ConnMod}=Info,Report,GL,State) ->
%% this function was including all prefix data no matter what
%% header field value is - leaving behavior as is it was
PrefixType = full,
case get_log(Info,GL,State) of
{LogType,_,_} when LogType==html; LogType==silent ->
%% The error will anyway be written in the html log by the
Expand All @@ -144,8 +159,8 @@ write_error(Time,#conn_log{module=ConnMod}=Info,Report,GL,State) ->
Str = if LogType == html, Dest == gl -> ["$tc_html","~n~ts~ts~ts"];
true -> "~n~ts~ts~ts"
end,
io:format(Fd,Str,[format_head(ConnMod,LogType,Time," ERROR"),
format_title(LogType,Info),
io:format(Fd,Str,[format_head(ConnMod,LogType,PrefixType,Time," ERROR"),
format_title(LogType,PrefixType,Info),
format_error(LogType,Report)])
end.

Expand Down Expand Up @@ -176,18 +191,22 @@ get_fd(#conn_log{name=ConnName},Fds) ->

%%%-----------------------------------------------------------------
%%% Formatting
format_head(ConnMod,LogType,Time) ->
format_head(ConnMod,LogType,Time,"").
format_head(ConnMod,LogType,PrefixType,Time) ->
format_head(ConnMod,LogType,PrefixType,Time,"").

format_head(ConnMod,raw,Time,Text) ->
format_head(_ConnMod,raw,short,Time,_Text) ->
io_lib:format("~n~s, ",[pretty_head(now_to_time(Time))]);
format_head(ConnMod,raw,_,Time,Text) ->
io_lib:format("~n~w, ~w~ts, ",[now_to_time(Time),ConnMod,Text]);
format_head(ConnMod,_,Time,Text) ->
format_head(ConnMod,_,_,Time,Text) ->
Head = pad_char_end(?WIDTH,pretty_head(now_to_time(Time),ConnMod,Text),$=),
io_lib:format("~n~ts",[Head]).

format_title(raw,#conn_log{client=Client}=Info) ->
format_title(raw,short,_Info) ->
"";
format_title(raw,full,#conn_log{client=Client}=Info) ->
io_lib:format("Client ~tw ~s ~ts",[Client,actionstr(Info),serverstr(Info)]);
format_title(_,Info) ->
format_title(_,_,Info) ->
Title = pad_char_end(?WIDTH,pretty_title(Info),$=),
io_lib:format("~n~ts", [Title]).

Expand Down Expand Up @@ -229,6 +248,11 @@ pretty_head({{{Y,Mo,D},{H,Mi,S}},MicroS},ConnMod,Text0) ->
[Text,t(D),month(Mo),Y,t(H),t(Mi),t(S),
micro2milli(MicroS)]).

pretty_head({{{Y,Mo,D},{H,Mi,S}},MicroS}) ->
io_lib:format("~s-~s-~w::~s:~s:~s,~s ",
[t(D),month(Mo),Y,t(H),t(Mi),t(S),
micro2milli(MicroS)]).

pretty_title(#conn_log{client=Client}=Info) ->
io_lib:format("= Client ~tw ~s ~ts ",
[Client,actionstr(Info),serverstr(Info)]).
Expand Down
9 changes: 5 additions & 4 deletions lib/common_test/src/cth_conn_log.erl
Original file line number Diff line number Diff line change
Expand Up @@ -91,12 +91,13 @@ get_log_opts(Mod,Opts) ->
end,
LogType = proplists:get_value(log_type,Opts,DefaultLogType),
Hosts = proplists:get_value(hosts,Opts,[]),
{LogType,Hosts}.
{LogType,Hosts,[{prefix, proplists:get_value(prefix,Opts,disabled)}]}.

pre_init_per_testcase(_Suite,TestCase,Config,CthState) ->
{_, _, CtTelnetOpts} = proplists:get_value(ct_telnet, CthState, {null, null, []}),
Logs =
lists:map(
fun({ConnMod,{LogType,Hosts}}) ->
fun({ConnMod,{LogType,Hosts, _Opts}}) ->
ct_util:set_testdata({{?MODULE,ConnMod},LogType}),
case LogType of
LogType when LogType==raw; LogType==pretty ->
Expand Down Expand Up @@ -128,11 +129,11 @@ pre_init_per_testcase(_Suite,TestCase,Config,CthState) ->
end
end,
CthState),

GL = group_leader(),
Update =
fun(Init) when Init == undefined; Init == [] ->
error_logger:add_report_handler(ct_conn_log_h,{GL,Logs}),
error_logger:add_report_handler(ct_conn_log_h,
{GL,Logs,CtTelnetOpts}),
[TestCase];
(PrevUsers) ->
error_logger:info_report(update,{GL,Logs}),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -29,10 +29,9 @@
%%--------------------------------------------------------------------

suite() ->
[
{require,telnet_server_conn1,{unix,[telnet]}},
[{require,telnet_server_conn1,{unix,[telnet]}},
{require,ct_conn_log},
{ct_hooks, [{cth_conn_log,[]}]}
{ct_hooks, [{cth_conn_log,[{ct_telnet, [{prefix, short}]}]}]}
].

all() ->
Expand Down

0 comments on commit 042ddc7

Please sign in to comment.