1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2016-2018. 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 #ifndef ERL_NFUNC_SCHED_H__
22 #define ERL_NFUNC_SCHED_H__
23 
24 #include "erl_process.h"
25 #include "bif.h"
26 #include "error.h"
27 
28 /*
29  * Native function wrappers are used to schedule native functions on both
30  * normal and dirty schedulers.
31  *
32  * A number of values are only stored for error handling, and the fields
33  * following `current` can be omitted when a wrapper is statically "scheduled"
34  * through placement in a function stub.
35  *
36  * 'argc' is >= 0 when ErtsNativeFunc is in use, and < 0 when not.
37  */
38 
39 typedef struct {
40     struct {
41         ErtsCodeInfo info;
42 #ifdef BEAMASM
43         // Code used by tracing/nif load
44         BeamInstr trace[1];
45 #endif
46         BeamInstr call_op; /* call_bif || call_nif */
47         BeamInstr dfunc;
48     } trampoline;
49 
50     struct erl_module_nif* m; /* NIF module, or NULL if BIF */
51     void *func;		/* Indirect NIF or BIF to execute (may be unused) */
52     const ErtsCodeMFA *current;/* Current as set when originally called */
53     /* --- The following is only used on error --- */
54     ErtsCodePtr pc;    /* Program counter */
55     const ErtsCodeMFA *mfa; /* MFA of original call */
56     int argc;		/* Number of arguments in original call */
57     int argv_size;	/* Allocated size of argv */
58     Eterm argv[1];	/* Saved arguments from the original call */
59 } ErtsNativeFunc;
60 
61 ErtsNativeFunc *erts_new_proc_nfunc(Process *c_p, int argc);
62 void erts_destroy_nfunc(Process *p);
63 ErtsNativeFunc *erts_nfunc_schedule(Process *c_p, Process *dirty_shadow_proc,
64                                const ErtsCodeMFA *mfa, ErtsCodePtr pc,
65                                BeamInstr instr,
66                                void *dfunc, void *ifunc,
67                                Eterm mod, Eterm func,
68                                int argc, const Eterm *argv);
69 void erts_nfunc_cleanup_nif_mod(ErtsNativeFunc *ep); /* erl_nif.c */
70 ERTS_GLB_INLINE ErtsNativeFunc *erts_get_proc_nfunc(Process *c_p, int extra);
71 ERTS_GLB_INLINE int erts_setup_nfunc_rootset(Process* proc, Eterm** objv,
72                                              Uint* nobj);
73 ERTS_GLB_INLINE int erts_check_nfunc_in_area(Process *p,
74                                              char *start, Uint size);
75 ERTS_GLB_INLINE void erts_nfunc_restore(Process *c_p, ErtsNativeFunc *ep,
76                                         Eterm result);
77 ERTS_GLB_INLINE void erts_nfunc_restore_error(Process* c_p,
78                                               ErtsCodePtr *pc,
79                                               Eterm *reg,
80                                               const ErtsCodeMFA **nif_mfa);
81 ERTS_GLB_INLINE Process *erts_proc_shadow2real(Process *c_p);
82 
83 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
84 
85 ERTS_GLB_INLINE ErtsNativeFunc *
erts_get_proc_nfunc(Process * c_p,int argc)86 erts_get_proc_nfunc(Process *c_p, int argc)
87 {
88     ErtsNativeFunc *nep = ERTS_PROC_GET_NFUNC_TRAP_WRAPPER(c_p);
89     if (!nep || (nep->argc < 0 && nep->argv_size < argc))
90 	return erts_new_proc_nfunc(c_p, argc);
91     return nep;
92 }
93 
94 /*
95  * If a process has saved arguments, they need to be part of the GC
96  * rootset. The function below is called from setup_rootset() in
97  * erl_gc.c. Any exception term saved in the ErtsNativeFunc is also made
98  * part of the GC rootset here; it always resides in rootset[0].
99  */
100 ERTS_GLB_INLINE int
erts_setup_nfunc_rootset(Process * proc,Eterm ** objv,Uint * nobj)101 erts_setup_nfunc_rootset(Process* proc, Eterm** objv, Uint* nobj)
102 {
103     ErtsNativeFunc* ep = (ErtsNativeFunc*) ERTS_PROC_GET_NFUNC_TRAP_WRAPPER(proc);
104 
105     if (!ep || ep->argc <= 0)
106 	return 0;
107 
108     *objv = ep->argv;
109     *nobj = ep->argc;
110     return 1;
111 }
112 
113 /*
114  * Check if native func wrapper points into code area...
115  */
116 ERTS_GLB_INLINE int
erts_check_nfunc_in_area(Process * p,char * start,Uint size)117 erts_check_nfunc_in_area(Process *p, char *start, Uint size)
118 {
119     ErtsNativeFunc *nep = ERTS_PROC_GET_NFUNC_TRAP_WRAPPER(p);
120     if (!nep || nep->argc < 0)
121 	return 0;
122     if (ErtsInArea(nep->pc, start, size))
123 	return 1;
124     if (ErtsInArea(nep->mfa, start, size))
125 	return 1;
126     if (ErtsInArea(nep->current, start, size))
127 	return 1;
128     return 0;
129 }
130 
131 ERTS_GLB_INLINE void
erts_nfunc_restore(Process * c_p,ErtsNativeFunc * ep,Eterm result)132 erts_nfunc_restore(Process *c_p, ErtsNativeFunc *ep, Eterm result)
133 {
134     ASSERT(!ERTS_SCHEDULER_IS_DIRTY(erts_get_scheduler_data()));
135     ERTS_LC_ASSERT(!(c_p->static_flags
136 			 & ERTS_STC_FLG_SHADOW_PROC));
137     ERTS_LC_ASSERT(erts_proc_lc_my_proc_locks(c_p)
138 		       & ERTS_PROC_LOCK_MAIN);
139 
140     c_p->current = ep->current;
141     ep->argc = -1; /* Unused nif-export marker... */
142 }
143 
144 ERTS_GLB_INLINE void
erts_nfunc_restore_error(Process * c_p,ErtsCodePtr * pc,Eterm * reg,const ErtsCodeMFA ** nif_mfa)145 erts_nfunc_restore_error(Process* c_p, ErtsCodePtr *pc,
146                          Eterm *reg, const ErtsCodeMFA **nif_mfa)
147 {
148     ErtsNativeFunc *nep = (ErtsNativeFunc *) ERTS_PROC_GET_NFUNC_TRAP_WRAPPER(c_p);
149     int ix;
150 
151     ASSERT(nep);
152     *pc = nep->pc;
153     *nif_mfa = nep->mfa;
154     for (ix = 0; ix < nep->argc; ix++)
155 	reg[ix] = nep->argv[ix];
156     erts_nfunc_restore(c_p, nep, THE_NON_VALUE);
157 }
158 
159 ERTS_GLB_INLINE Process *
erts_proc_shadow2real(Process * c_p)160 erts_proc_shadow2real(Process *c_p)
161 {
162     if (c_p->static_flags & ERTS_STC_FLG_SHADOW_PROC) {
163 	Process *real_c_p = c_p->next;
164 	ASSERT(ERTS_SCHEDULER_IS_DIRTY(erts_get_scheduler_data()));
165 	ASSERT(real_c_p->common.id == c_p->common.id);
166 	return real_c_p;
167     }
168     ASSERT(!ERTS_SCHEDULER_IS_DIRTY(erts_get_scheduler_data()));
169     return c_p;
170 }
171 
172 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
173 
174 #endif /* ERL_NFUNC_SCHED_H__ */
175 
176 #if defined(ERTS_WANT_NFUNC_SCHED_INTERNALS__) && !defined(ERTS_NFUNC_SCHED_INTERNALS__)
177 #define ERTS_NFUNC_SCHED_INTERNALS__
178 
179 #ifdef BEAMASM
180 #define NFUNC_FIELD__ trampoline.trace
181 #else
182 #define NFUNC_FIELD__ trampoline.call_op
183 #endif
184 
185 #define ERTS_I_BEAM_OP_TO_NFUNC(I)                                            \
186     (ASSERT(BeamIsOpCode(*(const BeamInstr*)(I), op_call_bif_W) ||            \
187             BeamIsOpCode(*(const BeamInstr*)(I), op_call_nif_WWW)),           \
188      ((ErtsNativeFunc *) (((char *) (I)) -                                    \
189         offsetof(ErtsNativeFunc, NFUNC_FIELD__))))
190 
191 #include "erl_message.h"
192 #include <stddef.h>
193 
194 ERTS_GLB_INLINE void erts_flush_dirty_shadow_proc(Process *sproc);
195 ERTS_GLB_INLINE void erts_cache_dirty_shadow_proc(Process *sproc);
196 ERTS_GLB_INLINE Process *erts_make_dirty_shadow_proc(ErtsSchedulerData *esdp,
197 						     Process *c_p);
198 
199 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
200 
201 ERTS_GLB_INLINE void
erts_flush_dirty_shadow_proc(Process * sproc)202 erts_flush_dirty_shadow_proc(Process *sproc)
203 {
204     Process *c_p = sproc->next;
205 
206     ASSERT(sproc->common.id == c_p->common.id);
207     ERTS_LC_ASSERT(erts_proc_lc_my_proc_locks(c_p)
208 		       & ERTS_PROC_LOCK_MAIN);
209 
210     ASSERT(c_p->stop == sproc->stop);
211     ASSERT(c_p->hend == sproc->hend);
212     ASSERT(c_p->heap == sproc->heap);
213     ASSERT(c_p->abandoned_heap == sproc->abandoned_heap);
214     ASSERT(c_p->heap_sz == sproc->heap_sz);
215     ASSERT(c_p->high_water == sproc->high_water);
216     ASSERT(c_p->old_heap == sproc->old_heap);
217     ASSERT(c_p->old_htop == sproc->old_htop);
218     ASSERT(c_p->old_hend == sproc->old_hend);
219 
220     ASSERT(c_p->htop <= sproc->htop && sproc->htop <= c_p->stop);
221 
222     c_p->htop = sproc->htop;
223 
224     if (!c_p->mbuf)
225 	c_p->mbuf = sproc->mbuf;
226     else if (sproc->mbuf) {
227 	ErlHeapFragment *bp;
228 	for (bp = sproc->mbuf; bp->next; bp = bp->next)
229 	    ASSERT(!bp->off_heap.first);
230 	bp->next = c_p->mbuf;
231 	c_p->mbuf = sproc->mbuf;
232     }
233 
234     c_p->mbuf_sz += sproc->mbuf_sz;
235 
236     if (!c_p->off_heap.first)
237 	c_p->off_heap.first = sproc->off_heap.first;
238     else if (sproc->off_heap.first) {
239 	struct erl_off_heap_header *ohhp;
240 	for (ohhp = sproc->off_heap.first; ohhp->next; ohhp = ohhp->next)
241 	    ;
242 	ohhp->next = c_p->off_heap.first;
243 	c_p->off_heap.first = sproc->off_heap.first;
244     }
245 
246     c_p->off_heap.overhead += sproc->off_heap.overhead;
247 }
248 
249 ERTS_GLB_INLINE void
erts_cache_dirty_shadow_proc(Process * sproc)250 erts_cache_dirty_shadow_proc(Process *sproc)
251 {
252     Process *c_p = sproc->next;
253     ASSERT(c_p);
254     ASSERT(sproc->common.id == c_p->common.id);
255     ERTS_LC_ASSERT(erts_proc_lc_my_proc_locks(c_p)
256 		       & ERTS_PROC_LOCK_MAIN);
257 
258     sproc->htop = c_p->htop;
259     sproc->stop = c_p->stop;
260     sproc->hend = c_p->hend;
261     sproc->heap = c_p->heap;
262     sproc->abandoned_heap = c_p->abandoned_heap;
263     sproc->heap_sz = c_p->heap_sz;
264     sproc->high_water = c_p->high_water;
265     sproc->old_hend = c_p->old_hend;
266     sproc->old_htop = c_p->old_htop;
267     sproc->old_heap = c_p->old_heap;
268     sproc->mbuf = NULL;
269     sproc->mbuf_sz = 0;
270     ERTS_INIT_OFF_HEAP(&sproc->off_heap);
271 }
272 
273 ERTS_GLB_INLINE Process *
erts_make_dirty_shadow_proc(ErtsSchedulerData * esdp,Process * c_p)274 erts_make_dirty_shadow_proc(ErtsSchedulerData *esdp, Process *c_p)
275 {
276     Process *sproc;
277 
278     ASSERT(ERTS_SCHEDULER_IS_DIRTY(esdp));
279 
280     sproc = esdp->dirty_shadow_process;
281     ASSERT(sproc);
282     ASSERT(sproc->static_flags & ERTS_STC_FLG_SHADOW_PROC);
283     ASSERT(erts_atomic32_read_nob(&sproc->state)
284 	   == (ERTS_PSFLG_ACTIVE
285 	       | ERTS_PSFLG_DIRTY_RUNNING
286 	       | ERTS_PSFLG_PROXY));
287 
288     sproc->next = c_p;
289     sproc->common.id = c_p->common.id;
290 
291     erts_cache_dirty_shadow_proc(sproc);
292 
293     return sproc;
294 }
295 
296 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
297 
298 
299 #endif /* defined(ERTS_WANT_NFUNC_SCHED_INTERNALS__) && !defined(ERTS_NFUNC_SCHED_INTERNALS__) */
300 
301