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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_contracts.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:
43
43
 
44
44
%%-----------------------------------------------------------------------
45
45
 
46
 
-spec(get_contract_return/1 :: (#contract{}) -> erl_type()).
 
46
-spec get_contract_return(#contract{}) -> erl_type().
47
47
get_contract_return(#contract{contracts=Cs, args=GenArgs}) ->
48
48
  process_contracts(Cs, GenArgs).
49
49
 
50
 
-spec(get_contract_return/2 :: (#contract{}, [erl_type()]) -> erl_type()).
 
50
-spec get_contract_return(#contract{}, [erl_type()]) -> erl_type().
51
51
get_contract_return(#contract{contracts=Cs}, Args) ->
52
52
  process_contracts(Cs, Args).
53
53
 
54
 
-spec(get_contract_args/1 :: (#contract{}) -> [erl_type()]).
 
54
-spec get_contract_args(#contract{}) -> [erl_type()].
55
55
get_contract_args(#contract{args=Args}) ->
56
56
  Args.
57
57
 
58
 
-spec(get_contract_signature/1 :: (#contract{}) -> erl_type()).
 
58
-spec get_contract_signature(#contract{}) -> erl_type().
59
59
get_contract_signature(#contract{contracts=Cs, args=GeneralDomain}) ->
60
60
  Range = process_contracts(Cs, GeneralDomain),
61
61
  erl_types:t_fun(GeneralDomain, Range).
62
62
 
63
 
-spec(is_overloaded/1 :: (#contract{}) -> bool()).
 
63
-spec is_overloaded(#contract{}) -> bool().
64
64
is_overloaded(#contract{contracts=Cs}) ->
65
65
  not(Cs =:= []).
66
66
 
67
 
-spec(contract_to_string/1 :: (#contract{}) -> string()).
 
67
-spec contract_to_string(#contract{}) -> string().
68
68
contract_to_string(#contract{forms=Forms}) ->
69
69
  contract_to_string_1(Forms).
70
70
 
102
102
sequence([H], _Delimiter) -> H;
103
103
sequence([H|T], Delimiter) -> H ++ Delimiter ++ sequence(T, Delimiter).
104
104
 
105
 
-spec(check_contracts/3 :: 
106
 
      (orddict(), #dialyzer_callgraph{}, dict()) -> [{mfa(), #contract{}}]).
 
105
-spec check_contracts(orddict(), #dialyzer_callgraph{}, dict()) -> [{mfa(), #contract{}}].
107
106
 
108
107
check_contracts(Contracts, Callgraph, FunTypes) ->
109
108
  FoldFun =
130
129
  dict:fold(FoldFun, [], FunTypes).
131
130
 
132
131
%% Checks all components of a contract
133
 
-spec(check_contract/2 ::
134
 
      (#contract{}, erl_type()) -> 'ok' | 'error' | {'error',_}).
 
132
-spec check_contract(#contract{}, erl_type()) -> 'ok' | 'error' | {'error',_}.
135
133
 
136
134
check_contract(#contract{contracts=Contracts}, SuccType) ->
137
135
  try 
146
144
      ok -> 
147
145
        InfList = [erl_types:t_inf(Contract, SuccType) 
148
146
                   || Contract <- Contracts2],
149
 
        InfDomains = lists:flatmap(fun erl_types:t_fun_args/1, InfList),
150
 
        case erl_types:any_none_or_unit(InfDomains) of
151
 
          true -> error;
152
 
          false ->
153
 
            STRange = erl_types:t_fun_range(SuccType),
154
 
            case erl_types:t_is_none_or_unit(STRange) of
155
 
              true -> ok;
156
 
              false -> 
157
 
                GenRanges = [erl_types:t_fun_range(C) || C <- Contracts2],
158
 
                case lists:any(fun(Range) -> 
159
 
                                   InfRange = erl_types:t_inf(STRange, Range),
160
 
                                   erl_types:t_is_none(InfRange)
161
 
                               end, GenRanges) of
162
 
                  true -> error;
163
 
                  false -> ok
164
 
                end
165
 
            end
166
 
        end
 
147
        check_contract_inf_list(InfList, SuccType)
167
148
    end
168
149
  catch throw:{error, Error} -> {error, Error}
169
150
  end.
178
159
    false -> error
179
160
  end.
180
161
 
 
162
%% Allow a contract if one of the overloaded contracts is possible.
 
163
%% We used to be more strict, e.g., all overloaded contracts had to be
 
164
%% possible.
 
165
check_contract_inf_list([FunType|Left], SuccType) ->
 
166
  case lists:any(fun erl_types:t_is_none_or_unit/1, 
 
167
                 erl_types:t_fun_args(FunType)) of
 
168
    true -> check_contract_inf_list(Left, SuccType);
 
169
    false ->
 
170
      STRange = erl_types:t_fun_range(SuccType),
 
171
      case erl_types:t_is_none_or_unit(STRange) of
 
172
        true -> ok;
 
173
        false -> 
 
174
          Range = erl_types:t_fun_range(FunType),
 
175
          case erl_types:t_is_none(erl_types:t_inf(STRange, Range)) of
 
176
            true -> check_contract_inf_list(Left, SuccType);
 
177
            false -> ok
 
178
          end
 
179
      end
 
180
  end;
 
181
check_contract_inf_list([], _SuccType) ->
 
182
  error.
 
183
 
181
184
%% This is the heart of the "range function"
182
 
-spec(process_contracts/2 :: ([{_,_}], [erl_type()]) -> erl_type()).
 
185
-spec process_contracts([{_,_}], [erl_type()]) -> erl_type().
183
186
 
184
187
process_contracts(OverContracts, Args) ->
185
188
  process_contracts(OverContracts, Args, erl_types:t_none()).
194
197
process_contracts([], _Args, AccRange) ->
195
198
  AccRange.
196
199
 
197
 
-spec(process_contract/2 ::
198
 
      ({_,_}, [erl_type()]) -> 'error' | {'ok',erl_type()}).
 
200
-spec process_contract({_,_}, [erl_type()]) -> 'error' | {'ok',erl_type()}.
199
201
 
200
202
process_contract({Contract, Constraints}, CallTypes0) ->
201
203
  CallTypesFun = erl_types:t_fun(CallTypes0, erl_types:t_any()),
232
234
  %%  erl_types:t_assign_variables_to_subtype(Contract, Inf).
233
235
 
234
236
%% Checks the contracts for functions that are not implemented
235
 
-spec(contracts_without_fun/3 :: 
236
 
      (dict(), [_], #dialyzer_callgraph{}) -> [dial_warning()]).
 
237
-spec contracts_without_fun(dict(), [_], #dialyzer_callgraph{}) -> [dial_warning()].
237
238
 
238
239
contracts_without_fun(Contracts, AllFuns0, Callgraph) ->
239
240
  AllFuns1 = [{dialyzer_callgraph:lookup_name(Label, Callgraph), Arity} 
240
241
              || {Label, Arity} <- AllFuns0],
241
242
  AllFuns2 = [{M, F, A} || {{ok,{M,F,_}}, A} <- AllFuns1],
242
243
  AllContracts = dict:fetch_keys(Contracts),
243
 
  ErrorContracts = lists:subtract(AllContracts, AllFuns2),
244
 
  lists:map(fun({M,F,A}) -> 
245
 
                File = atom_to_list(M) ++ ".erl",
246
 
                {Line, _Contract} = dict:fetch({M,F,A}, Contracts),
247
 
                {?WARN_CONTRACT_SYNTAX, {File, Line}, 
248
 
                 {spec_missing_fun, [M, F, A]}}
249
 
            end, ErrorContracts).
 
244
  ErrorContracts = AllContracts -- AllFuns2,
 
245
  [warn_spec_missing_fun(C, Contracts) || C <- ErrorContracts].
 
246
 
 
247
warn_spec_missing_fun({M,F,A}, Contracts) ->
 
248
  File = atom_to_list(M) ++ ".erl",
 
249
  {Line, _Contract} = dict:fetch({M,F,A}, Contracts),
 
250
  {?WARN_CONTRACT_SYNTAX, {File, Line}, {spec_missing_fun, [M, F, A]}}.
250
251
 
251
252
%% This treats the "when" constraints. It will be extended
252
253
insert_constraints([{subtype, Type1, Type2}|Left], Dict) ->
268
269
  insert_constraints(Left, Dict1);
269
270
insert_constraints([], Dict) -> Dict.
270
271
 
271
 
-spec(contract_from_form/2 :: ([_], dict()) -> #contract{}).
 
272
-spec contract_from_form([_], dict()) -> #contract{}.
272
273
 
273
274
contract_from_form(Forms, RecDict) ->
274
275
  {Cs, Forms1} = contract_from_form(Forms, RecDict, [], []),
316
317
  AccSig1 = erl_types:subst_all_vars_to_any(AccSig),
317
318
  erl_types:t_fun_args(AccSig1).
318
319
 
319
 
-spec(get_invalid_contract_warnings/3 ::
320
 
      ([atom()], #dialyzer_codeserver{}, #dialyzer_plt{}) -> [dial_warning()]).
 
320
-spec get_invalid_contract_warnings([atom()], #dialyzer_codeserver{}, #dialyzer_plt{}) -> [dial_warning()].
321
321
 
322
322
get_invalid_contract_warnings(Modules, CodeServer, Plt) ->
323
323
  get_invalid_contract_warnings_modules(Modules, CodeServer, Plt, []).
368
368
invalid_contract_warning({M, F, A}, FileLine, Type, RecDict) ->
369
369
  {?WARN_CONTRACT_TYPES, FileLine,
370
370
   {invalid_contract, [M, F, A, dialyzer_utils:format_sig(Type, RecDict)]}}.
371
 
  
372
371
 
373
372
picky_contract_check(CSig0, Sig0, MFA, FileLine, Contract, RecDict, Acc) ->
374
373
  CSig = erl_types:t_abstract_records(CSig0, RecDict),