~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/debugger/test/int_SUITE_data/ordsets1.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1998-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
%% Copyright (C) 1991, Ellemtel Telecommunications Systems Laboratories
 
22
%% File    : ordsets.erl
 
23
%% Author  : Robert Virding
 
24
%% Purpose : Functions for manipulating sets as ordered lists.
 
25
 
 
26
%% As yet some of these are not very efficiently written.
 
27
 
 
28
-module(ordsets1).
 
29
 
 
30
-export([new_set/0,is_set/1,set_to_list/1,list_to_set/1]).
 
31
-export([is_element/2,add_element/2,del_element/2]).
 
32
-export([union/2,union/1,intersection/2,intersection/1]).
 
33
-export([subtract/2,subset/2]).
 
34
 
 
35
%% new_set()
 
36
%%  Return a new empty ordered set.
 
37
 
 
38
new_set() ->
 
39
    [].
 
40
 
 
41
%% is_set(Set)
 
42
%%  Return 'true' if Set is an ordered set of elements, else 'false'.
 
43
 
 
44
is_set([E|Es]) ->
 
45
    is_set(Es, E);
 
46
is_set([]) ->
 
47
    true.
 
48
 
 
49
is_set([E2|Es], E1) when E1 < E2 ->
 
50
    is_set(Es, E2);
 
51
is_set([E2|Es], E1) ->
 
52
    false;
 
53
is_set([], E1) ->
 
54
    true.
 
55
 
 
56
%% set_to_list(OrdSet)
 
57
%%  Return the elements in OrdSet as a list.
 
58
 
 
59
set_to_list(S) ->
 
60
    S.
 
61
 
 
62
%% list_to_set(List)
 
63
%%  Build an ordered set from the elements in List.
 
64
 
 
65
list_to_set([E|Es]) ->
 
66
    add_element(E, list_to_set(Es));
 
67
list_to_set([]) ->
 
68
    [].
 
69
 
 
70
%% is_element(Element, OrdSet)
 
71
%%  Return 'true' if Element is an element of OrdSet, else 'false'.
 
72
 
 
73
is_element(E, [H|Es]) when E < H ->
 
74
    false;
 
75
is_element(E, [H|Es]) when E == H ->
 
76
    true;
 
77
is_element(E, [H|Es]) when E > H ->
 
78
    is_element(E, Es);
 
79
is_element(E, []) ->
 
80
    false.
 
81
 
 
82
%% add_element(Element, OrdSet)
 
83
%%  Return OrdSet with Element inserted in it.
 
84
 
 
85
add_element(E, [H|Es]) when E < H ->
 
86
    [E,H|Es];
 
87
add_element(E, [H|Es]) when E == H ->
 
88
    [H|Es];
 
89
add_element(E, [H|Es]) when E > H ->
 
90
    [H|add_element(E, Es)];
 
91
add_element(E, []) ->
 
92
    [E].
 
93
 
 
94
%% del_element(Element, OrdSet)
 
95
%%  Return OrdSet but with Element removed.
 
96
 
 
97
del_element(E, [H|Es]) when E < H ->
 
98
    [H|Es];
 
99
del_element(E, [H|Es]) when E == H ->
 
100
    Es;
 
101
del_element(E, [H|Es]) when E > H ->
 
102
    [H|del_element(E, Es)];
 
103
del_element(E, []) ->
 
104
    [].
 
105
 
 
106
%% union(Set1, Set2)
 
107
%%  Return the union of Set1 and Set2.
 
108
 
 
109
union([H1|Es1], [H2|Es2]) when H1 < H2 ->
 
110
    [H1|union(Es1, [H2|Es2])];
 
111
union([H1|Es1], [H2|Es2]) when H1 == H2 ->
 
112
    [H1|union(Es1, Es2)];
 
113
union([H1|Es1], [H2|Es2]) when H1 > H2 ->
 
114
    [H2|union([H1|Es1], Es2)];
 
115
union([], Es2) ->
 
116
    Es2;
 
117
union(Es1, []) ->
 
118
    Es1.
 
119
 
 
120
%% union(OrdSets)
 
121
%%  Return the union of the list of sets.
 
122
 
 
123
union([S1,S2|Ss]) ->
 
124
    union1(union(S1,S2), Ss);
 
125
union([S]) ->
 
126
    S;
 
127
union([]) ->
 
128
    [].
 
129
 
 
130
union1(S1, [S2|Ss]) ->
 
131
    union1(union(S1, S2), Ss);
 
132
union1(S1, []) ->
 
133
    S1.
 
134
 
 
135
%% intersection(Set1, Set2)
 
136
%%  Return the intersection of Set1 and Set2.
 
137
 
 
138
intersection([H1|Es1], [H2|Es2]) when H1 < H2 ->
 
139
    intersection(Es1, [H2|Es2]);
 
140
intersection([H1|Es1], [H2|Es2]) when H1 == H2 ->
 
141
    [H1|intersection(Es1, Es2)];
 
142
intersection([H1|Es1], [H2|Es2]) when H1 > H2 ->
 
143
    intersection([H1|Es1], Es2);
 
144
intersection([], Es2) ->
 
145
    [];
 
146
intersection(Es1, []) ->
 
147
    [].
 
148
 
 
149
%% intersection(OrdSets)
 
150
%%  Return the intersection of the list of sets.
 
151
 
 
152
intersection([S1,S2|Ss]) ->
 
153
    intersection1(intersection(S1,S2), Ss);
 
154
intersection([S]) ->
 
155
    S;
 
156
intersection([]) ->
 
157
    [].
 
158
 
 
159
intersection1(S1, [S2|Ss]) ->
 
160
    intersection1(intersection(S1, S2), Ss);
 
161
intersection1(S1, []) ->
 
162
    S1.
 
163
 
 
164
%% subtract(Set1, Set2)
 
165
%%  Return all and only the elements of Set1 which are not also in Set2.
 
166
 
 
167
subtract([H1|Es1], [H2|Es2]) when H1 < H2 ->
 
168
    [H1|subtract(Es1, [H2|Es2])];
 
169
subtract([H1|Es1], [H2|Es2]) when H1 == H2 ->
 
170
    subtract(Es1, Es2);
 
171
subtract([H1|Es1], [H2|Es2]) when H1 > H2 ->
 
172
    subtract([H1|Es1], Es2);
 
173
subtract([], Es2) ->
 
174
    [];
 
175
subtract(Es1, []) ->
 
176
    Es1.
 
177
 
 
178
%% subset(Set1, Set2)
 
179
%%  Return 'true' when every element of Set1 is also a member of Set2,
 
180
%%  else 'false'.
 
181
 
 
182
subset([H1|Es1], [H2|Es2]) when H1 < H2 ->      %H1 not in Set2
 
183
    false;
 
184
subset([H1|Es1], [H2|Es2]) when H1 == H2 ->
 
185
    subset(Es1, Es2);
 
186
subset([H1|Es1], [H2|Es2]) when H1 > H2 ->
 
187
    subset([H1|Es1], Es2);
 
188
subset([], Es2) ->
 
189
    true;
 
190
subset(Es1, []) ->
 
191
    false.