~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/common_test/src/cth_log_redirect.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
-module(cth_log_redirect).
 
20
 
 
21
%%% @doc Common Test Framework functions handling test specifications.
 
22
%%%
 
23
%%% <p>This module redirects sasl and error logger info to common test log.</p>
 
24
%%% @end
 
25
 
 
26
 
 
27
%% CTH Callbacks
 
28
-export([id/1, init/2, post_init_per_group/4, pre_end_per_group/3,
 
29
         post_end_per_testcase/4]).
 
30
 
 
31
%% Event handler Callbacks
 
32
-export([init/1,
 
33
         handle_event/2, handle_call/2, handle_info/2,
 
34
         terminate/2]).
 
35
 
 
36
id(_Opts) ->
 
37
    ?MODULE.
 
38
 
 
39
init(?MODULE, _Opts) ->
 
40
    error_logger:add_report_handler(?MODULE),
 
41
    tc_log.
 
42
 
 
43
post_init_per_group(Group, Config, Result, tc_log) ->
 
44
    case lists:member(parallel,proplists:get_value(
 
45
                                 tc_group_properties,Config,[])) of
 
46
        true ->
 
47
            {Result, {set_log_func(ct_log),Group}};
 
48
        false ->
 
49
            {Result, tc_log}
 
50
    end;
 
51
post_init_per_group(_Group, _Config, Result, State) ->
 
52
    {Result, State}.
 
53
 
 
54
post_end_per_testcase(_TC, _Config, Result, State) ->
 
55
    %% Make sure that the event queue is flushed
 
56
    %% before ending this test case.
 
57
    gen_event:call(error_logger, ?MODULE, flush),
 
58
    {Result, State}.
 
59
 
 
60
pre_end_per_group(Group, Config, {ct_log, Group}) ->
 
61
    {Config, set_log_func(tc_log)};
 
62
pre_end_per_group(_Group, Config, State) ->
 
63
    {Config, State}.
 
64
 
 
65
 
 
66
%% Copied and modified from sasl_report_tty_h.erl
 
67
init(_Type) ->
 
68
    {ok, tc_log}.
 
69
 
 
70
handle_event({_Type, GL, _Msg}, State) when node(GL) /= node() ->
 
71
    {ok, State};
 
72
handle_event(Event, LogFunc) ->
 
73
    case lists:keyfind(sasl, 1, application:which_applications()) of
 
74
        false ->
 
75
            sasl_not_started;
 
76
        _Else ->
 
77
            {ok, ErrLogType} = application:get_env(sasl, errlog_type),
 
78
            SReport = sasl_report:format_report(group_leader(), ErrLogType,
 
79
                                                tag_event(Event)),
 
80
            if is_list(SReport) ->
 
81
                    ct_logs:LogFunc(sasl, SReport, []);
 
82
               true -> %% Report is an atom if no logging is to be done
 
83
                    ignore
 
84
            end
 
85
    end,
 
86
    EReport = error_logger_tty_h:write_event(
 
87
                tag_event(Event),io_lib),
 
88
    if is_list(EReport) ->
 
89
            ct_logs:LogFunc(error_logger, EReport, []);
 
90
       true -> %% Report is an atom if no logging is to be done
 
91
            ignore
 
92
    end,
 
93
    {ok, LogFunc}.
 
94
 
 
95
 
 
96
handle_info(_,State) -> {ok, State}.
 
97
 
 
98
handle_call(flush,State) ->
 
99
    {ok, ok, State};
 
100
handle_call({set_logfunc,NewLogFunc},_) ->
 
101
    {ok, NewLogFunc, NewLogFunc};
 
102
handle_call(_Query, _State) -> {error, bad_query}.
 
103
 
 
104
terminate(_Reason, _Type) ->
 
105
    [].
 
106
 
 
107
tag_event(Event) ->
 
108
    {calendar:local_time(), Event}.
 
109
 
 
110
set_log_func(Func) ->
 
111
    gen_event:call(error_logger, ?MODULE, {set_logfunc, Func}).