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

« back to all changes in this revision

Viewing changes to lib/tools/test/make_SUITE.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 1996-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(make_SUITE).
 
20
 
 
21
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
22
         init_per_group/2,end_per_group/2, make_all/1, make_files/1]).
 
23
-export([otp_6057_init/1,
 
24
         otp_6057_a/1, otp_6057_b/1, otp_6057_c/1,
 
25
         otp_6057_end/1]).
 
26
 
 
27
-include_lib("test_server/include/test_server.hrl").
 
28
 
 
29
-include_lib("kernel/include/file.hrl").
 
30
 
 
31
%% in ./make_SUITE_data there are test-files used by this
 
32
%% test suite. There are 4 files named test1.erl ... test5.erl.
 
33
%% The test files are attacked in various ways in order to put make on trial.
 
34
%% 
 
35
%% Also, and Emakefile exists in ./make_SUITE_data. This file specifies
 
36
%% that the file :"test5.erl" shall be compiled with the 'S' option,
 
37
%% i.e. produce "test5.S" instead of "test5.<objext>"
 
38
 
 
39
suite() -> [{ct_hooks,[ts_install_cth]}].
 
40
 
 
41
all() -> 
 
42
    [make_all, make_files, {group, otp_6057}].
 
43
 
 
44
groups() -> 
 
45
    [{otp_6057,[],[otp_6057_a, otp_6057_b,
 
46
                   otp_6057_c]}].
 
47
 
 
48
init_per_suite(Config) ->
 
49
    Config.
 
50
 
 
51
end_per_suite(_Config) ->
 
52
    ok.
 
53
 
 
54
init_per_group(_GroupName, Config) ->
 
55
    otp_6057_init(Config).
 
56
 
 
57
end_per_group(_GroupName, Config) ->
 
58
    otp_6057_end(Config).
 
59
 
 
60
 
 
61
test_files() -> ["test1", "test2", "test3", "test4"].
 
62
 
 
63
make_all(suite) -> [];
 
64
make_all(Config) when is_list(Config) ->
 
65
    ?line Current = prepare_data_dir(Config),
 
66
    ?line up_to_date = make:all(),
 
67
    ?line ok = ensure_exists(test_files()),
 
