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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
15
15
%%----------------------------------------------------------------------------
16
16
 
17
17
-include("typer.hrl").
18
 
-include("typer_options.hrl").
19
18
 
20
19
%%----------------------------------------------------------------------------
21
20
 
22
21
-define(TYPER_ANN_DIR, "typer_ann").
23
22
 
24
 
-type(func_info() :: {pos_integer(), atom(), byte()}).
 
23
-type func_info() :: {pos_integer(), atom(), byte()}.
25
24
 
26
25
-record(info, {recMap = typer_map:new() :: dict(),
27
26
               funcs = []               :: [func_info()],
32
31
 
33
32
%%----------------------------------------------------------------------------
34
33
 
35
 
-spec(annotate/1 :: (#typer_analysis{}) -> 'ok').
 
34
-spec annotate(#typer_analysis{}) -> 'ok'.
36
35
 
37
36
annotate(Analysis) ->
38
 
  case typer_options:option_type(Analysis#typer_analysis.mode) of
39
 
    for_show ->
40
 
      Fun = fun({File,Module}) -> 
41
 
              Info = get_final_info(File, Module, Analysis),
42
 
              show_type_info_only(File, Info)
43
 
            end,
44
 
      lists:foreach(Fun, Analysis#typer_analysis.final_files);
45
 
    for_annotation ->
46
 
      annotate_file(Analysis)
47
 
  end.
48
 
 
49
 
annotate_file(Analysis) ->
50
 
  Mode = Analysis#typer_analysis.mode,
51
 
  case Mode of
 
37
  case Analysis#typer_analysis.mode of
 
38
    ?SHOW -> show(Analysis);
 
39
    ?SHOW_EXPORTED -> show(Analysis);
52
40
    ?ANNOTATE ->
53
 
      Fun = fun({File,Module}) ->
 
41
      Fun = fun({File, Module}) ->
54
42
                Info = get_final_info(File, Module, Analysis),
55
43
                write_typed_file(File, Info)
56
44
            end,
89
77
    end,
90
78
  lists:foreach(Fun, dict:fetch_keys(Inc#inc.map)).
91
79
 
 
80
show(Analysis) ->
 
81
  Fun = fun({File, Module}) -> 
 
82
            Info = get_final_info(File, Module, Analysis),
 
83
            show_type_info_only(File, Info)
 
84
        end,
 
85
  lists:foreach(Fun, Analysis#typer_analysis.final_files).
 
86
 
92
87
get_final_info(File, Module, Analysis) ->
93
88
  RecMap = get_recMap(File, Analysis),
94
89
  TypeMap = get_typeMap(Module, Analysis,RecMap),
111
106
        end,
112
107
  lists:foldl(Fun, TmpInc, Funcs).
113
108
 
114
 
-spec(is_yecc_file/2 ::
115
 
      (string(), #inc{}) -> {'not_yecc', #inc{}} | {'yecc_generated', #inc{}}).
 
109
-spec is_yecc_file(string(), #inc{}) -> {'not_yecc', #inc{}}
 
110
                                      | {'yecc_generated', #inc{}}.
116
111
is_yecc_file(File, Inc) ->
117
112
  case lists:member(File, Inc#inc.filter) of
118
113
    true -> {yecc_generated, Inc};
136
131
      end
137
132
  end.
138
133
 
139
 
check_imported_funcs({File,{Line,F,A}},Inc,TypeMap) ->
 
134
check_imported_funcs({File,{Line,F,A}}, Inc, TypeMap) ->
140
135
  IncMap = Inc#inc.map,
141
 
  Type = get_type_info({F,A},TypeMap),
142
 
  case typer_map:lookup(File,IncMap) of
 
136
  Type = get_type_info({F,A}, TypeMap),
 
137
  case typer_map:lookup(File, IncMap) of
143
138
    none -> %% File is not added. Add it
144
139
      Obj = {File,[{{F,A},{Line,Type}}]},
145
 
      NewMap = typer_map:insert(Obj,IncMap),
 
140
      NewMap = typer_map:insert(Obj, IncMap),
146
141
      Inc#inc{map=NewMap};
147
142
    Val -> %% File is already in. Check.
148
 
      case lists:keysearch({F,A},1,Val) of
 
143
      case lists:keysearch({F,A}, 1, Val) of
149
144
        false -> 
150
145
          %% Function is not in. Good. Add.
151
146
          Obj = {File,Val++[{{F,A},{Line,Type}}]},
152
 
          NewMap = typer_map:insert(Obj,IncMap),
 
147
          NewMap = typer_map:insert(Obj, IncMap),
153
148
          Inc#inc{map=NewMap};
154
149
        {_,Type} -> 
155
150
          %% Function is in and with same type
156
151
          Inc;
157
152
        {_,_} ->
158
153
          %% Function is in but with diff type
159
 
          inc_warning({F,A},File),
160
 
          Elem = lists:keydelete({F,A},1,Val),
 
154
          inc_warning({F,A}, File),
 
155
          Elem = lists:keydelete({F,A}, 1, Val),
161
156
          NewMap = case Elem of
162
157
                     [] -> 
163
 
                       typer_map:remove(File,IncMap);
 
158
                       typer_map:remove(File, IncMap);
164
159
                     _  ->
165
160
                       Obj = {File,Elem},
166
 
                       typer_map:insert(Obj,IncMap)
 
161
                       typer_map:insert(Obj, IncMap)
167
162
                   end,
168
163
          Inc#inc{map=NewMap}
169
164
      end
170
165
  end.
171
166
 
172
 
inc_warning({F,A},File) ->          
 
167
inc_warning({F,A}, File) ->         
173
168
  io:format("      ***Warning: Skip function ~p/~p ",[F,A]),
174
169
  io:format("in file ~p because of inconsistent type\n",[File]).
175
170
 
178
173
  normalize_obj(Inc1).
179
174
 
180
175
remove_yecc_generated_file(TmpInc) ->
181
 
  Fun = fun(Key,Inc) ->
182
 
            NewMap = typer_map:remove(Key,Inc#inc.map),
 
176
  Fun = fun(Key, Inc) ->
 
177
            NewMap = typer_map:remove(Key, Inc#inc.map),
183
178
            Inc#inc{map=NewMap}
184
179
        end,
185
 
  lists:foldl(Fun,TmpInc,TmpInc#inc.filter).
 
180
  lists:foldl(Fun, TmpInc, TmpInc#inc.filter).
186
181
  
187
182
normalize_obj(TmpInc) ->
188
 
  Fun = fun(Key,Val,Inc) ->
 
183
  Fun = fun(Key, Val, Inc) ->
189
184
            NewVal = [{{Line,F,A},Type} || {{F,A},{Line,Type}} <- Val],
190
185
            typer_map:insert({Key,NewVal},Inc)
191
186
        end,
192
187
  NewMap = typer_map:fold(Fun, typer_map:new(), TmpInc#inc.map),
193
188
  TmpInc#inc{map=NewMap}.
194
 
  
 
189
 
195
190
get_recMap(File, Analysis) ->
196
191
  typer_map:lookup(File, Analysis#typer_analysis.record).
197
192
 
202
197
      none -> [];
203
198
      {value, List} -> List
204
199
    end,
205
 
  Codeserver = Analysis#typer_analysis.code_server,
206
 
  TypeInfoList =
207
 
    lists:map(
208
 
      fun({MFA = {M,F,A}, Range, Arg}) ->
209
 
          case dialyzer_codeserver:lookup_contract(MFA, Codeserver) of
210
 
            {ok, {_Line, C}} ->
211
 
              Sig = erl_types:t_fun(Arg, Range),
212
 
              case dialyzer_contracts:check_contract(C, Sig) of
213
 
                ok -> {{F, A}, {contract, C}};
214
 
                {error, What} ->
215
 
                  typer:error(
216
 
                    io_lib:format("Error in contract of function ~w:~w/~w: ~s",
217
 
                                  [M,F,A,What]));
218
 
                error ->
219
 
                  CString = dialyzer_contracts:contract_to_string(C),
220
 
                  SigString = dialyzer_utils:format_sig(Sig, RecMap),
221
 
                  typer:error(
222
 
                    io_lib:format("Error in contract of function ~w:~w/~w. " 
223
 
                                  "The contract is\n" ++ CString ++ 
224
 
                                  "\tbut the inferred signature is\n~s",
225
 
                                  [M,F,A,SigString]))
226
 
              end;
227
 
            error ->
228
 
              {{F,A},{Range,Arg}}
229
 
          end
230
 
      end, TypeInfo),
 
200
  CodeServer = Analysis#typer_analysis.code_server,
 
201
  TypeInfoList = [get_type(I, CodeServer, RecMap) || I <- TypeInfo],
231
202
  typer_map:from_list(TypeInfoList).
232
203
 
 
204
get_type({MFA = {M,F,A}, Range, Arg}, CodeServer, RecMap) ->
 
205
  case dialyzer_codeserver:lookup_contract(MFA, CodeServer) of
 
206
    {ok, {_Line, C}} ->
 
207
      Sig = erl_types:t_fun(Arg, Range),
 
208
      case dialyzer_contracts:check_contract(C, Sig) of
 
209
        ok -> {{F, A}, {contract, C}};
 
210
        {error, What} ->
 
211
          typer:error(
 
212
            io_lib:format("Error in contract of function ~w:~w/~w: ~s",
 
213
                          [M, F, A, What]));
 
214
        error ->
 
215
          CString = dialyzer_contracts:contract_to_string(C),
 
216
          SigString = dialyzer_utils:format_sig(Sig, RecMap),
 
217
          typer:error(
 
218
            io_lib:format("Error in contract of function ~w:~w/~w\n" 
 
219
                          "\t The contract is: " ++ CString ++ "\n" ++
 
220
                          "\t but the inferred signature is: ~s",
 
221
                          [M, F, A, SigString]))
 
222
      end;
 
223
    error ->
 
224
      {{F,A},{Range,Arg}}
 
225
  end.
 
226
 
233
227
get_functions(File, Analysis) ->
234
228
  case Analysis#typer_analysis.mode of
235
229
    ?SHOW ->
249
243
normalize_incFuncs(Funcs) ->
250
244
  [FuncInfo || {_FileName,FuncInfo} <- Funcs].
251
245
 
252
 
-spec(remove_module_info/1 :: ([func_info()]) -> [func_info()]).
 
246
-spec remove_module_info([func_info()]) -> [func_info()].
253
247
remove_module_info(FuncInfoList) ->
254
 
  F = fun 
255
 
        ({_,module_info,0}) -> false;
256
 
        ({_,module_info,1}) -> false;
257
 
        ({Line,F,A}) when is_integer(Line), is_atom(F), is_integer(A) -> true
 
248
  F = fun ({_,module_info,0}) -> false;
 
249
          ({_,module_info,1}) -> false;
 
250
          ({Line,F,A}) when is_integer(Line), is_atom(F), is_integer(A) -> true
258
251
      end,
259
252
  lists:filter(F, FuncInfoList).
260
253
 
261
254
write_typed_file(File, Info) ->
262
 
  io:format("      Processing file: ~p\n",[File]),
 
255
  io:format("      Processing file: ~p\n", [File]),
263
256
  Dir = filename:dirname(File),
264
257
  RootName = filename:basename(filename:rootname(File)),
265
258
  Ext = filename:extension(File),
266
259
  TyperAnnDir = filename:join(Dir, ?TYPER_ANN_DIR),
267
260
  TmpNewFilename = lists:concat([RootName,".ann",Ext]),
268
 
  NewFileName = filename:join(TyperAnnDir,TmpNewFilename),
 
261
  NewFileName = filename:join(TyperAnnDir, TmpNewFilename),
269
262
  case file:make_dir(TyperAnnDir) of
270
263
    {error, Reason} ->
271
264
      case Reason of
294
287
  ok = file:write_file(File, list_to_binary(Rest), [append]);
295
288
write_typed_file([First|RestCh], File, Info, LineNo, Acc) ->
296
289
  [{Line,F,A}|RestFuncs] = Info#info.funcs,
297
 
  case Line of 
 
290
  case Line of
298
291
    1 -> %% This will happen only for inc files
299
292
      ok = raw_write(F, A, Info, File, []),
300
293
      NewInfo = Info#info{funcs=RestFuncs},
319
312
      end
320
313
  end.
321
314
 
322
 
raw_write(F, A, Info, File, Content) ->  
 
315
raw_write(F, A, Info, File, Content) ->
323
316
  TypeInfo = get_type_string(F, A, Info, file),
324
 
  ContentList = lists:reverse(Content)++TypeInfo++"\n",
 
317
  ContentList = lists:reverse(Content) ++ TypeInfo ++ "\n",
325
318
  ContentBin = list_to_binary(ContentList),
326
319
  file:write_file(File, ContentBin, [append]).
327
320
 
340
333
      case {Mode, Type} of
341
334
        {file, {contract, _}} -> "";
342
335
        _ ->
343
 
          Prefix = lists:concat(["-spec(", F, "/", A, " :: "]),
344
 
          lists:concat([Prefix, TypeStr, [")."]])
 
336
          Prefix = lists:concat(["-spec ", F]),
 
337
          lists:concat([Prefix, TypeStr, "."])
345
338
      end;
346
339
    false ->
347
 
      Prefix = lists:concat(["%% @typer_spec ", F, "/", A, " :: "]),
348
 
      lists:concat([Prefix, TypeStr])
 
340
      Prefix = lists:concat(["%% @spec ", F]),
 
341
      lists:concat([Prefix, TypeStr, "."])
349
342
  end.
350
343
 
351
344
show_type_info_only(File, Info) ->
352
345
  io:format("\n%% File: ~p\n%% ", [File]),
353
 
  OutputString = lists:concat(["~.",length(File)+8,"c~n"]),
 
346
  OutputString = lists:concat(["~.", length(File)+8, "c~n"]),
354
347
  io:fwrite(OutputString, [$-]),
355
 
  Fun =
356
 
    fun ({_LineNo,F,A}) ->
357
 
        TypeInfo = get_type_string(F,A,Info,show),
358
 
        io:format("~s\n", [TypeInfo])
359
 
    end,
 
348
  Fun = fun ({_LineNo, F, A}) ->
 
349
            TypeInfo = get_type_string(F, A, Info, show),
 
350
            io:format("~s\n", [TypeInfo])
 
351
        end,
360
352
  lists:foreach(Fun, Info#info.funcs).
361
353
 
362
354
get_type_info(Func, TypeMap) ->