~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/stdlib/src/ordsets.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
 
19
20
-module(ordsets).
21
22
-export([new/0,is_set/1,size/1,to_list/1,from_list/1]).
22
23
-export([is_element/2,add_element/2,del_element/2]).
23
24
-export([union/2,union/1,intersection/2,intersection/1]).
 
25
-export([is_disjoint/2]).
24
26
-export([subtract/2,is_subset/2]).
25
27
-export([fold/3,filter/2]).
26
28
 
 
29
-type ordset() :: [_].
 
30
 
27
31
%% new() -> Set.
28
32
%%  Return a new empty ordered set.
29
33
 
 
34
-spec new() -> ordset().
 
35
 
30
36
new() -> [].
31
37
 
32
38
%% is_set(Term) -> bool().
33
39
%%  Return 'true' if Set is an ordered set of elements, else 'false'.
34
40
 
 
41
-spec is_set(term()) -> bool().
 
42
 
35
43
is_set([E|Es]) -> is_set(Es, E);
36
44
is_set([]) -> true;
37
45
is_set(_) -> false.
44
52
%% size(OrdSet) -> int().
45
53
%%  Return the number of elements in OrdSet.
46
54
 
 
55
-spec size(ordset()) -> non_neg_integer().
 
56
 
47
57
size(S) -> length(S).
48
58
 
49
59
%% to_list(OrdSet) -> [Elem].
50
60
%%  Return the elements in OrdSet as a list.
51
61
 
 
62
-spec to_list(ordset()) -> [term()].
 
63
 
52
64
to_list(S) -> S.
53
65
 
54
66
%% from_list([Elem]) -> Set.
55
67
%%  Build an ordered set from the elements in List.
56
68
 
 
69
-spec from_list([term()]) -> ordset().
 
70
 
57
71
from_list(L) ->
58
72
    lists:usort(L).
59
73
 
60
74
%% is_element(Element, OrdSet) -> bool().
61
75
%%  Return 'true' if Element is an element of OrdSet, else 'false'.
62
76
 
 
77
-spec is_element(term(), ordset()) -> bool().
 
78
 
63
79
is_element(E, [H|Es]) when E > H -> is_element(E, Es);
64
80
is_element(E, [H|_]) when E < H -> false;
65
81
is_element(_E, [_H|_]) -> true;                 %E == H
68
84
%% add_element(Element, OrdSet) -> OrdSet.
69
85
%%  Return OrdSet with Element inserted in it.
70
86
 
 
87
-spec add_element(term(), ordset()) -> ordset().
 
88
 
71
89
add_element(E, [H|Es]) when E > H -> [H|add_element(E, Es)];
72
90
add_element(E, [H|_]=Set) when E < H -> [E|Set];
73
91
add_element(_E, [_H|_]=Set) -> Set;             %E == H
74
 
add_element(E, []) ->[E].
 
92
add_element(E, []) -> [E].
75
93
 
76
94
%% del_element(Element, OrdSet) -> OrdSet.
77
95
%%  Return OrdSet but with Element removed.
78
96
 
 
97
-spec del_element(term(), ordset()) -> ordset().
 
98
 
79
99
del_element(E, [H|Es]) when E > H -> [H|del_element(E, Es)];
80
100
del_element(E, [H|_]=Set) when E < H -> Set;
81
101
del_element(_E, [_H|Es]) -> Es;                 %E == H
82
 
del_element(_, []) ->[].
 
102
del_element(_, []) -> [].
83
103
 
84
104
%% union(OrdSet1, OrdSet2) -> OrdSet
85
105
%%  Return the union of OrdSet1 and OrdSet2.
86
106
 
 
107
-spec union(ordset(), ordset()) -> ordset().
 
108
 
87
109
union([E1|Es1], [E2|_]=Set2) when E1 < E2 ->
88
110
    [E1|union(Es1, Set2)];
