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

« back to all changes in this revision

Viewing changes to lib/hipe/cerl/erl_types.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:
59
59
         t_bitstr_concat/2,
60
60
         t_bitstr_match/2,
61
61
         t_bitstr_unit/1,
62
 
         t_bool/0,
 
62
         t_boolean/0,
63
63
         t_byte/0,
64
64
         t_char/0,
65
65
         t_collect_vars/1,
109
109
         t_is_binary/1,
110
110
         t_is_bitstr/1,
111
111
         t_is_bitwidth/1,
112
 
         t_is_bool/1,
 
112
         t_is_boolean/1,
113
113
         %% t_is_byte/1,
114
114
         %% t_is_char/1,
115
115
         t_is_cons/1,
669
669
 
670
670
%%------------------------------------
671
671
 
672
 
-spec t_bool() -> erl_type().
 
672
-spec t_boolean() -> erl_type().
673
673
 
674
 
t_bool() ->
 
674
t_boolean() ->
675
675
  ?atom(set_from_list([false, true])).
676
676
 
677
 
-spec t_is_bool(erl_type()) -> bool().
 
677
-spec t_is_boolean(erl_type()) -> bool().
678
678
 
679
 
t_is_bool(?atom(?any)) -> false;
680
 
t_is_bool(?atom(Set)) ->
 
679
t_is_boolean(?atom(?any)) -> false;
 
680
t_is_boolean(?atom(Set)) ->
681
681
  case set_size(Set) of
682
682
    1 -> set_is_element(true, Set) orelse set_is_element(false, Set);
683
683
    2 -> set_is_element(true, Set) andalso set_is_element(false, Set);
684
684
    N when is_integer(N), N > 2 -> false
685
685
  end;
686
 
t_is_bool(_) -> false.
 
686
t_is_boolean(_) -> false.
687
687
 
688
688
%%-----------------------------------------------------------------------------
689
689
%% Binaries
697
697
-spec t_is_binary(erl_type()) -> bool().
698
698
 
699
699
t_is_binary(?bitstr(U, B)) -> 
700
 
  ((U rem 8) =:= 0) and ((B rem 8) =:= 0);
 
700
  ((U rem 8) =:= 0) andalso ((B rem 8) =:= 0);
701
701
t_is_binary(_) -> false.
702
702
 
703
703
%%-----------------------------------------------------------------------------
1388
1388
                    t_sup(t_atom(), t_tid()),
1389
1389
                    t_sup(t_atom(), t_tid()),
1390
1390
                    t_sup(t_atom(), t_tid()),
1391
 
                    t_bool()])).
 
1391
                    t_boolean()])).
1392
1392
 
1393
1393
-spec t_gb_set() -> erl_type().
1394
1394
 
3085
3085
            _RecDict, _VarDict) -> 
3086
3086
  t_bitstr(Unit, Base);
3087
3087
t_from_form({type, _L, bitstring, []}, _RecDict, _VarDict) -> t_bitstr();
3088
 
t_from_form({type, _L, bool, []}, _RecDict, _VarDict) -> t_bool();
 
3088
t_from_form({type, _L, bool, []}, _RecDict, _VarDict) -> t_boolean();   % XXX: Temporarily
 
3089
t_from_form({type, _L, boolean, []}, _RecDict, _VarDict) -> t_boolean();
3089
3090
t_from_form({type, _L, byte, []}, _RecDict, _VarDict) -> t_byte();
3090
3091
t_from_form({type, _L, char, []}, _RecDict, _VarDict) -> t_char();
3091
3092
t_from_form({type, _L, dict, []}, _RecDict, _VarDict) -> t_dict();
3513
3514
 
3514
3515
  True   = t_atom(true),
3515
3516
  False  = t_atom(false),
3516
 
  Bool   = t_bool(),
3517
 
  true   = t_is_bool(True),
3518
 
  true   = t_is_bool(Bool),
3519
 
  false  = t_is_bool(Atom1),
 
3517
  Bool   = t_boolean(),
 
3518
  true   = t_is_boolean(True),
 
3519
  true   = t_is_boolean(Bool),
 
3520
  false  = t_is_boolean(Atom1),
3520
3521
 
3521
3522
  Binary = t_binary(),
3522
3523
  true   = t_is_binary(Binary),
3568
3569
  true      = t_is_fun(Function3),  
3569
3570
 
3570
3571
  List1 = t_list(),
3571
 
  List2 = t_list(t_bool()),
3572
 
  List3 = t_cons(t_bool(), List2),
3573
 
  List4 = t_cons(t_bool(), t_atom()),
3574
 
  List5 = t_cons(t_bool(), t_nil()),
 
3572
  List2 = t_list(t_boolean()),
 
3573
  List3 = t_cons(t_boolean(), List2),
 
3574
  List4 = t_cons(t_boolean(), t_atom()),
 
3575
  List5 = t_cons(t_boolean(), t_nil()),
3575
3576
  List6 = t_cons_tl(List5),
3576
3577
  List7 = t_sup(List4, List5),
3577
3578
  List8 = t_inf(List7, t_list()),
3578
3579
  List9 = t_cons(),
3579
3580
  List10 = t_cons_tl(List9),
3580
 
  true  = t_is_bool(t_cons_hd(List5)),
 
3581
  true  = t_is_boolean(t_cons_hd(List5)),
3581
3582
  true  = t_is_list(List5),
3582
3583
  false = t_is_list(List4),
3583
3584
 
3593
3594
  Union6 = t_sup(Function1, Function2),
3594
3595
  Union7 = t_sup(Function4, Function5),
3595
3596
  Union8 = t_sup(True, False),
3596
 
  true   = t_is_bool(Union8),
 
3597
  true   = t_is_boolean(Union8),
3597
3598
  Union9 = t_sup(Int2, t_integer(2)),
3598
3599
  true   = t_is_byte(Union9),
3599
3600
  Union10 = t_sup(t_tuple([t_atom(true), ?any]),