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

« 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-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
34
34
 
35
35
-import(erl_types, 
36
36
        [t_any/0, t_atom/0, t_atom_vals/1,
37
 
         t_binary/0, t_bitstr/0, t_bitstr/2, t_bitstr_concat/1, t_bool/0,
 
37
         t_binary/0, t_bitstr/0, t_bitstr/2, t_bitstr_concat/1, t_boolean/0,
38
38
         t_collect_vars/1, t_cons/2, t_cons_hd/1, t_cons_tl/1,
39
39
         t_float/0, t_from_range/2, t_from_term/1,
40
40
         t_fun/0, t_fun/2, t_fun_args/1, t_fun_range/1, 
901
901
%% function get_underapprox_from_guard/2
902
902
%%
903
903
get_type_test({erlang, is_atom, 1}) ->      {ok, t_atom()};
904
 
get_type_test({erlang, is_boolean, 1}) ->   {ok, t_bool()};
 
904
get_type_test({erlang, is_boolean, 1}) ->   {ok, t_boolean()};
905
905
get_type_test({erlang, is_binary, 1}) ->    {ok, t_binary()};
906
906
get_type_test({erlang, is_bitstring, 1}) -> {ok, t_bitstr()};
907
907
get_type_test({erlang, is_float, 1}) ->     {ok, t_float()};
1188
1188
get_bif_constr({erlang, is_bitstring, 1}, Dst, [Arg], State) ->
1189
1189
  get_bif_test_constr(Dst, Arg, t_bitstr(), State);
1190
1190
get_bif_constr({erlang, is_boolean, 1}, Dst, [Arg], State) ->
1191
 
  get_bif_test_constr(Dst, Arg, t_bool(), State);
 
1191
  get_bif_test_constr(Dst, Arg, t_boolean(), State);
1192
1192
get_bif_constr({erlang, is_float, 1}, Dst, [Arg], State) ->
1193
1193
  get_bif_test_constr(Dst, Arg, t_float(), State);
1194
1194
get_bif_constr({erlang, is_function, 1}, Dst, [Arg], State) ->
1207
1207
               end
1208
1208
           end,
1209
1209
  ArgV = mk_fun_var(ArgFun, [Dst, Arity]),
1210
 
  mk_conj_constraint_list([mk_constraint(Dst, sub, t_bool()),
 
1210
  mk_conj_constraint_list([mk_constraint(Dst, sub, t_boolean()),
1211
1211
                           mk_constraint(Arity, sub, t_integer()),
1212
1212
                           mk_constraint(Fun, sub, ArgV)]);
1213
1213
get_bif_constr({erlang, is_integer, 1}, Dst, [Arg], State) ->
1331
1331
                         true ->
1332
1332
                           case t_is_atom(true, lookup_type(Var, Map)) of
1333
1333
                             true -> False;
1334
 
                             false -> t_bool()
 
1334
                             false -> t_boolean()
1335
1335
                           end;
1336
1336
                         false -> 
1337
 
                           t_bool()
 
1337
                           t_boolean()
1338
1338
                       end
1339
1339
                   end
1340
1340
               end
1351
1351
                       case (t_is_atom(true, Arg1Type) 
1352
1352
                             andalso t_is_atom(true, Arg2Type)) of
1353
1353
                         true -> True;
1354
 
                         false -> t_bool()
 
1354
                         false -> t_boolean()
1355
1355
                       end
1356
1356
                   end
1357
1357
               end
1375
1375
                         true ->
1376
1376
                           case t_is_atom(false, lookup_type(Var, Map)) of
1377
1377
                             true -> True;
1378
 
                             false -> t_bool()
 
1378
                             false -> t_boolean()
1379
1379
                           end;
1380
1380
                         false -> 
1381
 
                           t_bool()
 
1381
                           t_boolean()
1382
1382
                       end
1383
1383
                   end
1384
1384
               end
1395
1395
                       case (t_is_atom(false, Arg1Type) 
1396
1396
                             andalso t_is_atom(false, Arg2Type)) of
1397
1397
                         true -> False;
1398
 
                         false -> t_bool()
 
1398
                         false -> t_boolean()
1399
1399
                       end
1400
1400
                   end
1401
1401
               end
1421
1421
                  false ->
1422
1422
                    case t_is_atom(false, Type) of
1423
1423
                      true -> True;
1424
 
                      false -> t_bool()
 
1424
                      false -> t_boolean()
1425
1425
                    end
1426
1426
                end
1427
1427
            end
1456
1456
               ArgType2 = lookup_type(Arg2, Map),
1457
1457
               case t_is_none(t_inf(ArgType1, ArgType2)) of
1458
1458
                 true -> t_from_term(false);
1459
 
                 false -> t_bool()
 
1459
                 false -> t_boolean()
1460
1460
               end
1461
1461
           end,
1462
1462
  DstArgs = [Dst, Arg1, Arg2],
1600
1600
                         false ->
1601
1601
                           case t_is_subtype(ArgType, Type) of
1602
1602
                             true -> t_from_term(true);
1603
 
                             false -> t_bool()
 
1603
                             false -> t_boolean()
1604
1604
                           end
1605
1605
                       end;
1606
1606
                     false ->  t_from_term(false)
1608
1608
                 false -> 
1609
1609
                   case t_is_subtype(ArgType, Type) of
1610
1610
                     true -> t_from_term(true);
1611
 
                     false -> t_bool()
 
1611
                     false -> t_boolean()
1612
1612
                   end
1613
1613
               end
1614
1614
           end,
1626
1626
  ?debug("============ Analyzing Fun: ~w ===========\n", 
1627
1627
         [debug_lookup_name(Fun)]),
1628
1628
  solve_fun(Fun, dict:new(), State);
1629
 
solve(SCC = [_|_], State) ->
 
1629
solve([_|_] = SCC, State) ->
1630
1630
  ?debug("============ Analyzing SCC: ~w ===========\n", 
1631
1631
         [[debug_lookup_name(F) || F <- SCC]]),
1632
 
  solve_scc(SCC, dict:new(), State).
 
1632
  solve_scc(SCC, dict:new(), State, false).
1633
1633
 
1634
1634
solve_fun(Fun, FunMap, State) ->
1635
1635
  Cs = state__get_cs(Fun, State),
1644
1644
               end,
1645
1645
  enter_type(Fun, NewType, NewFunMap1).
1646
1646
 
1647
 
solve_scc(SCC, Map, State) ->
 
1647
solve_scc(SCC, Map, State, TryingUnit) ->
1648
1648
  State1 = state__mark_as_non_self_rec(SCC, State),
1649
1649
  Vars0 = [{Fun, state__get_rec_var(Fun, State)} || Fun <- SCC],  
1650
1650
  Vars = [Var || {_, {ok, Var}} <- Vars0],
1652
1652
  Types = unsafe_lookup_type_list(Funs, Map),
1653
1653
  RecTypes = [t_limit(Type, ?TYPE_LIMIT) || Type <- Types],
1654
1654
  CleanMap = lists:foldl(fun(Fun, AccFunMap) ->
1655
 
                                dict:erase(t_var_name(Fun), AccFunMap)
 
1655
                             dict:erase(t_var_name(Fun), AccFunMap)
1656
1656
                         end, Map, SCC),
1657
1657
  Map1 = enter_type_lists(Vars, RecTypes, CleanMap),
1658
1658
  ?debug("Checking SCC: ~w\n", [[debug_lookup_name(F) || F <- SCC]]),
1663
1663
    true ->
1664
1664
      ?debug("SCC ~w reached fixpoint\n", [SCC]),
1665
1665
      NewTypes = unsafe_lookup_type_list(Funs, Map2),
1666
 
      case lists:all(fun(T) -> t_is_none(t_fun_range(T)) end, NewTypes) of
 
1666
      case lists:all(fun(T) -> t_is_none(t_fun_range(T)) end, NewTypes)
 
1667
        andalso TryingUnit =:= false of
1667
1668
        true ->
1668
1669
          UnitTypes = [t_fun(state__fun_arity(F, State), t_unit())
1669
1670
                       || F <- Funs],
1670
1671
          Map3 = enter_type_lists(Funs, UnitTypes, Map2),
1671
 
          solve_scc(SCC, Map3, State);
 
1672
          solve_scc(SCC, Map3, State, true);
1672
1673
        false ->
1673
1674
          Map2
1674
1675
      end;
1675
1676
    false -> 
1676
1677
      ?debug("SCC ~w did not reach fixpoint\n", [SCC]),
1677
 
      solve_scc(SCC, Map2, State)
 
1678
      solve_scc(SCC, Map2, State, TryingUnit)
1678
1679
  end.
1679
1680
 
1680
1681
scc_fold_fun(F, FunMap, State) ->