~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/typer/src/typer_annotator.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% -*- erlang-indent-level: 2 -*-
2
 
%%
3
 
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
6
 
%% 
7
 
%% The contents of this file are subject to the Erlang Public License,
8
 
%% Version 1.1, (the "License"); you may not use this file except in
9
 
%% compliance with the License. You should have received a copy of the
10
 
%% Erlang Public License along with this software. If not, it can be
11
 
%% retrieved online at http://www.erlang.org/.
12
 
%% 
13
 
%% Software distributed under the License is distributed on an "AS IS"
14
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
 
%% the License for the specific language governing rights and limitations
16
 
%% under the License.
17
 
%% 
18
 
%% %CopyrightEnd%
19
 
%%
20
 
%%============================================================================
21
 
%% File    : typer_annotator.erl
22
 
%% Author  : Bingwen He <hebingwen@hotmail.com>
23
 
%% Description : 
24
 
%%    If file 'FILENAME' has been analyzed, then the output of
25
 
%%    command "diff -B FILENAME.erl typer_ann/FILENAME.ann.erl"
26
 
%%    should be exactly what TypEr has added, namely type info.
27
 
%%============================================================================
28
 
 
29
 
-module(typer_annotator).
30
 
 
31
 
-export([annotate/1]).
32
 
 
33
 
%%----------------------------------------------------------------------------
34
 
 
35
 
-include("typer.hrl").
36
 
 
37
 
%%----------------------------------------------------------------------------
38
 
 
39
 
-define(TYPER_ANN_DIR, "typer_ann").
40
 
 
41
 
-type func_info() :: {non_neg_integer(), atom(), arity()}.
42
 
 
43
 
-record(info, {recMap = typer_map:new() :: dict(),
44
 
               funcs = []               :: [func_info()],
45
 
               typeMap                  :: dict(),
46
 
               contracts                :: boolean()}).
47
 
-record(inc, {map    = typer_map:new() :: dict(),
48
 
              filter = []              :: [string()]}).
49
 
 
50
 
%%----------------------------------------------------------------------------
51
 
 
52
 
