~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): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% -*- erlang-indent-level: 2 -*-
 
2
%%--------------------------------------------------------------------
 
3
%% ``The contents of this file are subject to the Erlang Public License,
 
4
%% Version 1.1, (the "License"); you may not use this file except in
 
5
%% compliance with the License. You should have received a copy of the
 
6
%% 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
%% 
 
9
%% Software distributed under the License is distributed on an "AS IS"
 
10
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
11
%% the License for the specific language governing rights and limitations
 
12
%% under the License.
 
13
%% 
 
14
%% Copyright 2006, Tobias Lindahl and Kostis Sagonas
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
 
 
19
%%%-------------------------------------------------------------------
 
20
%%% File    : dialyzer_analysis_callgraph.erl
 
21
%%% Author  : Tobias Lindahl <tobiasl@it.uu.se>
 
22
%%% Description : 
 
23
%%%
 
24
%%% Created :  5 Apr 2005 by Tobias Lindahl <tobiasl@it.uu.se>
 
25
%%%-------------------------------------------------------------------
 
26
-module(dialyzer_analysis_callgraph).
 
27
 
 
28
-export([start/3]).
 
29
 
 
30
-include("dialyzer.hrl").
 
31
 
 
32
-record(analysis_state, 
 
33
        {  
 
34
          codeserver,
 
35
          core_transform,
 
36
          defines,
 
37
          doc_plt,
 
38
          include_dirs,
 
39
          no_warn_unused,
 
40
          options,
 
41
          parent,
 
42
          plt,
 
43
          start_from,
 
44
          supress_inline
 
45
         }).
 
46
 
 
47
-record(state, {parent, legal_warnings}).
 
48
 
 
49
-define(HIPE_COMPILE_OPTS, [dialyzer|?HIPE_DEF_OPTS]).
 
50
 
 
51
%%____________________________________________________________
 
52
%%
 
53
%% Main
 
54
%%
 
55
 
 
56
start(Parent, LegalWarnings, Analysis) ->
 
57
  NewAnalysis1 = expand_files(Analysis),
 
58
  init_plt(NewAnalysis1),
 
59
  NewAnalysis2 = run_analysis(NewAnalysis1),
 
60
  State = #state{parent=Parent, legal_warnings=LegalWarnings},
 
61
  loop(State, NewAnalysis2, none).
 
62
 
 
63
run_analysis(Analysis) ->
 
64
  Self = self(),
 
65
  Fun = fun() -> analysis_start(Self, Analysis) end,
 
66
  Analysis#analysis{analysis_pid=spawn_link(Fun)}.
 
