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

« back to all changes in this revision

Viewing changes to lib/common_test/src/ct_hooks.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 2004-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
 
 
20
%%% @doc Common Test Framework test execution control module.
 
21
%%%
 
22
%%% <p>This module is a proxy for calling and handling common test hooks.</p>
 
23
 
 
24
-module(ct_hooks).
 
25
 
 
26
%% API Exports
 
27
-export([init/1]).
 
28
-export([init_tc/3]).
 
29
-export([end_tc/5]).
 
30
-export([terminate/1]).
 
31
-export([on_tc_skip/2]).
 
32
-export([on_tc_fail/2]).
 
33
 
 
34
-type proplist() :: [{atom(),term()}].
 
35
 
 
36
%% If you change this, remember to update ct_util:look -> stop clause as well.
 
37
-define(config_name, ct_hooks).
 
38
 
 
39
%% -------------------------------------------------------------------------
 
40
%% API Functions
 
41
%% -------------------------------------------------------------------------
 
42
 
 
43
%% @doc Called before any suites are started
 
44
-spec init(State :: term()) -> ok |
 
45
                               {error, Reason :: term()}.
 
46
init(Opts) ->
 
47
    call([{Hook, call_id, undefined} || Hook <- get_new_hooks(Opts)],
 
48
         ok, init, []).
 
49
                      
 
50
 
 
51
%% @doc Called after all suites are done.
 
52
-spec terminate(Hooks :: term()) ->
 
53
    ok.
 
54
terminate(Hooks) ->
 
55
    call([{HookId, fun call_terminate/3} || {HookId,_,_} <- Hooks],
 
56
         ct_hooks_terminate_dummy, terminate, Hooks),
 
57
    ok.
 
58
 
 
59
%% @doc Called as each test case is started. This includes all configuration
 
60
%% tests.
 
61
-spec init_tc(Mod :: atom(), Func :: atom(), Args :: list()) ->
 
62
    NewConfig :: proplist() |
 
63
    {skip, Reason :: term()} |
 
64
    {auto_skip, Reason :: term()} |
 
65
    {fail, Reason :: term()}.
 
66
init_tc(ct_framework, _Func, Args) ->
 
67
    Args;
 
68
init_tc(Mod, init_per_suite, Config) ->
 
69
    Info = try proplists:get_value(ct_hooks, Mod:suite(),[]) of
 
70
               List when is_list(List) -> 
 
71
                   [{ct_hooks,List}];
 
72
               CTHook when is_atom(CTHook) ->
 
73
                   [{ct_hooks,[CTHook]}]
 
74
           catch error:undef ->
 
75
                   [{ct_hooks,[]}]
 
76
           end,
 
77
    call(fun call_generic/3, Config ++ Info, [pre_init_per_suite, Mod]);
 
78
init_tc(Mod, end_per_suite, Config) ->
 
79
    call(fun call_generic/3, Config, [pre_end_per_suite, Mod]);
 
80
init_tc(Mod, {init_per_group, GroupName, Opts}, Config) ->
 
81
    maybe_start_locker(Mod, GroupName, Opts),
 
82
    call(fun call_generic/3, Config, [pre_init_per_group, GroupName]);
 
83
init_tc(_Mod, {end_per_group, GroupName, _}, Config) ->
 
84
    call(fun call_generic/3, Config, [pre_end_per_group, GroupName]);
 
85
init_tc(_Mod, TC, Config) ->
 
86
    call(fun call_generic/3, Config, [pre_init_per_testcase, TC]).
 
87
 
 
88
%% @doc Called as each test case is completed. This includes all configuration
 
89
%% tests.
 
90
-spec end_tc(Mod :: atom(),
 
91
             Func :: atom(),
 
92
             Args :: list(),
 
93
             Result :: term(),
 
94
             Resturn :: term()) ->
 
95
    NewConfig :: proplist() |
 
96
    {skip, Reason :: term()} |
 
97
    {auto_skip, Reason :: term()} |
 
98
    {fail, Reason :: term()} |
 
99
    ok | '$ct_no_change'.
 
100
end_tc(ct_framework, _Func, _Args, Result, _Return) ->
 
101
    Result;
 
102
 
 
103
end_tc(Mod, init_per_suite, Config, _Result, Return) ->
 
104
    call(fun call_generic/3, Return, [post_init_per_suite, Mod, Config],
 
105
         '$ct_no_change');
 
106
 
 
107
end_tc(Mod, end_per_suite, Config, Result, _Return) ->
 
108
    call(fun call_generic/3, Result, [post_end_per_suite, Mod, Config],
 
109
        '$ct_no_change');
 
110
 
 
111
end_tc(_Mod, {init_per_group, GroupName, _}, Config, _Result, Return) ->
 
112
    call(fun call_generic/3, Return, [post_init_per_group, GroupName, Config],
 
113
         '$ct_no_change');
 
