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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/dialyzer_common.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
%%% File        : dialyzer_common.erl
 
2
%%% Author      : Stavros Aronis <aronisstav@gmail.com>
 
3
%%% Description : Generator and common infrastructure for simple dialyzer
 
4
%%%               test suites (some options, some input files or directories
 
5
%%%               and the relevant results).
 
6
%%% Created     : 11 Jun 2010 by Stavros Aronis <stavros@enjoy>
 
7
 
 
8
-module(dialyzer_common).
 
9
 
 
10
-export([check_plt/1, check/4, create_suite/1,
 
11
         create_all_suites/0, new_tests/2]).
 
12
 
 
13
-include_lib("kernel/include/file.hrl").
 
14
 
 
15
-define(suite_suffix, "_tests_SUITE").
 
16
-define(data_folder, "_data").
 
17
-define(erlang_extension, ".erl").
 
18
-define(output_file_mode, write).
 
19
-define(dialyzer_option_file, "dialyzer_options").
 
20
-define(input_files_directory, "src").
 
21
-define(result_files_directory, "results").
 
22
-define(plt_filename,"dialyzer_plt").
 
23
-define(home_plt_filename,".dialyzer_plt").
 
24
-define(plt_lockfile,"plt_lock").
 
25
-define(required_modules, [erts, kernel, stdlib]).
 
26
 
 
27
-record(suite, {suitename  :: string(),
 
28
                outputfile :: file:io_device(),
 
29
                options    :: options(),
 
30
                testcases  :: [testcase()]}).
 
31
 
 
32
-record(options, {time_limit       =  1 :: integer(),
 
33
                  dialyzer_options = [] :: dialyzer:dial_options()}).
 
34
 
 
35
-type options() :: #options{}.
 
36
-type testcase() :: {atom(), 'file' | 'dir'}.
 
37
 
 
38
-spec check_plt(string()) -> ok.
 
39
 
 
40
check_plt(OutDir) ->
 
41
    io:format("Checking plt:"),
 
42
    PltFilename = filename:join(OutDir, ?plt_filename),
 
43
    case file:read_file_info(PltFilename) of
 
44
        {ok, _} -> dialyzer_check_plt(PltFilename);
 
45
        {error, _ } ->
 
46
            io:format("No plt found in test run directory!"),
 
47
            PltLockFile = filename:join(OutDir, ?plt_lockfile),
 
48
            case file:read_file_info(PltLockFile) of 
 
49
                {ok, _} ->
 
50
                    explain_fail_with_lock(),
 
51
                    fail;
 
52
                {error, _} ->
 
53
                    io:format("Locking plt generation."),
 
54
                    case file:open(PltLockFile,[?output_file_mode]) of
 
55
                        {ok, OutFile} ->
 
56
                            io:format(OutFile,"Locking plt generation.",[]),
 
57
                            file:close(OutFile);
 
58
                        {error, Reason} ->
 
59
                            io:format("Couldn't write lock file ~p.",[Reason]),
 
60
                            fail
 
61
                    end,
 
62
                    obtain_plt(PltFilename)
 
63
            end
 
64
    end.
 
65
 
 
66
dialyzer_check_plt(PltFilename) ->
 
67
    try dialyzer:run([{analysis_type, plt_check},
 
68
                      {init_plt, PltFilename}]) of
 
69
        [] -> ok
 
70
    catch
 
71
        Class:Info ->
 
72
            io:format("Failed. The error was: ~w\n~p",[Class, Info]),
 
73
            io:format("A previously run dialyzer suite failed to generate"
 
74
                      " a correct plt."),
 
75
            fail
 
76
    end.
 
77
 
 
78
explain_fail_with_lock() ->
 
79
    io:format("Some other suite started creating a plt. It might not have"
 
80
              " finished (Dialyzer's suites shouldn't run in parallel), or"
 
81
              " it reached timeout and was killed (in which case"
 
82
              " plt_timeout, defined in dialyzer_test_constants.hrl"
 
83
              " should be increased), or it failed.").
 
