~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_frag_hash_test.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
-module(mnesia_frag_hash_test).
 
2
 
 
3
-export([test/0]).
 
4
 
 
5
-define(NUM_FRAGS, 20).
 
6
-define(NUM_KEYS, 10000).
 
7
 
 
8
-record(hash_state,
 
9
        {n_fragments,
 
10
         next_n_to_split,
 
11
         n_doubles,
 
12
         function}).
 
13
 
 
14
% OLD mnesia_frag_hash:key_to_frag_number/2.
 
15
old_key_to_frag_number(#hash_state{function = phash, next_n_to_split = SplitN, n_doubles = L}, Key) ->
 
16
    P = SplitN,
 
17
    A = erlang:phash(Key, power2(L)),
 
18
    if
 
19
        A < P ->
 
20
            erlang:phash(Key, power2(L + 1));
 
21
        true ->
 
22
            A
 
23
    end;
 
24
old_key_to_frag_number(#hash_state{function = phash2, next_n_to_split = SplitN, n_doubles = L}, Key) ->
 
25
    P = SplitN,
 
26
    A = erlang:phash2(Key, power2(L)) + 1,
 
27
    if
 
28
        A < P ->
 
29
            erlang:phash2(Key, power2(L + 1)) + 1;
 
30
        true ->
 
31
            A
 
32
    end;
 
33
old_key_to_frag_number(OldState, Key) ->
 
34
    State = convert_old_state(OldState),
 
35
    old_key_to_frag_number(State, Key).
 
36
 
 
37
 
 
38
% NEW mnesia_frag_hash:key_to_frag_number/2.
 
39
new_key_to_frag_number(#hash_state{function = phash, n_fragments = N, n_doubles = L}, Key) ->
 
40
    A = erlang:phash(Key, power2(L + 1)),
 
41
    if
 
42
        A > N ->
 
43
            A - power2(L);
 
44
        true ->
 
45
            A
 
46
    end;
 
47
new_key_to_frag_number(#hash_state{function = phash2, n_fragments = N, n_doubles = L}, Key) ->
 
48
    A = erlang:phash2(Key, power2(L + 1)) + 1,
 
49
    if
 
50
        A > N ->
 
51
            A - power2(L);
 
52
        true ->
 
53
            A
 
54
    end;
 
55
new_key_to_frag_number(OldState, Key) ->
 
56
    State = convert_old_state(OldState),
 
57
    new_key_to_frag_number(State, Key).
 
58
 
 
59
 
 
60
% Helpers for key_to_frag_number functions.
 
61
 
 
62
power2(Y) ->
 
63
    1 bsl Y. % trunc(math:pow(2, Y)).
 
64
 
 
65
convert_old_state({hash_state, N, P, L}) ->
 
66
    #hash_state{n_fragments     = N,
 
67
                next_n_to_split = P,
 
68
                n_doubles       = L,
 
69
                function        = phash}.
 
70
 
 
71
 
 
72
test() ->
 
73
    test2(mnesia_frag_hash:init_state(undefined, undefined)), % phash2
 
74
    test2({hash_state, 1, 1, 0}). % phash
 
75
 
 
76
test2(I) ->
 
77
    test_keys(I),
 
78
    lists:foldl(
 
79
        fun(_, S) -> test_frag(S) end,
 
80
        I, lists:seq(1, ?NUM_FRAGS)),
 
81
    ok.
 
82
 
 
83
test_frag(State) ->
 
84
    {State2,_,_} = mnesia_frag_hash:add_frag(State),
 
85
    test_keys(State2),
 
86
    State2.
 
87
 
 
88
test_keys(State) ->
 
89
    [test_key(State, Key) || Key <- lists:seq(1, ?NUM_KEYS)].
 
90
 
 
91
test_key(State, Key) ->
 
92
    Old = old_key_to_frag_number(State, Key),
 
93
    New = new_key_to_frag_number(State, Key),
 
94
    Old = New.