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

« back to all changes in this revision

Viewing changes to lib/test_server/src/ts_install_cth.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 2010-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 TS Installed SCB
 
21
%%%
 
22
%%% This module does what the make parts of the ts:run/x command did,
 
23
%%% but not the Makefile.first parts! So they have to be done by ts or
 
24
%%% manually!!
 
25
 
 
26
-module(ts_install_cth).
 
27
 
 
28
%% Suite Callbacks
 
29
-export([id/1]).
 
30
-export([init/2]).
 
31
 
 
32
-export([pre_init_per_suite/3]).
 
33
-export([post_init_per_suite/4]).
 
34
-export([pre_end_per_suite/3]).
 
35
-export([post_end_per_suite/4]).
 
36
 
 
37
-export([pre_init_per_group/3]).
 
38
-export([post_init_per_group/4]).
 
39
-export([pre_end_per_group/3]).
 
40
-export([post_end_per_group/4]).
 
41
 
 
42
-export([pre_init_per_testcase/3]).
 
43
-export([post_end_per_testcase/4]).
 
44
 
 
45
-export([on_tc_fail/3]).
 
46
-export([on_tc_skip/3]).
 
47
 
 
48
-export([terminate/1]).
 
49
 
 
50
-include_lib("kernel/include/file.hrl").
 
51
 
 
52
-type config() :: proplists:proplist().
 
53
-type reason() :: term().
 
54
-type skip_or_fail() :: {skip, reason()} |
 
55
                        {auto_skip, reason()} |
 
56
                        {fail, reason()}.
 
57
 
 
58
-record(state, { ts_conf_dir, target_system, install_opts, nodenames, nodes }).
 
59
 
 
60
%% @doc The id of this SCB
 
61
-spec id(Opts :: term()) ->
 
62
    Id :: term().
 
63
id(_Opts) ->
 
64
    ?MODULE.
 
65
 
 
66
%% @doc Always called before any other callback function.
 
67
-spec init(Id :: term(), Opts :: proplists:proplist()) ->
 
68
    {ok, State :: #state{}}.
 
69
init(_Id, Opts) ->
 
70
    Nodenames = proplists:get_value(nodenames, Opts, 0),
 
71
    Nodes = proplists:get_value(nodes, Opts, 0),
 
72
    TSConfDir = proplists:get_value(ts_conf_dir, Opts),
 
73
    TargetSystem = proplists:get_value(target_system, Opts, install_local),
 
74
    InstallOpts = proplists:get_value(install_opts, Opts, []),
 
75
    {ok, #state{ nodenames = Nodenames,
 
76
                 nodes = Nodes,
 
77
                 ts_conf_dir = TSConfDir,
 
78
                 target_system = TargetSystem, 
 
79
                 install_opts = InstallOpts } }.
 
80
 
 
81
%% @doc Called before init_per_suite is called.
 
