~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/small_SUITE_data/src/my_sofs.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% Program showing the problems with record field accesses.
 
2
 
 
3
-module(my_sofs).
 
4
-export([ordset_of_sets/3, is_equal/2]).
 
5
 
 
6
-define(TAG, 'Set').
 
7
-define(ORDTAG, 'OrdSet').
 
8
 
 
9
-record(?TAG, {data = [], type = type}).
 
10
-record(?ORDTAG, {orddata = {}, ordtype = type}).
 
11
 
 
12
-define(LIST(S), (S)#?TAG.data).
 
13
-define(TYPE(S), (S)#?TAG.type).
 
14
-define(SET(L, T), #?TAG{data = L, type = T}).
 
15
-define(IS_SET(S), record(S, ?TAG)).
 
16
 
 
17
%% Ordered sets and atoms:
 
18
-define(ORDDATA(S), (S)#?ORDTAG.orddata).
 
19
-define(ORDTYPE(S), (S)#?ORDTAG.ordtype).
 
20
-define(ORDSET(L, T), #?ORDTAG{orddata = L, ordtype = T}).
 
21
-define(IS_ORDSET(S), record(S, ?ORDTAG)).
 
22
 
 
23
%% When IS_SET is true:
 
24
-define(ANYTYPE, '_').
 
25
-define(REL_TYPE(I, R), element(I, R)).
 
26
-define(SET_OF(X), [X]).
 
27
 
 
28
is_equal(S1, S2) when ?IS_SET(S1), ?IS_SET(S2) ->
 
29
    case match_types(?TYPE(S1), ?TYPE(S2)) of
 
30
        true  -> ?LIST(S1) == ?LIST(S2);
 
31
        false -> erlang:error(type_mismatch, [S1, S2])
 
32
    end;
 
33
is_equal(S1, S2) when ?IS_ORDSET(S1), ?IS_ORDSET(S2) ->
 
34
    case match_types(?TYPE(S1), ?TYPE(S2)) of
 
35
        true  -> ?ORDDATA(S1) == ?ORDDATA(S2);
 
36
        false -> erlang:error(type_mismatch, [S1, S2])
 
37
    end;
 
38
is_equal(S1, S2) when ?IS_SET(S1), ?IS_ORDSET(S2) ->
 
39
    erlang:error(type_mismatch, [S1, S2]);
 
40
is_equal(S1, S2) when ?IS_ORDSET(S1), ?IS_SET(S2) ->
 
41
    erlang:error(type_mismatch, [S1, S2]).
 
42
 
 
43
%% Type = OrderedSetType
 
44
%%      | SetType
 
45
%%      | atom() except '_'
 
46
%% OrderedSetType = {Type, ..., Type}
 
47
%% SetType = [ElementType]           % list of exactly one element
 
48
%% ElementType = '_'                 % any type (implies empty set)
 
49
%%             | Type
 
50
 
 
51
ordset_of_sets([S | Ss], L, T) when ?IS_SET(S) ->
 
52
    ordset_of_sets(Ss, [?LIST(S) | L], [[?TYPE(S)] | T]);
 
53
ordset_of_sets([S | Ss], L, T) when ?IS_ORDSET(S) ->
 
54
    ordset_of_sets(Ss, [?LIST(S) | L], [?ORDTYPE(S) | T]);
 
55
ordset_of_sets([], L, T) ->
 
56
    ?ORDSET(list_to_tuple(lists:reverse(L)), list_to_tuple(lists:reverse(T)));
 
57
ordset_of_sets(_, _L, _T) ->
 
58
    error.
 
59
 
 
60
%% inlined.
 
61
match_types(T, T) -> true;
 
62
match_types(Type1, Type2) -> match_types1(Type1, Type2).
 
63
 
 
64
match_types1(Atom, Atom) when is_atom(Atom) ->
 
65
    true;
 
66
match_types1(?ANYTYPE, _) ->
 
67
    true;
 
68
match_types1(_, ?ANYTYPE) ->
 
69
    true;
 
70
match_types1(?SET_OF(Type1), ?SET_OF(Type2)) ->
 
71
    match_types1(Type1, Type2);
 
72
match_types1(T1, T2) when tuple(T1), tuple(T2), size(T1) =:= size(T2) ->
 
73
    match_typesl(size(T1), T1, T2);
 
74
match_types1(_T1, _T2) ->
 
75
    false.
 
76
 
 
77
match_typesl(0, _T1, _T2) ->
 
78
    true;
 
79
match_typesl(N, T1, T2) ->
 
80
    case match_types1(?REL_TYPE(N, T1), ?REL_TYPE(N, T2)) of
 
81
        true  -> match_typesl(N-1, T1, T2);
 
82
        false -> false
 
83
    end.