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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_frag_old_hash.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%%
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%%
 
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: mnesia_frag_old_hash.erl,v 1.1 2008/12/17 09:53:38 mikpe Exp $
 
17
%%
 
18
%%%----------------------------------------------------------------------
 
19
%%% Purpose : Implements hashing functionality for fragmented tables
 
20
%%%----------------------------------------------------------------------
 
21
 
 
22
-module(mnesia_frag_old_hash).
 
23
-behaviour(mnesia_frag_hash).
 
24
 
 
25
%% Hashing callback functions
 
26
-export([
 
27
         init_state/2,
 
28
         add_frag/1,
 
29
         del_frag/1,
 
30
         key_to_frag_number/2,
 
31
         match_spec_to_frag_numbers/2
 
32
        ]).
 
33
 
 
34
-record(old_hash_state,
 
35
        {n_fragments,
 
36
         next_n_to_split,
 
37
         n_doubles}).
 
38
 
 
39
%% Old style. Kept for backwards compatibility.
 
40
-record(frag_hash,
 
41
        {foreign_key,
 
42
         n_fragments,
 
43
         next_n_to_split,
 
44
         n_doubles}).
 
45
 
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
 
 
48
init_state(_Tab, InitialState) when InitialState == undefined ->
 
49
    #old_hash_state{n_fragments     = 1,
 
50
                    next_n_to_split = 1,
 
51
                    n_doubles       = 0};
 
52
init_state(_Tab, FH) when record(FH, frag_hash) ->
 
53
    %% Old style. Kept for backwards compatibility.
 
54
    #old_hash_state{n_fragments     = FH#frag_hash.n_fragments,
 
55
                    next_n_to_split = FH#frag_hash.next_n_to_split,
 
56
                    n_doubles       = FH#frag_hash.n_doubles}.
 
57
 
 
58
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
59
 
 
60
add_frag(State) when record(State, old_hash_state) ->
 
61
    SplitN = State#old_hash_state.next_n_to_split,
 
62
    P = SplitN + 1,
 
63
    L = State#old_hash_state.n_doubles,
 
64
    NewN = State#old_hash_state.n_fragments + 1,
 
65
    State2 = case trunc(math:pow(2, L)) + 1 of
 
66
                 P2 when P2 == P ->
 
67
                     State#old_hash_state{n_fragments = NewN,
 
68
                                          next_n_to_split = 1,
 
69
                                          n_doubles = L + 1};
 
70
                 _ ->
 
71
                     State#old_hash_state{n_fragments = NewN,
 
72
                                          next_n_to_split = P}
 
73
             end,
 
74
    {State2, [SplitN], [NewN]}.
 
75
 
 
76
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
77
 
 
78
del_frag(State) when record(State, old_hash_state) ->
 
79
    P = State#old_hash_state.next_n_to_split - 1,
 
80
    L = State#old_hash_state.n_doubles,
 
81
    N = State#old_hash_state.n_fragments,
 
82
    if
 
83
        P < 1 ->
 
84
            L2 = L - 1,
 
85
            MergeN = trunc(math:pow(2, L2)),
 
86
            State2 = State#old_hash_state{n_fragments = N - 1,
 
87
                                          next_n_to_split = MergeN,
 
88
                                          n_doubles = L2},
 
89
            {State2, [N], [MergeN]};
 
90
        true ->
 
91
            MergeN = P,
 
92
            State2 = State#old_hash_state{n_fragments = N - 1,
 
93
                                          next_n_to_split = MergeN},
 
94
            {State2, [N], [MergeN]}
 
95
        end.
 
96
 
 
97
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
98
 
 
99
key_to_frag_number(State, Key) when record(State, old_hash_state) ->
 
100
    L = State#old_hash_state.n_doubles,
 
101
    A = erlang:hash(Key, trunc(math:pow(2, L))),
 
102
    P = State#old_hash_state.next_n_to_split,
 
103
    if
 
104
        A < P ->
 
105
            erlang:hash(Key, trunc(math:pow(2, L + 1)));
 
106
        true ->
 
107
            A
 
108
    end.
 
109
 
 
110
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
111
 
 
112
match_spec_to_frag_numbers(State, MatchSpec) when record(State, old_hash_state) ->
 
113
    case MatchSpec of
 
114
        [{HeadPat, _, _}] when tuple(HeadPat), size(HeadPat) > 2 ->
 
115
            KeyPat = element(2, HeadPat),
 
116
            case has_var(KeyPat) of
 
117
                false ->
 
118
                    [key_to_frag_number(State, KeyPat)];
 
119
                true ->
 
120
                    lists:seq(1, State#old_hash_state.n_fragments)
 
121
            end;
 
122
        _ ->
 
123
            lists:seq(1, State#old_hash_state.n_fragments)
 
124
    end.
 
125
 
 
126
has_var(Pat) ->
 
127
    mnesia:has_var(Pat).