~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • 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:
28
28
 
29
29
#define EXPORT_SIZE   500
30
30
#define EXPORT_LIMIT  (64*1024)
31
 
#define EXPORT_RATE   100
32
31
 
33
32
#define EXPORT_HASH(m,f,a) ((m)*(f)+(a))
34
 
IndexTable export_table;
 
33
 
 
34
static IndexTable export_table; /* Not locked. */
 
35
static Hash secondary_export_table; /* Locked. */
 
36
 
 
37
#include "erl_smp.h"
 
38
 
 
39
static erts_smp_rwmtx_t export_table_lock; /* Locks the secondary export table. */
 
40
 
 
41
#define export_read_lock()      erts_smp_rwmtx_rlock(&export_table_lock)
 
42
#define export_read_unlock()    erts_smp_rwmtx_runlock(&export_table_lock)
 
43
#define export_write_lock()     erts_smp_rwmtx_rwlock(&export_table_lock)
 
44
#define export_write_unlock()   erts_smp_rwmtx_rwunlock(&export_table_lock)
 
45
#define export_init_lock()      erts_smp_rwmtx_init(&export_table_lock, \
 
46
                                                    "export_tab")
35
47
 
36
48
extern Eterm* em_call_error_handler;
37
49
extern Uint* em_call_traced_function;
38
50
 
39
51
void
40
 
export_info(CIO to)
 
52
export_info(int to, void *to_arg)
41
53
{
42
 
    index_info(to, &export_table);
 
54
#ifdef ERTS_SMP
 
55
    int lock = !ERTS_IS_CRASH_DUMPING;
 
56
    if (lock)
 
57
        export_read_lock();
 
58
#endif
 
59
    index_info(to, to_arg, &export_table);
 
60
    hash_info(to, to_arg, &secondary_export_table);
 
61
#ifdef ERTS_SMP
 
62
    if (lock)
 
63
        export_read_unlock();
 
64
#endif
43
65
}
44
66
 
45
67
 
89
111
{
90
112
    HashFunctions f;
91
113
 
 
114
    export_init_lock();
92
115
    f.hash = (H_FUN) export_hash;
93
116
    f.cmp  = (HCMP_FUN) export_cmp;
94
117
    f.alloc = (HALLOC_FUN) export_alloc;
95
118
    f.free = (HFREE_FUN) export_free;
96
119
 
97
 
    index_init(ERTS_ALC_T_EXPORT_TABLE, &export_table, "export_list",
98
 
               EXPORT_SIZE, EXPORT_LIMIT, EXPORT_RATE, f);
 
120
    erts_index_init(ERTS_ALC_T_EXPORT_TABLE, &export_table, "export_list",
 
121
                    EXPORT_SIZE, EXPORT_LIMIT, f);
 
122
    hash_init(ERTS_ALC_T_EXPORT_TABLE, &secondary_export_table,
 
123
              "secondary_export_table", 50, f);
99
124
}
100
125
 
101
126
/*
115
140
erts_find_export_entry(Eterm m, Eterm f, unsigned int a)
116
141
{
117
142
    HashValue hval = EXPORT_HASH(m, f, a);
118
 
    int ix = hval % export_table.htable.size;
119
 
    HashBucket* b = export_table.htable.bucket[ix];
 
143
    int ix;
 
144
    HashBucket* b;
 
145
 
 
146
    ix = hval % export_table.htable.size;
 
147
    b = export_table.htable.bucket[ix];
120
148
 
121
149
    /*
122
150
     * Note: We have inlined the code from hash.c for speed.
125
153
    while (b != (HashBucket*) 0) {
126
154
        Export* ep = (Export *) b;
127
155
        if (ep->code[0] == m && ep->code[1] == f && ep->code[2] == a) {
128
 
            return ep;
 
156
            break;
129
157
        }
130
158
        b = b->next;
131
159
    }
132
 
    return NULL;
 
160
    return (Export*)b;
133
161
}
134
162
 
135
163
 
154
182
    e.code[1] = f;
155
183
    e.code[2] = a;
156
184
 
157
 
    if ((ep = hash_get(&export_table.htable, (void*) &e)) == NULL) {
158
 
        return NULL;
159
 
    }
160
 
    if (ep->address == ep->code+3 && ep->code[3] != (Uint) em_call_traced_function) {
161
 
        return NULL;
 
185
    ep = hash_get(&export_table.htable, (void*) &e);
 
186
    if (ep != NULL && ep->address == ep->code+3 &&
 
187
        ep->code[3] != (Uint) em_call_traced_function) {
 
188
        ep = NULL;
162
189
    }
163
190
    return ep;
164
191
}
165
192
 
166
 
 
167
193
/*
168
194
 * Returns a pointer to an existing export entry for a MFA,
169
195
 * or creates a new one and returns the pointer.
 
196
 *
 
197
 * This function provides unlocked write access to the main export
 
198
 * table. It should only be used during start up or when
 
199
 * all other threads are blocked.
170
200
 */
