1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 1996-2017. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 #ifdef HAVE_CONFIG_H
22 #  include "config.h"
23 #endif
24 
25 #include "sys.h"
26 #include "erl_vm.h"
27 #include "global.h"
28 #include "export.h"
29 #include "hash.h"
30 #include "jit/beam_asm.h"
31 
32 #define EXPORT_INITIAL_SIZE   4000
33 #define EXPORT_LIMIT  (512*1024)
34 
35 #define EXPORT_HASH(m,f,a) ((atom_val(m) * atom_val(f)) ^ (a))
36 
37 #ifdef DEBUG
38 #  define IF_DEBUG(x) x
39 #else
40 #  define IF_DEBUG(x)
41 #endif
42 
43 static IndexTable export_tables[ERTS_NUM_CODE_IX];  /* Active not locked */
44 
45 static erts_atomic_t total_entries_bytes;
46 
47 /* This lock protects the staging export table from concurrent access
48  * AND it protects the staging table from becoming active.
49  */
50 erts_mtx_t export_staging_lock;
51 
52 struct export_entry
53 {
54     IndexSlot slot; /* MUST BE LOCATED AT TOP OF STRUCT!!! */
55     Export* ep;
56 };
57 
58 /* Helper struct that brings things together in one allocation
59 */
60 struct export_blob
61 {
62     Export exp;
63     struct export_entry entryv[ERTS_NUM_CODE_IX];
64     /* Note that entryv is not indexed by "code_ix".
65      */
66 };
67 
68 /* Helper struct only used as template
69 */
70 struct export_templ
71 {
72     struct export_entry entry;
73     Export exp;
74 };
75 
entry_to_blob(struct export_entry * ee)76 static struct export_blob* entry_to_blob(struct export_entry* ee)
77 {
78     return ErtsContainerStruct(ee->ep, struct export_blob, exp);
79 }
80 
81 void
export_info(fmtfn_t to,void * to_arg)82 export_info(fmtfn_t to, void *to_arg)
83 {
84     int lock = !ERTS_IS_CRASH_DUMPING;
85     if (lock)
86 	export_staging_lock();
87     index_info(to, to_arg, &export_tables[erts_active_code_ix()]);
88     hash_info(to, to_arg, &export_tables[erts_staging_code_ix()].htable);
89     if (lock)
90 	export_staging_unlock();
91 }
92 
93 
94 static HashValue
export_hash(struct export_entry * ee)95 export_hash(struct export_entry* ee)
96 {
97     Export* x = ee->ep;
98     return EXPORT_HASH(x->info.mfa.module, x->info.mfa.function,
99                        x->info.mfa.arity);
100 }
101 
102 static int
export_cmp(struct export_entry * tmpl_e,struct export_entry * obj_e)103 export_cmp(struct export_entry* tmpl_e, struct export_entry* obj_e)
104 {
105     Export* tmpl = tmpl_e->ep;
106     Export* obj = obj_e->ep;
107     return !(tmpl->info.mfa.module == obj->info.mfa.module &&
108 	     tmpl->info.mfa.function == obj->info.mfa.function &&
109 	     tmpl->info.mfa.arity == obj->info.mfa.arity);
110 }
111 
112 
113 static struct export_entry*
export_alloc(struct export_entry * tmpl_e)114 export_alloc(struct export_entry* tmpl_e)
115 {
116     struct export_blob* blob;
117     unsigned ix;
118 
119     if (tmpl_e->slot.index == -1) {  /* Template, allocate blob */
120 	Export* tmpl = tmpl_e->ep;
121 	Export* obj;
122 
123 	blob = (struct export_blob*) erts_alloc(ERTS_ALC_T_EXPORT, sizeof(*blob));
124 	erts_atomic_add_nob(&total_entries_bytes, sizeof(*blob));
125 	obj = &blob->exp;
126 	obj->info.op = 0;
127 	obj->info.u.gen_bp = NULL;
128 	obj->info.mfa.module = tmpl->info.mfa.module;
129 	obj->info.mfa.function = tmpl->info.mfa.function;
130 	obj->info.mfa.arity = tmpl->info.mfa.arity;
131         obj->bif_number = -1;
132         obj->is_bif_traced = 0;
133 
134         memset(&obj->trampoline, 0, sizeof(obj->trampoline));
135 
136         if (BeamOpsAreInitialized()) {
137             obj->trampoline.common.op = BeamOpCodeAddr(op_call_error_handler);
138         }
139 
140         for (ix=0; ix<ERTS_NUM_CODE_IX; ix++) {
141             erts_activate_export_trampoline(obj, ix);
142 
143             blob->entryv[ix].slot.index = -1;
144             blob->entryv[ix].ep = &blob->exp;
145         }
146 
147 	ix = 0;
148 
149 	DBG_TRACE_MFA_P(&obj->info.mfa, "export allocation at %p", obj);
150     }
151     else { /* Existing entry in another table, use free entry in blob */
152 	blob = entry_to_blob(tmpl_e);
153 	for (ix = 0; blob->entryv[ix].slot.index >= 0; ix++) {
154 	    ASSERT(ix < ERTS_NUM_CODE_IX);
155 	}
156     }
157     return &blob->entryv[ix];
158 }
159 
160 static void
export_free(struct export_entry * obj)161 export_free(struct export_entry* obj)
162 {
163     struct export_blob* blob = entry_to_blob(obj);
164     int i;
165     obj->slot.index = -1;
166     for (i=0; i < ERTS_NUM_CODE_IX; i++) {
167 	if (blob->entryv[i].slot.index >= 0) {
168 	    DBG_TRACE_MFA_P(&blob->exp.info.mfa, "export entry slot %u freed for %p",
169 			  (obj - blob->entryv), &blob->exp);
170 	    return;
171 	}
172     }
173     DBG_TRACE_MFA_P(&blob->exp.info.mfa, "export blob deallocation at %p", &blob->exp);
174     erts_free(ERTS_ALC_T_EXPORT, blob);
175     erts_atomic_add_nob(&total_entries_bytes, -sizeof(*blob));
176 }
177 
178 void
init_export_table(void)179 init_export_table(void)
180 {
181     HashFunctions f;
182     int i;
183 
184     erts_mtx_init(&export_staging_lock, "export_tab", NIL,
185         ERTS_LOCK_FLAGS_PROPERTY_STATIC | ERTS_LOCK_FLAGS_CATEGORY_GENERIC);
186     erts_atomic_init_nob(&total_entries_bytes, 0);
187 
188     f.hash = (H_FUN) export_hash;
189     f.cmp  = (HCMP_FUN) export_cmp;
190     f.alloc = (HALLOC_FUN) export_alloc;
191     f.free = (HFREE_FUN) export_free;
192     f.meta_alloc = (HMALLOC_FUN) erts_alloc;
193     f.meta_free = (HMFREE_FUN) erts_free;
194     f.meta_print = (HMPRINT_FUN) erts_print;
195 
196     for (i=0; i<ERTS_NUM_CODE_IX; i++) {
197 	erts_index_init(ERTS_ALC_T_EXPORT_TABLE, &export_tables[i], "export_list",
198 			EXPORT_INITIAL_SIZE, EXPORT_LIMIT, f);
199     }
200 }
201 
init_template(struct export_templ * templ,Eterm m,Eterm f,unsigned a)202 static struct export_entry* init_template(struct export_templ* templ,
203 					  Eterm m, Eterm f, unsigned a)
204 {
205     templ->entry.ep = &templ->exp;
206     templ->entry.slot.index = -1;
207     templ->exp.info.mfa.module = m;
208     templ->exp.info.mfa.function = f;
209     templ->exp.info.mfa.arity = a;
210     templ->exp.bif_number = -1;
211     templ->exp.is_bif_traced = 0;
212     return &templ->entry;
213 }
214 
215 /*
216  * Return a pointer to the export entry for the given function,
217  * or NULL otherwise.  Notes:
218  *
219  * 1) BIFs have export entries and can be called through
220  *    a wrapper in the export entry.
221  * 2) Functions referenced by a loaded module, but not yet loaded
222  *    also have export entries.  The export entry contains
223  *    a wrapper which invokes the error handler if a function is
224  *    called through such an export entry.
225  * 3) This function is suitable for the implementation of erlang:apply/3.
226  */
227 extern Export* /* inline-helper */
228 erts_find_export_entry(Eterm m, Eterm f, unsigned int a,ErtsCodeIndex code_ix);
229 
230 Export*
erts_find_export_entry(Eterm m,Eterm f,unsigned int a,ErtsCodeIndex code_ix)231 erts_find_export_entry(Eterm m, Eterm f, unsigned int a, ErtsCodeIndex code_ix)
232 {
233     struct export_templ templ;
234     struct export_entry *ee =
235         hash_fetch(&export_tables[code_ix].htable,
236                    init_template(&templ, m, f, a),
237                    (H_FUN)export_hash, (HCMP_FUN)export_cmp);
238     if (ee) return ee->ep;
239     return NULL;
240 }
241 
242 /*
243  * Find the export entry for a loaded function.
244  * Returns a NULL pointer if the given function is not loaded, or
245  * a pointer to the export entry.
246  *
247  * Note: This function never returns export entries for BIFs
248  * or functions which are not yet loaded.  This makes it suitable
249  * for use by the erlang:function_exported/3 BIF or whenever you
250  * cannot depend on the error_handler.
251  */
252 
253 Export*
erts_find_function(Eterm m,Eterm f,unsigned int a,ErtsCodeIndex code_ix)254 erts_find_function(Eterm m, Eterm f, unsigned int a, ErtsCodeIndex code_ix)
255 {
256     struct export_templ templ;
257     struct export_entry* ee;
258 
259     ee = hash_get(&export_tables[code_ix].htable, init_template(&templ, m, f, a));
260 
261     if (ee == NULL
262         || (erts_is_export_trampoline_active(ee->ep, code_ix) &&
263             !BeamIsOpCode(ee->ep->trampoline.common.op, op_i_generic_breakpoint))) {
264         return NULL;
265     }
266 
267     return ee->ep;
268 }
269 
270 /*
271  * Returns a pointer to an existing export entry for a MFA,
272  * or creates a new one and returns the pointer.
273  *
274  * This function acts on the staging export table. It should only be used
275  * to load new code.
276  */
277 
278 Export*
erts_export_put(Eterm mod,Eterm func,unsigned int arity)279 erts_export_put(Eterm mod, Eterm func, unsigned int arity)
280 {
281     ErtsCodeIndex code_ix = erts_staging_code_ix();
282     struct export_templ templ;
283     struct export_entry* ee;
284     Export* res;
285 
286     ASSERT(is_atom(mod));
287     ASSERT(is_atom(func));
288     export_staging_lock();
289     ee = (struct export_entry*) index_put_entry(&export_tables[code_ix],
290 						init_template(&templ, mod, func, arity));
291     export_staging_unlock();
292 
293     res = ee->ep;
294 
295 #ifdef BEAMASM
296     res->addresses[ERTS_SAVE_CALLS_CODE_IX] = beam_save_calls;
297 #endif
298 
299     return res;
300 }
301 
302 /*
303  * Find the existing export entry for M:F/A. Failing that, create a stub
304  * export entry (making a call through it will cause the error_handler to
305  * be called).
306  *
307  * Stub export entries will be placed in the loader export table.
308  */
309 
310 Export*
erts_export_get_or_make_stub(Eterm mod,Eterm func,unsigned int arity)311 erts_export_get_or_make_stub(Eterm mod, Eterm func, unsigned int arity)
312 {
313     ErtsCodeIndex code_ix;
314     Export* ep;
315     IF_DEBUG(int retrying = 0;)
316 
317     ASSERT(is_atom(mod));
318     ASSERT(is_atom(func));
319 
320     do {
321 	code_ix = erts_active_code_ix();
322 	ep = erts_find_export_entry(mod, func, arity, code_ix);
323 	if (ep == 0) {
324 	    /*
325 	     * The code is not loaded (yet). Put the export in the staging
326 	     * export table, to avoid having to lock the active export table.
327 	     */
328 	    export_staging_lock();
329 	    if (erts_active_code_ix() == code_ix) {
330 		struct export_templ templ;
331 	        struct export_entry* entry;
332 
333 		IndexTable* tab = &export_tables[erts_staging_code_ix()];
334 		init_template(&templ, mod, func, arity);
335 		entry = (struct export_entry *) index_put_entry(tab, &templ.entry);
336 		ep = entry->ep;
337 
338 #ifdef BEAMASM
339                 ep->addresses[ERTS_SAVE_CALLS_CODE_IX] = beam_save_calls;
340 #endif
341 
342 		ASSERT(ep);
343 	    }
344 	    else { /* race */
345 		ASSERT(!retrying);
346 		IF_DEBUG(retrying = 1);
347 	    }
348 	    export_staging_unlock();
349 	}
350     } while (!ep);
351     return ep;
352 }
353 
export_list(int i,ErtsCodeIndex code_ix)354 Export *export_list(int i, ErtsCodeIndex code_ix)
355 {
356     return ((struct export_entry*) erts_index_lookup(&export_tables[code_ix], i))->ep;
357 }
358 
export_list_size(ErtsCodeIndex code_ix)359 int export_list_size(ErtsCodeIndex code_ix)
360 {
361     return erts_index_num_entries(&export_tables[code_ix]);
362 }
363 
export_table_sz(void)364 int export_table_sz(void)
365 {
366     int i, bytes = 0;
367 
368     export_staging_lock();
369     for (i=0; i<ERTS_NUM_CODE_IX; i++) {
370 	bytes += index_table_sz(&export_tables[i]);
371     }
372     export_staging_unlock();
373     return bytes;
374 }
export_entries_sz(void)375 int export_entries_sz(void)
376 {
377     return erts_atomic_read_nob(&total_entries_bytes);
378 }
export_get(Export * e)379 Export *export_get(Export *e)
380 {
381     struct export_entry ee;
382     struct export_entry* entry;
383 
384     ee.ep = e;
385     entry = (struct export_entry*)hash_get(&export_tables[erts_active_code_ix()].htable, &ee);
386     return entry ? entry->ep : NULL;
387 }
388 
389 IF_DEBUG(static ErtsCodeIndex debug_start_load_ix = 0;)
390 
391 
export_start_staging(void)392 void export_start_staging(void)
393 {
394     ErtsCodeIndex dst_ix = erts_staging_code_ix();
395     ErtsCodeIndex src_ix = erts_active_code_ix();
396     IndexTable* dst = &export_tables[dst_ix];
397     IndexTable* src = &export_tables[src_ix];
398     struct export_entry* src_entry;
399 #ifdef DEBUG
400     struct export_entry* dst_entry;
401 #endif
402     int i;
403 
404     ASSERT(dst_ix != src_ix);
405     ASSERT(debug_start_load_ix == -1);
406 
407     export_staging_lock();
408     /*
409      * Insert all entries in src into dst table
410      */
411     for (i = 0; i < src->entries; i++) {
412 	src_entry = (struct export_entry*) erts_index_lookup(src, i);
413         src_entry->ep->addresses[dst_ix] = src_entry->ep->addresses[src_ix];
414 #ifdef DEBUG
415 	dst_entry = (struct export_entry*)
416 #endif
417 	    index_put_entry(dst, src_entry);
418 	ASSERT(entry_to_blob(src_entry) == entry_to_blob(dst_entry));
419     }
420     export_staging_unlock();
421 
422     IF_DEBUG(debug_start_load_ix = dst_ix);
423 }
424 
export_end_staging(int commit)425 void export_end_staging(int commit)
426 {
427     ASSERT(debug_start_load_ix == erts_staging_code_ix());
428     IF_DEBUG(debug_start_load_ix = -1);
429 }
430 
431