~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
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:
56
56
 
57
57
-include("dialyzer.hrl").
58
58
 
59
 
-type(mod_deps() :: dict()).
 
59
-type mod_deps() :: dict().
60
60
 
61
61
%% XXX: This is only for a version or so, to protect against old plts.
62
 
-type(old_md5() :: [{atom(), binary()}]). 
 
62
-type old_md5() :: [{atom(), binary()}]. 
63
63
 
64
64
-record(dialyzer_file_plt, {version=[]            :: string(), 
65
65
                            md5=[]                :: md5() | old_md5(),
69
69
                            implementation_md5=[] :: [{atom(), _}]
70
70
                           }).
71
71
 
72
 
-spec(new/0 :: () -> #dialyzer_plt{}).
 
72
-spec new() -> #dialyzer_plt{}.
73
73
 
74
74
new() ->
75
75
  #dialyzer_plt{info=table_new(), contracts=table_new()}.
76
76
 
77
 
-spec(delete_module/2 :: (#dialyzer_plt{}, atom()) -> #dialyzer_plt{}).
 
77
-spec delete_module(#dialyzer_plt{}, atom()) -> #dialyzer_plt{}.
78
78
 
79
79
delete_module(#dialyzer_plt{info=Info, contracts=Contracts}, Mod) ->
80
80
  #dialyzer_plt{info=table_delete_module(Info, Mod),
81
81
                contracts=table_delete_module(Contracts, Mod)}.
82
82
 
83
 
-spec(delete_list/2 :: (#dialyzer_plt{}, [_]) -> #dialyzer_plt{}).
 
83
-spec delete_list(#dialyzer_plt{}, [_]) -> #dialyzer_plt{}.
84
84
 
85
85
delete_list(#dialyzer_plt{info=Info, contracts=Contracts}, List) ->
86
86
  #dialyzer_plt{info=table_delete_list(Info, List),
87
87
                contracts=table_delete_list(Contracts, List)}.
88
88
 
89
 
-spec(insert_contract_list/2 :: 
90
 
      (#dialyzer_plt{}, [{mfa(), #contract{}}]) -> #dialyzer_plt{}).
 
89
-spec insert_contract_list(#dialyzer_plt{}, [{mfa(), #contract{}}]) -> #dialyzer_plt{}.
91
90
 
92
91
insert_contract_list(Plt = #dialyzer_plt{contracts=Contracts}, List) ->
93
92
  Plt#dialyzer_plt{contracts=table_insert_list(Contracts, List)}.
94
93
 
95
 
-spec(lookup_contract/2 :: 
96
 
      (#dialyzer_plt{}, mfa()) -> 'none' | {'value', #contract{}}).
 
94
-spec lookup_contract(#dialyzer_plt{}, mfa()) -> 'none' | {'value',#contract{}}.
97
95
 
98
96
lookup_contract(#dialyzer_plt{contracts=Contracts}, 
99
97
                MFA={M, F, A}) when is_atom(M), is_atom(F), is_integer(A), 
100
98
                                    0 =< A, A =< 255 ->
101
99
  table_lookup(Contracts, MFA).
102
100
 
103
 
-spec(delete_contract_list/2 :: (#dialyzer_plt{}, [mfa()]) -> #dialyzer_plt{}).
 
101
-spec delete_contract_list(#dialyzer_plt{}, [mfa()]) -> #dialyzer_plt{}.
104
102
 
105
103
delete_contract_list(Plt = #dialyzer_plt{contracts=Contracts}, List) ->
106
104
  Plt#dialyzer_plt{contracts=table_delete_list(Contracts, List)}.
107
105
 
108
106
 
109
 
%% -spec(insert/3 :: (#dialyzer_plt{}, mfa() | integer(), {_, _}) ->
110
 
%%       #dialyzer_plt{}).
 
107
%% -spec insert(#dialyzer_plt{}, mfa() | integer(), {_, _}) -> #dialyzer_plt{}.
111
108
%% 
112
109
%% insert(Plt = #dialyzer_plt{info=Info}, Id, Types) ->
113
110
%%   Plt#dialyzer_plt{info=table_insert(Info, Id, Types)}.
114
111
 
115
 
-spec(insert_list/2 :: (#dialyzer_plt{}, [{mfa() | integer(), {_, _}}]) ->
116
 
         #dialyzer_plt{}).
 
112
-spec insert_list(#dialyzer_plt{}, [{mfa() | integer(), {_, _}}]) -> #dialyzer_plt{}.
117
113
 
118
114
insert_list(Plt = #dialyzer_plt{info=Info}, List) ->
119
115
  Plt#dialyzer_plt{info=table_insert_list(Info, List)}.
120
116
 
121
 
-spec(lookup/2 :: (#dialyzer_plt{}, integer() | mfa()) -> 
122
 
         'none' | {'value', {_, _}}).
 
117
-spec lookup(#dialyzer_plt{}, integer() | mfa()) -> 'none' | {'value', {_, _}}.
123
118
 
124
119
lookup(#dialyzer_plt{info=Info}, MFA={M, F, A}) when is_atom(M), 
125
120
                                                     is_atom(F),
129
124
lookup(#dialyzer_plt{info=Info}, Label) when is_integer(Label) ->
130
125
  table_lookup(Info, Label).
131
126
 
132
 
-spec(lookup_module/2 :: 
133
 
      (#dialyzer_plt{}, atom()) -> 'none' | {'value', [{_, _}]}).
 
127
-spec lookup_module(#dialyzer_plt{}, atom()) -> 'none' | {'value', [{mfa(), _, _}]}.
134
128
 
135
129
lookup_module(#dialyzer_plt{info=Info}, M) when is_atom(M) ->
136
130
  table_lookup_module(Info, M).
137
131
 
138
 
-spec(contains_module/2 :: (#dialyzer_plt{}, atom()) -> bool()).
 
132
-spec contains_module(#dialyzer_plt{}, atom()) -> bool().
139
133
 
140
134
contains_module(#dialyzer_plt{info=Info, contracts=Cs}, M) when is_atom(M) ->
141
135
  table_contains_module(Info, M) orelse table_contains_module(Cs, M).
142
136
 
143
 
-spec(contains_mfa/2 :: (#dialyzer_plt{}, mfa()) -> bool()).
 
137
-spec contains_mfa(#dialyzer_plt{}, mfa()) -> bool().
144
138
 
145
139
contains_mfa(#dialyzer_plt{info=Info, contracts=Contracts}, MFA) ->
146
140
  (table_lookup(Info, MFA) =/= none) 
147
141
    orelse (table_lookup(Contracts, MFA) =/= none).
148
142
 
149
 
-spec(get_default_plt/0 :: () -> string()).
 
143
-spec get_default_plt() -> string().
150
144
 
151
145
get_default_plt() ->
152
146
  case os:getenv("DIALYZER_PLT") of
153
147
    false ->
154
148
      case os:getenv("HOME") of
155
 
        false -> error("Please specify which plt to use");
 
149
        false ->
 
150
          error("The HOME environment variable needs to be set " ++
 
151
                "so that Dialyzer knows where to find the default PLT");
156
152
        HomeDir -> filename:join(HomeDir, ".dialyzer_plt")
157
153
      end;
158
154
    UserSpecPlt -> UserSpecPlt
159
155
  end.
160
156
 
161
 
-spec(plt_and_info_from_file/1 :: (string()) -> {#dialyzer_plt{}, {_, _}}).
 
157
-spec plt_and_info_from_file(string()) -> {#dialyzer_plt{}, {_, _}}.
162
158
  
163
159
plt_and_info_from_file(FileName) ->
164
160
  from_file(FileName, true).
165
161
 
166
 
-spec(from_file/1 :: (string()) -> #dialyzer_plt{}).
 
162
-spec from_file(string()) -> #dialyzer_plt{}.
167
163
         
168
164
from_file(FileName) ->
169
165
  from_file(FileName, false).
191
187
                          [FileName, Reason]))
192
188
  end.
193
189
 
194
 
-spec(included_files/1 :: (string()) -> {ok, [string()]} 
195
 
                                      | {error, 'no_such_file' | 'read_error'}).
196
 
         
 
190
-spec included_files(string()) -> {ok, [string()]} 
 
191
                               | {error, 'no_such_file' | 'read_error'}.
197
192
 
198
193
included_files(FileName) ->
199
194
  case get_record_from_file(FileName) of
226
221
      {error, read_error}
227
222
  end.
228
223
 
229
 
-spec(merge_plts/1 :: ([#dialyzer_plt{}]) -> #dialyzer_plt{}).
 
224
-spec merge_plts([#dialyzer_plt{}]) -> #dialyzer_plt{}.
230
225
 
231
226
merge_plts(List) ->
232
 
  InfoList = lists:map(fun(#dialyzer_plt{info=Info}) -> Info end, List),
233
 
  ContractsList = lists:map(fun(#dialyzer_plt{contracts=Contracts}) -> 
234
 
                                Contracts 
235
 
                              end, List),
 
227
  InfoList = [Info || #dialyzer_plt{info=Info} <- List],
 
228
  ContractsList = [Contracts || #dialyzer_plt{contracts=Contracts} <- List],
236
229
  #dialyzer_plt{info=table_merge(InfoList),
237
230
                contracts=table_merge(ContractsList)}.
238
231
 
239
 
-spec(to_file/4 :: (string(), #dialyzer_plt{}, dict(), {md5(), dict()}) -> 'ok').
 
232
-spec to_file(string(), #dialyzer_plt{}, dict(), {md5(), dict()}) -> 'ok'.
240
233
 
241
234
to_file(FileName, #dialyzer_plt{info=Info, contracts=Contracts}, 
242
235
        ModDeps, {MD5, OldModDeps}) ->
260
253
      throw({dialyzer_error, Msg})
261
254
  end.
262
255
 
263
 
-type(md5_diff() :: [{'differ',atom()} | {'removed',atom()}]).
264
 
-type(check_error() :: 'not_valid' | 'no_such_file' | 'read_error' |
265
 
                       {'no_file_to_remove', string()}).
 
256
-type md5_diff()    :: [{'differ',atom()} | {'removed',atom()}].
 
257
-type check_error() :: 'not_valid' | 'no_such_file' | 'read_error'
 
258
                     | {'no_file_to_remove', string()}.
266
259
      
267
 
-spec(check_plt/3 :: 
268
 
      (string(), [string()], [string()]) -> 
 
260
-spec check_plt(string(), [string()], [string()]) -> 
269
261
         'ok'
270
262
       | {'error', check_error()}
271
263
       | {'differ', md5(), md5_diff(), mod_deps()}
272
 
       | {'old_version', md5()}).
 
264
       | {'old_version', md5()}.
273
265
 
274
266
check_plt(FileName, RemoveFiles, AddFiles) ->
275
267
  case get_record_from_file(FileName) of
334
326
  Files2 = [filename:join([Dir, "ebin", F]) || F <- Files1],
335
327
  compute_md5_from_files(Files2).
336
328
 
337
 
-spec(compute_md5_from_files/1 :: ([string()]) -> [{string(), binary()}]).
 
329
-spec compute_md5_from_files([string()]) -> [{string(), binary()}].
338
330
 
339
331
compute_md5_from_files(Files) ->
340
332
  lists:keysort(1, [{F, compute_md5_from_file(F)} || F <- Files]).
347
339
    true ->
348
340
      case dialyzer_utils:get_abstract_code_from_beam(File) of
349
341
        error ->
350
 
          Msg = io_lib:format("Could not compute md5 for file: ~s\n", [File]),
 
342
          Msg = io_lib:format("Could not get abstract code for file: ~s (please recompile it with +debug_info)\n", [File]),
351
343
          throw({dialyzer_error, Msg});
352
344
        {ok, Abs} ->
353
345
          erlang:md5(term_to_binary(Abs))
393
385
%%---------------------------------------------------------------------------
394
386
%% Edoc
395
387
 
396
 
-spec(to_edoc/1 :: (#dialyzer_plt{}) -> string()).
 
388
-spec to_edoc(#dialyzer_plt{}) -> string().
397
389
 
398
390
to_edoc(#dialyzer_plt{info=Info}) ->
399
391
  %% TODO: Should print contracts as well.
404
396
beam_file_to_module(Filename) ->
405
397
  list_to_atom(filename:basename(Filename, ".beam")).
406
398
 
407
 
-spec(to_edoc/4 :: (#dialyzer_plt{}, atom(), atom(), byte()) -> string()).
 
399
-spec to_edoc(#dialyzer_plt{}, atom(), atom(), byte()) -> string().
408
400
 
409
401
to_edoc(PLT, M, F, A) when is_atom(M), is_atom(F) ->
410
402
  {value, Val} = lookup(PLT, {M, F, A}),
518
510
%%---------------------------------------------------------------------------
519
511
%% Debug utilities.
520
512
 
521
 
-spec(pp_non_returning/0 :: () -> 'ok').
 
513
-spec pp_non_returning() -> 'ok'.
522
514
 
523
515
pp_non_returning() ->
524
516
  PltFile = filename:join([code:lib_dir(dialyzer), "plt", "dialyzer_init_plt"]),
545
537
                end, lists:sort(None)),
546
538
  ok.
547
539
 
548
 
-spec(pp_mod/1 :: (atom()) -> 'ok').
 
540
-spec pp_mod(atom()) -> 'ok'.
549
541
 
550
542
pp_mod(Mod) when is_atom(Mod) ->
551
543
  PltFile = filename:join([code:lib_dir(dialyzer), "plt", "dialyzer_init_plt"]),