171
201
 
172
202
Export*
173
203
erts_export_put(Eterm mod, Eterm func, unsigned int arity)
174
204
{
175
205
    Export e;
176
 
    
177
 
    ASSERT(is_atom(mod));
178
 
    ASSERT(is_atom(func));
179
 
    
180
 
    e.fake_op_func_info_for_hipe[0] = 0;
181
 
    e.fake_op_func_info_for_hipe[1] = 0;
182
 
    e.code[0] = mod;
183
 
    e.code[1] = func;
184
 
    e.code[2] = arity;
185
 
    e.address = e.code+3;
186
 
    e.code[4] = 0;
187
 
    e.match_prog_set = NULL;
188
 
    return export_list(index_put(&export_table, (void*) &e));
 
206
    int ix;
 
207
 
 
208
    ERTS_SMP_LC_ASSERT(erts_initialized == 0 || erts_smp_is_system_blocked(0));
 
209
    ASSERT(is_atom(mod));
 
210
    ASSERT(is_atom(func));
 
211
    e.code[0] = mod;
 
212
    e.code[1] = func;
 
213
    e.code[2] = arity;
 
214
    ix = index_put(&export_table, (void*) &e);
 
215
    return (Export*) erts_index_lookup(&export_table, ix);
 
216
}
 
217
 
 
218
/*
 
219
 * Find the existing export entry for M:F/A. Failing that, create a stub
 
220
 * export entry (making a call through it will cause the error_handler to
 
221
 * be called).
 
222
 *
 
223
 * Stub export entries will be placed in the secondary export table.
 
224
 * erts_export_consolidate() will move all stub export entries into the
 
225
 * main export table (will be done the next time code is loaded).
 
226
 */
 
227
 
 
228
Export*
 
229
erts_export_get_or_make_stub(Eterm mod, Eterm func, unsigned int arity)
 
230
{
 
231
    Export e;
 
232
    Export* ep;
 
233
    
 
234
    ASSERT(is_atom(mod));
 
235
    ASSERT(is_atom(func));
 
236
    
 
237
    e.code[0] = mod;
 
238
    e.code[1] = func;
 
239
    e.code[2] = arity;
 
240
    ep = erts_find_export_entry(mod, func, arity);
 
241
    if (ep == 0) {
 
242
        /*
 
243
         * The code is not loaded (yet). Put the export in the secondary
 
244
         * export table, to avoid having to lock the main export table.
 
245
         */
 
246
        export_write_lock();
 
247
        ep = (Export *) hash_put(&secondary_export_table, (void*) &e);
 
248
        export_write_unlock();
 
249
    }
 
250
    return ep;
 
251
}
 
252
 
 
253
/*
 
254
 * To be called before loading code (with other threads blocked).
 
255
 * This function will move all export entries from the secondary
 
256
 * export table into the primary.
 
257
 */
 
258
void
 
259
erts_export_consolidate(void)
 
260
{
 
261
#ifdef DEBUG
 
262
    HashInfo hi;
 
263
#endif
 
264
 
 
265
    ERTS_SMP_LC_ASSERT(erts_initialized == 0 || erts_smp_is_system_blocked(0));
 
266
 
 
267
    export_write_lock();
 
268
    erts_index_merge(&secondary_export_table, &export_table);
 
269
    erts_hash_merge(&secondary_export_table, &export_table.htable);
 
270
    export_write_unlock();
 
271
#ifdef DEBUG
 
272
    hash_get_info(&hi, &export_table.htable);
 
273
    ASSERT(export_table.entries == hi.objs);
 
274
#endif
 
275
}
 
276
 
 
277
Export *export_list(int i)
 
278
{
 
279
    return (Export*) erts_index_lookup(&export_table, i);
 
280
}
 
281
 
 
282
int export_list_size(void)
 
283
{
 
284
    return export_table.entries;
 
285
}
 
286
 
 
287
int export_table_sz(void)
 
288
{
 
289
    return index_table_sz(&export_table);
 
290
}
 
291
 
 
292
Export *export_get(Export *e)
 
293
{
 
294
    return hash_get(&export_table.htable, e);
189
295
}