diff options
author | Hans Bolinder <[email protected]> | 2014-02-03 10:27:39 +0100 |
---|---|---|
committer | Hans Bolinder <[email protected]> | 2014-02-23 15:01:29 +0100 |
commit | b66e75c285cba469c5225f3394da149456d17d16 (patch) | |
tree | 3b11b80782cff70e478e8f11017bfc26745843cd /lib/stdlib/src/sets.erl | |
parent | 85a5aca047ea4c3dcdeb1e47cdf523a48140bf18 (diff) | |
download | otp-b66e75c285cba469c5225f3394da149456d17d16.tar.gz otp-b66e75c285cba469c5225f3394da149456d17d16.tar.bz2 otp-b66e75c285cba469c5225f3394da149456d17d16.zip |
Deprecate pre-defined built-in types
The types array(), dict(), digraph(), gb_set(), gb_tree(), queue(),
set(), and tid() have been deprecated. They will be removed in OTP 18.0.
Instead the types array:array(), dict:dict(), digraph:graph(),
gb_set:set(), gb_tree:tree(), queue:queue(), sets:set(), and ets:tid()
can be used. (Note: it has always been necessary to use ets:tid().)
It is allowed in OTP 17.0 to locally re-define the types array(), dict(),
and so on.
New types array:array/1, dict:dict/2, gb_sets:set/1, gb_trees:tree/2,
queue:queue/1, and sets:set/1 have been added.
Diffstat (limited to 'lib/stdlib/src/sets.erl')
-rw-r--r-- | lib/stdlib/src/sets.erl | 114 |
1 files changed, 56 insertions, 58 deletions
diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index ebf011a7d9..be4b600f25 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2013. All Rights Reserved. +%% Copyright Ericsson AB 2000-2014. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -43,6 +43,8 @@ -export([subtract/2,is_subset/2]). -export([fold/3,filter/2]). +-export_type([set/0, set/1]). + %% Note: mk_seg/1 must be changed too if seg_size is changed. -define(seg_size, 16). -define(max_seg, 32). @@ -54,7 +56,8 @@ %%------------------------------------------------------------------------------ -type seg() :: tuple(). --type segs() :: tuple(). +-type segs(E) :: tuple() + | E. % dummy %% Define a hash set. The default values are the standard ones. -record(set, @@ -65,14 +68,12 @@ exp_size=?exp_size :: non_neg_integer(), % Size to expand at con_size=?con_size :: non_neg_integer(), % Size to contract at empty :: seg(), % Empty segment - segs :: segs() % Segments + segs :: segs(_) % Segments }). -%% A declaration equivalent to the following one is hard-coded in erl_types. -%% That declaration contains hard-coded information about the #set{} -%% record and the types of its fields. So, please make sure that any -%% changes to its structure are also propagated to erl_types.erl. -%% -%% -opaque set() :: #set{}. + +-opaque set() :: set(_). + +-opaque set(Element) :: #set{segs :: segs(Element)}. %%------------------------------------------------------------------------------ @@ -98,24 +99,23 @@ size(S) -> S#set.size. %% to_list(Set) -> [Elem]. %% Return the elements in Set as a list. -spec to_list(Set) -> List when - Set :: set(), - List :: [term()]. + Set :: set(Element), + List :: [Element]. to_list(S) -> fold(fun (Elem, List) -> [Elem|List] end, [], S). %% from_list([Elem]) -> Set. %% Build a set from the elements in List. -spec from_list(List) -> Set when - List :: [term()], - Set :: set(). + List :: [Element], + Set :: set(Element). from_list(L) -> lists:foldl(fun (E, S) -> add_element(E, S) end, new(), L). %% is_element(Element, Set) -> boolean(). %% Return 'true' if Element is an element of Set, else 'false'. -spec is_element(Element, Set) -> boolean() when - Element :: term(), - Set :: set(). + Set :: set(Element). is_element(E, S) -> Slot = get_slot(S, E), Bkt = get_bucket(S, Slot), @@ -124,9 +124,8 @@ is_element(E, S) -> %% add_element(Element, Set) -> Set. %% Return Set with Element inserted in it. -spec add_element(Element, Set1) -> Set2 when - Element :: term(), - Set1 :: set(), - Set2 :: set(). + Set1 :: set(Element), + Set2 :: set(Element). add_element(E, S0) -> Slot = get_slot(S0, E), {S1,Ic} = on_bucket(fun (B0) -> add_bkt_el(E, B0, B0) end, S0, Slot), @@ -141,9 +140,8 @@ add_bkt_el(E, [], Bkt) -> {[E|Bkt],1}. %% del_element(Element, Set) -> Set. %% Return Set but with Element removed. -spec del_element(Element, Set1) -> Set2 when - Element :: term(), - Set1 :: set(), - Set2 :: set(). + Set1 :: set(Element), + Set2 :: set(Element). del_element(E, S0) -> Slot = get_slot(S0, E), {S1,Dc} = on_bucket(fun (B0) -> del_bkt_el(E, B0) end, S0, Slot), @@ -159,9 +157,9 @@ del_bkt_el(_, []) -> {[],0}. %% union(Set1, Set2) -> Set %% Return the union of Set1 and Set2. -spec union(Set1, Set2) -> Set3 when - Set1 :: set(), - Set2 :: set(), - Set3 :: set(). + Set1 :: set(Element), + Set2 :: set(Element), + Set3 :: set(Element). union(S1, S2) when S1#set.size < S2#set.size -> fold(fun (E, S) -> add_element(E, S) end, S2, S1); union(S1, S2) -> @@ -170,14 +168,14 @@ union(S1, S2) -> %% union([Set]) -> Set %% Return the union of the list of sets. -spec union(SetList) -> Set when - SetList :: [set()], - Set :: set(). + SetList :: [set(Element)], + Set :: set(Element). union([S1,S2|Ss]) -> union1(union(S1, S2), Ss); union([S]) -> S; union([]) -> new(). --spec union1(set(), [set()]) -> set(). +-spec union1(set(E), [set(E)]) -> set(E). union1(S1, [S2|Ss]) -> union1(union(S1, S2), Ss); union1(S1, []) -> S1. @@ -185,9 +183,9 @@ union1(S1, []) -> S1. %% intersection(Set1, Set2) -> Set. %% Return the intersection of Set1 and Set2. -spec intersection(Set1, Set2) -> Set3 when - Set1 :: set(), - Set2 :: set(), - Set3 :: set(). + Set1 :: set(Element), + Set2 :: set(Element), + Set3 :: set(Element). intersection(S1, S2) when S1#set.size < S2#set.size -> filter(fun (E) -> is_element(E, S2) end, S1); intersection(S1, S2) -> @@ -196,13 +194,13 @@ intersection(S1, S2) -> %% intersection([Set]) -> Set. %% Return the intersection of the list of sets. -spec intersection(SetList) -> Set when - SetList :: [set(),...], - Set :: set(). + SetList :: [set(Element),...], + Set :: set(Element). intersection([S1,S2|Ss]) -> intersection1(intersection(S1, S2), Ss); intersection([S]) -> S. --spec intersection1(set(), [set()]) -> set(). +-spec intersection1(set(E), [set(E)]) -> set(E). intersection1(S1, [S2|Ss]) -> intersection1(intersection(S1, S2), Ss); intersection1(S1, []) -> S1. @@ -210,8 +208,8 @@ intersection1(S1, []) -> S1. %% is_disjoint(Set1, Set2) -> boolean(). %% Check whether Set1 and Set2 are disjoint. -spec is_disjoint(Set1, Set2) -> boolean() when - Set1 :: set(), - Set2 :: set(). + Set1 :: set(Element), + Set2 :: set(Element). is_disjoint(S1, S2) when S1#set.size < S2#set.size -> fold(fun (_, false) -> false; (E, true) -> not is_element(E, S2) @@ -225,9 +223,9 @@ is_disjoint(S1, S2) -> %% Return all and only the elements of Set1 which are not also in %% Set2. -spec subtract(Set1, Set2) -> Set3 when - Set1 :: set(), - Set2 :: set(), - Set3 :: set(). + Set1 :: set(Element), + Set2 :: set(Element), + Set3 :: set(Element). subtract(S1, S2) -> filter(fun (E) -> not is_element(E, S2) end, S1). @@ -235,34 +233,34 @@ subtract(S1, S2) -> %% Return 'true' when every element of Set1 is also a member of %% Set2, else 'false'. -spec is_subset(Set1, Set2) -> boolean() when - Set1 :: set(), - Set2 :: set(). + Set1 :: set(Element), + Set2 :: set(Element). is_subset(S1, S2) -> fold(fun (E, Sub) -> Sub andalso is_element(E, S2) end, true, S1). %% fold(Fun, Accumulator, Set) -> Accumulator. %% Fold function Fun over all elements in Set and return Accumulator. -spec fold(Function, Acc0, Set) -> Acc1 when - Function :: fun((E :: term(),AccIn) -> AccOut), - Set :: set(), - Acc0 :: T, - Acc1 :: T, - AccIn :: T, - AccOut :: T. + Function :: fun((Element, AccIn) -> AccOut), + Set :: set(Element), + Acc0 :: Acc, + Acc1 :: Acc, + AccIn :: Acc, + AccOut :: Acc. fold(F, Acc, D) -> fold_set(F, Acc, D). %% filter(Fun, Set) -> Set. %% Filter Set with Fun. -spec filter(Pred, Set1) -> Set2 when - Pred :: fun((E :: term()) -> boolean()), - Set1 :: set(), - Set2 :: set(). + Pred :: fun((Element) -> boolean()), + Set1 :: set(Element), + Set2 :: set(Element). filter(F, D) -> filter_set(F, D). %% get_slot(Hashdb, Key) -> Slot. %% Get the slot. First hash on the new range, if we hit a bucket %% which has not been split use the unsplit buddy bucket. --spec get_slot(set(), term()) -> non_neg_integer(). +-spec get_slot(set(E), E) -> non_neg_integer(). get_slot(T, Key) -> H = erlang:phash(Key, T#set.maxn), if @@ -276,8 +274,8 @@ get_bucket(T, Slot) -> get_bucket_s(T#set.segs, Slot). %% on_bucket(Fun, Hashdb, Slot) -> {NewHashDb,Result}. %% Apply Fun to the bucket in Slot and replace the returned bucket. --spec on_bucket(fun((_) -> {[_], 0 | 1}), set(), non_neg_integer()) -> - {set(), 0 | 1}. +-spec on_bucket(fun((_) -> {[_], 0 | 1}), set(E), non_neg_integer()) -> + {set(E), 0 | 1}. on_bucket(F, T, Slot) -> SegI = ((Slot-1) div ?seg_size) + 1, BktI = ((Slot-1) rem ?seg_size) + 1, @@ -351,7 +349,7 @@ put_bucket_s(Segs, Slot, Bkt) -> Seg = setelement(BktI, element(SegI, Segs), Bkt), setelement(SegI, Segs, Seg). --spec maybe_expand(set(), 0 | 1) -> set(). +-spec maybe_expand(set(E), 0 | 1) -> set(E). maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size -> T = maybe_expand_segs(T0), %Do we need more segments. N = T#set.n + 1, %Next slot to expand into @@ -369,14 +367,14 @@ maybe_expand(T0, Ic) when T0#set.size + Ic > T0#set.exp_size -> segs = Segs2}; maybe_expand(T, Ic) -> T#set{size = T#set.size + Ic}. --spec maybe_expand_segs(set()) -> set(). +-spec maybe_expand_segs(set(E)) -> set(E). maybe_expand_segs(T) when T#set.n =:= T#set.maxn -> T#set{maxn = 2 * T#set.maxn, bso = 2 * T#set.bso, segs = expand_segs(T#set.segs, T#set.empty)}; maybe_expand_segs(T) -> T. --spec maybe_contract(set(), non_neg_integer()) -> set(). +-spec maybe_contract(set(E), non_neg_integer()) -> set(E). maybe_contract(T, Dc) when T#set.size - Dc < T#set.con_size, T#set.n > ?seg_size -> N = T#set.n, @@ -395,7 +393,7 @@ maybe_contract(T, Dc) when T#set.size - Dc < T#set.con_size, segs = Segs2}); maybe_contract(T, Dc) -> T#set{size = T#set.size - Dc}. --spec maybe_contract_segs(set()) -> set(). +-spec maybe_contract_segs(set(E)) -> set(E). maybe_contract_segs(T) when T#set.n =:= T#set.bso -> T#set{maxn = T#set.maxn div 2, bso = T#set.bso div 2, @@ -422,7 +420,7 @@ mk_seg(16) -> {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}. %% of segments. We special case the powers of 2 upto 32, this should %% catch most case. N.B. the last element in the segments tuple is %% an extra element containing a default empty segment. --spec expand_segs(segs(), seg()) -> segs(). +-spec expand_segs(segs(E), seg()) -> segs(E). expand_segs({B1}, Empty) -> {B1,Empty}; expand_segs({B1,B2}, Empty) -> @@ -440,7 +438,7 @@ expand_segs(Segs, Empty) -> list_to_tuple(tuple_to_list(Segs) ++ lists:duplicate(tuple_size(Segs), Empty)). --spec contract_segs(segs()) -> segs(). +-spec contract_segs(segs(E)) -> segs(E). contract_segs({B1,_}) -> {B1}; contract_segs({B1,B2,_,_}) -> |