~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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 2000-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
%% We use the dynamic hashing techniques by Per-�ke Larsson as
54
55
 
55
56
%% Define a hashtable.  The default values are the standard ones.
56
57
-record(dict,
57
 
        {size=0                 ::integer(),    % Number of elements
58
 
         n=?seg_size            ::integer(),    % Number of active slots
59
 
         maxn=?seg_size         ::integer(),    % Maximum slots
60
 
         bso=?seg_size div 2    ::integer(),    % Buddy slot offset
61
 
         exp_size=?exp_size     ::integer(),    % Size to expand at
62
 
         con_size=?con_size     ::integer(),    % Size to contract at
63
 
         empty,                                 % Empty segment
64
 
         segs                   ::tuple()       % Segments
 
58
        {size=0               :: non_neg_integer(),     % Number of elements
 
59
         n=?seg_size          :: non_neg_integer(),     % Number of active slots
 
60
         maxn=?seg_size       :: non_neg_integer(),     % Maximum slots
 
61
         bso=?seg_size div 2  :: non_neg_integer(),     % Buddy slot offset
 
62
         exp_size=?exp_size   :: non_neg_integer(),     % Size to expand at
 
63
         con_size=?con_size   :: non_neg_integer(),     % Size to contract at
 
64
         empty                :: tuple(),               % Empty segment
 
65
         segs                 :: tuple()                % Segments
65
66
        }).
 
67
%% A declaration equivalent to the following one is hard-coded in erl_types.
 
68
%% That declaration contains hard-coded information about the #dict{}
 
69
%% structure and the types of its fields.  So, please make sure that any
 
70
%% changes to its structure are also propagated to erl_types.erl.
 
71
%%
 
72
%% -opaque dict() :: #dict{}.
66
73
 
67
74
-define(kv(K,V), [K|V]).                        % Key-Value pair format
68
75
%%-define(kv(K,V), {K,V}).                      % Key-Value pair format
69
76
 
70
 
%% new() -> Table.
 
77
-spec new() -> dict().
71
78
 
72
79
new() ->
73
80
    Empty = mk_seg(?seg_size),
74
81
    #dict{empty=Empty,segs={Empty}}.
75
82
 
76
 
%% is_key(Key, Dictionary) -> bool().
 
83
-spec is_key(term(), dict()) -> bool().
77
84
 
78
85
is_key(Key, D) ->
79
86
    Slot = get_slot(D, Key),
84
91
find_key(K, [_|Bkt]) -> find_key(K, Bkt);
85
92
find_key(_, []) -> false.
86
93
 
87
 
%% to_list(Dictionary) -> [{Key,Value}].
 
94
-spec to_list(dict()) -> [{term(), term()}].
88
95
 
89
96
to_list(D) ->
90
97
    fold(fun (Key, Val, List) -> [{Key,Val}|List] end, [], D).
91
98
 
92
 
%% from_list([{Key,Value}]) -> Dictionary.
 
99
-spec from_list([{term(), term()}]) -> dict().
93
100
 
94
101
from_list(L) ->
95
102
    lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, new(), L).
96
103
 
97
 
%% size(Dictionary) -> integer().
 
104
-spec size(dict()) -> non_neg_integer().
98
105
 
