~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_test_support_eh.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2010. 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
 
 
20
%%% @doc Event handler module
 
21
%%%
 
22
%%% <p>This is an event handler module used for testing that 
 
23
%%%    Common Test generates events as expected.</p>
 
24
%%%
 
25
-module(ct_test_support_eh).
 
26
 
 
27
-behaviour(gen_event).
 
28
 
 
29
-include_lib("test_server/include/test_server.hrl").
 
30
-include_lib("common_test/include/ct_event.hrl").
 
31
 
 
32
%% gen_event callbacks
 
33
-export([init/1, handle_event/2, handle_call/2, 
 
34
         handle_info/2, terminate/2, code_change/3]).
 
35
 
 
36
-record(state, {cbm=ct_test_support,
 
37
                trace_level=50}).
 
38
 
 
39
%%====================================================================
 
40
%% gen_event callbacks
 
41
%%====================================================================
 
42
%%--------------------------------------------------------------------
 
43
%% Function: init(Args) -> {ok, State}
 
44
%% Description: Whenever a new event handler is added to an event manager,
 
45
%% this function is called to initialize the event handler.
 
46
%%--------------------------------------------------------------------
 
47
init(String = [X|_]) when is_integer(X) ->
 
48
    case erl_scan:string(String++".") of
 
49
        {ok,Ts,_} ->
 
50
            case erl_parse:parse_term(Ts) of
 
51
                {ok,Args} ->
 
52
                    init(Args);
 
53
                _ ->
 
54
                    init(String)
 
55
            end;
 
56
        _ ->
 
57
            init(String)
 
58
    end;
 
59
 
 
60
init(Args) ->
 
61
    S1 = case lists:keysearch(cbm, 1, Args) of
 
62
             {_,{cbm,CBM}} ->
 
63
                 #state{cbm=CBM};
 
64
             _ ->
 
65
                 #state{}
 
66
         end,
 
67
    S2 = case lists:keysearch(trace_level, 1, Args) of
 
68
             {_,{trace_level,Level}} ->
 
69
                 S1#state{trace_level=Level};
 
70
             _ ->
 
71
                 S1
 
72
         end,
 
73
    print(S2#state.trace_level, "Event Handler ~w started with ~p~n",
 
74
          [?MODULE,Args]),
 
75
    {ok,S2}.
 
76
 
 
77
%%--------------------------------------------------------------------
 
78
%% Function:  
 
79
%% handle_event(Event, State) -> {ok, State} |
 
80
%%                               {swap_handler, Args1, State1, Mod2, Args2} |
 
81
%%                               remove_handler
 
82
%% Description:Whenever an event manager receives an event sent using
 
83
%% gen_event:notify/2 or gen_event:sync_notify/2, this function is called for
 
84
%% each installed event handler to handle the event. 
 
85
%%--------------------------------------------------------------------
 
86
handle_event(Event, State=#state{cbm=CBM, trace_level=_Level}) ->
 
87
    % print(_Level, "~p: ~p~n", [Event#event.name,Event#event.data]),
 
88
    CBM:handle_event(?MODULE, Event),
 
89
    {ok,State}.
 
90
 
 
91
%%--------------------------------------------------------------------
 
92
%% Function: 
 
93
%% handle_call(Request, State) -> {ok, Reply, State} |
 
94
%%                                {swap_handler, Reply, Args1, State1, 
 
95
%%                                  Mod2, Args2} |
 
96
%%                                {remove_handler, Reply}
 
97
%% Description: Whenever an event manager receives a request sent using
 
98
%% gen_event:call/3,4, this function is called for the specified event 
 
99
%% handler to handle the request.
 
100
%%--------------------------------------------------------------------
 
101
handle_call(_Req, State) ->
 
102
    Reply = ok,
 
103
    {ok, Reply, State}.
 
104
 
 
105
%%--------------------------------------------------------------------
 
106
%% Function: 
 
107
%% handle_info(Info, State) -> {ok, State} |
 
108
%%                             {swap_handler, Args1, State1, Mod2, Args2} |
 
109
%%                              remove_handler
 
110
%% Description: This function is called for each installed event handler when
 
111
%% an event manager receives any other message than an event or a synchronous
 
112
%% request (or a system message).
 
113
%%--------------------------------------------------------------------
 
114
handle_info(_Info, State) ->
 
115
    {ok, State}.
 
116
 
 
117
%%--------------------------------------------------------------------
 
118
%% Function: terminate(Reason, State) -> void()
 
119
%% Description:Whenever an event handler is deleted from an event manager,
 
120
%% this function is called. It should be the opposite of Module:init/1 and 
 
121
%% do any necessary cleaning up. 
 
122
%%--------------------------------------------------------------------
 
123
terminate(_Reason, _State) ->
 
124
    ok.
 
125
 
 
126
%%--------------------------------------------------------------------
 
127
%% Function: code_change(OldVsn, State, Extra) -> {ok, NewState} 
 
128
%% Description: Convert process state when code is changed
 
129
%%--------------------------------------------------------------------
 
130
code_change(_OldVsn, State, _Extra) ->
 
131
    {ok, State}.
 
132
 
 
133
%%--------------------------------------------------------------------
 
134
%%% Internal functions
 
135
%%--------------------------------------------------------------------
 
136
 
 
137
print(Level, _Str, _Args) ->
 
138
    test_server:format(Level, _Str,_Args).
 
139
 
 
140