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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/ordsets.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
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
26
26
-export([subtract/2,is_subset/2]).
27
27
-export([fold/3,filter/2]).
28
28
 
 
29
-export_type([ordset/1]).
 
30
 
29
31
-type ordset(T) :: [T].
30
32
 
31
33
%% new() -> Set.
32
34
%%  Return a new empty ordered set.
33
35
 
34
 
-spec new() -> ordset(term()).
 
36
-spec new() -> [].
35
37
 
36
38
new() -> [].
37
39
 
84
86
%% add_element(Element, OrdSet) -> OrdSet.
85
87
%%  Return OrdSet with Element inserted in it.
86
88
 
87
 
-spec add_element(term(), ordset(_)) -> ordset(_).
 
89
-spec add_element(E, ordset(T)) -> [T | E,...].
88
90
 
89
91
add_element(E, [H|Es]) when E > H -> [H|add_element(E, Es)];
90
92
add_element(E, [H|_]=Set) when E < H -> [E|Set];
94
96
%% del_element(Element, OrdSet) -> OrdSet.
95
97
%%  Return OrdSet but with Element removed.
96
98
 
97
 
-spec del_element(term(), ordset(_)) -> ordset(_).
 
99
-spec del_element(term(), ordset(T)) -> ordset(T).
98
100
 
99
101
del_element(E, [H|Es]) when E > H -> [H|del_element(E, Es)];
100
102
del_element(E, [H|_]=Set) when E < H -> Set;
104
106
%% union(OrdSet1, OrdSet2) -> OrdSet
105
107
%%  Return the union of OrdSet1 and OrdSet2.
106
108
 
107
 
-spec union(ordset(_), ordset(_)) -> ordset(_).
 
109
-spec union(ordset(T1), ordset(T2)) -> ordset(T1 | T2).
108
110
 
109
111
union([E1|Es1], [E2|_]=Set2) when E1 < E2 ->
110
112
    [E1|union(Es1, Set2)];
118
120
%% union([OrdSet]) -> OrdSet
119
121
%%  Return the union of the list of ordered sets.
120
122
 
121
 
-spec union([ordset(_)]) -> ordset(_).
 
123
-spec union([ordset(T)]) -> ordset(T).
122
124
 
123
125
union([S1,S2|Ss]) ->
124
126
    union1(union(S1, S2), Ss);
147
149
%% intersection([OrdSet]) -> OrdSet.
148
150
%%  Return the intersection of the list of ordered sets.
149
151
 
150
 
-spec intersection([ordset(_)]) -> ordset(_).
 
152
-spec intersection([ordset(_),...]) -> ordset(_).
151
153
 
152
154
intersection([S1,S2|Ss]) ->
153
155
    intersection1(intersection(S1, S2), Ss);
206
208
%% fold(Fun, Accumulator, OrdSet) -> Accumulator.
207
209
%%  Fold function Fun over all elements in OrdSet and return Accumulator.
208
210
 
209
 
-spec fold(fun((_, _) -> _), _, ordset(_)) -> _.
 
211
-spec fold(fun((T, term()) -> term()), term(), ordset(T)) -> term().
210
212
 
211
213
fold(F, Acc, Set) ->
212
214
    lists:foldl(F, Acc, Set).
214
216
%% filter(Fun, OrdSet) -> OrdSet.
215
217
%%  Filter OrdSet with Fun.
216
218
 
217
 
-spec filter(fun((_) -> boolean()), ordset(_)) -> ordset(_).
 
219
-spec filter(fun((T) -> boolean()), ordset(T)) -> ordset(T).
218
220
 
219
221
filter(F, Set) ->
220
222
    lists:filter(F, Set).