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