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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%-----------------------------------------------------------------------
3
 
%% ``The contents of this file are subject to the Erlang Public License,
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
4
8
%% Version 1.1, (the "License"); you may not use this file except in
5
9
%% compliance with the License. You should have received a copy of the
6
10
%% Erlang Public License along with this software. If not, it can be
7
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
11
%% retrieved online at http://www.erlang.org/.
8
12
%% 
9
13
%% Software distributed under the License is distributed on an "AS IS"
10
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
11
15
%% the License for the specific language governing rights and limitations
12
16
%% under the License.
13
17
%% 
14
 
%% Copyright 2006, Tobias Lindahl and Kostis Sagonas
15
 
%% 
16
 
%%     $Id$
 
18
%% %CopyrightEnd%
17
19
%%
18
20
 
19
21
%%%-------------------------------------------------------------------
45
47
         scan_core_tree/2,
46
48
         strip_module_deps/2,
47
49
         take_scc/1, 
48
 
         remove_external/1]).
49
 
 
50
 
-define(NO_UNUSED, true).
51
 
-ifndef(NO_UNUSED).
52
 
-export([to_dot/1]).
53
 
-endif.
 
50
         remove_external/1,
 
51
         to_dot/2,
 
52
         to_ps/3]).
54
53
 
55
54
%%----------------------------------------------------------------------
56
55
 
62
61
-spec new() -> #dialyzer_callgraph{}.
63
62
 
64
63
new() ->
65
 
  #dialyzer_callgraph{calls=dict:new(),
66
 
                      digraph=digraph_new(),
67
 
                      esc=sets:new(),
68
 
                      name_map=dict:new(),
69
 
                      postorder=[],
70
 
                      rec_var_map=dict:new(),
71
 
                      rev_name_map=dict:new(),
72
 
                      self_rec=sets:new()}.
 
64
  #dialyzer_callgraph{}.
73
65
 
