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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_cl.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_cl.erl
 
21
%%% Authors : Tobias Lindahl <tobiasl@csd.uu.se>
 
22
%%%           Kostis Sagonas <kostis@it.uu.se>
 
23
%%% Description : The command line interface for the Dialyzer tool.
 
24
%%%
 
25
%%% Created : 27 Apr 2004 by Tobias Lindahl <tobiasl@csd.uu.se>
 
26
%%%-------------------------------------------------------------------
 
27
-module(dialyzer_cl).
 
28
 
 
29
-export([start/1, check_init_plt/1]).
 
30
 
 
31
-include("dialyzer.hrl").         %% file is automatically generated
 
32
-include("hipe_icode_type.hrl").
 
33
 
 
34
-record(cl_state, {backend_pid,
 
35
                   legal_warnings=[],
 
36
                   init_plt,
 
37
                   output=standard_io,
 
38
                   output_plt,
 
39
                   user_plt,
 
40
                   nof_warnings=0::integer(),
 
41
                   return_status=0::integer()
 
42
                  }).
 
43
 
 
44
start(Options) when is_list(Options) ->
 
45
  start(dialyzer_options:build(Options));
 
46
start(#options{} = DialyzerOptions) ->
 
47
  process_flag(trap_exit, true),
 
48
  State = new_state(DialyzerOptions#options.init_plt),
 
49
  NewState1 = init_output(State, DialyzerOptions),
 
50
  NewState2 = 
 
51
    NewState1#cl_state{legal_warnings=DialyzerOptions#options.legal_warnings,
 
52
                       output_plt=DialyzerOptions#options.output_plt},
 
53
  InitAnalysis = build_analysis_record(NewState2, DialyzerOptions),
 
54
  NewState3 = run_analysis(NewState2, InitAnalysis),
 
55
  cl_loop(NewState3).
 
56
 
 
57
check_init_plt(Opts) ->
 
58
  process_flag(trap_exit, true),
 
59
  Quiet = get(dialyzer_options_quiet),
 
60
  case dialyzer_plt:check_init_plt(Opts#options.plt_libs,
 
61
                                   Opts#options.init_plt) of
 
62
    {fail, MD5, Libs, InitPlt} ->      
 
63
      if Quiet -> ok;
 
64
         true  -> io:format(" no\n", [])
 
65
      end,
 
66
      case check_if_installed() of
 
67
        true -> 
 
68
          Msg = "    The initial PLT is not up-to-date.\n"
 
69
            "    Since Dialyzer is installed no new PLT will be built.\n"
 
70
            "    Please refer to the manual.\n",
 
71
          io:format("~s", [Msg]),
 
72
          error;
 
73
        false ->
 
74
          Msg = "    Creating initial PLT"
 
75
            " (will take several minutes; please be patient)\n",
 
76
          io:format("~s", [Msg]),
 
77
          case create_init_plt(MD5, Libs, InitPlt, Opts#options.include_dirs) of
 
78
            ?RET_INTERNAL_ERROR -> error;
 
79
            ?RET_NOTHING_SUSPICIOUS -> ok;
 
80
            ?RET_DISCREPANCIES_FOUND -> ok
 
81
          end
 
82
      end;
 
83
    {ok, _InitPlt} ->
 
84
      if Quiet -> ok;
 
85
         true  -> io:format(" yes\n")
 
86
      end,
 
87
      ok;
 
88
    {error, Msg} ->
 
89
      io:format(" no\n~s\n", [Msg]),
 
90
      error
 
91
  end.
 
92
 
 
93
check_if_installed() ->
 
94
  case filename:basename(code:lib_dir(dialyzer)) of
 
95
    "dialyzer" -> false;
 
96
    "dialyzer-" ++ _Version -> true
 
97
  end.  
 
98
 
 
99
create_init_plt(MD5, Libs, InitPlt, IncludeDirs) ->  
 
100
  State = new_state_no_init(),
 
101
  State1 = State#cl_state{output_plt=InitPlt},
 
102
  Files = [filename:join(code:lib_dir(Lib), "ebin")|| Lib <- Libs],
 
103
  Analysis = #analysis{fixpoint=first,
 
104
                       files=Files, 
 
105
                       granularity=all, 
 
106
                       init_plt=dialyzer_plt:new(dialyzer_empty_plt),
 
107
                       include_dirs=IncludeDirs,
 
108
                       plt_info={MD5, Libs},
 
109
                       start_from=byte_code,
 
110
                       core_transform=succ_typings,
 
111
                       user_plt=State1#cl_state.user_plt,
 
112
                       supress_inline=true},
 
113
  cl_loop(run_analysis(State1, Analysis)).
 
114
 
 
115
new_state(InitPlt) ->
 
116
  NewInitPlt = dialyzer_plt:from_file(dialyzer_init_plt, InitPlt),
 
117
  new_state1(NewInitPlt).
 
118
 
 
119
new_state_no_init() ->
 
120
  new_state1(none).
 
121
 
 
122
new_state1(InitPlt) ->
 
123
  UserPLT = dialyzer_plt:new(dialyzer_user_plt),
 
124
  #cl_state{user_plt=UserPLT, init_plt=InitPlt}.
 
125
 
 
126
init_output(State, DialyzerOptions) ->
 
127
  case DialyzerOptions#options.output_file of
 
128
    "" ->
 
129
      State;
 
130
    OutputFile ->
 
131
      case file:open(OutputFile, [write]) of
 
132
        {ok, File} ->
 
133
          State#cl_state{output=File};
 
134
        {error, Reason} ->
 
135
          io:format("Could not open output file ~p, Reason ~p\n",
 
136
                    [OutputFile, Reason]),
 
137
          exit(error)
 
138
      end
 
139
  end.
 
140
 
 
141
maybe_close_output_file(State) ->
 
142
  case State#cl_state.output of
 
143
    standard_io -> ok;
 
144
    File -> file:close(File)
 
145
  end.
 
146
 
 
147
%% ----------------------------------------------------------------
 
148
%%
 
149
%%  Main Loop
 
150
%%
 
151
 
 
152
cl_loop(State) ->
 
153
  BackendPid = State#cl_state.backend_pid,
 
154
  Output = State#cl_state.output,
 
155
  receive
 
156
    {BackendPid, log, _LogMsg} ->
 
157
      %io:format(Output,"Log: ~s", [_LogMsg]),
 
158
      cl_loop(State);
 
159
    {BackendPid, warnings, Warnings} ->
 
160
      NewState = print_warnings(State, Warnings),
 
161
      cl_loop(NewState);
 
162
    {BackendPid, error, Msg} ->
 
163
      io:format(Output, "~s", [Msg]),
 
164
      cl_loop(State#cl_state{return_status=-1});
 
165
    {BackendPid, done} ->
 
166
      return_value(State);
 
167
    {BackendPid, ext_calls, ExtCalls} ->
 
168
      Quiet = get(dialyzer_options_quiet),
 
169
      if Quiet -> ok;
 
170
         true  -> io:format("\nUnknown functions: ~p\n", [ExtCalls])
 
171
      end,
 
172
      cl_loop(State);
 
173
    {'EXIT', BackendPid, {error, Reason}} ->
 
174
      Msg = failed_anal_msg(Reason),
 
175
      error(State, Msg);
 
176
    {'EXIT', BackendPid, Reason} when Reason =/= 'normal' ->
 
177
      Msg = failed_anal_msg(Reason),
 
178
      maybe_close_output_file(State),
 
179
      error(State, Msg);
 
180
    _Other ->
 
181
      %% io:format(Output, "Received ~p\n", [Other]),
 
182
      cl_loop(State)
 
183
  end.
 
184
 
 
185
failed_anal_msg(Reason) ->
 
186
  io_lib:format("Analysis failed with error report: ~p\n", [Reason]).
 
187
 
 
188
print_warnings(State = #cl_state{output=Output}, Warnings) ->
 
189
  NofOldWarnings = State#cl_state.nof_warnings,
 
190
  case NofOldWarnings of
 
191
    0 ->
 
192
      io:format(Output, "\n", []); %% warnings are just starting to appaer
 
193
    _ ->
 
194
      ok
 
195
  end,
 
196
  io:format(Output, "~s", [Warnings]),
 
197
  NofNewWarning = length(string:tokens(lists:flatten(Warnings), "\n")),
 
198
  State#cl_state{nof_warnings=NofOldWarnings+NofNewWarning}.
 
199
 
 
200
error(State, Msg) ->
 
201
  io:format(State#cl_state.output, "~s", [Msg]),
 
202
  return_value(State#cl_state{return_status=-1}).
 
203
 
 
204
return_value(State = #cl_state{return_status=-1}) ->
 
205
  maybe_close_output_file(State),
 
206
  ?RET_INTERNAL_ERROR;
 
207
return_value(State = #cl_state{nof_warnings=NofWarnings, output_plt=OutputPlt,
 
208
                               user_plt=UserPlt, init_plt=InitPlt}) ->
 
209
  if OutputPlt =/= undefined ->
 
210
      case dialyzer_plt:merge_and_write_file([InitPlt, UserPlt], OutputPlt) of
 
211
        ok -> ok;
 
212
        {error, What} -> 
 
213
          error(State, io_lib:format("Error while writing plt to file: ~w\n", 
 
214
                                     [What]))
 
215
      end;
 
216
     true ->
 
217
      ok
 
218
  end,
 
219
  maybe_close_output_file(State),
 
220
  if NofWarnings =:= 0 ->
 
221
      ?RET_NOTHING_SUSPICIOUS;
 
222
     true ->
 
223
      ?RET_DISCREPANCIES_FOUND
 
224
  end.
 
225
 
 
226
 
 
227
%% ----------------------------------------------------------------
 
228
%%
 
229
%%  Run the analysis
 
230
%%
 
231
 
 
232
build_analysis_record(State, DialyzerOptions) ->
 
233
  PLT = State#cl_state.user_plt,
 
234
  From = DialyzerOptions#options.from,
 
235
  IncludeDirs = DialyzerOptions#options.include_dirs,
 
236
  Defines = DialyzerOptions#options.defines,
 
237
  SupressInline = DialyzerOptions#options.supress_inline,
 
238
  Files0 = ordsets:from_list(DialyzerOptions#options.files),
 
239
  Files1 = ordsets:from_list(lists:concat([filelib:wildcard(F) || F <- Files0])),
 
240
  Files2 = add_files_rec(DialyzerOptions#options.files_rec, From),  
 
241
  Files = ordsets:union(Files1, Files2),
 
242
  CoreTransform = DialyzerOptions#options.core_transform,
 
243
  InitPlt = State#cl_state.init_plt,
 
244
  #analysis{fixpoint=first, core_transform=CoreTransform,
 
245
            defines=Defines, granularity=all,
 
246
            include_dirs=IncludeDirs, init_plt=InitPlt, user_plt=PLT, 
 
247
            files=Files, start_from=From, supress_inline=SupressInline}.
 
248
 
 
249
 
 
250
add_files_rec(Files, From) ->
 
251
  Files1 = ordsets:from_list(Files), 
 
252
  Dirs1 = ordsets:filter(fun(X) -> filelib:is_dir(X) end, Files1),  
 
253
  Dirs2 = ordsets:union(Dirs1, all_subdirs(Dirs1)),  
 
254
  FinalFiles = ordsets:union(Files1, Dirs2),
 
255
  case From of
 
256
    byte_code -> filter_files(FinalFiles, ".beam");
 
257
    src_code -> filter_files(FinalFiles, ".erl")
 
258
  end.
 
259
 
 
260
all_subdirs(Dirs) ->
 
261
  all_subdirs(Dirs, []).
 
262
 
 
263
all_subdirs([Dir|T], Acc) ->
 
264
  {ok, Files} = file:list_dir(Dir),
 
265
  SubDirs = lists:zf(fun(F) ->
 
266
                       SubDir = filename:join(Dir, F),
 
267
                       case filelib:is_dir(SubDir) of
 
268
                         true -> {true, SubDir};
 
269
                         false -> false
 
270
                       end
 
271
                   end, Files),
 
272
  NewAcc = ordsets:union(ordsets:from_list(SubDirs), Acc),
 
273
  all_subdirs(T++SubDirs, NewAcc);
 
274
all_subdirs([], Acc) ->
 
275
  Acc.
 
276
 
 
277
filter_files(Files, Extension) ->
 
278
  Fun = fun(X) -> 
 
279
            filename:extension(X) =:= Extension
 
280
              orelse 
 
281
                (filelib:is_dir(X) andalso contains_files(X, Extension))
 
282
        end,
 
283
  lists:filter(Fun, Files).
 
284
 
 
285
contains_files(Dir, Extension) ->
 
286
  {ok, Files} = file:list_dir(Dir),
 
287
  lists:any(fun(X) -> filename:extension(X) =:= Extension end, Files).
 
288
 
 
289
 
 
290
run_analysis(State, Analysis) ->
 
291
  Self = self(),
 
292
  LegalWarnings = State#cl_state.legal_warnings,
 
293
  Fun = fun() -> 
 
294
            dialyzer_analysis_callgraph:start(Self, LegalWarnings, Analysis)
 
295
        end,
 
296
  BackendPid = spawn_link(Fun),
 
297
  State#cl_state{backend_pid=BackendPid}.