67
 
 
68
loop(State, Analysis = #analysis{}, ExtCalls) ->
 
69
  AnalPid = Analysis#analysis.analysis_pid,
 
70
  Parent = State#state.parent,
 
71
  receive
 
72
    {AnalPid, log, LogMsg} ->
 
73
      send_log(Parent, LogMsg),
 
74
      loop(State, Analysis, ExtCalls);
 
75
    {AnalPid, warnings, Warnings} ->
 
76
      case filter_warnings(State#state.legal_warnings, Warnings) of
 
77
        [] -> ok;
 
78
        SendWarnings ->
 
79
          send_warnings(Parent, SendWarnings)
 
80
      end,
 
81
      loop(State, Analysis, ExtCalls);
 
82
    {AnalPid, error, Msg} ->
 
83
      send_error(Parent, Msg),
 
84
      loop(State, Analysis, ExtCalls);
 
85
    {AnalPid, done} ->      
 
86
      case ExtCalls of
 
87
        none ->
 
88
          send_analysis_done(Parent);
 
89
        _ ->
 
90
          send_ext_calls(Parent, ExtCalls),
 
91
          send_analysis_done(Parent)
 
92
      end;
 
93
    {AnalPid, ext_calls, NewExtCalls} ->
 
94
      loop(State, Analysis, NewExtCalls);
 
95
    {Parent, stop} ->
 
96
      exit(AnalPid, kill),
 
97
      ok
 
98
  end.
 
99
 
 
100
%%____________________________________________________________
 
101
%%
 
102
%% The Analysis
 
103
%%
 
104
 
 
105
analysis_start(Parent, Analysis) ->
 
106
  %%XXX: Until we move the icode analysis out of HiPE
 
107
  put(hipe_target_arch, x86), 
 
108
  
 
109
  CServer = dialyzer_codeserver:new(),
 
110
 
 
111
  Plt = Analysis#analysis.user_plt,
 
112
  State = #analysis_state{codeserver=CServer,
 
113
                          core_transform=Analysis#analysis.core_transform,
 
114
                          defines=Analysis#analysis.defines,
 
115
                          doc_plt=Analysis#analysis.doc_plt,
 
116
                          include_dirs=Analysis#analysis.include_dirs,
 
117
                          plt=Plt,
 
118
                          parent=Parent,
 
119
                          start_from=Analysis#analysis.start_from,
 
120
                          supress_inline=Analysis#analysis.supress_inline
 
121
                         },
 
122
  Files = ordsets:from_list(Analysis#analysis.files),
 
123
  {Callgraph, NoWarn, NewCServer} = compile_and_store(Files, State),
 
124
  State1 = State#analysis_state{codeserver=NewCServer},
 
125
  State2 = State1#analysis_state{no_warn_unused=NoWarn},
 
126
  %% Remove all old versions of the files being analyzed
 
127
  dialyzer_plt:delete_list(Plt, dialyzer_callgraph:all_nodes(Callgraph)),
 
128
  analyze_callgraph(Callgraph, State2),
 
129
  dialyzer_callgraph:delete(Callgraph),
 
130
  Exports = dialyzer_codeserver:all_exports(NewCServer),
 
131
  dialyzer_plt:strip_non_member_mfas(Plt, Exports),
 
132
  send_analysis_done(Parent).
 
133
  
 
134
analyze_callgraph(Callgraph, State) ->
 
135
  case State#analysis_state.core_transform of
 
136
    succ_typings ->
 
137
      Plt = State#analysis_state.plt,
 
138
      Codeserver = State#analysis_state.codeserver,
 
139
      Callgraph1 = dialyzer_callgraph:finalize(Callgraph),
 
140
      dialyzer_succ_typings:analyze_callgraph(Callgraph1, Plt, Codeserver);
 
141
    cerl_typean ->
 
142
      case erlang:system_info(schedulers) of
 
143
        1 -> 
 
144
          Callgraph1 = dialyzer_callgraph:finalize(Callgraph),
 
145
          analyze_callgraph_single_threaded(Callgraph1, State);
 
146
        N when is_integer(N), N > 1 -> 
 
147
          analyze_callgraph_in_parallell(Callgraph, State, N)
 
148
      end
 
149
  end.
 
150
 
 
151
analyze_callgraph_in_parallell(Callgraph, State, N) ->
 
152
  CallgraphList1 = dialyzer_callgraph:split_into_components(Callgraph),
 
153
  CallgraphList2 = [dialyzer_callgraph:finalize(CG) || CG <- CallgraphList1],
 
154
  parallell_analysis_loop(CallgraphList2, State, 0, N).
 
155
 
 
156
parallell_analysis_loop([], #analysis_state{parent=Parent}, 0, _MaxProc) ->
 
157
  send_analysis_done(Parent),
 
158
  ok;
 
159
parallell_analysis_loop([CG|CGs], State, Running, MaxProc) 
 
160
  when Running < MaxProc ->
 
161
  Pid = self(),
 
162
  spawn_link(fun()->
 
163
                 %%XXX: Until we move the icode analysis out of HiPE
 
164
                 put(hipe_target_arch, x86), 
 
165
                 %%io:format("Starting with nodes: ~p\n",
 
166
                 %%          [dialyzer_callgraph:all_nodes(CG)]),
 
167
                 %% Hijack our parents messages.
 
168
                 State1 = State#analysis_state{parent=Pid},
 
169
                 analyze_callgraph_single_threaded(CG, State1),
 
170
                 Pid ! done
 
171
             end),
 
172
  parallell_analysis_loop(CGs, State, Running+1, MaxProc);
 
173
parallell_analysis_loop(CGs, State, Running, MaxProc) ->
 
174
  Parent =  State#analysis_state.parent,
 
175
  receive
 
176
    {_Pid, log, LogMsg} ->
 
177
      Parent ! {self(), log, LogMsg},
 
178
      parallell_analysis_loop(CGs, State, Running, MaxProc);
 
179
    {_Pid, warnings, Warnings} -> 
 
180
      Parent ! {self(), warnings, Warnings},
 
181
      parallell_analysis_loop(CGs, State, Running, MaxProc);
 
182
    {_Pid, error, Msg} ->
 
183
      Parent ! {self(), error, Msg},
 
184
      parallell_analysis_loop(CGs, State, Running, MaxProc);
 
185
    done ->
 
186
      parallell_analysis_loop(CGs, State, Running - 1, MaxProc)
 
187
  end.
 
188
 
 
189
analyze_callgraph_single_threaded(Callgraph, State) ->
 
190
  case dialyzer_callgraph:take_scc(Callgraph) of
 
191
    {ok, SCC, NewCallgraph} ->
 
192
      case State#analysis_state.core_transform of
 
193
        cerl_typean ->
 
194
          %% Since we are only analyzing once, we can use the top-down
 
195
          %% version to get the warnings etc.
 
196
          analyze_scc_warnings(SCC, Callgraph, State);
 
197
        succ_typings ->
 
198
          analyze_scc_succ_typings(SCC, Callgraph, State)
 
199
      end,
 
200
      analyze_callgraph_single_threaded(NewCallgraph, State);
 
201
    none ->
 
202
      ok
 
203
  end.
 
204
 
 
205
analyze_scc_succ_typings(SCC, Callgraph, State) ->
 
206
  Parent = State#analysis_state.parent,
 
207
  %%io:format("Analyzing scc: ~w\n", [SCC]),
 
208
  Msg = io_lib:format("Analyzing SCC: ~p\n", [SCC]),
 
209
  send_log(Parent, Msg),
 
210
  CServer = State#analysis_state.codeserver,
 
211
  NextLabel = dialyzer_codeserver:next_core_label(CServer),
 
212
  SCC1 = [{MFA, dialyzer_codeserver:lookup(MFA, core, CServer)}
 
213
          || MFA <- SCC, is_integer(MFA) =:= false],
 
214
  false = lists:any(fun({_, X}) -> X =:= error end, SCC1),
 
215
  SCC2 = [{MFA, Def} || {MFA, {ok, Def}} <- SCC1],
 
216
  Plt = State#analysis_state.plt,
 
217
  SuccTypes0 = dialyzer_typesig:analyze_scc(SCC2, NextLabel, Callgraph, Plt),
 
218
  SuccTypes1 = [{MFA, erl_types:t_fun_range(T), erl_types:t_fun_args(T)}
 
219
                || {MFA, T} <- SuccTypes0],
 
220
%  io:format("Succ typings:\n", []),
 
221
%  [io:format("\t~w\t~s\n", [MFA, erl_types:t_to_string(Type)])
 
222
%   ||{MFA, Type} <- SuccTypes0],
 
223
  dialyzer_plt:insert(Plt, SuccTypes1).
 
224
 
 
225
analyze_scc_warnings([Fun], Callgraph, State=#analysis_state{parent=Parent}) ->
 
226
  Msg = io_lib:format("Analyzing Fun: ~p\n", [Fun]),
 
227
  send_log(Parent, Msg),  
 
228
  case dialyzer_callgraph:is_self_rec(Fun, Callgraph) of
 
229
    true -> analyze_scc_icode([Fun], State);
 
230
    false -> 
 
231
      {_, Warnings} = analyze_fun_icode(Fun, State),
 
232
      send_warnings(Parent, Warnings)
 
233
  end;
 
234
analyze_scc_warnings(SCC, _Callgraph, State = #analysis_state{parent=Parent}) ->
 
235
  %%io:format("Analyzing scc: ~p\n", [SCC]),
 
236
  Msg = io_lib:format("Analyzing SCC: ~p\n", [SCC]),
 
237
  send_log(Parent, Msg),
 
238
  analyze_scc_icode(SCC, State).
 
239
 
 
240
analyze_scc_icode(SCC, State = #analysis_state{parent=Parent}) ->
 
241
  Res = [analyze_fun_icode(MFA, State) || MFA <- SCC],
 
242
  case lists:any(fun({X, _}) -> X =:= not_fixpoint end, Res) of
 
243
    true -> 
 
244
      analyze_scc_icode(SCC, State);
 
245
    false -> 
 
246
      send_log(Parent, "Reached fixpoint for SCC\n"),
 
247
      Warnings = lists:foldl(fun({_, W}, Acc) -> W ++ Acc end, [], Res),
 
248
      send_warnings(Parent, Warnings)
 
249
  end.
 
250
 
 
251
analyze_fun_icode(MFA, #analysis_state{codeserver=CServer, doc_plt=DocPlt,
 
252
                                       no_warn_unused=NoWarn,
 
253
                                       parent=Parent, plt=Plt}) ->
 
254
  %%io:format("Analyzing icode for: ~p\n", [MFA]),
 
255
  case dialyzer_codeserver:lookup(MFA, icode, CServer) of
 
256
    {ok, CFG} ->
 
257
      Msg1 = io_lib:format("  Analyzing icode for: ~p ...", [MFA]),
 
258
      send_log(Parent, Msg1),
 
259
      {T1, _} = statistics(runtime),
 
260
      Res = dialyzer_icode:run_analysis(CFG, MFA, Plt, NoWarn, true),
 
261
      {T2, _} = statistics(runtime),
 
262
      Msg2 = io_lib:format("done in ~.2f secs\n", [(T2-T1)/1000]),
 
263
      send_log(Parent, Msg2),
 
264
      case Res of
 
265
        {not_fixpoint, UpdateInfo, Warnings} ->
 
266
          if DocPlt =:= undefined -> ok;
 
267
             true -> dialyzer_plt:insert(DocPlt, [UpdateInfo])
 
268
          end,
 
269
          dialyzer_plt:insert(Plt, [UpdateInfo]),
 
270
          {not_fixpoint, Warnings};
 
271
        {fixpoint, UpdateInfo, Warnings} ->
 
272
          if DocPlt =:= undefined -> ok;
 
273
             true -> dialyzer_plt:insert(DocPlt, [UpdateInfo])
 
274
          end,
 
275
          dialyzer_plt:insert(Plt, [UpdateInfo]),
 
276
          {fixpoint, Warnings}
 
277
      end;
 
278
    error ->
 
279
      %% Since hipe removes module_info it is ok to not find the code
 
280
      %% for it. The only time this happens is when we start from
 
281
      %% byte_code and there is no abstract code.
 
282
      case MFA of
 
283
        {_, module_info, 0} -> ok;
 
284
        {_, module_info, 1} -> ok;
 
285
        _ ->
 
286
          Msg = io_lib:format("Could not find icode for ~w\n", [MFA]),
 
287
          send_error(Parent, Msg)
 
288
      end,
 
289
      {fixpoint, []}
 
290
  end.
 
291
 
 
292
%%____________________________________________________________
 
293
%%
 
294
%% Build the callgraph and fill the codeserver.
 
295
%%
 
296
 
 
297
compile_and_store(Files, State = #analysis_state{}) ->
 
298
  send_log(State#analysis_state.parent, 
 
299
           "Reading files and computing callgraph\n"),
 
300
  {T1, _} = statistics(runtime),
 
301
  Includes = [{i, X} || X <- State#analysis_state.include_dirs],
 
302
  Defines = [{d, Macro, Val} || {Macro, Val} <- State#analysis_state.defines],
 
303
  Callgraph = dialyzer_callgraph:new(),
 
304
  CoreTransform = State#analysis_state.core_transform,
 
305
  Plt = State#analysis_state.plt,
 
306
  case State#analysis_state.start_from of
 
307
    src_code -> 
 
308
      Fun = fun(File, {TmpCG, TmpCServer, TmpFailed, TmpNoWarn}) ->
 
309
                case compile_src(File, Includes, Defines, 
 
310
                                 TmpCG, TmpCServer, CoreTransform, Plt) of
 
311
                  {error, Reason} -> 
 
312
                    {TmpCG, TmpCServer, [{File, Reason}|TmpFailed], TmpNoWarn};
 
313
                  {ok, NewCG, NoWarn, NewCServer} -> 
 
314
                    {NewCG, NewCServer, TmpFailed, NoWarn++TmpNoWarn}
 
315
                end
 
316
            end;
 
317
    byte_code ->
 
318
      Fun = fun(File, {TmpCG, TmpCServer, TmpFailed, TmpNoWarn}) -> 
 
319
                case compile_byte(File, TmpCG, TmpCServer, 
 
320
                                  CoreTransform, Plt) of
 
321
                  {error, Reason} -> 
 
322
                    {TmpCG, TmpCServer, [{File, Reason}|TmpFailed], TmpNoWarn};
 
323
                  {ok, NewCG, NoWarn, NewCServer} -> 
 
324
                    {NewCG, NewCServer, TmpFailed, NoWarn++TmpNoWarn}
 
325
                end
 
326
            end
 
327
  end,
 
328
  CServer = State#analysis_state.codeserver,
 
329
  {NewCallgraph1, NewCServer, Failed, NoWarn} = 
 
330
    lists:foldl(Fun, {Callgraph, CServer, [], []}, Files),
 
331
  {T2, _} = statistics(runtime),
 
332
  Msg1 = io_lib:format("Done scanning and gathering edges in ~.2f secs\n"
 
333
                       "Removing edges\n", 
 
334
                       [(T2-T1)/1000]),
 
335
  send_log(State#analysis_state.parent, Msg1),
 
336
 
 
337
  %%io:format("All exports: ~p\n", [dialyzer_codeserver:all_exports(NewCServer)]),
 
338
  
 
339
  NewCallgraph2 = cleanup_callgraph(State, NewCServer, NewCallgraph1, Files),
 
340
  send_scan_fail(State#analysis_state.parent, Failed),
 
341
  {T3, _} = statistics(runtime),
 
342
  Msg2 = io_lib:format("Done removing edges in ~.2g secs\n", [(T3-T2)/1000]),
 
343
  send_log(State#analysis_state.parent, Msg2),  
 
344
  {NewCallgraph2, sets:from_list(NoWarn), NewCServer}.
 
345
 
 
346
cleanup_callgraph(#analysis_state{plt=InitPlt, parent=Parent, 
 
347
                                   start_from=StartFrom}, 
 
348
                   CServer, Callgraph, Files) ->
 
349
  {Callgraph1, ExtCalls} = dialyzer_callgraph:remove_external(Callgraph),
 
350
  ExtCalls1 = lists:filter(fun({_From, To}) -> 
 
351
                               not dialyzer_plt:contains_mfa(InitPlt, To)
 
352
                           end, ExtCalls),
 
353
  {BadCalls1, RealExtCalls} =
 
354
    if ExtCalls1 =:= [] -> {[], []};
 
355
       true -> 
 
356
        Modules = 
 
357
          case StartFrom of
 
358
            byte_code -> [list_to_atom(filename:basename(F, ".beam"))
 
359
                          || F <- Files];
 
360
            src_code -> [list_to_atom(filename:basename(F, ".erl"))
 
361
                         || F <- Files]
 
362
          end,
 
363
        ModuleSet = sets:from_list(Modules),
 
364
        lists:partition(fun({_From, {M, _F, _A}}) -> 
 
365
                            sets:is_element(M, ModuleSet)
 
366
                        end, ExtCalls1)
 
367
    end,
 
368
  NonLocalCalls = dialyzer_callgraph:non_local_calls(Callgraph1),
 
369
  BadCalls2 = lists:filter(fun({_From, To}) ->
 
370
                               not dialyzer_codeserver:is_exported(To, CServer)
 
371
                           end, NonLocalCalls),
 
372
  case BadCalls1 ++ BadCalls2 of
 
373
    [] -> ok;
 
374
    BadCalls -> send_bad_calls(Parent, BadCalls)
 
375
  end,
 
376
  if RealExtCalls =:= [] -> ok;
 
377
     true ->
 
378
      send_ext_calls(Parent, lists:usort([To || {_From, To} <- RealExtCalls]))
 
379
  end,
 
380
  Callgraph1.
 
381
 
 
382
compile_src(File, Includes, Defines, Callgraph, CServer, CoreTransform, Plt) ->
 
383
  DefaultIncludes = default_includes(filename:dirname(File)),
 
384
  CompOpts = ?SRC_COMPILE_OPTS ++ Includes++Defines++DefaultIncludes,
 
385
  Mod = list_to_atom(filename:basename(File, ".erl")),
 
386
  case compile:file(File, [to_pp, binary|CompOpts]) of
 
387
    error -> {error, []};
 
388
    {error, Errors, _} -> {error, format_errors(Errors)};
 
389
    {ok, _, AbstrCode} ->
 
390
      case abs_get_core(AbstrCode, Mod) of
 
391
        error -> error;
 
392
        {Core, NoWarn} ->
 
393
          compile_core(Mod, Core, NoWarn, Callgraph, 
 
394
                       CServer, CoreTransform, Plt)
 
395
      end
 
396
  end.
 
397
 
 
398
compile_byte(File, Callgraph, CServer, CoreTransform, Plt) ->
 
399
  %% We must always set the code path, because the hipe compiler
 
400
  %% does a M:module_info() call!
 
401
  OldPath = code:get_path(),
 
402
  Mod = list_to_atom(filename:basename(File, ".beam")),
 
403
  Dir = filename:dirname(File),
 
404
  case code:add_patha(Dir) of
 
405
    true ->            
 
406
      Res = 
 
407
        case beam_get_core(File, Mod) of
 
408
          error ->        
 
409
            case (catch hipe:c(Mod, ?HIPE_COMPILE_OPTS)) of
 
410
              {'EXIT', Why} -> {error, io_lib:format("~p", [Why])};
 
411
              {error, Why} -> {error, io_lib:format("~p", [Why])};
 
412
              {ok, Icode} ->
 
413
                CServer1 = dialyzer_codeserver:insert(Icode, icode, CServer),
 
414
                Exp = beam_get_exports(File),
 
415
                CServer2 = dialyzer_codeserver:insert_exports(Exp, CServer1),
 
416
                NewCG = dialyzer_callgraph:scan_icode(Icode, Callgraph),
 
417
                NoWarn = beam_get_nowarn(File),
 
418
                {ok, NewCG, NoWarn, CServer2}
 
419
            end;
 
420
          {Core, NoWarn} ->
 
421
            compile_core(Mod, Core, NoWarn, Callgraph, 
 
422
                         CServer, CoreTransform, Plt)
 
423
        end,
 
424
      true = code:set_path(OldPath),
 
425
      Res;
 
426
    false ->
 
427
      {error, "Could not add path: "++Dir}
 
428
  end.
 
429
 
 
430
compile_core(Mod, Core, NoWarn, Callgraph, CServer, CoreTransform, Plt) ->
 
431
  Exp = core_get_exports(Core),
 
432
  CServer1 = dialyzer_codeserver:insert_exports(Exp, CServer),
 
433
  {LabeledCore, CServer2} = label_core(Core, CServer1),
 
434
  case CoreTransform of
 
435
    succ_typings ->
 
436
      store_code_and_build_callgraph(Mod, LabeledCore, none, Callgraph, 
 
437
                                     CServer2, CoreTransform, NoWarn);
 
438
    cerl_typean  -> 
 
439
      AnnCore = dialyzer_dataflow:annotate_module(LabeledCore, Plt),
 
440
      TransCore = cerl:to_records(AnnCore),
 
441
      case (catch hipe:compile_core(Mod, TransCore, [], 
 
442
                                    ?HIPE_COMPILE_OPTS)) of
 
443
        {'EXIT', Why} -> {error, io_lib:format("~p", [Why])};
 
444
        {error, Why} -> {error, io_lib:format("~p", [Why])};
 
445
        {ok, Icode} ->
 
446
          store_code_and_build_callgraph(Mod, TransCore, Icode, Callgraph, 
 
447
                                         CServer2, CoreTransform, NoWarn)
 
448
      end
 
449
  end.
 
450
 
 
451
beam_get_core(File, Mod) ->
 
452
  case beam_get_abstract_code(File) of
 
453
    error -> error;
 
454
    {ok, Abs} -> abs_get_core(Abs, Mod)
 
455
  end.
 
456
 
 
457
beam_get_abstract_code(File) ->
 
458
  case beam_lib:chunks(File, [abstract_code]) of
 
459
    {ok,{_,List}} ->
 
460
      case lists:keysearch(abstract_code, 1, List) of
 
461
        {value, {abstract_code,{raw_abstract_v1,Abstr}}} -> {ok, Abstr};
 
462
        _ -> error
 
463
      end;
 
464
    _ ->
 
465
      %% No or unsuitable abstract code.
 
466
      error
 
467
  end.
 
468
 
 
469
abs_get_core(AbstrCode, Mod) ->
 
470
  try compile:forms(AbstrCode, ?SRC_COMPILE_OPTS) of
 
471
      {ok,_,Core} -> {Core, abs_get_nowarn(AbstrCode, Mod)};
 
472
      _ -> error
 
473
  catch
 
474
    error:_ -> error
 
475
  end.
 
476
  
 
477
abs_get_nowarn(Abs, M) ->
 
478
  [{M, F, A} 
 
479
   || {attribute, _, compile, {nowarn_unused_function, {F, A}}} <- Abs].
 
480
 
 
481
beam_get_exports(File) ->
 
482
  case beam_lib:chunks(File, [exports]) of
 
483
    {ok,{_,[{exports, List}]}} ->
 
484
      M = list_to_atom(filename:basename(File, ".beam")),
 
485
      [{M, F, A} || {F, A} <- List];
 
486
    error ->
 
487
      []
 
488
  end.
 
489
 
 
490
beam_get_nowarn(File) ->
 
491
  case beam_lib:chunks(File, [compile_info]) of
 
492
    {ok,{_,[{compile_info, List}]}} ->
 
493
      M = list_to_atom(filename:basename(File, ".beam")),
 
494
      [{M, F, A} || {nowarn_unused_function, {F, A}} <- List];
 
495
    error ->
 
496
      []
 
497
  end.
 
498
 
 
499
core_get_exports(Core) ->
 
500
  Tree = cerl:from_records(Core),
 
501
  Exports1 = cerl:module_exports(Tree),  
 
502
  Exports2 = [cerl:var_name(V) || V <- Exports1],
 
503
  M = cerl:atom_val(cerl:module_name(Tree)),
 
504
  [{M, F, A} || {F, A} <- Exports2].
 
505
 
 
506
label_core(Core, CServer) ->
 
507
  NextLabel = dialyzer_codeserver:next_core_label(CServer),
 
508
  CoreTree = cerl:from_records(Core),
 
509
  {LabeledTree, NewNextLabel} = cerl_trees:label(CoreTree, NextLabel),
 
510
  {cerl:to_records(LabeledTree), 
 
511
   dialyzer_codeserver:update_next_core_label(NewNextLabel, CServer)}.
 
512
 
 
513
 
 
514
store_code_and_build_callgraph(Mod, Core, Icode, Callgraph, CServer, 
 
515
                               CoreTransform, NoWarn) ->
 
516
  case CoreTransform of
 
517
    succ_typings ->
 
518
      CoreTree = cerl:from_records(Core),
 
519
      NewCallgraph = dialyzer_callgraph:scan_core_tree(CoreTree, Callgraph),
 
520
      CServer2 = dialyzer_codeserver:insert([{Mod, CoreTree}], core, CServer),
 
521
      {ok, NewCallgraph, NoWarn, CServer2};
 
522
    cerl_typean ->
 
523
      %% When building the callgraph from core that is not lambda
 
524
      %% lifted, we lose the lifted functions. We solve this for now
 
525
      %% by scanning the icode instead of the core code. I can't wait
 
526
      %% to get rid of the icode.
 
527
      CServer1 = dialyzer_codeserver:insert(Icode, icode, CServer),
 
528
      NewCallgraph = dialyzer_callgraph:scan_icode(Icode, Callgraph),
 
529
      {ok, NewCallgraph, NoWarn, CServer1}
 
530
  end.
 
531
 
 
532
 
 
533
 
 
534
%%____________________________________________________________
 
535
%%
 
536
%% Utilities
 
537
%%
 
538
 
 
539
expand_files(Analysis) ->
 
540
  Files = Analysis#analysis.files,
 
541
  Ext = 
 
542
    case Analysis#analysis.start_from of
 
543
      byte_code -> ".beam";
 
544
      src_code -> ".erl"
 
545
    end,
 
546
  case expand_files(Files, Ext, []) of
 
547
    [] ->
 
548
      exit({error, "No files to analyze. Check analysis type."});
 
549
    NewFiles ->
 
550
      Analysis#analysis{files=NewFiles}
 
551
  end.
 
552
 
 
553
expand_files([File|Left], Ext, Acc) ->
 
554
  case filelib:is_dir(File) of
 
555
    true ->
 
556
      {ok, List} = file:list_dir(File),
 
557
      NewFiles = [filename:join(File, X)
 
558
                  || X <- List, filename:extension(X)==Ext],
 
559
      expand_files(Left, Ext, NewFiles++Acc);
 
560
    false ->
 
561
      expand_files(Left, Ext, [File|Acc])
 
562
  end;
 
563
expand_files([], _Ext, Acc) ->
 
564
  ordsets:from_list(Acc).
 
565
 
 
566
format_errors([{Mod, Errors}|Left])->
 
567
  FormatedError = 
 
568
    [io_lib:format("~s:~w: ~s\n", [Mod, Line,apply(M,format_error, [Desc])])
 
569
     || {Line, M, Desc} <- Errors],
 
570
  [lists:flatten(FormatedError) | format_errors(Left)];
 
571
format_errors([]) ->
 
572
  [].
 
573
 
 
574
default_includes(Dir) ->
 
575
  L1 = ["..", "../incl", "../inc", "../include"],
 
576
  [{i, filename:join(Dir, X)}||X<-L1].
 
577
  
 
578
%%____________________________________________________________
 
579
%%
 
580
%% Handle Messages
 
581
%%
 
582
 
 
583
send_log(Parent, Msg) ->
 
584
  Parent ! {self(), log, Msg}.
 
585
 
 
586
send_warnings(_Parent, []) ->
 
587
  ok;
 
588
send_warnings(Parent, Warnings) ->
 
589
  Parent ! {self(), warnings, Warnings}.
 
590
 
 
591
filter_warnings(LegalWarnings, Warnings) ->
 
592
  [String || {Tag, String} <- Warnings, lists:member(Tag, LegalWarnings)].
 
593
 
 
594
send_analysis_done(Parent) ->
 
595
  Parent ! {self(), done}.
 
596
 
 
597
send_error(Parent, Msg) ->
 
598
  Parent ! {self(), error, Msg}.
 
599
 
 
600
send_scan_fail(_Parent, []) ->
 
601
  ok;
 
602
send_scan_fail(Parent, [{FailFile, Reason}|Left]) ->
 
603
  Msg = io_lib:format("Error scanning file: ~p\n~s\n", 
 
604
                      [FailFile, Reason]),
 
605
  send_error(Parent, Msg),
 
606
  send_scan_fail(Parent, Left).
 
607
  
 
608
send_ext_calls(Parent, ExtCalls) ->
 
609
  Parent ! {self(), ext_calls, ExtCalls}.
 
610
 
 
611
send_bad_calls(Parent, BadCalls) ->
 
612
  Warnings = 
 
613
    [{?WARN_CALLGRAPH, 
 
614
      io_lib:format("~w calls missing or unexported function ~w\n", [From, To])} 
 
615
     || {From, To} <- BadCalls],
 
616
  send_warnings(Parent, Warnings).
 
617
 
 
618
%%____________________________________________________________
 
619
%%
 
620
%% Handle the PLT
 
621
%%
 
622
 
 
623
init_plt(#analysis{init_plt=InitPlt, user_plt=Plt, plt_info=Info}) ->
 
624
  dialyzer_plt:copy(InitPlt, Plt),
 
625
  case Info of
 
626
    none -> ok;
 
627
    {MD5, Libs} -> 
 
628
      dialyzer_plt:insert(Plt, {md5, MD5}),
 
629
      dialyzer_plt:insert(Plt, {libs, Libs}),
 
630
      ok
 
631
  end.