~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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-2010. 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
 
43
43
          parent                        :: pid(),
44
44
          plt                           :: dialyzer_plt:plt(),
45
45
          start_from     = byte_code    :: start_from(),
46
 
          use_contracts  = true         :: boolean()
 
46
          use_contracts  = true         :: boolean(),
 
47
          behaviours = {false,[]}   :: {boolean(),[atom()]}
47
48
         }).
48
49
 
49
50
-record(server_state, {parent :: pid(), legal_warnings :: [dial_warn_tag()]}).
56
57
 
57
58
start(Parent, LegalWarnings, Analysis) ->
58
59
  RacesOn = ordsets:is_element(?WARN_RACE_CONDITION, LegalWarnings),
59
 
  Analysis0 = Analysis#analysis{race_detection = RacesOn},
 
60
  BehavOn = ordsets:is_element(?WARN_BEHAVIOUR, LegalWarnings),
 
61
  Analysis0 = Analysis#analysis{race_detection = RacesOn,
 
62
                                behaviours_chk = BehavOn},
60
63
  Analysis1 = expand_files(Analysis0),
61
64
  Analysis2 = run_analysis(Analysis1),
62
65
  State = #server_state{parent = Parent, legal_warnings = LegalWarnings},
93
96
      end;
94
97
    {AnalPid, ext_calls, NewExtCalls} ->
95
98
      loop(State, Analysis, NewExtCalls);
 
99
    {AnalPid, unknown_behaviours, UnknownBehaviour} ->
 
100
      send_unknown_behaviours(Parent, UnknownBehaviour),
 
101
      loop(State, Analysis, ExtCalls);
96
102
    {AnalPid, mod_deps, ModDeps} ->
97
103
      send_mod_deps(Parent, ModDeps),
98
104
      loop(State, Analysis, ExtCalls);
116
122
                          plt = Plt,
117
123
                          parent = Parent,
118
124
                          start_from = Analysis#analysis.start_from,
119
 
                          use_contracts = Analysis#analysis.use_contracts
 
125
                          use_contracts = Analysis#analysis.use_contracts,
 
126
                          behaviours = {Analysis#analysis.behaviours_chk,
 
127
                                            []}
120
128
                         },
121
129
  Files = ordsets:from_list(Analysis#analysis.files),
122
130
  {Callgraph, NoWarn, TmpCServer0} = compile_and_store(Files, State),
167
175
      State#analysis_state{plt = NewPlt};
168
176
    succ_typings ->
169
177
      NoWarn = State#analysis_state.no_warn_unused,
 
178
      {BehavioursChk, _Known} = State#analysis_state.behaviours,
170
179
      DocPlt = State#analysis_state.doc_plt,
171
180
      Callgraph1 = dialyzer_callgraph:finalize(Callgraph),
172
181
      {Warnings, NewPlt, NewDocPlt} = 
173
182
        dialyzer_succ_typings:get_warnings(Callgraph1, Plt, DocPlt,
174
 
                                           Codeserver, NoWarn, Parent),
 
183
                                           Codeserver, NoWarn, Parent,
 
184
                                           BehavioursChk),
175
185
      dialyzer_callgraph:delete(Callgraph1),
176
186
      send_warnings(State#analysis_state.parent, Warnings),
177
187
      State#analysis_state{plt = NewPlt, doc_plt = NewDocPlt}
186
196
                                         include_dirs = Dirs,
187
197
                                         parent = Parent,
188
198
                                         use_contracts = UseContracts,
189
 
                                         start_from = StartFrom} = State) ->
 
199
                                         start_from = StartFrom,
 
200
                                         behaviours = {BehChk, _}
 
201
                                        } = State) ->
190
202
  send_log(Parent, "Reading files and computing callgraph... "),
191
203
  {T1, _} = statistics(runtime),
192
204
  Includes = [{i, D} || D <- Dirs],
234
246
  {T2, _} = statistics(runtime),
235
247
  Msg1 = io_lib:format("done in ~.2f secs\nRemoving edges... ", [(T2-T1)/1000]),
236
248
  send_log(Parent, Msg1),
237
 
  NewCallgraph2 = cleanup_callgraph(State, NewCServer, NewCallgraph1, Modules),
 
249
  {KnownBehaviours, UnknownBehaviours} =
 
250
    dialyzer_behaviours:get_behaviours(Modules, NewCServer),
 
251
  if UnknownBehaviours =:= [] -> ok;
 
252
     true -> send_unknown_behaviours(Parent, UnknownBehaviours)
 
253
  end,
 
254
  State1 = State#analysis_state{behaviours = {BehChk,KnownBehaviours}},
 
255
  NewCallgraph2 = cleanup_callgraph(State1, NewCServer, NewCallgraph1, Modules),
238
256
  {T3, _} = statistics(runtime),
239
257
  Msg2 = io_lib:format("done in ~.2f secs\n", [(T3-T2)/1000]),
240
258
  send_log(Parent, Msg2),  
241
259
  {NewCallgraph2, sets:from_list(NoWarn), NewCServer}.
242
260
 
243
261
cleanup_callgraph(#analysis_state{plt = InitPlt, parent = Parent, 
244
 
                                  codeserver = CodeServer},
 
262
                                  codeserver = CodeServer,
 
263
                                  behaviours = {BehChk, KnownBehaviours}
 
264
                                 },
245
265
                  CServer, Callgraph, Modules) ->
246
266
  ModuleDeps = dialyzer_callgraph:module_deps(Callgraph),
247
267
  send_mod_deps(Parent, ModuleDeps),
248
268
  {Callgraph1, ExtCalls} = dialyzer_callgraph:remove_external(Callgraph),
 
269
  if BehChk ->
 
270
      RelevantAPICalls =
 
271
        dialyzer_behaviours:get_behaviour_apis(KnownBehaviours),
 
272
      BehaviourAPICalls = [Call || {_From, To} = Call <- ExtCalls,
 
273
                                   lists:member(To, RelevantAPICalls)],
 
274
      Callgraph2 =
 
275
        dialyzer_callgraph:put_behaviour_api_calls(BehaviourAPICalls,
 
276
                                                   Callgraph1);
 
277
     true ->
 
278
      Callgraph2 = Callgraph1
 
279
  end,
249
280
  ExtCalls1 = [Call || Call = {_From, To} <- ExtCalls,
250
281
                       not dialyzer_plt:contains_mfa(InitPlt, To)],
251
282
  {BadCalls1, RealExtCalls} =
268
299
     true ->
269
300
      send_ext_calls(Parent, lists:usort([To || {_From, To} <- RealExtCalls]))
270
301
  end,
271
 
  Callgraph1.
 
302
  Callgraph2.
272
303
 
273
304
compile_src(File, Includes, Defines, Callgraph, CServer, UseContracts) ->
274
305
  DefaultIncludes = default_includes(filename:dirname(File)),
445
476
  Parent ! {self(), ext_calls, ExtCalls},
446
477
  ok.
447
478
 
 
479
send_unknown_behaviours(Parent, UnknownBehaviours) ->
 
480
  Parent ! {self(), unknown_behaviours, UnknownBehaviours},
 
481
  ok.
 
482
 
448
483
send_codeserver_plt(Parent, CServer, Plt ) ->
449
484
  Parent ! {self(), cserver, CServer, Plt},
450
485
  ok.