114
 
 
115
end_tc(Mod, {end_per_group, GroupName, Opts}, Config, Result, _Return) ->
 
116
    Res = call(fun call_generic/3, Result,
 
117
               [post_end_per_group, GroupName, Config], '$ct_no_change'),
 
118
    maybe_stop_locker(Mod, GroupName,Opts),
 
119
    Res;
 
120
 
 
121
end_tc(_Mod, TC, Config, Result, _Return) ->
 
122
    call(fun call_generic/3, Result, [post_end_per_testcase, TC, Config],
 
123
        '$ct_no_change').
 
124
 
 
125
on_tc_skip(How, {_Suite, Case, Reason}) ->
 
126
    call(fun call_cleanup/3, {How, Reason}, [on_tc_skip, Case]).
 
127
 
 
128
on_tc_fail(_How, {_Suite, Case, Reason}) ->
 
129
    call(fun call_cleanup/3, Reason, [on_tc_fail, Case]).
 
130
 
 
131
%% -------------------------------------------------------------------------
 
132
%% Internal Functions
 
133
%% -------------------------------------------------------------------------
 
134
call_id(Mod, Config, Meta) when is_atom(Mod) ->
 
135
    call_id({Mod, []}, Config, Meta);
 
136
call_id({Mod, Opts}, Config, Scope) ->
 
137
    Id = catch_apply(Mod,id,[Opts], make_ref()),
 
138
    {Config, {Id, scope(Scope), {Mod, {Id,Opts}}}}.
 
139
        
 
140
call_init({Mod,{Id,Opts}},Config,_Meta) ->
 
141
    NewState = Mod:init(Id, Opts),
 
142
    {Config, {Mod, NewState}}.
 
143
 
 
144
call_terminate({Mod, State}, _, _) ->
 
145
    catch_apply(Mod,terminate,[State], ok),
 
146
    {[],{Mod,State}}.
 
147
 
 
148
call_cleanup({Mod, State}, Reason, [Function | Args]) ->
 
149
    NewState = catch_apply(Mod,Function, Args ++ [Reason, State],
 
150
                           State),
 
151
    {Reason, {Mod, NewState}}.
 
152
 
 
153
call_generic({Mod, State}, Value, [Function | Args]) ->
 
154
    {NewValue, NewState} = catch_apply(Mod, Function, Args ++ [Value, State],
 
155
                                       {Value,State}),
 
156
    {NewValue, {Mod, NewState}}.
 
157
 
 
158
%% Generic call function
 
159
call(Fun, Config, Meta) ->
 
160
    maybe_lock(),
 
161
    Hooks = get_hooks(),
 
162
    Res = call([{HookId,Fun} || {HookId,_, _} <- Hooks] ++
 
163
                   get_new_hooks(Config, Fun),
 
164
               remove(?config_name,Config), Meta, Hooks),
 
165
    maybe_unlock(),
 
166
    Res.
 
167
 
 
168
call(Fun, Config, Meta, NoChangeRet) when is_function(Fun) ->
 
169
    case call(Fun,Config,Meta) of
 
170
        Config -> NoChangeRet;
 
171
        NewReturn -> NewReturn
 
172
    end;
 
173
 
 
174
call([{Hook, call_id, NextFun} | Rest], Config, Meta, Hooks) ->
 
175
    try
 
176
        {Config, {NewId, _, _} = NewHook} = call_id(Hook, Config, Meta),
 
177
        {NewHooks, NewRest} = 
 
178
            case lists:keyfind(NewId, 1, Hooks) of
 
179
                false when NextFun =:= undefined ->
 
180
                    {Hooks ++ [NewHook],
 
181
                     [{NewId, fun call_init/3} | Rest]};
 
182
                ExistingHook when is_tuple(ExistingHook) ->
 
183
                    {Hooks, Rest};
 
184
                _ ->
 
185
                    {Hooks ++ [NewHook],
 
186
                     [{NewId, fun call_init/3},{NewId,NextFun} | Rest]}
 
187
            end,
 
188
        call(NewRest, Config, Meta, NewHooks)
 
189
    catch Error:Reason ->
 
190
            Trace = erlang:get_stacktrace(),
 
191
            ct_logs:log("Suite Hook","Failed to start a CTH: ~p:~p",
 
192
                        [Error,{Reason,Trace}]),
 
193
            call([], {fail,"Failed to start CTH"
 
194
                      ", see the CT Log for details"}, Meta, Hooks)
 
195
    end;
 
196
call([{HookId, Fun} | Rest], Config, Meta, Hooks) ->
 
197
    try
 
198
        {_,Scope,ModState} = lists:keyfind(HookId, 1, Hooks),
 
199
        {NewConf, NewHookInfo} =  Fun(ModState, Config, Meta),
 
200
        NewCalls = get_new_hooks(NewConf, Fun),
 
201
        NewHooks = lists:keyreplace(HookId, 1, Hooks, {HookId, Scope, NewHookInfo}),
 