84
 
 
85
obtain_plt(PltFilename) ->
 
86
    io:format("Obtaining plt:"),
 
87
    HomeDir = os:getenv("HOME"),
 
88
    HomePlt = filename:join(HomeDir, ?home_plt_filename),
 
89
    io:format("Will try to use ~s as a starting point and add otp apps ~w.",
 
90
              [HomePlt, ?required_modules]),
 
91
    try dialyzer:run([{analysis_type, plt_add},
 
92
                      {apps, ?required_modules},
 
93
                      {output_plt, PltFilename},
 
94
                      {init_plt, HomePlt}]) of
 
95
        [] ->
 
96
            io:format("Successfully added everything!"),
 
97
            ok
 
98
    catch
 
99
        Class:Reason ->
 
100
            io:format("Failed. The error was: ~w\n~p",[Class, Reason]),
 
101
            build_plt(PltFilename)
 
102
    end.
 
103
 
 
104
build_plt(PltFilename) ->
 
105
    io:format("Building plt from scratch:"),
 
106
    try dialyzer:run([{analysis_type, plt_build},
 
107
                      {apps, ?required_modules},
 
108
                      {output_plt, PltFilename}]) of
 
109
        [] ->
 
110
            io:format("Successfully created plt!"),
 
111
            ok
 
112
    catch
 
113
        Class:Reason ->
 
114
            io:format("Failed. The error was: ~w\n~p",[Class, Reason]),
 
115
            fail
 
116
    end.
 
117
 
 
118
-spec check(atom(), dialyzer:dial_options(), string(), string()) ->
 
119
                   'same' | {differ, [term()]}.
 
120
 
 
121
check(TestCase, Opts, Dir, OutDir) ->
 
122
    PltFilename = filename:join(OutDir, ?plt_filename),
 
123
    SrcDir = filename:join(Dir, ?input_files_directory),
 
124
    ResDir = filename:join(Dir, ?result_files_directory),
 
125
    Filename = filename:join(SrcDir, atom_to_list(TestCase)),
 
126
    Files =
 
127
        case file_utils:file_type(Filename) of
 
128
            {ok, 'directory'} ->
 
129
                {ok, ListFiles} = file_utils:list_dir(Filename, ".erl",
 
130
                                                      false),
 
131
                ListFiles;
 
132
            {error, _} ->
 
133
                FilenameErl = Filename ++ ".erl",
 
134
                case file_utils:file_type(FilenameErl) of
 
135
                    {ok, 'regular'} -> [FilenameErl]
 
136
                end
 
137
        end,
 
138
    ResFile = atom_to_list(TestCase),
 
139
    NewResFile = filename:join(OutDir, ResFile),
 
140
    OldResFile = filename:join(ResDir, ResFile),
 
141
    ProperOpts = fix_options(Opts, Dir),
 
142
    try dialyzer:run([{files, Files},{from, src_code},{init_plt, PltFilename},
 
143
                      {check_plt, false}|ProperOpts]) of
 
144
        RawWarns ->
 
145
            Warns = lists:sort([dialyzer:format_warning(W) || W <- RawWarns]),
 
146
            case Warns of
 
147
                [] -> ok;
 
148
                _  ->
 
149
                    case file:open(NewResFile,[?output_file_mode]) of
 
150
                        {ok, OutFile} ->
 
151
                            io:format(OutFile,"\n~s",[Warns]),
 
152
                            file:close(OutFile);
 
153
                        Other -> erlang:error(Other)
 
154
                    end
 
155
            end,
 
156
            case file_utils:diff(NewResFile, OldResFile) of
 
157
                'same' -> file:delete(NewResFile),
 
158
                          'same';
 
159
                Any    -> escape_strings(Any)
 
160
            end
 
161
    catch
 
162
        Kind:Error -> {'dialyzer crashed', Kind, Error}
 
163
    end.
 
