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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_cl_parse.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
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%-----------------------------------------------------------------------
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
 
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
%%
20
20
 
21
21
-module(dialyzer_cl_parse).
22
22
 
23
 
-export([start/0]).
24
 
-export([collect_args/1]).      % used also by typer_options.erl
 
23
-export([start/0, get_lib_dir/1]).
 
24
-export([collect_args/1]).      % used also by typer
25
25
 
26
26
-include("dialyzer.hrl").
27
27
 
30
30
-type dial_cl_parse_ret() :: {'check_init', #options{}}
31
31
                           | {'plt_info', #options{}}
32
32
                           | {'cl', #options{}}
33
 
                           | {{'gui', 'gs' | 'wx'}, #options{}} 
 
33
                           | {{'gui', 'gs' | 'wx'}, #options{}}
34
34
                           | {'error', string()}.
35
35
 
 
36
-type deep_string() :: string() | [deep_string()].
 
37
 
36
38
%%-----------------------------------------------------------------------
37
39
 
38
40
-spec start() -> dial_cl_parse_ret().
53
55
  put(dialyzer_options_analysis_type, plt_add),
54
56
  cl(T);
55
57
cl(["--apps"|T]) ->
56
 
  T1 = get_lib_dir(T, []),
 
58
  T1 = get_lib_dir(T),
57
59
  {Args, T2} = collect_args(T1),
58
60
  append_var(dialyzer_options_files_rec, Args),
59
61
  cl(T2);
68
70
cl(["--no_check_plt"|T]) ->
69
71
  put(dialyzer_options_check_plt, false),
70
72
  cl(T);
 
73
cl(["-nn"|T]) ->
 
74
  cl(["--no_native"|T]);
 
75
cl(["--no_native"|T]) ->
 
76
  put(dialyzer_options_native, false),
 
77
  cl(T);
71
78
cl(["--plt_info"|T]) ->
72
79
  put(dialyzer_options_analysis_type, plt_info),
73
80
  cl(T);
75
82
  put(dialyzer_options_get_warnings, true),
76
83
  cl(T);
77
84
cl(["-D"|_]) ->
78
 
  error("No defines specified after -D");
 
85
  cl_error("No defines specified after -D");
79
86
cl(["-D"++Define|T]) ->
80
87
  Def = re:split(Define, "=", [{return, list}]),
81
88
  append_defines(Def),
85
92
cl(["--help"|_]) ->
86
93
  help_message();
87
94
cl(["-I"]) ->
88
 
  error("no include directory specified after -I");
 
95
  cl_error("no include directory specified after -I");
89
96
cl(["-I", Dir|T]) ->
90
97
  append_include(Dir),
91
98
  cl(T);
106
113
  NewTail = command_line(T),
107
114
  cl(NewTail);
108
115
cl(["--output"]) ->
109
 
  error("No outfile specified");
 
116
  cl_error("No outfile specified");
110
117
cl(["-o"]) ->
111
 
  error("No outfile specified");
 
118
  cl_error("No outfile specified");
112
119
cl(["--output",Output|T]) ->
113
120
  put(dialyzer_output, Output),
114
121
  cl(T);
115
122
cl(["--output_plt"]) ->
116
 
  error("No outfile specified for --output_plt");
 
123
  cl_error("No outfile specified for --output_plt");
117
124
cl(["--output_plt",Output|T]) ->
118
125
  put(dialyzer_output_plt, Output),
119
126
  cl(T);
126
133
cl(["--raw"|T]) ->
127
134
  put(dialyzer_output_format, raw),
128
135
  cl(T);
 
136
cl(["--fullpath"|T]) ->
 
137
  put(dialyzer_filename_opt, fullpath),
 
138
  cl(T);
129
139
cl(["-pa", Path|T]) ->
130
140
  case code:add_patha(Path) of
131
141
    true -> cl(T);
132
 
    {error, _} -> error("Bad directory for -pa: "++Path)
 
142
    {error, _} -> cl_error("Bad directory for -pa: " ++ Path)
133
143
  end;
134
 
cl(["--plt", PLT|T]) ->
135
 
  put(dialyzer_init_plt, PLT),
136
 
  cl(T);
137
144
cl(["--plt"]) ->
138
145
  error("No plt specified for --plt");
 
146
cl(["--plt", PLT|T]) ->
 
147
  put(dialyzer_init_plts, [PLT]),
 
148
  cl(T);
 
149
cl(["--plts"]) ->
 
150
  error("No plts specified for --plts");
 
151
cl(["--plts"|T]) ->
 
152
  {PLTs, NewT} = get_plts(T, []),
 
153
  put(dialyzer_init_plts, PLTs),
 
154
  cl(NewT);
139
155
cl(["-q"|T]) ->
140
156
  put(dialyzer_options_report_mode, quiet),
141
157
  cl(T);
158
174
  put(dialyzer_options_report_mode, verbose),
159
175
  cl(T);
160
176
cl(["-W"|_]) ->
161
 
  error("-W given without warning");
 
177
  cl_error("-W given without warning");
162
178
cl(["-Whelp"|_]) ->
163
179
  help_warnings();
164
180
cl(["-W"++Warn|T]) ->
165
181
  append_var(dialyzer_warnings, [list_to_atom(Warn)]),
166
182
  cl(T);
167
183
cl(["--dump_callgraph"]) ->
168
 
  error("No outfile specified for --dump_callgraph");
 
184
  cl_error("No outfile specified for --dump_callgraph");
169
185
cl(["--dump_callgraph", File|T]) ->
170
186
  put(dialyzer_callgraph_file, File),
171
187
  cl(T);
181
197
      NewTail = command_line(L),
182
198
      cl(NewTail);
183
199
    false ->
184
 
      error("Unknown option: "++H)
 
200
      cl_error("Unknown option: " ++ H)
185
201
  end;
186
202
cl([]) ->
187
203
  {RetTag, Opts} =
191
207
        {plt_info, cl_options()};
192
208
      false ->
193
209
        case get(dialyzer_options_mode) of
194
 
          {gui,_} = GUI -> {GUI, common_options()};
 
210
          {gui, _} = GUI -> {GUI, common_options()};
195
211
          cl ->
196
212
            case get(dialyzer_options_analysis_type) =:= plt_check of
197
213
              true  -> {check_init, cl_options()};
200
216
        end
201
217
    end,
202
218
  case dialyzer_options:build(Opts) of
203
 
    {error, Msg} -> error(Msg);
 
219
    {error, Msg} -> cl_error(Msg);
204
220
    OptsRecord -> {RetTag, OptsRecord}
205
221
  end.
206
222
 
216
232
  end,
217
233
  T.
218
234
 
219
 
error(Str) ->
 
235
-spec cl_error(deep_string()) -> no_return().
 
236
 
 
237
cl_error(Str) ->
220
238
  Msg = lists:flatten(Str),
221
239
  throw({dialyzer_cl_parse_error, Msg}).
222
240
 
230
248
  put(dialyzer_options_defines,   DefaultOpts#options.defines),
231
249
  put(dialyzer_options_files,     DefaultOpts#options.files),
232
250
  put(dialyzer_output_format,     formatted),
 
251
  put(dialyzer_filename_opt,      basename),
233
252
  put(dialyzer_options_check_plt, DefaultOpts#options.check_plt),
234
253
  ok.
235
254
 
268
287
   {files_rec, get(dialyzer_options_files_rec)},
269
288
   {output_file, get(dialyzer_output)},
270
289
   {output_format, get(dialyzer_output_format)},
 
290
   {filename_opt, get(dialyzer_filename_opt)},
271
291
   {analysis_type, get(dialyzer_options_analysis_type)},
272
292
   {get_warnings, get(dialyzer_options_get_warnings)},
273
293
   {callgraph_file, get(dialyzer_callgraph_file)}
277
297
  [{defines, get(dialyzer_options_defines)},
278
298
   {from, get(dialyzer_options_from)},
279
299
   {include_dirs, get(dialyzer_include)},
280
 
   {init_plt, get(dialyzer_init_plt)},
 
300
   {plts, get(dialyzer_init_plts)},
281
301
   {output_plt, get(dialyzer_output_plt)},
282
302
   {report_mode, get(dialyzer_options_report_mode)},
283
303
   {use_spec, get(dialyzer_options_use_contracts)},
286
306
 
287
307
%%-----------------------------------------------------------------------
288
308
 
 
309
-spec get_lib_dir([string()]) -> [string()].
 
310
 
 
311
get_lib_dir(Apps) ->
 
312
  get_lib_dir(Apps, []).
 
313
 
289
314
get_lib_dir([H|T], Acc) ->
290
315
  NewElem =
291
316
    case code:lib_dir(list_to_atom(H)) of
302
327
 
303
328
%%-----------------------------------------------------------------------
304
329
 
 
330
get_plts(["--"|T], Acc) -> {lists:reverse(Acc), T};
 
331
get_plts(["-"++_Opt = H|T], Acc) -> {lists:reverse(Acc), [H|T]};
 
332
get_plts([H|T], Acc) -> get_plts(T, [H|Acc]);
 
333
get_plts([], Acc) -> {lists:reverse(Acc), []}.
 
334
 
 
335
%%-----------------------------------------------------------------------
 
336
 
 
337
-spec help_warnings() -> no_return().
 
338
 
305
339
help_warnings() ->
306
340
  S = warning_options_msg(),
307
341
  io:put_chars(S),
308
342
  erlang:halt(?RET_NOTHING_SUSPICIOUS).
309
343
 
 
344
-spec help_message() -> no_return().
 
345
 
310
346
help_message() ->
311
347
  S = "Usage: dialyzer [--help] [--version] [--shell] [--quiet] [--verbose]
312
 
                [-pa dir]* [--plt plt] [-Ddefine]* [-I include_dir]* 
313
 
                [--output_plt file] [-Wwarn]* [--src] [--gui | --wx]
314
 
                [-c applications] [-r applications] [-o outfile]
 
348
                [-pa dir]* [--plt plt] [--plts plt*] [-Ddefine]*
 
349
                [-I include_dir]* [--output_plt file] [-Wwarn]*
 
350
                [--src] [--gui | --wx] [files_or_dirs] [-r dirs]
 
351
                [--apps applications] [-o outfile]
315
352
                [--build_plt] [--add_to_plt] [--remove_from_plt]
316
 
                [--check_plt] [--no_check_plt] [--plt_info] [--get_warnings]
317
 
Options: 
318
 
  -c applications (or --command-line applications)
319
 
      Use Dialyzer from the command line (no GUI) to detect defects in the
320
 
      specified applications (directories or .erl or .beam files)
321
 
  -r applications
322
 
      Same as -c only that directories are searched recursively for 
323
 
      subdirectories containing .erl or .beam files (depending on the 
324
 
      type of analysis)
 
353
                [--check_plt] [--no_check_plt] [--plt_info] [--get_warnings]
 
354
                [--no_native] [--fullpath]
 
355
Options:
 
356
  files_or_dirs (for backwards compatibility also as: -c files_or_dirs)
 
357
      Use Dialyzer from the command line to detect defects in the
 
358
      specified files or directories containing .erl or .beam files,
 
359
      depending on the type of the analysis.
 
360
  -r dirs
 
361
      Same as the previous but the specified directories are searched
 
362
      recursively for subdirectories containing .erl or .beam files in
 
363
      them, depending on the type of analysis.
 
364
  --apps applications
 
365
      Option typically used when building or modifying a plt as in:
 
366
        dialyzer --build_plt --apps erts kernel stdlib mnesia ...
 
367
      to conveniently refer to library applications corresponding to the
 
368
      Erlang/OTP installation. However, the option is general and can also
 
369
      be used during analysis in order to refer to Erlang/OTP applications.
 
370
      In addition, file or directory names can also be included, as in:
 
371
        dialyzer --apps inets ssl ./ebin ../other_lib/ebin/my_module.beam
325
372
  -o outfile (or --output outfile)
326
373
      When using Dialyzer from the command line, send the analysis
327
 
      results to the specified \"outfile\" rather than to stdout
 
374
      results to the specified outfile rather than to stdout.
328
375
  --raw
329
376
      When using Dialyzer from the command line, output the raw analysis
330
377
      results (Erlang terms) instead of the formatted result.
331
378
      The raw format is easier to post-process (for instance, to filter
332
 
      warnings or to output HTML pages)
 
379
      warnings or to output HTML pages).
333
380
  --src
334
381
      Override the default, which is to analyze BEAM files, and
335
 
      analyze starting from Erlang source code instead
 
382
      analyze starting from Erlang source code instead.
336
383
  -Dname (or -Dname=value)
337
 
      When analyzing from source, pass the define to Dialyzer (**)
 
384
      When analyzing from source, pass the define to Dialyzer. (**)
338
385
  -I include_dir
339
 
      When analyzing from source, pass the include_dir to Dialyzer (**)
 
386
      When analyzing from source, pass the include_dir to Dialyzer. (**)
340
387
  -pa dir
341
388
      Include dir in the path for Erlang (useful when analyzing files
342
 
      that have '-include_lib()' directives)
 
389
      that have '-include_lib()' directives).
343
390
  --output_plt file
344
 
      Store the plt at the specified file after building it
 
391
      Store the plt at the specified file after building it.
345
392
  --plt plt
346
393
      Use the specified plt as the initial plt (if the plt was built 
347
 
      during setup the files will be checked for consistency)
 
394
      during setup the files will be checked for consistency).
 
395
  --plts plt*
 
396
      Merge the specified plts to create the initial plt -- requires
 
397
      that the plts are disjoint (i.e., do not have any module
 
398
      appearing in more than one plt).
 
399
      The plts are created in the usual way:
 
400
        dialyzer --build_plt --output_plt plt_1 files_to_include
 
401
        ...
 
402
        dialyzer --build_plt --output_plt plt_n files_to_include
 
403
      and then can be used in either of the following ways:
 
404
        dialyzer files_to_analyze --plts plt_1 ... plt_n
 
405
      or:
 
406
        dialyzer --plts plt_1 ... plt_n -- files_to_analyze
 
407
      (Note the -- delimiter in the second case)
348
408
  -Wwarn
349
409
      A family of options which selectively turn on/off warnings
350
 
      (for help on the names of warnings use dialyzer -Whelp)
 
410
      (for help on the names of warnings use dialyzer -Whelp).
351
411
  --shell
352
 
      Do not disable the Erlang shell while running the GUI
 
412
      Do not disable the Erlang shell while running the GUI.
353
413
  --version (or -v)
354
 
      Prints the Dialyzer version and some more information and exits
 
414
      Print the Dialyzer version and some more information and exit.
355
415
  --help (or -h)
356
 
      Prints this message and exits
 
416
      Print this message and exit.
357
417
  --quiet (or -q)
358
 
      Makes Dialyzer a bit more quiet
 
418
      Make Dialyzer a bit more quiet.
359
419
  --verbose
360
 
      Makes Dialyzer a bit more verbose
 
420
      Make Dialyzer a bit more verbose.
361
421
  --build_plt
362
422
      The analysis starts from an empty plt and creates a new one from the
363
423
      files specified with -c and -r. Only works for beam files.
364
 
      Use --plt or --output_plt to override the default plt location.
 
424
      Use --plt(s) or --output_plt to override the default plt location.
365
425
  --add_to_plt
366
426
      The plt is extended to also include the files specified with -c and -r.
367
 
      Use --plt to specify wich plt to start from, and --output_plt to 
368
 
      specify where to put the plt. Note that the analysis might include 
369
 
      files from the plt if they depend on the new files. 
 
427
      Use --plt(s) to specify which plt to start from, and --output_plt to
 
428
      specify where to put the plt. Note that the analysis might include
 
429
      files from the plt if they depend on the new files.
370
430
      This option only works with beam files.
371
431
  --remove_from_plt
372
432
      The information from the files specified with -c and -r is removed
373
433
      from the plt. Note that this may cause a re-analysis of the remaining
374
434
      dependent files.
375
435
  --check_plt
376
 
      Checks the plt for consistency and rebuilds it if it is not up-to-date.
 
436
      Check the plt for consistency and rebuild it if it is not up-to-date.
377
437
      Actually, this option is of rare use as it is on by default.
378
438
  --no_check_plt (or -n)
379
439
      Skip the plt check when running Dialyzer. Useful when working with
380
440
      installed plts that never change.
381
441
  --plt_info
382
 
      Makes Dialyzer print information about the plt and then quit. The plt 
383
 
      can be specified with --plt.
 
442
      Make Dialyzer print information about the plt and then quit. The plt
 
443
      can be specified with --plt(s).
384
444
  --get_warnings
385
 
      Makes Dialyzer emit warnings even when manipulating the plt. Only 
386
 
      emits warnings for files that are actually analyzed.
 
445
      Make Dialyzer emit warnings even when manipulating the plt. Warnings
 
446
      are only emitted for files that are actually analyzed.
387
447
  --dump_callgraph file
388
448
      Dump the call graph into the specified file whose format is determined
389
449
      by the file name extension. Supported extensions are: raw, dot, and ps.
390
450
      If something else is used as file name extension, default format '.raw'
391
451
      will be used.
 
452
  --no_native (or -nn)
 
453
      Bypass the native code compilation of some key files that Dialyzer
 
454
      heuristically performs when dialyzing many files; this avoids the
 
455
      compilation time but it may result in (much) longer analysis time.
 
456
  --fullpath
 
457
      Display the full path names of files for which warnings are emitted.
392
458
  --gui
393
459
      Use the gs-based GUI.
394
460
  --wx
432
498
     Include warnings for functions that only return by means of an exception.
433
499
  -Wrace_conditions ***
434
500
     Include warnings for possible race conditions.
 
501
  -Wbehaviours ***
 
502
     Include warnings about behaviour callbacks which drift from the published
 
503
     recommended interfaces.
435
504
  -Wunderspecs ***
436
 
     Warn about underspecified functions 
 
505
     Warn about underspecified functions
437
506
     (those whose -spec is strictly more allowing than the success typing).
438
507
 
439
508
The following options are also available but their use is not recommended:
440
509
(they are mostly for Dialyzer developers and internal debugging)
441
510
  -Woverspecs ***
442
 
     Warn about overspecified functions 
 
511
     Warn about overspecified functions
443
512
     (those whose -spec is strictly less allowing than the success typing).
444
513
  -Wspecdiffs ***
445
514
     Warn when the -spec is different than the success typing.