~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

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/.
8
 
%%
 
11
%% retrieved online at http://www.erlang.org/.
 
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
 
%%
14
 
%% Copyright 2006-2008, Tobias Lindahl and Kostis Sagonas
15
 
%%
16
 
%% $Id$
 
17
%% 
 
18
%% %CopyrightEnd%
17
19
%%
18
20
 
19
21
%%%-------------------------------------------------------------------
29
31
         analyze_callgraph/4,
30
32
         get_warnings/6]).
31
33
 
32
 
%-define(DEBUG, true).
33
34
%% These are only intended as debug functions.
34
35
-export([doit/1,
35
36
         get_top_level_signatures/3]).
36
37
 
37
 
%-define(DEBUG_PP, true).
 
38
%%-define(DEBUG, true).
 
39
%%-define(DEBUG_PP, true).
38
40
 
39
41
-ifdef(DEBUG).
40
42
-define(debug(X__, Y__), io:format(X__, Y__)).
50
52
-include("dialyzer_callgraph.hrl").
51
53
 
52
54
%%--------------------------------------------------------------------
53
 
 
54
 
-record(state, {callgraph        :: #dialyzer_callgraph{},
55
 
                codeserver       :: #dialyzer_codeserver{},
56
 
                no_warn_unused   :: set(),
57
 
                parent=none      :: 'none' | pid(),
58
 
                plt              :: #dialyzer_plt{}}).
 
55
%% State record -- local to this module
 
56
 
 
57
-type parent() :: 'none' | pid().
 
58
 
 
59
-record(st, {callgraph      :: #dialyzer_callgraph{},
 
60
             codeserver     :: #dialyzer_codeserver{},
 
61
             no_warn_unused :: set(),
 
62
             parent = none  :: parent(),
 
63
             plt            :: #dialyzer_plt{}}).
59
64
 
60
65
%%--------------------------------------------------------------------
61
66
 
66
71
  analyze_callgraph(Callgraph, Plt, Codeserver, none).
67
72
 
68
73
-spec analyze_callgraph(#dialyzer_callgraph{}, #dialyzer_plt{},
69
 
                        #dialyzer_codeserver{}, 'none' | pid()) -> #dialyzer_plt{}.
 
74
                        #dialyzer_codeserver{}, parent()) -> #dialyzer_plt{}.
70
75
 
71
76
analyze_callgraph(Callgraph, Plt, Codeserver, Parent) ->
72
 
  State = #state{callgraph=Callgraph, plt=Plt, 
73
 
                 codeserver=Codeserver, parent=Parent},
 
77
  State = #st{callgraph = Callgraph, plt = Plt, 
 
78
              codeserver = Codeserver, parent = Parent},
74
79
  NewState = get_refined_success_typings(State),
75
 
  NewState#state.plt.
 
80
  NewState#st.plt.
76
81
 
77
82
%%--------------------------------------------------------------------
78
83
 
80
85
  case find_succ_typings(State) of
81
86
    {fixpoint, State1} -> State1;
82
87
    {not_fixpoint, NotFixpoint1, State1} ->
83
 
      Callgraph = State1#state.callgraph,
 
88
      Callgraph = State1#st.callgraph,
84
89
      NotFixpoint2 = [lookup_name(F, Callgraph) || F <- NotFixpoint1],
85
90
      ModulePostorder = 
86
91
        dialyzer_callgraph:module_postorder_from_funs(NotFixpoint2, Callgraph),
88
93
        {fixpoint, State2} ->
89
94
          State2;
90
95
        {not_fixpoint, NotFixpoint3, State2} ->
91
 
          Callgraph1 = State2#state.callgraph,
 
96
          Callgraph1 = State2#st.callgraph,
92
97
          %% Need to reset the callgraph.
93
98
          NotFixpoint4 = [lookup_name(F, Callgraph1) || F <- NotFixpoint3],
94
99
          Callgraph2 = dialyzer_callgraph:reset_from_funs(NotFixpoint4, 
95
100
                                                          Callgraph1),
96
 
          get_refined_success_typings(State2#state{callgraph=Callgraph2})
 
101
          get_refined_success_typings(State2#st{callgraph = Callgraph2})
97
102
      end
98
103
  end.
99
104
 
103
108
         {[dial_warning()], #dialyzer_plt{}, doc_plt()}.
104
109
 
105
110
get_warnings(Callgraph, Plt, DocPlt, Codeserver, NoWarnUnused, Parent) ->
106
 
  InitState = #state{callgraph=Callgraph, plt=Plt, no_warn_unused=NoWarnUnused,
107
 
                     codeserver=Codeserver, parent=Parent},
 
111
  InitState = #st{callgraph = Callgraph, codeserver = Codeserver,
 
112
                  no_warn_unused = NoWarnUnused, parent = Parent, plt = Plt},
108
113
  NewState = get_refined_success_typings(InitState),
109
 
  Mods = dialyzer_callgraph:modules(NewState#state.callgraph),
 
114
  Mods = dialyzer_callgraph:modules(NewState#st.callgraph),
110
115
  CWarns = dialyzer_contracts:get_invalid_contract_warnings(Mods, Codeserver,
111
 
                                                            NewState#state.plt),
 
116
                                                            NewState#st.plt),
112
117
  get_warnings_from_modules(Mods, NewState, DocPlt, CWarns).
113
118
 
114
 
get_warnings_from_modules([M|Left], State, DocPlt, Acc) when is_atom(M) ->
115
 
  send_log(State#state.parent, io_lib:format("Getting warnings for ~w\n", [M])),
116
 
  #state{plt=Plt, 
117
 
         callgraph=Callgraph,
118
 
         codeserver=Codeserver,
119
 
         no_warn_unused=NoWarnUnused} = State,
 
119
get_warnings_from_modules([M|Ms], State, DocPlt, Acc) when is_atom(M) ->
 
120
  send_log(State#st.parent, io_lib:format("Getting warnings for ~w\n", [M])),
 
121
  #st{callgraph = Callgraph, codeserver = Codeserver,
 
122
      no_warn_unused = NoWarnUnused, plt = Plt} = State,
120
123
  {ok, Tree} = dialyzer_codeserver:lookup(M, Codeserver),
121
124
  Records = dialyzer_codeserver:lookup_records(M, Codeserver),
122
125
  Contracts = dialyzer_codeserver:lookup_contracts(M, Codeserver),
124
127
  %% Check if there are contracts for functions that do not exist
125
128
  Warnings1 = 
126
129
    dialyzer_contracts:contracts_without_fun(Contracts, AllFuns, Callgraph),
127
 
  {Warnings2, FunTypes} = dialyzer_dataflow:get_warnings(Tree, Plt, Callgraph, 
128
 
                                                         Records, NoWarnUnused),
 
130
  {Warnings2, FunTypes, InterModuleCalls, ModLocalCalls} =
 
131
    dialyzer_dataflow:get_warnings(Tree, Plt, Callgraph, Records, NoWarnUnused),
129
132
  NewDocPlt = insert_into_doc_plt(FunTypes, Callgraph, DocPlt),
130
 
  get_warnings_from_modules(Left, State, NewDocPlt, [Warnings1,Warnings2|Acc]);
131
 
get_warnings_from_modules([], #state{plt=Plt}, DocPlt, Acc) ->
 
133
  NewCallgraph =
 
134
    callgraph__renew_module_calls(InterModuleCalls, ModLocalCalls, Callgraph),
 
135
  State1 = st__renew_state_calls(NewCallgraph, State),
 
136
  get_warnings_from_modules(Ms, State1, NewDocPlt, [Warnings1,Warnings2|Acc]);
 
137
get_warnings_from_modules([], #st{plt = Plt}, DocPlt, Acc) ->
132
138
  {lists:flatten(Acc), Plt, DocPlt}.
133
139
 
134
140
refine_succ_typings(ModulePostorder, State) ->
135
141
  ?debug("Module postorder: ~p\n", [ModulePostorder]),
136
142
  refine_succ_typings(ModulePostorder, State, []).
137
143
 
138
 
refine_succ_typings([SCC|Left], State, Fixpoint) ->
 
144
refine_succ_typings([SCC|SCCs], State, Fixpoint) ->
139
145
  Msg = io_lib:format("Dataflow of one SCC: ~w\n", [SCC]),
140
 
  send_log(State#state.parent, Msg),
 
146
  send_log(State#st.parent, Msg),
141
147
  ?debug("~s\n", [Msg]),
142
148
  {NewState, FixpointFromScc} =
143
149
    case SCC of
145
151
      [_|_] -> refine_one_scc(SCC, State)
146
152
    end,
147
153
  NewFixpoint = ordsets:union(Fixpoint, FixpointFromScc),
148
 
  refine_succ_typings(Left, NewState, NewFixpoint);
 
154
  refine_succ_typings(SCCs, NewState, NewFixpoint);
149
155
refine_succ_typings([], State, Fixpoint) ->
150
156
  case Fixpoint =:= [] of
151
157
    true -> {fixpoint, State};
152
158
    false -> {not_fixpoint, Fixpoint, State}
153
159
  end.
154
160
 
155
 
-spec refine_one_module(atom(), #state{}) -> {#state{}, ordset(non_neg_integer())}. % labels
 
161
-spec refine_one_module(module(), #st{}) -> {#st{}, [label()]}. % ordset
156
162
 
157
 
refine_one_module(M, State) ->      
158
 
  {ok, Tree} = dialyzer_codeserver:lookup(M, State#state.codeserver),
 
163
refine_one_module(M, State) ->
 
164
  #st{callgraph = Callgraph, codeserver = CodeServer, plt = PLT} = State,
 
165
  {ok, Tree} = dialyzer_codeserver:lookup(M, CodeServer),
159
166
  AllFuns = collect_fun_info([Tree]),
160
167
  FunTypes = get_fun_types_from_plt(AllFuns, State),
161
 
  Records = dialyzer_codeserver:lookup_records(M, State#state.codeserver),
162
 
  NewFunTypes = dialyzer_dataflow:get_fun_types(Tree, State#state.plt, 
163
 
                                                State#state.callgraph, Records),
 
168
  Records = dialyzer_codeserver:lookup_records(M, CodeServer),
 
169
  {NewFunTypes, InterModCalls, ModLocalCalls} =
 
170
    dialyzer_dataflow:get_fun_types(Tree, PLT, Callgraph, Records),
 
171
  NewCallgraph =
 
172
    callgraph__renew_module_calls(InterModCalls, ModLocalCalls, Callgraph),
164
173
  case reached_fixpoint(FunTypes, NewFunTypes) of
165
 
    true -> {State, []};
 
174
    true ->
 
175
      State1 = st__renew_state_calls(NewCallgraph, State),
 
176
      {State1, []};
166
177
    {false, NotFixpoint} ->
167
178
      ?debug("Not fixpoint\n", []),
168
179
      NewState = insert_into_plt(dict:from_list(NotFixpoint), State),
169
 
      {NewState, ordsets:from_list([FunLbl || {FunLbl, _Type} <- NotFixpoint])}
 
180
      NewState1 = st__renew_state_calls(NewCallgraph, NewState),
 
181
      {NewState1, ordsets:from_list([FunLbl || {FunLbl,_Type} <- NotFixpoint])}
170
182
  end.
171
183
 
 
184
callgraph__renew_module_calls(InterModuleCalls, ModuleLocalCalls, Callgraph) ->
 
185
  Callgraph#dialyzer_callgraph{inter_module_calls = InterModuleCalls,
 
186
                               module_local_calls = ModuleLocalCalls}.
 
187
 
 
188
st__renew_state_calls(Callgraph, State) ->
 
189
  State#st{callgraph = Callgraph}.
 
190
 
172
191
refine_one_scc(SCC, State) ->
173
192
  refine_one_scc(SCC, State, []).
174
193
 
181
200
      refine_one_scc(SCC, NewState, NewAccFixpoint)
182
201
  end.
183
202
 
184
 
refine_mods_in_scc([M|Left], State, Fixpoint) ->
185
 
  {NewState, FixpointFromModule} = refine_one_module(M, State),
 
203
refine_mods_in_scc([Mod|Mods], State, Fixpoint) ->
 
204
  {NewState, FixpointFromModule} = refine_one_module(Mod, State),
186
205
  NewFixpoint = ordsets:union(FixpointFromModule, Fixpoint),
187
 
  refine_mods_in_scc(Left, NewState, NewFixpoint);
 
206
  refine_mods_in_scc(Mods, NewState, NewFixpoint);
188
207
refine_mods_in_scc([], State, Fixpoint) ->
189
208
  {State, Fixpoint}.
190
209
 
209
228
  compare_types(OldTypes, NewTypes, Strict).
210
229
 
211
230
is_failed_or_not_called_fun(Type) ->
212
 
  any_none([erl_types:t_fun_range(Type)|erl_types:t_fun_args(Type)]).
 
231
  erl_types:any_none([erl_types:t_fun_range(Type)|erl_types:t_fun_args(Type)]).
213
232
 
214
 
any_none([T|Ts]) ->
215
 
  case erl_types:t_is_none(T) of
216
 
    true -> true;
217
 
    false -> any_none(Ts)
218
 
  end;
219
 
any_none([]) ->
220
 
  false.
221
 
      
222
233
compare_types(Dict1, Dict2, Strict) ->  
223
234
  List1 = lists:keysort(1, dict:to_list(Dict1)),
224
235
  List2 = lists:keysort(1, dict:to_list(Dict2)),
254
265
find_succ_typings(State) ->
255
266
  find_succ_typings(State, []).
256
267
 
257
 
find_succ_typings(State, NotFixpoint) ->
258
 
  case dialyzer_callgraph:take_scc(State#state.callgraph) of
 
268
find_succ_typings(#st{callgraph = Callgraph, parent = Parent} = State,
 
269
                  NotFixpoint) ->
 
270
  case dialyzer_callgraph:take_scc(Callgraph) of
259
271
    {ok, SCC, NewCallgraph} ->
260
 
      Msg = io_lib:format("Typesig analysis for scc: ~w\n", [format_scc(SCC)]),
261
 
      ?debug("~s\n", [Msg]),
262
 
      send_log(State#state.parent, Msg),
263
 
      {NewState, NewNotFixpoint1} = 
264
 
        analyze_scc(SCC, State#state{callgraph=NewCallgraph}),
 
272
      Msg = io_lib:format("Typesig analysis for SCC: ~w\n", [format_scc(SCC)]),
 
273
      ?debug("~s", [Msg]),
 
274
      send_log(Parent, Msg),
 
275
      {NewState, NewNotFixpoint1} =
 
276
        analyze_scc(SCC, State#st{callgraph = NewCallgraph}),
265
277
      NewNotFixpoint2 = ordsets:union(NewNotFixpoint1, NotFixpoint),
266
278
      find_succ_typings(NewState, NewNotFixpoint2);
267
279
    none ->
268
 
      ?debug("Done\n\n", []),
 
280
      ?debug("==================== Typesig done ====================\n\n", []),
269
281
      case NotFixpoint =:= [] of
270
282
        true -> {fixpoint, State};
271
283
        false -> {not_fixpoint, NotFixpoint, State}
272
284
      end
273
285
  end.
274
286
 
275
 
analyze_scc(SCC, State = #state{codeserver=Codeserver}) ->
 
287
analyze_scc(SCC, #st{codeserver = Codeserver} = State) ->
276
288
  SCC1 = [{MFA, 
277
289
           dialyzer_codeserver:lookup(MFA, Codeserver),
278
290
           dialyzer_codeserver:lookup_records(M, Codeserver)}
279
 
          || MFA = {M,_,_} <- SCC],
 
291
          || {M, _, _} = MFA <- SCC],
280
292
  false = lists:any(fun({_, X, _}) -> X =:= error end, SCC1),
281
293
  SCC2 = [{MFA, Def, Rec} || {MFA, {ok, Def}, Rec} <- SCC1],
282
294
  Contracts1 = [{MFA, dialyzer_codeserver:lookup_contract(MFA, Codeserver)}
283
 
                ||  MFA = {_, _, _} <- SCC],
 
295
                || {_, _, _} = MFA <- SCC],
284
296
  Contracts2 = [{MFA, Contract} || {MFA, {ok, Contract}} <- Contracts1],
285
297
  Contracts3 = orddict:from_list(Contracts2),
286
298
  {SuccTypes, PltContracts, NotFixpoint} = 
287
299
    find_succ_types_for_scc(SCC2, Contracts3, State),
288
300
  State1 = insert_into_plt(SuccTypes, State),
289
 
  ContrPlt = dialyzer_plt:insert_contract_list(State1#state.plt, PltContracts),
290
 
  {State1#state{plt=ContrPlt}, NotFixpoint}.
 
301
  ContrPlt = dialyzer_plt:insert_contract_list(State1#st.plt, PltContracts),
 
302
  {State1#st{plt = ContrPlt}, NotFixpoint}.
291
303
 
292
304
find_succ_types_for_scc(SCC, Contracts, 
293
 
                        State = #state{codeserver=Codeserver, 
294
 
                                       callgraph=Callgraph,
295
 
                                       plt=Plt}) ->
296
 
  %% Assume that the Plt contains the current propagated types.
 
305
                        #st{codeserver = Codeserver, 
 
306
                            callgraph = Callgraph, plt = Plt} = State) ->
 
307
  %% Assume that the PLT contains the current propagated types
297
308
  AllFuns = collect_fun_info([Fun || {_MFA, {_Var, Fun}, _Rec} <- SCC]),
298
309
  PropTypes = get_fun_types_from_plt(AllFuns, State),
299
310
  MFAs = [MFA || {MFA, {_Var, _Fun}, _Rec} <- SCC],
300
311
  NextLabel = dialyzer_codeserver:next_core_label(Codeserver),
301
 
  Plt1 = dialyzer_plt:delete_contract_list(State#state.plt, MFAs),
 
312
  Plt1 = dialyzer_plt:delete_contract_list(Plt, MFAs),
302
313
  FunTypes = dialyzer_typesig:analyze_scc_get_all_fun_types(SCC, NextLabel, 
303
314
                                                            Callgraph, Plt1, 
304
315
                                                            PropTypes),
305
316
  AllFunSet = sets:from_list([X || {X, _} <- AllFuns]),
306
 
  FilteredFunTypes = dict:filter(fun(X, _) -> 
307
 
                                     sets:is_element(X, AllFunSet) 
308
 
                                 end, FunTypes),
 
317
  FilteredFunTypes = dict:filter(fun(X, _) ->
 
318
                                      sets:is_element(X, AllFunSet) 
 
319
                                  end, FunTypes),
309
320
  %% Check contracts
310
321
  PltContracts = dialyzer_contracts:check_contracts(Contracts, Callgraph, 
311
322
                                                    FilteredFunTypes),
312
323
  ContractFixpoint =
313
 
    not lists:any(fun({MFA, _C}) ->
314
 
                      %% Check the non-deleted plt
315
 
                      case dialyzer_plt:lookup_contract(Plt, MFA) of
316
 
                        none -> true;
317
 
                        {value, _} -> false
318
 
                      end
319
 
                  end, PltContracts),
 
324
    lists:all(fun({MFA, _C}) ->
 
325
                  %% Check the non-deleted PLT
 
326
                  case dialyzer_plt:lookup_contract(Plt, MFA) of
 
327
                    none -> false;
 
328
                    {value, _} -> true
 
329
                  end
 
330
              end, PltContracts),
320
331
  case (ContractFixpoint andalso 
321
332
        reached_fixpoint_strict(PropTypes, FilteredFunTypes)) of
322
333
    true ->
323
334
      {FilteredFunTypes, PltContracts, []};
324
 
    false -> 
 
335
    false ->
325
336
      ?debug("Not fixpoint for: ~w\n", [AllFuns]),
326
 
      {FilteredFunTypes, PltContracts, 
 
337
      {FilteredFunTypes, PltContracts,
327
338
       ordsets:from_list([Fun || {Fun, _Arity} <- AllFuns])}
328
339
  end.
329
340
 
339
350
collect_fun_info(Trees) ->
340
351
  collect_fun_info(Trees, []).
341
352
 
342
 
collect_fun_info([Tree|Left], List) ->
343
 
  FoldFun = fun(SubTree, Acc) ->
344
 
                case cerl:is_c_fun(SubTree) of
345
 
                  true -> [{cerl_trees:get_label(SubTree), 
346
 
                            cerl:fun_arity(SubTree)}|Acc];
347
 
                  false -> Acc
348
 
                end
349
 
            end,
350
 
  collect_fun_info(Left, cerl_trees:fold(FoldFun, List, Tree));
 
353
collect_fun_info([Tree|Trees], List) ->
 
354
  Fun = fun(SubTree, Acc) ->
 
355
            case cerl:is_c_fun(SubTree) of
 
356
              true ->
 
357
                [{cerl_trees:get_label(SubTree), cerl:fun_arity(SubTree)}|Acc];
 
358
              false -> Acc
 
359
            end
 
360
        end,
 
361
  collect_fun_info(Trees, cerl_trees:fold(Fun, List, Tree));
351
362
collect_fun_info([], List) ->
352
363
  List.
353
364
 
354
 
lookup_fun_type(Label, Arity, #state{callgraph=Callgraph, plt=Plt}) ->  
 
365
lookup_fun_type(Label, Arity, #st{callgraph = Callgraph, plt = Plt}) ->
355
366
  ID = lookup_name(Label, Callgraph),
356
367
  case dialyzer_plt:lookup(Plt, ID) of
357
368
    none -> erl_types:t_fun(Arity, erl_types:t_any());
364
375
  SuccTypes = format_succ_types(FunTypes, Callgraph),
365
376
  dialyzer_plt:insert_list(DocPlt, SuccTypes).
366
377
 
367
 
insert_into_plt(SuccTypes0, State = #state{callgraph=Callgraph, plt=Plt}) ->
 
378
insert_into_plt(SuccTypes0, #st{callgraph = Callgraph, plt = Plt} = State) ->
368
379
  SuccTypes = format_succ_types(SuccTypes0, Callgraph),
369
380
  debug_pp_succ_typings(SuccTypes),
370
 
  State#state{plt=dialyzer_plt:insert_list(Plt, SuccTypes)}.
 
381
  State#st{plt = dialyzer_plt:insert_list(Plt, SuccTypes)}.
371
382
 
372
383
format_succ_types(SuccTypes, Callgraph) ->
373
384
  format_succ_types(dict:to_list(SuccTypes), Callgraph, []).
383
394
-ifdef(DEBUG).
384
395
debug_pp_succ_typings(SuccTypes) ->
385
396
  ?debug("Succ typings:\n", []),
386
 
  [?debug("\t~w\t~s\n", 
 
397
  [?debug("  ~w :: ~s\n", 
387
398
          [MFA, erl_types:t_to_string(erl_types:t_fun(ArgT, RetT))])
388
 
   ||{MFA, RetT, ArgT} <- SuccTypes],
389
 
  [?debug("\t~w\t~s\n", 
 
399
   || {MFA, {RetT, ArgT}} <- SuccTypes],
 
400
  ?debug("Contracts:\n", []),
 
401
  [?debug("  ~w :: ~s\n", 
390
402
          [MFA, erl_types:t_to_string(erl_types:t_fun(ArgT, RetFun(ArgT)))])
391
 
   ||{MFA, {contract, RetFun, ArgT}} <- SuccTypes],
 
403
   || {MFA, {contract, RetFun, ArgT}} <- SuccTypes],
 
404
  ?debug("\n", []),
392
405
  ok.
393
406
-else.
394
 
debug_pp_succ_typings(_) ->  
 
407
debug_pp_succ_typings(_) ->
395
408
  ok.
396
409
-endif.
397
410
 
408
421
  ok.
409
422
 
410
423
format_scc(SCC) ->
411
 
  [X || X = {_M, _F, _A} <- SCC].
 
424
  [MFA || {_M, _F, _A} = MFA <- SCC].
412
425
 
413
426
%% ============================================================================
414
427
%%
416
429
%%
417
430
%% ============================================================================
418
431
 
419
 
-spec doit(atom() | string()) -> 'ok'.
 
432
-spec doit(module() | string()) -> 'ok'.
420
433
 
421
434
doit(Module) ->
422
435
  {ok, AbstrCode} = dialyzer_utils:get_abstract_code_from_src(Module),
425
438
  %% contract typing info in dictionary format
426
439
  {ok, Contracts} = dialyzer_utils:get_spec_info(AbstrCode, Records),
427
440
  Sigs0 = get_top_level_signatures(Code, Records, Contracts),
428
 
  M = 
429
 
    if is_atom(Module) ->  
430
 
        list_to_atom(filename:basename(atom_to_list(Module)));
431
 
       is_list(Module) -> 
432
 
        list_to_atom(filename:basename(Module))
433
 
    end,
 
441
  M = if is_atom(Module) ->  
 
442
          list_to_atom(filename:basename(atom_to_list(Module)));
 
443
         is_list(Module) -> 
 
444
          list_to_atom(filename:basename(Module))
 
445
      end,
434
446
  Sigs1 = [{{M, F, A}, Type} || {{F, A}, Type} <- Sigs0],
435
447
  Sigs = ordsets:from_list(Sigs1),
436
 
  io:nl(),
 
448
  io:format("==================== Final result ====================\n\n", []),
437
449
  pp_signatures(Sigs, Records),
438
450
  ok.
439
451
 
440
452
-spec get_top_level_signatures(core_records(), dict(), dict()) ->
441
 
                ordset({{atom(),byte()},erl_type()}).
 
453
                [{{atom(), arity()}, erl_type()}].
442
454
 
443
455
get_top_level_signatures(Code, Records, Contracts) ->
444
456
  Tree = cerl:from_records(Code),
473
485
  pp_signatures(Left, Records);
474
486
pp_signatures([{{_, module_info, 1}, _}|Left], Records) -> 
475
487
  pp_signatures(Left, Records);
476
 
pp_signatures([{{M, F, A}, Type}|Left], Records) ->
 
488
pp_signatures([{{M, F, _A}, Type}|Left], Records) ->
477
489
  TypeString =
478
490
    case cerl:is_literal(Type) of
479
491
      true -> io_lib:format("~w", [cerl:concrete(Type)]);
480
 
      false -> "fun" ++ String = erl_types:t_to_string(Type, Records),
481
 
               String
 
492
      false -> "fun(" ++ String = erl_types:t_to_string(Type, Records),
 
493
               string:strip(String, right, $))
482
494
    end,
483
 
  io:format("~w:~w/~w :: ~s\n", [M, F, A, TypeString]),
 
495
  io:format("~w:~w~s\n", [M, F, TypeString]),
484
496
  pp_signatures(Left, Records);
485
497
pp_signatures([], _Records) ->
486
498
  ok.
500
512
                         cerl:set_ann(T, [{'label', Label}])
501
513
                     end
502
514
                 end, Tree).
503
 
                            
504
515
-else.
505
 
debug_pp(_Tree, _Map) -> 
 
516
debug_pp(_Tree, _Map) ->
506
517
  ok.
507
518
-endif. % DEBUG_PP
508
519
 
519
530
  ModuleName = cerl:concrete(cerl:module_name(LabeledTree)),
520
531
  Insert = [{ModuleName, LabeledTree}],
521
532
  Codeserver2 = dialyzer_codeserver:insert(Insert, Codeserver1),
522
 
  Codeserver3 = 
 
533
  Codeserver3 =
523
534
    dialyzer_codeserver:update_next_core_label(NextLabel, Codeserver2),
524
 
  Codeserver4 = 
 
535
  Codeserver4 =
525
536
    dialyzer_codeserver:store_records(ModuleName, Records, Codeserver3),
526
 
  Codeserver5 =  
 
537
  Codeserver5 =
527
538
    dialyzer_codeserver:store_contracts(ModuleName, Contracts, Codeserver4),
528
539
  Res = analyze_callgraph(Callgraph4, Plt, Codeserver5),
529
540
  dialyzer_callgraph:delete(Callgraph4),