164
 
 
165
fix_options(Opts, Dir) ->
 
166
    fix_options(Opts, Dir, []).
 
167
 
 
168
fix_options([], _Dir, Acc) ->
 
169
    Acc;
 
170
fix_options([{pa, Path} | Rest], Dir, Acc) ->
 
171
    case code:add_patha(filename:join(Dir, Path)) of
 
172
        true       -> fix_options(Rest, Dir, Acc);
 
173
        {error, _} -> erlang:error("Bad directory for pa: " ++ Path)
 
174
    end;
 
175
fix_options([{DirOption, RelativeDirs} | Rest], Dir, Acc) 
 
176
  when DirOption =:= include_dirs ;
 
177
       DirOption =:= files_rec ;
 
178
       DirOption =:= files ->
 
179
    ProperRelativeDirs = [filename:join(Dir,RDir) || RDir <- RelativeDirs],
 
180
    fix_options(Rest, Dir, [{include_dirs, ProperRelativeDirs} | Acc]);
 
181
fix_options([Opt | Rest], Dir, Acc) ->
 
182
    fix_options(Rest, Dir, [Opt | Acc]).
 
183
 
 
184
-spec new_tests(string(), [atom()]) -> [atom()].
 
185
 
 
186
new_tests(Dirname, DeclaredTestcases) ->
 
187
    SrcDir = filename:join(Dirname, ?input_files_directory),
 
188
    get_testcases(SrcDir) -- DeclaredTestcases.
 
189
 
 
190
get_testcases(Dirname) ->
 
191
    {ok, Files} = file_utils:list_dir(Dirname, ".erl", true),
 
192
    [list_to_atom(filename:basename(F,".erl")) || F <-Files].
 
193
 
 
194
-spec create_all_suites() -> 'ok'.
 
195
 
 
196
create_all_suites() ->
 
197
    {ok, Cwd} = file:get_cwd(),
 
198
    Suites = get_suites(Cwd),
 
199
    lists:foreach(fun create_suite/1, Suites).
 
200
 
 
201
escape_strings({differ,List}) ->
 
202
    Map = fun({T,L,S}) -> {T,L,xmerl_lib:export_text(S)} end,
 
203
    {differ, lists:keysort(3, lists:map(Map, List))}.
 
204
 
 
205
-spec get_suites(file:filename()) -> [string()].
 
206
 
 
207
get_suites(Dir) ->
 
208
    case file:list_dir(Dir) of
 
209
        {error, _} -> [];
 
210
        {ok, Filenames} ->
 
211
            FullFilenames = [filename:join(Dir, F) || F <-Filenames ],
 
212
            Dirs = [suffix(filename:basename(F), "_tests_SUITE_data") ||
 
213
                       F <- FullFilenames,
 
214
                       file_utils:file_type(F) =:= {ok, 'directory'}],
 
215
            [S || {yes, S} <- Dirs]
 
216
    end.
 
217
 
 
218
suffix(String, Suffix) ->
 
219
    Index = string:rstr(String, Suffix),
 
220
    case string:substr(String, Index) =:= Suffix of
 
221
        true -> {yes, string:sub_string(String,1,Index-1)};
 
222
        false -> no
 
223
    end.
 
224
 
 
225
-spec create_suite(string()) -> 'ok'.
 
226
 
 
227
create_suite(SuiteName) ->
 
228
    {ok, Cwd} = file:get_cwd(),
 
229
    SuiteDirN = generate_suite_dir_from_name(Cwd, SuiteName),
 
230
    OutputFile = generate_suite_file(Cwd, SuiteName),
 
231
    {OptionsFileN, InputDirN} = check_neccessary_files(SuiteDirN),
 
232
    generate_suite(SuiteName, OutputFile, OptionsFileN, InputDirN).
 
233
 
 
234
generate_suite_dir_from_name(Cwd, SuiteName) ->
 
235
    filename:join(Cwd, SuiteName ++ ?suite_suffix ++ ?data_folder).
 
