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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_typesig.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:
53
53
-record(fun_var, {'fun'  :: fun((_) -> any()), 
54
54
                   deps  :: [integer()]}).
55
55
 
56
 
-type(type_or_fun_var() :: any()).
 
56
-type type_or_fun_var() :: any().
57
57
 
58
58
-record(constraint, {lhs   :: type_or_fun_var(),
59
59
                     op    :: 'eq' | 'sub', 
66
66
                          id    :: {'list', integer()}
67
67
                         }).
68
68
 
69
 
-type(type_var() :: any()).
 
69
-type type_var() :: any().
70
70
 
71
71
-record(constraint_ref, {id    :: type_var(), 
72
72
                         deps  :: [integer()]}).
130
130
%%             about functions that can be called by this SCC.
131
131
%%-----------------------------------------------------------------------------
132
132
 
133
 
-type(typesig_scc() :: [{mfa(), {_, _}, dict()}]).
134
 
-type(typesig_ret() :: [{mfa(),erl_type()}]).
 
133
-type typesig_scc() :: [{mfa(), {_, _}, dict()}].
 
134
-type typesig_ret() :: [{mfa(),erl_type()}].
135
135
 
136
 
-spec(analyze_scc/4 ::
137
 
      (typesig_scc(), integer(), #dialyzer_callgraph{}, #dialyzer_plt{}) ->
138
 
         typesig_ret()).
 
136
-spec analyze_scc(typesig_scc(), integer(), #dialyzer_callgraph{}, #dialyzer_plt{}) ->
 
137
         typesig_ret().
139
138
 
140
139
analyze_scc(SCC, NextLabel, CallGraph, Plt) when is_integer(NextLabel) ->
141
140
  assert_format_of_scc(SCC),
146
145
assert_format_of_scc([]) ->
147
146
  ok.
148
147
 
149
 
-spec(analyze_scc_get_all_fun_types/5 ::
150
 
      (typesig_scc(), integer(), #dialyzer_callgraph{}, 
151
 
       #dialyzer_plt{}, dict()) -> dict()).
 
148
-spec analyze_scc_get_all_fun_types(typesig_scc(), integer(),
 
149
                                    #dialyzer_callgraph{}, 
 
150
                                    #dialyzer_plt{}, dict()) -> dict().
152
151
 
153
152
analyze_scc_get_all_fun_types(SCC, NextLabel, CallGraph, Plt, PropTypes) ->
154
153
  assert_format_of_scc(SCC),
763
762
handle_clauses_1([], _TopVar, _Arg, _DefinedVars, State, _SubtrType, Acc) ->
764
763
  {state__new_constraint_context(State), Acc}.
765
764
 
766
 
-spec(get_safe_underapprox/2 :: ([_], core_tree()) -> erl_type()).
 
765
-spec get_safe_underapprox([_], core_tree()) -> erl_type().
767
766
 
768
767
get_safe_underapprox(Pats, Guard) ->
769
768
  try
1532
1531
  case lists:member(error, MFAs) of
1533
1532
    true -> error;
1534
1533
    false ->
1535
 
      MFAs1 = [X || {ok, X} <- MFAs],
1536
 
      Constrs =
1537
 
        lists:map(fun(MFA) ->
1538
 
                      State1 = state__new_constraint_context(State),
1539
 
                      State2 = get_plt_constr(MFA, Dst, ArgTypes, State1),
1540
 
                      state__cs(State2)
1541
 
                  end, MFAs1),
 
1534
      Constrs = [begin
 
1535
                   State1 = state__new_constraint_context(State),
 
1536
                   State2 = get_plt_constr(MFA, Dst, ArgTypes, State1),
 
1537
                   state__cs(State2)
 
1538
                 end || {ok, MFA} <- MFAs],
1542
1539
      ApplyConstr = mk_disj_constraint_list(Constrs),
1543
1540
      {ok, state__store_conj(ApplyConstr, State)}
1544
1541
  end.
1791
1788
  end.
1792
1789
 
1793
1790
expand_to_conjunctions(#constraint_list{type=conj, list=List}) ->
1794
 
  List1 = lists:filter(fun(#constraint{}) -> true;
1795
 
                          (#constraint_ref{}) -> true;
1796
 
                          (#constraint_list{}) -> false
1797
 
                       end, List),
 
1791
  List1 = [C || C <- List, is_simple_constraint(C)],
1798
1792
  List2 = [expand_to_conjunctions(C) || C = #constraint_list{} <- List],
1799
1793
  case List2 =:= [] of
1800
1794
    true -> [mk_conj_constraint_list(List1)];
1810
1804
  if length(List) > ?DISJ_NORM_FORM_LIMIT -> throw(too_many_disj);
1811
1805
     true -> ok
1812
1806
  end,
1813
 
  List1 = lists:filter(fun(#constraint{}) -> true;
1814
 
                          (#constraint_ref{}) -> true;
1815
 
                          (#constraint_list{}) -> false
1816
 
                       end, List),
 
1807
  List1 = [C || C <- List, is_simple_constraint(C)],
1817
1808
  %% Just an assert.
1818
1809
  [] = [C || C=#constraint{} <- List1],
1819
1810
  Expanded = lists:flatten([expand_to_conjunctions(C) 
1823
1814
     true -> ReturnList
1824
1815
  end.
1825
1816
 
 
1817
is_simple_constraint(#constraint{}) -> true;
 
1818
is_simple_constraint(#constraint_ref{}) -> true;
 
1819
is_simple_constraint(#constraint_list{}) -> false.
 
1820
 
1826
1821
combine_conj_lists([List1, List2|Left], Prefix) ->
1827
1822
  NewList = [mk_conj_constraint_list([L1, L2]) || L1 <- List1, L2 <- List2],
1828
1823
  if length(NewList) > ?DISJ_NORM_FORM_LIMIT -> throw(too_many_disj);
1831
1826
  combine_conj_lists([NewList|Left], Prefix);
1832
1827
combine_conj_lists([List], Prefix) ->
1833
1828
  [mk_conj_constraint_list([mk_conj_constraint_list(Prefix), L]) || L <- List].
1834
 
  
1835
 
                                                  
1836
1829
 
1837
1830
calculate_deps(List) ->
1838
1831
  calculate_deps(List, []).
1849
1842
mk_disj_constraint_list([NotReallyAList]) ->
1850
1843
  NotReallyAList;
1851
1844
mk_disj_constraint_list(List) ->
1852
 
  %% Make sure all elements in the list is a conjunction or a
 
1845
  %% Make sure each element in the list is either a conjunction or a
1853
1846
  %% ref. Wrap single constraints into conjunctions.
1854
 
  List1 = lists:map(fun(C = #constraint{}) -> mk_conj_constraint_list([C]);
1855
 
                       (C = #constraint_list{}) -> C;
1856
 
                       (C = #constraint_ref{}) -> C
1857
 
                    end, List),
 
1847
  List1 = [wrap_simple_constr(C) || C <- List],
1858
1848
  mk_constraint_list(disj, List1).
1859
1849
 
 
1850
wrap_simple_constr(C = #constraint{}) -> mk_conj_constraint_list([C]);
 
1851
wrap_simple_constr(C = #constraint_list{}) -> C;
 
1852
wrap_simple_constr(C = #constraint_ref{}) -> C.
 
1853
 
1860
1854
enumerate_constraints(State) ->
1861
1855
  Cs = [mk_constraint_ref(Id, get_deps(state__get_cs(Id, State))) 
1862
1856
        || Id <- state__scc(State)],