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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_cl.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
 
29
29
 
30
30
-module(dialyzer_cl).
31
31
 
 
32
%% Avoid warning for local function error/1 clashing with autoimported BIF.
 
33
-compile({no_auto_import,[error/1]}).
 
34
%% Avoid warning for local function error/2 clashing with autoimported BIF.
 
35
-compile({no_auto_import,[error/2]}).
32
36
-export([start/1]).
33
37
 
34
38
-include("dialyzer.hrl").
38
42
        {backend_pid                      :: pid(),
39
43
         erlang_mode     = false          :: boolean(),
40
44
         external_calls  = []             :: [mfa()],
 
45
         external_types  = []             :: [mfa()],
41
46
         legal_warnings  = ordsets:new()  :: [dial_warn_tag()],
42
47
         mod_deps        = dict:new()     :: dict(),
43
48
         output          = standard_io    :: io:device(),
44
 
         output_format   = formatted      :: 'raw' | 'formatted',
 
49
         output_format   = formatted      :: format(),
 
50
         filename_opt    = basename       :: fopt(),
45
51
         output_plt      = none           :: 'none' | file:filename(),
46
52
         plt_info        = none           :: 'none' | dialyzer_plt:plt_info(),
47
53
         report_mode     = normal         :: rep_mode(),
48
54
         return_status= ?RET_NOTHING_SUSPICIOUS :: dial_ret(),
49
 
         stored_warnings = []             :: [dial_warning()]
 
55
         stored_warnings = []             :: [dial_warning()],
 
56
         unknown_behaviours = []          :: [dialyzer_behaviours:behaviour()]
50
57
        }).
51
58
 
52
59
%%--------------------------------------------------------------------
75
82
init_opts_for_build(Opts) ->
76
83
  case Opts#options.output_plt =:= none of
77
84
    true ->
78
 
      case Opts#options.init_plt of
79
 
        none -> Opts#options{init_plt = none, output_plt = get_default_plt()};
80
 
        Plt  -> Opts#options{init_plt = none, output_plt = Plt}
 
85
      case Opts#options.init_plts of
 
86
        [] -> Opts#options{output_plt = get_default_output_plt()};
 
87
        [Plt] -> Opts#options{init_plts = [], output_plt = Plt};
 
88
        Plts ->
 
89
          Msg = io_lib:format("Could not build multiple PLT files: ~s\n",
 
90
                              [format_plts(Plts)]),
 
91
          error(Msg)
81
92
      end;
82
 
    false -> Opts#options{init_plt = none}
 
93
    false -> Opts#options{init_plts = []}
83
94
  end.
84
95
 
85
96
%%--------------------------------------------------------------------
92
103
init_opts_for_add(Opts) ->
93
104
  case Opts#options.output_plt =:= none of
94
105
    true ->
95
 
      case Opts#options.init_plt of
96
 
        none -> Opts#options{output_plt = get_default_plt(),
97
 
                             init_plt = get_default_plt()};
98
 
        Plt  -> Opts#options{output_plt = Plt}
 
106
      case Opts#options.init_plts of
 
107
        [] -> Opts#options{output_plt = get_default_output_plt(),
 
108
                           init_plts = get_default_init_plt()};
 
109
        [Plt] -> Opts#options{output_plt = Plt};
 
110
        Plts ->
 
111
          Msg = io_lib:format("Could not add to multiple PLT files: ~s\n",
 
112
                              [format_plts(Plts)]),
 
113
          error(Msg)
99
114
      end;
100
115
    false ->
101
 
      case Opts#options.init_plt =:= none of
102
 
        true  -> Opts#options{init_plt = get_default_plt()};
 
116
      case Opts#options.init_plts =:= [] of
 
117
        true  -> Opts#options{init_plts = get_default_init_plt()};
103
118
        false -> Opts
104
119
      end
105
120
  end.
106
121
 
107
122
%%--------------------------------------------------------------------
108
123
 
109
 
check_plt(Opts) ->
 
