~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_frag_hash.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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_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
%header_doc_include
 
23
-module(mnesia_frag_hash).
 
24
-behaviour(mnesia_frag_hash).
 
25
 
 
26
%% Fragmented Table Hashing callback functions
 
27
-export([
 
28
         init_state/2,
 
29
         add_frag/1,
 
30
         del_frag/1,
 
31
         key_to_frag_number/2,
 
32
         match_spec_to_frag_numbers/2
 
33
        ]).
 
34
 
 
35
%header_doc_include
 
36
 
 
37
%impl_doc_include
 
38
-record(hash_state, {n_fragments, next_n_to_split, n_doubles}).
 
39
 
 
40
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
41
 
 
42
init_state(_Tab, State) when State == undefined ->
 
43
    #hash_state{n_fragments = 1,
 
44
                next_n_to_split = 1,
 
45
                n_doubles = 0}.
 
46
 
 
47
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
48
 
 
49
add_frag(State) when record(State, hash_state) ->
 
50
    SplitN = State#hash_state.next_n_to_split,
 
51
    P = SplitN + 1,
 
52
    L = State#hash_state.n_doubles,
 
53
    NewN = State#hash_state.n_fragments + 1,
 
54
    State2 = case trunc(math:pow(2, L)) + 1 of
 
55
                 P2 when P2 == P ->
 
56
                     State#hash_state{n_fragments = NewN,
 
57
                                      n_doubles = L + 1,
 
58
                                      next_n_to_split = 1};
 
59
                 _ ->
 
60
                     State#hash_state{n_fragments = NewN,
 
61
                                      next_n_to_split = P}
 
62
             end,
 
63
    {State2, [SplitN], [NewN]}.
 
64
 
 
65
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
66
 
 
67
del_frag(State) when record(State, hash_state) ->
 
68
    P = State#hash_state.next_n_to_split - 1,
 
69
    L = State#hash_state.n_doubles,
 
70
    N = State#hash_state.n_fragments,
 
71
    if
 
72
        P < 1 ->
 
73
            L2 = L - 1,
 
74
            MergeN = trunc(math:pow(2, L2)),
 
75
            State2 = State#hash_state{n_fragments = N - 1,
 
76
                                      next_n_to_split = MergeN,
 
77
                                      n_doubles = L2},
 
78
            {State2, [N], [MergeN]};
 
79
        true ->
 
80
            MergeN = P,
 
81
            State2 = State#hash_state{n_fragments = N - 1,
 
82
                                      next_n_to_split = MergeN},
 
83
            {State2, [N], [MergeN]}
 
84
        end.
 
85
 
 
86
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
87
 
 
88
key_to_frag_number(State, Key) when record(State, hash_state) ->
 
89
    L = State#hash_state.n_doubles,
 
90
    A = erlang:phash(Key, trunc(math:pow(2, L))),
 
91
    P = State#hash_state.next_n_to_split,
 
92
    if
 
93
        A < P ->
 
94
            erlang:phash(Key, trunc(math:pow(2, L + 1)));
 
95
        true ->
 
96
            A
 
97
    end.
 
98
 
 
99
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
100
 
 
101
match_spec_to_frag_numbers(State, MatchSpec) when record(State, hash_state) ->
 
102
    case MatchSpec of
 
103
        [{HeadPat, _, _}] when tuple(HeadPat), size(HeadPat) > 2 ->
 
104
            KeyPat = element(2, HeadPat),
 
105
            case has_var(KeyPat) of
 
106
                false ->
 
107
                    [key_to_frag_number(State, KeyPat)];
 
108
                true ->
 
109
                    lists:seq(1, State#hash_state.n_fragments)
 
110
            end;
 
111
        _ -> 
 
112
            lists:seq(1, State#hash_state.n_fragments)
 
113
    end.
 
114
 
 
115
%impl_doc_include
 
116
 
 
117
has_var(Pat) ->
 
118
    mnesia:has_var(Pat).