202
        call(NewCalls  ++ Rest, remove(?config_name, NewConf), Meta,
 
203
             terminate_if_scope_ends(HookId, Meta, NewHooks))
 
204
    catch throw:{error_in_cth_call,Reason} ->
 
205
            call(Rest, {fail, Reason}, Meta,
 
206
                 terminate_if_scope_ends(HookId, Meta, Hooks))
 
207
    end;
 
208
call([], Config, _Meta, Hooks) ->
 
209
    save_suite_data_async(Hooks),
 
210
    Config.
 
211
 
 
212
remove(Key,List) when is_list(List) ->
 
213
    [Conf || Conf <- List, is_tuple(Conf) =:= false
 
214
                 orelse element(1, Conf) =/= Key];
 
215
remove(_, Else) ->
 
216
    Else.
 
217
 
 
218
%% Translate scopes, i.e. init_per_group,group1 -> end_per_group,group1 etc
 
219
scope([pre_init_per_testcase, TC|_]) ->
 
220
    [post_end_per_testcase, TC];
 
221
scope([pre_init_per_group, GroupName|_]) ->
 
222
    [post_end_per_group, GroupName];
 
223
scope([post_init_per_group, GroupName|_]) ->
 
224
    [post_end_per_group, GroupName];
 
225
scope([pre_init_per_suite, SuiteName|_]) ->
 
226
    [post_end_per_suite, SuiteName];
 
227
scope([post_init_per_suite, SuiteName|_]) ->
 
228
    [post_end_per_suite, SuiteName];
 
229
scope(init) ->
 
230
    none.
 
231
 
 
232
terminate_if_scope_ends(HookId, [Function,Tag|T], Hooks) when T =/= [] ->
 
233
    terminate_if_scope_ends(HookId,[Function,Tag],Hooks);
 
234
terminate_if_scope_ends(HookId, Function, Hooks) ->
 
235
    case lists:keyfind(HookId, 1, Hooks) of
 
236
        {HookId, Function, _ModState} = Hook ->
 
237
            terminate([Hook]),
 
238
            lists:keydelete(HookId, 1, Hooks);
 
239
        _ ->
 
240
            Hooks
 
241
    end.
 
242
 
 
243
%% Fetch hook functions
 
244
get_new_hooks(Config, Fun) ->
 
245
    lists:foldl(fun(NewHook, Acc) ->
 
246
                        [{NewHook, call_id, Fun} | Acc]
 
247
                end, [], get_new_hooks(Config)).
 
248
 
 
249
get_new_hooks(Config) when is_list(Config) ->
 
250
    lists:flatmap(fun({?config_name, HookConfigs}) ->
 
251
                          HookConfigs;
 
252
                     (_) ->
 
253
                          []
 
254
                  end, Config);
 
255
get_new_hooks(_Config) ->
 
256
    [].
 
257
 
 
258
save_suite_data_async(Hooks) ->
 
259
    ct_util:save_suite_data_async(?config_name, Hooks).
 
260
 
 
261
get_hooks() ->
 
262
    ct_util:read_suite_data(?config_name).
 
263
 
 
264
catch_apply(M,F,A, Default) ->
 
265
    try
 
266
        apply(M,F,A)
 
267
    catch error:Reason ->
 
268
            case erlang:get_stacktrace() of
 
269
            %% Return the default if it was the CTH module which did not have the function.
 
270
                [{M,F,A}|_] when Reason == undef ->
 
271
                    Default;
 
272
                Trace ->
 
273
                    ct_logs:log("Suite Hook","Call to CTH failed: ~p:~p",
 
274
                                [error,{Reason,Trace}]),
 
275
                    throw({error_in_cth_call,
 
276
                           lists:flatten(
 
277
                             io_lib:format("~p:~p/~p CTH call failed",
 
278
                                           [M,F,length(A)]))})
 
279
            end
 
280
    end.
 
281
 
 
282
 
 
283
%% We need to lock around the state for parallel groups only. This is because
 
284
%% we will get several processes reading and writing the state for a single
 
285
%% cth at the same time.
 
286
maybe_start_locker(Mod,GroupName,Opts) ->
 
287
    case lists:member(parallel,Opts) of
 
288
        true ->
 
289
            {ok, _Pid} = ct_hooks_lock:start({Mod,GroupName});
 
290
        false ->
 
291
            ok
 
292
    end.
 
293
 
 
294
maybe_stop_locker(Mod,GroupName,Opts) ->
 
295
    case lists:member(parallel,Opts) of
 
296
        true ->
 
297
            stopped = ct_hooks_lock:stop({Mod,GroupName});
 
298
        false ->
 
299
            ok
 
300
    end.
 
301
 
 
302
 
 
303
maybe_lock() ->
 
304
    locked = ct_hooks_lock:request().
 
305
 
 
306
maybe_unlock() ->
 
307
    unlocked = ct_hooks_lock:release().