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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer.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:
49
49
%%  - plt_info/1:       Get information of the specified plt.
50
50
%%--------------------------------------------------------------------
51
51
 
52
 
-spec(plain_cl/0 :: () -> no_return()).
 
52
-spec plain_cl() -> no_return().
53
53
 
54
54
plain_cl() ->
55
55
  case dialyzer_cl_parse:start() of
61
61
      try check_gui_options(Opts)
62
62
      catch throw:{dialyzer_error, Msg} -> cl_error(Msg)
63
63
      end,
64
 
      case cl_check_init(Opts) of
65
 
        {error, _} = Error -> gui_halt(Error, Opts);
66
 
        {ok, ?RET_NOTHING_SUSPICIOUS} ->
 
64
      case Opts#options.check_plt of
 
65
        true ->
 
66
          case cl_check_init(Opts#options{get_warnings=false}) of
 
67
            {error, _} = Error -> cl_halt(Error, Opts);
 
68
            {ok, _} -> gui_halt(internal_gui(Opts), Opts)
 
69
          end;
 
70
        false ->
67
71
          gui_halt(internal_gui(Opts), Opts)
68
72
      end;
69
73
    {cl, Opts} -> 
70
 
      case cl_check_init(Opts) of
71
 
        {error, _} = Error -> cl_halt(Error, Opts);
72
 
        {ok, ?RET_NOTHING_SUSPICIOUS} ->
 
74
      case Opts#options.check_plt of
 
75
        true ->
 
76
          case cl_check_init(Opts#options{get_warnings=false}) of
 
77
            {error, _} = Error -> cl_halt(Error, Opts);
 
78
            {ok, _} -> cl_halt(cl(Opts), Opts)
 
79
          end;
 
80
        false ->
73
81
          cl_halt(cl(Opts), Opts)
74
82
      end;
75
83
    {error, Msg} -> 
105
113
        Msg = io_lib:format("Could not read the plt file ~p\n", [Plt]),
106
114
        throw({dialyzer_error, Msg});
107
115
      {error, no_such_file} ->
108
 
        Msg = io_lib:format("The plt file ~p does not exist.\n", [Plt]),
 
116
        Msg = io_lib:format("The plt file ~p does not exist\n", [Plt]),
109
117
        throw({dialyzer_error, Msg})
110
118
    end,
111
119
  case Opts#options.output_file of
131
139
      end,
132
140
  doit(F).
133
141
 
134
 
-spec(run/1 :: (dial_options()) -> [dial_warning()]).
 
142
-spec run(dial_options()) -> [dial_warning()].
135
143
 
136
144
run(Opts) when length(Opts) > 0 ->
137
145
  try
161
169
      end,
162
170
  doit(F).
163
171
 
164
 
-spec(gui/0 :: () -> 'ok').
 
172
-spec gui() -> 'ok'.
165
173
 
166
174
gui() ->
167
175
  gui([]).
168
176
 
169
 
-spec(gui/1 :: (dial_options()) -> 'ok').
 
177
-spec gui(dial_options()) -> 'ok'.
170
178
 
171
179
gui(Opts) ->
172
180
  try
198
206
  Msg = io_lib:format("Analysis mode ~w is illegal in gui mode", [Mode]),
199
207
  throw({dialyzer_error, Msg}).
200
208
 
201
 
-spec(plt_info/1 :: (string()) -> {ok, [{'files', [string()]}]}
202
 
                                | {error, atom()}) .
 
209
-spec plt_info(string()) -> {ok, [{'files', [string()]}]} | {error, atom()}.
203
210
 
204
211
plt_info(Plt) ->
205
212
  case dialyzer_plt:included_files(Plt) of
226
233
gui_halt(R, Opts) ->
227
234
  cl_halt(R, Opts#options{report_mode=quiet}).
228
235
 
229
 
-spec(cl_halt/2 ::
230
 
      ({'ok',atom()} | {'error',string()}, #options{}) -> no_return()).
 
236
-spec cl_halt({'ok',dial_ret()} | {'error',string()}, #options{}) -> no_return().
231
237
 
232
238
cl_halt({ok, R = ?RET_NOTHING_SUSPICIOUS},  #options{report_mode=quiet}) -> 
233
239
  halt(R);
246
252
  cl_check_log(Output),
247
253
  halt(?RET_INTERNAL_ERROR).
248
254
 
249
 
-spec(cl_check_log/1 :: (string()) -> 'ok').
 
255
-spec cl_check_log(string()) -> 'ok'.
250
256
 
251
257
cl_check_log(none) ->
252
258
  ok;
253
259
cl_check_log(Output) ->
254
260
  io:format("  Check output file `~s' for details\n", [Output]).
255
261
 
256
 
-spec(format_warning/1 :: (dial_warning()) -> string()).
 
262
-spec format_warning(dial_warning()) -> string().
257
263
 
258
264
format_warning({_Tag, {File, Line}, Msg}) when is_list(File), 
259
265
                                               is_integer(Line) ->
285
291
message_to_string({improper_list_constr, [TlType]}) ->
286
292
  io_lib:format("Cons will produce an improper list since its "
287
293
                "2nd argument is ~s\n", [TlType]);
 
294
message_to_string({record_matching, [String, Name]}) ->
 
295
  io_lib:format("The ~s violates the "
 
296
                "declared type for #~w{}\n", [String, Name]);
288
297
message_to_string({record_constr, [Types, Name]}) ->
289
298
  io_lib:format("Record construction ~s violates the "
290
299
                "declared type for #~w{}\n", [Types, Name]);
301
310
message_to_string({guard_fail, []}) ->
302
311
  "Clause guard cannot succeed.\n";
303
312
message_to_string({guard_fail, [Arg1, Infix, Arg2]}) ->
304
 
  io_lib:format("Guard test ~s ~s ~s can never succeed.\n",
 
313
  io_lib:format("Guard test ~s ~s ~s can never succeed\n",
305
314
                [Arg1, Infix, Arg2]);
306
315
message_to_string({guard_fail, [Guard, Args]}) ->
307
316
  io_lib:format("Guard test ~w~s can never succeed\n", [Guard, Args]);
325
334
  end;
326
335
message_to_string({spec_missing_fun, [M, F, A]}) ->
327
336
  io_lib:format("Contract for function that does not exist: ~w:~w/~w\n",
328
 
                [M,F,A]);
 
337
                [M, F, A]);
329
338
message_to_string({invalid_contract, [M, F, A, Sig]}) ->
330
339
  io_lib:format("Invalid type specification for function ~w:~w/~w. "
331
340
                "The success typing is ~s\n", 
332
341
                [M, F, A, Sig]);
333
342
message_to_string({overlapping_contract, []}) ->
334
343
  "Overloaded contract has overlapping domains;"
335
 
    " such contracts are currently unsupported and are simply ignored \n";
 
344
    " such contracts are currently unsupported and are simply ignored\n";
336
345
message_to_string({contract_subtype, [M, F, A, Contract, Sig]}) ->
337
346
  io_lib:format("Type specification ~w:~w/~w :: ~s "
338
347
                "is a subtype of the success typing: ~s\n", 
339
348
                [M, F, A, Contract, Sig]);
340
349
message_to_string({contract_supertype, [M, F, A, Contract, Sig]}) ->
341
350
  io_lib:format("Type specification ~w:~w/~w :: ~s "
342
 
                "is a supertype of the success typing: ~s\n", 
 
351
                "is a supertype of the success typing: ~s\n",
343
352
                [M, F, A, Contract, Sig]);
344
353
message_to_string({contract_diff, [M, F, A, Contract, Sig]}) ->
345
354
  io_lib:format("Type specification ~w:~w/~w :: ~s "
346
 
                "is not equal to the success typing: ~s\n", 
 
355
                "is not equal to the success typing: ~s\n",
347
356
                [M, F, A, Contract, Sig]);
348
357
message_to_string({call_to_missing, [M, F, A]}) ->
349
358
  io_lib:format("Call to missing or unexported function ~w:~w/~w\n", [M, F, A]);
366
375
    only_sig ->
367
376
      case ArgNs =:= [] of
368
377
        true -> 
369
 
          %% We do not know which arguments that caused the failure. 
370
 
          io_lib:format("will fail since the success typing arguments"
 
378
          %% We do not know which arguments caused the failure. 
 
379
          io_lib:format("will never return since the success typing arguments"
371
380
                        " are ~s\n", [SigArgs]);
372
381
        false ->
373
 
          io_lib:format("will fail since it differs in argument" 
 
382
          io_lib:format("will never return since it differs in argument" 
374
383
                        " ~s from the success typing arguments: ~s\n", 
375
384
                        [PositionString, SigArgs])
376
385
      end;
377
386
    only_contract -> 
378
387
      case (ArgNs =:= []) orelse IsOverloaded of
379
388
        true ->
380
 
          %% We do not know which arguments that caused the failure. 
 
389
          %% We do not know which arguments caused the failure. 
381
390
          io_lib:format("breaks the contract ~s\n", [Contract]);
382
391
        false ->
383
392
          io_lib:format("breaks the contract ~s in argument ~s\n",
384
393
                        [Contract, PositionString])
385
394
      end;
386
395
    both  ->
387
 
      io_lib:format("will fail since the success typing is ~s -> ~s and "
388
 
                    "the contract is ~s\n", [SigArgs, SigRet, Contract])
 
396
      io_lib:format("will never return since the success typing is ~s -> ~s"
 
397
                    " and the contract is ~s\n", [SigArgs, SigRet, Contract])
389
398
  end.