-spec annotate(#typer_analysis{}) -> 'ok'.
53
 
 
54
 
annotate(Analysis) ->
55
 
  case Analysis#typer_analysis.mode of
56
 
    ?SHOW -> show(Analysis);
57
 
    ?SHOW_EXPORTED -> show(Analysis);
58
 
    ?ANNOTATE ->
59
 
      Fun = fun({File, Module}) ->
60
 
                Info = get_final_info(File, Module, Analysis),
61
 
                write_typed_file(File, Info)
62
 
            end,
63
 
      lists:foreach(Fun, Analysis#typer_analysis.final_files);
64
 
    ?ANNOTATE_INC_FILES ->
65
 
      IncInfo = write_and_collect_inc_info(Analysis),
66
 
      write_inc_files(IncInfo)
67
 
  end.
68
 
 
69
 
write_and_collect_inc_info(Analysis) ->
70
 
  Fun = fun({File, Module}, Inc) ->
71
 
            Info = get_final_info(File, Module, Analysis),
72
 
            write_typed_file(File, Info),
73
 
            IncFuns = get_functions(File, Analysis),
74
 
            collect_imported_funcs(IncFuns, Info#info.typeMap, Inc)
75
 
        end,
76
 
  NewInc = lists:foldl(Fun,#inc{}, Analysis#typer_analysis.final_files),
77
 
  clean_inc(NewInc).
78
 
 
79
 
write_inc_files(Inc) ->
80
 
  Fun =
81
 
    fun (File) ->
82
 
        Val = typer_map:lookup(File,Inc#inc.map),
83
 
        %% Val is function with its type info
84
 
        %% in form [{{Line,F,A},Type}]
85
 
        Functions = [Key || {Key,_} <- Val],
86
 
        Val1 = [{{F,A},Type} || {{_Line,F,A},Type} <- Val],
87
 
        Info = #info{typeMap = typer_map:from_list(Val1),
88
 
                     recMap = typer_map:new(),
89
 
                     %% Note we need to sort functions here!
90
 
                     funcs = lists:keysort(1, Functions)},
91
 
        %% io:format("TypeMap ~p\n", [Info#info.typeMap]),
92
 
        %% io:format("Funcs ~p\n", [Info#info.funcs]),
93
 
        %% io:format("RecMap ~p\n", [Info#info.recMap]),
94
 
        write_typed_file(File, Info)
95
 
    end,
96
 
  lists:foreach(Fun, dict:fetch_keys(Inc#inc.map)).
97
 
 
98
 
show(Analysis) ->
99
 
  Fun = fun({File, Module}) -> 
100
 
            Info = get_final_info(File, Module, Analysis),
101
 
            show_type_info_only(File, Info)
102
 
        end,
103
 
  lists:foreach(Fun, Analysis#typer_analysis.final_files).
104
 
 
105
 
get_final_info(File, Module, Analysis) ->
106
 
  RecMap = get_recMap(File, Analysis),
107
 
  TypeMap = get_typeMap(Module, Analysis,RecMap),
108
 
  Functions = get_functions(File, Analysis),
109
 
  Contracts = Analysis#typer_analysis.contracts,
110
 
  #info{recMap=RecMap, funcs=Functions, typeMap=TypeMap, contracts=Contracts}.
111
 
 
112
 
collect_imported_funcs(Funcs, TypeMap, TmpInc) ->
113
 
  %% Coming from other sourses, including:
114
 
  %% FIXME: How to deal with yecc-generated file????
115
 
  %%     --.yrl (yecc-generated file)???
116
 
  %%     -- yeccpre.hrl (yecc-generated file)???
117
 
  %%     -- other cases
118
 
  Fun = fun({File,_} = Obj, Inc) ->
119
 
            case is_yecc_file(File, Inc) of
120
 
              {yecc_generated, NewInc} -> NewInc;
121
 
              {not_yecc, NewInc} ->
122
 
                check_imported_funcs(Obj, NewInc, TypeMap)
123
 
            end
124
 
        end,
125
 
  lists:foldl(Fun, TmpInc, Funcs).
126
 
 
127
 
-spec is_yecc_file(string(), #inc{}) -> {'not_yecc', #inc{}}
128
 
                                      | {'yecc_generated', #inc{}}.
129
 
is_yecc_file(File, Inc) ->
130
 
  case lists:member(File, Inc#inc.filter) of
131
 
    true -> {yecc_generated, Inc};
132
 
    false ->
133
 
      case filename:extension(File) of
134
 
        ".yrl" ->
135
 
          Rootname = filename:rootname(File, ".yrl"),
136
 
          Obj = Rootname ++ ".erl",
137
 
          case lists:member(Obj, Inc#inc.filter) of
138
 
            true -> {yecc_generated, Inc};
139
 
            false ->
140
 
              NewFilter = [Obj|Inc#inc.filter],
141
 
              NewInc = Inc#inc{filter = NewFilter},
142
 
              {yecc_generated, NewInc}
143
 
          end;
144
 
        _ ->
145
 
          case filename:basename(File) of
146
 
            "yeccpre.hrl" -> {yecc_generated, Inc};
147
 
            _ -> {not_yecc, Inc}
148
 
          end
149
 
      end
150
 
  end.
151
 
 
152
 
check_imported_funcs({File, {Line, F, A}}, Inc, TypeMap) ->
153
 
  IncMap = Inc#inc.map,
154
 
  FA = {F, A},
155
 
  Type = get_type_info(FA, TypeMap),
156
 
  case typer_map:lookup(File, IncMap) of
157
 
    none -> %% File is not added. Add it
158
 
      Obj = {File,[{FA, {Line, Type}}]},
159
 
      NewMap = typer_map:insert(Obj, IncMap),
160
 
      Inc#inc{map = NewMap};
161
 
    Val -> %% File is already in. Check.
162
 
      case lists:keyfind(FA, 1, Val) of
163
 
        false ->
164
 
          %% Function is not in; add it
165
 
          Obj = {File, Val ++ [{FA, {Line, Type}}]},
166
 
          NewMap = typer_map:insert(Obj, IncMap),
167
 
          Inc#inc{map = NewMap};
168
 
        Type ->
169
 
          %% Function is in and with same type
170
 
          Inc;
171
 
        _ ->
172
 
          %% Function is in but with diff type
173
 
          inc_warning(FA, File),
174
 
          Elem = lists:keydelete(FA, 1, Val),
175
 
          NewMap = case Elem of
176
 
                     [] ->
177
 
                       typer_map:remove(File, IncMap);
178
 
                     _  ->
179
 
                       typer_map:insert({File, Elem}, IncMap)
180
 
                   end,
181
 
          Inc#inc{map = NewMap}
182
 
      end
183
 
  end.
184
 
 
185
 
inc_warning({F, A}, File) ->
186
 
  io:format("      ***Warning: Skip function ~p/~p ", [F, A]),
187
 
  io:format("in file ~p because of inconsistent type\n", [File]).
188
 
 
189
 
clean_inc(Inc) ->
190
 
  Inc1 = remove_yecc_generated_file(Inc),
191
 
  normalize_obj(Inc1).
192
 
 
193
 
remove_yecc_generated_file(TmpInc) ->
194
 
  Fun = fun(Key, Inc) ->
195
 
            NewMap = typer_map:remove(Key, Inc#inc.map),
196
 
            Inc#inc{map = NewMap}
197
 
        end,
198
 
  lists:foldl(Fun, TmpInc, TmpInc#inc.filter).
199
 
  
200
 
normalize_obj(TmpInc) ->
201
 
  Fun = fun(Key, Val, Inc) ->
202
 
            NewVal = [{{Line,F,A},Type} || {{F,A},{Line,Type}} <- Val],
203
 
            typer_map:insert({Key,NewVal}, Inc)
204
 
        end,
205
 
  NewMap = typer_map:fold(Fun, typer_map:new(), TmpInc#inc.map),
206
 
  TmpInc#inc{map = NewMap}.
207
 
 
208
 
get_recMap(File, Analysis) ->
209
 
  typer_map:lookup(File, Analysis#typer_analysis.record).
210
 
 
211
 
get_typeMap(Module, Analysis, RecMap) ->
212
 
  TypeInfoPlt = Analysis#typer_analysis.trust_plt,
213
 
  TypeInfo = 
214
 
    case dialyzer_plt:lookup_module(TypeInfoPlt, Module) of
215
 
      none -> [];
216
 
      {value, List} -> List
217
 
    end,
218
 
  CodeServer = Analysis#typer_analysis.code_server,
219
 
  TypeInfoList = [get_type(I, CodeServer, RecMap) || I <- TypeInfo],
220
 
  typer_map:from_list(TypeInfoList).
221
 
 
222
 
get_type({{M, F, A} = MFA, Range, Arg}, CodeServer, RecMap) ->
223
 
  case dialyzer_codeserver:lookup_mfa_contract(MFA, CodeServer) of
224
 
    error ->
225
 
      {{F, A}, {Range, Arg}};
226
 
    {ok, {_FileLine, Contract}} ->
227
 
      Sig = erl_types:t_fun(Arg, Range),
228
 
      case dialyzer_contracts:check_contract(Contract, Sig) of
229
 
        ok -> {{F, A}, {contract, Contract}};
230
 
        {error, invalid_contract} ->
231
 
          CString = dialyzer_contracts:contract_to_string(Contract),
232
 
          SigString = dialyzer_utils:format_sig(Sig, RecMap),
233
 
          typer:error(
234
 
            io_lib:format("Error in contract of function ~w:~w/~w\n" 
235
 
                          "\t The contract is: " ++ CString ++ "\n" ++
236
 
                          "\t but the inferred signature is: ~s",
237
 
                          [M, F, A, SigString]));
238
 
        {error, Msg} ->
239
 
          typer:error(
240
 
            io_lib:format("Error in contract of function ~w:~w/~w: ~s",
241
 
                          [M, F, A, Msg]))
242
 
      end
243
 
  end.
244
 
 
245
 
get_functions(File, Analysis) ->
246
 
  case Analysis#typer_analysis.mode of
247
 
    ?SHOW ->
248
 
      Funcs = typer_map:lookup(File, Analysis#typer_analysis.func),
249
 
      Inc_Funcs = typer_map:lookup(File, Analysis#typer_analysis.inc_func),
250
 
      remove_module_info(Funcs) ++ normalize_incFuncs(Inc_Funcs);
251
 
    ?SHOW_EXPORTED ->
252
 
      Ex_Funcs = typer_map:lookup(File, Analysis#typer_analysis.ex_func),
253
 
      remove_module_info(Ex_Funcs);
254
 
    ?ANNOTATE ->
255
 
      Funcs = typer_map:lookup(File, Analysis#typer_analysis.func),
256
 
      remove_module_info(Funcs);
257
 
    ?ANNOTATE_INC_FILES ->
258
 
      typer_map:lookup(File, Analysis#typer_analysis.inc_func)
259
 
  end.
260
 
 
261
 
normalize_incFuncs(Funcs) ->
262
 
  [FuncInfo || {_FileName, FuncInfo} <- Funcs].
263
 
 
264
 
-spec remove_module_info([func_info()]) -> [func_info()].
265
 
 
266
 
remove_module_info(FuncInfoList) ->
267
 
  F = fun ({_,module_info,0}) -> false;
268
 
          ({_,module_info,1}) -> false;
269
 
          ({Line,F,A}) when is_integer(Line), is_atom(F), is_integer(A) -> true
270
 
      end,
271
 
  lists:filter(F, FuncInfoList).
272
 
 
273
 
write_typed_file(File, Info) ->
274
 
  io:format("      Processing file: ~p\n", [File]),
275
 
  Dir = filename:dirname(File),
276
 
  RootName = filename:basename(filename:rootname(File)),
277
 
  Ext = filename:extension(File),
278
 
  TyperAnnDir = filename:join(Dir, ?TYPER_ANN_DIR),
279
 
  TmpNewFilename = lists:concat([RootName,".ann",Ext]),
280
 
  NewFileName = filename:join(TyperAnnDir, TmpNewFilename),
281
 
  case file:make_dir(TyperAnnDir) of
282
 
    {error, Reason} ->
283
 
      case Reason of
284
 
        eexist -> %% TypEr dir exists; remove old typer files
285
 
          ok = file:delete(NewFileName),
286
 
          write_typed_file(File, Info, NewFileName);
287
 
        enospc ->
288
 
          io:format("  Not enough space in ~p\n", [Dir]);
289
 
        eacces ->
290
 
          io:format("  No write permission in ~p\n", [Dir]);
291
 
        _ ->
292
 
          io:format("Unknown error when writing ~p\n", [Dir]),
293
 
          halt()
294
 
      end;
295
 
    ok -> %% Typer dir does NOT exist
296
 
      write_typed_file(File, Info, NewFileName)
297
 
  end.
298
 
 
299
 
write_typed_file(File, Info, NewFileName) ->
300
 
  {ok, Binary} = file:read_file(File),
301
 
  Chars = binary_to_list(Binary),
302
 
  write_typed_file(Chars, NewFileName, Info, 1, []),
303
 
  io:format("             Saved as: ~p\n", [NewFileName]).
304
 
 
305
 
write_typed_file(Chars, File, #info{funcs = []}, _LNo, _Acc) ->
306
 
  ok = file:write_file(File, list_to_binary(Chars), [append]);
307
 
write_typed_file([Ch|Chs] = Chars, File, Info, LineNo, Acc) ->
308
 
  [{Line,F,A}|RestFuncs] = Info#info.funcs,
309
 
  case Line of
310
 
    1 -> %% This will happen only for inc files
311
 
      ok = raw_write(F, A, Info, File, []),
312
 
      NewInfo = Info#info{funcs = RestFuncs},
313
 
      NewAcc = [],
314
 
      write_typed_file(Chars, File, NewInfo, Line, NewAcc);
315
 
    _ ->
316
 
      case Ch of
317
 
        10 ->
318
 
          NewLineNo = LineNo + 1,
319
 
          {NewInfo, NewAcc} =
320
 
            case NewLineNo of
321
 
              Line ->
322
 
                ok = raw_write(F, A, Info, File, [Ch|Acc]),
323
 
                {Info#info{funcs = RestFuncs}, []};
324
 
              _ ->
325
 
                {Info, [Ch|Acc]}
326
 
            end,
327
 
          write_typed_file(Chs, File, NewInfo, NewLineNo, NewAcc);
328
 
        _ ->
329
 
          write_typed_file(Chs, File, Info, LineNo, [Ch|Acc])
330
 
      end
331
 
  end.
332
 
 
333
 
raw_write(F, A, Info, File, Content) ->
334
 
  TypeInfo = get_type_string(F, A, Info, file),
335
 
  ContentList = lists:reverse(Content) ++ TypeInfo ++ "\n",
336
 
  ContentBin = list_to_binary(ContentList),
337
 
  file:write_file(File, ContentBin, [append]).
338
 
 
339
 
get_type_string(F, A, Info, Mode) ->
340
 
  Type = get_type_info({F,A}, Info#info.typeMap),
341
 
  TypeStr =
342
 
    case Type of
343
 
      {contract, C} -> 
344
 
        dialyzer_contracts:contract_to_string(C);
345
 
      {RetType, ArgType} ->
346
 
        dialyzer_utils:format_sig(erl_types:t_fun(ArgType, RetType),
347
 
                                  Info#info.recMap)
348
 
    end,
349
 
  case Info#info.contracts of
350
 
    true ->
351
 
      case {Mode, Type} of
352
 
        {file, {contract, _}} -> "";
353
 
        _ ->
354
 
          Prefix = lists:concat(["-spec ", F]),
355
 
          lists:concat([Prefix, TypeStr, "."])
356
 
      end;
357
 
    false ->
358
 
      Prefix = lists:concat(["%% @spec ", F]),
359
 
      lists:concat([Prefix, TypeStr, "."])
360
 
  end.
361
 
 
362
 
show_type_info_only(File, Info) ->
363
 
  io:format("\n%% File: ~p\n%% ", [File]),
364
 
  OutputString = lists:concat(["~.", length(File)+8, "c~n"]),
365
 
  io:fwrite(OutputString, [$-]),
366
 
  Fun = fun ({_LineNo, F, A}) ->
367
 
            TypeInfo = get_type_string(F, A, Info, show),
368
 
            io:format("~s\n", [TypeInfo])
369
 
        end,
370
 
  lists:foreach(Fun, Info#info.funcs).
371
 
 
372
 
get_type_info(Func, TypeMap) ->
373
 
  case typer_map:lookup(Func, TypeMap) of
374
 
    none ->
375
 
      %% Note: Typeinfo of any function should exist in
376
 
      %% the result offered by dialyzer, otherwise there 
377
 
      %% *must* be something wrong with the analysis
378
 
      io:format("No type info for function: ~p\n", [Func]),
379
 
      halt();
380
 
    {contract, _Fun} = C -> C;
381
 
    {_RetType, _ArgType} = RA -> RA 
382
 
  end.