236
 
 
237
generate_suite_file(Cwd, SuiteName) ->
 
238
    OutputFilename =
 
239
        filename:join(Cwd, SuiteName ++ ?suite_suffix ++ ?erlang_extension),
 
240
    case file:open(OutputFilename, [?output_file_mode]) of
 
241
        {ok, IoDevice} -> IoDevice;
 
242
        {error, _} = E -> exit({E, OutputFilename})
 
243
    end.
 
244
 
 
245
check_neccessary_files(SuiteDirN) ->
 
246
    InputDirN = filename:join(SuiteDirN, ?input_files_directory),
 
247
    check_file_exists(InputDirN, directory),
 
248
    OptionsFileN = filename:join(SuiteDirN, ?dialyzer_option_file),
 
249
    check_file_exists(OptionsFileN, regular),
 
250
    {OptionsFileN, InputDirN}.
 
251
 
 
252
check_file_exists(Filename, Type) ->
 
253
    case file:read_file_info(Filename) of
 
254
        {ok, FileInfo} ->
 
255
            case FileInfo#file_info.type of
 
256
                Type -> ok;
 
257
                Else -> exit({error, {wrong_input_file_type, Else}})
 
258
            end;
 
259
        {error, _} = E -> exit({E, Filename, Type})
 
260
    end.
 
261
 
 
262
generate_suite(SuiteName, OutputFile, OptionsFileN, InputDirN) ->
 
263
    Options = read_options(OptionsFileN),
 
264
    TestCases = list_testcases(InputDirN),
 
265
    Suite = #suite{suitename = SuiteName, outputfile = OutputFile,
 
266
                   options = Options, testcases = TestCases},
 
267
    write_suite(Suite),
 
268
    file:close(OutputFile).
 
269
 
 
270
read_options(OptionsFileN) ->
 
271
    case file:consult(OptionsFileN) of
 