82
-spec pre_init_per_suite(Suite :: atom(),
 
83
                         Config :: config(),
 
84
                         State :: #state{}) ->
 
85
        {config() | skip_or_fail(), NewState :: #state{}}.
 
86
pre_init_per_suite(Suite,Config,#state{ ts_conf_dir = undefined} = State) ->
 
87
    DataDir = proplists:get_value(data_dir, Config),
 
88
    ParentDir = filename:join(
 
89
                  lists:reverse(
 
90
                    tl(lists:reverse(filename:split(DataDir))))),
 
91
    TSConfDir = filename:join([ParentDir, "..","test_server"]),
 
92
    pre_init_per_suite(Suite, Config, State#state{ ts_conf_dir = TSConfDir });
 
93
pre_init_per_suite(_Suite,Config,State) ->
 
94
    DataDir = proplists:get_value(data_dir, Config),
 
95
    try
 
96
        {ok,Variables} = 
 
97
            file:consult(filename:join(State#state.ts_conf_dir,"variables")),
 
98
 
 
99
        %% Make the stuff in all_SUITE_data if it exists
 
100
        AllDir = filename:join(DataDir,"../all_SUITE_data"),
 
101
        case filelib:is_dir(AllDir) of
 
102
            true ->
 
103
                make_non_erlang(AllDir,Variables);
 
104
            false ->
 
105
                ok
 
106
        end,
 
107
        
 
108
        make_non_erlang(DataDir, Variables),
 
109
 
 
110
        {add_node_name(Config, State), State}
 
111
    catch Error:Reason ->
 
112
            Stack = erlang:get_stacktrace(),
 
113
            ct:pal("~p failed! ~p:{~p,~p}",[?MODULE,Error,Reason,Stack]),
 
114
            {{fail,{?MODULE,{Error,Reason, Stack}}},State}
 
115
    end.
 
116
 
 
117
%% @doc Called after init_per_suite.
 
118
-spec post_init_per_suite(Suite :: atom(),
 
119
                          Config :: config(),
 
120
                          Return :: config() | skip_or_fail(),
 
121
                          State :: #state{}) ->
 
122
        {config() | skip_or_fail(), NewState :: #state{}}.
 
123
post_init_per_suite(_Suite,_Config,Return,State) ->
 
124
    test_server_ctrl:kill_slavenodes(),
 
125
    {Return, State}.
 
126
 
 
127
%% @doc Called before end_per_suite. 
 
128
-spec pre_end_per_suite(Suite :: atom(),
 
129
                        Config :: config() | skip_or_fail(),
 
130
                        State :: #state{}) ->
 
131
        {ok | skip_or_fail(), NewState :: #state{}}.
 
132
pre_end_per_suite(_Suite,Config,State) ->
 
133
    {Config, State}.
 
134
 
 
135
%% @doc Called after end_per_suite. 
 
136
-spec post_end_per_suite(Suite :: atom(),
 
137
                         Config :: config(),
 
138
                         Return :: term(),
 
139
                         State :: #state{}) ->
 
140
        {ok | skip_or_fail(), NewState :: #state{}}.
 
141
post_end_per_suite(_Suite,_Config,Return,State) ->
 
142
    {Return, State}.
 
143
 
 
144
%% @doc Called before each init_per_group.
 
145
-spec pre_init_per_group(Group :: atom(),
 
146
                         Config :: config(),
 
147
                         State :: #state{}) ->
 
148
        {config() | skip_or_fail(), NewState :: #state{}}.
 
149
pre_init_per_group(_Group,Config,State) ->
 
150
    {add_node_name(Config, State), State}.
 
151
 
 
152
%% @doc Called after each init_per_group.
 
153
-spec post_init_per_group(Group :: atom(),
 
154
                          Config :: config(),
 
155
                          Return :: config() | skip_or_fail(),
 
156
                          State :: #state{}) ->
 
157
        {config() | skip_or_fail(), NewState :: #state{}}.
 
158
post_init_per_group(_Group,_Config,Return,State) ->
 
159
    {Return, State}.
 
160
 
 
161
%% @doc Called after each end_per_group. 
 
162
-spec pre_end_per_group(Group :: atom(),
 
163
                        Config :: config() | skip_or_fail(),
 
164
                        State :: #state{}) ->
 
165
        {ok | skip_or_fail(), NewState :: #state{}}.
 
166
pre_end_per_group(_Group,Config,State) ->
 
167
    {Config, State}.
 
168
 
 
169
%% @doc Called after each end_per_group. 
 
170
-spec post_end_per_group(Group :: atom(),
 
171
                         Config :: config(),
 
172
                         Return :: term(),
 
173
                         State :: #state{}) ->
 
174
        {ok | skip_or_fail(), NewState :: #state{}}.
 
175
post_end_per_group(_Group,_Config,Return,State) ->
 
176
    {Return, State}.
 
177
 
 
178
%% @doc Called before each test case.
 
179
-spec pre_init_per_testcase(TC :: atom(),
 
180
                            Config :: config(),
 
181
                            State :: #state{}) ->
 
182
        {config() | skip_or_fail(), NewState :: #state{}}.
 
183
pre_init_per_testcase(_TC,Config,State) ->
 
184
    {add_node_name(Config, State), State}.
 
185
 
 
186
%% @doc Called after each test case. 
 
187
-spec post_end_per_testcase(TC :: atom(),
 
188
                            Config :: config(),
 
189
                            Return :: term(),
 
190
                            State :: #state{}) ->
 
191
        {ok | skip_or_fail(), NewState :: #state{}}.
 
192
post_end_per_testcase(_TC,_Config,Return,State) ->
 
193
    {Return, State}.
 
194
 
 
195
%% @doc Called after a test case failed.
 
196
-spec on_tc_fail(TC :: init_per_suite | end_per_suite |
 
197
                       init_per_group | end_per_group | atom(),
 
198
                 Reason :: term(), State :: #state{}) ->
 
199
        NewState :: #state{}.
 
200
on_tc_fail(_TC, _Reason, State) ->
 
201
    State.
 
202
 
 
203
%% @doc Called when a test case is skipped. 
 
204
-spec on_tc_skip(TC :: end_per_suite | init_per_group | end_per_group | atom(),
 
205
                 {tc_auto_skip, {failed, {Mod :: atom(), Function :: atom(), 
 
206
                                          Reason :: term()}}} |
 
207
                 {tc_user_skip, {skipped, Reason :: term()}},
 
208
                 State :: #state{}) ->
 
209
        NewState :: #state{}.
 
210
on_tc_skip(_TC, _Reason, State) ->
 
211
    State.
 
212
 
 
213
%% @doc Called when the scope of the SCB is done.
 
214
-spec terminate(State :: #state{}) ->
 
215
        term().
 
216
terminate(_State) ->
 
217
    ok.
 
218
 
 
219
%%% ============================================================================
 
220
%%% Local functions
 
221
%%% ============================================================================
 
222
%% Configure and run all the Makefiles in the data dirs of the suite 
 
223
%% in question
 
224
make_non_erlang(DataDir, Variables) ->
 
225
    {ok,CurrWD} = file:get_cwd(),
 
226
    try
 
227
        file:set_cwd(DataDir),
 
228
        MakeCommand = proplists:get_value(make_command,Variables),
 
229
        
 
230
        FirstMakefile = filename:join(DataDir,"Makefile.first"),
 
231
        case filelib:is_regular(FirstMakefile) of
 
232
            true ->
 
233
                ct:log("Making ~p",[FirstMakefile]),
 
234
                ok = ts_make:make(
 
235
                       MakeCommand, DataDir, filename:basename(FirstMakefile));
 
236
            false ->
 
237
                ok
 
238
        end,
 
239
        
 
240
        MakefileSrc = filename:join(DataDir,"Makefile.src"),
 
241
        MakefileDest = filename:join(DataDir,"Makefile"),
 
242
        case filelib:is_regular(MakefileSrc) of
 
243
            true ->
 
244
                ok = ts_lib:subst_file(MakefileSrc,MakefileDest,Variables),
 
245
                ct:log("Making ~p",[MakefileDest]),
 
246
                ok = ts_make:make([{makefile,"Makefile"},{data_dir,DataDir} 
 
247
                                   | Variables]);
 
248
            false ->
 
249
                ok
 
250
        end
 
251
    after
 
252
        file:set_cwd(CurrWD),
 
253
        timer:sleep(100)
 
254
    end.
 
255
 
 
256
%% Add a nodename to config if it does not exist
 
257
add_node_name(Config, State) ->
 
258
    case proplists:get_value(nodenames, Config) of
 
259
        undefined ->
 
260
            lists:keystore(
 
261
               nodenames, 1, Config, 
 
262
               {nodenames,generate_nodenames(State#state.nodenames)});
 
263
        _Else ->
 
264
            Config
 
265
    end.
 
266
 
 
267
 
 
268
%% Copied from test_server_ctrl.erl
 
269
generate_nodenames(Num) ->
 
270
    {ok,Name} = inet:gethostname(),
 
271
    generate_nodenames2(Num, [Name], []).
 
272
 
 
273
generate_nodenames2(0, _Hosts, Acc) ->
 
274
    Acc;
 
275
generate_nodenames2(N, Hosts, Acc) ->
 
276
    Host=lists:nth((N rem (length(Hosts)))+1, Hosts),
 
277
    Name=list_to_atom(temp_nodename("nod", []) ++ "@" ++ Host),
 
278
    generate_nodenames2(N-1, Hosts, [Name|Acc]).
 
279
 
 
280
temp_nodename([], Acc) ->
 
281
    lists:flatten(Acc);
 
282
temp_nodename([Chr|Base], Acc) ->
 
283
    {A,B,C} = erlang:now(),
 
284
    New = [Chr | integer_to_list(Chr bxor A bxor B+A bxor C+B)],
 
285
    temp_nodename(Base, [New|Acc]).