1|// Low-level VM code for ARM64 CPUs.
2|// Bytecode interpreter, fast functions and helper functions.
3|// Copyright (C) 2005-2017 Mike Pall. See Copyright Notice in luajit.h
4|
5|.arch arm64
6|.section code_op, code_sub
7|
8|.actionlist build_actionlist
9|.globals GLOB_
10|.globalnames globnames
11|.externnames extnames
12|
13|// Note: The ragged indentation of the instructions is intentional.
14|//       The starting columns indicate data dependencies.
15|
16|//-----------------------------------------------------------------------
17|
18|// ARM64 registers and the AAPCS64 ABI 1.0 at a glance:
19|//
20|// x0-x17 temp, x19-x28 callee-saved, x29 fp, x30 lr
21|// x18 is reserved on most platforms. Don't use it, save it or restore it.
22|// x31 doesn't exist. Register number 31 either means xzr/wzr (zero) or sp,
23|// depending on the instruction.
24|// v0-v7 temp, v8-v15 callee-saved (only d8-d15 preserved), v16-v31 temp
25|//
26|// x0-x7/v0-v7 hold parameters and results.
27|
28|// Fixed register assignments for the interpreter.
29|
30|// The following must be C callee-save.
31|.define BASE,		x19	// Base of current Lua stack frame.
32|.define KBASE,		x20	// Constants of current Lua function.
33|.define PC,		x21	// Next PC.
34|.define GLREG,		x22	// Global state.
35|.define LREG,		x23	// Register holding lua_State (also in SAVE_L).
36|.define TISNUM,	x24	// Constant LJ_TISNUM << 47.
37|.define TISNUMhi,	x25	// Constant LJ_TISNUM << 15.
38|.define TISNIL,	x26	// Constant -1LL.
39|.define fp,		x29	// Yes, we have to maintain a frame pointer.
40|
41|.define ST_INTERP,	w26	// Constant -1.
42|
43|// The following temporaries are not saved across C calls, except for RA/RC.
44|.define RA,		x27
45|.define RC,		x28
46|.define RB,		x17
47|.define RAw,		w27
48|.define RCw,		w28
49|.define RBw,		w17
50|.define INS,		x16
51|.define INSw,		w16
52|.define ITYPE,		x15
53|.define TMP0,		x8
54|.define TMP1,		x9
55|.define TMP2,		x10
56|.define TMP3,		x11
57|.define TMP0w,		w8
58|.define TMP1w,		w9
59|.define TMP2w,		w10
60|.define TMP3w,		w11
61|
62|// Calling conventions. Also used as temporaries.
63|.define CARG1,		x0
64|.define CARG2,		x1
65|.define CARG3,		x2
66|.define CARG4,		x3
67|.define CARG5,		x4
68|.define CARG1w,	w0
69|.define CARG2w,	w1
70|.define CARG3w,	w2
71|.define CARG4w,	w3
72|.define CARG5w,	w4
73|
74|.define FARG1,		d0
75|.define FARG2,		d1
76|
77|.define CRET1,		x0
78|.define CRET1w,	w0
79|
80|// Stack layout while in interpreter. Must match with lj_frame.h.
81|
82|.define CFRAME_SPACE,	208
83|//----- 16 byte aligned, <-- sp entering interpreter
84|// Unused		[sp, #204]	// 32 bit values
85|.define SAVE_NRES,	[sp, #200]
86|.define SAVE_ERRF,	[sp, #196]
87|.define SAVE_MULTRES,	[sp, #192]
88|.define TMPD,		[sp, #184]	// 64 bit values
89|.define SAVE_L,	[sp, #176]
90|.define SAVE_PC,	[sp, #168]
91|.define SAVE_CFRAME,	[sp, #160]
92|.define SAVE_FPR_,	96		// 96+8*8: 64 bit FPR saves
93|.define SAVE_GPR_,	16		// 16+10*8: 64 bit GPR saves
94|.define SAVE_LR,	[sp, #8]
95|.define SAVE_FP,	[sp]
96|//----- 16 byte aligned, <-- sp while in interpreter.
97|
98|.define TMPDofs,	#184
99|
100|.macro save_, gpr1, gpr2, fpr1, fpr2
101|  stp d..fpr1, d..fpr2, [sp, # SAVE_FPR_+(fpr1-8)*8]
102|  stp x..gpr1, x..gpr2, [sp, # SAVE_GPR_+(gpr1-19)*8]
103|.endmacro
104|.macro rest_, gpr1, gpr2, fpr1, fpr2
105|  ldp d..fpr1, d..fpr2, [sp, # SAVE_FPR_+(fpr1-8)*8]
106|  ldp x..gpr1, x..gpr2, [sp, # SAVE_GPR_+(gpr1-19)*8]
107|.endmacro
108|
109|.macro saveregs
110|  stp fp, lr, [sp, #-CFRAME_SPACE]!
111|  add fp, sp, #0
112|  stp x19, x20, [sp, # SAVE_GPR_]
113|  save_ 21, 22, 8, 9
114|  save_ 23, 24, 10, 11
115|  save_ 25, 26, 12, 13
116|  save_ 27, 28, 14, 15
117|.endmacro
118|.macro restoreregs
119|  ldp x19, x20, [sp, # SAVE_GPR_]
120|  rest_ 21, 22, 8, 9
121|  rest_ 23, 24, 10, 11
122|  rest_ 25, 26, 12, 13
123|  rest_ 27, 28, 14, 15
124|  ldp fp, lr, [sp], # CFRAME_SPACE
125|.endmacro
126|
127|// Type definitions. Some of these are only used for documentation.
128|.type L,		lua_State,	LREG
129|.type GL,		global_State,	GLREG
130|.type TVALUE,		TValue
131|.type GCOBJ,		GCobj
132|.type STR,		GCstr
133|.type TAB,		GCtab
134|.type LFUNC,		GCfuncL
135|.type CFUNC,		GCfuncC
136|.type PROTO,		GCproto
137|.type UPVAL,		GCupval
138|.type NODE,		Node
139|.type NARGS8,		int
140|.type TRACE,		GCtrace
141|.type SBUF,		SBuf
142|
143|//-----------------------------------------------------------------------
144|
145|// Trap for not-yet-implemented parts.
146|.macro NYI; brk; .endmacro
147|
148|//-----------------------------------------------------------------------
149|
150|// Access to frame relative to BASE.
151|.define FRAME_FUNC,	#-16
152|.define FRAME_PC,	#-8
153|
154|.macro decode_RA, dst, ins; ubfx dst, ins, #8, #8; .endmacro
155|.macro decode_RB, dst, ins; ubfx dst, ins, #24, #8; .endmacro
156|.macro decode_RC, dst, ins; ubfx dst, ins, #16, #8; .endmacro
157|.macro decode_RD, dst, ins; ubfx dst, ins, #16, #16; .endmacro
158|.macro decode_RC8RD, dst, src; ubfiz dst, src, #3, #8; .endmacro
159|
160|// Instruction decode+dispatch.
161|.macro ins_NEXT
162|  ldr INSw, [PC], #4
163|  add TMP1, GL, INS, uxtb #3
164|   decode_RA RA, INS
165|  ldr TMP0, [TMP1, #GG_G2DISP]
166|   decode_RD RC, INS
167|  br TMP0
168|.endmacro
169|
170|// Instruction footer.
171|.if 1
172|  // Replicated dispatch. Less unpredictable branches, but higher I-Cache use.
173|  .define ins_next, ins_NEXT
174|  .define ins_next_, ins_NEXT
175|.else
176|  // Common dispatch. Lower I-Cache use, only one (very) unpredictable branch.
177|  // Affects only certain kinds of benchmarks (and only with -j off).
178|  .macro ins_next
179|    b ->ins_next
180|  .endmacro
181|  .macro ins_next_
182|  ->ins_next:
183|    ins_NEXT
184|  .endmacro
185|.endif
186|
187|// Call decode and dispatch.
188|.macro ins_callt
189|  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
190|  ldr PC, LFUNC:CARG3->pc
191|  ldr INSw, [PC], #4
192|  add TMP1, GL, INS, uxtb #3
193|   decode_RA RA, INS
194|  ldr TMP0, [TMP1, #GG_G2DISP]
195|   add RA, BASE, RA, lsl #3
196|  br TMP0
197|.endmacro
198|
199|.macro ins_call
200|  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, PC = caller PC
201|  str PC, [BASE, FRAME_PC]
202|  ins_callt
203|.endmacro
204|
205|//-----------------------------------------------------------------------
206|
207|// Macros to check the TValue type and extract the GCobj. Branch on failure.
208|.macro checktp, reg, tp, target
209|  asr ITYPE, reg, #47
210|  cmn ITYPE, #-tp
211|   and reg, reg, #LJ_GCVMASK
212|  bne target
213|.endmacro
214|.macro checktp, dst, reg, tp, target
215|  asr ITYPE, reg, #47
216|  cmn ITYPE, #-tp
217|   and dst, reg, #LJ_GCVMASK
218|  bne target
219|.endmacro
220|.macro checkstr, reg, target; checktp reg, LJ_TSTR, target; .endmacro
221|.macro checktab, reg, target; checktp reg, LJ_TTAB, target; .endmacro
222|.macro checkfunc, reg, target; checktp reg, LJ_TFUNC, target; .endmacro
223|.macro checkint, reg, target
224|  cmp TISNUMhi, reg, lsr #32
225|  bne target
226|.endmacro
227|.macro checknum, reg, target
228|  cmp TISNUMhi, reg, lsr #32
229|  bls target
230|.endmacro
231|.macro checknumber, reg, target
232|  cmp TISNUMhi, reg, lsr #32
233|  blo target
234|.endmacro
235|
236|.macro mov_false, reg; movn reg, #0x8000, lsl #32; .endmacro
237|.macro mov_true, reg; movn reg, #0x0001, lsl #48; .endmacro
238|
239#define GL_J(field)	(GG_G2J + (int)offsetof(jit_State, field))
240|
241#define PC2PROTO(field)  ((int)offsetof(GCproto, field)-(int)sizeof(GCproto))
242|
243|.macro hotcheck, delta
244|  lsr CARG1, PC, #1
245|  and CARG1, CARG1, #126
246|  add CARG1, CARG1, #GG_G2DISP+GG_DISP2HOT
247|  ldrh CARG2w, [GL, CARG1]
248|  subs CARG2, CARG2, #delta
249|  strh CARG2w, [GL, CARG1]
250|.endmacro
251|
252|.macro hotloop
253|  hotcheck HOTCOUNT_LOOP
254|  blo ->vm_hotloop
255|.endmacro
256|
257|.macro hotcall
258|  hotcheck HOTCOUNT_CALL
259|  blo ->vm_hotcall
260|.endmacro
261|
262|// Set current VM state.
263|.macro mv_vmstate, reg, st; movn reg, #LJ_VMST_..st; .endmacro
264|.macro st_vmstate, reg; str reg, GL->vmstate; .endmacro
265|
266|// Move table write barrier back. Overwrites mark and tmp.
267|.macro barrierback, tab, mark, tmp
268|  ldr tmp, GL->gc.grayagain
269|   and mark, mark, #~LJ_GC_BLACK	// black2gray(tab)
270|  str tab, GL->gc.grayagain
271|   strb mark, tab->marked
272|  str tmp, tab->gclist
273|.endmacro
274|
275|//-----------------------------------------------------------------------
276
277#if !LJ_DUALNUM
278#error "Only dual-number mode supported for ARM64 target"
279#endif
280
281/* Generate subroutines used by opcodes and other parts of the VM. */
282/* The .code_sub section should be last to help static branch prediction. */
283static void build_subroutines(BuildCtx *ctx)
284{
285  |.code_sub
286  |
287  |//-----------------------------------------------------------------------
288  |//-- Return handling ----------------------------------------------------
289  |//-----------------------------------------------------------------------
290  |
291  |->vm_returnp:
292  |  // See vm_return. Also: RB = previous base.
293  |  tbz PC, #2, ->cont_dispatch	// (PC & FRAME_P) == 0?
294  |
295  |  // Return from pcall or xpcall fast func.
296  |  ldr PC, [RB, FRAME_PC]		// Fetch PC of previous frame.
297  |   mov_true TMP0
298  |  mov BASE, RB
299  |  // Prepending may overwrite the pcall frame, so do it at the end.
300  |   str TMP0, [RA, #-8]!		// Prepend true to results.
301  |
302  |->vm_returnc:
303  |  adds RC, RC, #8			// RC = (nresults+1)*8.
304  |  mov CRET1, #LUA_YIELD
305  |  beq ->vm_unwind_c_eh
306  |  str RCw, SAVE_MULTRES
307  |  ands CARG1, PC, #FRAME_TYPE
308  |  beq ->BC_RET_Z			// Handle regular return to Lua.
309  |
310  |->vm_return:
311  |  // BASE = base, RA = resultptr, RC/MULTRES = (nresults+1)*8, PC = return
312  |  // CARG1 = PC & FRAME_TYPE
313  |  and RB, PC, #~FRAME_TYPEP
314  |   cmp CARG1, #FRAME_C
315  |  sub RB, BASE, RB			// RB = previous base.
316  |   bne ->vm_returnp
317  |
318  |  str RB, L->base
319  |   ldrsw CARG2, SAVE_NRES		// CARG2 = nresults+1.
320  |    mv_vmstate TMP0w, C
321  |   sub BASE, BASE, #16
322  |  subs TMP2, RC, #8
323  |    st_vmstate TMP0w
324  |  beq >2
325  |1:
326  |  subs TMP2, TMP2, #8
327  |   ldr TMP0, [RA], #8
328  |   str TMP0, [BASE], #8
329  |  bne <1
330  |2:
331  |  cmp RC, CARG2, lsl #3		// More/less results wanted?
332  |  bne >6
333  |3:
334  |  str BASE, L->top			// Store new top.
335  |
336  |->vm_leave_cp:
337  |  ldr RC, SAVE_CFRAME		// Restore previous C frame.
338  |   mov CRET1, #0			// Ok return status for vm_pcall.
339  |  str RC, L->cframe
340  |
341  |->vm_leave_unw:
342  |  restoreregs
343  |  ret
344  |
345  |6:
346  |  bgt >7				// Less results wanted?
347  |  // More results wanted. Check stack size and fill up results with nil.
348  |  ldr CARG3, L->maxstack
349  |  cmp BASE, CARG3
350  |  bhs >8
351  |   str TISNIL, [BASE], #8
352  |  add RC, RC, #8
353  |  b <2
354  |
355  |7:  // Less results wanted.
356  |  cbz CARG2, <3			// LUA_MULTRET+1 case?
357  |  sub CARG1, RC, CARG2, lsl #3
358  |  sub BASE, BASE, CARG1		// Shrink top.
359  |  b <3
360  |
361  |8:  // Corner case: need to grow stack for filling up results.
362  |  // This can happen if:
363  |  // - A C function grows the stack (a lot).
364  |  // - The GC shrinks the stack in between.
365  |  // - A return back from a lua_call() with (high) nresults adjustment.
366  |  str BASE, L->top			// Save current top held in BASE (yes).
367  |  mov CARG1, L
368  |  bl extern lj_state_growstack	// (lua_State *L, int n)
369  |  ldr BASE, L->top			// Need the (realloced) L->top in BASE.
370  |  ldrsw CARG2, SAVE_NRES
371  |  b <2
372  |
373  |->vm_unwind_c:			// Unwind C stack, return from vm_pcall.
374  |  // (void *cframe, int errcode)
375  |  mov sp, CARG1
376  |  mov CRET1, CARG2
377  |->vm_unwind_c_eh:			// Landing pad for external unwinder.
378  |  ldr L, SAVE_L
379  |   mv_vmstate TMP0w, C
380  |  ldr GL, L->glref
381  |   st_vmstate TMP0w
382  |  b ->vm_leave_unw
383  |
384  |->vm_unwind_ff:			// Unwind C stack, return from ff pcall.
385  |  // (void *cframe)
386  |  and sp, CARG1, #CFRAME_RAWMASK
387  |->vm_unwind_ff_eh:			// Landing pad for external unwinder.
388  |  ldr L, SAVE_L
389  |    movz TISNUM, #(LJ_TISNUM>>1)&0xffff, lsl #48
390  |    movz TISNUMhi, #(LJ_TISNUM>>1)&0xffff, lsl #16
391  |    movn TISNIL, #0
392  |    mov RC, #16			// 2 results: false + error message.
393  |  ldr BASE, L->base
394  |   ldr GL, L->glref			// Setup pointer to global state.
395  |    mov_false TMP0
396  |  sub RA, BASE, #8			// Results start at BASE-8.
397  |  ldr PC, [BASE, FRAME_PC]		// Fetch PC of previous frame.
398  |    str TMP0, [BASE, #-8]		// Prepend false to error message.
399  |   st_vmstate ST_INTERP
400  |  b ->vm_returnc
401  |
402  |//-----------------------------------------------------------------------
403  |//-- Grow stack for calls -----------------------------------------------
404  |//-----------------------------------------------------------------------
405  |
406  |->vm_growstack_c:			// Grow stack for C function.
407  |  // CARG1 = L
408  |  mov CARG2, #LUA_MINSTACK
409  |  b >2
410  |
411  |->vm_growstack_l:			// Grow stack for Lua function.
412  |  // BASE = new base, RA = BASE+framesize*8, RC = nargs*8, PC = first PC
413  |  add RC, BASE, RC
414  |   sub RA, RA, BASE
415  |    mov CARG1, L
416  |  stp BASE, RC, L->base
417  |   add PC, PC, #4			// Must point after first instruction.
418  |   lsr CARG2, RA, #3
419  |2:
420  |  // L->base = new base, L->top = top
421  |  str PC, SAVE_PC
422  |  bl extern lj_state_growstack	// (lua_State *L, int n)
423  |  ldp BASE, RC, L->base
424  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]
425  |   sub NARGS8:RC, RC, BASE
426  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
427  |  // BASE = new base, RB = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
428  |  ins_callt				// Just retry the call.
429  |
430  |//-----------------------------------------------------------------------
431  |//-- Entry points into the assembler VM ---------------------------------
432  |//-----------------------------------------------------------------------
433  |
434  |->vm_resume:				// Setup C frame and resume thread.
435  |  // (lua_State *L, TValue *base, int nres1 = 0, ptrdiff_t ef = 0)
436  |  saveregs
437  |  mov L, CARG1
438  |    ldr GL, L->glref			// Setup pointer to global state.
439  |  mov BASE, CARG2
440  |   str L, SAVE_L
441  |  mov PC, #FRAME_CP
442  |   str wzr, SAVE_NRES
443  |    add TMP0, sp, #CFRAME_RESUME
444  |  ldrb TMP1w, L->status
445  |   str wzr, SAVE_ERRF
446  |   str L, SAVE_PC			// Any value outside of bytecode is ok.
447  |   str xzr, SAVE_CFRAME
448  |    str TMP0, L->cframe
449  |  cbz TMP1w, >3
450  |
451  |  // Resume after yield (like a return).
452  |  str L, GL->cur_L
453  |  mov RA, BASE
454  |   ldp BASE, CARG1, L->base
455  |    movz TISNUM, #(LJ_TISNUM>>1)&0xffff, lsl #48
456  |    movz TISNUMhi, #(LJ_TISNUM>>1)&0xffff, lsl #16
457  |  ldr PC, [BASE, FRAME_PC]
458  |     strb wzr, L->status
459  |    movn TISNIL, #0
460  |   sub RC, CARG1, BASE
461  |  ands CARG1, PC, #FRAME_TYPE
462  |   add RC, RC, #8
463  |     st_vmstate ST_INTERP
464  |   str RCw, SAVE_MULTRES
465  |  beq ->BC_RET_Z
466  |  b ->vm_return
467  |
468  |->vm_pcall:				// Setup protected C frame and enter VM.
469  |  // (lua_State *L, TValue *base, int nres1, ptrdiff_t ef)
470  |  saveregs
471  |  mov PC, #FRAME_CP
472  |  str CARG4w, SAVE_ERRF
473  |  b >1
474  |
475  |->vm_call:				// Setup C frame and enter VM.
476  |  // (lua_State *L, TValue *base, int nres1)
477  |  saveregs
478  |  mov PC, #FRAME_C
479  |
480  |1:  // Entry point for vm_pcall above (PC = ftype).
481  |  ldr RC, L:CARG1->cframe
482  |   str CARG3w, SAVE_NRES
483  |    mov L, CARG1
484  |   str CARG1, SAVE_L
485  |    ldr GL, L->glref			// Setup pointer to global state.
486  |     mov BASE, CARG2
487  |   str CARG1, SAVE_PC		// Any value outside of bytecode is ok.
488  |  str RC, SAVE_CFRAME
489  |  str fp, L->cframe			// Add our C frame to cframe chain.
490  |
491  |3:  // Entry point for vm_cpcall/vm_resume (BASE = base, PC = ftype).
492  |  str L, GL->cur_L
493  |  ldp RB, CARG1, L->base		// RB = old base (for vmeta_call).
494  |    movz TISNUM, #(LJ_TISNUM>>1)&0xffff, lsl #48
495  |    movz TISNUMhi, #(LJ_TISNUM>>1)&0xffff, lsl #16
496  |  add PC, PC, BASE
497  |    movn TISNIL, #0
498  |  sub PC, PC, RB			// PC = frame delta + frame type
499  |   sub NARGS8:RC, CARG1, BASE
500  |    st_vmstate ST_INTERP
501  |
502  |->vm_call_dispatch:
503  |  // RB = old base, BASE = new base, RC = nargs*8, PC = caller PC
504  |  ldr CARG3, [BASE, FRAME_FUNC]
505  |  checkfunc CARG3, ->vmeta_call
506  |
507  |->vm_call_dispatch_f:
508  |  ins_call
509  |  // BASE = new base, CARG3 = func, RC = nargs*8, PC = caller PC
510  |
511  |->vm_cpcall:				// Setup protected C frame, call C.
512  |  // (lua_State *L, lua_CFunction func, void *ud, lua_CPFunction cp)
513  |  saveregs
514  |  mov L, CARG1
515  |   ldr RA, L:CARG1->stack
516  |  str CARG1, SAVE_L
517  |    ldr GL, L->glref			// Setup pointer to global state.
518  |   ldr RB, L->top
519  |  str CARG1, SAVE_PC			// Any value outside of bytecode is ok.
520  |  ldr RC, L->cframe
521  |   sub RA, RA, RB			// Compute -savestack(L, L->top).
522  |   str RAw, SAVE_NRES		// Neg. delta means cframe w/o frame.
523  |  str wzr, SAVE_ERRF			// No error function.
524  |  str RC, SAVE_CFRAME
525  |  str fp, L->cframe			// Add our C frame to cframe chain.
526  |    str L, GL->cur_L
527  |  blr CARG4			// (lua_State *L, lua_CFunction func, void *ud)
528  |  mov BASE, CRET1
529  |   mov PC, #FRAME_CP
530  |  cbnz BASE, <3			// Else continue with the call.
531  |  b ->vm_leave_cp			// No base? Just remove C frame.
532  |
533  |//-----------------------------------------------------------------------
534  |//-- Metamethod handling ------------------------------------------------
535  |//-----------------------------------------------------------------------
536  |
537  |//-- Continuation dispatch ----------------------------------------------
538  |
539  |->cont_dispatch:
540  |  // BASE = meta base, RA = resultptr, RC = (nresults+1)*8
541  |  ldr LFUNC:CARG3, [RB, FRAME_FUNC]
542  |    ldr CARG1, [BASE, #-32]		// Get continuation.
543  |   mov CARG4, BASE
544  |   mov BASE, RB			// Restore caller BASE.
545  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
546  |.if FFI
547  |    cmp CARG1, #1
548  |.endif
549  |   ldr PC, [CARG4, #-24]		// Restore PC from [cont|PC].
550  |  ldr CARG3, LFUNC:CARG3->pc
551  |    add TMP0, RA, RC
552  |    str TISNIL, [TMP0, #-8]		// Ensure one valid arg.
553  |.if FFI
554  |    bls >1
555  |.endif
556  |  ldr KBASE, [CARG3, #PC2PROTO(k)]
557  |  // BASE = base, RA = resultptr, CARG4 = meta base
558  |    br CARG1
559  |
560  |.if FFI
561  |1:
562  |  beq ->cont_ffi_callback		// cont = 1: return from FFI callback.
563  |  // cont = 0: tailcall from C function.
564  |   sub CARG4, CARG4, #32
565  |   sub RC, CARG4, BASE
566  |  b ->vm_call_tail
567  |.endif
568  |
569  |->cont_cat:				// RA = resultptr, CARG4 = meta base
570  |  ldr INSw, [PC, #-4]
571  |   sub CARG2, CARG4, #32
572  |   ldr TMP0, [RA]
573  |     str BASE, L->base
574  |  decode_RB RB, INS
575  |   decode_RA RA, INS
576  |  add TMP1, BASE, RB, lsl #3
577  |  subs TMP1, CARG2, TMP1
578  |  beq >1
579  |   str TMP0, [CARG2]
580  |  lsr CARG3, TMP1, #3
581  |  b ->BC_CAT_Z
582  |
583  |1:
584  |   str TMP0, [BASE, RA, lsl #3]
585  |  b ->cont_nop
586  |
587  |//-- Table indexing metamethods -----------------------------------------
588  |
589  |->vmeta_tgets1:
590  |  movn CARG4, #~LJ_TSTR
591  |   add CARG2, BASE, RB, lsl #3
592  |  add CARG4, STR:RC, CARG4, lsl #47
593  |  b >2
594  |
595  |->vmeta_tgets:
596  |  movk CARG2, #(LJ_TTAB>>1)&0xffff, lsl #48
597  |  str CARG2, GL->tmptv
598  |  add CARG2, GL, #offsetof(global_State, tmptv)
599  |2:
600  |   add CARG3, sp, TMPDofs
601  |  str CARG4, TMPD
602  |  b >1
603  |
604  |->vmeta_tgetb:			// RB = table, RC = index
605  |  add RC, RC, TISNUM
606  |   add CARG2, BASE, RB, lsl #3
607  |   add CARG3, sp, TMPDofs
608  |  str RC, TMPD
609  |  b >1
610  |
611  |->vmeta_tgetv:			// RB = table, RC = key
612  |  add CARG2, BASE, RB, lsl #3
613  |   add CARG3, BASE, RC, lsl #3
614  |1:
615  |   str BASE, L->base
616  |  mov CARG1, L
617  |   str PC, SAVE_PC
618  |  bl extern lj_meta_tget		// (lua_State *L, TValue *o, TValue *k)
619  |  // Returns TValue * (finished) or NULL (metamethod).
620  |  cbz CRET1, >3
621  |  ldr TMP0, [CRET1]
622  |  str TMP0, [BASE, RA, lsl #3]
623  |  ins_next
624  |
625  |3:  // Call __index metamethod.
626  |  // BASE = base, L->top = new base, stack = cont/func/t/k
627  |   sub TMP1, BASE, #FRAME_CONT
628  |  ldr BASE, L->top
629  |    mov NARGS8:RC, #16		// 2 args for func(t, k).
630  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]  // Guaranteed to be a function here.
631  |    str PC, [BASE, #-24]		// [cont|PC]
632  |   sub PC, BASE, TMP1
633  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
634  |  b ->vm_call_dispatch_f
635  |
636  |->vmeta_tgetr:
637  |  sxtw CARG2, TMP1w
638  |  bl extern lj_tab_getinth		// (GCtab *t, int32_t key)
639  |  // Returns cTValue * or NULL.
640  |  mov TMP0, TISNIL
641  |  cbz CRET1, ->BC_TGETR_Z
642  |  ldr TMP0, [CRET1]
643  |  b ->BC_TGETR_Z
644  |
645  |//-----------------------------------------------------------------------
646  |
647  |->vmeta_tsets1:
648  |  movn CARG4, #~LJ_TSTR
649  |   add CARG2, BASE, RB, lsl #3
650  |  add CARG4, STR:RC, CARG4, lsl #47
651  |  b >2
652  |
653  |->vmeta_tsets:
654  |  movk CARG2, #(LJ_TTAB>>1)&0xffff, lsl #48
655  |  str CARG2, GL->tmptv
656  |  add CARG2, GL, #offsetof(global_State, tmptv)
657  |2:
658  |   add CARG3, sp, TMPDofs
659  |  str CARG4, TMPD
660  |  b >1
661  |
662  |->vmeta_tsetb:			// RB = table, RC = index
663  |  add RC, RC, TISNUM
664  |   add CARG2, BASE, RB, lsl #3
665  |   add CARG3, sp, TMPDofs
666  |  str RC, TMPD
667  |  b >1
668  |
669  |->vmeta_tsetv:
670  |  add CARG2, BASE, RB, lsl #3
671  |   add CARG3, BASE, RC, lsl #3
672  |1:
673  |   str BASE, L->base
674  |  mov CARG1, L
675  |   str PC, SAVE_PC
676  |  bl extern lj_meta_tset		// (lua_State *L, TValue *o, TValue *k)
677  |  // Returns TValue * (finished) or NULL (metamethod).
678  |   ldr TMP0, [BASE, RA, lsl #3]
679  |  cbz CRET1, >3
680  |  // NOBARRIER: lj_meta_tset ensures the table is not black.
681  |   str TMP0, [CRET1]
682  |  ins_next
683  |
684  |3:  // Call __newindex metamethod.
685  |  // BASE = base, L->top = new base, stack = cont/func/t/k/(v)
686  |   sub TMP1, BASE, #FRAME_CONT
687  |  ldr BASE, L->top
688  |    mov NARGS8:RC, #24		// 3 args for func(t, k, v).
689  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]  // Guaranteed to be a function here.
690  |   str TMP0, [BASE, #16]		// Copy value to third argument.
691  |    str PC, [BASE, #-24]		// [cont|PC]
692  |   sub PC, BASE, TMP1
693  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
694  |  b ->vm_call_dispatch_f
695  |
696  |->vmeta_tsetr:
697  |  sxtw CARG3, TMP1w
698  |  str BASE, L->base
699  |  str PC, SAVE_PC
700  |  bl extern lj_tab_setinth  // (lua_State *L, GCtab *t, int32_t key)
701  |  // Returns TValue *.
702  |  b ->BC_TSETR_Z
703  |
704  |//-- Comparison metamethods ---------------------------------------------
705  |
706  |->vmeta_comp:
707  |  add CARG2, BASE, RA, lsl #3
708  |   sub PC, PC, #4
709  |  add CARG3, BASE, RC, lsl #3
710  |   str BASE, L->base
711  |  mov CARG1, L
712  |   str PC, SAVE_PC
713  |  uxtb CARG4w, INSw
714  |  bl extern lj_meta_comp  // (lua_State *L, TValue *o1, *o2, int op)
715  |  // Returns 0/1 or TValue * (metamethod).
716  |3:
717  |  cmp CRET1, #1
718  |  bhi ->vmeta_binop
719  |4:
720  |   ldrh RBw, [PC, #2]
721  |    add PC, PC, #4
722  |   add RB, PC, RB, lsl #2
723  |   sub RB, RB, #0x20000
724  |  csel PC, PC, RB, lo
725  |->cont_nop:
726  |  ins_next
727  |
728  |->cont_ra:				// RA = resultptr
729  |  ldr INSw, [PC, #-4]
730  |   ldr TMP0, [RA]
731  |  decode_RA TMP1, INS
732  |   str TMP0, [BASE, TMP1, lsl #3]
733  |  b ->cont_nop
734  |
735  |->cont_condt:			// RA = resultptr
736  |  ldr TMP0, [RA]
737  |   mov_true TMP1
738  |  cmp TMP1, TMP0			// Branch if result is true.
739  |  b <4
740  |
741  |->cont_condf:			// RA = resultptr
742  |  ldr TMP0, [RA]
743  |   mov_false TMP1
744  |  cmp TMP0, TMP1			// Branch if result is false.
745  |  b <4
746  |
747  |->vmeta_equal:
748  |  // CARG2, CARG3, CARG4 are already set by BC_ISEQV/BC_ISNEV.
749  |  and TAB:CARG3, CARG3, #LJ_GCVMASK
750  |  sub PC, PC, #4
751  |   str BASE, L->base
752  |   mov CARG1, L
753  |  str PC, SAVE_PC
754  |  bl extern lj_meta_equal  // (lua_State *L, GCobj *o1, *o2, int ne)
755  |  // Returns 0/1 or TValue * (metamethod).
756  |  b <3
757  |
758  |->vmeta_equal_cd:
759  |.if FFI
760  |  sub PC, PC, #4
761  |   str BASE, L->base
762  |   mov CARG1, L
763  |   mov CARG2, INS
764  |  str PC, SAVE_PC
765  |  bl extern lj_meta_equal_cd		// (lua_State *L, BCIns op)
766  |  // Returns 0/1 or TValue * (metamethod).
767  |  b <3
768  |.endif
769  |
770  |->vmeta_istype:
771  |  sub PC, PC, #4
772  |   str BASE, L->base
773  |   mov CARG1, L
774  |   mov CARG2, RA
775  |   mov CARG3, RC
776  |  str PC, SAVE_PC
777  |  bl extern lj_meta_istype  // (lua_State *L, BCReg ra, BCReg tp)
778  |  b ->cont_nop
779  |
780  |//-- Arithmetic metamethods ---------------------------------------------
781  |
782  |->vmeta_arith_vn:
783  |  add CARG3, BASE, RB, lsl #3
784  |   add CARG4, KBASE, RC, lsl #3
785  |  b >1
786  |
787  |->vmeta_arith_nv:
788  |  add CARG4, BASE, RB, lsl #3
789  |   add CARG3, KBASE, RC, lsl #3
790  |  b >1
791  |
792  |->vmeta_unm:
793  |  add CARG3, BASE, RC, lsl #3
794  |  mov CARG4, CARG3
795  |  b >1
796  |
797  |->vmeta_arith_vv:
798  |  add CARG3, BASE, RB, lsl #3
799  |   add CARG4, BASE, RC, lsl #3
800  |1:
801  |  uxtb CARG5w, INSw
802  |   add CARG2, BASE, RA, lsl #3
803  |    str BASE, L->base
804  |   mov CARG1, L
805  |    str PC, SAVE_PC
806  |  bl extern lj_meta_arith  // (lua_State *L, TValue *ra,*rb,*rc, BCReg op)
807  |  // Returns NULL (finished) or TValue * (metamethod).
808  |  cbz CRET1, ->cont_nop
809  |
810  |  // Call metamethod for binary op.
811  |->vmeta_binop:
812  |  // BASE = old base, CRET1 = new base, stack = cont/func/o1/o2
813  |  sub TMP1, CRET1, BASE
814  |   str PC, [CRET1, #-24]		// [cont|PC]
815  |  add PC, TMP1, #FRAME_CONT
816  |  mov BASE, CRET1
817  |   mov NARGS8:RC, #16		// 2 args for func(o1, o2).
818  |  b ->vm_call_dispatch
819  |
820  |->vmeta_len:
821  |  add CARG2, BASE, RC, lsl #3
822#if LJ_52
823  |  mov TAB:RC, TAB:CARG1		// Save table (ignored for other types).
824#endif
825  |   str BASE, L->base
826  |  mov CARG1, L
827  |   str PC, SAVE_PC
828  |  bl extern lj_meta_len		// (lua_State *L, TValue *o)
829  |  // Returns NULL (retry) or TValue * (metamethod base).
830#if LJ_52
831  |  cbnz CRET1, ->vmeta_binop		// Binop call for compatibility.
832  |  mov TAB:CARG1, TAB:RC
833  |  b ->BC_LEN_Z
834#else
835  |  b ->vmeta_binop			// Binop call for compatibility.
836#endif
837  |
838  |//-- Call metamethod ----------------------------------------------------
839  |
840  |->vmeta_call:			// Resolve and call __call metamethod.
841  |  // RB = old base, BASE = new base, RC = nargs*8
842  |  mov CARG1, L
843  |   str RB, L->base			// This is the callers base!
844  |  sub CARG2, BASE, #16
845  |   str PC, SAVE_PC
846  |  add CARG3, BASE, NARGS8:RC
847  |  bl extern lj_meta_call	// (lua_State *L, TValue *func, TValue *top)
848  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]  // Guaranteed to be a function here.
849  |   add NARGS8:RC, NARGS8:RC, #8	// Got one more argument now.
850  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
851  |  ins_call
852  |
853  |->vmeta_callt:			// Resolve __call for BC_CALLT.
854  |  // BASE = old base, RA = new base, RC = nargs*8
855  |  mov CARG1, L
856  |   str BASE, L->base
857  |  sub CARG2, RA, #16
858  |   str PC, SAVE_PC
859  |  add CARG3, RA, NARGS8:RC
860  |  bl extern lj_meta_call	// (lua_State *L, TValue *func, TValue *top)
861  |  ldr TMP1, [RA, FRAME_FUNC]		// Guaranteed to be a function here.
862  |   ldr PC, [BASE, FRAME_PC]
863  |   add NARGS8:RC, NARGS8:RC, #8	// Got one more argument now.
864  |  and LFUNC:CARG3, TMP1, #LJ_GCVMASK
865  |  b ->BC_CALLT2_Z
866  |
867  |//-- Argument coercion for 'for' statement ------------------------------
868  |
869  |->vmeta_for:
870  |  mov CARG1, L
871  |   str BASE, L->base
872  |  mov CARG2, RA
873  |   str PC, SAVE_PC
874  |  bl extern lj_meta_for	// (lua_State *L, TValue *base)
875  |  ldr INSw, [PC, #-4]
876  |.if JIT
877  |   uxtb TMP0w, INSw
878  |.endif
879  |  decode_RA RA, INS
880  |  decode_RD RC, INS
881  |.if JIT
882  |   cmp TMP0, #BC_JFORI
883  |   beq =>BC_JFORI
884  |.endif
885  |  b =>BC_FORI
886  |
887  |//-----------------------------------------------------------------------
888  |//-- Fast functions -----------------------------------------------------
889  |//-----------------------------------------------------------------------
890  |
891  |.macro .ffunc, name
892  |->ff_ .. name:
893  |.endmacro
894  |
895  |.macro .ffunc_1, name
896  |->ff_ .. name:
897  |  ldr CARG1, [BASE]
898  |   cmp NARGS8:RC, #8
899  |   blo ->fff_fallback
900  |.endmacro
901  |
902  |.macro .ffunc_2, name
903  |->ff_ .. name:
904  |  ldp CARG1, CARG2, [BASE]
905  |   cmp NARGS8:RC, #16
906  |   blo ->fff_fallback
907  |.endmacro
908  |
909  |.macro .ffunc_n, name
910  |  .ffunc name
911  |  ldr CARG1, [BASE]
912  |   cmp NARGS8:RC, #8
913  |  ldr FARG1, [BASE]
914  |   blo ->fff_fallback
915  |  checknum CARG1, ->fff_fallback
916  |.endmacro
917  |
918  |.macro .ffunc_nn, name
919  |  .ffunc name
920  |  ldp CARG1, CARG2, [BASE]
921  |   cmp NARGS8:RC, #16
922  |  ldp FARG1, FARG2, [BASE]
923  |   blo ->fff_fallback
924  |  checknum CARG1, ->fff_fallback
925  |  checknum CARG2, ->fff_fallback
926  |.endmacro
927  |
928  |// Inlined GC threshold check. Caveat: uses CARG1 and CARG2.
929  |.macro ffgccheck
930  |  ldp CARG1, CARG2, GL->gc.total	// Assumes threshold follows total.
931  |  cmp CARG1, CARG2
932  |  blt >1
933  |  bl ->fff_gcstep
934  |1:
935  |.endmacro
936  |
937  |//-- Base library: checks -----------------------------------------------
938  |
939  |.ffunc_1 assert
940  |   ldr PC, [BASE, FRAME_PC]
941  |  mov_false TMP1
942  |  cmp CARG1, TMP1
943  |  bhs ->fff_fallback
944  |  str CARG1, [BASE, #-16]
945  |  sub RB, BASE, #8
946  |  subs RA, NARGS8:RC, #8
947  |   add RC, NARGS8:RC, #8		// Compute (nresults+1)*8.
948  |  cbz RA, ->fff_res			// Done if exactly 1 argument.
949  |1:
950  |   ldr CARG1, [RB, #16]
951  |  sub RA, RA, #8
952  |   str CARG1, [RB], #8
953  |  cbnz RA, <1
954  |  b ->fff_res
955  |
956  |.ffunc_1 type
957  |  mov TMP0, #~LJ_TISNUM
958  |  asr ITYPE, CARG1, #47
959  |  cmn ITYPE, #~LJ_TISNUM
960  |  csinv TMP1, TMP0, ITYPE, lo
961  |  add TMP1, TMP1, #offsetof(GCfuncC, upvalue)/8
962  |  ldr CARG1, [CFUNC:CARG3, TMP1, lsl #3]
963  |  b ->fff_restv
964  |
965  |//-- Base library: getters and setters ---------------------------------
966  |
967  |.ffunc_1 getmetatable
968  |  asr ITYPE, CARG1, #47
969  |  cmn ITYPE, #-LJ_TTAB
970  |  ccmn ITYPE, #-LJ_TUDATA, #4, ne
971  |   and TAB:CARG1, CARG1, #LJ_GCVMASK
972  |  bne >6
973  |1:  // Field metatable must be at same offset for GCtab and GCudata!
974  |  ldr TAB:RB, TAB:CARG1->metatable
975  |2:
976  |   mov CARG1, TISNIL
977  |   ldr STR:RC, GL->gcroot[GCROOT_MMNAME+MM_metatable]
978  |  cbz TAB:RB, ->fff_restv
979  |  ldr TMP1w, TAB:RB->hmask
980  |   ldr TMP2w, STR:RC->hash
981  |    ldr NODE:CARG3, TAB:RB->node
982  |  and TMP1w, TMP1w, TMP2w		// idx = str->hash & tab->hmask
983  |  add TMP1, TMP1, TMP1, lsl #1
984  |  movn CARG4, #~LJ_TSTR
985  |    add NODE:CARG3, NODE:CARG3, TMP1, lsl #3  // node = tab->node + idx*3*8
986  |  add CARG4, STR:RC, CARG4, lsl #47	// Tagged key to look for.
987  |3:  // Rearranged logic, because we expect _not_ to find the key.
988  |  ldp CARG1, TMP0, NODE:CARG3->val
989  |   ldr NODE:CARG3, NODE:CARG3->next
990  |  cmp TMP0, CARG4
991  |  beq >5
992  |  cbnz NODE:CARG3, <3
993  |4:
994  |  mov CARG1, RB			// Use metatable as default result.
995  |  movk CARG1, #(LJ_TTAB>>1)&0xffff, lsl #48
996  |  b ->fff_restv
997  |5:
998  |  cmp TMP0, TISNIL
999  |  bne ->fff_restv
1000  |  b <4
1001  |
1002  |6:
1003  |  movn TMP0, #~LJ_TISNUM
1004  |  cmp ITYPE, TMP0
1005  |  csel ITYPE, ITYPE, TMP0, hs
1006  |  sub TMP1, GL, ITYPE, lsl #3
1007  |  ldr TAB:RB, [TMP1, #offsetof(global_State, gcroot[GCROOT_BASEMT])-8]
1008  |  b <2
1009  |
1010  |.ffunc_2 setmetatable
1011  |  // Fast path: no mt for table yet and not clearing the mt.
1012  |  checktp TMP1, CARG1, LJ_TTAB, ->fff_fallback
1013  |   ldr TAB:TMP0, TAB:TMP1->metatable
1014  |  asr ITYPE, CARG2, #47
1015  |   ldrb TMP2w, TAB:TMP1->marked
1016  |  cmn ITYPE, #-LJ_TTAB
1017  |    and TAB:CARG2, CARG2, #LJ_GCVMASK
1018  |  ccmp TAB:TMP0, #0, #0, eq
1019  |  bne ->fff_fallback
1020  |    str TAB:CARG2, TAB:TMP1->metatable
1021  |   tbz TMP2w, #2, ->fff_restv	// isblack(table)
1022  |  barrierback TAB:TMP1, TMP2w, TMP0
1023  |  b ->fff_restv
1024  |
1025  |.ffunc rawget
1026  |  ldr CARG2, [BASE]
1027  |   cmp NARGS8:RC, #16
1028  |   blo ->fff_fallback
1029  |  checktab CARG2, ->fff_fallback
1030  |   mov CARG1, L
1031  |   add CARG3, BASE, #8
1032  |  bl extern lj_tab_get  // (lua_State *L, GCtab *t, cTValue *key)
1033  |  // Returns cTValue *.
1034  |  ldr CARG1, [CRET1]
1035  |  b ->fff_restv
1036  |
1037  |//-- Base library: conversions ------------------------------------------
1038  |
1039  |.ffunc tonumber
1040  |  // Only handles the number case inline (without a base argument).
1041  |  ldr CARG1, [BASE]
1042  |   cmp NARGS8:RC, #8
1043  |   bne ->fff_fallback
1044  |  checknumber CARG1, ->fff_fallback
1045  |  b ->fff_restv
1046  |
1047  |.ffunc_1 tostring
1048  |  // Only handles the string or number case inline.
1049  |  asr ITYPE, CARG1, #47
1050  |  cmn ITYPE, #-LJ_TSTR
1051  |  // A __tostring method in the string base metatable is ignored.
1052  |  beq ->fff_restv
1053  |  // Handle numbers inline, unless a number base metatable is present.
1054  |  ldr TMP1, GL->gcroot[GCROOT_BASEMT_NUM]
1055  |   str BASE, L->base
1056  |  cmn ITYPE, #-LJ_TISNUM
1057  |  ccmp TMP1, #0, #0, ls
1058  |   str PC, SAVE_PC			// Redundant (but a defined value).
1059  |  bne ->fff_fallback
1060  |  ffgccheck
1061  |  mov CARG1, L
1062  |  mov CARG2, BASE
1063  |  bl extern lj_strfmt_number		// (lua_State *L, cTValue *o)
1064  |  // Returns GCstr *.
1065  |   movn TMP1, #~LJ_TSTR
1066  |  ldr BASE, L->base
1067  |   add CARG1, CARG1, TMP1, lsl #47
1068  |  b ->fff_restv
1069  |
1070  |//-- Base library: iterators -------------------------------------------
1071  |
1072  |.ffunc_1 next
1073  |  checktp CARG2, CARG1, LJ_TTAB, ->fff_fallback
1074  |  str TISNIL, [BASE, NARGS8:RC]	// Set missing 2nd arg to nil.
1075  |  ldr PC, [BASE, FRAME_PC]
1076  |   stp BASE, BASE, L->base		// Add frame since C call can throw.
1077  |  mov CARG1, L
1078  |  add CARG3, BASE, #8
1079  |   str PC, SAVE_PC
1080  |  bl extern lj_tab_next	// (lua_State *L, GCtab *t, TValue *key)
1081  |  // Returns 0 at end of traversal.
1082  |  str TISNIL, [BASE, #-16]
1083  |  cbz CRET1, ->fff_res1		// End of traversal: return nil.
1084  |  ldp CARG1, CARG2, [BASE, #8]	// Copy key and value to results.
1085  |    mov RC, #(2+1)*8
1086  |  stp CARG1, CARG2, [BASE, #-16]
1087  |  b ->fff_res
1088  |
1089  |.ffunc_1 pairs
1090  |  checktp TMP1, CARG1, LJ_TTAB, ->fff_fallback
1091#if LJ_52
1092  |  ldr TAB:CARG2, TAB:TMP1->metatable
1093#endif
1094  |   ldr CFUNC:CARG4, CFUNC:CARG3->upvalue[0]
1095  |    ldr PC, [BASE, FRAME_PC]
1096#if LJ_52
1097  |  cbnz TAB:CARG2, ->fff_fallback
1098#endif
1099  |  mov RC, #(3+1)*8
1100  |  stp CARG1, TISNIL, [BASE, #-8]
1101  |   str CFUNC:CARG4, [BASE, #-16]
1102  |  b ->fff_res
1103  |
1104  |.ffunc_2 ipairs_aux
1105  |  checktab CARG1, ->fff_fallback
1106  |   checkint CARG2, ->fff_fallback
1107  |  ldr TMP1w, TAB:CARG1->asize
1108  |   ldr CARG3, TAB:CARG1->array
1109  |    ldr TMP0w, TAB:CARG1->hmask
1110  |  add CARG2w, CARG2w, #1
1111  |  cmp CARG2w, TMP1w
1112  |    ldr PC, [BASE, FRAME_PC]
1113  |     add TMP2, CARG2, TISNUM
1114  |   mov RC, #(0+1)*8
1115  |     str TMP2, [BASE, #-16]
1116  |  bhs >2				// Not in array part?
1117  |  ldr TMP0, [CARG3, CARG2, lsl #3]
1118  |1:
1119  |   mov TMP1, #(2+1)*8
1120  |   cmp TMP0, TISNIL
1121  |  str TMP0, [BASE, #-8]
1122  |   csel RC, RC, TMP1, eq
1123  |  b ->fff_res
1124  |2:  // Check for empty hash part first. Otherwise call C function.
1125  |  cbz TMP0w, ->fff_res
1126  |  bl extern lj_tab_getinth		// (GCtab *t, int32_t key)
1127  |  // Returns cTValue * or NULL.
1128  |  cbz CRET1, ->fff_res
1129  |  ldr TMP0, [CRET1]
1130  |  b <1
1131  |
1132  |.ffunc_1 ipairs
1133  |  checktp TMP1, CARG1, LJ_TTAB, ->fff_fallback
1134#if LJ_52
1135  |  ldr TAB:CARG2, TAB:TMP1->metatable
1136#endif
1137  |   ldr CFUNC:CARG4, CFUNC:CARG3->upvalue[0]
1138  |    ldr PC, [BASE, FRAME_PC]
1139#if LJ_52
1140  |  cbnz TAB:CARG2, ->fff_fallback
1141#endif
1142  |  mov RC, #(3+1)*8
1143  |  stp CARG1, TISNUM, [BASE, #-8]
1144  |   str CFUNC:CARG4, [BASE, #-16]
1145  |  b ->fff_res
1146  |
1147  |//-- Base library: catch errors ----------------------------------------
1148  |
1149  |.ffunc pcall
1150  |  ldrb TMP0w, GL->hookmask
1151  |   subs NARGS8:RC, NARGS8:RC, #8
1152  |   blo ->fff_fallback
1153  |    mov RB, BASE
1154  |    add BASE, BASE, #16
1155  |  ubfx TMP0w, TMP0w, #HOOK_ACTIVE_SHIFT, #1
1156  |  add PC, TMP0, #16+FRAME_PCALL
1157  |   beq ->vm_call_dispatch
1158  |1:
1159  |   add TMP2, BASE, NARGS8:RC
1160  |2:
1161  |   ldr TMP0, [TMP2, #-16]
1162  |   str TMP0, [TMP2, #-8]!
1163  |  cmp TMP2, BASE
1164  |  bne <2
1165  |  b ->vm_call_dispatch
1166  |
1167  |.ffunc xpcall
1168  |     ldp CARG1, CARG2, [BASE]
1169  |  ldrb TMP0w, GL->hookmask
1170  |   subs NARGS8:RC, NARGS8:RC, #16
1171  |   blo ->fff_fallback
1172  |    mov RB, BASE
1173  |    add BASE, BASE, #24
1174  |     asr ITYPE, CARG2, #47
1175  |  ubfx TMP0w, TMP0w, #HOOK_ACTIVE_SHIFT, #1
1176  |     cmn ITYPE, #-LJ_TFUNC
1177  |  add PC, TMP0, #24+FRAME_PCALL
1178  |     bne ->fff_fallback		// Traceback must be a function.
1179  |     stp CARG2, CARG1, [RB]		// Swap function and traceback.
1180  |   cbz NARGS8:RC, ->vm_call_dispatch
1181  |  b <1
1182  |
1183  |//-- Coroutine library --------------------------------------------------
1184  |
1185  |.macro coroutine_resume_wrap, resume
1186  |.if resume
1187  |.ffunc_1 coroutine_resume
1188  |  checktp CARG1, LJ_TTHREAD, ->fff_fallback
1189  |.else
1190  |.ffunc coroutine_wrap_aux
1191  |  ldr L:CARG1, CFUNC:CARG3->upvalue[0].gcr
1192  |  and L:CARG1, CARG1, #LJ_GCVMASK
1193  |.endif
1194  |   ldr PC, [BASE, FRAME_PC]
1195  |     str BASE, L->base
1196  |  ldp RB, CARG2, L:CARG1->base
1197  |   ldrb TMP1w, L:CARG1->status
1198  |  add TMP0, CARG2, TMP1
1199  |   str PC, SAVE_PC
1200  |  cmp TMP0, RB
1201  |  beq ->fff_fallback
1202  |   cmp TMP1, #LUA_YIELD
1203  |    add TMP0, CARG2, #8
1204  |   csel CARG2, CARG2, TMP0, hs
1205  |   ldr CARG4, L:CARG1->maxstack
1206  |   add CARG3, CARG2, NARGS8:RC
1207  |    ldr RB, L:CARG1->cframe
1208  |   ccmp CARG3, CARG4, #2, ls
1209  |    ccmp RB, #0, #2, ls
1210  |    bhi ->fff_fallback
1211  |.if resume
1212  |  sub CARG3, CARG3, #8		// Keep resumed thread in stack for GC.
1213  |  add BASE, BASE, #8
1214  |  sub NARGS8:RC, NARGS8:RC, #8
1215  |.endif
1216  |  str CARG3, L:CARG1->top
1217  |  str BASE, L->top
1218  |  cbz NARGS8:RC, >3
1219  |2:  // Move args to coroutine.
1220  |   ldr TMP0, [BASE, RB]
1221  |  cmp RB, NARGS8:RC
1222  |   str TMP0, [CARG2, RB]
1223  |   add RB, RB, #8
1224  |  bne <2
1225  |3:
1226  |  mov CARG3, #0
1227  |   mov L:RA, L:CARG1
1228  |  mov CARG4, #0
1229  |  bl ->vm_resume			// (lua_State *L, TValue *base, 0, 0)
1230  |  // Returns thread status.
1231  |4:
1232  |  ldp CARG3, CARG4, L:RA->base
1233  |   cmp CRET1, #LUA_YIELD
1234  |  ldr BASE, L->base
1235  |    str L, GL->cur_L
1236  |    st_vmstate ST_INTERP
1237  |   bhi >8
1238  |  sub RC, CARG4, CARG3
1239  |   ldr CARG1, L->maxstack
1240  |   add CARG2, BASE, RC
1241  |  cbz RC, >6				// No results?
1242  |  cmp CARG2, CARG1
1243  |   mov RB, #0
1244  |  bhi >9				// Need to grow stack?
1245  |
1246  |  sub CARG4, RC, #8
1247  |   str CARG3, L:RA->top		// Clear coroutine stack.
1248  |5:  // Move results from coroutine.
1249  |   ldr TMP0, [CARG3, RB]
1250  |  cmp RB, CARG4
1251  |   str TMP0, [BASE, RB]
1252  |   add RB, RB, #8
1253  |  bne <5
1254  |6:
1255  |.if resume
1256  |  mov_true TMP1
1257  |   add RC, RC, #16
1258  |7:
1259  |  str TMP1, [BASE, #-8]		// Prepend true/false to results.
1260  |   sub RA, BASE, #8
1261  |.else
1262  |   mov RA, BASE
1263  |   add RC, RC, #8
1264  |.endif
1265  |  ands CARG1, PC, #FRAME_TYPE
1266  |   str PC, SAVE_PC
1267  |   str RCw, SAVE_MULTRES
1268  |  beq ->BC_RET_Z
1269  |  b ->vm_return
1270  |
1271  |8:  // Coroutine returned with error (at co->top-1).
1272  |.if resume
1273  |  ldr TMP0, [CARG4, #-8]!
1274  |   mov_false TMP1
1275  |    mov RC, #(2+1)*8
1276  |  str CARG4, L:RA->top		// Remove error from coroutine stack.
1277  |  str TMP0, [BASE]			// Copy error message.
1278  |  b <7
1279  |.else
1280  |  mov CARG1, L
1281  |  mov CARG2, L:RA
1282  |  bl extern lj_ffh_coroutine_wrap_err  // (lua_State *L, lua_State *co)
1283  |  // Never returns.
1284  |.endif
1285  |
1286  |9:  // Handle stack expansion on return from yield.
1287  |  mov CARG1, L
1288  |  lsr CARG2, RC, #3
1289  |  bl extern lj_state_growstack	// (lua_State *L, int n)
1290  |  mov CRET1, #0
1291  |  b <4
1292  |.endmacro
1293  |
1294  |  coroutine_resume_wrap 1		// coroutine.resume
1295  |  coroutine_resume_wrap 0		// coroutine.wrap
1296  |
1297  |.ffunc coroutine_yield
1298  |  ldr TMP0, L->cframe
1299  |   add TMP1, BASE, NARGS8:RC
1300  |    mov CRET1, #LUA_YIELD
1301  |   stp BASE, TMP1, L->base
1302  |  tbz TMP0, #0, ->fff_fallback
1303  |   str xzr, L->cframe
1304  |    strb CRET1w, L->status
1305  |  b ->vm_leave_unw
1306  |
1307  |//-- Math library -------------------------------------------------------
1308  |
1309  |.macro math_round, func, round
1310  |  .ffunc math_ .. func
1311  |  ldr CARG1, [BASE]
1312  |   cmp NARGS8:RC, #8
1313  |  ldr d0, [BASE]
1314  |   blo ->fff_fallback
1315  |  cmp TISNUMhi, CARG1, lsr #32
1316  |  beq ->fff_restv
1317  |  blo ->fff_fallback
1318  |  round d0, d0
1319  |  b ->fff_resn
1320  |.endmacro
1321  |
1322  |  math_round floor, frintm
1323  |  math_round ceil, frintp
1324  |
1325  |.ffunc_1 math_abs
1326  |  checknumber CARG1, ->fff_fallback
1327  |  and CARG1, CARG1, #U64x(7fffffff,ffffffff)
1328  |  bne ->fff_restv
1329  |  eor CARG2w, CARG1w, CARG1w, asr #31
1330  |   movz CARG3, #0x41e0, lsl #48	// 2^31.
1331  |  subs CARG1w, CARG2w, CARG1w, asr #31
1332  |   add CARG1, CARG1, TISNUM
1333  |  csel CARG1, CARG1, CARG3, pl
1334  |  // Fallthrough.
1335  |
1336  |->fff_restv:
1337  |  // CARG1 = TValue result.
1338  |  ldr PC, [BASE, FRAME_PC]
1339  |  str CARG1, [BASE, #-16]
1340  |->fff_res1:
1341  |  // PC = return.
1342  |  mov RC, #(1+1)*8
1343  |->fff_res:
1344  |  // RC = (nresults+1)*8, PC = return.
1345  |  ands CARG1, PC, #FRAME_TYPE
1346  |   str RCw, SAVE_MULTRES
1347  |   sub RA, BASE, #16
1348  |  bne ->vm_return
1349  |  ldr INSw, [PC, #-4]
1350  |  decode_RB RB, INS
1351  |5:
1352  |  cmp RC, RB, lsl #3			// More results expected?
1353  |  blo >6
1354  |  decode_RA TMP1, INS
1355  |  // Adjust BASE. KBASE is assumed to be set for the calling frame.
1356  |  sub BASE, RA, TMP1, lsl #3
1357  |  ins_next
1358  |
1359  |6:  // Fill up results with nil.
1360  |  add TMP1, RA, RC
1361  |   add RC, RC, #8
1362  |  str TISNIL, [TMP1, #-8]
1363  |  b <5
1364  |
1365  |.macro math_extern, func
1366  |  .ffunc_n math_ .. func
1367  |  bl extern func
1368  |  b ->fff_resn
1369  |.endmacro
1370  |
1371  |.macro math_extern2, func
1372  |  .ffunc_nn math_ .. func
1373  |  bl extern func
1374  |  b ->fff_resn
1375  |.endmacro
1376  |
1377  |.ffunc_n math_sqrt
1378  |  fsqrt d0, d0
1379  |->fff_resn:
1380  |  ldr PC, [BASE, FRAME_PC]
1381  |  str d0, [BASE, #-16]
1382  |  b ->fff_res1
1383  |
1384  |.ffunc math_log
1385  |  ldr CARG1, [BASE]
1386  |   cmp NARGS8:RC, #8
1387  |  ldr FARG1, [BASE]
1388  |   bne ->fff_fallback			// Need exactly 1 argument.
1389  |  checknum CARG1, ->fff_fallback
1390  |  bl extern log
1391  |  b ->fff_resn
1392  |
1393  |  math_extern log10
1394  |  math_extern exp
1395  |  math_extern sin
1396  |  math_extern cos
1397  |  math_extern tan
1398  |  math_extern asin
1399  |  math_extern acos
1400  |  math_extern atan
1401  |  math_extern sinh
1402  |  math_extern cosh
1403  |  math_extern tanh
1404  |  math_extern2 pow
1405  |  math_extern2 atan2
1406  |  math_extern2 fmod
1407  |
1408  |.ffunc_2 math_ldexp
1409  |  ldr FARG1, [BASE]
1410  |  checknum CARG1, ->fff_fallback
1411  |  checkint CARG2, ->fff_fallback
1412  |  sxtw CARG1, CARG2w
1413  |  bl extern ldexp			// (double x, int exp)
1414  |  b ->fff_resn
1415  |
1416  |.ffunc_n math_frexp
1417  |  add CARG1, sp, TMPDofs
1418  |  bl extern frexp
1419  |   ldr CARG2w, TMPD
1420  |    ldr PC, [BASE, FRAME_PC]
1421  |  str d0, [BASE, #-16]
1422  |    mov RC, #(2+1)*8
1423  |   add CARG2, CARG2, TISNUM
1424  |   str CARG2, [BASE, #-8]
1425  |  b ->fff_res
1426  |
1427  |.ffunc_n math_modf
1428  |  sub CARG1, BASE, #16
1429  |   ldr PC, [BASE, FRAME_PC]
1430  |  bl extern modf
1431  |   mov RC, #(2+1)*8
1432  |  str d0, [BASE, #-8]
1433  |  b ->fff_res
1434  |
1435  |.macro math_minmax, name, cond, fcond
1436  |  .ffunc_1 name
1437  |   add RB, BASE, RC
1438  |   add RA, BASE, #8
1439  |  checkint CARG1, >4
1440  |1:  // Handle integers.
1441  |  ldr CARG2, [RA]
1442  |   cmp RA, RB
1443  |   bhs ->fff_restv
1444  |  checkint CARG2, >3
1445  |  cmp CARG1w, CARG2w
1446  |   add RA, RA, #8
1447  |  csel CARG1, CARG2, CARG1, cond
1448  |  b <1
1449  |3:  // Convert intermediate result to number and continue below.
1450  |  scvtf d0, CARG1w
1451  |  blo ->fff_fallback
1452  |  ldr d1, [RA]
1453  |  b >6
1454  |
1455  |4:
1456  |  ldr d0, [BASE]
1457  |  blo ->fff_fallback
1458  |5:  // Handle numbers.
1459  |  ldr CARG2, [RA]
1460  |  ldr d1, [RA]
1461  |   cmp RA, RB
1462  |   bhs ->fff_resn
1463  |  checknum CARG2, >7
1464  |6:
1465  |  fcmp d0, d1
1466  |   add RA, RA, #8
1467  |  fcsel d0, d1, d0, fcond
1468  |  b <5
1469  |7:  // Convert integer to number and continue above.
1470  |  scvtf d1, CARG2w
1471  |  blo ->fff_fallback
1472  |  b <6
1473  |.endmacro
1474  |
1475  |  math_minmax math_min, gt, hi
1476  |  math_minmax math_max, lt, lo
1477  |
1478  |//-- String library -----------------------------------------------------
1479  |
1480  |.ffunc string_byte			// Only handle the 1-arg case here.
1481  |  ldp PC, CARG1, [BASE, FRAME_PC]
1482  |   cmp NARGS8:RC, #8
1483  |  asr ITYPE, CARG1, #47
1484  |  ccmn ITYPE, #-LJ_TSTR, #0, eq
1485  |   and STR:CARG1, CARG1, #LJ_GCVMASK
1486  |  bne ->fff_fallback
1487  |  ldrb TMP0w, STR:CARG1[1]		// Access is always ok (NUL at end).
1488  |   ldr CARG3w, STR:CARG1->len
1489  |  add TMP0, TMP0, TISNUM
1490  |  str TMP0, [BASE, #-16]
1491  |  mov RC, #(0+1)*8
1492  |   cbz CARG3, ->fff_res
1493  |  b ->fff_res1
1494  |
1495  |.ffunc string_char			// Only handle the 1-arg case here.
1496  |  ffgccheck
1497  |  ldp PC, CARG1, [BASE, FRAME_PC]
1498  |  cmp CARG1w, #255
1499  |   ccmp NARGS8:RC, #8, #0, ls		// Need exactly 1 argument.
1500  |  bne ->fff_fallback
1501  |  checkint CARG1, ->fff_fallback
1502  |  mov CARG3, #1
1503  |  mov CARG2, BASE			// Points to stack. Little-endian.
1504  |->fff_newstr:
1505  |  // CARG2 = str, CARG3 = len.
1506  |   str BASE, L->base
1507  |  mov CARG1, L
1508  |   str PC, SAVE_PC
1509  |  bl extern lj_str_new		// (lua_State *L, char *str, size_t l)
1510  |->fff_resstr:
1511  |  // Returns GCstr *.
1512  |  ldr BASE, L->base
1513  |   movn TMP1, #~LJ_TSTR
1514  |  add CARG1, CARG1, TMP1, lsl #47
1515  |  b ->fff_restv
1516  |
1517  |.ffunc string_sub
1518  |  ffgccheck
1519  |  ldr CARG1, [BASE]
1520  |    ldr CARG3, [BASE, #16]
1521  |   cmp NARGS8:RC, #16
1522  |    movn RB, #0
1523  |   beq >1
1524  |   blo ->fff_fallback
1525  |    checkint CARG3, ->fff_fallback
1526  |    sxtw RB, CARG3w
1527  |1:
1528  |  ldr CARG2, [BASE, #8]
1529  |  checkstr CARG1, ->fff_fallback
1530  |   ldr TMP1w, STR:CARG1->len
1531  |  checkint CARG2, ->fff_fallback
1532  |  sxtw CARG2, CARG2w
1533  |  // CARG1 = str, TMP1 = str->len, CARG2 = start, RB = end
1534  |   add TMP2, RB, TMP1
1535  |   cmp RB, #0
1536  |  add TMP0, CARG2, TMP1
1537  |   csinc RB, RB, TMP2, ge		// if (end < 0) end += len+1
1538  |  cmp CARG2, #0
1539  |  csinc CARG2, CARG2, TMP0, ge	// if (start < 0) start += len+1
1540  |   cmp RB, #0
1541  |   csel RB, RB, xzr, ge		// if (end < 0) end = 0
1542  |  cmp CARG2, #1
1543  |  csinc CARG2, CARG2, xzr, ge	// if (start < 1) start = 1
1544  |   cmp RB, TMP1
1545  |   csel RB, RB, TMP1, le		// if (end > len) end = len
1546  |  add CARG1, STR:CARG1, #sizeof(GCstr)-1
1547  |   subs CARG3, RB, CARG2		// len = end - start
1548  |  add CARG2, CARG1, CARG2
1549  |   add CARG3, CARG3, #1		// len += 1
1550  |   bge ->fff_newstr
1551  |  add STR:CARG1, GL, #offsetof(global_State, strempty)
1552  |   movn TMP1, #~LJ_TSTR
1553  |  add CARG1, CARG1, TMP1, lsl #47
1554  |  b ->fff_restv
1555  |
1556  |.macro ffstring_op, name
1557  |  .ffunc string_ .. name
1558  |  ffgccheck
1559  |  ldr CARG2, [BASE]
1560  |   cmp NARGS8:RC, #8
1561  |  asr ITYPE, CARG2, #47
1562  |  ccmn ITYPE, #-LJ_TSTR, #0, hs
1563  |   and STR:CARG2, CARG2, #LJ_GCVMASK
1564  |  bne ->fff_fallback
1565  |  ldr TMP0, GL->tmpbuf.b
1566  |   add SBUF:CARG1, GL, #offsetof(global_State, tmpbuf)
1567  |   str BASE, L->base
1568  |   str PC, SAVE_PC
1569  |   str L, GL->tmpbuf.L
1570  |  str TMP0, GL->tmpbuf.p
1571  |  bl extern lj_buf_putstr_ .. name
1572  |  bl extern lj_buf_tostr
1573  |  b ->fff_resstr
1574  |.endmacro
1575  |
1576  |ffstring_op reverse
1577  |ffstring_op lower
1578  |ffstring_op upper
1579  |
1580  |//-- Bit library --------------------------------------------------------
1581  |
1582  |// FP number to bit conversion for soft-float. Clobbers CARG1-CARG3
1583  |->vm_tobit_fb:
1584  |  bls ->fff_fallback
1585  |  add CARG2, CARG1, CARG1
1586  |  mov CARG3, #1076
1587  |  sub CARG3, CARG3, CARG2, lsr #53
1588  |  cmp CARG3, #53
1589  |  bhi >1
1590  |  and CARG2, CARG2, #U64x(001fffff,ffffffff)
1591  |  orr CARG2, CARG2, #U64x(00200000,00000000)
1592  |   cmp CARG1, #0
1593  |  lsr CARG2, CARG2, CARG3
1594  |   cneg CARG1w, CARG2w, mi
1595  |  br lr
1596  |1:
1597  |  mov CARG1w, #0
1598  |  br lr
1599  |
1600  |.macro .ffunc_bit, name
1601  |  .ffunc_1 bit_..name
1602  |  adr lr, >1
1603  |  checkint CARG1, ->vm_tobit_fb
1604  |1:
1605  |.endmacro
1606  |
1607  |.macro .ffunc_bit_op, name, ins
1608  |  .ffunc_bit name
1609  |  mov RA, #8
1610  |  mov TMP0w, CARG1w
1611  |  adr lr, >2
1612  |1:
1613  |  ldr CARG1, [BASE, RA]
1614  |   cmp RA, NARGS8:RC
1615  |    add RA, RA, #8
1616  |   bge >9
1617  |  checkint CARG1, ->vm_tobit_fb
1618  |2:
1619  |  ins TMP0w, TMP0w, CARG1w
1620  |  b <1
1621  |.endmacro
1622  |
1623  |.ffunc_bit_op band, and
1624  |.ffunc_bit_op bor, orr
1625  |.ffunc_bit_op bxor, eor
1626  |
1627  |.ffunc_bit tobit
1628  |  mov TMP0w, CARG1w
1629  |9:  // Label reused by .ffunc_bit_op users.
1630  |  add CARG1, TMP0, TISNUM
1631  |  b ->fff_restv
1632  |
1633  |.ffunc_bit bswap
1634  |  rev TMP0w, CARG1w
1635  |  add CARG1, TMP0, TISNUM
1636  |  b ->fff_restv
1637  |
1638  |.ffunc_bit bnot
1639  |  mvn TMP0w, CARG1w
1640  |  add CARG1, TMP0, TISNUM
1641  |  b ->fff_restv
1642  |
1643  |.macro .ffunc_bit_sh, name, ins, shmod
1644  |  .ffunc bit_..name
1645  |  ldp TMP0, CARG1, [BASE]
1646  |   cmp NARGS8:RC, #16
1647  |   blo ->fff_fallback
1648  |  adr lr, >1
1649  |  checkint CARG1, ->vm_tobit_fb
1650  |1:
1651  |.if shmod == 0
1652  |  mov TMP1, CARG1
1653  |.else
1654  |  neg TMP1, CARG1
1655  |.endif
1656  |  mov CARG1, TMP0
1657  |  adr lr, >2
1658  |  checkint CARG1, ->vm_tobit_fb
1659  |2:
1660  |  ins TMP0w, CARG1w, TMP1w
1661  |  add CARG1, TMP0, TISNUM
1662  |  b ->fff_restv
1663  |.endmacro
1664  |
1665  |.ffunc_bit_sh lshift, lsl, 0
1666  |.ffunc_bit_sh rshift, lsr, 0
1667  |.ffunc_bit_sh arshift, asr, 0
1668  |.ffunc_bit_sh rol, ror, 1
1669  |.ffunc_bit_sh ror, ror, 0
1670  |
1671  |//-----------------------------------------------------------------------
1672  |
1673  |->fff_fallback:			// Call fast function fallback handler.
1674  |  // BASE = new base, RC = nargs*8
1675  |   ldp CFUNC:CARG3, PC, [BASE, FRAME_FUNC]	// Fallback may overwrite PC.
1676  |  ldr TMP2, L->maxstack
1677  |  add TMP1, BASE, NARGS8:RC
1678  |  stp BASE, TMP1, L->base
1679  |   and CFUNC:CARG3, CARG3, #LJ_GCVMASK
1680  |  add TMP1, TMP1, #8*LUA_MINSTACK
1681  |   ldr CARG3, CFUNC:CARG3->f
1682  |    str PC, SAVE_PC			// Redundant (but a defined value).
1683  |  cmp TMP1, TMP2
1684  |   mov CARG1, L
1685  |  bhi >5				// Need to grow stack.
1686  |   blr CARG3				// (lua_State *L)
1687  |  // Either throws an error, or recovers and returns -1, 0 or nresults+1.
1688  |   ldr BASE, L->base
1689  |  cmp CRET1w, #0
1690  |   lsl RC, CRET1, #3
1691  |   sub RA, BASE, #16
1692  |  bgt ->fff_res			// Returned nresults+1?
1693  |1:  // Returned 0 or -1: retry fast path.
1694  |   ldr CARG1, L->top
1695  |    ldr CFUNC:CARG3, [BASE, FRAME_FUNC]
1696  |   sub NARGS8:RC, CARG1, BASE
1697  |  bne ->vm_call_tail			// Returned -1?
1698  |    and CFUNC:CARG3, CARG3, #LJ_GCVMASK
1699  |  ins_callt				// Returned 0: retry fast path.
1700  |
1701  |// Reconstruct previous base for vmeta_call during tailcall.
1702  |->vm_call_tail:
1703  |  ands TMP0, PC, #FRAME_TYPE
1704  |   and TMP1, PC, #~FRAME_TYPEP
1705  |  bne >3
1706  |  ldrb RAw, [PC, #-3]
1707  |  lsl RA, RA, #3
1708  |  add TMP1, RA, #16
1709  |3:
1710  |  sub RB, BASE, TMP1
1711  |  b ->vm_call_dispatch		// Resolve again for tailcall.
1712  |
1713  |5:  // Grow stack for fallback handler.
1714  |  mov CARG2, #LUA_MINSTACK
1715  |  bl extern lj_state_growstack	// (lua_State *L, int n)
1716  |  ldr BASE, L->base
1717  |  cmp CARG1, CARG1			// Set zero-flag to force retry.
1718  |  b <1
1719  |
1720  |->fff_gcstep:			// Call GC step function.
1721  |  // BASE = new base, RC = nargs*8
1722  |   add CARG2, BASE, NARGS8:RC	// Calculate L->top.
1723  |  mov RA, lr
1724  |   stp BASE, CARG2, L->base
1725  |   str PC, SAVE_PC			// Redundant (but a defined value).
1726  |  mov CARG1, L
1727  |  bl extern lj_gc_step		// (lua_State *L)
1728  |  ldp BASE, CARG2, L->base
1729  |   ldr CFUNC:CARG3, [BASE, FRAME_FUNC]
1730  |  mov lr, RA				// Help return address predictor.
1731  |  sub NARGS8:RC, CARG2, BASE		// Calculate nargs*8.
1732  |   and CFUNC:CARG3, CARG3, #LJ_GCVMASK
1733  |  ret
1734  |
1735  |//-----------------------------------------------------------------------
1736  |//-- Special dispatch targets -------------------------------------------
1737  |//-----------------------------------------------------------------------
1738  |
1739  |->vm_record:				// Dispatch target for recording phase.
1740  |.if JIT
1741  |  ldrb CARG1w, GL->hookmask
1742  |  tst CARG1, #HOOK_VMEVENT		// No recording while in vmevent.
1743  |  bne >5
1744  |  // Decrement the hookcount for consistency, but always do the call.
1745  |   ldr CARG2w, GL->hookcount
1746  |  tst CARG1, #HOOK_ACTIVE
1747  |  bne >1
1748  |   sub CARG2w, CARG2w, #1
1749  |  tst CARG1, #LUA_MASKLINE|LUA_MASKCOUNT
1750  |  beq >1
1751  |   str CARG2w, GL->hookcount
1752  |  b >1
1753  |.endif
1754  |
1755  |->vm_rethook:			// Dispatch target for return hooks.
1756  |  ldrb TMP2w, GL->hookmask
1757  |  tbz TMP2w, #HOOK_ACTIVE_SHIFT, >1	// Hook already active?
1758  |5:  // Re-dispatch to static ins.
1759  |  ldr TMP0, [TMP1, #GG_G2DISP+GG_DISP2STATIC]
1760  |  br TMP0
1761  |
1762  |->vm_inshook:			// Dispatch target for instr/line hooks.
1763  |  ldrb TMP2w, GL->hookmask
1764  |   ldr TMP3w, GL->hookcount
1765  |  tbnz TMP2w, #HOOK_ACTIVE_SHIFT, <5	// Hook already active?
1766  |  tst TMP2w, #LUA_MASKLINE|LUA_MASKCOUNT
1767  |  beq <5
1768  |   sub TMP3w, TMP3w, #1
1769  |   str TMP3w, GL->hookcount
1770  |   cbz TMP3w, >1
1771  |  tbz TMP2w, #LUA_HOOKLINE, <5
1772  |1:
1773  |  mov CARG1, L
1774  |   str BASE, L->base
1775  |  mov CARG2, PC
1776  |  // SAVE_PC must hold the _previous_ PC. The callee updates it with PC.
1777  |  bl extern lj_dispatch_ins		// (lua_State *L, const BCIns *pc)
1778  |3:
1779  |  ldr BASE, L->base
1780  |4:  // Re-dispatch to static ins.
1781  |  ldr INSw, [PC, #-4]
1782  |  add TMP1, GL, INS, uxtb #3
1783  |   decode_RA RA, INS
1784  |  ldr TMP0, [TMP1, #GG_G2DISP+GG_DISP2STATIC]
1785  |   decode_RD RC, INS
1786  |  br TMP0
1787  |
1788  |->cont_hook:				// Continue from hook yield.
1789  |  ldr CARG1, [CARG4, #-40]
1790  |   add PC, PC, #4
1791  |  str CARG1w, SAVE_MULTRES		// Restore MULTRES for *M ins.
1792  |  b <4
1793  |
1794  |->vm_hotloop:			// Hot loop counter underflow.
1795  |.if JIT
1796  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]  // Same as curr_topL(L).
1797  |   add CARG1, GL, #GG_G2DISP+GG_DISP2J
1798  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
1799  |   str PC, SAVE_PC
1800  |  ldr CARG3, LFUNC:CARG3->pc
1801  |   mov CARG2, PC
1802  |   str L, [GL, #GL_J(L)]
1803  |  ldrb CARG3w, [CARG3, #PC2PROTO(framesize)]
1804  |   str BASE, L->base
1805  |  add CARG3, BASE, CARG3, lsl #3
1806  |  str CARG3, L->top
1807  |  bl extern lj_trace_hot		// (jit_State *J, const BCIns *pc)
1808  |  b <3
1809  |.endif
1810  |
1811  |->vm_callhook:			// Dispatch target for call hooks.
1812  |  mov CARG2, PC
1813  |.if JIT
1814  |  b >1
1815  |.endif
1816  |
1817  |->vm_hotcall:			// Hot call counter underflow.
1818  |.if JIT
1819  |  orr CARG2, PC, #1
1820  |1:
1821  |.endif
1822  |  add TMP1, BASE, NARGS8:RC
1823  |   str PC, SAVE_PC
1824  |   mov CARG1, L
1825  |   sub RA, RA, BASE
1826  |  stp BASE, TMP1, L->base
1827  |  bl extern lj_dispatch_call		// (lua_State *L, const BCIns *pc)
1828  |  // Returns ASMFunction.
1829  |  ldp BASE, TMP1, L->base
1830  |   str xzr, SAVE_PC			// Invalidate for subsequent line hook.
1831  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]
1832  |  add RA, BASE, RA
1833  |  sub NARGS8:RC, TMP1, BASE
1834  |   ldr INSw, [PC, #-4]
1835  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
1836  |  br CRET1
1837  |
1838  |->cont_stitch:			// Trace stitching.
1839  |.if JIT
1840  |  // RA = resultptr, CARG4 = meta base
1841  |   ldr RB, SAVE_MULTRES
1842  |  ldr INSw, [PC, #-4]
1843  |    ldr TRACE:CARG3, [CARG4, #-40]	// Save previous trace.
1844  |   subs RB, RB, #8
1845  |  decode_RA RC, INS			// Call base.
1846  |    and CARG3, CARG3, #LJ_GCVMASK
1847  |   beq >2
1848  |1:  // Move results down.
1849  |  ldr CARG1, [RA]
1850  |    add RA, RA, #8
1851  |   subs RB, RB, #8
1852  |  str CARG1, [BASE, RC, lsl #3]
1853  |    add RC, RC, #1
1854  |   bne <1
1855  |2:
1856  |   decode_RA RA, INS
1857  |   decode_RB RB, INS
1858  |   add RA, RA, RB
1859  |3:
1860  |   cmp RA, RC
1861  |   bhi >9				// More results wanted?
1862  |
1863  |  ldrh RAw, TRACE:CARG3->traceno
1864  |  ldrh RCw, TRACE:CARG3->link
1865  |  cmp RCw, RAw
1866  |  beq ->cont_nop			// Blacklisted.
1867  |  cmp RCw, #0
1868  |  bne =>BC_JLOOP			// Jump to stitched trace.
1869  |
1870  |  // Stitch a new trace to the previous trace.
1871  |  mov CARG1, #GL_J(exitno)
1872  |  str RA, [GL, CARG1]
1873  |  mov CARG1, #GL_J(L)
1874  |  str L, [GL, CARG1]
1875  |  str BASE, L->base
1876  |  add CARG1, GL, #GG_G2J
1877  |  mov CARG2, PC
1878  |  bl extern lj_dispatch_stitch	// (jit_State *J, const BCIns *pc)
1879  |  ldr BASE, L->base
1880  |  b ->cont_nop
1881  |
1882  |9:  // Fill up results with nil.
1883  |  str TISNIL, [BASE, RC, lsl #3]
1884  |  add RC, RC, #1
1885  |  b <3
1886  |.endif
1887  |
1888  |->vm_profhook:			// Dispatch target for profiler hook.
1889#if LJ_HASPROFILE
1890  |  mov CARG1, L
1891  |   str BASE, L->base
1892  |  mov CARG2, PC
1893  |  bl extern lj_dispatch_profile	// (lua_State *L, const BCIns *pc)
1894  |  // HOOK_PROFILE is off again, so re-dispatch to dynamic instruction.
1895  |  ldr BASE, L->base
1896  |  sub PC, PC, #4
1897  |  b ->cont_nop
1898#endif
1899  |
1900  |//-----------------------------------------------------------------------
1901  |//-- Trace exit handler -------------------------------------------------
1902  |//-----------------------------------------------------------------------
1903  |
1904  |.macro savex_, a, b
1905  |  stp d..a, d..b, [sp, #a*8]
1906  |  stp x..a, x..b, [sp, #32*8+a*8]
1907  |.endmacro
1908  |
1909  |->vm_exit_handler:
1910  |.if JIT
1911  |  sub     sp, sp, #(64*8)
1912  |  savex_, 0, 1
1913  |  savex_, 2, 3
1914  |  savex_, 4, 5
1915  |  savex_, 6, 7
1916  |  savex_, 8, 9
1917  |  savex_, 10, 11
1918  |  savex_, 12, 13
1919  |  savex_, 14, 15
1920  |  savex_, 16, 17
1921  |  savex_, 18, 19
1922  |  savex_, 20, 21
1923  |  savex_, 22, 23
1924  |  savex_, 24, 25
1925  |  savex_, 26, 27
1926  |  savex_, 28, 29
1927  |  stp d30, d31, [sp, #30*8]
1928  |  ldr CARG1, [sp, #64*8]	// Load original value of lr.
1929  |   add CARG3, sp, #64*8	// Recompute original value of sp.
1930  |    mv_vmstate CARG4, EXIT
1931  |   stp xzr, CARG3, [sp, #62*8]	// Store 0/sp in RID_LR/RID_SP.
1932  |  sub CARG1, CARG1, lr
1933  |   ldr L, GL->cur_L
1934  |  lsr CARG1, CARG1, #2
1935  |   ldr BASE, GL->jit_base
1936  |  sub CARG1, CARG1, #2
1937  |   ldr CARG2w, [lr]		// Load trace number.
1938  |    st_vmstate CARG4
1939  |   str BASE, L->base
1940  |  ubfx CARG2w, CARG2w, #5, #16
1941  |  str CARG1w, [GL, #GL_J(exitno)]
1942  |   str CARG2w, [GL, #GL_J(parent)]
1943  |   str L, [GL, #GL_J(L)]
1944  |  str xzr, GL->jit_base
1945  |  add CARG1, GL, #GG_G2J
1946  |  mov CARG2, sp
1947  |  bl extern lj_trace_exit		// (jit_State *J, ExitState *ex)
1948  |  // Returns MULTRES (unscaled) or negated error code.
1949  |  ldr CARG2, L->cframe
1950  |   ldr BASE, L->base
1951  |  and sp, CARG2, #CFRAME_RAWMASK
1952  |   ldr PC, SAVE_PC			// Get SAVE_PC.
1953  |  str L, SAVE_L			// Set SAVE_L (on-trace resume/yield).
1954  |  b >1
1955  |.endif
1956  |
1957  |->vm_exit_interp:
1958  |  // CARG1 = MULTRES or negated error code, BASE, PC and GL set.
1959  |.if JIT
1960  |  ldr L, SAVE_L
1961  |1:
1962  |  cmp CARG1w, #0
1963  |  blt >9				// Check for error from exit.
1964  |   lsl RC, CARG1, #3
1965  |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
1966  |    movz TISNUM, #(LJ_TISNUM>>1)&0xffff, lsl #48
1967  |    movz TISNUMhi, #(LJ_TISNUM>>1)&0xffff, lsl #16
1968  |    movn TISNIL, #0
1969  |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
1970  |   str RC, SAVE_MULTRES
1971  |   str BASE, L->base
1972  |  ldr CARG2, LFUNC:CARG2->pc
1973  |   str xzr, GL->jit_base
1974  |    mv_vmstate CARG4, INTERP
1975  |  ldr KBASE, [CARG2, #PC2PROTO(k)]
1976  |  // Modified copy of ins_next which handles function header dispatch, too.
1977  |  ldrb RBw, [PC]
1978  |   ldr INSw, [PC], #4
1979  |    st_vmstate CARG4
1980  |  cmp RBw, #BC_FUNCC+2		// Fast function?
1981  |   add TMP1, GL, INS, uxtb #3
1982  |  bhs >4
1983  |2:
1984  |  cmp RBw, #BC_FUNCF			// Function header?
1985  |  add TMP0, GL, RB, uxtb #3
1986  |  ldr RB, [TMP0, #GG_G2DISP]
1987  |   decode_RA RA, INS
1988  |   lsr TMP0, INS, #16
1989  |   csel RC, TMP0, RC, lo
1990  |   blo >5
1991  |   ldr CARG3, [BASE, FRAME_FUNC]
1992  |   sub RC, RC, #8
1993  |   add RA, BASE, RA, lsl #3	// Yes: RA = BASE+framesize*8, RC = nargs*8
1994  |   and LFUNC:CARG3, CARG3, #LJ_GCVMASK
1995  |5:
1996  |  br RB
1997  |
1998  |4:  // Check frame below fast function.
1999  |  ldr CARG1, [BASE, FRAME_PC]
2000  |  ands CARG2, CARG1, #FRAME_TYPE
2001  |  bne <2			// Trace stitching continuation?
2002  |  // Otherwise set KBASE for Lua function below fast function.
2003  |  ldr CARG3, [CARG1, #-4]
2004  |  decode_RA CARG1, CARG3
2005  |  sub CARG2, BASE, CARG1, lsl #3
2006  |  ldr LFUNC:CARG3, [CARG2, #-32]
2007  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
2008  |  ldr CARG3, LFUNC:CARG3->pc
2009  |  ldr KBASE, [CARG3, #PC2PROTO(k)]
2010  |  b <2
2011  |
2012  |9:  // Rethrow error from the right C frame.
2013  |  neg CARG2, CARG1
2014  |  mov CARG1, L
2015  |  bl extern lj_err_throw		// (lua_State *L, int errcode)
2016  |.endif
2017  |
2018  |//-----------------------------------------------------------------------
2019  |//-- Math helper functions ----------------------------------------------
2020  |//-----------------------------------------------------------------------
2021  |
2022  |  // int lj_vm_modi(int dividend, int divisor);
2023  |->vm_modi:
2024  |    eor CARG4w, CARG1w, CARG2w
2025  |    cmp CARG4w, #0
2026  |  eor CARG3w, CARG1w, CARG1w, asr #31
2027  |   eor CARG4w, CARG2w, CARG2w, asr #31
2028  |  sub CARG3w, CARG3w, CARG1w, asr #31
2029  |   sub CARG4w, CARG4w, CARG2w, asr #31
2030  |  udiv CARG1w, CARG3w, CARG4w
2031  |  msub CARG1w, CARG1w, CARG4w, CARG3w
2032  |    ccmp CARG1w, #0, #4, mi
2033  |    sub CARG3w, CARG1w, CARG4w
2034  |    csel CARG1w, CARG1w, CARG3w, eq
2035  |  eor CARG3w, CARG1w, CARG2w
2036  |  cmp CARG3w, #0
2037  |  cneg CARG1w, CARG1w, mi
2038  |  ret
2039  |
2040  |//-----------------------------------------------------------------------
2041  |//-- Miscellaneous functions --------------------------------------------
2042  |//-----------------------------------------------------------------------
2043  |
2044  |//-----------------------------------------------------------------------
2045  |//-- FFI helper functions -----------------------------------------------
2046  |//-----------------------------------------------------------------------
2047  |
2048  |// Handler for callback functions.
2049  |// Saveregs already performed. Callback slot number in [sp], g in r12.
2050  |->vm_ffi_callback:
2051  |.if FFI
2052  |.type CTSTATE, CTState, PC
2053  |  saveregs
2054  |  ldr CTSTATE, GL:x10->ctype_state
2055  |  mov GL, x10
2056  |    add x10, sp, # CFRAME_SPACE
2057  |  str w9, CTSTATE->cb.slot
2058  |  stp x0, x1, CTSTATE->cb.gpr[0]
2059  |   stp d0, d1, CTSTATE->cb.fpr[0]
2060  |  stp x2, x3, CTSTATE->cb.gpr[2]
2061  |   stp d2, d3, CTSTATE->cb.fpr[2]
2062  |  stp x4, x5, CTSTATE->cb.gpr[4]
2063  |   stp d4, d5, CTSTATE->cb.fpr[4]
2064  |  stp x6, x7, CTSTATE->cb.gpr[6]
2065  |   stp d6, d7, CTSTATE->cb.fpr[6]
2066  |    str x10, CTSTATE->cb.stack
2067  |  mov CARG1, CTSTATE
2068  |   str CTSTATE, SAVE_PC		// Any value outside of bytecode is ok.
2069  |  mov CARG2, sp
2070  |  bl extern lj_ccallback_enter	// (CTState *cts, void *cf)
2071  |  // Returns lua_State *.
2072  |  ldp BASE, RC, L:CRET1->base
2073  |   movz TISNUM, #(LJ_TISNUM>>1)&0xffff, lsl #48
2074  |   movz TISNUMhi, #(LJ_TISNUM>>1)&0xffff, lsl #16
2075  |   movn TISNIL, #0
2076  |   mov L, CRET1
2077  |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]
2078  |  sub RC, RC, BASE
2079  |   st_vmstate ST_INTERP
2080  |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
2081  |  ins_callt
2082  |.endif
2083  |
2084  |->cont_ffi_callback:			// Return from FFI callback.
2085  |.if FFI
2086  |  ldr CTSTATE, GL->ctype_state
2087  |   stp BASE, CARG4, L->base
2088  |  str L, CTSTATE->L
2089  |  mov CARG1, CTSTATE
2090  |  mov CARG2, RA
2091  |  bl extern lj_ccallback_leave       // (CTState *cts, TValue *o)
2092  |  ldp x0, x1, CTSTATE->cb.gpr[0]
2093  |   ldp d0, d1, CTSTATE->cb.fpr[0]
2094  |  b ->vm_leave_unw
2095  |.endif
2096  |
2097  |->vm_ffi_call:			// Call C function via FFI.
2098  |  // Caveat: needs special frame unwinding, see below.
2099  |.if FFI
2100  |  .type CCSTATE, CCallState, x19
2101  |  stp fp, lr, [sp, #-32]!
2102  |  add fp, sp, #0
2103  |  str CCSTATE, [sp, #16]
2104  |  mov CCSTATE, x0
2105  |  ldr TMP0w, CCSTATE:x0->spadj
2106  |   ldrb TMP1w, CCSTATE->nsp
2107  |    add TMP2, CCSTATE, #offsetof(CCallState, stack)
2108  |   subs TMP1, TMP1, #1
2109  |    ldr TMP3, CCSTATE->func
2110  |  sub sp, fp, TMP0
2111  |   bmi >2
2112  |1:  // Copy stack slots
2113  |  ldr TMP0, [TMP2, TMP1, lsl #3]
2114  |  str TMP0, [sp, TMP1, lsl #3]
2115  |  subs TMP1, TMP1, #1
2116  |  bpl <1
2117  |2:
2118  |  ldp x0, x1, CCSTATE->gpr[0]
2119  |   ldp d0, d1, CCSTATE->fpr[0]
2120  |  ldp x2, x3, CCSTATE->gpr[2]
2121  |   ldp d2, d3, CCSTATE->fpr[2]
2122  |  ldp x4, x5, CCSTATE->gpr[4]
2123  |   ldp d4, d5, CCSTATE->fpr[4]
2124  |  ldp x6, x7, CCSTATE->gpr[6]
2125  |   ldp d6, d7, CCSTATE->fpr[6]
2126  |  ldr x8, CCSTATE->retp
2127  |  blr TMP3
2128  |  mov sp, fp
2129  |  stp x0, x1, CCSTATE->gpr[0]
2130  |   stp d0, d1, CCSTATE->fpr[0]
2131  |   stp d2, d3, CCSTATE->fpr[2]
2132  |  ldr CCSTATE, [sp, #16]
2133  |  ldp fp, lr, [sp], #32
2134  |  ret
2135  |.endif
2136  |// Note: vm_ffi_call must be the last function in this object file!
2137  |
2138  |//-----------------------------------------------------------------------
2139}
2140
2141/* Generate the code for a single instruction. */
2142static void build_ins(BuildCtx *ctx, BCOp op, int defop)
2143{
2144  int vk = 0;
2145  |=>defop:
2146
2147  switch (op) {
2148
2149  /* -- Comparison ops ---------------------------------------------------- */
2150
2151  /* Remember: all ops branch for a true comparison, fall through otherwise. */
2152
2153  case BC_ISLT: case BC_ISGE: case BC_ISLE: case BC_ISGT:
2154    |  // RA = src1, RC = src2, JMP with RC = target
2155    |  ldr CARG1, [BASE, RA, lsl #3]
2156    |    ldrh RBw, [PC, #2]
2157    |   ldr CARG2, [BASE, RC, lsl #3]
2158    |    add PC, PC, #4
2159    |    add RB, PC, RB, lsl #2
2160    |    sub RB, RB, #0x20000
2161    |  checkint CARG1, >3
2162    |   checkint CARG2, >4
2163    |  cmp CARG1w, CARG2w
2164    if (op == BC_ISLT) {
2165      |  csel PC, RB, PC, lt
2166    } else if (op == BC_ISGE) {
2167      |  csel PC, RB, PC, ge
2168    } else if (op == BC_ISLE) {
2169      |  csel PC, RB, PC, le
2170    } else {
2171      |  csel PC, RB, PC, gt
2172    }
2173    |1:
2174    |  ins_next
2175    |
2176    |3:  // RA not int.
2177    |    ldr FARG1, [BASE, RA, lsl #3]
2178    |  blo ->vmeta_comp
2179    |    ldr FARG2, [BASE, RC, lsl #3]
2180    |   cmp TISNUMhi, CARG2, lsr #32
2181    |   bhi >5
2182    |   bne ->vmeta_comp
2183    |  // RA number, RC int.
2184    |  scvtf FARG2, CARG2w
2185    |  b >5
2186    |
2187    |4:  // RA int, RC not int
2188    |    ldr FARG2, [BASE, RC, lsl #3]
2189    |   blo ->vmeta_comp
2190    |  // RA int, RC number.
2191    |  scvtf FARG1, CARG1w
2192    |
2193    |5:  // RA number, RC number
2194    |  fcmp FARG1, FARG2
2195    |  // To preserve NaN semantics GE/GT branch on unordered, but LT/LE don't.
2196    if (op == BC_ISLT) {
2197      |  csel PC, RB, PC, lo
2198    } else if (op == BC_ISGE) {
2199      |  csel PC, RB, PC, hs
2200    } else if (op == BC_ISLE) {
2201      |  csel PC, RB, PC, ls
2202    } else {
2203      |  csel PC, RB, PC, hi
2204    }
2205    |  b <1
2206    break;
2207
2208  case BC_ISEQV: case BC_ISNEV:
2209    vk = op == BC_ISEQV;
2210    |  // RA = src1, RC = src2, JMP with RC = target
2211    |  ldr CARG1, [BASE, RA, lsl #3]
2212    |   add RC, BASE, RC, lsl #3
2213    |    ldrh RBw, [PC, #2]
2214    |   ldr CARG3, [RC]
2215    |    add PC, PC, #4
2216    |    add RB, PC, RB, lsl #2
2217    |    sub RB, RB, #0x20000
2218    |  asr ITYPE, CARG3, #47
2219    |  cmn ITYPE, #-LJ_TISNUM
2220    if (vk) {
2221      |  bls ->BC_ISEQN_Z
2222    } else {
2223      |  bls ->BC_ISNEN_Z
2224    }
2225    |  // RC is not a number.
2226    |   asr TMP0, CARG1, #47
2227    |.if FFI
2228    |  // Check if RC or RA is a cdata.
2229    |  cmn ITYPE, #-LJ_TCDATA
2230    |   ccmn TMP0, #-LJ_TCDATA, #4, ne
2231    |  beq ->vmeta_equal_cd
2232    |.endif
2233    |  cmp CARG1, CARG3
2234    |  bne >2
2235    |  // Tag and value are equal.
2236    if (vk) {
2237      |->BC_ISEQV_Z:
2238      |  mov PC, RB			// Perform branch.
2239    }
2240    |1:
2241    |  ins_next
2242    |
2243    |2:  // Check if the tags are the same and it's a table or userdata.
2244    |  cmp ITYPE, TMP0
2245    |  ccmn ITYPE, #-LJ_TISTABUD, #2, eq
2246    if (vk) {
2247      |  bhi <1
2248    } else {
2249      |  bhi ->BC_ISEQV_Z		// Reuse code from opposite instruction.
2250    }
2251    |  // Different tables or userdatas. Need to check __eq metamethod.
2252    |  // Field metatable must be at same offset for GCtab and GCudata!
2253    |  and TAB:CARG2, CARG1, #LJ_GCVMASK
2254    |  ldr TAB:TMP2, TAB:CARG2->metatable
2255    if (vk) {
2256      |  cbz TAB:TMP2, <1		// No metatable?
2257      |  ldrb TMP1w, TAB:TMP2->nomm
2258      |   mov CARG4, #0			// ne = 0
2259      |  tbnz TMP1w, #MM_eq, <1		// 'no __eq' flag set: done.
2260    } else {
2261      |  cbz TAB:TMP2, ->BC_ISEQV_Z	// No metatable?
2262      |  ldrb TMP1w, TAB:TMP2->nomm
2263      |   mov CARG4, #1			// ne = 1.
2264      |  tbnz TMP1w, #MM_eq, ->BC_ISEQV_Z	// 'no __eq' flag set: done.
2265    }
2266    |  b ->vmeta_equal
2267    break;
2268
2269  case BC_ISEQS: case BC_ISNES:
2270    vk = op == BC_ISEQS;
2271    |  // RA = src, RC = str_const (~), JMP with RC = target
2272    |  ldr CARG1, [BASE, RA, lsl #3]
2273    |   mvn RC, RC
2274    |    ldrh RBw, [PC, #2]
2275    |   ldr CARG2, [KBASE, RC, lsl #3]
2276    |    add PC, PC, #4
2277    |   movn TMP0, #~LJ_TSTR
2278    |.if FFI
2279    |  asr ITYPE, CARG1, #47
2280    |.endif
2281    |    add RB, PC, RB, lsl #2
2282    |   add CARG2, CARG2, TMP0, lsl #47
2283    |    sub RB, RB, #0x20000
2284    |.if FFI
2285    |  cmn ITYPE, #-LJ_TCDATA
2286    |  beq ->vmeta_equal_cd
2287    |.endif
2288    |  cmp CARG1, CARG2
2289    if (vk) {
2290      |  csel PC, RB, PC, eq
2291    } else {
2292      |  csel PC, RB, PC, ne
2293    }
2294    |  ins_next
2295    break;
2296
2297  case BC_ISEQN: case BC_ISNEN:
2298    vk = op == BC_ISEQN;
2299    |  // RA = src, RC = num_const (~), JMP with RC = target
2300    |  ldr CARG1, [BASE, RA, lsl #3]
2301    |   add RC, KBASE, RC, lsl #3
2302    |    ldrh RBw, [PC, #2]
2303    |   ldr CARG3, [RC]
2304    |    add PC, PC, #4
2305    |    add RB, PC, RB, lsl #2
2306    |    sub RB, RB, #0x20000
2307    if (vk) {
2308      |->BC_ISEQN_Z:
2309    } else {
2310      |->BC_ISNEN_Z:
2311    }
2312    |  checkint CARG1, >4
2313    |   checkint CARG3, >6
2314    |  cmp CARG1w, CARG3w
2315    |1:
2316    if (vk) {
2317      |  csel PC, RB, PC, eq
2318      |2:
2319    } else {
2320      |2:
2321      |  csel PC, RB, PC, ne
2322    }
2323    |3:
2324    |  ins_next
2325    |
2326    |4:  // RA not int.
2327    |.if FFI
2328    |  blo >7
2329    |.else
2330    |  blo <2
2331    |.endif
2332    |    ldr FARG1, [BASE, RA, lsl #3]
2333    |    ldr FARG2, [RC]
2334    |   cmp TISNUMhi, CARG3, lsr #32
2335    |   bne >5
2336    |  // RA number, RC int.
2337    |  scvtf FARG2, CARG3w
2338    |5:
2339    |  // RA number, RC number.
2340    |  fcmp FARG1, FARG2
2341    |  b <1
2342    |
2343    |6:  // RA int, RC number
2344    |  ldr FARG2, [RC]
2345    |  scvtf FARG1, CARG1w
2346    |  fcmp FARG1, FARG2
2347    |  b <1
2348    |
2349    |.if FFI
2350    |7:
2351    |  asr ITYPE, CARG1, #47
2352    |  cmn ITYPE, #-LJ_TCDATA
2353    |  bne <2
2354    |  b ->vmeta_equal_cd
2355    |.endif
2356    break;
2357
2358  case BC_ISEQP: case BC_ISNEP:
2359    vk = op == BC_ISEQP;
2360    |  // RA = src, RC = primitive_type (~), JMP with RC = target
2361    |  ldr TMP0, [BASE, RA, lsl #3]
2362    |   ldrh RBw, [PC, #2]
2363    |   add PC, PC, #4
2364    |  add RC, RC, #1
2365    |   add RB, PC, RB, lsl #2
2366    |.if FFI
2367    |  asr ITYPE, TMP0, #47
2368    |  cmn ITYPE, #-LJ_TCDATA
2369    |  beq ->vmeta_equal_cd
2370    |  cmn RC, ITYPE
2371    |.else
2372    |  cmn RC, TMP0, asr #47
2373    |.endif
2374    |   sub RB, RB, #0x20000
2375    if (vk) {
2376      |  csel PC, RB, PC, eq
2377    } else {
2378      |  csel PC, RB, PC, ne
2379    }
2380    |  ins_next
2381    break;
2382
2383  /* -- Unary test and copy ops ------------------------------------------- */
2384
2385  case BC_ISTC: case BC_ISFC: case BC_IST: case BC_ISF:
2386    |  // RA = dst or unused, RC = src, JMP with RC = target
2387    |   ldrh RBw, [PC, #2]
2388    |  ldr TMP0, [BASE, RC, lsl #3]
2389    |   add PC, PC, #4
2390    |  mov_false TMP1
2391    |   add RB, PC, RB, lsl #2
2392    |  cmp TMP0, TMP1
2393    |   sub RB, RB, #0x20000
2394    if (op == BC_ISTC || op == BC_IST) {
2395      if (op == BC_ISTC) {
2396	|  csel RA, RA, RC, lo
2397      }
2398      |  csel PC, RB, PC, lo
2399    } else {
2400      if (op == BC_ISFC) {
2401	|  csel RA, RA, RC, hs
2402      }
2403      |  csel PC, RB, PC, hs
2404    }
2405    if (op == BC_ISTC || op == BC_ISFC) {
2406      |  str TMP0, [BASE, RA, lsl #3]
2407    }
2408    |  ins_next
2409    break;
2410
2411  case BC_ISTYPE:
2412    |  // RA = src, RC = -type
2413    |  ldr TMP0, [BASE, RA, lsl #3]
2414    |  cmn RC, TMP0, asr #47
2415    |  bne ->vmeta_istype
2416    |  ins_next
2417    break;
2418  case BC_ISNUM:
2419    |  // RA = src, RC = -(TISNUM-1)
2420    |  ldr TMP0, [BASE, RA]
2421    |  checknum TMP0, ->vmeta_istype
2422    |  ins_next
2423    break;
2424
2425  /* -- Unary ops --------------------------------------------------------- */
2426
2427  case BC_MOV:
2428    |  // RA = dst, RC = src
2429    |  ldr TMP0, [BASE, RC, lsl #3]
2430    |  str TMP0, [BASE, RA, lsl #3]
2431    |  ins_next
2432    break;
2433  case BC_NOT:
2434    |  // RA = dst, RC = src
2435    |  ldr TMP0, [BASE, RC, lsl #3]
2436    |   mov_false TMP1
2437    |   mov_true TMP2
2438    |  cmp TMP0, TMP1
2439    |  csel TMP0, TMP1, TMP2, lo
2440    |  str TMP0, [BASE, RA, lsl #3]
2441    |  ins_next
2442    break;
2443  case BC_UNM:
2444    |  // RA = dst, RC = src
2445    |  ldr TMP0, [BASE, RC, lsl #3]
2446    |  asr ITYPE, TMP0, #47
2447    |  cmn ITYPE, #-LJ_TISNUM
2448    |  bhi ->vmeta_unm
2449    |  eor TMP0, TMP0, #U64x(80000000,00000000)
2450    |  bne >5
2451    |  negs TMP0w, TMP0w
2452    |   movz CARG3, #0x41e0, lsl #48	// 2^31.
2453    |   add TMP0, TMP0, TISNUM
2454    |  csel TMP0, TMP0, CARG3, vc
2455    |5:
2456    |  str TMP0, [BASE, RA, lsl #3]
2457    |  ins_next
2458    break;
2459  case BC_LEN:
2460    |  // RA = dst, RC = src
2461    |  ldr CARG1, [BASE, RC, lsl #3]
2462    |  asr ITYPE, CARG1, #47
2463    |  cmn ITYPE, #-LJ_TSTR
2464    |   and CARG1, CARG1, #LJ_GCVMASK
2465    |  bne >2
2466    |  ldr CARG1w, STR:CARG1->len
2467    |1:
2468    |  add CARG1, CARG1, TISNUM
2469    |  str CARG1, [BASE, RA, lsl #3]
2470    |  ins_next
2471    |
2472    |2:
2473    |  cmn ITYPE, #-LJ_TTAB
2474    |  bne ->vmeta_len
2475#if LJ_52
2476    |  ldr TAB:CARG2, TAB:CARG1->metatable
2477    |  cbnz TAB:CARG2, >9
2478    |3:
2479#endif
2480    |->BC_LEN_Z:
2481    |  bl extern lj_tab_len		// (GCtab *t)
2482    |  // Returns uint32_t (but less than 2^31).
2483    |  b <1
2484    |
2485#if LJ_52
2486    |9:
2487    |  ldrb TMP1w, TAB:CARG2->nomm
2488    |  tbnz TMP1w, #MM_len, <3		// 'no __len' flag set: done.
2489    |  b ->vmeta_len
2490#endif
2491    break;
2492
2493  /* -- Binary ops -------------------------------------------------------- */
2494
2495    |.macro ins_arithcheck_int, target
2496    |  checkint CARG1, target
2497    |  checkint CARG2, target
2498    |.endmacro
2499    |
2500    |.macro ins_arithcheck_num, target
2501    |  checknum CARG1, target
2502    |  checknum CARG2, target
2503    |.endmacro
2504    |
2505    |.macro ins_arithcheck_nzdiv, target
2506    |  cbz CARG2w, target
2507    |.endmacro
2508    |
2509    |.macro ins_arithhead
2510    ||vk = ((int)op - BC_ADDVN) / (BC_ADDNV-BC_ADDVN);
2511    ||if (vk == 1) {
2512    |   and RC, RC, #255
2513    |    decode_RB RB, INS
2514    ||} else {
2515    |   decode_RB RB, INS
2516    |    and RC, RC, #255
2517    ||}
2518    |.endmacro
2519    |
2520    |.macro ins_arithload, reg1, reg2
2521    |  // RA = dst, RB = src1, RC = src2 | num_const
2522    ||switch (vk) {
2523    ||case 0:
2524    |   ldr reg1, [BASE, RB, lsl #3]
2525    |    ldr reg2, [KBASE, RC, lsl #3]
2526    ||  break;
2527    ||case 1:
2528    |   ldr reg1, [KBASE, RC, lsl #3]
2529    |    ldr reg2, [BASE, RB, lsl #3]
2530    ||  break;
2531    ||default:
2532    |   ldr reg1, [BASE, RB, lsl #3]
2533    |    ldr reg2, [BASE, RC, lsl #3]
2534    ||  break;
2535    ||}
2536    |.endmacro
2537    |
2538    |.macro ins_arithfallback, ins
2539    ||switch (vk) {
2540    ||case 0:
2541    |   ins ->vmeta_arith_vn
2542    ||  break;
2543    ||case 1:
2544    |   ins ->vmeta_arith_nv
2545    ||  break;
2546    ||default:
2547    |   ins ->vmeta_arith_vv
2548    ||  break;
2549    ||}
2550    |.endmacro
2551    |
2552    |.macro ins_arithmod, res, reg1, reg2
2553    |  fdiv d2, reg1, reg2
2554    |  frintm d2, d2
2555    |  fmsub res, d2, reg2, reg1
2556    |.endmacro
2557    |
2558    |.macro ins_arithdn, intins, fpins
2559    |  ins_arithhead
2560    |  ins_arithload CARG1, CARG2
2561    |  ins_arithcheck_int >5
2562    |.if "intins" == "smull"
2563    |  smull CARG1, CARG1w, CARG2w
2564    |  cmp CARG1, CARG1, sxtw
2565    |   mov CARG1w, CARG1w
2566    |  ins_arithfallback bne
2567    |.elif "intins" == "ins_arithmodi"
2568    |  ins_arithfallback ins_arithcheck_nzdiv
2569    |  bl ->vm_modi
2570    |.else
2571    |  intins CARG1w, CARG1w, CARG2w
2572    |  ins_arithfallback bvs
2573    |.endif
2574    |  add CARG1, CARG1, TISNUM
2575    |  str CARG1, [BASE, RA, lsl #3]
2576    |4:
2577    |  ins_next
2578    |
2579    |5:  // FP variant.
2580    |  ins_arithload FARG1, FARG2
2581    |  ins_arithfallback ins_arithcheck_num
2582    |  fpins FARG1, FARG1, FARG2
2583    |  str FARG1, [BASE, RA, lsl #3]
2584    |  b <4
2585    |.endmacro
2586    |
2587    |.macro ins_arithfp, fpins
2588    |  ins_arithhead
2589    |  ins_arithload CARG1, CARG2
2590    |  ins_arithload FARG1, FARG2
2591    |  ins_arithfallback ins_arithcheck_num
2592    |.if "fpins" == "fpow"
2593    |  bl extern pow
2594    |.else
2595    |  fpins FARG1, FARG1, FARG2
2596    |.endif
2597    |  str FARG1, [BASE, RA, lsl #3]
2598    |  ins_next
2599    |.endmacro
2600
2601  case BC_ADDVN: case BC_ADDNV: case BC_ADDVV:
2602    |  ins_arithdn adds, fadd
2603    break;
2604  case BC_SUBVN: case BC_SUBNV: case BC_SUBVV:
2605    |  ins_arithdn subs, fsub
2606    break;
2607  case BC_MULVN: case BC_MULNV: case BC_MULVV:
2608    |  ins_arithdn smull, fmul
2609    break;
2610  case BC_DIVVN: case BC_DIVNV: case BC_DIVVV:
2611    |  ins_arithfp fdiv
2612    break;
2613  case BC_MODVN: case BC_MODNV: case BC_MODVV:
2614    |  ins_arithdn ins_arithmodi, ins_arithmod
2615    break;
2616  case BC_POW:
2617    |  // NYI: (partial) integer arithmetic.
2618    |  ins_arithfp fpow
2619    break;
2620
2621  case BC_CAT:
2622    |  decode_RB RB, INS
2623    |   and RC, RC, #255
2624    |  // RA = dst, RB = src_start, RC = src_end
2625    |   str BASE, L->base
2626    |  sub CARG3, RC, RB
2627    |  add CARG2, BASE, RC, lsl #3
2628    |->BC_CAT_Z:
2629    |  // RA = dst, CARG2 = top-1, CARG3 = left
2630    |  mov CARG1, L
2631    |   str PC, SAVE_PC
2632    |  bl extern lj_meta_cat		// (lua_State *L, TValue *top, int left)
2633    |  // Returns NULL (finished) or TValue * (metamethod).
2634    |  ldrb RBw, [PC, #-1]
2635    |   ldr BASE, L->base
2636    |   cbnz CRET1, ->vmeta_binop
2637    |  ldr TMP0, [BASE, RB, lsl #3]
2638    |  str TMP0, [BASE, RA, lsl #3]	// Copy result to RA.
2639    |  ins_next
2640    break;
2641
2642  /* -- Constant ops ------------------------------------------------------ */
2643
2644  case BC_KSTR:
2645    |  // RA = dst, RC = str_const (~)
2646    |  mvn RC, RC
2647    |  ldr TMP0, [KBASE, RC, lsl #3]
2648    |   movn TMP1, #~LJ_TSTR
2649    |  add TMP0, TMP0, TMP1, lsl #47
2650    |  str TMP0, [BASE, RA, lsl #3]
2651    |  ins_next
2652    break;
2653  case BC_KCDATA:
2654    |.if FFI
2655    |  // RA = dst, RC = cdata_const (~)
2656    |  mvn RC, RC
2657    |  ldr TMP0, [KBASE, RC, lsl #3]
2658    |   movn TMP1, #~LJ_TCDATA
2659    |  add TMP0, TMP0, TMP1, lsl #47
2660    |  str TMP0, [BASE, RA, lsl #3]
2661    |  ins_next
2662    |.endif
2663    break;
2664  case BC_KSHORT:
2665    |  // RA = dst, RC = int16_literal
2666    |  sxth RCw, RCw
2667    |  add TMP0, RC, TISNUM
2668    |  str TMP0, [BASE, RA, lsl #3]
2669    |  ins_next
2670    break;
2671  case BC_KNUM:
2672    |  // RA = dst, RC = num_const
2673    |  ldr TMP0, [KBASE, RC, lsl #3]
2674    |  str TMP0, [BASE, RA, lsl #3]
2675    |  ins_next
2676    break;
2677  case BC_KPRI:
2678    |  // RA = dst, RC = primitive_type (~)
2679    |  mvn TMP0, RC, lsl #47
2680    |  str TMP0, [BASE, RA, lsl #3]
2681    |  ins_next
2682    break;
2683  case BC_KNIL:
2684    |  // RA = base, RC = end
2685    |  add RA, BASE, RA, lsl #3
2686    |   add RC, BASE, RC, lsl #3
2687    |  str TISNIL, [RA], #8
2688    |1:
2689    |   cmp RA, RC
2690    |  str TISNIL, [RA], #8
2691    |   blt <1
2692    |  ins_next_
2693    break;
2694
2695  /* -- Upvalue and function ops ------------------------------------------ */
2696
2697  case BC_UGET:
2698    |  // RA = dst, RC = uvnum
2699    |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
2700    |   add RC, RC, #offsetof(GCfuncL, uvptr)/8
2701    |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
2702    |  ldr UPVAL:CARG2, [LFUNC:CARG2, RC, lsl #3]
2703    |  ldr CARG2, UPVAL:CARG2->v
2704    |  ldr TMP0, [CARG2]
2705    |  str TMP0, [BASE, RA, lsl #3]
2706    |  ins_next
2707    break;
2708  case BC_USETV:
2709    |  // RA = uvnum, RC = src
2710    |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
2711    |   add RA, RA, #offsetof(GCfuncL, uvptr)/8
2712    |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
2713    |  ldr UPVAL:CARG1, [LFUNC:CARG2, RA, lsl #3]
2714    |   ldr CARG3, [BASE, RC, lsl #3]
2715    |    ldr CARG2, UPVAL:CARG1->v
2716    |  ldrb TMP2w, UPVAL:CARG1->marked
2717    |  ldrb TMP0w, UPVAL:CARG1->closed
2718    |    asr ITYPE, CARG3, #47
2719    |   str CARG3, [CARG2]
2720    |    add ITYPE, ITYPE, #-LJ_TISGCV
2721    |  tst TMP2w, #LJ_GC_BLACK		// isblack(uv)
2722    |  ccmp TMP0w, #0, #4, ne		// && uv->closed
2723    |    ccmn ITYPE, #-(LJ_TNUMX - LJ_TISGCV), #0, ne	// && tvisgcv(v)
2724    |  bhi >2
2725    |1:
2726    |  ins_next
2727    |
2728    |2:  // Check if new value is white.
2729    |  and GCOBJ:CARG3, CARG3, #LJ_GCVMASK
2730    |  ldrb TMP1w, GCOBJ:CARG3->gch.marked
2731    |  tst TMP1w, #LJ_GC_WHITES		// iswhite(str)
2732    |  beq <1
2733    |  // Crossed a write barrier. Move the barrier forward.
2734    |  mov CARG1, GL
2735    |  bl extern lj_gc_barrieruv	// (global_State *g, TValue *tv)
2736    |  b <1
2737    break;
2738  case BC_USETS:
2739    |  // RA = uvnum, RC = str_const (~)
2740    |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
2741    |   add RA, RA, #offsetof(GCfuncL, uvptr)/8
2742    |    mvn RC, RC
2743    |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
2744    |  ldr UPVAL:CARG1, [LFUNC:CARG2, RA, lsl #3]
2745    |   ldr STR:CARG3, [KBASE, RC, lsl #3]
2746    |   movn TMP0, #~LJ_TSTR
2747    |    ldr CARG2, UPVAL:CARG1->v
2748    |  ldrb TMP2w, UPVAL:CARG1->marked
2749    |   add TMP0, STR:CARG3, TMP0, lsl #47
2750    |    ldrb TMP1w, STR:CARG3->marked
2751    |   str TMP0, [CARG2]
2752    |  tbnz TMP2w, #2, >2		// isblack(uv)
2753    |1:
2754    |  ins_next
2755    |
2756    |2:  // Check if string is white and ensure upvalue is closed.
2757    |  ldrb TMP0w, UPVAL:CARG1->closed
2758    |    tst TMP1w, #LJ_GC_WHITES	// iswhite(str)
2759    |  ccmp TMP0w, #0, #0, ne
2760    |  beq <1
2761    |  // Crossed a write barrier. Move the barrier forward.
2762    |  mov CARG1, GL
2763    |  bl extern lj_gc_barrieruv	// (global_State *g, TValue *tv)
2764    |  b <1
2765    break;
2766  case BC_USETN:
2767    |  // RA = uvnum, RC = num_const
2768    |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
2769    |   add RA, RA, #offsetof(GCfuncL, uvptr)/8
2770    |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
2771    |  ldr UPVAL:CARG2, [LFUNC:CARG2, RA, lsl #3]
2772    |   ldr TMP0, [KBASE, RC, lsl #3]
2773    |  ldr CARG2, UPVAL:CARG2->v
2774    |   str TMP0, [CARG2]
2775    |  ins_next
2776    break;
2777  case BC_USETP:
2778    |  // RA = uvnum, RC = primitive_type (~)
2779    |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
2780    |   add RA, RA, #offsetof(GCfuncL, uvptr)/8
2781    |  and LFUNC:CARG2, CARG2, #LJ_GCVMASK
2782    |  ldr UPVAL:CARG2, [LFUNC:CARG2, RA, lsl #3]
2783    |   mvn TMP0, RC, lsl #47
2784    |  ldr CARG2, UPVAL:CARG2->v
2785    |   str TMP0, [CARG2]
2786    |  ins_next
2787    break;
2788
2789  case BC_UCLO:
2790    |  // RA = level, RC = target
2791    |  ldr CARG3, L->openupval
2792    |   add RC, PC, RC, lsl #2
2793    |    str BASE, L->base
2794    |   sub PC, RC, #0x20000
2795    |  cbz CARG3, >1
2796    |  mov CARG1, L
2797    |  add CARG2, BASE, RA, lsl #3
2798    |  bl extern lj_func_closeuv	// (lua_State *L, TValue *level)
2799    |  ldr BASE, L->base
2800    |1:
2801    |  ins_next
2802    break;
2803
2804  case BC_FNEW:
2805    |  // RA = dst, RC = proto_const (~) (holding function prototype)
2806    |  mvn RC, RC
2807    |   str BASE, L->base
2808    |  ldr LFUNC:CARG3, [BASE, FRAME_FUNC]
2809    |    str PC, SAVE_PC
2810    |   ldr CARG2, [KBASE, RC, lsl #3]
2811    |    mov CARG1, L
2812    |  and LFUNC:CARG3, CARG3, #LJ_GCVMASK
2813    |  // (lua_State *L, GCproto *pt, GCfuncL *parent)
2814    |  bl extern lj_func_newL_gc
2815    |  // Returns GCfuncL *.
2816    |  ldr BASE, L->base
2817    |   movn TMP0, #~LJ_TFUNC
2818    |   add CRET1, CRET1, TMP0, lsl #47
2819    |  str CRET1, [BASE, RA, lsl #3]
2820    |  ins_next
2821    break;
2822
2823  /* -- Table ops --------------------------------------------------------- */
2824
2825  case BC_TNEW:
2826  case BC_TDUP:
2827    |  // RA = dst, RC = (hbits|asize) | tab_const (~)
2828    |  ldp CARG3, CARG4, GL->gc.total	// Assumes threshold follows total.
2829    |   str BASE, L->base
2830    |   str PC, SAVE_PC
2831    |   mov CARG1, L
2832    |  cmp CARG3, CARG4
2833    |  bhs >5
2834    |1:
2835    if (op == BC_TNEW) {
2836      |  and CARG2, RC, #0x7ff
2837      |   lsr CARG3, RC, #11
2838      |  cmp CARG2, #0x7ff
2839      |  mov TMP0, #0x801
2840      |  csel CARG2, CARG2, TMP0, ne
2841      |  bl extern lj_tab_new  // (lua_State *L, int32_t asize, uint32_t hbits)
2842      |  // Returns GCtab *.
2843    } else {
2844      |  mvn RC, RC
2845      |  ldr CARG2, [KBASE, RC, lsl #3]
2846      |  bl extern lj_tab_dup  // (lua_State *L, Table *kt)
2847      |  // Returns GCtab *.
2848    }
2849    |  ldr BASE, L->base
2850    |   movk CRET1, #(LJ_TTAB>>1)&0xffff, lsl #48
2851    |  str CRET1, [BASE, RA, lsl #3]
2852    |  ins_next
2853    |
2854    |5:
2855    |  bl extern lj_gc_step_fixtop  // (lua_State *L)
2856    |  mov CARG1, L
2857    |  b <1
2858    break;
2859
2860  case BC_GGET:
2861    |  // RA = dst, RC = str_const (~)
2862  case BC_GSET:
2863    |  // RA = dst, RC = str_const (~)
2864    |  ldr LFUNC:CARG1, [BASE, FRAME_FUNC]
2865    |   mvn RC, RC
2866    |  and LFUNC:CARG1, CARG1, #LJ_GCVMASK
2867    |  ldr TAB:CARG2, LFUNC:CARG1->env
2868    |   ldr STR:RC, [KBASE, RC, lsl #3]
2869    if (op == BC_GGET) {
2870      |  b ->BC_TGETS_Z
2871    } else {
2872      |  b ->BC_TSETS_Z
2873    }
2874    break;
2875
2876  case BC_TGETV:
2877    |  decode_RB RB, INS
2878    |   and RC, RC, #255
2879    |  // RA = dst, RB = table, RC = key
2880    |  ldr CARG2, [BASE, RB, lsl #3]
2881    |   ldr TMP1, [BASE, RC, lsl #3]
2882    |  checktab CARG2, ->vmeta_tgetv
2883    |  checkint TMP1, >9		// Integer key?
2884    |  ldr CARG3, TAB:CARG2->array
2885    |   ldr CARG1w, TAB:CARG2->asize
2886    |  add CARG3, CARG3, TMP1, uxtw #3
2887    |   cmp TMP1w, CARG1w		// In array part?
2888    |   bhs ->vmeta_tgetv
2889    |  ldr TMP0, [CARG3]
2890    |  cmp TMP0, TISNIL
2891    |  beq >5
2892    |1:
2893    |  str TMP0, [BASE, RA, lsl #3]
2894    |  ins_next
2895    |
2896    |5:  // Check for __index if table value is nil.
2897    |  ldr TAB:CARG1, TAB:CARG2->metatable
2898    |  cbz TAB:CARG1, <1		// No metatable: done.
2899    |  ldrb TMP1w, TAB:CARG1->nomm
2900    |  tbnz TMP1w, #MM_index, <1	// 'no __index' flag set: done.
2901    |  b ->vmeta_tgetv
2902    |
2903    |9:
2904    |  asr ITYPE, TMP1, #47
2905    |  cmn ITYPE, #-LJ_TSTR		// String key?
2906    |  bne ->vmeta_tgetv
2907    |   and STR:RC, TMP1, #LJ_GCVMASK
2908    |  b ->BC_TGETS_Z
2909    break;
2910  case BC_TGETS:
2911    |  decode_RB RB, INS
2912    |   and RC, RC, #255
2913    |  // RA = dst, RB = table, RC = str_const (~)
2914    |  ldr CARG2, [BASE, RB, lsl #3]
2915    |   mvn RC, RC
2916    |   ldr STR:RC, [KBASE, RC, lsl #3]
2917    |  checktab CARG2, ->vmeta_tgets1
2918    |->BC_TGETS_Z:
2919    |  // TAB:CARG2 = GCtab *, STR:RC = GCstr *, RA = dst
2920    |  ldr TMP1w, TAB:CARG2->hmask
2921    |   ldr TMP2w, STR:RC->hash
2922    |    ldr NODE:CARG3, TAB:CARG2->node
2923    |  and TMP1w, TMP1w, TMP2w		// idx = str->hash & tab->hmask
2924    |  add TMP1, TMP1, TMP1, lsl #1
2925    |  movn CARG4, #~LJ_TSTR
2926    |    add NODE:CARG3, NODE:CARG3, TMP1, lsl #3  // node = tab->node + idx*3*8
2927    |  add CARG4, STR:RC, CARG4, lsl #47	// Tagged key to look for.
2928    |1:
2929    |  ldp TMP0, CARG1, NODE:CARG3->val
2930    |   ldr NODE:CARG3, NODE:CARG3->next
2931    |  cmp CARG1, CARG4
2932    |  bne >4
2933    |  cmp TMP0, TISNIL
2934    |  beq >5
2935    |3:
2936    |  str TMP0, [BASE, RA, lsl #3]
2937    |  ins_next
2938    |
2939    |4:  // Follow hash chain.
2940    |  cbnz NODE:CARG3, <1
2941    |  // End of hash chain: key not found, nil result.
2942    |   mov TMP0, TISNIL
2943    |
2944    |5:  // Check for __index if table value is nil.
2945    |  ldr TAB:CARG1, TAB:CARG2->metatable
2946    |  cbz TAB:CARG1, <3		// No metatable: done.
2947    |  ldrb TMP1w, TAB:CARG1->nomm
2948    |  tbnz TMP1w, #MM_index, <3	// 'no __index' flag set: done.
2949    |  b ->vmeta_tgets
2950    break;
2951  case BC_TGETB:
2952    |  decode_RB RB, INS
2953    |   and RC, RC, #255
2954    |  // RA = dst, RB = table, RC = index
2955    |  ldr CARG2, [BASE, RB, lsl #3]
2956    |  checktab CARG2, ->vmeta_tgetb
2957    |  ldr CARG3, TAB:CARG2->array
2958    |   ldr CARG1w, TAB:CARG2->asize
2959    |  add CARG3, CARG3, RC, lsl #3
2960    |   cmp RCw, CARG1w			// In array part?
2961    |   bhs ->vmeta_tgetb
2962    |  ldr TMP0, [CARG3]
2963    |  cmp TMP0, TISNIL
2964    |  beq >5
2965    |1:
2966    |  str TMP0, [BASE, RA, lsl #3]
2967    |  ins_next
2968    |
2969    |5:  // Check for __index if table value is nil.
2970    |  ldr TAB:CARG1, TAB:CARG2->metatable
2971    |  cbz TAB:CARG1, <1		// No metatable: done.
2972    |  ldrb TMP1w, TAB:CARG1->nomm
2973    |  tbnz TMP1w, #MM_index, <1	// 'no __index' flag set: done.
2974    |  b ->vmeta_tgetb
2975    break;
2976  case BC_TGETR:
2977    |  decode_RB RB, INS
2978    |   and RC, RC, #255
2979    |  // RA = dst, RB = table, RC = key
2980    |  ldr CARG1, [BASE, RB, lsl #3]
2981    |   ldr TMP1, [BASE, RC, lsl #3]
2982    |  and TAB:CARG1, CARG1, #LJ_GCVMASK
2983    |  ldr CARG3, TAB:CARG1->array
2984    |   ldr TMP2w, TAB:CARG1->asize
2985    |  add CARG3, CARG3, TMP1w, uxtw #3
2986    |   cmp TMP1w, TMP2w		// In array part?
2987    |   bhs ->vmeta_tgetr
2988    |  ldr TMP0, [CARG3]
2989    |->BC_TGETR_Z:
2990    |  str TMP0, [BASE, RA, lsl #3]
2991    |  ins_next
2992    break;
2993
2994  case BC_TSETV:
2995    |  decode_RB RB, INS
2996    |   and RC, RC, #255
2997    |  // RA = src, RB = table, RC = key
2998    |  ldr CARG2, [BASE, RB, lsl #3]
2999    |   ldr TMP1, [BASE, RC, lsl #3]
3000    |  checktab CARG2, ->vmeta_tsetv
3001    |  checkint TMP1, >9		// Integer key?
3002    |  ldr CARG3, TAB:CARG2->array
3003    |   ldr CARG1w, TAB:CARG2->asize
3004    |  add CARG3, CARG3, TMP1, uxtw #3
3005    |   cmp TMP1w, CARG1w		// In array part?
3006    |   bhs ->vmeta_tsetv
3007    |  ldr TMP1, [CARG3]
3008    |   ldr TMP0, [BASE, RA, lsl #3]
3009    |    ldrb TMP2w, TAB:CARG2->marked
3010    |  cmp TMP1, TISNIL			// Previous value is nil?
3011    |  beq >5
3012    |1:
3013    |   str TMP0, [CARG3]
3014    |    tbnz TMP2w, #2, >7		// isblack(table)
3015    |2:
3016    |   ins_next
3017    |
3018    |5:  // Check for __newindex if previous value is nil.
3019    |  ldr TAB:CARG1, TAB:CARG2->metatable
3020    |  cbz TAB:CARG1, <1		// No metatable: done.
3021    |  ldrb TMP1w, TAB:CARG1->nomm
3022    |  tbnz TMP1w, #MM_newindex, <1	// 'no __newindex' flag set: done.
3023    |  b ->vmeta_tsetv
3024    |
3025    |7:  // Possible table write barrier for the value. Skip valiswhite check.
3026    |  barrierback TAB:CARG2, TMP2w, TMP1
3027    |  b <2
3028    |
3029    |9:
3030    |  asr ITYPE, TMP1, #47
3031    |  cmn ITYPE, #-LJ_TSTR		// String key?
3032    |  bne ->vmeta_tsetv
3033    |   and STR:RC, TMP1, #LJ_GCVMASK
3034    |  b ->BC_TSETS_Z
3035    break;
3036  case BC_TSETS:
3037    |  decode_RB RB, INS
3038    |   and RC, RC, #255
3039    |  // RA = dst, RB = table, RC = str_const (~)
3040    |  ldr CARG2, [BASE, RB, lsl #3]
3041    |   mvn RC, RC
3042    |   ldr STR:RC, [KBASE, RC, lsl #3]
3043    |  checktab CARG2, ->vmeta_tsets1
3044    |->BC_TSETS_Z:
3045    |  // TAB:CARG2 = GCtab *, STR:RC = GCstr *, RA = src
3046    |  ldr TMP1w, TAB:CARG2->hmask
3047    |   ldr TMP2w, STR:RC->hash
3048    |    ldr NODE:CARG3, TAB:CARG2->node
3049    |  and TMP1w, TMP1w, TMP2w		// idx = str->hash & tab->hmask
3050    |  add TMP1, TMP1, TMP1, lsl #1
3051    |  movn CARG4, #~LJ_TSTR
3052    |    add NODE:CARG3, NODE:CARG3, TMP1, lsl #3  // node = tab->node + idx*3*8
3053    |  add CARG4, STR:RC, CARG4, lsl #47	// Tagged key to look for.
3054    |   strb wzr, TAB:CARG2->nomm	// Clear metamethod cache.
3055    |1:
3056    |  ldp TMP1, CARG1, NODE:CARG3->val
3057    |   ldr NODE:TMP3, NODE:CARG3->next
3058    |    ldrb TMP2w, TAB:CARG2->marked
3059    |  cmp CARG1, CARG4
3060    |  bne >5
3061    |   ldr TMP0, [BASE, RA, lsl #3]
3062    |  cmp TMP1, TISNIL			// Previous value is nil?
3063    |  beq >4
3064    |2:
3065    |   str TMP0, NODE:CARG3->val
3066    |    tbnz TMP2w, #2, >7		// isblack(table)
3067    |3:
3068    |  ins_next
3069    |
3070    |4:  // Check for __newindex if previous value is nil.
3071    |  ldr TAB:CARG1, TAB:CARG2->metatable
3072    |  cbz TAB:CARG1, <2		// No metatable: done.
3073    |  ldrb TMP1w, TAB:CARG1->nomm
3074    |  tbnz TMP1w, #MM_newindex, <2	// 'no __newindex' flag set: done.
3075    |  b ->vmeta_tsets
3076    |
3077    |5:  // Follow hash chain.
3078    |  mov NODE:CARG3, NODE:TMP3
3079    |  cbnz NODE:TMP3, <1
3080    |  // End of hash chain: key not found, add a new one.
3081    |
3082    |  // But check for __newindex first.
3083    |  ldr TAB:CARG1, TAB:CARG2->metatable
3084    |  cbz TAB:CARG1, >6		// No metatable: continue.
3085    |  ldrb TMP1w, TAB:CARG1->nomm
3086    |  // 'no __newindex' flag NOT set: check.
3087    |  tbz TMP1w, #MM_newindex, ->vmeta_tsets
3088    |6:
3089    |  movn TMP1, #~LJ_TSTR
3090    |   str PC, SAVE_PC
3091    |  add TMP0, STR:RC, TMP1, lsl #47
3092    |   str BASE, L->base
3093    |   mov CARG1, L
3094    |  str TMP0, TMPD
3095    |   add CARG3, sp, TMPDofs
3096    |  bl extern lj_tab_newkey		// (lua_State *L, GCtab *t, TValue *k)
3097    |  // Returns TValue *.
3098    |  ldr BASE, L->base
3099    |  ldr TMP0, [BASE, RA, lsl #3]
3100    |  str TMP0, [CRET1]
3101    |  b <3				// No 2nd write barrier needed.
3102    |
3103    |7:  // Possible table write barrier for the value. Skip valiswhite check.
3104    |  barrierback TAB:CARG2, TMP2w, TMP1
3105    |  b <3
3106    break;
3107  case BC_TSETB:
3108    |  decode_RB RB, INS
3109    |   and RC, RC, #255
3110    |  // RA = src, RB = table, RC = index
3111    |  ldr CARG2, [BASE, RB, lsl #3]
3112    |  checktab CARG2, ->vmeta_tsetb
3113    |  ldr CARG3, TAB:CARG2->array
3114    |   ldr CARG1w, TAB:CARG2->asize
3115    |  add CARG3, CARG3, RC, lsl #3
3116    |   cmp RCw, CARG1w			// In array part?
3117    |   bhs ->vmeta_tsetb
3118    |  ldr TMP1, [CARG3]
3119    |   ldr TMP0, [BASE, RA, lsl #3]
3120    |    ldrb TMP2w, TAB:CARG2->marked
3121    |  cmp TMP1, TISNIL			// Previous value is nil?
3122    |  beq >5
3123    |1:
3124    |   str TMP0, [CARG3]
3125    |    tbnz TMP2w, #2, >7		// isblack(table)
3126    |2:
3127    |   ins_next
3128    |
3129    |5:  // Check for __newindex if previous value is nil.
3130    |  ldr TAB:CARG1, TAB:CARG2->metatable
3131    |  cbz TAB:CARG1, <1		// No metatable: done.
3132    |  ldrb TMP1w, TAB:CARG1->nomm
3133    |  tbnz TMP1w, #MM_newindex, <1	// 'no __newindex' flag set: done.
3134    |  b ->vmeta_tsetb
3135    |
3136    |7:  // Possible table write barrier for the value. Skip valiswhite check.
3137    |  barrierback TAB:CARG2, TMP2w, TMP1
3138    |  b <2
3139    break;
3140  case BC_TSETR:
3141    |  decode_RB RB, INS
3142    |   and RC, RC, #255
3143    |  // RA = src, RB = table, RC = key
3144    |  ldr CARG2, [BASE, RB, lsl #3]
3145    |   ldr TMP1, [BASE, RC, lsl #3]
3146    |  and TAB:CARG2, CARG2, #LJ_GCVMASK
3147    |  ldr CARG1, TAB:CARG2->array
3148    |    ldrb TMP2w, TAB:CARG2->marked
3149    |   ldr CARG4w, TAB:CARG2->asize
3150    |  add CARG1, CARG1, TMP1, uxtw #3
3151    |    tbnz TMP2w, #2, >7		// isblack(table)
3152    |2:
3153    |   cmp TMP1w, CARG4w		// In array part?
3154    |   bhs ->vmeta_tsetr
3155    |->BC_TSETR_Z:
3156    |   ldr TMP0, [BASE, RA, lsl #3]
3157    |   str TMP0, [CARG1]
3158    |   ins_next
3159    |
3160    |7:  // Possible table write barrier for the value. Skip valiswhite check.
3161    |  barrierback TAB:CARG2, TMP2w, TMP0
3162    |  b <2
3163    break;
3164
3165  case BC_TSETM:
3166    |  // RA = base (table at base-1), RC = num_const (start index)
3167    |  add RA, BASE, RA, lsl #3
3168    |1:
3169    |   ldr RBw, SAVE_MULTRES
3170    |  ldr TAB:CARG2, [RA, #-8]		// Guaranteed to be a table.
3171    |   ldr TMP1, [KBASE, RC, lsl #3]	// Integer constant is in lo-word.
3172    |    sub RB, RB, #8
3173    |    cbz RB, >4			// Nothing to copy?
3174    |  and TAB:CARG2, CARG2, #LJ_GCVMASK
3175    |  ldr CARG1w, TAB:CARG2->asize
3176    |   add CARG3w, TMP1w, RBw, lsr #3
3177    |   ldr CARG4, TAB:CARG2->array
3178    |  cmp CARG3, CARG1
3179    |    add RB, RA, RB
3180    |  bhi >5
3181    |   add TMP1, CARG4, TMP1w, uxtw #3
3182    |    ldrb TMP2w, TAB:CARG2->marked
3183    |3:  // Copy result slots to table.
3184    |   ldr TMP0, [RA], #8
3185    |   str TMP0, [TMP1], #8
3186    |  cmp RA, RB
3187    |  blo <3
3188    |    tbnz TMP2w, #2, >7		// isblack(table)
3189    |4:
3190    |  ins_next
3191    |
3192    |5:  // Need to resize array part.
3193    |   str BASE, L->base
3194    |  mov CARG1, L
3195    |   str PC, SAVE_PC
3196    |  bl extern lj_tab_reasize		// (lua_State *L, GCtab *t, int nasize)
3197    |  // Must not reallocate the stack.
3198    |  b <1
3199    |
3200    |7:  // Possible table write barrier for any value. Skip valiswhite check.
3201    |  barrierback TAB:CARG2, TMP2w, TMP1
3202    |  b <4
3203    break;
3204
3205  /* -- Calls and vararg handling ----------------------------------------- */
3206
3207  case BC_CALLM:
3208    |  // RA = base, (RB = nresults+1,) RC = extra_nargs
3209    |  ldr TMP0w, SAVE_MULTRES
3210    |  decode_RC8RD NARGS8:RC, RC
3211    |  add NARGS8:RC, NARGS8:RC, TMP0
3212    |  b ->BC_CALL_Z
3213    break;
3214  case BC_CALL:
3215    |  decode_RC8RD NARGS8:RC, RC
3216    |  // RA = base, (RB = nresults+1,) RC = (nargs+1)*8
3217    |->BC_CALL_Z:
3218    |  mov RB, BASE			// Save old BASE for vmeta_call.
3219    |  add BASE, BASE, RA, lsl #3
3220    |  ldr CARG3, [BASE]
3221    |   sub NARGS8:RC, NARGS8:RC, #8
3222    |   add BASE, BASE, #16
3223    |  checkfunc CARG3, ->vmeta_call
3224    |  ins_call
3225    break;
3226
3227  case BC_CALLMT:
3228    |  // RA = base, (RB = 0,) RC = extra_nargs
3229    |  ldr TMP0w, SAVE_MULTRES
3230    |  add NARGS8:RC, TMP0, RC, lsl #3
3231    |  b ->BC_CALLT1_Z
3232    break;
3233  case BC_CALLT:
3234    |  lsl NARGS8:RC, RC, #3
3235    |  // RA = base, (RB = 0,) RC = (nargs+1)*8
3236    |->BC_CALLT1_Z:
3237    |  add RA, BASE, RA, lsl #3
3238    |  ldr TMP1, [RA]
3239    |   sub NARGS8:RC, NARGS8:RC, #8
3240    |   add RA, RA, #16
3241    |  checktp CARG3, TMP1, LJ_TFUNC, ->vmeta_callt
3242    |  ldr PC, [BASE, FRAME_PC]
3243    |->BC_CALLT2_Z:
3244    |   mov RB, #0
3245    |   ldrb TMP2w, LFUNC:CARG3->ffid
3246    |  tst PC, #FRAME_TYPE
3247    |  bne >7
3248    |1:
3249    |  str TMP1, [BASE, FRAME_FUNC]	// Copy function down, but keep PC.
3250    |  cbz NARGS8:RC, >3
3251    |2:
3252    |  ldr TMP0, [RA, RB]
3253    |   add TMP1, RB, #8
3254    |   cmp TMP1, NARGS8:RC
3255    |  str TMP0, [BASE, RB]
3256    |    mov RB, TMP1
3257    |   bne <2
3258    |3:
3259    |  cmp TMP2, #1			// (> FF_C) Calling a fast function?
3260    |  bhi >5
3261    |4:
3262    |  ins_callt
3263    |
3264    |5:  // Tailcall to a fast function with a Lua frame below.
3265    |  ldrb RAw, [PC, #-3]
3266    |  sub CARG1, BASE, RA, lsl #3
3267    |  ldr LFUNC:CARG1, [CARG1, #-32]
3268    |  and LFUNC:CARG1, CARG1, #LJ_GCVMASK
3269    |  ldr CARG1, LFUNC:CARG1->pc
3270    |  ldr KBASE, [CARG1, #PC2PROTO(k)]
3271    |  b <4
3272    |
3273    |7:  // Tailcall from a vararg function.
3274    |  eor PC, PC, #FRAME_VARG
3275    |  tst PC, #FRAME_TYPEP		// Vararg frame below?
3276    |  csel TMP2, RB, TMP2, ne		// Clear ffid if no Lua function below.
3277    |  bne <1
3278    |  sub BASE, BASE, PC
3279    |  ldr PC, [BASE, FRAME_PC]
3280    |  tst PC, #FRAME_TYPE
3281    |  csel TMP2, RB, TMP2, ne		// Clear ffid if no Lua function below.
3282    |  b <1
3283    break;
3284
3285  case BC_ITERC:
3286    |  // RA = base, (RB = nresults+1, RC = nargs+1 (2+1))
3287    |  add RA, BASE, RA, lsl #3
3288    |  ldr CARG3, [RA, #-24]
3289    |    mov RB, BASE			// Save old BASE for vmeta_call.
3290    |   ldp CARG1, CARG2, [RA, #-16]
3291    |    add BASE, RA, #16
3292    |    mov NARGS8:RC, #16		// Iterators get 2 arguments.
3293    |  str CARG3, [RA]			// Copy callable.
3294    |   stp CARG1, CARG2, [RA, #16]	// Copy state and control var.
3295    |  checkfunc CARG3, ->vmeta_call
3296    |  ins_call
3297    break;
3298
3299  case BC_ITERN:
3300    |  // RA = base, (RB = nresults+1, RC = nargs+1 (2+1))
3301    |.if JIT
3302    |  // NYI: add hotloop, record BC_ITERN.
3303    |.endif
3304    |  add RA, BASE, RA, lsl #3
3305    |  ldr TAB:RB, [RA, #-16]
3306    |    ldrh TMP3w, [PC, #2]
3307    |  ldr CARG1w, [RA, #-8]		// Get index from control var.
3308    |    add PC, PC, #4
3309    |    add TMP3, PC, TMP3, lsl #2
3310    |  and TAB:RB, RB, #LJ_GCVMASK
3311    |    sub TMP3, TMP3, #0x20000
3312    |  ldr TMP1w, TAB:RB->asize
3313    |   ldr CARG2, TAB:RB->array
3314    |1:  // Traverse array part.
3315    |  subs RC, CARG1, TMP1
3316    |   add CARG3, CARG2, CARG1, lsl #3
3317    |  bhs >5				// Index points after array part?
3318    |   ldr TMP0, [CARG3]
3319    |   cmp TMP0, TISNIL
3320    |   cinc CARG1, CARG1, eq		// Skip holes in array part.
3321    |   beq <1
3322    |   add CARG1, CARG1, TISNUM
3323    |   stp CARG1, TMP0, [RA]
3324    |    add CARG1, CARG1, #1
3325    |3:
3326    |    str CARG1w, [RA, #-8]		// Update control var.
3327    |  mov PC, TMP3
3328    |4:
3329    |  ins_next
3330    |
3331    |5:  // Traverse hash part.
3332    |  ldr TMP2w, TAB:RB->hmask
3333    |   ldr NODE:RB, TAB:RB->node
3334    |6:
3335    |   add CARG1, RC, RC, lsl #1
3336    |  cmp RC, TMP2			// End of iteration? Branch to ITERN+1.
3337    |   add NODE:CARG3, NODE:RB, CARG1, lsl #3  // node = tab->node + idx*3*8
3338    |  bhi <4
3339    |  ldp TMP0, CARG1, NODE:CARG3->val
3340    |  cmp TMP0, TISNIL
3341    |   add RC, RC, #1
3342    |  beq <6				// Skip holes in hash part.
3343    |  stp CARG1, TMP0, [RA]
3344    |  add CARG1, RC, TMP1
3345    |  b <3
3346    break;
3347
3348  case BC_ISNEXT:
3349    |  // RA = base, RC = target (points to ITERN)
3350    |  add RA, BASE, RA, lsl #3
3351    |  ldr CFUNC:CARG1, [RA, #-24]
3352    |     add RC, PC, RC, lsl #2
3353    |   ldp TAB:CARG3, CARG4, [RA, #-16]
3354    |     sub RC, RC, #0x20000
3355    |  checkfunc CFUNC:CARG1, >5
3356    |   asr TMP0, TAB:CARG3, #47
3357    |  ldrb TMP1w, CFUNC:CARG1->ffid
3358    |   cmn TMP0, #-LJ_TTAB
3359    |   ccmp CARG4, TISNIL, #0, eq
3360    |  ccmp TMP1w, #FF_next_N, #0, eq
3361    |  bne >5
3362    |  mov TMP0w, #0xfffe7fff
3363    |  lsl TMP0, TMP0, #32
3364    |  str TMP0, [RA, #-8]		// Initialize control var.
3365    |1:
3366    |     mov PC, RC
3367    |  ins_next
3368    |
3369    |5:  // Despecialize bytecode if any of the checks fail.
3370    |  mov TMP0, #BC_JMP
3371    |   mov TMP1, #BC_ITERC
3372    |  strb TMP0w, [PC, #-4]
3373    |   strb TMP1w, [RC]
3374    |  b <1
3375    break;
3376
3377  case BC_VARG:
3378    |  decode_RB RB, INS
3379    |   and RC, RC, #255
3380    |  // RA = base, RB = (nresults+1), RC = numparams
3381    |  ldr TMP1, [BASE, FRAME_PC]
3382    |  add RC, BASE, RC, lsl #3
3383    |   add RA, BASE, RA, lsl #3
3384    |  add RC, RC, #FRAME_VARG
3385    |   add TMP2, RA, RB, lsl #3
3386    |  sub RC, RC, TMP1			// RC = vbase
3387    |  // Note: RC may now be even _above_ BASE if nargs was < numparams.
3388    |   sub TMP3, BASE, #16		// TMP3 = vtop
3389    |  cbz RB, >5
3390    |   sub TMP2, TMP2, #16
3391    |1:  // Copy vararg slots to destination slots.
3392    |  cmp RC, TMP3
3393    |  ldr TMP0, [RC], #8
3394    |  csel TMP0, TMP0, TISNIL, lo
3395    |   cmp RA, TMP2
3396    |  str TMP0, [RA], #8
3397    |   blo <1
3398    |2:
3399    |  ins_next
3400    |
3401    |5:  // Copy all varargs.
3402    |  ldr TMP0, L->maxstack
3403    |   subs TMP2, TMP3, RC
3404    |   csel RB, xzr, TMP2, le		// MULTRES = (max(vtop-vbase,0)+1)*8
3405    |   add RB, RB, #8
3406    |  add TMP1, RA, TMP2
3407    |   str RBw, SAVE_MULTRES
3408    |   ble <2				// Nothing to copy.
3409    |  cmp TMP1, TMP0
3410    |  bhi >7
3411    |6:
3412    |  ldr TMP0, [RC], #8
3413    |  str TMP0, [RA], #8
3414    |  cmp RC, TMP3
3415    |  blo <6
3416    |  b <2
3417    |
3418    |7:  // Grow stack for varargs.
3419    |  lsr CARG2, TMP2, #3
3420    |   stp BASE, RA, L->base
3421    |  mov CARG1, L
3422    |  sub RC, RC, BASE			// Need delta, because BASE may change.
3423    |   str PC, SAVE_PC
3424    |  bl extern lj_state_growstack	// (lua_State *L, int n)
3425    |  ldp BASE, RA, L->base
3426    |  add RC, BASE, RC
3427    |  sub TMP3, BASE, #16
3428    |  b <6
3429    break;
3430
3431  /* -- Returns ----------------------------------------------------------- */
3432
3433  case BC_RETM:
3434    |  // RA = results, RC = extra results
3435    |  ldr TMP0w, SAVE_MULTRES
3436    |   ldr PC, [BASE, FRAME_PC]
3437    |    add RA, BASE, RA, lsl #3
3438    |  add RC, TMP0, RC, lsl #3
3439    |  b ->BC_RETM_Z
3440    break;
3441
3442  case BC_RET:
3443    |  // RA = results, RC = nresults+1
3444    |  ldr PC, [BASE, FRAME_PC]
3445    |   lsl RC, RC, #3
3446    |    add RA, BASE, RA, lsl #3
3447    |->BC_RETM_Z:
3448    |   str RCw, SAVE_MULTRES
3449    |1:
3450    |  ands CARG1, PC, #FRAME_TYPE
3451    |   eor CARG2, PC, #FRAME_VARG
3452    |  bne ->BC_RETV2_Z
3453    |
3454    |->BC_RET_Z:
3455    |  // BASE = base, RA = resultptr, RC = (nresults+1)*8, PC = return
3456    |  ldr INSw, [PC, #-4]
3457    |  subs TMP1, RC, #8
3458    |   sub CARG3, BASE, #16
3459    |  beq >3
3460    |2:
3461    |  ldr TMP0, [RA], #8
3462    |   add BASE, BASE, #8
3463    |   sub TMP1, TMP1, #8
3464    |  str TMP0, [BASE, #-24]
3465    |   cbnz TMP1, <2
3466    |3:
3467    |  decode_RA RA, INS
3468    |  sub CARG4, CARG3, RA, lsl #3
3469    |   decode_RB RB, INS
3470    |  ldr LFUNC:CARG1, [CARG4, FRAME_FUNC]
3471    |5:
3472    |  cmp RC, RB, lsl #3		// More results expected?
3473    |  blo >6
3474    |  and LFUNC:CARG1, CARG1, #LJ_GCVMASK
3475    |  mov BASE, CARG4
3476    |  ldr CARG2, LFUNC:CARG1->pc
3477    |  ldr KBASE, [CARG2, #PC2PROTO(k)]
3478    |   ins_next
3479    |
3480    |6:  // Fill up results with nil.
3481    |  add BASE, BASE, #8
3482    |   add RC, RC, #8
3483    |  str TISNIL, [BASE, #-24]
3484    |  b <5
3485    |
3486    |->BC_RETV1_Z:  // Non-standard return case.
3487    |  add RA, BASE, RA, lsl #3
3488    |->BC_RETV2_Z:
3489    |  tst CARG2, #FRAME_TYPEP
3490    |  bne ->vm_return
3491    |  // Return from vararg function: relocate BASE down.
3492    |  sub BASE, BASE, CARG2
3493    |  ldr PC, [BASE, FRAME_PC]
3494    |  b <1
3495    break;
3496
3497  case BC_RET0: case BC_RET1:
3498    |  // RA = results, RC = nresults+1
3499    |  ldr PC, [BASE, FRAME_PC]
3500    |   lsl RC, RC, #3
3501    |   str RCw, SAVE_MULTRES
3502    |  ands CARG1, PC, #FRAME_TYPE
3503    |   eor CARG2, PC, #FRAME_VARG
3504    |  bne ->BC_RETV1_Z
3505    |   ldr INSw, [PC, #-4]
3506    if (op == BC_RET1) {
3507      |  ldr TMP0, [BASE, RA, lsl #3]
3508    }
3509    |  sub CARG4, BASE, #16
3510    |   decode_RA RA, INS
3511    |  sub BASE, CARG4, RA, lsl #3
3512    if (op == BC_RET1) {
3513      |  str TMP0, [CARG4], #8
3514    }
3515    |   decode_RB RB, INS
3516    |  ldr LFUNC:CARG1, [BASE, FRAME_FUNC]
3517    |5:
3518    |  cmp RC, RB, lsl #3
3519    |  blo >6
3520    |  and LFUNC:CARG1, CARG1, #LJ_GCVMASK
3521    |  ldr CARG2, LFUNC:CARG1->pc
3522    |  ldr KBASE, [CARG2, #PC2PROTO(k)]
3523    |  ins_next
3524    |
3525    |6:  // Fill up results with nil.
3526    |  add RC, RC, #8
3527    |  str TISNIL, [CARG4], #8
3528    |  b <5
3529    break;
3530
3531  /* -- Loops and branches ------------------------------------------------ */
3532
3533  |.define FOR_IDX,  [RA];      .define FOR_TIDX,  [RA, #4]
3534  |.define FOR_STOP, [RA, #8];  .define FOR_TSTOP, [RA, #12]
3535  |.define FOR_STEP, [RA, #16]; .define FOR_TSTEP, [RA, #20]
3536  |.define FOR_EXT,  [RA, #24]; .define FOR_TEXT,  [RA, #28]
3537
3538  case BC_FORL:
3539    |.if JIT
3540    |  hotloop
3541    |.endif
3542    |  // Fall through. Assumes BC_IFORL follows.
3543    break;
3544
3545  case BC_JFORI:
3546  case BC_JFORL:
3547#if !LJ_HASJIT
3548    break;
3549#endif
3550  case BC_FORI:
3551  case BC_IFORL:
3552    |  // RA = base, RC = target (after end of loop or start of loop)
3553    vk = (op == BC_IFORL || op == BC_JFORL);
3554    |  add RA, BASE, RA, lsl #3
3555    |  ldp CARG1, CARG2, FOR_IDX		// CARG1 = IDX, CARG2 = STOP
3556    |   ldr CARG3, FOR_STEP			// CARG3 = STEP
3557    if (op != BC_JFORL) {
3558      |   add RC, PC, RC, lsl #2
3559      |   sub RC, RC, #0x20000
3560    }
3561    |  checkint CARG1, >5
3562    if (!vk) {
3563      |  checkint CARG2, ->vmeta_for
3564      |   checkint CARG3, ->vmeta_for
3565      |  tbnz CARG3w, #31, >4
3566      |  cmp CARG1w, CARG2w
3567    } else {
3568      |  adds CARG1w, CARG1w, CARG3w
3569      |  bvs >2
3570      |   add TMP0, CARG1, TISNUM
3571      |  tbnz CARG3w, #31, >4
3572      |  cmp CARG1w, CARG2w
3573    }
3574    |1:
3575    if (op == BC_FORI) {
3576      |  csel PC, RC, PC, gt
3577    } else if (op == BC_JFORI) {
3578      |  mov PC, RC
3579      |  ldrh RCw, [RC, #-2]
3580    } else if (op == BC_IFORL) {
3581      |  csel PC, RC, PC, le
3582    }
3583    if (vk) {
3584      |   str TMP0, FOR_IDX
3585      |   str TMP0, FOR_EXT
3586    } else {
3587      |  str CARG1, FOR_EXT
3588    }
3589    if (op == BC_JFORI || op == BC_JFORL) {
3590      |  ble =>BC_JLOOP
3591    }
3592    |2:
3593    |   ins_next
3594    |
3595    |4:  // Invert check for negative step.
3596    |  cmp CARG2w, CARG1w
3597    |  b <1
3598    |
3599    |5:  // FP loop.
3600    |  ldp d0, d1, FOR_IDX
3601    |  blo ->vmeta_for
3602    if (!vk) {
3603      |  checknum CARG2, ->vmeta_for
3604      |   checknum CARG3, ->vmeta_for
3605      |  str d0, FOR_EXT
3606    } else {
3607      |  ldr d2, FOR_STEP
3608      |  fadd d0, d0, d2
3609    }
3610    |  tbnz CARG3, #63, >7
3611    |  fcmp d0, d1
3612    |6:
3613    if (vk) {
3614      |  str d0, FOR_IDX
3615      |  str d0, FOR_EXT
3616    }
3617    if (op == BC_FORI) {
3618      |  csel PC, RC, PC, hi
3619    } else if (op == BC_JFORI) {
3620      |  ldrh RCw, [RC, #-2]
3621      |  bls =>BC_JLOOP
3622    } else if (op == BC_IFORL) {
3623      |  csel PC, RC, PC, ls
3624    } else {
3625      |  bls =>BC_JLOOP
3626    }
3627    |  b <2
3628    |
3629    |7:  // Invert check for negative step.
3630    |  fcmp d1, d0
3631    |  b <6
3632    break;
3633
3634  case BC_ITERL:
3635    |.if JIT
3636    |  hotloop
3637    |.endif
3638    |  // Fall through. Assumes BC_IITERL follows.
3639    break;
3640
3641  case BC_JITERL:
3642#if !LJ_HASJIT
3643    break;
3644#endif
3645  case BC_IITERL:
3646    |  // RA = base, RC = target
3647    |  ldr CARG1, [BASE, RA, lsl #3]
3648    |   add TMP1, BASE, RA, lsl #3
3649    |  cmp CARG1, TISNIL
3650    |  beq >1				// Stop if iterator returned nil.
3651    if (op == BC_JITERL) {
3652      |  str CARG1, [TMP1, #-8]
3653      |  b =>BC_JLOOP
3654    } else {
3655      |  add TMP0, PC, RC, lsl #2	// Otherwise save control var + branch.
3656      |  sub PC, TMP0, #0x20000
3657      |  str CARG1, [TMP1, #-8]
3658    }
3659    |1:
3660    |  ins_next
3661    break;
3662
3663  case BC_LOOP:
3664    |  // RA = base, RC = target (loop extent)
3665    |  // Note: RA/RC is only used by trace recorder to determine scope/extent
3666    |  // This opcode does NOT jump, it's only purpose is to detect a hot loop.
3667    |.if JIT
3668    |  hotloop
3669    |.endif
3670    |  // Fall through. Assumes BC_ILOOP follows.
3671    break;
3672
3673  case BC_ILOOP:
3674    |  // RA = base, RC = target (loop extent)
3675    |  ins_next
3676    break;
3677
3678  case BC_JLOOP:
3679    |.if JIT
3680    |  // RA = base (ignored), RC = traceno
3681    |  ldr CARG1, [GL, #GL_J(trace)]
3682    |   mov CARG2, #0  // Traces on ARM64 don't store the trace #, so use 0.
3683    |  ldr TRACE:RC, [CARG1, RC, lsl #3]
3684    |   st_vmstate CARG2
3685    |  ldr RA, TRACE:RC->mcode
3686    |   str BASE, GL->jit_base
3687    |   str L, GL->tmpbuf.L
3688    |  sub sp, sp, #16	// See SPS_FIXED. Avoids sp adjust in every root trace.
3689    |  br RA
3690    |.endif
3691    break;
3692
3693  case BC_JMP:
3694    |  // RA = base (only used by trace recorder), RC = target
3695    |  add RC, PC, RC, lsl #2
3696    |  sub PC, RC, #0x20000
3697    |  ins_next
3698    break;
3699
3700  /* -- Function headers -------------------------------------------------- */
3701
3702  case BC_FUNCF:
3703    |.if JIT
3704    |  hotcall
3705    |.endif
3706  case BC_FUNCV:  /* NYI: compiled vararg functions. */
3707    |  // Fall through. Assumes BC_IFUNCF/BC_IFUNCV follow.
3708    break;
3709
3710  case BC_JFUNCF:
3711#if !LJ_HASJIT
3712    break;
3713#endif
3714  case BC_IFUNCF:
3715    |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
3716    |  ldr CARG1, L->maxstack
3717    |   ldrb TMP1w, [PC, #-4+PC2PROTO(numparams)]
3718    |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
3719    |  cmp RA, CARG1
3720    |  bhi ->vm_growstack_l
3721    |2:
3722    |  cmp NARGS8:RC, TMP1, lsl #3	// Check for missing parameters.
3723    |  blo >3
3724    if (op == BC_JFUNCF) {
3725      |  decode_RD RC, INS
3726      |  b =>BC_JLOOP
3727    } else {
3728      |  ins_next
3729    }
3730    |
3731    |3:  // Clear missing parameters.
3732    |  str TISNIL, [BASE, NARGS8:RC]
3733    |  add NARGS8:RC, NARGS8:RC, #8
3734    |  b <2
3735    break;
3736
3737  case BC_JFUNCV:
3738#if !LJ_HASJIT
3739    break;
3740#endif
3741    |  NYI  // NYI: compiled vararg functions
3742    break;  /* NYI: compiled vararg functions. */
3743
3744  case BC_IFUNCV:
3745    |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
3746    |  ldr CARG1, L->maxstack
3747    |   movn TMP0, #~LJ_TFUNC
3748    |   add TMP2, BASE, RC
3749    |   add LFUNC:CARG3, CARG3, TMP0, lsl #47
3750    |  add RA, RA, RC
3751    |   add TMP0, RC, #16+FRAME_VARG
3752    |   str LFUNC:CARG3, [TMP2], #8	// Store (tagged) copy of LFUNC.
3753    |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
3754    |  cmp RA, CARG1
3755    |   str TMP0, [TMP2], #8		// Store delta + FRAME_VARG.
3756    |  bhs ->vm_growstack_l
3757    |   sub RC, TMP2, #16
3758    |  ldrb TMP1w, [PC, #-4+PC2PROTO(numparams)]
3759    |   mov RA, BASE
3760    |   mov BASE, TMP2
3761    |  cbz TMP1, >2
3762    |1:
3763    |  cmp RA, RC			// Less args than parameters?
3764    |  bhs >3
3765    |   ldr TMP0, [RA]
3766    |  sub TMP1, TMP1, #1
3767    |    str TISNIL, [RA], #8		// Clear old fixarg slot (help the GC).
3768    |   str TMP0, [TMP2], #8
3769    |  cbnz TMP1, <1
3770    |2:
3771    |  ins_next
3772    |
3773    |3:
3774    |  sub TMP1, TMP1, #1
3775    |   str TISNIL, [TMP2], #8
3776    |  cbz TMP1, <2
3777    |  b <3
3778    break;
3779
3780  case BC_FUNCC:
3781  case BC_FUNCCW:
3782    |  // BASE = new base, RA = BASE+framesize*8, CARG3 = CFUNC, RC = nargs*8
3783    if (op == BC_FUNCC) {
3784      |  ldr CARG4, CFUNC:CARG3->f
3785    } else {
3786      |  ldr CARG4, GL->wrapf
3787    }
3788    |   add CARG2, RA, NARGS8:RC
3789    |   ldr CARG1, L->maxstack
3790    |  add RC, BASE, NARGS8:RC
3791    |   cmp CARG2, CARG1
3792    |  stp BASE, RC, L->base
3793    if (op == BC_FUNCCW) {
3794      |  ldr CARG2, CFUNC:CARG3->f
3795    }
3796    |    mv_vmstate TMP0w, C
3797    |  mov CARG1, L
3798    |   bhi ->vm_growstack_c		// Need to grow stack.
3799    |    st_vmstate TMP0w
3800    |  blr CARG4			// (lua_State *L [, lua_CFunction f])
3801    |  // Returns nresults.
3802    |  ldp BASE, TMP1, L->base
3803    |    str L, GL->cur_L
3804    |   sbfiz RC, CRET1, #3, #32
3805    |    st_vmstate ST_INTERP
3806    |  ldr PC, [BASE, FRAME_PC]
3807    |   sub RA, TMP1, RC		// RA = L->top - nresults*8
3808    |  b ->vm_returnc
3809    break;
3810
3811  /* ---------------------------------------------------------------------- */
3812
3813  default:
3814    fprintf(stderr, "Error: undefined opcode BC_%s\n", bc_names[op]);
3815    exit(2);
3816    break;
3817  }
3818}
3819
3820static int build_backend(BuildCtx *ctx)
3821{
3822  int op;
3823
3824  dasm_growpc(Dst, BC__MAX);
3825
3826  build_subroutines(ctx);
3827
3828  |.code_op
3829  for (op = 0; op < BC__MAX; op++)
3830    build_ins(ctx, (BCOp)op, op);
3831
3832  return BC__MAX;
3833}
3834
3835/* Emit pseudo frame-info for all assembler functions. */
3836static void emit_asm_debug(BuildCtx *ctx)
3837{
3838  int fcofs = (int)((uint8_t *)ctx->glob[GLOB_vm_ffi_call] - ctx->code);
3839  int i, cf = CFRAME_SIZE >> 3;
3840  switch (ctx->mode) {
3841  case BUILD_elfasm:
3842    fprintf(ctx->fp, "\t.section .debug_frame,\"\",%%progbits\n");
3843    fprintf(ctx->fp,
3844	".Lframe0:\n"
3845	"\t.long .LECIE0-.LSCIE0\n"
3846	".LSCIE0:\n"
3847	"\t.long 0xffffffff\n"
3848	"\t.byte 0x1\n"
3849	"\t.string \"\"\n"
3850	"\t.uleb128 0x1\n"
3851	"\t.sleb128 -8\n"
3852	"\t.byte 30\n"				/* Return address is in lr. */
3853	"\t.byte 0xc\n\t.uleb128 31\n\t.uleb128 0\n"	/* def_cfa sp */
3854	"\t.align 3\n"
3855	".LECIE0:\n\n");
3856    fprintf(ctx->fp,
3857	".LSFDE0:\n"
3858	"\t.long .LEFDE0-.LASFDE0\n"
3859	".LASFDE0:\n"
3860	"\t.long .Lframe0\n"
3861	"\t.quad .Lbegin\n"
3862	"\t.quad %d\n"
3863	"\t.byte 0xe\n\t.uleb128 %d\n"		/* def_cfa_offset */
3864	"\t.byte 0x9d\n\t.uleb128 %d\n"		/* offset fp */
3865	"\t.byte 0x9e\n\t.uleb128 %d\n",	/* offset lr */
3866	fcofs, CFRAME_SIZE, cf, cf-1);
3867    for (i = 19; i <= 28; i++)  /* offset x19-x28 */
3868      fprintf(ctx->fp, "\t.byte 0x%x\n\t.uleb128 %d\n", 0x80+i, cf-i+17);
3869    for (i = 8; i <= 15; i++)  /* offset d8-d15 */
3870      fprintf(ctx->fp, "\t.byte 5\n\t.uleb128 0x%x\n\t.uleb128 %d\n",
3871	      64+i, cf-i-4);
3872    fprintf(ctx->fp,
3873	"\t.align 3\n"
3874	".LEFDE0:\n\n");
3875#if LJ_HASFFI
3876    fprintf(ctx->fp,
3877	".LSFDE1:\n"
3878	"\t.long .LEFDE1-.LASFDE1\n"
3879	".LASFDE1:\n"
3880	"\t.long .Lframe0\n"
3881	"\t.quad lj_vm_ffi_call\n"
3882	"\t.quad %d\n"
3883	"\t.byte 0xe\n\t.uleb128 32\n"		/* def_cfa_offset */
3884	"\t.byte 0x9d\n\t.uleb128 4\n"		/* offset fp */
3885	"\t.byte 0x9e\n\t.uleb128 3\n"		/* offset lr */
3886	"\t.byte 0x93\n\t.uleb128 2\n"		/* offset x19 */
3887	"\t.align 3\n"
3888	".LEFDE1:\n\n", (int)ctx->codesz - fcofs);
3889#endif
3890    fprintf(ctx->fp, "\t.section .eh_frame,\"a\",%%progbits\n");
3891    fprintf(ctx->fp,
3892	".Lframe1:\n"
3893	"\t.long .LECIE1-.LSCIE1\n"
3894	".LSCIE1:\n"
3895	"\t.long 0\n"
3896	"\t.byte 0x1\n"
3897	"\t.string \"zPR\"\n"
3898	"\t.uleb128 0x1\n"
3899	"\t.sleb128 -8\n"
3900	"\t.byte 30\n"				/* Return address is in lr. */
3901	"\t.uleb128 6\n"			/* augmentation length */
3902	"\t.byte 0x1b\n"			/* pcrel|sdata4 */
3903	"\t.long lj_err_unwind_dwarf-.\n"
3904	"\t.byte 0x1b\n"			/* pcrel|sdata4 */
3905	"\t.byte 0xc\n\t.uleb128 31\n\t.uleb128 0\n"	/* def_cfa sp */
3906	"\t.align 3\n"
3907	".LECIE1:\n\n");
3908    fprintf(ctx->fp,
3909	".LSFDE2:\n"
3910	"\t.long .LEFDE2-.LASFDE2\n"
3911	".LASFDE2:\n"
3912	"\t.long .LASFDE2-.Lframe1\n"
3913	"\t.long .Lbegin-.\n"
3914	"\t.long %d\n"
3915	"\t.uleb128 0\n"			/* augmentation length */
3916	"\t.byte 0xe\n\t.uleb128 %d\n"		/* def_cfa_offset */
3917	"\t.byte 0x9d\n\t.uleb128 %d\n"		/* offset fp */
3918	"\t.byte 0x9e\n\t.uleb128 %d\n",	/* offset lr */
3919	fcofs, CFRAME_SIZE, cf, cf-1);
3920    for (i = 19; i <= 28; i++)  /* offset x19-x28 */
3921      fprintf(ctx->fp, "\t.byte 0x%x\n\t.uleb128 %d\n", 0x80+i, cf-i+17);
3922    for (i = 8; i <= 15; i++)  /* offset d8-d15 */
3923      fprintf(ctx->fp, "\t.byte 5\n\t.uleb128 0x%x\n\t.uleb128 %d\n",
3924	      64+i, cf-i-4);
3925    fprintf(ctx->fp,
3926	"\t.align 3\n"
3927	".LEFDE2:\n\n");
3928#if LJ_HASFFI
3929    fprintf(ctx->fp,
3930	".Lframe2:\n"
3931	"\t.long .LECIE2-.LSCIE2\n"
3932	".LSCIE2:\n"
3933	"\t.long 0\n"
3934	"\t.byte 0x1\n"
3935	"\t.string \"zR\"\n"
3936	"\t.uleb128 0x1\n"
3937	"\t.sleb128 -8\n"
3938	"\t.byte 30\n"				/* Return address is in lr. */
3939	"\t.uleb128 1\n"			/* augmentation length */
3940	"\t.byte 0x1b\n"			/* pcrel|sdata4 */
3941	"\t.byte 0xc\n\t.uleb128 31\n\t.uleb128 0\n"	/* def_cfa sp */
3942	"\t.align 3\n"
3943	".LECIE2:\n\n");
3944    fprintf(ctx->fp,
3945	".LSFDE3:\n"
3946	"\t.long .LEFDE3-.LASFDE3\n"
3947	".LASFDE3:\n"
3948	"\t.long .LASFDE3-.Lframe2\n"
3949	"\t.long lj_vm_ffi_call-.\n"
3950	"\t.long %d\n"
3951	"\t.uleb128 0\n"			/* augmentation length */
3952	"\t.byte 0xe\n\t.uleb128 32\n"		/* def_cfa_offset */
3953	"\t.byte 0x9d\n\t.uleb128 4\n"		/* offset fp */
3954	"\t.byte 0x9e\n\t.uleb128 3\n"		/* offset lr */
3955	"\t.byte 0x93\n\t.uleb128 2\n"		/* offset x19 */
3956	"\t.align 3\n"
3957	".LEFDE3:\n\n", (int)ctx->codesz - fcofs);
3958#endif
3959    break;
3960  default:
3961    break;
3962  }
3963}
3964
3965