74
66
-spec delete(#dialyzer_callgraph{}) -> 'true'.
75
67
 
76
 
delete(#dialyzer_callgraph{digraph=Digraph}) ->
 
68
delete(#dialyzer_callgraph{digraph = Digraph}) ->
77
69
  digraph_delete(Digraph).
78
70
 
79
71
-spec all_nodes(#dialyzer_callgraph{}) -> [_].
80
72
 
81
 
all_nodes(#dialyzer_callgraph{digraph=DG}) ->
 
73
all_nodes(#dialyzer_callgraph{digraph = DG}) ->
82
74
  digraph_vertices(DG).
83
75
 
84
 
-spec lookup_rec_var(integer(), #dialyzer_callgraph{}) -> 'error' | {'ok',_}.
 
76
-spec lookup_rec_var(label(), #dialyzer_callgraph{}) -> 'error' | {'ok',_}.
85
77
 
86
 
lookup_rec_var(Label, #dialyzer_callgraph{rec_var_map=RecVarMap}) 
 
78
lookup_rec_var(Label, #dialyzer_callgraph{rec_var_map = RecVarMap}) 
87
79
  when is_integer(Label) ->
88
80
  dict:find(Label, RecVarMap).
89
81
 
90
 
-spec lookup_call_site(integer(), #dialyzer_callgraph{}) -> 'error' | {'ok',_}.
 
82
-spec lookup_call_site(label(), #dialyzer_callgraph{}) -> 'error' | {'ok',_}.
91
83
 
92
 
lookup_call_site(Label, #dialyzer_callgraph{calls=Calls})
 
84
lookup_call_site(Label, #dialyzer_callgraph{calls = Calls})
93
85
  when is_integer(Label) ->
94
86
  dict:find(Label, Calls).
95
87
 
96
 
-spec lookup_name(integer(), #dialyzer_callgraph{}) -> 'error' | {'ok',mfa()}.
 
88
-spec lookup_name(label(), #dialyzer_callgraph{}) -> 'error' | {'ok', mfa()}.
97
89
 
98
 
lookup_name(Label, #dialyzer_callgraph{name_map=NameMap})
 
90
lookup_name(Label, #dialyzer_callgraph{name_map = NameMap})
99
91
  when is_integer(Label) ->
100
92
  dict:find(Label, NameMap).
101
93
 
102
 
-spec lookup_label(mfa_or_funlbl(), #dialyzer_callgraph{}) -> {'ok',integer()}.
 
94
-spec lookup_label(mfa_or_funlbl(), #dialyzer_callgraph{}) -> {'ok', integer()}.
103
95
 
104
 
lookup_label(MFA = {_,_,_}, #dialyzer_callgraph{rev_name_map=RevNameMap}) ->
 
96
lookup_label({_,_,_} = MFA, #dialyzer_callgraph{rev_name_map = RevNameMap}) ->
105
97
  {ok, _Lbl} = dict:find(MFA, RevNameMap);
106
98
lookup_label(Label, #dialyzer_callgraph{}) when is_integer(Label) ->
107
99
  {ok, Label}.
108
100
 
109
101
-spec in_neighbours(mfa_or_funlbl(), #dialyzer_callgraph{}) -> 'none' | [any(),...].
110
102
 
111
 
in_neighbours(Label, CG=#dialyzer_callgraph{}) when is_integer(Label) ->
112
 
  Name = case dict:find(Label, CG#dialyzer_callgraph.name_map) of
 
103
in_neighbours(Label, #dialyzer_callgraph{digraph = Digraph, name_map = NameMap})
 
104
  when is_integer(Label) ->
 
105
  Name = case dict:find(Label, NameMap) of
113
106
           {ok, Val} -> Val;
114
107
           error -> Label
115
108
         end,
116
 
  digraph_in_neighbours(Name, CG#dialyzer_callgraph.digraph);
117
 
in_neighbours(MFA={_,_,_}, CG=#dialyzer_callgraph{}) ->
118
 
  digraph_in_neighbours(MFA, CG#dialyzer_callgraph.digraph).
 
109
  digraph_in_neighbours(Name, Digraph);
 
110
in_neighbours({_,_,_} = MFA, #dialyzer_callgraph{digraph = Digraph}) ->
 
111
  digraph_in_neighbours(MFA, Digraph).
119
112
 
120
113
-spec is_self_rec(mfa_or_funlbl(), #dialyzer_callgraph{}) -> bool().
121
114
 
122
 
is_self_rec(MfaOrLabel, #dialyzer_callgraph{self_rec=SelfRecs}) ->
 
115
is_self_rec(MfaOrLabel, #dialyzer_callgraph{self_rec = SelfRecs}) ->
123
116
  sets:is_element(MfaOrLabel, SelfRecs).
124
117
 
125
 
-spec is_escaping(integer(), #dialyzer_callgraph{}) -> bool().
 
118
-spec is_escaping(label(), #dialyzer_callgraph{}) -> bool().
126
119
 
127
 
is_escaping(Label, #dialyzer_callgraph{esc=Esc}) when is_integer(Label) ->
 
120
is_escaping(Label, #dialyzer_callgraph{esc = Esc}) when is_integer(Label) ->
128
121
  sets:is_element(Label, Esc).  
129
122
 
130
123
-type callgraph_edge() :: {mfa_or_funlbl(),mfa_or_funlbl()}.
132
125
 
133
126
add_edges([], CG) ->
134
127
  CG;
135
 
add_edges(Edges, CG = #dialyzer_callgraph{digraph=Callgraph}) ->
136
 
  CG#dialyzer_callgraph{digraph=digraph_add_edges(Edges, Callgraph)}.
 
128
add_edges(Edges, CG = #dialyzer_callgraph{digraph = Callgraph}) ->
 
129
  CG#dialyzer_callgraph{digraph = digraph_add_edges(Edges, Callgraph)}.
137
130
 
138
131
-spec add_edges([callgraph_edge()], [mfa_or_funlbl()], #dialyzer_callgraph{}) ->
139
132
         #dialyzer_callgraph{}.
140
133
 
141
 
add_edges(Edges, MFAs, CG = #dialyzer_callgraph{digraph=DG}) ->
 
134
add_edges(Edges, MFAs, CG = #dialyzer_callgraph{digraph = DG}) ->
142
135
  DG1 = digraph_confirm_vertices(MFAs, DG),
143
 
  add_edges(Edges, CG#dialyzer_callgraph{digraph=DG1}).
 
136
  add_edges(Edges, CG#dialyzer_callgraph{digraph = DG1}).
144
137
 
145
138
-spec take_scc(#dialyzer_callgraph{}) ->
146
139
                'none' | {'ok', scc(), #dialyzer_callgraph{}}.
147
140
 
148
 
take_scc(CG = #dialyzer_callgraph{postorder=[SCC|Left]}) ->
149
 
  {ok, SCC, CG#dialyzer_callgraph{postorder=Left}};
150
 
take_scc(#dialyzer_callgraph{postorder=[]}) ->
 
141
take_scc(CG = #dialyzer_callgraph{postorder = [SCC|SCCs]}) ->
 
142
  {ok, SCC, CG#dialyzer_callgraph{postorder = SCCs}};
 
143
take_scc(#dialyzer_callgraph{postorder = []}) ->
151
144
  none.
152
145
 
153
146
-spec remove_external(#dialyzer_callgraph{}) -> {#dialyzer_callgraph{}, [tuple()]}.
154
147
 
155
 
remove_external(CG = #dialyzer_callgraph{digraph=DG}) ->
 
148
remove_external(CG = #dialyzer_callgraph{digraph = DG}) ->
156
149
  {NewDG, External} = digraph_remove_external(DG),
157
 
  {CG#dialyzer_callgraph{digraph=NewDG}, External}.
158
 
 
159
 
-spec non_local_calls(#dialyzer_callgraph{}) -> [{mfa(),mfa()}].
160
 
 
161
 
non_local_calls(#dialyzer_callgraph{digraph=DG}) ->
162
 
  Edges = digraph_edges(DG),            
 
150
  {CG#dialyzer_callgraph{digraph = NewDG}, External}.
 
151
 
 
152
-spec non_local_calls(#dialyzer_callgraph{}) -> mfa_calls().
 
153
 
 
154
non_local_calls(#dialyzer_callgraph{digraph = DG}) ->
 
155
  Edges = digraph_edges(DG),
163
156
  find_non_local_calls(Edges, sets:new()).
164
157
 
165
 
find_non_local_calls([{{M, _, _}, {M, _, _}}|Left], Set) ->
 
158
-spec find_non_local_calls([{mfa_or_funlbl(), mfa_or_funlbl()}], set()) -> mfa_calls().
 
159
 
 
160
find_non_local_calls([{{M,_,_}, {M,_,_}}|Left], Set) ->
166
161
  find_non_local_calls(Left, Set);
167
 
find_non_local_calls([Edge={{M1, _, _},{M2, _, _}}|Left], Set) when M1 =/= M2 ->
 
162
find_non_local_calls([{{M1,_,_}, {M2,_,_}} = Edge|Left], Set) when M1 =/= M2 ->
168
163
  find_non_local_calls(Left, sets:add_element(Edge, Set));
169
164
find_non_local_calls([{{_,_,_}, Label}|Left], Set) when is_integer(Label) ->
170
165
  find_non_local_calls(Left, Set);  
180
175
%% Handling of modules & SCCs
181
176
%%----------------------------------------------------------------------
182
177
 
183
 
-spec modules(#dialyzer_callgraph{}) -> [atom()].
 
178
-spec modules(#dialyzer_callgraph{}) -> [module()].
184
179
 
185
 
modules(#dialyzer_callgraph{digraph=DG}) ->
 
180
modules(#dialyzer_callgraph{digraph = DG}) ->
186
181
  ordsets:from_list([M || {M,_F,_A} <- digraph_vertices(DG)]).
187
182
 
188
 
-spec module_postorder(#dialyzer_callgraph{}) -> [[atom()]].
 
183
-spec module_postorder(#dialyzer_callgraph{}) -> [[module()]].
189
184
 
190
 
module_postorder(#dialyzer_callgraph{digraph=DG}) ->
 
185
module_postorder(#dialyzer_callgraph{digraph = DG}) ->
191
186
  Edges = digraph_edges(DG),
192
187
  Nodes = ordsets:from_list([M || {M,_F,_A} <- digraph_vertices(DG)]),
193
 
  MDG = digraph_new(),
 
188
  MDG = digraph:new(),
194
189
  MDG1 = digraph_confirm_vertices(Nodes, MDG),
195
190
  MDG2 = create_module_digraph(Edges, MDG1),
196
191
  MDG3 = digraph_utils:condensation(MDG2),
203
198
%% The module deps of a module are modules that depend on the module
204
199
-spec module_deps(#dialyzer_callgraph{}) -> dict().
205
200
 
206
 
module_deps(#dialyzer_callgraph{digraph=DG}) ->
 
201
module_deps(#dialyzer_callgraph{digraph = DG}) ->
207
202
  Edges = digraph_edges(DG),
208
203
  Nodes = ordsets:from_list([M || {M,_F,_A} <- digraph_vertices(DG)]),
209
 
  MDG = digraph_new(),
 
204
  MDG = digraph:new(),
210
205
  MDG1 = digraph_confirm_vertices(Nodes, MDG),
211
206
  MDG2 = create_module_digraph(Edges, MDG1),
212
207
  Deps = [{N, ordsets:from_list(digraph:in_neighbours(MDG2, N))}
217
212
-spec strip_module_deps(dict(), set()) -> dict().
218
213
 
219
214
strip_module_deps(ModDeps, StripSet) ->
220
 
  FilterFun1 = fun(Val) -> not sets:is_element(Val, StripSet)end,
221
 
  MapFun = fun(_Key, ValSet) -> ordsets:filter(FilterFun1, ValSet)end,
 
215
  FilterFun1 = fun(Val) -> not sets:is_element(Val, StripSet) end,
 
216
  MapFun = fun(_Key, ValSet) -> ordsets:filter(FilterFun1, ValSet) end,
222
217
  ModDeps1 = dict:map(MapFun, ModDeps),
223
218
  FilterFun2 = fun(_Key, ValSet) -> ValSet =/= [] end,
224
219
  dict:filter(FilterFun2, ModDeps1).
226
221
sort_sccs_internally(PO, MDG) ->
227
222
  sort_sccs_internally(PO, MDG, []).
228
223
 
229
 
sort_sccs_internally([SCC|Left], MDG, Acc) ->
 
224
sort_sccs_internally([SCC|SCCs], MDG, Acc) ->
230
225
  case length(SCC) >= 3 of
231
 
    false -> sort_sccs_internally(Left, MDG, [SCC|Acc]);
 
226
    false -> sort_sccs_internally(SCCs, MDG, [SCC|Acc]);
232
227
    true ->
233
228
      TmpDG = digraph_utils:subgraph(MDG, SCC),
234
229
      NewSCC = digraph_utils:postorder(TmpDG),
235
230
      digraph_delete(TmpDG),
236
 
      sort_sccs_internally(Left, MDG, [NewSCC|Acc])
 
231
      sort_sccs_internally(SCCs, MDG, [NewSCC|Acc])
237
232
  end;
238
233
sort_sccs_internally([], _MDG, Acc) ->
239
234
  lists:reverse(Acc).
240
235
 
241
236
create_module_digraph([{{M,_,_}, {M,_,_}}|Left], MDG) ->
242
237
  create_module_digraph(Left, MDG);
243
 
create_module_digraph([{{M1,_,_},{M2,_,_}}|Left], MDG) ->
 
238
create_module_digraph([{{M1,_,_}, {M2,_,_}}|Left], MDG) ->
244
239
  create_module_digraph(Left, digraph_add_edge(M1, M2, MDG));
245
240
create_module_digraph([{_, _}|Left], MDG) ->
246
241
  create_module_digraph(Left, MDG);
249
244
 
250
245
-spec finalize(#dialyzer_callgraph{}) -> #dialyzer_callgraph{}.
251
246
 
252
 
finalize(CG = #dialyzer_callgraph{digraph=DG}) ->
253
 
  CG#dialyzer_callgraph{postorder=digraph_finalize(DG)}.
 
247
finalize(#dialyzer_callgraph{digraph = DG} = CG) ->
 
248
  CG#dialyzer_callgraph{postorder = digraph_finalize(DG)}.
254
249
 
255
250
-spec reset_from_funs([_], #dialyzer_callgraph{}) -> #dialyzer_callgraph{}.
256
251
 
257
 
reset_from_funs(Funs, CG = #dialyzer_callgraph{digraph=DG}) ->
 
252
reset_from_funs(Funs, #dialyzer_callgraph{digraph = DG} = CG) ->
258
253
  SubGraph = digraph_reaching_subgraph(Funs, DG),
259
254
  Postorder = digraph_finalize(SubGraph),
260
255
  digraph_delete(SubGraph),
261
 
  CG#dialyzer_callgraph{postorder=Postorder}.
 
256
  CG#dialyzer_callgraph{postorder = Postorder}.
262
257
 
263
258
-spec module_postorder_from_funs([_], #dialyzer_callgraph{}) -> [[atom()]].
264
 
         
265
 
module_postorder_from_funs(Funs, CG = #dialyzer_callgraph{digraph=DG}) ->
 
259
 
 
260
module_postorder_from_funs(Funs, CG = #dialyzer_callgraph{digraph = DG}) ->
266
261
  SubGraph = digraph_reaching_subgraph(Funs, DG),
267
 
  PO = module_postorder(CG#dialyzer_callgraph{digraph=SubGraph}),
 
262
  PO = module_postorder(CG#dialyzer_callgraph{digraph = SubGraph}),
268
263
  digraph_delete(SubGraph),
269
264
  PO.
270
265
  
319
314
 
320
315
  %% Get rid of the 'top' function from nodes and edges.
321
316
  Names3 = ordsets:del_element(top, Names2),
322
 
  NamedEdges3 = [{From, To} || {From, To} <- NamedEdges2++NamedEdges1,
323
 
                               From =/= top, To =/= top],
 
317
  AllEdges = NamedEdges2 ++ NamedEdges1,
 
318
  NamedEdges3 = [E || {From, To} = E <- AllEdges, From =/= top, To =/= top],
324
319
 
325
 
  CG1 = add_edges(NamedEdges3, Names3, CG),  
 
320
  CG1 = add_edges(NamedEdges3, Names3, CG),
 
321
  {ModuleLocalCalls, InterModuleCalls} =
 
322
    case get(dialyzer_race_analysis) of
 
323
      true -> {remove_top_elements(NamedEdges1), NamedEdges2};
 
324
      _ -> {[], []}
 
325
    end,
326
326
  CG1#dialyzer_callgraph{calls=NewCalls,
327
327
                         esc=NewEsc,
328
328
                         name_map=NewNameMap,
329
329
                         rec_var_map=NewRecVarMap, 
330
330
                         rev_name_map=NewRevNameMap,
331
 
                         self_rec=SelfRecs}.
 
331
                         self_rec=SelfRecs,
 
332
                         module_local_calls=ModuleLocalCalls,
 
333
                         inter_module_calls=InterModuleCalls}.
332
334
 
333
335
build_maps(Tree, RecVarMap, NameMap, RevNameMap) ->
334
336
  %% We only care about the named (top level) functions. The anonymous
423
425
%% Digraph
424
426
%%
425
427
 
426
 
digraph_new() ->
427
 
  digraph:new().
428
 
 
429
428
digraph_add_edges([{From, To}|Left], DG) ->
430
429
  digraph_add_edges(Left, digraph_add_edge(From, To, DG));
431
430
digraph_add_edges([], DG) ->
530
529
  {NewModule, 
531
530
   [SCC || SCC <- Leaves, scc_belongs_to_module(SCC, NewModule)]}.
532
531
 
533
 
-spec scc_belongs_to_module(scc(), atom()) -> bool().
 
532
-spec scc_belongs_to_module(scc(), module()) -> bool().
534
533
 
535
534
scc_belongs_to_module([Label|Left], Module) when is_integer(Label) ->
536
535
  scc_belongs_to_module(Left, Module);
541
540
scc_belongs_to_module([], _Module) ->
542
541
  false.
543
542
      
544
 
-spec find_module(scc()) -> atom().
 
543
-spec find_module(scc()) -> module().
545
544
 
546
545
find_module([{M, _, _}|_]) -> M;
547
546
find_module([Label|Left]) when is_integer(Label) -> find_module(Left).
560
559
%% Utilities for 'dot'
561
560
%%=============================================================================
562
561
 
563
 
-ifndef(NO_UNUSED).
564
 
 
565
 
-spec to_dot(#dialyzer_callgraph{}) -> string().
566
 
 
567
 
to_dot(CG = #dialyzer_callgraph{digraph=DG, esc=Esc}) ->
 
562
-spec to_dot(#dialyzer_callgraph{}, filename()) -> 'ok'.
 
563
 
 
564
to_dot(#dialyzer_callgraph{digraph = DG, esc = Esc} = CG, File) ->
568
565
  Fun = fun(L) ->
569
566
            case lookup_name(L, CG) of
570
567
              error -> L;
574
571
  Escaping = [{Fun(L), {color, red}} 
575
572
              || L <- sets:to_list(Esc), L =/= external],
576
573
  Vertices = digraph_edges(DG),
577
 
  hipe_dot:translate_list(Vertices, "/tmp/cg.dot", "CG", Escaping),
578
 
  os:cmd("dot -T ps -o /tmp/cg.ps /tmp/cg.dot").
579
 
 
580
 
-endif.
 
574
  hipe_dot:translate_list(Vertices, File, "CG", Escaping).
 
575
 
 
576
-spec to_ps(#dialyzer_callgraph{}, filename(), string()) -> 'ok'.
 
577
 
 
578
to_ps(CG = #dialyzer_callgraph{}, File, Args) ->
 
579
  Dot_File = filename:rootname(File) ++ ".dot",
 
580
  to_dot(CG, Dot_File),
 
581
  Command = io_lib:format("dot -Tps ~s -o ~s ~s", [Args, File, Dot_File]),
 
582
  _ = os:cmd(Command),
 
583
  ok.
 
584
 
 
585
%%=============================================================================
 
586
%% Race Utilities
 
587
%%=============================================================================
 
588
 
 
589
remove_top_elements(Calls) ->
 
590
  [C || {From,_To} = C <- Calls, From =/= top].