~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): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
48
48
%%-export([get_slot/2,get_bucket/2,on_bucket/3,fold_dict/3,
49
49
%%       maybe_expand/2,maybe_contract/2]).
50
50
 
51
 
%-define(seg_size, 2).
52
 
%-define(max_seg, 32).
53
 
%-define(expand_load, 2).
54
 
%-define(contract_load, 1).
 
51
%% Note: mk_seg/1 must be changed too if seg_size is changed.
55
52
-define(seg_size, 16).
56
53
-define(max_seg, 32).
57
54
-define(expand_load, 5).
58
55
-define(contract_load, 3).
 
56
-define(exp_size, (?seg_size * ?expand_load)).
 
57
-define(con_size, (?seg_size * ?contract_load)).
59
58
 
60
59
%% Define a hashtable.  The default values are the standard ones.
61
60
-record(dict,
62
 
        {size=0,                                %Number of elements
63
 
         n=?seg_size,                           %Number of active slots
64
 
         maxn=?seg_size,                        %Maximum slots
65
 
         bso=?seg_size div 2,                   %Buddy slot offset
66
 
         exp_size=?seg_size * ?expand_load,     %Size to expand at
67
 
         con_size=?seg_size * ?contract_load,   %Size to contract at
68
 
         empty,                                 %Empty segment
69
 
         segs                                   %Segments
 
61
        {size=0                 ::integer(),    % Number of elements
 
62
         n=?seg_size            ::integer(),    % Number of active slots
 
63
         maxn=?seg_size         ::integer(),    % Maximum slots
 
64
         bso=?seg_size div 2    ::integer(),    % Buddy slot offset
 
65
         exp_size=?exp_size     ::integer(),    % Size to expand at
 
66
         con_size=?con_size     ::integer(),    % Size to contract at
 
67
         empty,                                 % Empty segment
 
68
         segs                   ::tuple()       % Segments
70
69
        }).
71
70
 
72
 
-define(kv(K,V), [K|V]).                        %Key-Value pair format
73
 
%%-define(kv(K,V), {K,V}).                      %Key-Value pair format
 
71
-define(kv(K,V), [K|V]).                        % Key-Value pair format
 
72
%%-define(kv(K,V), {K,V}).                      % Key-Value pair format
74
73
 
75
74
%% new() -> Table.
76
75
 
99
98
from_list(L) ->
100
99
    lists:foldl(fun ({K,V}, D) -> store(K, V, D) end, new(), L).
101
100
 
102
 
%% size(Dictionary) -> int().
 
101
%% size(Dictionary) -> integer().
103
102
 
104
 
size(D) -> D#dict.size. 
 
103
size(#dict{size=N}) when is_integer(N), N >= 0 -> N. 
105
104
 
106
105
%% fetch(Key, Dictionary) -> Value.
107
106
 
250
249
 
251
250
update(Key, F, D0) ->
252
251
    Slot = get_slot(D0, Key),
253
 
    {D1,_Uv} = on_bucket(fun (B0) -> update_bkt(Key, F, B0) end,
254
 
                        D0, Slot),
 
252
    {D1,_Uv} = on_bucket(fun (B0) -> update_bkt(Key, F, B0) end, D0, Slot),
255
253
    D1.
256
254
 
257
255
update_bkt(Key, F, [?kv(Key,Val)|Bkt]) ->
274
272
update_bkt(Key, F, I, [Other|Bkt0]) ->
275
273
    {Bkt1,Ic} = update_bkt(Key, F, I, Bkt0),
276
274
    {[Other|Bkt1],Ic};
277
 
update_bkt(Key, _, I, []) -> {[?kv(Key,I)],1}.
 
275
update_bkt(Key, F, I, []) when is_function(F, 1) -> {[?kv(Key,I)],1}.
278
276
 
279
277
%% update_counter(Key, Incr, Dictionary) -> Dictionary.
280
278
 
281
 
update_counter(Key, Incr, D0) ->
 
279
update_counter(Key, Incr, D0) when is_integer(Incr) ->
282
280
    Slot = get_slot(D0, Key),
283
281
    {D1,Ic} = on_bucket(fun (B0) -> counter_bkt(Key, Incr, B0) end,
284
282
                        D0, Slot),
352
350
    {B1,Res} = F(B0),                           %Op on the bucket.
353
351
    {T#dict{segs=setelement(SegI, Segs, setelement(BktI, Seg, B1))},Res}.
354
352
 
355
 
%% fold_dict(Fun, Acc, Dictionary) -> Dictionary.
 
353
%% fold_dict(Fun, Acc, Dictionary) -> Acc.
356
354
%% map_dict(Fun, Dictionary) -> Dictionary.
357
355
%% filter_dict(Fun, Dictionary) -> Dictionary.
358
 
 
 
356
%%
359
357
%%  Work functions for fold, map and filter operations.  These
360
358
%%  traverse the hash structure rebuilding as necessary.  Note we
361
 
%%  could have implemented map and filter using fold but these are be
 
359
%%  could have implemented map and filter using fold but these are
362
360
%%  faster.  We hope!
363
361
 
364
362
fold_dict(F, Acc, D) ->
365
363
    Segs = D#dict.segs,
366
 
    fold_segs(F, Acc, Segs, size(Segs)).
 
364
    fold_segs(F, Acc, Segs, erlang:size(Segs)).
367
365
 
368
366
fold_segs(F, Acc, Segs, I) when I >= 1 ->
369
367
    Seg = element(I, Segs),
370
 
    fold_segs(F, fold_seg(F, Acc, Seg, size(Seg)), Segs, I-1);
371
 
fold_segs(_, Acc, _, _) -> Acc.
 
368
    fold_segs(F, fold_seg(F, Acc, Seg, erlang:size(Seg)), Segs, I-1);
 
369
fold_segs(F, Acc, _, 0) when is_function(F, 3) -> Acc.
372
370
 
373
371
fold_seg(F, Acc, Seg, I) when I >= 1 ->
374
372
    fold_seg(F, fold_bucket(F, Acc, element(I, Seg)), Seg, I-1);
375
 
fold_seg(_, Acc, _, _) -> Acc.
 
373
fold_seg(F, Acc, _, 0) when is_function(F, 3) -> Acc.
376
374
 
377
375
fold_bucket(F, Acc, [?kv(Key,Val)|Bkt]) ->
378
376
    fold_bucket(F, F(Key, Val, Acc), Bkt);
379
 
fold_bucket(_, Acc, []) -> Acc.
 
377
fold_bucket(F, Acc, []) when is_function(F, 3) -> Acc.
380
378
 
381
379
map_dict(F, D) ->
382
380
    Segs0 = tuple_to_list(D#dict.segs),
387
385
    Bkts0 = tuple_to_list(Seg),
388
386
    Bkts1 = map_bkt_list(F, Bkts0),
389
387
    [list_to_tuple(Bkts1)|map_seg_list(F, Segs)];
390
 
map_seg_list(_, []) -> [].
 
388
map_seg_list(F, []) when is_function(F, 2) -> [].
391
389
 
392
390
map_bkt_list(F, [Bkt0|Bkts]) ->
393
391
    [map_bucket(F, Bkt0)|map_bkt_list(F, Bkts)];
394
 
map_bkt_list(_, []) -> [].
 
392
map_bkt_list(F, []) when is_function(F, 2) -> [].
395
393
 
396
394
map_bucket(F, [?kv(Key,Val)|Bkt]) ->
397
395
    [?kv(Key,F(Key, Val))|map_bucket(F, Bkt)];
398
 
map_bucket(_, []) -> [].
 
396
map_bucket(F, []) when is_function(F, 2) -> [].
399
397
 
400
398
filter_dict(F, D) ->
401
399
    Segs0 = tuple_to_list(D#dict.segs),
406
404
    Bkts0 = tuple_to_list(Seg),
407
405
    {Bkts1,Fc1} = filter_bkt_list(F, Bkts0, [], Fc0),
408
406
    filter_seg_list(F, Segs, [list_to_tuple(Bkts1)|Fss], Fc1);
409
 
filter_seg_list(_, [], Fss, Fc) ->
 
407
filter_seg_list(F, [], Fss, Fc) when is_function(F, 2) ->
410
408
    {lists:reverse(Fss, []),Fc}.
411
409
 
412
410
filter_bkt_list(F, [Bkt0|Bkts], Fbs, Fc0) ->
413
411
    {Bkt1,Fc1} = filter_bucket(F, Bkt0, [], Fc0),
414
412
    filter_bkt_list(F, Bkts, [Bkt1|Fbs], Fc1);
415
 
filter_bkt_list(_, [], Fbs, Fc) ->
 
413
filter_bkt_list(F, [], Fbs, Fc) when is_function(F, 2) ->
416
414
    {lists:reverse(Fbs),Fc}.
417
415
 
418
416
filter_bucket(F, [?kv(Key,Val)=E|Bkt], Fb, Fc) ->
420
418
        true -> filter_bucket(F, Bkt, [E|Fb], Fc);
421
419
        false -> filter_bucket(F, Bkt, Fb, Fc+1)
422
420
    end;
423
 
filter_bucket(_, [], Fb, Fc) ->
 
421
filter_bucket(F, [], Fb, Fc) when is_function(F, 2) ->
424
422
    {lists:reverse(Fb),Fc}.
425
423
 
426
424
%% get_bucket_s(Segments, Slot) -> Bucket.
437
435
    Seg = setelement(BktI, element(SegI, Segs), Bkt),
438
436
    setelement(SegI, Segs, Seg).
439
437
 
440
 
maybe_expand(T0, Ic) when T0#dict.size + Ic > T0#dict.exp_size ->
 
438
%% In maybe_expand(), the variable Ic only takes the values 0 or 1,
 
439
%% but type inference is not strong enough to infer this. Thus, the
 
440
%% use of explicit pattern matching and an auxiliary function.
 
441
 
 
442
maybe_expand(T, 0) -> maybe_expand_aux(T, 0);
 
443
maybe_expand(T, 1) -> maybe_expand_aux(T, 1).
 
444
 
 
445
maybe_expand_aux(T0, Ic) when T0#dict.size + Ic > T0#dict.exp_size ->
441
446
    T = maybe_expand_segs(T0),                  %Do we need more segments.
442
447
    N = T#dict.n + 1,                           %Next slot to expand into
443
448
    Segs0 = T#dict.segs,
452
457
           exp_size=N * ?expand_load,
453
458
           con_size=N * ?contract_load,
454
459
           segs=Segs2};
455
 
maybe_expand(T, Ic) -> T#dict{size=T#dict.size + Ic}.
 
460
maybe_expand_aux(T, Ic) -> T#dict{size=T#dict.size + Ic}.
456
461
 
457
462
maybe_expand_segs(T) when T#dict.n == T#dict.maxn ->
458
463
    T#dict{maxn=2 * T#dict.maxn,
497
502
 
498
503
%% mk_seg(Size) -> Segment.
499
504
 
500
 
mk_seg(4) -> {[],[],[],[]};
501
 
mk_seg(8) -> {[],[],[],[],[],[],[],[]};
502
 
mk_seg(16) -> {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]};
503
 
mk_seg(32) ->
504
 
    {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],
505
 
     [],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]};
506
 
mk_seg(Size) -> list_to_tuple(lists:duplicate(Size, [])).
 
505
mk_seg(16) -> {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}.
507
506
 
508
507
%% expand_segs(Segs, EmptySeg) -> NewSegs.
509
508
%% contract_segs(Segs) -> NewSegs.
526
525
     Empty,Empty,Empty,Empty,Empty,Empty,Empty,Empty,
527
526
     Empty,Empty,Empty,Empty,Empty,Empty,Empty,Empty};
528
527
expand_segs(Segs, Empty) ->
529
 
    list_to_tuple(tuple_to_list(Segs) ++ lists:duplicate(size(Segs), Empty)).
 
528
    list_to_tuple(tuple_to_list(Segs) ++ lists:duplicate(erlang:size(Segs), Empty)).
530
529
 
531
530
contract_segs({B1,_}) ->
532
531
    {B1};
540
539
               _,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_}) ->
541
540
    {B1,B2,B3,B4,B5,B6,B7,B8,B9,B10,B11,B12,B13,B14,B15,B16};
542
541
contract_segs(Segs) ->
543
 
    Ss = size(Segs) div 2,
 
542
    Ss = erlang:size(Segs) div 2,
544
543
    list_to_tuple(lists:sublist(tuple_to_list(Segs), 1, Ss)).