~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to erts/emulator/beam/safe_hash.c

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

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 2008, Ericsson Utvecklings
 
14
 * AB. All Rights Reserved.''
 
15
 * 
 
16
 *     $Id$
 
17
 */
 
18
/*
 
19
** General thread safe hash table. Simular interface as hash.h
 
20
**
 
21
** Author: Sverker Eriksson
 
22
*/
 
23
#ifdef HAVE_CONFIG_H
 
24
#  include "config.h"
 
25
#endif
 
26
 
 
27
#include "safe_hash.h"
 
28
 
 
29
/* Currently only used by erl_check_io on Windows */
 
30
#ifndef ERTS_SYS_CONTINOUS_FD_NUMBERS
 
31
 
 
32
 
 
33
static ERTS_INLINE void set_size(SafeHash* h, int size)
 
34
{
 
35
    ASSERT(size % SAFE_HASH_LOCK_CNT == 0);
 
36
    /* This important property allows us to lock the right mutex
 
37
    ** without reading the table size (that can change without the lock) */
 
38
 
 
39
    h->size_mask = size - 1;
 
40
    ASSERT((size & h->size_mask) == 0);
 
41
    /* An even power of 2 is just for fast bit masking */
 
42
 
 
43
    h->grow_limit = size; /* grow table at 100% load */
 
44
}
 
45
 
 
46
static ERTS_INLINE int align_up_pow2(int val)
 
47
{
 
48
    int x = val & (val-1);
 
49
    if (x==0) return val ? val : 1;
 
50
    do {
 
51
        val = x;
 
52
        x &= x - 1; 
 
53
    }while (x);
 
54
    return val << 1;
 
55
}
 
56
 
 
57
/*
 
58
** Rehash all objects
 
59
*/
 
60
static void rehash(SafeHash* h, int grow_limit)
 
61
{
 
62
    if (erts_smp_atomic_xchg(&h->is_rehashing, 1) != 0) {        
 
63
        return; /* already in progress */
 
64
    }
 
65
    if (h->grow_limit == grow_limit) {
 
66
        int i, size, bytes;
 
67
        SafeHashBucket** new_tab;
 
68
        SafeHashBucket** old_tab = h->tab;
 
69
        int old_size = h->size_mask + 1;
 
70
 
 
71
        size = old_size * 2; /* double table size */
 
72
        bytes = size * sizeof(SafeHashBucket*);
 
73
        new_tab = (SafeHashBucket **) erts_alloc(h->type, bytes);
 
74
        sys_memzero(new_tab, bytes);
 
75
 
 
76
        for (i=0; i<SAFE_HASH_LOCK_CNT; i++) { /* stop all traffic */
 
77
            erts_smp_mtx_lock(&h->lock_vec[i].mtx);
 
78
        }
 
79
 
 
80
        h->tab = new_tab;
 
81
        set_size(h, size);
 
82
 
 
83
        for (i = 0; i < old_size; i++) {
 
84
            SafeHashBucket* b = old_tab[i];
 
85
            while (b != NULL) {
 
86
                SafeHashBucket* b_next = b->next;
 
87
                int ix = b->hvalue & h->size_mask;
 
88
                b->next = new_tab[ix];
 
89
                new_tab[ix] = b;
 
90
                b = b_next;
 
91
            }
 
92
        }
 
93
 
 
94
        for (i=0; i<SAFE_HASH_LOCK_CNT; i++) {
 
95
            erts_smp_mtx_unlock(&h->lock_vec[i].mtx);
 
96
        }
 
97
        erts_free(h->type, (void *) old_tab);
 
98
    }
 
99
    /*else already done */
 
100
    erts_smp_atomic_set(&h->is_rehashing, 0);
 
101
}
 
102
 
 
103
 
 
104
/*
 
105
** Get info about hash
 
106
*/
 
107
void safe_hash_get_info(SafeHashInfo *hi, SafeHash *h)
 
108
{
 
109
    int size;
 
110
    int i, lock_ix;
 
111
    int max_depth = 0;
 
112
    int objects = 0;
 
113
 
 
114
    for (lock_ix=0; lock_ix<SAFE_HASH_LOCK_CNT; lock_ix++) {
 
115
        erts_smp_mtx_lock(&h->lock_vec[lock_ix].mtx); 
 
116
        size = h->size_mask + 1;
 
117
        for (i = lock_ix; i < size; i += SAFE_HASH_LOCK_CNT) {
 
118
            int depth = 0;
 
119
            SafeHashBucket* b = h->tab[i];
 
120
            while (b != NULL) {
 
121
                objects++;
 
122
                depth++;
 
123
                b = b->next;
 
124
            }
 
125
            if (depth > max_depth)
 
126
                max_depth = depth;
 
127
        }
 
128
        erts_smp_mtx_unlock(&h->lock_vec[lock_ix].mtx); 
 
129
    }
 
130
 
 
131
    hi->name  = h->name;
 
132
    hi->size  = size;
 
133
    hi->objs  = objects;
 
134
    hi->depth = max_depth;
 
135
}
 
136
 
 
137
/*
 
138
** Returns size of table in bytes. Stored objects not included.
 
139
**/
 
140
int safe_hash_table_sz(SafeHash *h)
 
141
{
 
142
  int i, size;
 
143
  for(i=0; h->name[i]; i++);
 
144
  i++;
 
145
  erts_smp_mtx_lock(&h->lock_vec[0].mtx); /* any lock will do to read size */
 
146
  size = h->size_mask + 1;
 
147
  erts_smp_mtx_unlock(&h->lock_vec[0].mtx);
 
148
  return sizeof(SafeHash) + size*sizeof(SafeHashBucket*) + i;
 
149
}
 
