~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_cl_parse.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
25
25
 
26
26
%%-----------------------------------------------------------------------
27
27
 
28
 
-type(dial_cl_parse_ret() :: {'check_init',#options{}}
 
28
-type dial_cl_parse_ret() :: {'check_init',#options{}}
29
29
                           | {'plt_info', #options{}}
30
30
                           | {'cl',#options{}}
31
31
                           | {'gui',#options{}} 
32
 
                           | {'error',string()}).
 
32
                           | {'error',string()}.
33
33
 
34
34
%%-----------------------------------------------------------------------
35
35
 
36
 
-spec(start/0 :: () -> dial_cl_parse_ret()).
 
36
-spec start() -> dial_cl_parse_ret().
37
37
 
38
38
start() ->
39
39
  init(),
59
59
  put(dialyzer_options_mode, cl),
60
60
  put(dialyzer_options_analysis_type, plt_check),
61
61
  cl(T);
 
62
cl(["--no_check_plt"|T]) ->
 
63
  put(dialyzer_options_check_plt, false),
 
64
  cl(T);
62
65
cl(["--plt_info"|T]) ->
63
66
  put(dialyzer_options_mode, cl),
64
67
  put(dialyzer_options_analysis_type, plt_info),
191
194
    OptsRecord -> {RetTag, OptsRecord}
192
195
  end.
193
196
 
 
197
%%-----------------------------------------------------------------------
194
198
 
195
199
command_line(T0) ->
196
200
  {Args,T} = collect_args(T0),
217
221
  put(dialyzer_options_defines,         DefaultOpts#options.defines),
218
222
  put(dialyzer_options_files,           DefaultOpts#options.files),
219
223
  put(dialyzer_output_format,           formatted),
 
224
  put(dialyzer_options_check_plt,       DefaultOpts#options.check_plt),
220
225
  ok.
221
226
 
222
227
append_defines([Def, Val]) ->
235
240
 
236
241
%%-----------------------------------------------------------------------
237
242
 
238
 
-spec(collect_args/1 :: ([string()]) -> {[string()],[string()]}).
 
243
-spec collect_args([string()]) -> {[string()], [string()]}.
239
244
 
240
245
collect_args(List) ->
241
246
  collect_args_1(List, []).
242
247
 
243
248
collect_args_1(["-"++_|_]=L, Acc) ->
244
 
  {lists:reverse(Acc),L};
 
249
  {lists:reverse(Acc), L};
245
250
collect_args_1([Arg|T], Acc) ->
246
251
  collect_args_1(T, [Arg|Acc]);
247
252
collect_args_1([], Acc) ->
248
 
  {lists:reverse(Acc),[]}.
 
253
  {lists:reverse(Acc), []}.
249
254
 
250
255
%%-----------------------------------------------------------------------
251
256
 
252
257
cl_options() ->
253
 
  [{files,get(dialyzer_options_files)},
254
 
   {files_rec,get(dialyzer_options_files_rec)},
255
 
   {output_file,get(dialyzer_output)},
256
 
   {output_format,get(dialyzer_output_format)},
 
258
  [{files, get(dialyzer_options_files)},
 
259
   {files_rec, get(dialyzer_options_files_rec)},
 
260
   {output_file, get(dialyzer_output)},
 
261
   {output_format, get(dialyzer_output_format)},
257
262
   {analysis_type, get(dialyzer_options_analysis_type)},
258
263
   {get_warnings, get(dialyzer_options_get_warnings)}
259
264
   |common_options()].
266
271
   {output_plt, get(dialyzer_output_plt)},
267
272
   {report_mode, get(dialyzer_options_report_mode)},
268
273
   {use_spec, get(dialyzer_options_use_contracts)},
269
 
   {warnings, get(dialyzer_warnings)}].
 
274
   {warnings, get(dialyzer_warnings)},
 
275
   {check_plt, get(dialyzer_options_check_plt)}].
270
276
 
271
277
%%-----------------------------------------------------------------------
272
278
 
299
305
                [-pa dir]* [--plt plt] [-Ddefine]* [-I include_dir]* 
300
306
                [--output_plt file] [-Wwarn]* [--src] 
301
307
                [-c applications] [-r applications] [-o outfile]
302
 
                [--build_plt] [--add_to_plt] [--remove_from_plt] [--check_plt]
303
 
                [--plt_info] [--get_warnings]
 
308
                [--build_plt] [--add_to_plt] [--remove_from_plt]
 
309
                [--check_plt] [--no_check_plt] [--plt_info] [--get_warnings]
304
310
Options: 
305
311
   -c applications (or --command-line applications)
306
312
       Use Dialyzer from the command line (no GUI) to detect defects in the
361
367
       dependent files.
362
368
   --check_plt
363
369
       Checks the plt for consistency and rebuilds it if it is not up-to-date.
 
370
   --no_check_plt
 
371
       Skip the plt check when running Dialyzer. Useful when working with
 
372
       installed plts that never change.
364
373
   --plt_info
365
374
       Makes Dialyzer print information about the plt and then quit. The plt 
366
375
       can be specified with --plt.