124
check_plt(#options{init_plts = []} = Opts) ->
110
125
  Opts1 = init_opts_for_check(Opts),
111
 
  report_check(Opts),
112
 
  plt_common(Opts1, [], []).
 
126
  report_check(Opts1),
 
127
  plt_common(Opts1, [], []);
 
128
check_plt(#options{init_plts = Plts} = Opts) ->
 
129
  check_plt_aux(Plts, Opts).
 
130
 
 
131
check_plt_aux([_] = Plt, Opts) ->
 
132
  Opts1 = Opts#options{init_plts = Plt},
 
133
  Opts2 = init_opts_for_check(Opts1),
 
134
  report_check(Opts2),
 
135
  plt_common(Opts2, [], []);
 
136
check_plt_aux([Plt|Plts], Opts) ->
 
137
  Opts1 = Opts#options{init_plts = [Plt]},
 
138
  Opts2 = init_opts_for_check(Opts1),
 
139
  report_check(Opts2),
 
140
  plt_common(Opts2, [], []),
 
141
  check_plt_aux(Plts, Opts).
113
142
 
114
143
init_opts_for_check(Opts) ->
115
 
  Plt =
116
 
    case Opts#options.init_plt of
117
 
      none -> get_default_plt();
118
 
      Plt0 -> Plt0
 
144
  InitPlt =
 
145
    case Opts#options.init_plts of
 
146
      []-> get_default_init_plt();
 
147
      Plt -> Plt
119
148
    end,
 
149
  [OutputPlt] = InitPlt,
120
150
  Opts#options{files         = [],
121
151
               files_rec     = [],
122
152
               analysis_type = plt_check,
123
153
               defines       = [],
124
154
               from          = byte_code,
125
 
               init_plt      = Plt,
 
155
               init_plts     = InitPlt,
126
156
               include_dirs  = [],
127
 
               output_plt    = Plt,
 
157
               output_plt    = OutputPlt,
128
158
               use_contracts = true
129
159
              }.
130
160
 
138
168
init_opts_for_remove(Opts) ->
139
169
  case Opts#options.output_plt =:= none of
140
170
    true ->
141
 
      case Opts#options.init_plt of
142
 
        none -> Opts#options{output_plt = get_default_plt(),
143
 
                             init_plt = get_default_plt()};
144
 
        Plt  -> Opts#options{output_plt = Plt}
 
171
      case Opts#options.init_plts of
 
172
        [] -> Opts#options{output_plt = get_default_output_plt(),
 
173
                           init_plts = get_default_init_plt()};
 
174
        [Plt] -> Opts#options{output_plt = Plt};
 
175
        Plts ->
 
176
          Msg = io_lib:format("Could not remove from multiple PLT files: ~s\n",
 
177
                              [format_plts(Plts)]),
 
178
          error(Msg)
145
179
      end;
146
180
    false ->
147
 
      case Opts#options.init_plt =:= none of
148
 
        true  -> Opts#options{init_plt = get_default_plt()};
 
181
      case Opts#options.init_plts =:= [] of
 
182
        true  -> Opts#options{init_plts = get_default_init_plt()};
149
183
        false -> Opts
150
184
      end
151
185
  end.
152
186
 
153
187
%%--------------------------------------------------------------------
154
188
 
155
 
plt_common(Opts, RemoveFiles, AddFiles) ->
 