150
 
 
151
/*
 
152
** Init a pre allocated or static hash structure
 
153
** and allocate buckets. NOT SAFE
 
154
*/
 
155
SafeHash* safe_hash_init(ErtsAlcType_t type, SafeHash* h, char* name, int size, SafeHashFunctions fun)
 
156
{
 
157
    int i, bytes;
 
158
 
 
159
    size = align_up_pow2(size);
 
160
    bytes = size * sizeof(SafeHashBucket*);
 
161
    h->type = type;
 
162
    h->tab = (SafeHashBucket**) erts_alloc(h->type, bytes);
 
163
    sys_memzero(h->tab, bytes);
 
164
    h->name = name;
 
165
    h->fun = fun;
 
166
    set_size(h,size);
 
167
    erts_smp_atomic_init(&h->is_rehashing, 0);
 
168
    erts_smp_atomic_init(&h->nitems, 0);
 
169
    for (i=0; i<SAFE_HASH_LOCK_CNT; i++) {
 
170
        erts_smp_mtx_init(&h->lock_vec[i].mtx,"safe_hash");
 
171
    }
 
172
    return h;
 
173
}
 
174
 
 
175
 
 
176
/*
 
177
** Find an object in the hash table
 
178
*/
 
179
void* safe_hash_get(SafeHash* h, void* tmpl)
 
180
{
 
181
    SafeHashValue hval = h->fun.hash(tmpl);
 
182
    SafeHashBucket* b;
 
183
    erts_smp_mtx_t* lock = &h->lock_vec[hval % SAFE_HASH_LOCK_CNT].mtx;
 
184
    erts_smp_mtx_lock(lock);
 
185
    b = h->tab[hval & h->size_mask];
 
186
        
 
187
    while(b != NULL) {
 
188
        if ((b->hvalue == hval) && (h->fun.cmp(tmpl, (void*)b) == 0))
 
189
            break;
 
190
        b = b->next;
 
191
    }
 
192
    erts_smp_mtx_unlock(lock);
 
193
    return (void*) b;
 
194
}
 
195
 
 
196
/*
 
197
** Find or insert an object in the hash table
 
198
*/
 
199
void* safe_hash_put(SafeHash* h, void* tmpl)
 
200
{
 
201
    int grow_limit;
 
202
    SafeHashValue hval = h->fun.hash(tmpl);
 
203
    SafeHashBucket* b;
 
204
    SafeHashBucket** head;
 
205
    erts_smp_mtx_t* lock = &h->lock_vec[hval % SAFE_HASH_LOCK_CNT].mtx;
 
206
    erts_smp_mtx_lock(lock);
 
207
    head = &h->tab[hval & h->size_mask];
 
208
    b = *head;
 
209
    while(b != NULL) {
 
210
        if ((b->hvalue == hval) && (h->fun.cmp(tmpl, (void*)b) == 0)) {
 
211
            erts_smp_mtx_unlock(lock);
 
212
            return b;
 
213
        }
 
214
        b = b->next;
 
215
    }
 
216
 
 
217
    b = (SafeHashBucket*) h->fun.alloc(tmpl);
 
218
    b->hvalue = hval;
 
219
    b->next = *head;
 
220
    *head = b;
 
221
    grow_limit = h->grow_limit;
 
222
    erts_smp_mtx_unlock(lock);
 
223
    if (erts_smp_atomic_inctest(&h->nitems) > grow_limit) {
 
224
        rehash(h, grow_limit);
 
225
    }
 
226
    return (void*) b;
 
227
}
 
228
 
 
229
/*
 
230
** Erase hash entry return template if erased
 
231
** return 0 if not erased
 
232
*/
 
233
void* safe_hash_erase(SafeHash* h, void* tmpl)
 
234
{
 
235
    SafeHashValue hval = h->fun.hash(tmpl);
 
236
    SafeHashBucket* b;
 
237
    SafeHashBucket** prevp;
 
238
    erts_smp_mtx_t* lock = &h->lock_vec[hval % SAFE_HASH_LOCK_CNT].mtx;
 
239
    erts_smp_mtx_lock(lock);
 
240
    prevp = &h->tab[hval & h->size_mask];
 
241
    b = *prevp;
 
242
    while(b != NULL) {
 
243
        if ((b->hvalue == hval) && (h->fun.cmp(tmpl, (void*)b) == 0)) {
 
244
            *prevp = b->next;
 
245
            erts_smp_mtx_unlock(lock);
 
246
            erts_smp_atomic_dec(&h->nitems);
 
247
            h->fun.free((void*)b);
 
248
            return tmpl;
 
249
        }
 
250
        prevp = &b->next;
 
251
        b = b->next;
 
252
    }
 
253
    erts_smp_mtx_unlock(lock);
 
254
    return NULL;
 
255
}
 
256
 
 
257
/*
 
258
** Call 'func(obj,func_arg2)' for all objects in table. NOT SAFE!!!
 
259
*/
 
260
void safe_hash_for_each(SafeHash* h, void (*func)(void *, void *), void *func_arg2)
 
261
{
 
262
    int i;
 
263
 
 
264
    for (i = 0; i <= h->size_mask; i++) {
 
265
        SafeHashBucket* b = h->tab[i];
 
266
        while (b != NULL) {
 
267
            (*func)((void *) b, func_arg2);
 
268
            b = b->next;
 
269
        }
 
270
    }
 
271
}
 
272
 
 
273
#endif /* !ERTS_SYS_CONTINOUS_FD_NUMBERS */
 
274