68
    ?line ok = ensure_exists(["test5"],".S"), % Emakefile: [{test5,['S']}
 
69
    ?line file:set_cwd(Current),
 
70
    ?line ensure_no_messages(),
 
71
    ok.
 
72
 
 
73
make_files(suite) -> [];
 
74
make_files(Config) when is_list(Config) ->
 
75
    ?line Current = prepare_data_dir(Config),
 
76
 
 
77
    %% Make files that exist.
 
78
 
 
79
    ?line Files = [test1, test2],
 
80
    ?line up_to_date = make:files(Files), % ok files
 
81
    ?line ok = ensure_exists(Files),
 
82
 
 
83
    ?line error = make:files([test1,test7]), % non existing file
 
84
    ?line up_to_date = make:files([test1,test2],[debug_info]), % with option
 
85
 
 
86
    ?line file:set_cwd(Current),
 
87
    ?line ensure_no_messages(),
 
88
    ok.
 
89
 
 
90
 
 
91
%% Moves to the data directory of this suite, clean it from any object
 
92
%% files (*.jam for a JAM emulator).  Returns the previous directory.
 
93
prepare_data_dir(Config) ->
 
94
    ?line {ok, Current} = file:get_cwd(),
 
95
    ?line {value, {data_dir, Dir}} = lists:keysearch(data_dir, 1, Config),
 
96
    ?line file:set_cwd(Dir),
 
97
    ?line {ok, Files} = file:list_dir("."),
 
98
    ?line delete_obj(Files, code:objfile_extension()),
 
99
    ?line ensure_no_messages(),
 
100
    Current.
 
101
 
 
102
delete_obj([File|Rest], ObjExt) ->
 
103
    ?line case filename:extension(File) of
 
104
              ObjExt -> file:delete(File);
 
105
              ".S" -> file:delete(File);
 
106
              _ -> ok
 
107
          end,
 
108
    ?line delete_obj(Rest, ObjExt);
 
109
delete_obj([], _) ->
 
110
    ok.
 
111
 
 
112
 
 
113
 
 
114
%% Ensure that the given object files exists.
 
115
ensure_exists(Names) ->
 
116
    ensure_exists(Names, code:objfile_extension()).
 
117
 
 
118
ensure_exists([Name|Rest], ObjExt) when is_atom(Name) ->
 
119
    ensure_exists([atom_to_list(Name)|Rest], ObjExt);
 
120
ensure_exists([Name|Rest], ObjExt) ->
 
121
    case filelib:is_regular(Name++ObjExt) of
 
122
        true ->
 
123
            ensure_exists(Rest, ObjExt);
 
124
        false ->
 
125
            Name++ObjExt
 
126
    end;
 
127
ensure_exists([], _) ->
 
128
    ok.
 
129
 
 
130
otp_6057_init(Config) when is_list(Config) ->
 
131
    ?line DataDir = ?config(data_dir, Config),
 
132
    ?line PrivDir = ?config(priv_dir, Config),
 
133
 
 
134
    %% Create the directories PrivDir/otp_6057/src1, /src2 and /ebin
 
135
    Src1 = filename:join([PrivDir, otp_6057, src1]),
 
136
    Src2 = filename:join([PrivDir, otp_6057, src2]),
 
137
    Ebin = filename:join([PrivDir, otp_6057, ebin]),
 
138
    ?line ok = file:make_dir(filename:join(PrivDir, otp_6057)),
 
139
    ?line ok = file:make_dir(Src1), 
 
140
    ?line ok = file:make_dir(Src2), 
 
141
    ?line ok = file:make_dir(Ebin), 
 
142
 
 
143
    %% Copy test1.erl and test2.erl to src1, and test3.erl to src2
 
144
    Test1orig = filename:join(DataDir, "test1.erl"),
 
145
    Test2orig = filename:join(DataDir, "test2.erl"),
 
146
    Test3orig = filename:join(DataDir, "test3.erl"),
 
147
    Test1 = filename:join(Src1, "test1.erl"),
 
148
    Test2 = filename:join(Src1, "test2.erl"),
 
149
    Test3 = filename:join(Src2, "test3.erl"),
 
150
    ?line {ok, _} = file:copy(Test1orig, Test1),
 
151
    ?line {ok, _} = file:copy(Test2orig, Test2),
 
152
    ?line {ok, _} = file:copy(Test3orig, Test3),
 
153
 
 
154
    %% Create an Emakefile in src1
 
155
    Emakefile = filename:join(Src1, "Emakefile"),
 
156
    ?line {ok, Fd} = file:open(Emakefile, write),
 
157
    ?line ok = io:write(Fd, {["test1.erl","test2","../src2/test3"],
 
158
                             [{outdir,"../ebin"}]}),
 
159
    ?line ok = io:fwrite(Fd, ".~n", []),
 
160
    ?line ok = file:close(Fd),
 
161
 
 
162
    ?line ensure_no_messages(),
 
163
    Config.
 
164
 
 
165
otp_6057_a(suite) ->
 
166
    [];
 
167
otp_6057_a(doc) ->
 
168
    ["Test that make:all/0, suite/0 looks for object file in correct place"];
 
169
otp_6057_a(Config) when is_list(Config) ->
 
170
    ?line PrivDir = ?config(priv_dir, Config),
 
171
 
 
172
    %% Go to src1, saving old CWD
 
173
    ?line {ok, CWD} = file:get_cwd(),
 
174
    Src1 = filename:join([PrivDir, otp_6057, src1]),
 
175
    ?line ok = file:set_cwd(Src1),
 
176
 
 
177
    %% Call make:all()
 
178
    ?line up_to_date = make:all(),
 
179
 
 
180
    %% Ensure that all beam files are created in the ebin directory
 
181
    Ebin = filename:join([PrivDir, otp_6057, ebin]),
 
182
    Test1 = filename:join(Ebin, test1),
 
183
    Test2 = filename:join(Ebin, test2),
 
184
    Test3 = filename:join(Ebin, test3),
 
185
    case ensure_exists([Test1, Test2, Test3]) of
 
186
        ok -> ok;
 
187
        Missing ->
 
188
            ?line ?t:fail({"missing beam file", Missing})
 
189
    end,
 
190
 
 
191
    %% Check creation date of test1.beam and make sure it is not
 
192
    %% recompiled if make:all() is called again.
 
193
    %% (Sleep a while, if the file is recompiled within a second then
 
194
    %%  mtime will be the same).
 
195
    ?line {ok, FileInfo1} = file:read_file_info(Test1++".beam"),
 
196
    Date1 = FileInfo1#file_info.mtime,
 
197
    ?t:sleep(?t:seconds(2)),
 
198
    ?line up_to_date = make:all(),
 
199
    ?line {ok, FileInfo2} = file:read_file_info(Test1++".beam"),
 
200
    case FileInfo2#file_info.mtime of
 
201
        Date1 -> ok;
 
202
        _Date2 ->
 
203
            ?line ?t:fail({"recompiled beam file", Test1++".beam"})
 
204
    end,
 
205
 
 
206
    %% Remove the beam files
 
207
    ?line ok =
 
208
        ensure_removed([Test1++".beam",Test2++".beam",Test2++".beam"]),
 
209
 
 
210
    %% Return to original CWD
 
211
    ?line ok = file:set_cwd(CWD),
 
212
 
 
213
    ?line ensure_no_messages(),
 
214
    ok.
 
215
 
 
216
otp_6057_b(suite) ->
 
217
    [];
 
218
otp_6057_b(doc) ->
 
219
    ["Test that make:files/1 can handle a file in another directory"];
 
220
otp_6057_b(Config) when is_list(Config) ->
 
221
    ?line PrivDir = ?config(priv_dir, Config),
 
222
 
 
223
    %% Go to src1, saving old CWD
 
224
    ?line {ok, CWD} = file:get_cwd(),
 
225
    Src1 = filename:join([PrivDir, otp_6057, src1]),
 
226
    ?line ok = file:set_cwd(Src1),
 
227
 
 
228
    %% Ensure there is no beam file already
 
229
    Ebin = filename:join([PrivDir, otp_6057, ebin]),
 
230
    Test3 = filename:join(Ebin, "test3"),
 
231
    ?line ok = ensure_removed([Test3++".beam"]),
 
232
 
 
233
    %% Call make:files/1
 
234
    ?line up_to_date = make:files(["../src2/test3"]),
 
235
    
 
236
    %% Ensure that the beam file is created in the ebin directory
 
237
    case ensure_exists([Test3]) of
 
238
        ok -> ok;
 
239
        Missing ->
 
240
            ?line ?t:fail({"missing beam file", Missing})
 
241
    end,
 
242
 
 
243
    %% Remove the beam file
 
244
    ?line ok = ensure_removed([Test3++".beam"]),
 
245
 
 
246
    %% Return to original CWD
 
247
    ?line ok = file:set_cwd(CWD),
 
248
 
 
249
    ?line ensure_no_messages(),
 
250
    ok.
 
251
 
 
252
otp_6057_c(suite) ->
 
253
    [];
 
254
otp_6057_c(doc) ->
 
255
    ["Test that make:files/1 find options in Emakefile if a file is "
 
256
     "given with the .erl extension there"];
 
257
otp_6057_c(Config) when is_list(Config) ->
 
258
    ?line PrivDir = ?config(priv_dir, Config),
 
259
 
 
260
    %% Go to src1, saving old CWD
 
261
    ?line {ok, CWD} = file:get_cwd(),
 
262
    Src1 = filename:join([PrivDir, otp_6057, src1]),
 
263
    ?line ok = file:set_cwd(Src1),
 
264
 
 
265
    %% Ensure there are no beam files already
 
266
    Ebin = filename:join([PrivDir, otp_6057, ebin]),
 
267
    Test1 = filename:join(Ebin, "test1"),
 
268
    Test2 = filename:join(Ebin, "test2"),
 
269
    ?line ok = ensure_removed([Test1++".beam",Test2++".beam"]),
 
270
 
 
271
    %% Call make:files/1
 
272
    ?line up_to_date = make:files([test1, test2]),
 
273
    
 
274
    %% Ensure that the beam files are created in the ebin directory
 
275
    Ebin = filename:join([PrivDir, otp_6057, ebin]),
 
276
    case ensure_exists([Test1, Test2]) of
 
277
        ok -> ok;
 
278
        Missing ->
 
279
            ?line ?t:fail({"missing beam file", Missing})
 
280
    end,
 
281
 
 
282
    %% Remove the beam files
 
283
    ?line ok = ensure_removed([Test1++".beam", Test2++".beam"]),
 
284
 
 
285
    %% Return to original CWD
 
286
    ?line ok = file:set_cwd(CWD),
 
287
 
 
288
    ?line ensure_no_messages(),
 
289
    ok.
 
290
 
 
291
otp_6057_end(Config) when is_list(Config) ->
 
292
    Config.
 
293
 
 
294
ensure_removed([File|Files]) ->
 
295
    file:delete(File),
 
296
    ensure_removed(Files);
 
297
ensure_removed([]) ->
 
298
    ok.
 
299
 
 
300
ensure_no_messages() ->
 
301
    ensure_no_messages(0).
 
302
 
 
303
ensure_no_messages(N) ->
 
304
    receive
 
305
        Any ->
 
306
            io:format("Unexpected message: ~p", [Any]),
 
307
            ensure_no_messages(N+1)
 
308
    after 0 ->
 
309
            case N of
 
310
                0 -> ok;
 
311
                N -> ?t:fail()
 
312
            end
 
313
    end.
 
314