189
plt_common(#options{init_plts = [InitPlt]} = Opts, RemoveFiles, AddFiles) ->
156
190
  case check_plt(Opts, RemoveFiles, AddFiles) of
157
191
    ok ->
 
192
      case Opts#options.output_plt of
 
193
        none -> ok;
 
194
        OutPlt ->
 
195
          {ok, Binary} = file:read_file(InitPlt),
 
196
          file:write_file(OutPlt, Binary)
 
197
      end,
158
198
      case Opts#options.report_mode of
159
199
        quiet -> ok;
160
200
        _ -> io:put_chars(" yes\n")
168
208
      report_failed_plt_check(Opts, DiffMd5),
169
209
      {AnalFiles, RemovedMods, ModDeps1} = 
170
210
        expand_dependent_modules(Md5, DiffMd5, ModDeps),
171
 
      Plt = clean_plt(Opts#options.init_plt, RemovedMods),
 
211
      Plt = clean_plt(InitPlt, RemovedMods),
172
212
      case AnalFiles =:= [] of
173
213
        true ->
174
214
          %% Only removed stuff. Just write the PLT.
180
220
      end;
181
221
    {error, no_such_file} ->
182
222
      Msg = io_lib:format("Could not find the PLT: ~s\n~s",
183
 
                          [Opts#options.init_plt, default_plt_error_msg()]),
 
223
                          [InitPlt, default_plt_error_msg()]),
184
224
      error(Msg);
185
225
    {error, not_valid} ->
186
226
      Msg = io_lib:format("The file: ~s is not a valid PLT file\n~s",
187
 
                          [Opts#options.init_plt, default_plt_error_msg()]),
 
227
                          [InitPlt, default_plt_error_msg()]),
188
228
      error(Msg);
189
229
    {error, read_error} ->
190
230
      Msg = io_lib:format("Could not read the PLT: ~s\n~s",
191
 
                          [Opts#options.init_plt, default_plt_error_msg()]),
 
231
                          [InitPlt, default_plt_error_msg()]),
192
232
      error(Msg);
193
233
    {error, {no_file_to_remove, F}} ->
194
234
      Msg = io_lib:format("Could not remove the file ~s from the PLT: ~s\n",
195
 
                          [F, Opts#options.init_plt]),
 
235
                          [F, InitPlt]),
196
236
      error(Msg)
197
237
  end.
198
238
 
212
252
 
213
253
%%--------------------------------------------------------------------
214
254
 
215
 
check_plt(Opts, RemoveFiles, AddFiles) ->
216
 
  Plt = Opts#options.init_plt,
 
255
check_plt(#options{init_plts = [Plt]} = Opts, RemoveFiles, AddFiles) ->
217
256
  case dialyzer_plt:check_plt(Plt, RemoveFiles, AddFiles) of
218
257
    {old_version, _MD5} = OldVersion ->
219
258
      report_old_version(Opts),
228
267
 
229
268
%%--------------------------------------------------------------------
230
269
 
231
 
report_check(#options{report_mode = ReportMode, init_plt = InitPlt}) ->
 
270
report_check(#options{report_mode = ReportMode, init_plts = [InitPlt]}) ->
232
271
  case ReportMode of
233
272
    quiet -> ok;
234
273
    _ ->
235
274
      io:format("  Checking whether the PLT ~s is up-to-date...", [InitPlt])
236
275
  end.
237
276
 
238
 
report_old_version(#options{report_mode = ReportMode, init_plt = InitPlt}) ->
 
277
report_old_version(#options{report_mode = ReportMode, init_plts = [InitPlt]}) ->
239
278
  case ReportMode of
240
279
    quiet -> ok;
241
280
    _ ->
258
297
 
259
298
report_analysis_start(#options{analysis_type = Type,
260
299
                               report_mode = ReportMode,
261
 
                               init_plt = InitPlt, 
 
300
                               init_plts = InitPlts,
262
301
                               output_plt = OutputPlt}) ->
263
302
  case ReportMode of
264
303
    quiet -> ok;
266
305
      io:format("  "),
267
306
      case Type of
268
307
        plt_add ->
 
308
          [InitPlt] = InitPlts,
269
309
          case InitPlt =:= OutputPlt of
270
310
            true -> io:format("Adding information to ~s...", [OutputPlt]);
271
311
            false -> io:format("Adding information from ~s to ~s...", 
276
316
        plt_check ->
277
317
          io:format("Rebuilding the information in ~s...", [OutputPlt]);
278
318
        plt_remove ->
 
319
          [InitPlt] = InitPlts,
279
320
          case InitPlt =:= OutputPlt of
280
321
            true -> io:format("Removing information from ~s...", [OutputPlt]);
281
322
            false -> io:format("Removing information from ~s to ~s...", 
314
355
 
315
356
%%--------------------------------------------------------------------
316
357
 
317
 
get_default_plt() ->
 
358
get_default_init_plt() ->
 
359
  [dialyzer_plt:get_default_plt()].
 
360
 
 
361
get_default_output_plt() ->
318
362
  dialyzer_plt:get_default_plt().
319
363
 
320
364
%%--------------------------------------------------------------------
321
365
 
 
366
format_plts([Plt]) -> Plt;
 
367
format_plts([Plt|Plts]) ->
 
368
  Plt ++ ", " ++ format_plts(Plts).
 
369
 
 
370
%%--------------------------------------------------------------------
 
371
 
322
372
do_analysis(Options) ->
323
373
  Files = get_files_from_opts(Options),
324
 
  case Options#options.init_plt of
325
 
    none -> do_analysis(Files, Options, dialyzer_plt:new(), none);
326
 
    File -> do_analysis(Files, Options, dialyzer_plt:from_file(File), none)
 
374
  case Options#options.init_plts of
 
375
    [] -> do_analysis(Files, Options, dialyzer_plt:new(), none);
 
376
    PltFiles ->
 
377
      Plts = [dialyzer_plt:from_file(F) || F <- PltFiles],
 
378
      Plt = dialyzer_plt:merge_plts_or_report_conflicts(PltFiles, Plts),
 
379
      do_analysis(Files, Options, Plt, none)
327
380
  end.
328
381
  
329
382
do_analysis(Files, Options, Plt, PltInfo) ->
440
493
-spec hipe_compile([file:filename()], #options{}) -> 'ok'.
441
494
 
442
495
hipe_compile(Files, #options{erlang_mode = ErlangMode} = Options) ->
443
 
  case (length(Files) < ?MIN_FILES_FOR_NATIVE_COMPILE) orelse ErlangMode of
 
496
  NoNative = (get(dialyzer_options_native) =:= false),
 
497
  FewFiles = (length(Files) < ?MIN_FILES_FOR_NATIVE_COMPILE),
 
498
  case NoNative orelse FewFiles orelse ErlangMode of
444
499
    true -> ok;
445
500
    false ->
446
501
      case erlang:system_info(hipe_architecture) of
484
539
new_state() ->
485
540
  #cl_state{}.
486
541
 
487
 
init_output(State0, #options{output_file = OutFile, output_format = OutFormat}) ->
488
 
  State = State0#cl_state{output_format = OutFormat},
 
542
init_output(State0, #options{output_file = OutFile,
 
543
                             output_format = OutFormat,
 
544
                             filename_opt = FOpt}) ->
 
545
  State = State0#cl_state{output_format = OutFormat, filename_opt = FOpt},
489
546
  case OutFile =:= none of
490
547
    true ->
491
548
      State;
528
585
    {BackendPid, warnings, Warnings} ->
529
586
      NewState = store_warnings(State, Warnings),
530
587
      cl_loop(NewState, LogCache);
 
588
    {BackendPid, unknown_behaviours, Behaviours} ->
 
589
      NewState = store_unknown_behaviours(State, Behaviours),
 
590
      cl_loop(NewState, LogCache);
531
591
    {BackendPid, done, NewPlt, _NewDocPlt} ->
532
592
      return_value(State, NewPlt);
533
593
    {BackendPid, ext_calls, ExtCalls} ->
534
594
      cl_loop(State#cl_state{external_calls = ExtCalls}, LogCache);
 
595
    {BackendPid, ext_types, ExtTypes} ->
 
596
      cl_loop(State#cl_state{external_types = ExtTypes}, LogCache);
535
597
    {BackendPid, mod_deps, ModDeps} ->
536
598
      NewState = State#cl_state{mod_deps = ModDeps},
537
599
      cl_loop(NewState, LogCache);
546
608
      cl_loop(State, LogCache)
547
609
  end.
548
610
 
549
 
-spec failed_anal_msg(string(), [_]) -> string().
 
611
-spec failed_anal_msg(string(), [_]) -> nonempty_string().
550
612
 
551
613
failed_anal_msg(Reason, LogCache) ->
552
614
  Msg = "Analysis failed with error: " ++ Reason ++ "\n",
568
630
store_warnings(#cl_state{stored_warnings = StoredWarnings} = St, Warnings) ->
569
631
  St#cl_state{stored_warnings = StoredWarnings ++ Warnings}.
570
632
 
 
633
-spec store_unknown_behaviours(#cl_state{}, [dialyzer_behaviours:behaviour()]) -> #cl_state{}.
 
634
 
 
635
store_unknown_behaviours(#cl_state{unknown_behaviours = Behs} = St, Beh) ->
 
636
  St#cl_state{unknown_behaviours = Beh ++ Behs}.
 
637
 
571
638
-spec error(string()) -> no_return().
572
639
 
573
640
error(Msg) ->
602
669
    false ->
603
670
      print_warnings(State),
604
671
      print_ext_calls(State),
 
672
      print_ext_types(State),
 
673
      print_unknown_behaviours(State),
605
674
      maybe_close_output_file(State),
606
675
      {RetValue, []};
607
676
    true -> 
637
706
do_print_ext_calls(_, [], _) ->
638
707
  ok.
639
708
 
 
709
print_ext_types(#cl_state{report_mode = quiet}) ->
 
710
  ok;
 
711
print_ext_types(#cl_state{output = Output,
 
712
                          external_calls = Calls,
 
713
                          external_types = Types,
 
714
                          stored_warnings = Warnings,
 
715
                          output_format = Format}) ->
 
716
  case Types =:= [] of
 
717
    true -> ok;
 
718
    false ->
 
719
      case Warnings =:= [] andalso Calls =:= [] of
 
720
        true -> io:nl(Output); %% Need to do a newline first
 
721
        false -> ok
 
722
      end,
 
723
      case Format of
 
724
        formatted ->
 
725
          io:put_chars(Output, "Unknown types:\n"),
 
726
          do_print_ext_types(Output, Types, "  ");
 
727
        raw ->
 
728
          io:put_chars(Output, "%% Unknown types:\n"),
 
729
          do_print_ext_types(Output, Types, "%%  ")
 
730
      end
 
731
  end.
 
732
 
 
733
do_print_ext_types(Output, [{M,F,A}|T], Before) ->
 
734
  io:format(Output, "~s~p:~p/~p\n", [Before,M,F,A]),
 
735
  do_print_ext_types(Output, T, Before);
 
736
do_print_ext_types(_, [], _) ->
 
737
  ok.
 
738
 
 
739
%%print_unknown_behaviours(#cl_state{report_mode = quiet}) ->
 
740
%%  ok;
 
741
print_unknown_behaviours(#cl_state{output = Output,
 
742
                                   external_calls = Calls,
 
743
                                   external_types = Types,
 
744
                                   stored_warnings = Warnings,
 
745
                                   unknown_behaviours = DupBehaviours,
 
746
                                   legal_warnings = LegalWarnings,
 
747
                                   output_format = Format}) ->
 
748
  case ordsets:is_element(?WARN_BEHAVIOUR, LegalWarnings)
 
749
    andalso DupBehaviours =/= [] of
 
750
    false -> ok;
 
751
    true ->
 
752
      Behaviours = lists:usort(DupBehaviours),
 
753
      case Warnings =:= [] andalso Calls =:= [] andalso Types =:= [] of
 
754
        true -> io:nl(Output); %% Need to do a newline first
 
755
        false -> ok
 
756
      end,
 
757
      case Format of
 
758
        formatted ->
 
759
          io:put_chars(Output, "Unknown behaviours (behaviour_info(callbacks)"
 
760
                       " does not return any specs):\n"),
 
761
          do_print_unknown_behaviours(Output, Behaviours, "  ");
 
762
        raw ->
 
763
          io:put_chars(Output, "%% Unknown behaviours:\n"),
 
764
          do_print_unknown_behaviours(Output, Behaviours, "%%  ")
 
765
      end
 
766
  end.
 
767
 
 
768
do_print_unknown_behaviours(Output, [B|T], Before) ->
 
769
  io:format(Output, "~s~p\n", [Before,B]),
 
770
  do_print_unknown_behaviours(Output, T, Before);
 
771
do_print_unknown_behaviours(_, [], _) ->
 
772
  ok.
 
773
 
640
774
print_warnings(#cl_state{stored_warnings = []}) ->
641
775
  ok;
642
776
print_warnings(#cl_state{output = Output,
643
777
                         output_format = Format,
 
778
                         filename_opt = FOpt,
644
779
                         stored_warnings = Warnings}) ->
645
780
  PrWarnings = process_warnings(Warnings),
646
781
  case PrWarnings of
648
783
    [_|_] ->
649
784
      S = case Format of
650
785
            formatted ->
651
 
              [dialyzer:format_warning(W) || W <- PrWarnings];
 
786
              [dialyzer:format_warning(W, FOpt) || W <- PrWarnings];
652
787
            raw ->
653
788
              [io_lib:format("~p. \n", [W]) || W <- PrWarnings]
654
789
          end,