272
        {ok, Opts} -> read_options(Opts, #options{});
 
273
        _ = E      -> exit({error, {incorrect_options_file, E}})
 
274
    end.
 
275
 
 
276
read_options([List], Options) when is_list(List) ->
 
277
    read_options(List, Options);
 
278
read_options([], Options) ->
 
279
    Options;
 
280
read_options([{time_limit, TimeLimit}|Opts], Options) ->
 
281
    read_options(Opts, Options#options{time_limit = TimeLimit});
 
282
read_options([{dialyzer_options, DialyzerOptions}|Opts], Options) ->
 
283
    read_options(Opts, Options#options{dialyzer_options = DialyzerOptions}).
 
284
 
 
285
list_testcases(Dirname) ->
 
286
    {ok, Files} = file_utils:list_dir(Dirname, ".erl", true),
 
287
    [list_to_atom(filename:basename(F,".erl")) || F <-Files].
 
288
 
 
289
write_suite(Suite) ->
 
290
    write_header(Suite),
 
291
    write_consistency(Suite),
 
292
    write_testcases(Suite).
 
293
 
 
294
write_header(#suite{suitename = SuiteName, outputfile = OutputFile,
 
295
                    options = Options, testcases = TestCases}) ->
 
296
    Test_Plus_Consistency =
 
297
        [list_to_atom(SuiteName ++ ?suite_suffix ++ "_consistency")|TestCases],
 
298
    Exports = format_export(Test_Plus_Consistency),
 
299
    TimeLimit = Options#options.time_limit,
 
300
    DialyzerOptions = Options#options.dialyzer_options,
 
301
    io:format(OutputFile,
 
302
              "%% ATTENTION!\n"
 
303
              "%% This is an automatically generated file. Do not edit.\n"
 
304
              "%% Use './remake' script to refresh it if needed.\n"
 
305
              "%% All Dialyzer options should be defined in dialyzer_options\n"
 
306
              "%% file.\n\n"
 
307
              "-module(~s).\n\n"
 
308
              "-include(\"ct.hrl\").\n"
 
309
              "-include(\"dialyzer_test_constants.hrl\").\n\n"
 
310
              "-export([suite/0, init_per_suite/0, init_per_suite/1,\n"
 
311
              "         end_per_suite/1, all/0]).\n"
 
312
              "~s\n\n"
 
313
              "suite() ->\n"
 
314
              "  [{timetrap, {minutes, ~w}}].\n\n"
 
315
              "init_per_suite() ->\n"
 
316
              "  [{timetrap, ?plt_timeout}].\n"
 
317
              "init_per_suite(Config) ->\n"
 
318
              "  OutDir = ?config(priv_dir, Config),\n"
 
319
              "  case dialyzer_common:check_plt(OutDir) of\n"
 
320
              "    fail -> {skip, \"Plt creation/check failed.\"};\n"
 
321
              "    ok -> [{dialyzer_options, ~p}|Config]\n"
 
322
              "  end.\n\n"
 
323
              "end_per_suite(_Config) ->\n"
 
324
              "  ok.\n\n"
 
325
              "all() ->\n"
 
326
              "  ~p.\n\n"
 
327
              "dialyze(Config, TestCase) ->\n"
 
328
              "  Opts = ?config(dialyzer_options, Config),\n"
 
329
              "  Dir = ?config(data_dir, Config),\n"
 
330
              "  OutDir = ?config(priv_dir, Config),\n"
 
331
              "  dialyzer_common:check(TestCase, Opts, Dir, OutDir)."
 
332
              "\n\n"
 
333
              ,[SuiteName ++ ?suite_suffix, Exports, TimeLimit,
 
334
                DialyzerOptions, Test_Plus_Consistency]).
 
335
 
 
336
format_export(TestCases) ->
 
337
    TestCasesArity =
 
338
        [list_to_atom(atom_to_list(N)++"/1") || N <- TestCases],
 
339
    TestCaseString = io_lib:format("-export(~p).", [TestCasesArity]),
 
340
    strip_quotes(lists:flatten(TestCaseString),[]).
 
341
 
 
342
strip_quotes([], Result) ->
 
343
    lists:reverse(Result);
 
344
strip_quotes([$' |Rest], Result) ->
 
345
    strip_quotes(Rest, Result);
 
346
strip_quotes([$\, |Rest], Result) ->
 
347
    strip_quotes(Rest, [$\ , $\, |Result]);
 
348
strip_quotes([C|Rest], Result) ->
 
349
    strip_quotes(Rest, [C|Result]).
 
350
 
 
351
write_consistency(#suite{suitename = SuiteName, outputfile = OutputFile}) ->
 
352
    write_consistency(SuiteName, OutputFile).
 
353
 
 
354
write_consistency(SuiteName, OutputFile) ->
 
355
    io:format(OutputFile,
 
356
              "~s_consistency(Config) ->\n"
 
357
              "  Dir = ?config(data_dir, Config),\n"
 
358
              "  case dialyzer_common:new_tests(Dir, all()) of\n"
 
359
              "    []  -> ok;\n"
 
360
              "    New -> ct:fail({missing_tests,New})\n"
 
361
              "  end.\n\n",
 
362
              [SuiteName ++ ?suite_suffix]).
 
363
 
 
364
write_testcases(#suite{outputfile = OutputFile, testcases = TestCases}) ->
 
365
    write_testcases(OutputFile, TestCases).
 
366
 
 
367
write_testcases(OutputFile, [TestCase| Rest]) ->
 
368
    io:format(OutputFile,
 
369
              "~p(Config) ->\n"
 
370
              "  case dialyze(Config, ~p) of\n"
 
371
              "    'same' -> 'same';\n"
 
372
              "    Error  -> ct:fail(Error)\n"
 
373
              "  end.\n\n",
 
374
              [TestCase, TestCase]),
 
375
    write_testcases(OutputFile, Rest);
 
376
write_testcases(_OutputFile, []) ->
 
377
    ok.