99
106
size(#dict{size=N}) when is_integer(N), N >= 0 -> N. 
100
107
 
101
 
%% fetch(Key, Dictionary) -> Value.
 
108
-spec fetch(term(), dict()) -> term().
102
109
 
103
110
fetch(Key, D) ->
104
111
    Slot = get_slot(D, Key),
105
112
    Bkt = get_bucket(D, Slot),
106
 
    fetch_val(Key, Bkt).
 
113
    try fetch_val(Key, Bkt)
 
114
    catch
 
115
        badarg -> erlang:error(badarg, [Key, D])
 
116
    end.
107
117
 
108
118
fetch_val(K, [?kv(K,Val)|_]) -> Val;
109
 
fetch_val(K, [_|Bkt]) -> fetch_val(K, Bkt).
 
119
fetch_val(K, [_|Bkt]) -> fetch_val(K, Bkt);
 
120
fetch_val(_, []) -> throw(badarg).
110
121
 
111
 
%% find(Key, Dictionary) -> {ok,Value} | error.
 
122
-spec find(term(), dict()) -> {'ok', term()} | 'error'.
112
123
 
113
124
find(Key, D) ->
114
125
    Slot = get_slot(D, Key),
119
130
find_val(K, [_|Bkt]) -> find_val(K, Bkt);
120
131
find_val(_, []) -> error.
121
132
 
122
 
%% fetch_keys(Dictionary) -> [Key].
 
133
-spec fetch_keys(dict()) -> [term()].
123
134
 
124
135
fetch_keys(D) ->
125
136
    fold(fun (Key, _Val, Keys) -> [Key|Keys] end, [], D).
126
137
 
127
 
%% erase(Key, Dictionary) -> NewDictionary.
 
138
-spec erase(term(), dict()) -> dict().
128
139
%%  Erase all elements with key Key.
129
140
 
130
141
erase(Key, D0) -> 
139
150
    {[E|Bkt1],Dc};
140
151
erase_key(_, []) -> {[],0}.
141
152
 
142
 
%% store(Key, Value, Dictionary) -> Dictionary.
 
153
-spec store(term(), term(), dict()) -> dict().
143
154
 
144
155
store(Key, Val, D0) ->
145
156
    Slot = get_slot(D0, Key),
155
166
    {[Other|Bkt1],Ic};
156
167
store_bkt_val(Key, New, []) -> {[?kv(Key,New)],1}.
157
168
 
158
 
%% append(Key, Value, Dictionary) -> Dictionary.
 
169
-spec append(term(), term(), dict()) -> dict().
159
170
 
160
171
append(Key, Val, D0) ->
161
172
    Slot = get_slot(D0, Key),
171
182
    {[Other|Bkt1],Ic};
172
183
append_bkt(Key, Val, []) -> {[?kv(Key,[Val])],1}.
173
184
 
174
 
%% append_list(Key, List, Dictionary) -> Dictionary.
 
185
-spec append_list(term(), [term()], dict()) -> dict().
175
186
 
176
187
append_list(Key, L, D0) ->
177
188
    Slot = get_slot(D0, Key),
187
198
    {[Other|Bkt1],Ic};
188
199
app_list_bkt(Key, L, []) -> {[?kv(Key,L)],1}.
189
200
 
190
 
% %% first_key(Table) -> {ok,Key} | error.
191
 
% %%  Find the "first" key in a Table.
192
 
 
193
 
% first_key(T) ->
194
 
%     case next_bucket(T, 1) of
195
 
%       [?kv(K,Val)|Bkt] -> {ok,K};
196
 
%       [] -> error                             %No elements
197
 
%     end.
198
 
 
199
 
% next_bucket(T, Slot) when Slot > T#dict.n -> [];
200
 
% next_bucket(T, Slot) ->
201
 
%     case get_bucket(T, Slot) of
202
 
%       [] -> next_bucket(T, Slot+1);           %Empty bucket
203
 
%       B -> B
204
 
%     end.
205
 
 
206
 
%% next_key(Table, Key) -> {ok,NextKey} | error.
207
 
 
208
 
% next_key(T, Key) ->
209
 
%     Slot = get_slot(T, Key),
210
 
%     B = get_bucket(T, Slot),
211
 
%     %% Find a bucket with something in it.
212
 
%     Bkt = case bucket_after_key(Key, B) of
213
 
%             no_key -> exit(badarg);
214
 
%             [] -> next_bucket(T, Slot+1);
215
 
%             Rest -> Rest
216
 
%         end,
217
 
%     case Bkt of
218
 
%       [?kv(Next,Val)|_] -> {ok,Next};
219
 
%       [] -> error                             %We have reached the end!
220
 
%     end.
221
 
 
222
 
% bucket_after_key(Key, [?kv(Key,Val)|Bkt]) -> Bkt;
223
 
% bucket_after_key(Key, [Other|Bkt]) ->
224
 
%     bucket_after_key(Key, Bkt);
225
 
% bucket_after_key(Key, []) -> no_key.          %Key not found!
226
 
 
227
 
%% on_key(Fun, Key, Dictionary) -> Dictionary.
228
 
 
229
 
% on_key(F, Key, D0) ->
230
 
%     Slot = get_slot(D0, Key),
231
 
%     {D1,Dc} = on_bucket(fun (B0) -> on_key_bkt(Key, F, B0) end,
232
 
%                       D0, Slot),
233
 
%     maybe_contract(D1, Dc).
234
 
 
235
 
% on_key_bkt(Key, F, [?kv(Key,Val)|Bkt]) ->
236
 
%     case F(Val) of
237
 
%       {ok,New} -> {[?kv(Key,New)|Bkt],0}; 
238
 
%       erase -> {Bkt,1}
239
 
%     end;
240
 
% on_key_bkt(Key, F, [Other|Bkt0]) ->
241
 
%     {Bkt1,Dc} = on_key_bkt(Key, F, Bkt0),
242
 
%     {[Other|Bkt1],Dc}.
243
 
 
244
 
%% update(Key, Fun, Dictionary) -> Dictionary.
 
201
%% %% first_key(Table) -> {ok,Key} | error.
 
202
%% %%  Find the "first" key in a Table.
 
203
 
 
204
%% first_key(T) ->
 
205
%%     case next_bucket(T, 1) of
 
206
%%      [?kv(K,Val)|Bkt] -> {ok,K};
 
207
%%      [] -> error                             %No elements
 
208
%%     end.
 
209
 
 
210
%% next_bucket(T, Slot) when Slot > T#dict.n -> [];
 
211
%% next_bucket(T, Slot) ->
 
212
%%     case get_bucket(T, Slot) of
 
213
%%      [] -> next_bucket(T, Slot+1);           %Empty bucket
 
214
%%      B -> B
 
215
%%     end.
 
216
 
 
217
%% %% next_key(Table, Key) -> {ok,NextKey} | error.
 
218
 
 
219
%% next_key(T, Key) ->
 
220
%%     Slot = get_slot(T, Key),
 
221
%%     B = get_bucket(T, Slot),
 
222
%%     %% Find a bucket with something in it.
 
223
%%     Bkt = case bucket_after_key(Key, B) of
 
224
%%            no_key -> exit(badarg);
 
225
%%            [] -> next_bucket(T, Slot+1);
 
226
%%            Rest -> Rest
 
227
%%        end,
 
228
%%     case Bkt of
 
229
%%      [?kv(Next,Val)|_] -> {ok,Next};
 
230
%%      [] -> error                             %We have reached the end!
 
231
%%     end.
 
232
 
 
233
%% bucket_after_key(Key, [?kv(Key,Val)|Bkt]) -> Bkt;
 
234
%% bucket_after_key(Key, [Other|Bkt]) ->
 
235
%%     bucket_after_key(Key, Bkt);
 
236
%% bucket_after_key(Key, []) -> no_key.         %Key not found!
 
237
 
 
238
%% %% on_key(Fun, Key, Dictionary) -> Dictionary.
 
239
 
 
240
%% on_key(F, Key, D0) ->
 
241
%%     Slot = get_slot(D0, Key),
 
242
%%     {D1,Dc} = on_bucket(fun (B0) -> on_key_bkt(Key, F, B0) end,
 
243
%%                      D0, Slot),
 
244
%%     maybe_contract(D1, Dc).
 
245
 
 
246
%% on_key_bkt(Key, F, [?kv(Key,Val)|Bkt]) ->
 
247
%%     case F(Val) of
 
248
%%      {ok,New} -> {[?kv(Key,New)|Bkt],0}; 
 
249
%%      erase -> {Bkt,1}
 
250
%%     end;
 
251
%% on_key_bkt(Key, F, [Other|Bkt0]) ->
 
252
%%     {Bkt1,Dc} = on_key_bkt(Key, F, Bkt0),
 
253
%%     {[Other|Bkt1],Dc}.
 
254
 
 
255
-spec update(term(), fun((term()) -> term()), dict()) -> dict().
245
256
 
246
257
update(Key, F, D0) ->
247
258
    Slot = get_slot(D0, Key),
248
 
    {D1,_Uv} = on_bucket(fun (B0) -> update_bkt(Key, F, B0) end, D0, Slot),
249
 
    D1.
 
259
    try on_bucket(fun (B0) -> update_bkt(Key, F, B0) end, D0, Slot) of
 
260
        {D1,_Uv} -> D1
 
261
    catch
 
262
        badarg -> erlang:error(badarg, [Key, F, D0])
 
263
    end.
250
264
 
251
265
update_bkt(Key, F, [?kv(Key,Val)|Bkt]) ->
252
266
    Upd = F(Val),
253
267
    {[?kv(Key,Upd)|Bkt],Upd};
254
268
update_bkt(Key, F, [Other|Bkt0]) ->
255
269
    {Bkt1,Upd} = update_bkt(Key, F, Bkt0),
256
 
    {[Other|Bkt1],Upd}.
 
270
    {[Other|Bkt1],Upd};
 
271
update_bkt(_Key, _F, []) ->
 
272
    throw(badarg).
257
273
 
258
 
%% update(Key, Fun, Init, Dictionary) -> Dictionary.
 
274
-spec update(term(), fun((term()) -> term()), term(), dict()) -> dict().
259
275
 
260
276
update(Key, F, Init, D0) ->
261
277
    Slot = get_slot(D0, Key),
270
286
    {[Other|Bkt1],Ic};
271
287
update_bkt(Key, F, I, []) when is_function(F, 1) -> {[?kv(Key,I)],1}.
272
288
 
273
 
%% update_counter(Key, Incr, Dictionary) -> Dictionary.
 
289
-spec update_counter(term(), number(), dict()) -> dict().
274
290
 
275
291
update_counter(Key, Incr, D0) when is_number(Incr) ->
276
292
    Slot = get_slot(D0, Key),
285
301
    {[Other|Bkt1],Ic};
286
302
counter_bkt(Key, I, []) -> {[?kv(Key,I)],1}.
287
303
 
288
 
%% fold(FoldFun, Accumulator, Dictionary) -> Accumulator.
 
304
-spec fold(fun((term(), term(), term()) -> term()), term(), dict()) -> term().
289
305
%%  Fold function Fun over all "bags" in Table and return Accumulator.
290
306
 
291
307
fold(F, Acc, D) -> fold_dict(F, Acc, D).
292
308
 
293
 
%% map(MapFun, Dictionary) -> Dictionary.
 
309
-spec map(fun((term(), term()) -> term()), dict()) -> dict().
294
310
 
295
311
map(F, D) -> map_dict(F, D).
296
312
 
297
 
%% filter(FilterFun, Dictionary) -> Dictionary.
 
313
-spec filter(fun((term(), term()) -> bool()), dict()) -> dict().
298
314
 
299
315
filter(F, D) -> filter_dict(F, D).
300
316
 
301
 
%% merge(MergeFun, Dictionary, Dictionary) -> Dictionary.
 
317
-spec merge(fun((term(), term(), term()) -> term()), dict(), dict()) -> dict().
302
318
 
303
319
merge(F, D1, D2) when D1#dict.size < D2#dict.size ->
304
320
    fold_dict(fun (K, V1, D) ->