89
111
union([E1|_]=Set1, [E2|Es2]) when E1 > E2 ->
96
118
%% union([OrdSet]) -> OrdSet
97
119
%%  Return the union of the list of ordered sets.
98
120
 
 
121
-spec union([ordset()]) -> ordset().
 
122
 
99
123
union([S1,S2|Ss]) ->
100
124
    union1(union(S1, S2), Ss);
101
125
union([S]) -> S;
107
131
%% intersection(OrdSet1, OrdSet2) -> OrdSet.
108
132
%%  Return the intersection of OrdSet1 and OrdSet2.
109
133
 
 
134
-spec intersection(ordset(), ordset()) -> ordset().
 
135
 
110
136
intersection([E1|Es1], [E2|_]=Set2) when E1 < E2 ->
111
137
    intersection(Es1, Set2);
112
138
intersection([E1|_]=Set1, [E2|Es2]) when E1 > E2 ->
121
147
%% intersection([OrdSet]) -> OrdSet.
122
148
%%  Return the intersection of the list of ordered sets.
123
149
 
 
150
-spec intersection([ordset()]) -> ordset().
 
151
 
124
152
intersection([S1,S2|Ss]) ->
125
153
    intersection1(intersection(S1, S2), Ss);
126
154
intersection([S]) -> S.
129
157
    intersection1(intersection(S1, S2), Ss);
130
158
intersection1(S1, []) -> S1.
131
159
 
 
160
%% is_disjoint(OrdSet1, OrdSet2) -> true|false.
 
161
%%  Check whether OrdSet1 and OrdSet2 are disjoint.
 
162
 
 
163
-spec is_disjoint(ordset(), ordset()) -> bool().
 
164
 
 
165
is_disjoint([E1|Es1], [E2|_]=Set2) when E1 < E2 ->
 
166
    is_disjoint(Es1, Set2);
 
167
is_disjoint([E1|_]=Set1, [E2|Es2]) when E1 > E2 ->
 
168
    is_disjoint(Es2, Set1);                     % switch arguments!
 
169
is_disjoint([_E1|_Es1], [_E2|_Es2]) ->          %E1 == E2
 
170
    false;
 
171
is_disjoint([], _) ->
 
172
    true;
 
173
is_disjoint(_, []) ->
 
174
    true.
 
175
 
132
176
%% subtract(OrdSet1, OrdSet2) -> OrdSet.
133
177
%%  Return all and only the elements of OrdSet1 which are not also in
134
178
%%  OrdSet2.
135
179
 
 
180
-spec subtract(ordset(), ordset()) -> ordset().
 
181
 
136
182
subtract([E1|Es1], [E2|_]=Set2) when E1 < E2 ->
137
183
    [E1|subtract(Es1, Set2)];
138
184
subtract([E1|_]=Set1, [E2|Es2]) when E1 > E2 ->
146
192
%%  Return 'true' when every element of OrdSet1 is also a member of
147
193
%%  OrdSet2, else 'false'.
148
194
 
 
195
-spec is_subset(ordset(), ordset()) -> bool().
 
196
 
149
197
is_subset([E1|_], [E2|_]) when E1 < E2 ->       %E1 not in Set2
150
198
    false;
151
199
is_subset([E1|_]=Set1, [E2|Es2]) when E1 > E2 ->
158
206
%% fold(Fun, Accumulator, OrdSet) -> Accumulator.
159
207
%%  Fold function Fun over all elements in OrdSet and return Accumulator.
160
208
 
 
209
-spec fold(fun((_, _) -> _), _, ordset()) -> _.
 
210
 
161
211
fold(F, Acc, Set) ->
162
212
    lists:foldl(F, Acc, Set).
163
213
 
164
214
%% filter(Fun, OrdSet) -> OrdSet.
165
215
%%  Filter OrdSet with Fun.
166
216
 
 
217
-spec filter(fun((_) -> bool()), ordset()) -> ordset().
 
218
 
167
219
filter(F, Set) ->
168
220
    lists:filter(F, Set).