1|// Low-level VM code for MIPS64 CPUs.
2|// Bytecode interpreter, fast functions and helper functions.
3|// Copyright (C) 2005-2021 Mike Pall. See Copyright Notice in luajit.h
4|//
5|// Contributed by Djordje Kovacevic and Stefan Pejic from RT-RK.com.
6|// Sponsored by Cisco Systems, Inc.
7|
8|.arch mips64
9|.section code_op, code_sub
10|
11|.actionlist build_actionlist
12|.globals GLOB_
13|.globalnames globnames
14|.externnames extnames
15|
16|// Note: The ragged indentation of the instructions is intentional.
17|//       The starting columns indicate data dependencies.
18|
19|//-----------------------------------------------------------------------
20|
21|// Fixed register assignments for the interpreter.
22|// Don't use: r0 = 0, r26/r27 = reserved, r28 = gp, r29 = sp, r31 = ra
23|
24|.macro .FPU, a, b
25|.if FPU
26|  a, b
27|.endif
28|.endmacro
29|
30|// The following must be C callee-save (but BASE is often refetched).
31|.define BASE,		r16	// Base of current Lua stack frame.
32|.define KBASE,		r17	// Constants of current Lua function.
33|.define PC,		r18	// Next PC.
34|.define DISPATCH,	r19	// Opcode dispatch table.
35|.define LREG,		r20	// Register holding lua_State (also in SAVE_L).
36|.define MULTRES,	r21	// Size of multi-result: (nresults+1)*8.
37|
38|.define JGL,		r30	// On-trace: global_State + 32768.
39|
40|// Constants for type-comparisons, stores and conversions. C callee-save.
41|.define TISNIL,	r30
42|.define TISNUM,	r22
43|.if FPU
44|.define TOBIT,		f30	// 2^52 + 2^51.
45|.endif
46|
47|// The following temporaries are not saved across C calls, except for RA.
48|.define RA,		r23	// Callee-save.
49|.define RB,		r8
50|.define RC,		r9
51|.define RD,		r10
52|.define INS,		r11
53|
54|.define AT,		r1	// Assembler temporary.
55|.define TMP0,		r12
56|.define TMP1,		r13
57|.define TMP2,		r14
58|.define TMP3,		r15
59|
60|// MIPS n64 calling convention.
61|.define CFUNCADDR,	r25
62|.define CARG1,		r4
63|.define CARG2,		r5
64|.define CARG3,		r6
65|.define CARG4,		r7
66|.define CARG5,		r8
67|.define CARG6,		r9
68|.define CARG7,		r10
69|.define CARG8,		r11
70|
71|.define CRET1,		r2
72|.define CRET2,		r3
73|
74|.if FPU
75|.define FARG1,		f12
76|.define FARG2,		f13
77|.define FARG3,		f14
78|.define FARG4,		f15
79|.define FARG5,		f16
80|.define FARG6,		f17
81|.define FARG7,		f18
82|.define FARG8,		f19
83|
84|.define FRET1,		f0
85|.define FRET2,		f2
86|
87|.define FTMP0,		f20
88|.define FTMP1,		f21
89|.define FTMP2,		f22
90|.endif
91|
92|// Stack layout while in interpreter. Must match with lj_frame.h.
93|.if FPU		// MIPS64 hard-float.
94|
95|.define CFRAME_SPACE,	192	// Delta for sp.
96|
97|//----- 16 byte aligned, <-- sp entering interpreter
98|.define SAVE_ERRF,	188(sp)	// 32 bit values.
99|.define SAVE_NRES,	184(sp)
100|.define SAVE_CFRAME,	176(sp)	// 64 bit values.
101|.define SAVE_L,	168(sp)
102|.define SAVE_PC,	160(sp)
103|//----- 16 byte aligned
104|.define SAVE_GPR_,	80	// .. 80+10*8: 64 bit GPR saves.
105|.define SAVE_FPR_,	16	// .. 16+8*8: 64 bit FPR saves.
106|
107|.else			// MIPS64 soft-float
108|
109|.define CFRAME_SPACE,	128	// Delta for sp.
110|
111|//----- 16 byte aligned, <-- sp entering interpreter
112|.define SAVE_ERRF,	124(sp)	// 32 bit values.
113|.define SAVE_NRES,	120(sp)
114|.define SAVE_CFRAME,	112(sp)	// 64 bit values.
115|.define SAVE_L,	104(sp)
116|.define SAVE_PC,	96(sp)
117|//----- 16 byte aligned
118|.define SAVE_GPR_,	16	// .. 16+10*8: 64 bit GPR saves.
119|
120|.endif
121|
122|.define TMPX,		8(sp)	// Unused by interpreter, temp for JIT code.
123|.define TMPD,		0(sp)
124|//----- 16 byte aligned
125|
126|.define TMPD_OFS,	0
127|
128|.define SAVE_MULTRES,	TMPD
129|
130|//-----------------------------------------------------------------------
131|
132|.macro saveregs
133|  daddiu sp, sp, -CFRAME_SPACE
134|  sd ra, SAVE_GPR_+9*8(sp)
135|  sd r30, SAVE_GPR_+8*8(sp)
136|   .FPU sdc1 f31, SAVE_FPR_+7*8(sp)
137|  sd r23, SAVE_GPR_+7*8(sp)
138|   .FPU sdc1 f30, SAVE_FPR_+6*8(sp)
139|  sd r22, SAVE_GPR_+6*8(sp)
140|   .FPU sdc1 f29, SAVE_FPR_+5*8(sp)
141|  sd r21, SAVE_GPR_+5*8(sp)
142|   .FPU sdc1 f28, SAVE_FPR_+4*8(sp)
143|  sd r20, SAVE_GPR_+4*8(sp)
144|   .FPU sdc1 f27, SAVE_FPR_+3*8(sp)
145|  sd r19, SAVE_GPR_+3*8(sp)
146|   .FPU sdc1 f26, SAVE_FPR_+2*8(sp)
147|  sd r18, SAVE_GPR_+2*8(sp)
148|   .FPU sdc1 f25, SAVE_FPR_+1*8(sp)
149|  sd r17, SAVE_GPR_+1*8(sp)
150|   .FPU sdc1 f24, SAVE_FPR_+0*8(sp)
151|  sd r16, SAVE_GPR_+0*8(sp)
152|.endmacro
153|
154|.macro restoreregs_ret
155|  ld ra, SAVE_GPR_+9*8(sp)
156|  ld r30, SAVE_GPR_+8*8(sp)
157|  ld r23, SAVE_GPR_+7*8(sp)
158|   .FPU ldc1 f31, SAVE_FPR_+7*8(sp)
159|  ld r22, SAVE_GPR_+6*8(sp)
160|   .FPU ldc1 f30, SAVE_FPR_+6*8(sp)
161|  ld r21, SAVE_GPR_+5*8(sp)
162|   .FPU ldc1 f29, SAVE_FPR_+5*8(sp)
163|  ld r20, SAVE_GPR_+4*8(sp)
164|   .FPU ldc1 f28, SAVE_FPR_+4*8(sp)
165|  ld r19, SAVE_GPR_+3*8(sp)
166|   .FPU ldc1 f27, SAVE_FPR_+3*8(sp)
167|  ld r18, SAVE_GPR_+2*8(sp)
168|   .FPU ldc1 f26, SAVE_FPR_+2*8(sp)
169|  ld r17, SAVE_GPR_+1*8(sp)
170|   .FPU ldc1 f25, SAVE_FPR_+1*8(sp)
171|  ld r16, SAVE_GPR_+0*8(sp)
172|   .FPU ldc1 f24, SAVE_FPR_+0*8(sp)
173|  jr ra
174|  daddiu sp, sp, CFRAME_SPACE
175|.endmacro
176|
177|// Type definitions. Some of these are only used for documentation.
178|.type L,		lua_State,	LREG
179|.type GL,		global_State
180|.type TVALUE,		TValue
181|.type GCOBJ,		GCobj
182|.type STR,		GCstr
183|.type TAB,		GCtab
184|.type LFUNC,		GCfuncL
185|.type CFUNC,		GCfuncC
186|.type PROTO,		GCproto
187|.type UPVAL,		GCupval
188|.type NODE,		Node
189|.type NARGS8,		int
190|.type TRACE,		GCtrace
191|.type SBUF,		SBuf
192|
193|//-----------------------------------------------------------------------
194|
195|// Trap for not-yet-implemented parts.
196|.macro NYI; .long 0xec1cf0f0; .endmacro
197|
198|// Macros to mark delay slots.
199|.macro ., a; a; .endmacro
200|.macro ., a,b; a,b; .endmacro
201|.macro ., a,b,c; a,b,c; .endmacro
202|.macro ., a,b,c,d; a,b,c,d; .endmacro
203|
204|.define FRAME_PC,	-8
205|.define FRAME_FUNC,	-16
206|
207|//-----------------------------------------------------------------------
208|
209|// Endian-specific defines.
210|.if ENDIAN_LE
211|.define HI,		4
212|.define LO,		0
213|.define OFS_RD,	2
214|.define OFS_RA,	1
215|.define OFS_OP,	0
216|.else
217|.define HI,		0
218|.define LO,		4
219|.define OFS_RD,	0
220|.define OFS_RA,	2
221|.define OFS_OP,	3
222|.endif
223|
224|// Instruction decode.
225|.macro decode_OP1, dst, ins; andi dst, ins, 0xff; .endmacro
226|.macro decode_OP8a, dst, ins; andi dst, ins, 0xff; .endmacro
227|.macro decode_OP8b, dst; sll dst, dst, 3; .endmacro
228|.macro decode_RC8a, dst, ins; srl dst, ins, 13; .endmacro
229|.macro decode_RC8b, dst; andi dst, dst, 0x7f8; .endmacro
230|.macro decode_RD4b, dst; sll dst, dst, 2; .endmacro
231|.macro decode_RA8a, dst, ins; srl dst, ins, 5; .endmacro
232|.macro decode_RA8b, dst; andi dst, dst, 0x7f8; .endmacro
233|.macro decode_RB8a, dst, ins; srl dst, ins, 21; .endmacro
234|.macro decode_RB8b, dst; andi dst, dst, 0x7f8; .endmacro
235|.macro decode_RD8a, dst, ins; srl dst, ins, 16; .endmacro
236|.macro decode_RD8b, dst; sll dst, dst, 3; .endmacro
237|.macro decode_RDtoRC8, dst, src; andi dst, src, 0x7f8; .endmacro
238|
239|// Instruction fetch.
240|.macro ins_NEXT1
241|  lw INS, 0(PC)
242|   daddiu PC, PC, 4
243|.endmacro
244|// Instruction decode+dispatch.
245|.macro ins_NEXT2
246|  decode_OP8a TMP1, INS
247|  decode_OP8b TMP1
248|  daddu TMP0, DISPATCH, TMP1
249|   decode_RD8a RD, INS
250|  ld AT, 0(TMP0)
251|   decode_RA8a RA, INS
252|   decode_RD8b RD
253|  jr AT
254|   decode_RA8b RA
255|.endmacro
256|.macro ins_NEXT
257|  ins_NEXT1
258|  ins_NEXT2
259|.endmacro
260|
261|// Instruction footer.
262|.if 1
263|  // Replicated dispatch. Less unpredictable branches, but higher I-Cache use.
264|  .define ins_next, ins_NEXT
265|  .define ins_next_, ins_NEXT
266|  .define ins_next1, ins_NEXT1
267|  .define ins_next2, ins_NEXT2
268|.else
269|  // Common dispatch. Lower I-Cache use, only one (very) unpredictable branch.
270|  // Affects only certain kinds of benchmarks (and only with -j off).
271|  .macro ins_next
272|    b ->ins_next
273|  .endmacro
274|  .macro ins_next1
275|  .endmacro
276|  .macro ins_next2
277|    b ->ins_next
278|  .endmacro
279|  .macro ins_next_
280|  ->ins_next:
281|    ins_NEXT
282|  .endmacro
283|.endif
284|
285|// Call decode and dispatch.
286|.macro ins_callt
287|  // BASE = new base, RB = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
288|  ld PC, LFUNC:RB->pc
289|  lw INS, 0(PC)
290|   daddiu PC, PC, 4
291|  decode_OP8a TMP1, INS
292|   decode_RA8a RA, INS
293|  decode_OP8b TMP1
294|   decode_RA8b RA
295|  daddu TMP0, DISPATCH, TMP1
296|  ld TMP0, 0(TMP0)
297|  jr TMP0
298|   daddu RA, RA, BASE
299|.endmacro
300|
301|.macro ins_call
302|  // BASE = new base, RB = LFUNC/CFUNC, RC = nargs*8, PC = caller PC
303|  sd PC, FRAME_PC(BASE)
304|  ins_callt
305|.endmacro
306|
307|//-----------------------------------------------------------------------
308|
309|.macro branch_RD
310|  srl TMP0, RD, 1
311|  lui AT, (-(BCBIAS_J*4 >> 16) & 65535)
312|  addu TMP0, TMP0, AT
313|  daddu PC, PC, TMP0
314|.endmacro
315|
316|// Assumes DISPATCH is relative to GL.
317#define DISPATCH_GL(field)	(GG_DISP2G + (int)offsetof(global_State, field))
318#define DISPATCH_J(field)	(GG_DISP2J + (int)offsetof(jit_State, field))
319#define GG_DISP2GOT		(GG_OFS(got) - GG_OFS(dispatch))
320#define DISPATCH_GOT(name)	(GG_DISP2GOT + sizeof(void*)*LJ_GOT_##name)
321|
322#define PC2PROTO(field)  ((int)offsetof(GCproto, field)-(int)sizeof(GCproto))
323|
324|.macro load_got, func
325|  ld CFUNCADDR, DISPATCH_GOT(func)(DISPATCH)
326|.endmacro
327|// Much faster. Sadly, there's no easy way to force the required code layout.
328|// .macro call_intern, func; bal extern func; .endmacro
329|.macro call_intern, func; jalr CFUNCADDR; .endmacro
330|.macro call_extern; jalr CFUNCADDR; .endmacro
331|.macro jmp_extern; jr CFUNCADDR; .endmacro
332|
333|.macro hotcheck, delta, target
334|  dsrl TMP1, PC, 1
335|  andi TMP1, TMP1, 126
336|  daddu TMP1, TMP1, DISPATCH
337|  lhu TMP2, GG_DISP2HOT(TMP1)
338|  addiu TMP2, TMP2, -delta
339|  bltz TMP2, target
340|.  sh TMP2, GG_DISP2HOT(TMP1)
341|.endmacro
342|
343|.macro hotloop
344|  hotcheck HOTCOUNT_LOOP, ->vm_hotloop
345|.endmacro
346|
347|.macro hotcall
348|  hotcheck HOTCOUNT_CALL, ->vm_hotcall
349|.endmacro
350|
351|// Set current VM state. Uses TMP0.
352|.macro li_vmstate, st; li TMP0, ~LJ_VMST_..st; .endmacro
353|.macro st_vmstate; sw TMP0, DISPATCH_GL(vmstate)(DISPATCH); .endmacro
354|
355|// Move table write barrier back. Overwrites mark and tmp.
356|.macro barrierback, tab, mark, tmp, target
357|  ld tmp, DISPATCH_GL(gc.grayagain)(DISPATCH)
358|   andi mark, mark, ~LJ_GC_BLACK & 255		// black2gray(tab)
359|  sd tab, DISPATCH_GL(gc.grayagain)(DISPATCH)
360|   sb mark, tab->marked
361|  b target
362|.  sd tmp, tab->gclist
363|.endmacro
364|
365|// Clear type tag. Isolate lowest 14+32+1=47 bits of reg.
366|.macro cleartp, reg; dextm reg, reg, 0, 14; .endmacro
367|.macro cleartp, dst, reg; dextm dst, reg, 0, 14; .endmacro
368|
369|// Set type tag: Merge 17 type bits into bits [15+32=47, 31+32+1=64) of dst.
370|.macro settp, dst, tp; dinsu dst, tp, 15, 31; .endmacro
371|
372|// Extract (negative) type tag.
373|.macro gettp, dst, src; dsra dst, src, 47; .endmacro
374|
375|// Macros to check the TValue type and extract the GCobj. Branch on failure.
376|.macro checktp, reg, tp, target
377|  gettp AT, reg
378|  daddiu AT, AT, tp
379|  bnez AT, target
380|.  cleartp reg
381|.endmacro
382|.macro checktp, dst, reg, tp, target
383|  gettp AT, reg
384|  daddiu AT, AT, tp
385|  bnez AT, target
386|.  cleartp dst, reg
387|.endmacro
388|.macro checkstr, reg, target; checktp reg, -LJ_TSTR, target; .endmacro
389|.macro checktab, reg, target; checktp reg, -LJ_TTAB, target; .endmacro
390|.macro checkfunc, reg, target; checktp reg, -LJ_TFUNC, target; .endmacro
391|.macro checkint, reg, target	// Caveat: has delay slot!
392|  gettp AT, reg
393|  bne AT, TISNUM, target
394|.endmacro
395|.macro checknum, reg, target	// Caveat: has delay slot!
396|  gettp AT, reg
397|  sltiu AT, AT, LJ_TISNUM
398|  beqz AT, target
399|.endmacro
400|
401|.macro mov_false, reg
402|  lu reg, 0x8000
403|  dsll reg, reg, 32
404|  not reg, reg
405|.endmacro
406|.macro mov_true, reg
407|  li reg, 0x0001
408|  dsll reg, reg, 48
409|  not reg, reg
410|.endmacro
411|
412|//-----------------------------------------------------------------------
413
414/* Generate subroutines used by opcodes and other parts of the VM. */
415/* The .code_sub section should be last to help static branch prediction. */
416static void build_subroutines(BuildCtx *ctx)
417{
418  |.code_sub
419  |
420  |//-----------------------------------------------------------------------
421  |//-- Return handling ----------------------------------------------------
422  |//-----------------------------------------------------------------------
423  |
424  |->vm_returnp:
425  |  // See vm_return. Also: TMP2 = previous base.
426  |  andi AT, PC, FRAME_P
427  |  beqz AT, ->cont_dispatch
428  |
429  |  // Return from pcall or xpcall fast func.
430  |.  mov_true TMP1
431  |  ld PC, FRAME_PC(TMP2)		// Fetch PC of previous frame.
432  |  move BASE, TMP2			// Restore caller base.
433  |  // Prepending may overwrite the pcall frame, so do it at the end.
434  |   sd TMP1, -8(RA)			// Prepend true to results.
435  |   daddiu RA, RA, -8
436  |
437  |->vm_returnc:
438  |   addiu RD, RD, 8			// RD = (nresults+1)*8.
439  |  andi TMP0, PC, FRAME_TYPE
440  |   beqz RD, ->vm_unwind_c_eh
441  |.   li CRET1, LUA_YIELD
442  |  beqz TMP0, ->BC_RET_Z		// Handle regular return to Lua.
443  |.  move MULTRES, RD
444  |
445  |->vm_return:
446  |  // BASE = base, RA = resultptr, RD/MULTRES = (nresults+1)*8, PC = return
447  |  // TMP0 = PC & FRAME_TYPE
448  |   li TMP2, -8
449  |  xori AT, TMP0, FRAME_C
450  |   and TMP2, PC, TMP2
451  |  bnez AT, ->vm_returnp
452  |   dsubu TMP2, BASE, TMP2		// TMP2 = previous base.
453  |
454  |  addiu TMP1, RD, -8
455  |   sd TMP2, L->base
456  |    li_vmstate C
457  |   lw TMP2, SAVE_NRES
458  |   daddiu BASE, BASE, -16
459  |    st_vmstate
460  |  beqz TMP1, >2
461  |.   sll TMP2, TMP2, 3
462  |1:
463  |  addiu TMP1, TMP1, -8
464  |   ld CRET1, 0(RA)
465  |    daddiu RA, RA, 8
466  |   sd CRET1, 0(BASE)
467  |  bnez TMP1, <1
468  |.  daddiu BASE, BASE, 8
469  |
470  |2:
471  |  bne TMP2, RD, >6
472  |3:
473  |.  sd BASE, L->top			// Store new top.
474  |
475  |->vm_leave_cp:
476  |  ld TMP0, SAVE_CFRAME		// Restore previous C frame.
477  |   move CRET1, r0			// Ok return status for vm_pcall.
478  |  sd TMP0, L->cframe
479  |
480  |->vm_leave_unw:
481  |  restoreregs_ret
482  |
483  |6:
484  |  ld TMP1, L->maxstack
485  |  slt AT, TMP2, RD
486  |  bnez AT, >7			// Less results wanted?
487  |  // More results wanted. Check stack size and fill up results with nil.
488  |.  slt AT, BASE, TMP1
489  |  beqz AT, >8
490  |.  nop
491  |  sd TISNIL, 0(BASE)
492  |  addiu RD, RD, 8
493  |  b <2
494  |.  daddiu BASE, BASE, 8
495  |
496  |7:  // Less results wanted.
497  |  subu TMP0, RD, TMP2
498  |  dsubu TMP0, BASE, TMP0		// Either keep top or shrink it.
499  |.if MIPSR6
500  |  selnez TMP0, TMP0, TMP2		// LUA_MULTRET+1 case?
501  |  seleqz BASE, BASE, TMP2
502  |  b <3
503  |.  or BASE, BASE, TMP0
504  |.else
505  |  b <3
506  |.  movn BASE, TMP0, TMP2		// LUA_MULTRET+1 case?
507  |.endif
508  |
509  |8:  // Corner case: need to grow stack for filling up results.
510  |  // This can happen if:
511  |  // - A C function grows the stack (a lot).
512  |  // - The GC shrinks the stack in between.
513  |  // - A return back from a lua_call() with (high) nresults adjustment.
514  |  load_got lj_state_growstack
515  |   move MULTRES, RD
516  |  srl CARG2, TMP2, 3
517  |  call_intern lj_state_growstack	// (lua_State *L, int n)
518  |.  move CARG1, L
519  |    lw TMP2, SAVE_NRES
520  |  ld BASE, L->top			// Need the (realloced) L->top in BASE.
521  |   move RD, MULTRES
522  |  b <2
523  |.   sll TMP2, TMP2, 3
524  |
525  |->vm_unwind_c:			// Unwind C stack, return from vm_pcall.
526  |  // (void *cframe, int errcode)
527  |  move sp, CARG1
528  |  move CRET1, CARG2
529  |->vm_unwind_c_eh:			// Landing pad for external unwinder.
530  |  ld L, SAVE_L
531  |   li TMP0, ~LJ_VMST_C
532  |  ld GL:TMP1, L->glref
533  |  b ->vm_leave_unw
534  |.  sw TMP0, GL:TMP1->vmstate
535  |
536  |->vm_unwind_ff:			// Unwind C stack, return from ff pcall.
537  |  // (void *cframe)
538  |  li AT, -4
539  |  and sp, CARG1, AT
540  |->vm_unwind_ff_eh:			// Landing pad for external unwinder.
541  |  ld L, SAVE_L
542  |     .FPU lui TMP3, 0x59c0		// TOBIT = 2^52 + 2^51 (float).
543  |     li TISNIL, LJ_TNIL
544  |    li TISNUM, LJ_TISNUM
545  |  ld BASE, L->base
546  |   ld DISPATCH, L->glref		// Setup pointer to dispatch table.
547  |     .FPU mtc1 TMP3, TOBIT
548  |  mov_false TMP1
549  |    li_vmstate INTERP
550  |  ld PC, FRAME_PC(BASE)		// Fetch PC of previous frame.
551  |     .FPU cvt.d.s TOBIT, TOBIT
552  |  daddiu RA, BASE, -8		// Results start at BASE-8.
553  |   daddiu DISPATCH, DISPATCH, GG_G2DISP
554  |  sd TMP1, 0(RA)			// Prepend false to error message.
555  |    st_vmstate
556  |  b ->vm_returnc
557  |.  li RD, 16				// 2 results: false + error message.
558  |
559  |->vm_unwind_stub:			// Jump to exit stub from unwinder.
560  |  jr CARG1
561  |.  move ra, CARG2
562  |
563  |//-----------------------------------------------------------------------
564  |//-- Grow stack for calls -----------------------------------------------
565  |//-----------------------------------------------------------------------
566  |
567  |->vm_growstack_c:			// Grow stack for C function.
568  |  b >2
569  |.  li CARG2, LUA_MINSTACK
570  |
571  |->vm_growstack_l:			// Grow stack for Lua function.
572  |  // BASE = new base, RA = BASE+framesize*8, RC = nargs*8, PC = first PC
573  |  daddu RC, BASE, RC
574  |   dsubu RA, RA, BASE
575  |  sd BASE, L->base
576  |   daddiu PC, PC, 4			// Must point after first instruction.
577  |  sd RC, L->top
578  |   srl CARG2, RA, 3
579  |2:
580  |  // L->base = new base, L->top = top
581  |  load_got lj_state_growstack
582  |   sd PC, SAVE_PC
583  |  call_intern lj_state_growstack	// (lua_State *L, int n)
584  |.  move CARG1, L
585  |  ld BASE, L->base
586  |  ld RC, L->top
587  |  ld LFUNC:RB, FRAME_FUNC(BASE)
588  |  dsubu RC, RC, BASE
589  |  cleartp LFUNC:RB
590  |  // BASE = new base, RB = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
591  |  ins_callt				// Just retry the call.
592  |
593  |//-----------------------------------------------------------------------
594  |//-- Entry points into the assembler VM ---------------------------------
595  |//-----------------------------------------------------------------------
596  |
597  |->vm_resume:				// Setup C frame and resume thread.
598  |  // (lua_State *L, TValue *base, int nres1 = 0, ptrdiff_t ef = 0)
599  |  saveregs
600  |  move L, CARG1
601  |    ld DISPATCH, L->glref		// Setup pointer to dispatch table.
602  |  move BASE, CARG2
603  |    lbu TMP1, L->status
604  |   sd L, SAVE_L
605  |  li PC, FRAME_CP
606  |  daddiu TMP0, sp, CFRAME_RESUME
607  |    daddiu DISPATCH, DISPATCH, GG_G2DISP
608  |   sw r0, SAVE_NRES
609  |   sw r0, SAVE_ERRF
610  |   sd CARG1, SAVE_PC			// Any value outside of bytecode is ok.
611  |   sd r0, SAVE_CFRAME
612  |    beqz TMP1, >3
613  |. sd TMP0, L->cframe
614  |
615  |  // Resume after yield (like a return).
616  |  sd L, DISPATCH_GL(cur_L)(DISPATCH)
617  |  move RA, BASE
618  |   ld BASE, L->base
619  |   ld TMP1, L->top
620  |  ld PC, FRAME_PC(BASE)
621  |     .FPU  lui TMP3, 0x59c0		// TOBIT = 2^52 + 2^51 (float).
622  |   dsubu RD, TMP1, BASE
623  |     .FPU  mtc1 TMP3, TOBIT
624  |    sb r0, L->status
625  |     .FPU  cvt.d.s TOBIT, TOBIT
626  |    li_vmstate INTERP
627  |   daddiu RD, RD, 8
628  |    st_vmstate
629  |   move MULTRES, RD
630  |  andi TMP0, PC, FRAME_TYPE
631  |    li TISNIL, LJ_TNIL
632  |  beqz TMP0, ->BC_RET_Z
633  |.    li TISNUM, LJ_TISNUM
634  |  b ->vm_return
635  |.  nop
636  |
637  |->vm_pcall:				// Setup protected C frame and enter VM.
638  |  // (lua_State *L, TValue *base, int nres1, ptrdiff_t ef)
639  |  saveregs
640  |  sw CARG4, SAVE_ERRF
641  |  b >1
642  |.  li PC, FRAME_CP
643  |
644  |->vm_call:				// Setup C frame and enter VM.
645  |  // (lua_State *L, TValue *base, int nres1)
646  |  saveregs
647  |  li PC, FRAME_C
648  |
649  |1:  // Entry point for vm_pcall above (PC = ftype).
650  |  ld TMP1, L:CARG1->cframe
651  |    move L, CARG1
652  |   sw CARG3, SAVE_NRES
653  |    ld DISPATCH, L->glref		// Setup pointer to dispatch table.
654  |   sd CARG1, SAVE_L
655  |     move BASE, CARG2
656  |    daddiu DISPATCH, DISPATCH, GG_G2DISP
657  |   sd CARG1, SAVE_PC			// Any value outside of bytecode is ok.
658  |  sd TMP1, SAVE_CFRAME
659  |  sd sp, L->cframe			// Add our C frame to cframe chain.
660  |
661  |3:  // Entry point for vm_cpcall/vm_resume (BASE = base, PC = ftype).
662  |  sd L, DISPATCH_GL(cur_L)(DISPATCH)
663  |  ld TMP2, L->base			// TMP2 = old base (used in vmeta_call).
664  |     .FPU lui TMP3, 0x59c0		// TOBIT = 2^52 + 2^51 (float).
665  |   ld TMP1, L->top
666  |     .FPU mtc1 TMP3, TOBIT
667  |  daddu PC, PC, BASE
668  |   dsubu NARGS8:RC, TMP1, BASE
669  |     li TISNUM, LJ_TISNUM
670  |  dsubu PC, PC, TMP2			// PC = frame delta + frame type
671  |     .FPU cvt.d.s TOBIT, TOBIT
672  |    li_vmstate INTERP
673  |     li TISNIL, LJ_TNIL
674  |    st_vmstate
675  |
676  |->vm_call_dispatch:
677  |  // TMP2 = old base, BASE = new base, RC = nargs*8, PC = caller PC
678  |  ld LFUNC:RB, FRAME_FUNC(BASE)
679  |  checkfunc LFUNC:RB, ->vmeta_call
680  |
681  |->vm_call_dispatch_f:
682  |  ins_call
683  |  // BASE = new base, RB = func, RC = nargs*8, PC = caller PC
684  |
685  |->vm_cpcall:				// Setup protected C frame, call C.
686  |  // (lua_State *L, lua_CFunction func, void *ud, lua_CPFunction cp)
687  |  saveregs
688  |  move L, CARG1
689  |   ld TMP0, L:CARG1->stack
690  |  sd CARG1, SAVE_L
691  |   ld TMP1, L->top
692  |     ld DISPATCH, L->glref		// Setup pointer to dispatch table.
693  |  sd CARG1, SAVE_PC			// Any value outside of bytecode is ok.
694  |   dsubu TMP0, TMP0, TMP1		// Compute -savestack(L, L->top).
695  |    ld TMP1, L->cframe
696  |     daddiu DISPATCH, DISPATCH, GG_G2DISP
697  |   sw TMP0, SAVE_NRES		// Neg. delta means cframe w/o frame.
698  |  sw r0, SAVE_ERRF			// No error function.
699  |    sd TMP1, SAVE_CFRAME
700  |    sd sp, L->cframe			// Add our C frame to cframe chain.
701  |     sd L, DISPATCH_GL(cur_L)(DISPATCH)
702  |  jalr CARG4			// (lua_State *L, lua_CFunction func, void *ud)
703  |.  move CFUNCADDR, CARG4
704  |  move BASE, CRET1
705  |  bnez CRET1, <3			// Else continue with the call.
706  |.  li PC, FRAME_CP
707  |  b ->vm_leave_cp			// No base? Just remove C frame.
708  |.  nop
709  |
710  |//-----------------------------------------------------------------------
711  |//-- Metamethod handling ------------------------------------------------
712  |//-----------------------------------------------------------------------
713  |
714  |// The lj_meta_* functions (except for lj_meta_cat) don't reallocate the
715  |// stack, so BASE doesn't need to be reloaded across these calls.
716  |
717  |//-- Continuation dispatch ----------------------------------------------
718  |
719  |->cont_dispatch:
720  |  // BASE = meta base, RA = resultptr, RD = (nresults+1)*8
721  |  ld TMP0, -32(BASE)			// Continuation.
722  |   move RB, BASE
723  |   move BASE, TMP2			// Restore caller BASE.
724  |    ld LFUNC:TMP1, FRAME_FUNC(TMP2)
725  |.if FFI
726  |  sltiu AT, TMP0, 2
727  |.endif
728  |     ld PC, -24(RB)			// Restore PC from [cont|PC].
729  |    cleartp LFUNC:TMP1
730  |   daddu TMP2, RA, RD
731  |.if FFI
732  |  bnez AT, >1
733  |.endif
734  |.  sd TISNIL, -8(TMP2)		// Ensure one valid arg.
735  |    ld TMP1, LFUNC:TMP1->pc
736  |  // BASE = base, RA = resultptr, RB = meta base
737  |  jr TMP0				// Jump to continuation.
738  |.  ld KBASE, PC2PROTO(k)(TMP1)
739  |
740  |.if FFI
741  |1:
742  |  bnez TMP0, ->cont_ffi_callback	// cont = 1: return from FFI callback.
743  |  // cont = 0: tailcall from C function.
744  |.  daddiu TMP1, RB, -32
745  |  b ->vm_call_tail
746  |.  dsubu RC, TMP1, BASE
747  |.endif
748  |
749  |->cont_cat:				// RA = resultptr, RB = meta base
750  |  lw INS, -4(PC)
751  |   daddiu CARG2, RB, -32
752  |  ld CRET1, 0(RA)
753  |  decode_RB8a MULTRES, INS
754  |   decode_RA8a RA, INS
755  |  decode_RB8b MULTRES
756  |   decode_RA8b RA
757  |  daddu TMP1, BASE, MULTRES
758  |   sd BASE, L->base
759  |   dsubu CARG3, CARG2, TMP1
760  |  bne TMP1, CARG2, ->BC_CAT_Z
761  |.  sd CRET1, 0(CARG2)
762  |  daddu RA, BASE, RA
763  |  b ->cont_nop
764  |.  sd CRET1, 0(RA)
765  |
766  |//-- Table indexing metamethods -----------------------------------------
767  |
768  |->vmeta_tgets1:
769  |  daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv)
770  |  li TMP0, LJ_TSTR
771  |  settp STR:RC, TMP0
772  |  b >1
773  |.  sd STR:RC, 0(CARG3)
774  |
775  |->vmeta_tgets:
776  |  daddiu CARG2, DISPATCH, DISPATCH_GL(tmptv)
777  |  li TMP0, LJ_TTAB
778  |   li TMP1, LJ_TSTR
779  |  settp TAB:RB, TMP0
780  |   daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv2)
781  |  sd TAB:RB, 0(CARG2)
782  |   settp STR:RC, TMP1
783  |  b >1
784  |.  sd STR:RC, 0(CARG3)
785  |
786  |->vmeta_tgetb:			// TMP0 = index
787  |  daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv)
788  |  settp TMP0, TISNUM
789  |  sd TMP0, 0(CARG3)
790  |
791  |->vmeta_tgetv:
792  |1:
793  |  load_got lj_meta_tget
794  |  sd BASE, L->base
795  |  sd PC, SAVE_PC
796  |  call_intern lj_meta_tget		// (lua_State *L, TValue *o, TValue *k)
797  |.  move CARG1, L
798  |  // Returns TValue * (finished) or NULL (metamethod).
799  |  beqz CRET1, >3
800  |.  daddiu TMP1, BASE, -FRAME_CONT
801  |  ld CARG1, 0(CRET1)
802  |  ins_next1
803  |  sd CARG1, 0(RA)
804  |  ins_next2
805  |
806  |3:  // Call __index metamethod.
807  |  // BASE = base, L->top = new base, stack = cont/func/t/k
808  |  ld BASE, L->top
809  |  sd PC, -24(BASE)			// [cont|PC]
810  |   dsubu PC, BASE, TMP1
811  |  ld LFUNC:RB, FRAME_FUNC(BASE)	// Guaranteed to be a function here.
812  |  cleartp LFUNC:RB
813  |  b ->vm_call_dispatch_f
814  |.  li NARGS8:RC, 16			// 2 args for func(t, k).
815  |
816  |->vmeta_tgetr:
817  |  load_got lj_tab_getinth
818  |  call_intern lj_tab_getinth		// (GCtab *t, int32_t key)
819  |.  nop
820  |  // Returns cTValue * or NULL.
821  |  beqz CRET1, ->BC_TGETR_Z
822  |.  move CARG2, TISNIL
823  |  b ->BC_TGETR_Z
824  |.  ld CARG2, 0(CRET1)
825  |
826  |//-----------------------------------------------------------------------
827  |
828  |->vmeta_tsets1:
829  |  daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv)
830  |  li TMP0, LJ_TSTR
831  |  settp STR:RC, TMP0
832  |  b >1
833  |.  sd STR:RC, 0(CARG3)
834  |
835  |->vmeta_tsets:
836  |  daddiu CARG2, DISPATCH, DISPATCH_GL(tmptv)
837  |  li TMP0, LJ_TTAB
838  |   li TMP1, LJ_TSTR
839  |  settp TAB:RB, TMP0
840  |   daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv2)
841  |  sd TAB:RB, 0(CARG2)
842  |   settp STR:RC, TMP1
843  |  b >1
844  |.  sd STR:RC, 0(CARG3)
845  |
846  |->vmeta_tsetb:			// TMP0 = index
847  |  daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv)
848  |  settp TMP0, TISNUM
849  |  sd TMP0, 0(CARG3)
850  |
851  |->vmeta_tsetv:
852  |1:
853  |  load_got lj_meta_tset
854  |  sd BASE, L->base
855  |  sd PC, SAVE_PC
856  |  call_intern lj_meta_tset		// (lua_State *L, TValue *o, TValue *k)
857  |.  move CARG1, L
858  |  // Returns TValue * (finished) or NULL (metamethod).
859  |  beqz CRET1, >3
860  |.  ld CARG1, 0(RA)
861  |  // NOBARRIER: lj_meta_tset ensures the table is not black.
862  |  ins_next1
863  |  sd CARG1, 0(CRET1)
864  |  ins_next2
865  |
866  |3:  // Call __newindex metamethod.
867  |  // BASE = base, L->top = new base, stack = cont/func/t/k/(v)
868  |  daddiu TMP1, BASE, -FRAME_CONT
869  |  ld BASE, L->top
870  |  sd PC, -24(BASE)			// [cont|PC]
871  |   dsubu PC, BASE, TMP1
872  |  ld LFUNC:RB, FRAME_FUNC(BASE)	// Guaranteed to be a function here.
873  |  cleartp LFUNC:RB
874  |  sd CARG1, 16(BASE)			// Copy value to third argument.
875  |  b ->vm_call_dispatch_f
876  |.  li NARGS8:RC, 24			// 3 args for func(t, k, v)
877  |
878  |->vmeta_tsetr:
879  |  load_got lj_tab_setinth
880  |  sd BASE, L->base
881  |  sd PC, SAVE_PC
882  |  call_intern lj_tab_setinth	// (lua_State *L, GCtab *t, int32_t key)
883  |.  move CARG1, L
884  |  // Returns TValue *.
885  |  b ->BC_TSETR_Z
886  |.  nop
887  |
888  |//-- Comparison metamethods ---------------------------------------------
889  |
890  |->vmeta_comp:
891  |  // RA/RD point to o1/o2.
892  |  move CARG2, RA
893  |  move CARG3, RD
894  |  load_got lj_meta_comp
895  |  daddiu PC, PC, -4
896  |  sd BASE, L->base
897  |  sd PC, SAVE_PC
898  |  decode_OP1 CARG4, INS
899  |  call_intern lj_meta_comp	// (lua_State *L, TValue *o1, *o2, int op)
900  |.  move CARG1, L
901  |  // Returns 0/1 or TValue * (metamethod).
902  |3:
903  |  sltiu AT, CRET1, 2
904  |  beqz AT, ->vmeta_binop
905  |   negu TMP2, CRET1
906  |4:
907  |  lhu RD, OFS_RD(PC)
908  |   daddiu PC, PC, 4
909  |   lui TMP1, (-(BCBIAS_J*4 >> 16) & 65535)
910  |  sll RD, RD, 2
911  |  addu RD, RD, TMP1
912  |  and RD, RD, TMP2
913  |  daddu PC, PC, RD
914  |->cont_nop:
915  |  ins_next
916  |
917  |->cont_ra:				// RA = resultptr
918  |  lbu TMP1, -4+OFS_RA(PC)
919  |   ld CRET1, 0(RA)
920  |  sll TMP1, TMP1, 3
921  |  daddu TMP1, BASE, TMP1
922  |  b ->cont_nop
923  |.   sd CRET1, 0(TMP1)
924  |
925  |->cont_condt:			// RA = resultptr
926  |  ld TMP0, 0(RA)
927  |  gettp TMP0, TMP0
928  |  sltiu AT, TMP0, LJ_TISTRUECOND
929  |  b <4
930  |.  negu TMP2, AT			// Branch if result is true.
931  |
932  |->cont_condf:			// RA = resultptr
933  |  ld TMP0, 0(RA)
934  |  gettp TMP0, TMP0
935  |  sltiu AT, TMP0, LJ_TISTRUECOND
936  |  b <4
937  |.  addiu TMP2, AT, -1		// Branch if result is false.
938  |
939  |->vmeta_equal:
940  |  // CARG1/CARG2 point to o1/o2. TMP0 is set to 0/1.
941  |  load_got lj_meta_equal
942  |   cleartp LFUNC:CARG3, CARG2
943  |  cleartp LFUNC:CARG2, CARG1
944  |    move CARG4, TMP0
945  |  daddiu PC, PC, -4
946  |   sd BASE, L->base
947  |   sd PC, SAVE_PC
948  |  call_intern lj_meta_equal	// (lua_State *L, GCobj *o1, *o2, int ne)
949  |.  move CARG1, L
950  |  // Returns 0/1 or TValue * (metamethod).
951  |  b <3
952  |.  nop
953  |
954  |->vmeta_equal_cd:
955  |.if FFI
956  |  load_got lj_meta_equal_cd
957  |  move CARG2, INS
958  |  daddiu PC, PC, -4
959  |   sd BASE, L->base
960  |   sd PC, SAVE_PC
961  |  call_intern lj_meta_equal_cd	// (lua_State *L, BCIns op)
962  |.  move CARG1, L
963  |  // Returns 0/1 or TValue * (metamethod).
964  |  b <3
965  |.  nop
966  |.endif
967  |
968  |->vmeta_istype:
969  |  load_got lj_meta_istype
970  |  daddiu PC, PC, -4
971  |   sd BASE, L->base
972  |   srl CARG2, RA, 3
973  |   srl CARG3, RD, 3
974  |  sd PC, SAVE_PC
975  |  call_intern lj_meta_istype	// (lua_State *L, BCReg ra, BCReg tp)
976  |.  move CARG1, L
977  |  b ->cont_nop
978  |.  nop
979  |
980  |//-- Arithmetic metamethods ---------------------------------------------
981  |
982  |->vmeta_unm:
983  |  move RC, RB
984  |
985  |->vmeta_arith:
986  |  load_got lj_meta_arith
987  |   sd BASE, L->base
988  |  move CARG2, RA
989  |   sd PC, SAVE_PC
990  |  move CARG3, RB
991  |  move CARG4, RC
992  |  decode_OP1 CARG5, INS	// CARG5 == RB.
993  |  call_intern lj_meta_arith	// (lua_State *L, TValue *ra,*rb,*rc, BCReg op)
994  |.  move CARG1, L
995  |  // Returns NULL (finished) or TValue * (metamethod).
996  |  beqz CRET1, ->cont_nop
997  |.  nop
998  |
999  |  // Call metamethod for binary op.
1000  |->vmeta_binop:
1001  |  // BASE = old base, CRET1 = new base, stack = cont/func/o1/o2
1002  |  dsubu TMP1, CRET1, BASE
1003  |   sd PC, -24(CRET1)			// [cont|PC]
1004  |   move TMP2, BASE
1005  |  daddiu PC, TMP1, FRAME_CONT
1006  |   move BASE, CRET1
1007  |  b ->vm_call_dispatch
1008  |.  li NARGS8:RC, 16			// 2 args for func(o1, o2).
1009  |
1010  |->vmeta_len:
1011  |  // CARG2 already set by BC_LEN.
1012#if LJ_52
1013  |  move MULTRES, CARG1
1014#endif
1015  |  load_got lj_meta_len
1016  |   sd BASE, L->base
1017  |   sd PC, SAVE_PC
1018  |  call_intern lj_meta_len		// (lua_State *L, TValue *o)
1019  |.  move CARG1, L
1020  |  // Returns NULL (retry) or TValue * (metamethod base).
1021#if LJ_52
1022  |  bnez CRET1, ->vmeta_binop		// Binop call for compatibility.
1023  |.  nop
1024  |  b ->BC_LEN_Z
1025  |.  move CARG1, MULTRES
1026#else
1027  |  b ->vmeta_binop			// Binop call for compatibility.
1028  |.  nop
1029#endif
1030  |
1031  |//-- Call metamethod ----------------------------------------------------
1032  |
1033  |->vmeta_call:			// Resolve and call __call metamethod.
1034  |  // TMP2 = old base, BASE = new base, RC = nargs*8
1035  |  load_got lj_meta_call
1036  |   sd TMP2, L->base			// This is the callers base!
1037  |  daddiu CARG2, BASE, -16
1038  |   sd PC, SAVE_PC
1039  |  daddu CARG3, BASE, RC
1040  |   move MULTRES, NARGS8:RC
1041  |  call_intern lj_meta_call	// (lua_State *L, TValue *func, TValue *top)
1042  |.  move CARG1, L
1043  |  ld LFUNC:RB, FRAME_FUNC(BASE)	// Guaranteed to be a function here.
1044  |   daddiu NARGS8:RC, MULTRES, 8	// Got one more argument now.
1045  |  cleartp LFUNC:RB
1046  |  ins_call
1047  |
1048  |->vmeta_callt:			// Resolve __call for BC_CALLT.
1049  |  // BASE = old base, RA = new base, RC = nargs*8
1050  |  load_got lj_meta_call
1051  |   sd BASE, L->base
1052  |  daddiu CARG2, RA, -16
1053  |   sd PC, SAVE_PC
1054  |  daddu CARG3, RA, RC
1055  |   move MULTRES, NARGS8:RC
1056  |  call_intern lj_meta_call		// (lua_State *L, TValue *func, TValue *top)
1057  |.  move CARG1, L
1058  |   ld RB, FRAME_FUNC(RA)		// Guaranteed to be a function here.
1059  |  ld TMP1, FRAME_PC(BASE)
1060  |  daddiu NARGS8:RC, MULTRES, 8	// Got one more argument now.
1061  |  b ->BC_CALLT_Z
1062  |.  cleartp LFUNC:CARG3, RB
1063  |
1064  |//-- Argument coercion for 'for' statement ------------------------------
1065  |
1066  |->vmeta_for:
1067  |  load_got lj_meta_for
1068  |   sd BASE, L->base
1069  |  move CARG2, RA
1070  |   sd PC, SAVE_PC
1071  |  move MULTRES, INS
1072  |  call_intern lj_meta_for	// (lua_State *L, TValue *base)
1073  |.  move CARG1, L
1074  |.if JIT
1075  |  decode_OP1 TMP0, MULTRES
1076  |  li AT, BC_JFORI
1077  |.endif
1078  |  decode_RA8a RA, MULTRES
1079  |   decode_RD8a RD, MULTRES
1080  |  decode_RA8b RA
1081  |.if JIT
1082  |  beq TMP0, AT, =>BC_JFORI
1083  |.  decode_RD8b RD
1084  |  b =>BC_FORI
1085  |.  nop
1086  |.else
1087  |  b =>BC_FORI
1088  |.  decode_RD8b RD
1089  |.endif
1090  |
1091  |//-----------------------------------------------------------------------
1092  |//-- Fast functions -----------------------------------------------------
1093  |//-----------------------------------------------------------------------
1094  |
1095  |.macro .ffunc, name
1096  |->ff_ .. name:
1097  |.endmacro
1098  |
1099  |.macro .ffunc_1, name
1100  |->ff_ .. name:
1101  |  beqz NARGS8:RC, ->fff_fallback
1102  |.  ld CARG1, 0(BASE)
1103  |.endmacro
1104  |
1105  |.macro .ffunc_2, name
1106  |->ff_ .. name:
1107  |  sltiu AT, NARGS8:RC, 16
1108  |  ld CARG1, 0(BASE)
1109  |  bnez AT, ->fff_fallback
1110  |.  ld CARG2, 8(BASE)
1111  |.endmacro
1112  |
1113  |.macro .ffunc_n, name	// Caveat: has delay slot!
1114  |->ff_ .. name:
1115  |  ld CARG1, 0(BASE)
1116  |  beqz NARGS8:RC, ->fff_fallback
1117  |  // Either ldc1 or the 1st instruction of checknum is in the delay slot.
1118  |  .FPU ldc1 FARG1, 0(BASE)
1119  |  checknum CARG1, ->fff_fallback
1120  |.endmacro
1121  |
1122  |.macro .ffunc_nn, name	// Caveat: has delay slot!
1123  |->ff_ .. name:
1124  |  ld CARG1, 0(BASE)
1125  |    sltiu AT, NARGS8:RC, 16
1126  |   ld CARG2, 8(BASE)
1127  |  bnez AT, ->fff_fallback
1128  |.  gettp TMP0, CARG1
1129  |   gettp TMP1, CARG2
1130  |  sltiu TMP0, TMP0, LJ_TISNUM
1131  |   sltiu TMP1, TMP1, LJ_TISNUM
1132  |  .FPU ldc1 FARG1, 0(BASE)
1133  |  and TMP0, TMP0, TMP1
1134  |   .FPU ldc1 FARG2, 8(BASE)
1135  |  beqz TMP0, ->fff_fallback
1136  |.endmacro
1137  |
1138  |// Inlined GC threshold check. Caveat: uses TMP0 and TMP1 and has delay slot!
1139  |// MIPSR6: no delay slot, but a forbidden slot.
1140  |.macro ffgccheck
1141  |  ld TMP0, DISPATCH_GL(gc.total)(DISPATCH)
1142  |  ld TMP1, DISPATCH_GL(gc.threshold)(DISPATCH)
1143  |  dsubu AT, TMP0, TMP1
1144  |.if MIPSR6
1145  |  bgezalc AT, ->fff_gcstep
1146  |.else
1147  |  bgezal AT, ->fff_gcstep
1148  |.endif
1149  |.endmacro
1150  |
1151  |//-- Base library: checks -----------------------------------------------
1152  |.ffunc_1 assert
1153  |  gettp AT, CARG1
1154  |  sltiu AT, AT, LJ_TISTRUECOND
1155  |  beqz AT, ->fff_fallback
1156  |.  daddiu RA, BASE, -16
1157  |  ld PC, FRAME_PC(BASE)
1158  |  addiu RD, NARGS8:RC, 8		// Compute (nresults+1)*8.
1159  |  daddu TMP2, RA, RD
1160  |  daddiu TMP1, BASE, 8
1161  |  beq BASE, TMP2, ->fff_res		// Done if exactly 1 argument.
1162  |.  sd CARG1, 0(RA)
1163  |1:
1164  |  ld CRET1, 0(TMP1)
1165  |  sd CRET1, -16(TMP1)
1166  |  bne TMP1, TMP2, <1
1167  |.  daddiu TMP1, TMP1, 8
1168  |  b ->fff_res
1169  |.  nop
1170  |
1171  |.ffunc_1 type
1172  |  gettp TMP0, CARG1
1173  |  sltu TMP1, TISNUM, TMP0
1174  |  not TMP2, TMP0
1175  |  li TMP3, ~LJ_TISNUM
1176  |.if MIPSR6
1177  |  selnez TMP2, TMP2, TMP1
1178  |  seleqz TMP3, TMP3, TMP1
1179  |  or TMP2, TMP2, TMP3
1180  |.else
1181  |  movz TMP2, TMP3, TMP1
1182  |.endif
1183  |  dsll TMP2, TMP2, 3
1184  |  daddu TMP2, CFUNC:RB, TMP2
1185  |  b ->fff_restv
1186  |.  ld CARG1, CFUNC:TMP2->upvalue
1187  |
1188  |//-- Base library: getters and setters ---------------------------------
1189  |
1190  |.ffunc_1 getmetatable
1191  |  gettp TMP2, CARG1
1192  |  daddiu TMP0, TMP2, -LJ_TTAB
1193  |  daddiu TMP1, TMP2, -LJ_TUDATA
1194  |.if MIPSR6
1195  |  selnez TMP0, TMP1, TMP0
1196  |.else
1197  |  movn TMP0, TMP1, TMP0
1198  |.endif
1199  |  bnez TMP0, >6
1200  |.  cleartp TAB:CARG1
1201  |1:  // Field metatable must be at same offset for GCtab and GCudata!
1202  |  ld TAB:RB, TAB:CARG1->metatable
1203  |2:
1204  |  ld STR:RC, DISPATCH_GL(gcroot[GCROOT_MMNAME+MM_metatable])(DISPATCH)
1205  |  beqz TAB:RB, ->fff_restv
1206  |.  li CARG1, LJ_TNIL
1207  |  lw TMP0, TAB:RB->hmask
1208  |   lw TMP1, STR:RC->sid
1209  |    ld NODE:TMP2, TAB:RB->node
1210  |  and TMP1, TMP1, TMP0		// idx = str->sid & tab->hmask
1211  |  dsll TMP0, TMP1, 5
1212  |  dsll TMP1, TMP1, 3
1213  |  dsubu TMP1, TMP0, TMP1
1214  |  daddu NODE:TMP2, NODE:TMP2, TMP1	// node = tab->node + (idx*32-idx*8)
1215  |  li CARG4, LJ_TSTR
1216  |  settp STR:RC, CARG4		// Tagged key to look for.
1217  |3:  // Rearranged logic, because we expect _not_ to find the key.
1218  |  ld TMP0, NODE:TMP2->key
1219  |   ld CARG1, NODE:TMP2->val
1220  |    ld NODE:TMP2, NODE:TMP2->next
1221  |  beq RC, TMP0, >5
1222  |.  li AT, LJ_TTAB
1223  |  bnez NODE:TMP2, <3
1224  |.  nop
1225  |4:
1226  |  move CARG1, RB
1227  |  b ->fff_restv			// Not found, keep default result.
1228  |.  settp CARG1, AT
1229  |5:
1230  |  bne CARG1, TISNIL, ->fff_restv
1231  |.  nop
1232  |  b <4				// Ditto for nil value.
1233  |.  nop
1234  |
1235  |6:
1236  |  sltiu AT, TMP2, LJ_TISNUM
1237  |.if MIPSR6
1238  |  selnez TMP0, TISNUM, AT
1239  |  seleqz AT, TMP2, AT
1240  |  or TMP2, TMP0, AT
1241  |.else
1242  |  movn TMP2, TISNUM, AT
1243  |.endif
1244  |  dsll TMP2, TMP2, 3
1245  |   dsubu TMP0, DISPATCH, TMP2
1246  |  b <2
1247  |.  ld TAB:RB, DISPATCH_GL(gcroot[GCROOT_BASEMT])-8(TMP0)
1248  |
1249  |.ffunc_2 setmetatable
1250  |  // Fast path: no mt for table yet and not clearing the mt.
1251  |  checktp TMP1, CARG1, -LJ_TTAB, ->fff_fallback
1252  |  gettp TMP3, CARG2
1253  |   ld TAB:TMP0, TAB:TMP1->metatable
1254  |   lbu TMP2, TAB:TMP1->marked
1255  |  daddiu AT, TMP3, -LJ_TTAB
1256  |   cleartp TAB:CARG2
1257  |  or AT, AT, TAB:TMP0
1258  |  bnez AT, ->fff_fallback
1259  |.  andi AT, TMP2, LJ_GC_BLACK	// isblack(table)
1260  |  beqz AT, ->fff_restv
1261  |.  sd TAB:CARG2, TAB:TMP1->metatable
1262  |  barrierback TAB:TMP1, TMP2, TMP0, ->fff_restv
1263  |
1264  |.ffunc rawget
1265  |  ld CARG2, 0(BASE)
1266  |  sltiu AT, NARGS8:RC, 16
1267  |  load_got lj_tab_get
1268  |  gettp TMP0, CARG2
1269  |   cleartp CARG2
1270  |  daddiu TMP0, TMP0, -LJ_TTAB
1271  |  or AT, AT, TMP0
1272  |  bnez AT, ->fff_fallback
1273  |.  daddiu CARG3, BASE, 8
1274  |  call_intern lj_tab_get	// (lua_State *L, GCtab *t, cTValue *key)
1275  |.  move CARG1, L
1276  |  b ->fff_restv
1277  |.  ld CARG1, 0(CRET1)
1278  |
1279  |//-- Base library: conversions ------------------------------------------
1280  |
1281  |.ffunc tonumber
1282  |  // Only handles the number case inline (without a base argument).
1283  |  ld CARG1, 0(BASE)
1284  |  xori AT, NARGS8:RC, 8		// Exactly one number argument.
1285  |  gettp TMP1, CARG1
1286  |  sltu TMP0, TISNUM, TMP1
1287  |  or AT, AT, TMP0
1288  |  bnez AT, ->fff_fallback
1289  |.  nop
1290  |  b ->fff_restv
1291  |.  nop
1292  |
1293  |.ffunc_1 tostring
1294  |  // Only handles the string or number case inline.
1295  |  gettp TMP0, CARG1
1296  |  daddiu AT, TMP0, -LJ_TSTR
1297  |  // A __tostring method in the string base metatable is ignored.
1298  |  beqz AT, ->fff_restv	// String key?
1299  |  // Handle numbers inline, unless a number base metatable is present.
1300  |.  ld TMP1, DISPATCH_GL(gcroot[GCROOT_BASEMT_NUM])(DISPATCH)
1301  |  sltu TMP0, TISNUM, TMP0
1302  |  or TMP0, TMP0, TMP1
1303  |  bnez TMP0, ->fff_fallback
1304  |.  sd BASE, L->base			// Add frame since C call can throw.
1305  |.if MIPSR6
1306  |  sd PC, SAVE_PC			// Redundant (but a defined value).
1307  |  ffgccheck
1308  |.else
1309  |  ffgccheck
1310  |.  sd PC, SAVE_PC			// Redundant (but a defined value).
1311  |.endif
1312  |  load_got lj_strfmt_number
1313  |  move CARG1, L
1314  |  call_intern lj_strfmt_number	// (lua_State *L, cTValue *o)
1315  |.  move CARG2, BASE
1316  |  // Returns GCstr *.
1317  |  li AT, LJ_TSTR
1318  |  settp CRET1, AT
1319  |  b ->fff_restv
1320  |.  move CARG1, CRET1
1321  |
1322  |//-- Base library: iterators -------------------------------------------
1323  |
1324  |.ffunc_1 next
1325  |  checktp CARG1, -LJ_TTAB, ->fff_fallback
1326  |  daddu TMP2, BASE, NARGS8:RC
1327  |  sd TISNIL, 0(TMP2)			// Set missing 2nd arg to nil.
1328  |  load_got lj_tab_next
1329  |  ld PC, FRAME_PC(BASE)
1330  |  daddiu CARG2, BASE, 8
1331  |  call_intern lj_tab_next		// (GCtab *t, cTValue *key, TValue *o)
1332  |.  daddiu CARG3, BASE, -16
1333  |  // Returns 1=found, 0=end, -1=error.
1334  |   daddiu RA, BASE, -16
1335  |  bgtz CRET1, ->fff_res		// Found key/value.
1336  |.  li RD, (2+1)*8
1337  |  beqz CRET1, ->fff_restv		// End of traversal: return nil.
1338  |.  move CARG1, TISNIL
1339  |   ld CFUNC:RB, FRAME_FUNC(BASE)
1340  |   cleartp CFUNC:RB
1341  |  b ->fff_fallback			// Invalid key.
1342  |.  li RC, 2*8
1343  |
1344  |.ffunc_1 pairs
1345  |  checktp TAB:TMP1, CARG1, -LJ_TTAB, ->fff_fallback
1346  |  ld PC, FRAME_PC(BASE)
1347#if LJ_52
1348  |  ld TAB:TMP2, TAB:TMP1->metatable
1349  |  ld TMP0, CFUNC:RB->upvalue[0]
1350  |  bnez TAB:TMP2, ->fff_fallback
1351#else
1352  |  ld TMP0, CFUNC:RB->upvalue[0]
1353#endif
1354  |.  daddiu RA, BASE, -16
1355  |  sd TISNIL, 0(BASE)
1356  |   sd CARG1, -8(BASE)
1357  |    sd TMP0, 0(RA)
1358  |  b ->fff_res
1359  |.  li RD, (3+1)*8
1360  |
1361  |.ffunc_2 ipairs_aux
1362  |  checktab CARG1, ->fff_fallback
1363  |   checkint CARG2, ->fff_fallback
1364  |.  lw TMP0, TAB:CARG1->asize
1365  |   ld TMP1, TAB:CARG1->array
1366  |    ld PC, FRAME_PC(BASE)
1367  |  sextw TMP2, CARG2
1368  |  addiu TMP2, TMP2, 1
1369  |  sltu AT, TMP2, TMP0
1370  |    daddiu RA, BASE, -16
1371  |   zextw TMP0, TMP2
1372  |   settp TMP0, TISNUM
1373  |  beqz AT, >2			// Not in array part?
1374  |.  sd TMP0, 0(RA)
1375  |  dsll TMP3, TMP2, 3
1376  |  daddu TMP3, TMP1, TMP3
1377  |  ld TMP1, 0(TMP3)
1378  |1:
1379  |  beq TMP1, TISNIL, ->fff_res	// End of iteration, return 0 results.
1380  |.  li RD, (0+1)*8
1381  |  sd TMP1, -8(BASE)
1382  |  b ->fff_res
1383  |.  li RD, (2+1)*8
1384  |2:  // Check for empty hash part first. Otherwise call C function.
1385  |  lw TMP0, TAB:CARG1->hmask
1386  |  load_got lj_tab_getinth
1387  |  beqz TMP0, ->fff_res
1388  |.  li RD, (0+1)*8
1389  |  call_intern lj_tab_getinth		// (GCtab *t, int32_t key)
1390  |.  move CARG2, TMP2
1391  |  // Returns cTValue * or NULL.
1392  |  beqz CRET1, ->fff_res
1393  |.  li RD, (0+1)*8
1394  |  b <1
1395  |.  ld TMP1, 0(CRET1)
1396  |
1397  |.ffunc_1 ipairs
1398  |  checktp TAB:TMP1, CARG1, -LJ_TTAB, ->fff_fallback
1399  |  ld PC, FRAME_PC(BASE)
1400#if LJ_52
1401  |  ld TAB:TMP2, TAB:TMP1->metatable
1402  |  ld CFUNC:TMP0, CFUNC:RB->upvalue[0]
1403  |  bnez TAB:TMP2, ->fff_fallback
1404#else
1405  |  ld TMP0, CFUNC:RB->upvalue[0]
1406#endif
1407  |  daddiu RA, BASE, -16
1408  |  dsll AT, TISNUM, 47
1409  |  sd CARG1, -8(BASE)
1410  |   sd AT, 0(BASE)
1411  |    sd CFUNC:TMP0, 0(RA)
1412  |  b ->fff_res
1413  |.  li RD, (3+1)*8
1414  |
1415  |//-- Base library: catch errors ----------------------------------------
1416  |
1417  |.ffunc pcall
1418  |  daddiu NARGS8:RC, NARGS8:RC, -8
1419  |  lbu TMP3, DISPATCH_GL(hookmask)(DISPATCH)
1420  |  bltz NARGS8:RC, ->fff_fallback
1421  |.   move TMP2, BASE
1422  |   daddiu BASE, BASE, 16
1423  |  // Remember active hook before pcall.
1424  |  srl TMP3, TMP3, HOOK_ACTIVE_SHIFT
1425  |  andi TMP3, TMP3, 1
1426  |  daddiu PC, TMP3, 16+FRAME_PCALL
1427  |  beqz NARGS8:RC, ->vm_call_dispatch
1428  |1:
1429  |.  daddu TMP0, BASE, NARGS8:RC
1430  |2:
1431  |  ld TMP1, -16(TMP0)
1432  |  sd TMP1, -8(TMP0)
1433  |  daddiu TMP0, TMP0, -8
1434  |  bne TMP0, BASE, <2
1435  |.  nop
1436  |  b ->vm_call_dispatch
1437  |.  nop
1438  |
1439  |.ffunc xpcall
1440  |  daddiu NARGS8:TMP0, NARGS8:RC, -16
1441  |  ld CARG1, 0(BASE)
1442  |   ld CARG2, 8(BASE)
1443  |    bltz NARGS8:TMP0, ->fff_fallback
1444  |.    lbu TMP1, DISPATCH_GL(hookmask)(DISPATCH)
1445  |  gettp AT, CARG2
1446  |  daddiu AT, AT, -LJ_TFUNC
1447  |  bnez AT, ->fff_fallback		// Traceback must be a function.
1448  |.   move TMP2, BASE
1449  |  move NARGS8:RC, NARGS8:TMP0
1450  |   daddiu BASE, BASE, 24
1451  |  // Remember active hook before pcall.
1452  |  srl TMP3, TMP3, HOOK_ACTIVE_SHIFT
1453  |   sd CARG2, 0(TMP2)			// Swap function and traceback.
1454  |  andi TMP3, TMP3, 1
1455  |   sd CARG1, 8(TMP2)
1456  |  beqz NARGS8:RC, ->vm_call_dispatch
1457  |.  daddiu PC, TMP3, 24+FRAME_PCALL
1458  |  b <1
1459  |.  nop
1460  |
1461  |//-- Coroutine library --------------------------------------------------
1462  |
1463  |.macro coroutine_resume_wrap, resume
1464  |.if resume
1465  |.ffunc_1 coroutine_resume
1466  |  checktp CARG1, CARG1, -LJ_TTHREAD, ->fff_fallback
1467  |.else
1468  |.ffunc coroutine_wrap_aux
1469  |  ld L:CARG1, CFUNC:RB->upvalue[0].gcr
1470  |  cleartp L:CARG1
1471  |.endif
1472  |  lbu TMP0, L:CARG1->status
1473  |   ld TMP1, L:CARG1->cframe
1474  |    ld CARG2, L:CARG1->top
1475  |    ld TMP2, L:CARG1->base
1476  |  addiu AT, TMP0, -LUA_YIELD
1477  |    daddu CARG3, CARG2, TMP0
1478  |   daddiu TMP3, CARG2, 8
1479  |.if MIPSR6
1480  |  seleqz CARG2, CARG2, AT
1481  |  selnez TMP3, TMP3, AT
1482  |  bgtz AT, ->fff_fallback		// st > LUA_YIELD?
1483  |.  or CARG2, TMP3, CARG2
1484  |.else
1485  |  bgtz AT, ->fff_fallback		// st > LUA_YIELD?
1486  |.  movn CARG2, TMP3, AT
1487  |.endif
1488  |   xor TMP2, TMP2, CARG3
1489  |  bnez TMP1, ->fff_fallback		// cframe != 0?
1490  |.  or AT, TMP2, TMP0
1491  |  ld TMP0, L:CARG1->maxstack
1492  |  beqz AT, ->fff_fallback		// base == top && st == 0?
1493  |.  ld PC, FRAME_PC(BASE)
1494  |  daddu TMP2, CARG2, NARGS8:RC
1495  |  sltu AT, TMP0, TMP2
1496  |  bnez AT, ->fff_fallback		// Stack overflow?
1497  |.  sd PC, SAVE_PC
1498  |   sd BASE, L->base
1499  |1:
1500  |.if resume
1501  |  daddiu BASE, BASE, 8		// Keep resumed thread in stack for GC.
1502  |  daddiu NARGS8:RC, NARGS8:RC, -8
1503  |  daddiu TMP2, TMP2, -8
1504  |.endif
1505  |  sd TMP2, L:CARG1->top
1506  |  daddu TMP1, BASE, NARGS8:RC
1507  |  move CARG3, CARG2
1508  |  sd BASE, L->top
1509  |2:  // Move args to coroutine.
1510  |   ld CRET1, 0(BASE)
1511  |  sltu AT, BASE, TMP1
1512  |  beqz AT, >3
1513  |.  daddiu BASE, BASE, 8
1514  |   sd CRET1, 0(CARG3)
1515  |  b <2
1516  |.  daddiu CARG3, CARG3, 8
1517  |3:
1518  |  bal ->vm_resume			// (lua_State *L, TValue *base, 0, 0)
1519  |.  move L:RA, L:CARG1
1520  |  // Returns thread status.
1521  |4:
1522  |  ld TMP2, L:RA->base
1523  |   sltiu AT, CRET1, LUA_YIELD+1
1524  |  ld TMP3, L:RA->top
1525  |    li_vmstate INTERP
1526  |  ld BASE, L->base
1527  |    sd L, DISPATCH_GL(cur_L)(DISPATCH)
1528  |    st_vmstate
1529  |   beqz AT, >8
1530  |. dsubu RD, TMP3, TMP2
1531  |   ld TMP0, L->maxstack
1532  |  beqz RD, >6			// No results?
1533  |.  daddu TMP1, BASE, RD
1534  |  sltu AT, TMP0, TMP1
1535  |  bnez AT, >9			// Need to grow stack?
1536  |.  daddu TMP3, TMP2, RD
1537  |  sd TMP2, L:RA->top			// Clear coroutine stack.
1538  |  move TMP1, BASE
1539  |5:  // Move results from coroutine.
1540  |   ld CRET1, 0(TMP2)
1541  |  daddiu TMP2, TMP2, 8
1542  |  sltu AT, TMP2, TMP3
1543  |   sd CRET1, 0(TMP1)
1544  |  bnez AT, <5
1545  |.  daddiu TMP1, TMP1, 8
1546  |6:
1547  |  andi TMP0, PC, FRAME_TYPE
1548  |.if resume
1549  |  mov_true TMP1
1550  |   daddiu RA, BASE, -8
1551  |  sd TMP1, -8(BASE)			// Prepend true to results.
1552  |  daddiu RD, RD, 16
1553  |.else
1554  |  move RA, BASE
1555  |  daddiu RD, RD, 8
1556  |.endif
1557  |7:
1558  |  sd PC, SAVE_PC
1559  |  beqz TMP0, ->BC_RET_Z
1560  |.  move MULTRES, RD
1561  |  b ->vm_return
1562  |.  nop
1563  |
1564  |8:  // Coroutine returned with error (at co->top-1).
1565  |.if resume
1566  |  daddiu TMP3, TMP3, -8
1567  |   mov_false TMP1
1568  |  ld CRET1, 0(TMP3)
1569  |   sd TMP3, L:RA->top		// Remove error from coroutine stack.
1570  |    li RD, (2+1)*8
1571  |   sd TMP1, -8(BASE)			// Prepend false to results.
1572  |    daddiu RA, BASE, -8
1573  |  sd CRET1, 0(BASE)			// Copy error message.
1574  |  b <7
1575  |.  andi TMP0, PC, FRAME_TYPE
1576  |.else
1577  |  load_got lj_ffh_coroutine_wrap_err
1578  |  move CARG2, L:RA
1579  |  call_intern lj_ffh_coroutine_wrap_err  // (lua_State *L, lua_State *co)
1580  |.  move CARG1, L
1581  |.endif
1582  |
1583  |9:  // Handle stack expansion on return from yield.
1584  |  load_got lj_state_growstack
1585  |  srl CARG2, RD, 3
1586  |  call_intern lj_state_growstack	// (lua_State *L, int n)
1587  |.  move CARG1, L
1588  |  b <4
1589  |.  li CRET1, 0
1590  |.endmacro
1591  |
1592  |  coroutine_resume_wrap 1		// coroutine.resume
1593  |  coroutine_resume_wrap 0		// coroutine.wrap
1594  |
1595  |.ffunc coroutine_yield
1596  |  ld TMP0, L->cframe
1597  |   daddu TMP1, BASE, NARGS8:RC
1598  |   sd BASE, L->base
1599  |  andi TMP0, TMP0, CFRAME_RESUME
1600  |   sd TMP1, L->top
1601  |  beqz TMP0, ->fff_fallback
1602  |.   li CRET1, LUA_YIELD
1603  |  sd r0, L->cframe
1604  |  b ->vm_leave_unw
1605  |.   sb CRET1, L->status
1606  |
1607  |//-- Math library -------------------------------------------------------
1608  |
1609  |.ffunc_1 math_abs
1610  |  gettp CARG2, CARG1
1611  |  daddiu AT, CARG2, -LJ_TISNUM
1612  |  bnez AT, >1
1613  |.  sextw TMP1, CARG1
1614  |  sra TMP0, TMP1, 31			// Extract sign.
1615  |  xor TMP1, TMP1, TMP0
1616  |  dsubu CARG1, TMP1, TMP0
1617  |  dsll TMP3, CARG1, 32
1618  |  bgez TMP3, ->fff_restv
1619  |.  settp CARG1, TISNUM
1620  |  li CARG1, 0x41e0			// 2^31 as a double.
1621  |  b ->fff_restv
1622  |.  dsll CARG1, CARG1, 48
1623  |1:
1624  |  sltiu AT, CARG2, LJ_TISNUM
1625  |  beqz AT, ->fff_fallback
1626  |.  dextm CARG1, CARG1, 0, 30
1627  |// fallthrough
1628  |
1629  |->fff_restv:
1630  |  // CARG1 = TValue result.
1631  |  ld PC, FRAME_PC(BASE)
1632  |  daddiu RA, BASE, -16
1633  |   sd CARG1, -16(BASE)
1634  |->fff_res1:
1635  |  // RA = results, PC = return.
1636  |  li RD, (1+1)*8
1637  |->fff_res:
1638  |  // RA = results, RD = (nresults+1)*8, PC = return.
1639  |  andi TMP0, PC, FRAME_TYPE
1640  |  bnez TMP0, ->vm_return
1641  |.  move MULTRES, RD
1642  |  lw INS, -4(PC)
1643  |  decode_RB8a RB, INS
1644  |  decode_RB8b RB
1645  |5:
1646  |  sltu AT, RD, RB
1647  |  bnez AT, >6			// More results expected?
1648  |.  decode_RA8a TMP0, INS
1649  |  decode_RA8b TMP0
1650  |  ins_next1
1651  |  // Adjust BASE. KBASE is assumed to be set for the calling frame.
1652  |   dsubu BASE, RA, TMP0
1653  |  ins_next2
1654  |
1655  |6:  // Fill up results with nil.
1656  |  daddu TMP1, RA, RD
1657  |   daddiu RD, RD, 8
1658  |  b <5
1659  |.  sd TISNIL, -8(TMP1)
1660  |
1661  |.macro math_extern, func
1662  |  .ffunc_n math_ .. func
1663  |  load_got func
1664  |  call_extern
1665  |.  nop
1666  |  b ->fff_resn
1667  |.  nop
1668  |.endmacro
1669  |
1670  |.macro math_extern2, func
1671  |  .ffunc_nn math_ .. func
1672  |.  load_got func
1673  |  call_extern
1674  |.  nop
1675  |  b ->fff_resn
1676  |.  nop
1677  |.endmacro
1678  |
1679  |// TODO: Return integer type if result is integer (own sf implementation).
1680  |.macro math_round, func
1681  |->ff_math_ .. func:
1682  |  ld CARG1, 0(BASE)
1683  |  beqz NARGS8:RC, ->fff_fallback
1684  |.  gettp TMP0, CARG1
1685  |  beq TMP0, TISNUM, ->fff_restv
1686  |.  sltu AT, TMP0, TISNUM
1687  |  beqz AT, ->fff_fallback
1688  |.if FPU
1689  |.  ldc1 FARG1, 0(BASE)
1690  |  bal ->vm_ .. func
1691  |.  nop
1692  |.else
1693  |.  load_got func
1694  |  call_extern
1695  |.  nop
1696  |.endif
1697  |  b ->fff_resn
1698  |.  nop
1699  |.endmacro
1700  |
1701  |  math_round floor
1702  |  math_round ceil
1703  |
1704  |.ffunc math_log
1705  |  li AT, 8
1706  |  bne NARGS8:RC, AT, ->fff_fallback	// Exactly 1 argument.
1707  |.  ld CARG1, 0(BASE)
1708  |  checknum CARG1, ->fff_fallback
1709  |.  load_got log
1710  |.if FPU
1711  |  call_extern
1712  |.  ldc1 FARG1, 0(BASE)
1713  |.else
1714  |  call_extern
1715  |.  nop
1716  |.endif
1717  |  b ->fff_resn
1718  |.  nop
1719  |
1720  |  math_extern log10
1721  |  math_extern exp
1722  |  math_extern sin
1723  |  math_extern cos
1724  |  math_extern tan
1725  |  math_extern asin
1726  |  math_extern acos
1727  |  math_extern atan
1728  |  math_extern sinh
1729  |  math_extern cosh
1730  |  math_extern tanh
1731  |  math_extern2 pow
1732  |  math_extern2 atan2
1733  |  math_extern2 fmod
1734  |
1735  |.if FPU
1736  |.ffunc_n math_sqrt
1737  |.  sqrt.d FRET1, FARG1
1738  |// fallthrough to ->fff_resn
1739  |.else
1740  |  math_extern sqrt
1741  |.endif
1742  |
1743  |->fff_resn:
1744  |  ld PC, FRAME_PC(BASE)
1745  |  daddiu RA, BASE, -16
1746  |  b ->fff_res1
1747  |.if FPU
1748  |.  sdc1 FRET1, 0(RA)
1749  |.else
1750  |.  sd CRET1, 0(RA)
1751  |.endif
1752  |
1753  |
1754  |.ffunc_2 math_ldexp
1755  |  checknum CARG1, ->fff_fallback
1756  |  checkint CARG2, ->fff_fallback
1757  |.  load_got ldexp
1758  |  .FPU ldc1 FARG1, 0(BASE)
1759  |  call_extern
1760  |.  lw CARG2, 8+LO(BASE)
1761  |  b ->fff_resn
1762  |.  nop
1763  |
1764  |.ffunc_n math_frexp
1765  |  load_got frexp
1766  |   ld PC, FRAME_PC(BASE)
1767  |  call_extern
1768  |.  daddiu CARG2, DISPATCH, DISPATCH_GL(tmptv)
1769  |   lw TMP1, DISPATCH_GL(tmptv)(DISPATCH)
1770  |  daddiu RA, BASE, -16
1771  |.if FPU
1772  |   mtc1 TMP1, FARG2
1773  |  sdc1 FRET1, 0(RA)
1774  |   cvt.d.w FARG2, FARG2
1775  |   sdc1 FARG2, 8(RA)
1776  |.else
1777  |  sd CRET1, 0(RA)
1778  |  zextw TMP1, TMP1
1779  |  settp TMP1, TISNUM
1780  |  sd TMP1, 8(RA)
1781  |.endif
1782  |  b ->fff_res
1783  |.  li RD, (2+1)*8
1784  |
1785  |.ffunc_n math_modf
1786  |  load_got modf
1787  |   ld PC, FRAME_PC(BASE)
1788  |  call_extern
1789  |.  daddiu CARG2, BASE, -16
1790  |  daddiu RA, BASE, -16
1791  |.if FPU
1792  |  sdc1 FRET1, -8(BASE)
1793  |.else
1794  |  sd CRET1, -8(BASE)
1795  |.endif
1796  |  b ->fff_res
1797  |.  li RD, (2+1)*8
1798  |
1799  |.macro math_minmax, name, intins, intinsc, fpins
1800  |  .ffunc_1 name
1801  |  daddu TMP3, BASE, NARGS8:RC
1802  |  checkint CARG1, >5
1803  |.  daddiu TMP2, BASE, 8
1804  |1:  // Handle integers.
1805  |  beq TMP2, TMP3, ->fff_restv
1806  |.  ld CARG2, 0(TMP2)
1807  |  checkint CARG2, >3
1808  |.  sextw CARG1, CARG1
1809  |  lw CARG2, LO(TMP2)
1810  |.  slt AT, CARG1, CARG2
1811  |.if MIPSR6
1812  |  intins TMP1, CARG2, AT
1813  |  intinsc CARG1, CARG1, AT
1814  |  or CARG1, CARG1, TMP1
1815  |.else
1816  |  intins CARG1, CARG2, AT
1817  |.endif
1818  |  daddiu TMP2, TMP2, 8
1819  |  zextw CARG1, CARG1
1820  |  b <1
1821  |.  settp CARG1, TISNUM
1822  |
1823  |3:  // Convert intermediate result to number and continue with number loop.
1824  |  checknum CARG2, ->fff_fallback
1825  |.if FPU
1826  |.  mtc1 CARG1, FRET1
1827  |  cvt.d.w FRET1, FRET1
1828  |  b >7
1829  |.  ldc1 FARG1, 0(TMP2)
1830  |.else
1831  |.  nop
1832  |  bal ->vm_sfi2d_1
1833  |.  nop
1834  |  b >7
1835  |.  nop
1836  |.endif
1837  |
1838  |5:
1839  |  .FPU ldc1 FRET1, 0(BASE)
1840  |  checknum CARG1, ->fff_fallback
1841  |6:  // Handle numbers.
1842  |.  ld CARG2, 0(TMP2)
1843  |  beq TMP2, TMP3, ->fff_resn
1844  |.if FPU
1845  |  ldc1 FARG1, 0(TMP2)
1846  |.else
1847  |  move CRET1, CARG1
1848  |.endif
1849  |  checknum CARG2, >8
1850  |.  nop
1851  |7:
1852  |.if FPU
1853  |.if MIPSR6
1854  |  fpins FRET1, FRET1, FARG1
1855  |.else
1856  |.if fpins  // ismax
1857  |  c.olt.d FARG1, FRET1
1858  |.else
1859  |  c.olt.d FRET1, FARG1
1860  |.endif
1861  |  movf.d FRET1, FARG1
1862  |.endif
1863  |.else
1864  |.if fpins  // ismax
1865  |  bal ->vm_sfcmpogt
1866  |.else
1867  |  bal ->vm_sfcmpolt
1868  |.endif
1869  |.  nop
1870  |.if MIPSR6
1871  |  seleqz AT, CARG2, CRET1
1872  |  selnez CARG1, CARG1, CRET1
1873  |  or CARG1, CARG1, AT
1874  |.else
1875  |  movz CARG1, CARG2, CRET1
1876  |.endif
1877  |.endif
1878  |  b <6
1879  |.  daddiu TMP2, TMP2, 8
1880  |
1881  |8:  // Convert integer to number and continue with number loop.
1882  |  checkint CARG2, ->fff_fallback
1883  |.if FPU
1884  |.  lwc1 FARG1, LO(TMP2)
1885  |  b <7
1886  |.  cvt.d.w FARG1, FARG1
1887  |.else
1888  |.  lw CARG2, LO(TMP2)
1889  |  bal ->vm_sfi2d_2
1890  |.  nop
1891  |  b <7
1892  |.  nop
1893  |.endif
1894  |
1895  |.endmacro
1896  |
1897  |.if MIPSR6
1898  |  math_minmax math_min, seleqz, selnez, min.d
1899  |  math_minmax math_max, selnez, seleqz, max.d
1900  |.else
1901  |  math_minmax math_min, movz, _, 0
1902  |  math_minmax math_max, movn, _, 1
1903  |.endif
1904  |
1905  |//-- String library -----------------------------------------------------
1906  |
1907  |.ffunc string_byte			// Only handle the 1-arg case here.
1908  |  ld CARG1, 0(BASE)
1909  |  gettp TMP0, CARG1
1910  |  xori AT, NARGS8:RC, 8
1911  |  daddiu TMP0, TMP0, -LJ_TSTR
1912  |  or AT, AT, TMP0
1913  |  bnez AT, ->fff_fallback		// Need exactly 1 string argument.
1914  |.  cleartp STR:CARG1
1915  |  lw TMP0, STR:CARG1->len
1916  |    daddiu RA, BASE, -16
1917  |    ld PC, FRAME_PC(BASE)
1918  |  sltu RD, r0, TMP0
1919  |   lbu TMP1, STR:CARG1[1]		// Access is always ok (NUL at end).
1920  |  addiu RD, RD, 1
1921  |  sll RD, RD, 3			// RD = ((str->len != 0)+1)*8
1922  |  settp TMP1, TISNUM
1923  |  b ->fff_res
1924  |.  sd TMP1, 0(RA)
1925  |
1926  |.ffunc string_char			// Only handle the 1-arg case here.
1927  |  ffgccheck
1928  |.if not MIPSR6
1929  |.  nop
1930  |.endif
1931  |  ld CARG1, 0(BASE)
1932  |  gettp TMP0, CARG1
1933  |  xori AT, NARGS8:RC, 8		// Exactly 1 argument.
1934  |  daddiu TMP0, TMP0, -LJ_TISNUM	// Integer.
1935  |  li TMP1, 255
1936  |   sextw CARG1, CARG1
1937  |  or AT, AT, TMP0
1938  |   sltu TMP1, TMP1, CARG1		// !(255 < n).
1939  |   or AT, AT, TMP1
1940  |  bnez AT, ->fff_fallback
1941  |.  li CARG3, 1
1942  |  daddiu CARG2, sp, TMPD_OFS
1943  |  sb CARG1, TMPD
1944  |->fff_newstr:
1945  |  load_got lj_str_new
1946  |   sd BASE, L->base
1947  |   sd PC, SAVE_PC
1948  |  call_intern lj_str_new		// (lua_State *L, char *str, size_t l)
1949  |.  move CARG1, L
1950  |  // Returns GCstr *.
1951  |  ld BASE, L->base
1952  |->fff_resstr:
1953  |  li AT, LJ_TSTR
1954  |  settp CRET1, AT
1955  |  b ->fff_restv
1956  |.  move CARG1, CRET1
1957  |
1958  |.ffunc string_sub
1959  |  ffgccheck
1960  |.if not MIPSR6
1961  |.  nop
1962  |.endif
1963  |  addiu AT, NARGS8:RC, -16
1964  |  ld TMP0, 0(BASE)
1965  |  bltz AT, ->fff_fallback
1966  |.  gettp TMP3, TMP0
1967  |  cleartp STR:CARG1, TMP0
1968  |  ld CARG2, 8(BASE)
1969  |  beqz AT, >1
1970  |.  li CARG4, -1
1971  |  ld CARG3, 16(BASE)
1972  |  checkint CARG3, ->fff_fallback
1973  |.  sextw CARG4, CARG3
1974  |1:
1975  |  checkint CARG2, ->fff_fallback
1976  |.  li AT, LJ_TSTR
1977  |  bne TMP3, AT, ->fff_fallback
1978  |.  sextw CARG3, CARG2
1979  |  lw CARG2, STR:CARG1->len
1980  |  // STR:CARG1 = str, CARG2 = str->len, CARG3 = start, CARG4 = end
1981  |  slt AT, CARG4, r0
1982  |  addiu TMP0, CARG2, 1
1983  |  addu TMP1, CARG4, TMP0
1984  |   slt TMP3, CARG3, r0
1985  |.if MIPSR6
1986  |  seleqz CARG4, CARG4, AT
1987  |  selnez TMP1, TMP1, AT
1988  |  or CARG4, TMP1, CARG4		// if (end < 0) end += len+1
1989  |.else
1990  |  movn CARG4, TMP1, AT		// if (end < 0) end += len+1
1991  |.endif
1992  |   addu TMP1, CARG3, TMP0
1993  |.if MIPSR6
1994  |   selnez TMP1, TMP1, TMP3
1995  |   seleqz CARG3, CARG3, TMP3
1996  |   or CARG3, TMP1, CARG3		// if (start < 0) start += len+1
1997  |   li TMP2, 1
1998  |  slt AT, CARG4, r0
1999  |   slt TMP3, r0, CARG3
2000  |  seleqz CARG4, CARG4, AT		// if (end < 0) end = 0
2001  |   selnez CARG3, CARG3, TMP3
2002  |   seleqz TMP2, TMP2, TMP3
2003  |   or CARG3, TMP2, CARG3		// if (start < 1) start = 1
2004  |  slt AT, CARG2, CARG4
2005  |  seleqz CARG4, CARG4, AT
2006  |  selnez CARG2, CARG2, AT
2007  |  or CARG4, CARG2, CARG4		// if (end > len) end = len
2008  |.else
2009  |   movn CARG3, TMP1, TMP3		// if (start < 0) start += len+1
2010  |   li TMP2, 1
2011  |  slt AT, CARG4, r0
2012  |   slt TMP3, r0, CARG3
2013  |  movn CARG4, r0, AT			// if (end < 0) end = 0
2014  |   movz CARG3, TMP2, TMP3		// if (start < 1) start = 1
2015  |  slt AT, CARG2, CARG4
2016  |  movn CARG4, CARG2, AT		// if (end > len) end = len
2017  |.endif
2018  |   daddu CARG2, STR:CARG1, CARG3
2019  |  subu CARG3, CARG4, CARG3		// len = end - start
2020  |   daddiu CARG2, CARG2, sizeof(GCstr)-1
2021  |  bgez CARG3, ->fff_newstr
2022  |.  addiu CARG3, CARG3, 1		// len++
2023  |->fff_emptystr:  // Return empty string.
2024  |  li AT, LJ_TSTR
2025  |  daddiu STR:CARG1, DISPATCH, DISPATCH_GL(strempty)
2026  |  b ->fff_restv
2027  |.  settp CARG1, AT
2028  |
2029  |.macro ffstring_op, name
2030  |  .ffunc string_ .. name
2031  |  ffgccheck
2032  |.  nop
2033  |  beqz NARGS8:RC, ->fff_fallback
2034  |.  ld CARG2, 0(BASE)
2035  |  checkstr STR:CARG2, ->fff_fallback
2036  |  daddiu SBUF:CARG1, DISPATCH, DISPATCH_GL(tmpbuf)
2037  |  load_got lj_buf_putstr_ .. name
2038  |  ld TMP0, SBUF:CARG1->b
2039  |   sd L, SBUF:CARG1->L
2040  |   sd BASE, L->base
2041  |  sd TMP0, SBUF:CARG1->w
2042  |  call_intern extern lj_buf_putstr_ .. name
2043  |.  sd PC, SAVE_PC
2044  |  load_got lj_buf_tostr
2045  |  call_intern lj_buf_tostr
2046  |.  move SBUF:CARG1, SBUF:CRET1
2047  |  b ->fff_resstr
2048  |.  ld BASE, L->base
2049  |.endmacro
2050  |
2051  |ffstring_op reverse
2052  |ffstring_op lower
2053  |ffstring_op upper
2054  |
2055  |//-- Bit library --------------------------------------------------------
2056  |
2057  |->vm_tobit_fb:
2058  |  beqz TMP1, ->fff_fallback
2059  |.if FPU
2060  |.  ldc1 FARG1, 0(BASE)
2061  |  add.d FARG1, FARG1, TOBIT
2062  |  mfc1 CRET1, FARG1
2063  |  jr ra
2064  |.  zextw CRET1, CRET1
2065  |.else
2066  |// FP number to bit conversion for soft-float.
2067  |->vm_tobit:
2068  |  dsll TMP0, CARG1, 1
2069  |  li CARG3, 1076
2070  |  dsrl AT, TMP0, 53
2071  |  dsubu CARG3, CARG3, AT
2072  |  sltiu AT, CARG3, 54
2073  |  beqz AT, >1
2074  |.  dextm TMP0, TMP0, 0, 20
2075  |  dinsu TMP0, AT, 21, 21
2076  |  slt AT, CARG1, r0
2077  |  dsrlv CRET1, TMP0, CARG3
2078  |  dsubu TMP0, r0, CRET1
2079  |.if MIPSR6
2080  |  selnez TMP0, TMP0, AT
2081  |  seleqz CRET1, CRET1, AT
2082  |  or CRET1, CRET1, TMP0
2083  |.else
2084  |  movn CRET1, TMP0, AT
2085  |.endif
2086  |  jr ra
2087  |.  zextw CRET1, CRET1
2088  |1:
2089  |  jr ra
2090  |.  move CRET1, r0
2091  |
2092  |// FP number to int conversion with a check for soft-float.
2093  |// Modifies CARG1, CRET1, CRET2, TMP0, AT.
2094  |->vm_tointg:
2095  |.if JIT
2096  |  dsll CRET2, CARG1, 1
2097  |  beqz CRET2, >2
2098  |.  li TMP0, 1076
2099  |  dsrl AT, CRET2, 53
2100  |  dsubu TMP0, TMP0, AT
2101  |  sltiu AT, TMP0, 54
2102  |  beqz AT, >1
2103  |.  dextm CRET2, CRET2, 0, 20
2104  |  dinsu CRET2, AT, 21, 21
2105  |  slt AT, CARG1, r0
2106  |  dsrlv CRET1, CRET2, TMP0
2107  |  dsubu CARG1, r0, CRET1
2108  |.if MIPSR6
2109  |  seleqz CRET1, CRET1, AT
2110  |  selnez CARG1, CARG1, AT
2111  |  or CRET1, CRET1, CARG1
2112  |.else
2113  |  movn CRET1, CARG1, AT
2114  |.endif
2115  |  li CARG1, 64
2116  |  subu TMP0, CARG1, TMP0
2117  |  dsllv CRET2, CRET2, TMP0	// Integer check.
2118  |  sextw AT, CRET1
2119  |  xor AT, CRET1, AT		// Range check.
2120  |.if MIPSR6
2121  |  seleqz AT, AT, CRET2
2122  |  selnez CRET2, CRET2, CRET2
2123  |  jr ra
2124  |.  or CRET2, AT, CRET2
2125  |.else
2126  |  jr ra
2127  |.  movz CRET2, AT, CRET2
2128  |.endif
2129  |1:
2130  |  jr ra
2131  |.  li CRET2, 1
2132  |2:
2133  |  jr ra
2134  |.  move CRET1, r0
2135  |.endif
2136  |.endif
2137  |
2138  |.macro .ffunc_bit, name
2139  |  .ffunc_1 bit_..name
2140  |  gettp TMP0, CARG1
2141  |  beq TMP0, TISNUM, >6
2142  |.  zextw CRET1, CARG1
2143  |  bal ->vm_tobit_fb
2144  |.  sltiu TMP1, TMP0, LJ_TISNUM
2145  |6:
2146  |.endmacro
2147  |
2148  |.macro .ffunc_bit_op, name, bins
2149  |  .ffunc_bit name
2150  |  daddiu TMP2, BASE, 8
2151  |  daddu TMP3, BASE, NARGS8:RC
2152  |1:
2153  |  beq TMP2, TMP3, ->fff_resi
2154  |.  ld CARG1, 0(TMP2)
2155  |  gettp TMP0, CARG1
2156  |.if FPU
2157  |  bne TMP0, TISNUM, >2
2158  |.  daddiu TMP2, TMP2, 8
2159  |  zextw CARG1, CARG1
2160  |  b <1
2161  |.  bins CRET1, CRET1, CARG1
2162  |2:
2163  |   ldc1 FARG1, -8(TMP2)
2164  |  sltiu AT, TMP0, LJ_TISNUM
2165  |  beqz AT, ->fff_fallback
2166  |.  add.d FARG1, FARG1, TOBIT
2167  |  mfc1 CARG1, FARG1
2168  |  zextw CARG1, CARG1
2169  |  b <1
2170  |.  bins CRET1, CRET1, CARG1
2171  |.else
2172  |  beq TMP0, TISNUM, >2
2173  |.  move CRET2, CRET1
2174  |  bal ->vm_tobit_fb
2175  |.  sltiu TMP1, TMP0, LJ_TISNUM
2176  |  move CARG1, CRET2
2177  |2:
2178  |  zextw CARG1, CARG1
2179  |  bins CRET1, CRET1, CARG1
2180  |  b <1
2181  |.  daddiu TMP2, TMP2, 8
2182  |.endif
2183  |.endmacro
2184  |
2185  |.ffunc_bit_op band, and
2186  |.ffunc_bit_op bor, or
2187  |.ffunc_bit_op bxor, xor
2188  |
2189  |.ffunc_bit bswap
2190  |  dsrl TMP0, CRET1, 8
2191  |   dsrl TMP1, CRET1, 24
2192  |  andi TMP2, TMP0, 0xff00
2193  |   dins TMP1, CRET1, 24, 31
2194  |  dins TMP2, TMP0, 16, 23
2195  |  b ->fff_resi
2196  |.  or CRET1, TMP1, TMP2
2197  |
2198  |.ffunc_bit bnot
2199  |  not CRET1, CRET1
2200  |  b ->fff_resi
2201  |.  zextw CRET1, CRET1
2202  |
2203  |.macro .ffunc_bit_sh, name, shins, shmod
2204  |  .ffunc_2 bit_..name
2205  |  gettp TMP0, CARG1
2206  |  beq TMP0, TISNUM, >1
2207  |.  nop
2208  |  bal ->vm_tobit_fb
2209  |.  sltiu TMP1, TMP0, LJ_TISNUM
2210  |  move CARG1, CRET1
2211  |1:
2212  |  gettp TMP0, CARG2
2213  |  bne TMP0, TISNUM, ->fff_fallback
2214  |.  zextw CARG2, CARG2
2215  |  sextw CARG1, CARG1
2216  |.if shmod == 1
2217  |  negu CARG2, CARG2
2218  |.endif
2219  |  shins CRET1, CARG1, CARG2
2220  |  b ->fff_resi
2221  |.  zextw CRET1, CRET1
2222  |.endmacro
2223  |
2224  |.ffunc_bit_sh lshift, sllv, 0
2225  |.ffunc_bit_sh rshift, srlv, 0
2226  |.ffunc_bit_sh arshift, srav, 0
2227  |.ffunc_bit_sh rol, rotrv, 1
2228  |.ffunc_bit_sh ror, rotrv, 0
2229  |
2230  |.ffunc_bit tobit
2231  |->fff_resi:
2232  |  ld PC, FRAME_PC(BASE)
2233  |  daddiu RA, BASE, -16
2234  |  settp CRET1, TISNUM
2235  |  b ->fff_res1
2236  |.  sd CRET1, -16(BASE)
2237  |
2238  |//-----------------------------------------------------------------------
2239  |->fff_fallback:			// Call fast function fallback handler.
2240  |  // BASE = new base, RB = CFUNC, RC = nargs*8
2241  |  ld TMP3, CFUNC:RB->f
2242  |    daddu TMP1, BASE, NARGS8:RC
2243  |   ld PC, FRAME_PC(BASE)		// Fallback may overwrite PC.
2244  |    daddiu TMP0, TMP1, 8*LUA_MINSTACK
2245  |     ld TMP2, L->maxstack
2246  |   sd PC, SAVE_PC			// Redundant (but a defined value).
2247  |  sltu AT, TMP2, TMP0
2248  |     sd BASE, L->base
2249  |    sd TMP1, L->top
2250  |  bnez AT, >5			// Need to grow stack.
2251  |.  move CFUNCADDR, TMP3
2252  |  jalr TMP3				// (lua_State *L)
2253  |.  move CARG1, L
2254  |  // Either throws an error, or recovers and returns -1, 0 or nresults+1.
2255  |  ld BASE, L->base
2256  |   sll RD, CRET1, 3
2257  |  bgtz CRET1, ->fff_res		// Returned nresults+1?
2258  |.  daddiu RA, BASE, -16
2259  |1:  // Returned 0 or -1: retry fast path.
2260  |   ld LFUNC:RB, FRAME_FUNC(BASE)
2261  |  ld TMP0, L->top
2262  |   cleartp LFUNC:RB
2263  |  bnez CRET1, ->vm_call_tail		// Returned -1?
2264  |.  dsubu NARGS8:RC, TMP0, BASE
2265  |  ins_callt				// Returned 0: retry fast path.
2266  |
2267  |// Reconstruct previous base for vmeta_call during tailcall.
2268  |->vm_call_tail:
2269  |  andi TMP0, PC, FRAME_TYPE
2270  |   li AT, -4
2271  |  bnez TMP0, >3
2272  |.  and TMP1, PC, AT
2273  |  lbu TMP1, OFS_RA(PC)
2274  |  sll TMP1, TMP1, 3
2275  |  addiu TMP1, TMP1, 16
2276  |3:
2277  |  b ->vm_call_dispatch		// Resolve again for tailcall.
2278  |.  dsubu TMP2, BASE, TMP1
2279  |
2280  |5:  // Grow stack for fallback handler.
2281  |  load_got lj_state_growstack
2282  |  li CARG2, LUA_MINSTACK
2283  |  call_intern lj_state_growstack	// (lua_State *L, int n)
2284  |.  move CARG1, L
2285  |  ld BASE, L->base
2286  |  b <1
2287  |.  li CRET1, 0			// Force retry.
2288  |
2289  |->fff_gcstep:			// Call GC step function.
2290  |  // BASE = new base, RC = nargs*8
2291  |  move MULTRES, ra
2292  |  load_got lj_gc_step
2293  |   sd BASE, L->base
2294  |  daddu TMP0, BASE, NARGS8:RC
2295  |   sd PC, SAVE_PC			// Redundant (but a defined value).
2296  |  sd TMP0, L->top
2297  |  call_intern lj_gc_step		// (lua_State *L)
2298  |.  move CARG1, L
2299  |   ld BASE, L->base
2300  |  move ra, MULTRES
2301  |    ld TMP0, L->top
2302  |  ld CFUNC:RB, FRAME_FUNC(BASE)
2303  |  cleartp CFUNC:RB
2304  |  jr ra
2305  |.  dsubu NARGS8:RC, TMP0, BASE
2306  |
2307  |//-----------------------------------------------------------------------
2308  |//-- Special dispatch targets -------------------------------------------
2309  |//-----------------------------------------------------------------------
2310  |
2311  |->vm_record:				// Dispatch target for recording phase.
2312  |.if JIT
2313  |  lbu TMP3, DISPATCH_GL(hookmask)(DISPATCH)
2314  |  andi AT, TMP3, HOOK_VMEVENT	// No recording while in vmevent.
2315  |  bnez AT, >5
2316  |  // Decrement the hookcount for consistency, but always do the call.
2317  |.  lw TMP2, DISPATCH_GL(hookcount)(DISPATCH)
2318  |  andi AT, TMP3, HOOK_ACTIVE
2319  |  bnez AT, >1
2320  |.  addiu TMP2, TMP2, -1
2321  |  andi AT, TMP3, LUA_MASKLINE|LUA_MASKCOUNT
2322  |  beqz AT, >1
2323  |.  nop
2324  |  b >1
2325  |.  sw TMP2, DISPATCH_GL(hookcount)(DISPATCH)
2326  |.endif
2327  |
2328  |->vm_rethook:			// Dispatch target for return hooks.
2329  |  lbu TMP3, DISPATCH_GL(hookmask)(DISPATCH)
2330  |  andi AT, TMP3, HOOK_ACTIVE		// Hook already active?
2331  |  beqz AT, >1
2332  |5:  // Re-dispatch to static ins.
2333  |.  ld AT, GG_DISP2STATIC(TMP0)	// Assumes TMP0 holds DISPATCH+OP*4.
2334  |  jr AT
2335  |.  nop
2336  |
2337  |->vm_inshook:			// Dispatch target for instr/line hooks.
2338  |  lbu TMP3, DISPATCH_GL(hookmask)(DISPATCH)
2339  |  lw TMP2, DISPATCH_GL(hookcount)(DISPATCH)
2340  |  andi AT, TMP3, HOOK_ACTIVE		// Hook already active?
2341  |  bnez AT, <5
2342  |.  andi AT, TMP3, LUA_MASKLINE|LUA_MASKCOUNT
2343  |  beqz AT, <5
2344  |.  addiu TMP2, TMP2, -1
2345  |  beqz TMP2, >1
2346  |.  sw TMP2, DISPATCH_GL(hookcount)(DISPATCH)
2347  |  andi AT, TMP3, LUA_MASKLINE
2348  |  beqz AT, <5
2349  |1:
2350  |.  load_got lj_dispatch_ins
2351  |   sw MULTRES, SAVE_MULTRES
2352  |  move CARG2, PC
2353  |   sd BASE, L->base
2354  |  // SAVE_PC must hold the _previous_ PC. The callee updates it with PC.
2355  |  call_intern lj_dispatch_ins	// (lua_State *L, const BCIns *pc)
2356  |.  move CARG1, L
2357  |3:
2358  |  ld BASE, L->base
2359  |4:  // Re-dispatch to static ins.
2360  |  lw INS, -4(PC)
2361  |  decode_OP8a TMP1, INS
2362  |  decode_OP8b TMP1
2363  |  daddu TMP0, DISPATCH, TMP1
2364  |   decode_RD8a RD, INS
2365  |  ld AT, GG_DISP2STATIC(TMP0)
2366  |   decode_RA8a RA, INS
2367  |   decode_RD8b RD
2368  |  jr AT
2369  |   decode_RA8b RA
2370  |
2371  |->cont_hook:				// Continue from hook yield.
2372  |  daddiu PC, PC, 4
2373  |  b <4
2374  |.  lw MULTRES, -24+LO(RB)		// Restore MULTRES for *M ins.
2375  |
2376  |->vm_hotloop:			// Hot loop counter underflow.
2377  |.if JIT
2378  |  ld LFUNC:TMP1, FRAME_FUNC(BASE)
2379  |   daddiu CARG1, DISPATCH, GG_DISP2J
2380  |  cleartp LFUNC:TMP1
2381  |   sd PC, SAVE_PC
2382  |  ld TMP1, LFUNC:TMP1->pc
2383  |   move CARG2, PC
2384  |   sd L, DISPATCH_J(L)(DISPATCH)
2385  |  lbu TMP1, PC2PROTO(framesize)(TMP1)
2386  |  load_got lj_trace_hot
2387  |   sd BASE, L->base
2388  |  dsll TMP1, TMP1, 3
2389  |  daddu TMP1, BASE, TMP1
2390  |  call_intern lj_trace_hot		// (jit_State *J, const BCIns *pc)
2391  |.  sd TMP1, L->top
2392  |  b <3
2393  |.  nop
2394  |.endif
2395  |
2396  |
2397  |->vm_callhook:			// Dispatch target for call hooks.
2398  |.if JIT
2399  |  b >1
2400  |.endif
2401  |.  move CARG2, PC
2402  |
2403  |->vm_hotcall:			// Hot call counter underflow.
2404  |.if JIT
2405  |  ori CARG2, PC, 1
2406  |1:
2407  |.endif
2408  |  load_got lj_dispatch_call
2409  |  daddu TMP0, BASE, RC
2410  |   sd PC, SAVE_PC
2411  |   sd BASE, L->base
2412  |  dsubu RA, RA, BASE
2413  |   sd TMP0, L->top
2414  |  call_intern lj_dispatch_call	// (lua_State *L, const BCIns *pc)
2415  |.  move CARG1, L
2416  |  // Returns ASMFunction.
2417  |  ld BASE, L->base
2418  |   ld TMP0, L->top
2419  |   sd r0, SAVE_PC			// Invalidate for subsequent line hook.
2420  |  dsubu NARGS8:RC, TMP0, BASE
2421  |  daddu RA, BASE, RA
2422  |  ld LFUNC:RB, FRAME_FUNC(BASE)
2423  |  cleartp LFUNC:RB
2424  |  jr CRET1
2425  |.  lw INS, -4(PC)
2426  |
2427  |->cont_stitch:			// Trace stitching.
2428  |.if JIT
2429  |  // RA = resultptr, RB = meta base
2430  |  lw INS, -4(PC)
2431  |    ld TRACE:TMP2, -40(RB)		// Save previous trace.
2432  |  decode_RA8a RC, INS
2433  |   daddiu AT, MULTRES, -8
2434  |    cleartp TRACE:TMP2
2435  |  decode_RA8b RC
2436  |   beqz AT, >2
2437  |. daddu RC, BASE, RC			// Call base.
2438  |1:  // Move results down.
2439  |  ld CARG1, 0(RA)
2440  |   daddiu AT, AT, -8
2441  |    daddiu RA, RA, 8
2442  |  sd CARG1, 0(RC)
2443  |   bnez AT, <1
2444  |.   daddiu RC, RC, 8
2445  |2:
2446  |   decode_RA8a RA, INS
2447  |    decode_RB8a RB, INS
2448  |   decode_RA8b RA
2449  |    decode_RB8b RB
2450  |   daddu RA, RA, RB
2451  |   daddu RA, BASE, RA
2452  |3:
2453  |   sltu AT, RC, RA
2454  |   bnez AT, >9			// More results wanted?
2455  |.   nop
2456  |
2457  |  lhu TMP3, TRACE:TMP2->traceno
2458  |  lhu RD, TRACE:TMP2->link
2459  |  beq RD, TMP3, ->cont_nop		// Blacklisted.
2460  |.  load_got lj_dispatch_stitch
2461  |  bnez RD, =>BC_JLOOP		// Jump to stitched trace.
2462  |.  sll RD, RD, 3
2463  |
2464  |  // Stitch a new trace to the previous trace.
2465  |  sw TMP3, DISPATCH_J(exitno)(DISPATCH)
2466  |  sd L, DISPATCH_J(L)(DISPATCH)
2467  |  sd BASE, L->base
2468  |  daddiu CARG1, DISPATCH, GG_DISP2J
2469  |  call_intern lj_dispatch_stitch	// (jit_State *J, const BCIns *pc)
2470  |.  move CARG2, PC
2471  |  b ->cont_nop
2472  |.  ld BASE, L->base
2473  |
2474  |9:
2475  |  sd TISNIL, 0(RC)
2476  |  b <3
2477  |.  daddiu RC, RC, 8
2478  |.endif
2479  |
2480  |->vm_profhook:			// Dispatch target for profiler hook.
2481#if LJ_HASPROFILE
2482  |  load_got lj_dispatch_profile
2483  |   sw MULTRES, SAVE_MULTRES
2484  |  move CARG2, PC
2485  |   sd BASE, L->base
2486  |  call_intern lj_dispatch_profile	// (lua_State *L, const BCIns *pc)
2487  |.  move CARG1, L
2488  |  // HOOK_PROFILE is off again, so re-dispatch to dynamic instruction.
2489  |  daddiu PC, PC, -4
2490  |  b ->cont_nop
2491  |.  ld BASE, L->base
2492#endif
2493  |
2494  |//-----------------------------------------------------------------------
2495  |//-- Trace exit handler -------------------------------------------------
2496  |//-----------------------------------------------------------------------
2497  |
2498  |.macro savex_, a, b
2499  |.if FPU
2500  |  sdc1 f..a, a*8(sp)
2501  |  sdc1 f..b, b*8(sp)
2502  |  sd r..a, 32*8+a*8(sp)
2503  |  sd r..b, 32*8+b*8(sp)
2504  |.else
2505  |  sd r..a, a*8(sp)
2506  |  sd r..b, b*8(sp)
2507  |.endif
2508  |.endmacro
2509  |
2510  |->vm_exit_handler:
2511  |.if JIT
2512  |.if FPU
2513  |  daddiu sp, sp, -(32*8+32*8)
2514  |.else
2515  |  daddiu sp, sp, -(32*8)
2516  |.endif
2517  |  savex_ 0, 1
2518  |  savex_ 2, 3
2519  |  savex_ 4, 5
2520  |  savex_ 6, 7
2521  |  savex_ 8, 9
2522  |  savex_ 10, 11
2523  |  savex_ 12, 13
2524  |  savex_ 14, 15
2525  |  savex_ 16, 17
2526  |  savex_ 18, 19
2527  |  savex_ 20, 21
2528  |  savex_ 22, 23
2529  |  savex_ 24, 25
2530  |  savex_ 26, 27
2531  |  savex_ 28, 30
2532  |.if FPU
2533  |  sdc1 f29, 29*8(sp)
2534  |  sdc1 f31, 31*8(sp)
2535  |  sd r0, 32*8+31*8(sp)		// Clear RID_TMP.
2536  |  daddiu TMP2, sp, 32*8+32*8		// Recompute original value of sp.
2537  |  sd TMP2, 32*8+29*8(sp)		// Store sp in RID_SP
2538  |.else
2539  |  sd r0, 31*8(sp)			// Clear RID_TMP.
2540  |  daddiu TMP2, sp, 32*8		// Recompute original value of sp.
2541  |  sd TMP2, 29*8(sp)			// Store sp in RID_SP
2542  |.endif
2543  |  li_vmstate EXIT
2544  |  daddiu DISPATCH, JGL, -GG_DISP2G-32768
2545  |  lw TMP1, 0(TMP2)			// Load exit number.
2546  |  st_vmstate
2547  |  ld L, DISPATCH_GL(cur_L)(DISPATCH)
2548  |   ld BASE, DISPATCH_GL(jit_base)(DISPATCH)
2549  |  load_got lj_trace_exit
2550  |  sd L, DISPATCH_J(L)(DISPATCH)
2551  |  sw ra, DISPATCH_J(parent)(DISPATCH)  // Store trace number.
2552  |   sd BASE, L->base
2553  |  sw TMP1, DISPATCH_J(exitno)(DISPATCH)  // Store exit number.
2554  |  daddiu CARG1, DISPATCH, GG_DISP2J
2555  |   sd r0, DISPATCH_GL(jit_base)(DISPATCH)
2556  |  call_intern lj_trace_exit		// (jit_State *J, ExitState *ex)
2557  |.  move CARG2, sp
2558  |  // Returns MULTRES (unscaled) or negated error code.
2559  |  ld TMP1, L->cframe
2560  |  li AT, -4
2561  |   ld BASE, L->base
2562  |  and sp, TMP1, AT
2563  |   ld PC, SAVE_PC			// Get SAVE_PC.
2564  |  b >1
2565  |.  sd L, SAVE_L			// Set SAVE_L (on-trace resume/yield).
2566  |.endif
2567  |->vm_exit_interp:
2568  |.if JIT
2569  |  // CRET1 = MULTRES or negated error code, BASE, PC and JGL set.
2570  |  ld L, SAVE_L
2571  |   daddiu DISPATCH, JGL, -GG_DISP2G-32768
2572  |  sd BASE, L->base
2573  |1:
2574  |  bltz CRET1, >9			// Check for error from exit.
2575  |.  ld LFUNC:RB, FRAME_FUNC(BASE)
2576  |    .FPU lui TMP3, 0x59c0		// TOBIT = 2^52 + 2^51 (float).
2577  |  dsll MULTRES, CRET1, 3
2578  |  cleartp LFUNC:RB
2579  |  sw MULTRES, SAVE_MULTRES
2580  |    li TISNIL, LJ_TNIL
2581  |     li TISNUM, LJ_TISNUM		// Setup type comparison constants.
2582  |    .FPU mtc1 TMP3, TOBIT
2583  |  ld TMP1, LFUNC:RB->pc
2584  |   sd r0, DISPATCH_GL(jit_base)(DISPATCH)
2585  |  ld KBASE, PC2PROTO(k)(TMP1)
2586  |    .FPU cvt.d.s TOBIT, TOBIT
2587  |  // Modified copy of ins_next which handles function header dispatch, too.
2588  |  lw INS, 0(PC)
2589  |   daddiu PC, PC, 4
2590  |    // Assumes TISNIL == ~LJ_VMST_INTERP == -1
2591  |    sw TISNIL, DISPATCH_GL(vmstate)(DISPATCH)
2592  |  decode_OP8a TMP1, INS
2593  |  decode_OP8b TMP1
2594  |    sltiu TMP2, TMP1, BC_FUNCF*8
2595  |  daddu TMP0, DISPATCH, TMP1
2596  |   decode_RD8a RD, INS
2597  |  ld AT, 0(TMP0)
2598  |   decode_RA8a RA, INS
2599  |    beqz TMP2, >2
2600  |.  decode_RA8b RA
2601  |  jr AT
2602  |.  decode_RD8b RD
2603  |2:
2604  |  sltiu TMP2, TMP1, (BC_FUNCC+2)*8	// Fast function?
2605  |  bnez TMP2, >3
2606  |.  ld TMP1, FRAME_PC(BASE)
2607  |  // Check frame below fast function.
2608  |  andi TMP0, TMP1, FRAME_TYPE
2609  |  bnez TMP0, >3			// Trace stitching continuation?
2610  |.  nop
2611  |  // Otherwise set KBASE for Lua function below fast function.
2612  |  lw TMP2, -4(TMP1)
2613  |  decode_RA8a TMP0, TMP2
2614  |  decode_RA8b TMP0
2615  |  dsubu TMP1, BASE, TMP0
2616  |  ld LFUNC:TMP2, -32(TMP1)
2617  |  cleartp LFUNC:TMP2
2618  |  ld TMP1, LFUNC:TMP2->pc
2619  |  ld KBASE, PC2PROTO(k)(TMP1)
2620  |3:
2621  |  daddiu RC, MULTRES, -8
2622  |  jr AT
2623  |.  daddu RA, RA, BASE
2624  |
2625  |9:  // Rethrow error from the right C frame.
2626  |  load_got lj_err_trace
2627  |  sub CARG2, r0, CRET1
2628  |  call_intern lj_err_trace		// (lua_State *L, int errcode)
2629  |.  move CARG1, L
2630  |.endif
2631  |
2632  |//-----------------------------------------------------------------------
2633  |//-- Math helper functions ----------------------------------------------
2634  |//-----------------------------------------------------------------------
2635  |
2636  |// Hard-float round to integer.
2637  |// Modifies AT, TMP0, FRET1, FRET2, f4. Keeps all others incl. FARG1.
2638  |// MIPSR6: Modifies FTMP1, too.
2639  |.macro vm_round_hf, func
2640  |  lui TMP0, 0x4330			// Hiword of 2^52 (double).
2641  |  dsll TMP0, TMP0, 32
2642  |  dmtc1 TMP0, f4
2643  |  abs.d FRET2, FARG1			// |x|
2644  |    dmfc1 AT, FARG1
2645  |.if MIPSR6
2646  |  cmp.lt.d FTMP1, FRET2, f4
2647  |   add.d FRET1, FRET2, f4		// (|x| + 2^52) - 2^52
2648  |  bc1eqz FTMP1, >1			// Truncate only if |x| < 2^52.
2649  |.else
2650  |  c.olt.d 0, FRET2, f4
2651  |   add.d FRET1, FRET2, f4		// (|x| + 2^52) - 2^52
2652  |  bc1f 0, >1				// Truncate only if |x| < 2^52.
2653  |.endif
2654  |.  sub.d FRET1, FRET1, f4
2655  |    slt AT, AT, r0
2656  |.if "func" == "ceil"
2657  |   lui TMP0, 0xbff0			// Hiword of -1 (double). Preserves -0.
2658  |.else
2659  |   lui TMP0, 0x3ff0			// Hiword of +1 (double).
2660  |.endif
2661  |.if "func" == "trunc"
2662  |   dsll TMP0, TMP0, 32
2663  |   dmtc1 TMP0, f4
2664  |.if MIPSR6
2665  |  cmp.lt.d FTMP1, FRET2, FRET1	// |x| < result?
2666  |   sub.d FRET2, FRET1, f4
2667  |  sel.d  FTMP1, FRET1, FRET2		// If yes, subtract +1.
2668  |  dmtc1 AT, FRET1
2669  |  neg.d FRET2, FTMP1
2670  |  jr ra
2671  |.  sel.d FRET1, FTMP1, FRET2		// Merge sign bit back in.
2672  |.else
2673  |  c.olt.d 0, FRET2, FRET1		// |x| < result?
2674  |   sub.d FRET2, FRET1, f4
2675  |  movt.d FRET1, FRET2, 0		// If yes, subtract +1.
2676  |  neg.d FRET2, FRET1
2677  |  jr ra
2678  |.  movn.d FRET1, FRET2, AT		// Merge sign bit back in.
2679  |.endif
2680  |.else
2681  |  neg.d FRET2, FRET1
2682  |   dsll TMP0, TMP0, 32
2683  |   dmtc1 TMP0, f4
2684  |.if MIPSR6
2685  |  dmtc1 AT, FTMP1
2686  |  sel.d FTMP1, FRET1, FRET2
2687  |.if "func" == "ceil"
2688  |  cmp.lt.d FRET1, FTMP1, FARG1	// x > result?
2689  |.else
2690  |  cmp.lt.d FRET1, FARG1, FTMP1	// x < result?
2691  |.endif
2692  |   sub.d FRET2, FTMP1, f4		// If yes, subtract +-1.
2693  |  jr ra
2694  |.  sel.d FRET1, FTMP1, FRET2
2695  |.else
2696  |  movn.d FRET1, FRET2, AT		// Merge sign bit back in.
2697  |.if "func" == "ceil"
2698  |  c.olt.d 0, FRET1, FARG1		// x > result?
2699  |.else
2700  |  c.olt.d 0, FARG1, FRET1		// x < result?
2701  |.endif
2702  |   sub.d FRET2, FRET1, f4		// If yes, subtract +-1.
2703  |  jr ra
2704  |.  movt.d FRET1, FRET2, 0
2705  |.endif
2706  |.endif
2707  |1:
2708  |  jr ra
2709  |.  mov.d FRET1, FARG1
2710  |.endmacro
2711  |
2712  |.macro vm_round, func
2713  |.if FPU
2714  |  vm_round_hf, func
2715  |.endif
2716  |.endmacro
2717  |
2718  |->vm_floor:
2719  |  vm_round floor
2720  |->vm_ceil:
2721  |  vm_round ceil
2722  |->vm_trunc:
2723  |.if JIT
2724  |  vm_round trunc
2725  |.endif
2726  |
2727  |// Soft-float integer to number conversion.
2728  |.macro sfi2d, ARG
2729  |.if not FPU
2730  |  beqz ARG, >9			// Handle zero first.
2731  |.  sra TMP0, ARG, 31
2732  |  xor TMP1, ARG, TMP0
2733  |  dsubu TMP1, TMP1, TMP0		// Absolute value in TMP1.
2734  |  dclz ARG, TMP1
2735  |  addiu ARG, ARG, -11
2736  |  li AT, 0x3ff+63-11-1
2737  |   dsllv TMP1, TMP1, ARG		// Align mantissa left with leading 1.
2738  |  subu ARG, AT, ARG			// Exponent - 1.
2739  |  ins ARG, TMP0, 11, 11		// Sign | Exponent.
2740  |  dsll ARG, ARG, 52			// Align left.
2741  |  jr ra
2742  |.  daddu ARG, ARG, TMP1		// Add mantissa, increment exponent.
2743  |9:
2744  |  jr ra
2745  |.  nop
2746  |.endif
2747  |.endmacro
2748  |
2749  |// Input CARG1. Output: CARG1. Temporaries: AT, TMP0, TMP1.
2750  |->vm_sfi2d_1:
2751  |  sfi2d CARG1
2752  |
2753  |// Input CARG2. Output: CARG2. Temporaries: AT, TMP0, TMP1.
2754  |->vm_sfi2d_2:
2755  |  sfi2d CARG2
2756  |
2757  |// Soft-float comparison. Equivalent to c.eq.d.
2758  |// Input: CARG*. Output: CRET1. Temporaries: AT, TMP0, TMP1.
2759  |->vm_sfcmpeq:
2760  |.if not FPU
2761  |  dsll AT, CARG1, 1
2762  |  dsll TMP0, CARG2, 1
2763  |  or TMP1, AT, TMP0
2764  |  beqz TMP1, >8			// Both args +-0: return 1.
2765  |.  lui TMP1, 0xffe0
2766  |  dsll TMP1, TMP1, 32
2767  |   sltu AT, TMP1, AT
2768  |   sltu TMP0, TMP1, TMP0
2769  |  or TMP1, AT, TMP0
2770  |  bnez TMP1, >9			// Either arg is NaN: return 0;
2771  |.  xor AT, CARG1, CARG2
2772  |  jr ra
2773  |.  sltiu CRET1, AT, 1		// Same values: return 1.
2774  |8:
2775  |  jr ra
2776  |.  li CRET1, 1
2777  |9:
2778  |  jr ra
2779  |.  li CRET1, 0
2780  |.endif
2781  |
2782  |// Soft-float comparison. Equivalent to c.ult.d and c.olt.d.
2783  |// Input: CARG1, CARG2. Output: CRET1. Temporaries: AT, TMP0, TMP1, CRET2.
2784  |->vm_sfcmpult:
2785  |.if not FPU
2786  |  b >1
2787  |.  li CRET2, 1
2788  |.endif
2789  |
2790  |->vm_sfcmpolt:
2791  |.if not FPU
2792  |  li CRET2, 0
2793  |1:
2794  |  dsll AT, CARG1, 1
2795  |  dsll TMP0, CARG2, 1
2796  |  or TMP1, AT, TMP0
2797  |  beqz TMP1, >8			// Both args +-0: return 0.
2798  |.  lui TMP1, 0xffe0
2799  |  dsll TMP1, TMP1, 32
2800  |   sltu AT, TMP1, AT
2801  |   sltu TMP0, TMP1, TMP0
2802  |  or TMP1, AT, TMP0
2803  |  bnez TMP1, >9			// Either arg is NaN: return 0 or 1;
2804  |.  and AT, CARG1, CARG2
2805  |  bltz AT, >5			// Both args negative?
2806  |.  nop
2807  |  jr ra
2808  |.  slt CRET1, CARG1, CARG2
2809  |5:  // Swap conditions if both operands are negative.
2810  |  jr ra
2811  |.  slt CRET1, CARG2, CARG1
2812  |8:
2813  |  jr ra
2814  |.  li CRET1, 0
2815  |9:
2816  |  jr ra
2817  |.  move CRET1, CRET2
2818  |.endif
2819  |
2820  |->vm_sfcmpogt:
2821  |.if not FPU
2822  |  dsll AT, CARG2, 1
2823  |  dsll TMP0, CARG1, 1
2824  |  or TMP1, AT, TMP0
2825  |  beqz TMP1, >8			// Both args +-0: return 0.
2826  |.  lui TMP1, 0xffe0
2827  |  dsll TMP1, TMP1, 32
2828  |   sltu AT, TMP1, AT
2829  |   sltu TMP0, TMP1, TMP0
2830  |  or TMP1, AT, TMP0
2831  |  bnez TMP1, >9			// Either arg is NaN: return 0 or 1;
2832  |.  and AT, CARG2, CARG1
2833  |  bltz AT, >5			// Both args negative?
2834  |.  nop
2835  |  jr ra
2836  |.  slt CRET1, CARG2, CARG1
2837  |5:  // Swap conditions if both operands are negative.
2838  |  jr ra
2839  |.  slt CRET1, CARG1, CARG2
2840  |8:
2841  |  jr ra
2842  |.  li CRET1, 0
2843  |9:
2844  |  jr ra
2845  |.  li CRET1, 0
2846  |.endif
2847  |
2848  |// Soft-float comparison. Equivalent to c.ole.d a, b or c.ole.d b, a.
2849  |// Input: CARG1, CARG2, TMP3. Output: CRET1. Temporaries: AT, TMP0, TMP1.
2850  |->vm_sfcmpolex:
2851  |.if not FPU
2852  |  dsll AT, CARG1, 1
2853  |  dsll TMP0, CARG2, 1
2854  |  or TMP1, AT, TMP0
2855  |  beqz TMP1, >8			// Both args +-0: return 1.
2856  |.  lui TMP1, 0xffe0
2857  |  dsll TMP1, TMP1, 32
2858  |   sltu AT, TMP1, AT
2859  |   sltu TMP0, TMP1, TMP0
2860  |  or TMP1, AT, TMP0
2861  |  bnez TMP1, >9			// Either arg is NaN: return 0;
2862  |.  and AT, CARG1, CARG2
2863  |  xor AT, AT, TMP3
2864  |  bltz AT, >5			// Both args negative?
2865  |.  nop
2866  |  jr ra
2867  |.  slt CRET1, CARG2, CARG1
2868  |5:  // Swap conditions if both operands are negative.
2869  |  jr ra
2870  |.  slt CRET1, CARG1, CARG2
2871  |8:
2872  |  jr ra
2873  |.  li CRET1, 1
2874  |9:
2875  |  jr ra
2876  |.  li CRET1, 0
2877  |.endif
2878  |
2879  |.macro sfmin_max, name, fpcall
2880  |->vm_sf .. name:
2881  |.if JIT and not FPU
2882  |  move TMP2, ra
2883  |  bal ->fpcall
2884  |.  nop
2885  |  move ra, TMP2
2886  |  move TMP0, CRET1
2887  |  move CRET1, CARG1
2888  |.if MIPSR6
2889  |  selnez CRET1, CRET1, TMP0
2890  |  seleqz TMP0, CARG2, TMP0
2891  |  jr ra
2892  |.  or CRET1, CRET1, TMP0
2893  |.else
2894  |  jr ra
2895  |.  movz CRET1, CARG2, TMP0
2896  |.endif
2897  |.endif
2898  |.endmacro
2899  |
2900  |  sfmin_max min, vm_sfcmpolt
2901  |  sfmin_max max, vm_sfcmpogt
2902  |
2903  |//-----------------------------------------------------------------------
2904  |//-- Miscellaneous functions --------------------------------------------
2905  |//-----------------------------------------------------------------------
2906  |
2907  |.define NEXT_TAB,		TAB:CARG1
2908  |.define NEXT_IDX,		CARG2
2909  |.define NEXT_ASIZE,		CARG3
2910  |.define NEXT_NIL,		CARG4
2911  |.define NEXT_TMP0,		r12
2912  |.define NEXT_TMP1,		r13
2913  |.define NEXT_TMP2,		r14
2914  |.define NEXT_RES_VK,		CRET1
2915  |.define NEXT_RES_IDX,	CRET2
2916  |.define NEXT_RES_PTR,	sp
2917  |.define NEXT_RES_VAL,	0(sp)
2918  |.define NEXT_RES_KEY,	8(sp)
2919  |
2920  |// TValue *lj_vm_next(GCtab *t, uint32_t idx)
2921  |// Next idx returned in CRET2.
2922  |->vm_next:
2923  |.if JIT and ENDIAN_LE
2924  |   lw NEXT_ASIZE, NEXT_TAB->asize
2925  |  ld NEXT_TMP0, NEXT_TAB->array
2926  |    li NEXT_NIL, LJ_TNIL
2927  |1:  // Traverse array part.
2928  |   sltu AT, NEXT_IDX, NEXT_ASIZE
2929  |    sll NEXT_TMP1, NEXT_IDX, 3
2930  |   beqz AT, >5
2931  |.   daddu NEXT_TMP1, NEXT_TMP0, NEXT_TMP1
2932  |   li AT, LJ_TISNUM
2933  |  ld NEXT_TMP2, 0(NEXT_TMP1)
2934  |   dsll AT, AT, 47
2935  |   or NEXT_TMP1, NEXT_IDX, AT
2936  |  beq NEXT_TMP2, NEXT_NIL, <1
2937  |.  addiu NEXT_IDX, NEXT_IDX, 1
2938  |  sd NEXT_TMP2, NEXT_RES_VAL
2939  |   sd NEXT_TMP1, NEXT_RES_KEY
2940  |  move NEXT_RES_VK, NEXT_RES_PTR
2941  |  jr ra
2942  |.  move NEXT_RES_IDX, NEXT_IDX
2943  |
2944  |5:  // Traverse hash part.
2945  |  subu NEXT_RES_IDX, NEXT_IDX, NEXT_ASIZE
2946  |   ld NODE:NEXT_RES_VK, NEXT_TAB->node
2947  |    sll NEXT_TMP2, NEXT_RES_IDX, 5
2948  |  lw NEXT_TMP0, NEXT_TAB->hmask
2949  |    sll AT, NEXT_RES_IDX, 3
2950  |    subu AT, NEXT_TMP2, AT
2951  |   daddu NODE:NEXT_RES_VK, NODE:NEXT_RES_VK, AT
2952  |6:
2953  |  sltu AT, NEXT_TMP0, NEXT_RES_IDX
2954  |  bnez AT, >8
2955  |.  nop
2956  |  ld NEXT_TMP2, NODE:NEXT_RES_VK->val
2957  |  bne NEXT_TMP2, NEXT_NIL, >9
2958  |.  addiu NEXT_RES_IDX, NEXT_RES_IDX, 1
2959  |  // Skip holes in hash part.
2960  |  b <6
2961  |.  daddiu NODE:NEXT_RES_VK, NODE:NEXT_RES_VK, sizeof(Node)
2962  |
2963  |8:  // End of iteration. Set the key to nil (not the value).
2964  |  sd NEXT_NIL, NEXT_RES_KEY
2965  |  move NEXT_RES_VK, NEXT_RES_PTR
2966  |9:
2967  |  jr ra
2968  |.  addu NEXT_RES_IDX, NEXT_RES_IDX, NEXT_ASIZE
2969  |.endif
2970  |
2971  |//-----------------------------------------------------------------------
2972  |//-- FFI helper functions -----------------------------------------------
2973  |//-----------------------------------------------------------------------
2974  |
2975  |// Handler for callback functions. Callback slot number in r1, g in r2.
2976  |->vm_ffi_callback:
2977  |.if FFI
2978  |.type CTSTATE, CTState, PC
2979  |  saveregs
2980  |  ld CTSTATE, GL:r2->ctype_state
2981  |   daddiu DISPATCH, r2, GG_G2DISP
2982  |  load_got lj_ccallback_enter
2983  |  sw r1, CTSTATE->cb.slot
2984  |  sd CARG1, CTSTATE->cb.gpr[0]
2985  |  .FPU sdc1 FARG1, CTSTATE->cb.fpr[0]
2986  |  sd CARG2, CTSTATE->cb.gpr[1]
2987  |  .FPU sdc1 FARG2, CTSTATE->cb.fpr[1]
2988  |  sd CARG3, CTSTATE->cb.gpr[2]
2989  |  .FPU sdc1 FARG3, CTSTATE->cb.fpr[2]
2990  |  sd CARG4, CTSTATE->cb.gpr[3]
2991  |  .FPU sdc1 FARG4, CTSTATE->cb.fpr[3]
2992  |  sd CARG5, CTSTATE->cb.gpr[4]
2993  |  .FPU sdc1 FARG5, CTSTATE->cb.fpr[4]
2994  |  sd CARG6, CTSTATE->cb.gpr[5]
2995  |  .FPU sdc1 FARG6, CTSTATE->cb.fpr[5]
2996  |  sd CARG7, CTSTATE->cb.gpr[6]
2997  |  .FPU sdc1 FARG7, CTSTATE->cb.fpr[6]
2998  |  sd CARG8, CTSTATE->cb.gpr[7]
2999  |  .FPU sdc1 FARG8, CTSTATE->cb.fpr[7]
3000  |  daddiu TMP0, sp, CFRAME_SPACE
3001  |  sd TMP0, CTSTATE->cb.stack
3002  |  sd r0, SAVE_PC			// Any value outside of bytecode is ok.
3003  |   move CARG2, sp
3004  |  call_intern lj_ccallback_enter	// (CTState *cts, void *cf)
3005  |.  move CARG1, CTSTATE
3006  |  // Returns lua_State *.
3007  |  ld BASE, L:CRET1->base
3008  |  ld RC, L:CRET1->top
3009  |   move L, CRET1
3010  |     .FPU lui TMP3, 0x59c0		// TOBIT = 2^52 + 2^51 (float).
3011  |  ld LFUNC:RB, FRAME_FUNC(BASE)
3012  |     .FPU mtc1 TMP3, TOBIT
3013  |      li TISNIL, LJ_TNIL
3014  |       li TISNUM, LJ_TISNUM
3015  |    li_vmstate INTERP
3016  |  subu RC, RC, BASE
3017  |   cleartp LFUNC:RB
3018  |    st_vmstate
3019  |     .FPU cvt.d.s TOBIT, TOBIT
3020  |  ins_callt
3021  |.endif
3022  |
3023  |->cont_ffi_callback:			// Return from FFI callback.
3024  |.if FFI
3025  |  load_got lj_ccallback_leave
3026  |  ld CTSTATE, DISPATCH_GL(ctype_state)(DISPATCH)
3027  |   sd BASE, L->base
3028  |   sd RB, L->top
3029  |  sd L, CTSTATE->L
3030  |  move CARG2, RA
3031  |  call_intern lj_ccallback_leave	// (CTState *cts, TValue *o)
3032  |.  move CARG1, CTSTATE
3033  |  .FPU ldc1 FRET1, CTSTATE->cb.fpr[0]
3034  |  ld CRET1, CTSTATE->cb.gpr[0]
3035  |  .FPU ldc1 FRET2, CTSTATE->cb.fpr[1]
3036  |  b ->vm_leave_unw
3037  |.  ld CRET2, CTSTATE->cb.gpr[1]
3038  |.endif
3039  |
3040  |->vm_ffi_call:			// Call C function via FFI.
3041  |  // Caveat: needs special frame unwinding, see below.
3042  |.if FFI
3043  |  .type CCSTATE, CCallState, CARG1
3044  |  lw TMP1, CCSTATE->spadj
3045  |   lbu CARG2, CCSTATE->nsp
3046  |  move TMP2, sp
3047  |  dsubu sp, sp, TMP1
3048  |  sd ra, -8(TMP2)
3049  |   sll CARG2, CARG2, 3
3050  |  sd r16, -16(TMP2)
3051  |  sd CCSTATE, -24(TMP2)
3052  |  move r16, TMP2
3053  |  daddiu TMP1, CCSTATE, offsetof(CCallState, stack)
3054  |  move TMP2, sp
3055  |  beqz CARG2, >2
3056  |.  daddu TMP3, TMP1, CARG2
3057  |1:
3058  |   ld TMP0, 0(TMP1)
3059  |  daddiu TMP1, TMP1, 8
3060  |  sltu AT, TMP1, TMP3
3061  |   sd TMP0, 0(TMP2)
3062  |  bnez AT, <1
3063  |.  daddiu TMP2, TMP2, 8
3064  |2:
3065  |  ld CFUNCADDR, CCSTATE->func
3066  |  .FPU ldc1 FARG1, CCSTATE->gpr[0]
3067  |  ld CARG2, CCSTATE->gpr[1]
3068  |  .FPU ldc1 FARG2, CCSTATE->gpr[1]
3069  |  ld CARG3, CCSTATE->gpr[2]
3070  |  .FPU ldc1 FARG3, CCSTATE->gpr[2]
3071  |  ld CARG4, CCSTATE->gpr[3]
3072  |  .FPU ldc1 FARG4, CCSTATE->gpr[3]
3073  |  ld CARG5, CCSTATE->gpr[4]
3074  |  .FPU ldc1 FARG5, CCSTATE->gpr[4]
3075  |  ld CARG6, CCSTATE->gpr[5]
3076  |  .FPU ldc1 FARG6, CCSTATE->gpr[5]
3077  |  ld CARG7, CCSTATE->gpr[6]
3078  |  .FPU ldc1 FARG7, CCSTATE->gpr[6]
3079  |  ld CARG8, CCSTATE->gpr[7]
3080  |  .FPU ldc1 FARG8, CCSTATE->gpr[7]
3081  |  jalr CFUNCADDR
3082  |.  ld CARG1, CCSTATE->gpr[0]		// Do this last, since CCSTATE is CARG1.
3083  |  ld CCSTATE:TMP1, -24(r16)
3084  |  ld TMP2, -16(r16)
3085  |  ld ra, -8(r16)
3086  |  sd CRET1, CCSTATE:TMP1->gpr[0]
3087  |  sd CRET2, CCSTATE:TMP1->gpr[1]
3088  |.if FPU
3089  |  sdc1 FRET1, CCSTATE:TMP1->fpr[0]
3090  |  sdc1 FRET2, CCSTATE:TMP1->fpr[1]
3091  |.else
3092  |  sd CARG1, CCSTATE:TMP1->gpr[2]	// 2nd FP struct field for soft-float.
3093  |.endif
3094  |  move sp, r16
3095  |  jr ra
3096  |.  move r16, TMP2
3097  |.endif
3098  |// Note: vm_ffi_call must be the last function in this object file!
3099  |
3100  |//-----------------------------------------------------------------------
3101}
3102
3103/* Generate the code for a single instruction. */
3104static void build_ins(BuildCtx *ctx, BCOp op, int defop)
3105{
3106  int vk = 0;
3107  |=>defop:
3108
3109  switch (op) {
3110
3111  /* -- Comparison ops ---------------------------------------------------- */
3112
3113  /* Remember: all ops branch for a true comparison, fall through otherwise. */
3114
3115  case BC_ISLT: case BC_ISGE: case BC_ISLE: case BC_ISGT:
3116    |  // RA = src1*8, RD = src2*8, JMP with RD = target
3117    |.macro bc_comp, FRA, FRD, ARGRA, ARGRD, movop, fmovop, fcomp, sfcomp
3118    |  daddu RA, BASE, RA
3119    |   daddu RD, BASE, RD
3120    |  ld ARGRA, 0(RA)
3121    |   ld ARGRD, 0(RD)
3122    |    lhu TMP2, OFS_RD(PC)
3123    |  gettp CARG3, ARGRA
3124    |   gettp CARG4, ARGRD
3125    |  bne CARG3, TISNUM, >2
3126    |.   daddiu PC, PC, 4
3127    |  bne CARG4, TISNUM, >5
3128    |.   decode_RD4b TMP2
3129    |  sextw ARGRA, ARGRA
3130    |   sextw ARGRD, ARGRD
3131    |    lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3132    |  slt AT, CARG1, CARG2
3133    |    addu TMP2, TMP2, TMP3
3134    |.if MIPSR6
3135    |  movop TMP2, TMP2, AT
3136    |.else
3137    |  movop TMP2, r0, AT
3138    |.endif
3139    |1:
3140    |  daddu PC, PC, TMP2
3141    |  ins_next
3142    |
3143    |2:  // RA is not an integer.
3144    |  sltiu AT, CARG3, LJ_TISNUM
3145    |  beqz AT, ->vmeta_comp
3146    |.   lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3147    |  sltiu AT, CARG4, LJ_TISNUM
3148    |  beqz AT, >4
3149    |.   decode_RD4b TMP2
3150    |.if FPU
3151    |  ldc1 FRA, 0(RA)
3152    |   ldc1 FRD, 0(RD)
3153    |.endif
3154    |3:  // RA and RD are both numbers.
3155    |.if FPU
3156    |.if MIPSR6
3157    |  fcomp FTMP0, FTMP0, FTMP2
3158    |   addu TMP2, TMP2, TMP3
3159    |  mfc1 TMP3, FTMP0
3160    |  b <1
3161    |.  fmovop TMP2, TMP2, TMP3
3162    |.else
3163    |  fcomp FTMP0, FTMP2
3164    |   addu TMP2, TMP2, TMP3
3165    |  b <1
3166    |.  fmovop TMP2, r0
3167    |.endif
3168    |.else
3169    |  bal sfcomp
3170    |.   addu TMP2, TMP2, TMP3
3171    |  b <1
3172    |.if MIPSR6
3173    |.  movop TMP2, TMP2, CRET1
3174    |.else
3175    |.  movop TMP2, r0, CRET1
3176    |.endif
3177    |.endif
3178    |
3179    |4:  // RA is a number, RD is not a number.
3180    |  bne CARG4, TISNUM, ->vmeta_comp
3181    |  // RA is a number, RD is an integer. Convert RD to a number.
3182    |.if FPU
3183    |.  lwc1 FRD, LO(RD)
3184    |  ldc1 FRA, 0(RA)
3185    |  b <3
3186    |.  cvt.d.w FRD, FRD
3187    |.else
3188    |.if "ARGRD" == "CARG1"
3189    |.  sextw CARG1, CARG1
3190    |  bal ->vm_sfi2d_1
3191    |.  nop
3192    |.else
3193    |.  sextw CARG2, CARG2
3194    |  bal ->vm_sfi2d_2
3195    |.  nop
3196    |.endif
3197    |  b <3
3198    |.  nop
3199    |.endif
3200    |
3201    |5:  // RA is an integer, RD is not an integer
3202    |  sltiu AT, CARG4, LJ_TISNUM
3203    |  beqz AT, ->vmeta_comp
3204    |.  lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3205    |  // RA is an integer, RD is a number. Convert RA to a number.
3206    |.if FPU
3207    |   lwc1 FRA, LO(RA)
3208    |   ldc1 FRD, 0(RD)
3209    |  b <3
3210    |   cvt.d.w FRA, FRA
3211    |.else
3212    |.if "ARGRA" == "CARG1"
3213    |  bal ->vm_sfi2d_1
3214    |.  sextw CARG1, CARG1
3215    |.else
3216    |  bal ->vm_sfi2d_2
3217    |.  sextw CARG2, CARG2
3218    |.endif
3219    |  b <3
3220    |.  nop
3221    |.endif
3222    |.endmacro
3223    |
3224    |.if MIPSR6
3225    if (op == BC_ISLT) {
3226      |  bc_comp FTMP0, FTMP2, CARG1, CARG2, selnez, selnez, cmp.lt.d, ->vm_sfcmpolt
3227    } else if (op == BC_ISGE) {
3228      |  bc_comp FTMP0, FTMP2, CARG1, CARG2, seleqz, seleqz, cmp.lt.d, ->vm_sfcmpolt
3229    } else if (op == BC_ISLE) {
3230      |  bc_comp FTMP2, FTMP0, CARG2, CARG1, seleqz, seleqz, cmp.ult.d, ->vm_sfcmpult
3231    } else {
3232      |  bc_comp FTMP2, FTMP0, CARG2, CARG1, selnez, selnez, cmp.ult.d, ->vm_sfcmpult
3233    }
3234    |.else
3235    if (op == BC_ISLT) {
3236      |  bc_comp FTMP0, FTMP2, CARG1, CARG2, movz, movf, c.olt.d, ->vm_sfcmpolt
3237    } else if (op == BC_ISGE) {
3238      |  bc_comp FTMP0, FTMP2, CARG1, CARG2, movn, movt, c.olt.d, ->vm_sfcmpolt
3239    } else if (op == BC_ISLE) {
3240      |  bc_comp FTMP2, FTMP0, CARG2, CARG1, movn, movt, c.ult.d, ->vm_sfcmpult
3241    } else {
3242      |  bc_comp FTMP2, FTMP0, CARG2, CARG1, movz, movf, c.ult.d, ->vm_sfcmpult
3243    }
3244    |.endif
3245    break;
3246
3247  case BC_ISEQV: case BC_ISNEV:
3248    vk = op == BC_ISEQV;
3249    |  // RA = src1*8, RD = src2*8, JMP with RD = target
3250    |  daddu RA, BASE, RA
3251    |    daddiu PC, PC, 4
3252    |   daddu RD, BASE, RD
3253    |  ld CARG1, 0(RA)
3254    |    lhu TMP2, -4+OFS_RD(PC)
3255    |   ld CARG2, 0(RD)
3256    |  gettp CARG3, CARG1
3257    |   gettp CARG4, CARG2
3258    |  sltu AT, TISNUM, CARG3
3259    |   sltu TMP1, TISNUM, CARG4
3260    |  or AT, AT, TMP1
3261    if (vk) {
3262      |  beqz AT, ->BC_ISEQN_Z
3263    } else {
3264      |  beqz AT, ->BC_ISNEN_Z
3265    }
3266    |  // Either or both types are not numbers.
3267    |    lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3268    |.if FFI
3269    |.  li AT, LJ_TCDATA
3270    |  beq CARG3, AT, ->vmeta_equal_cd
3271    |.endif
3272    |   decode_RD4b TMP2
3273    |.if FFI
3274    |  beq CARG4, AT, ->vmeta_equal_cd
3275    |.  nop
3276    |.endif
3277    |  bne CARG1, CARG2, >2
3278    |.  addu TMP2, TMP2, TMP3
3279    |  // Tag and value are equal.
3280    if (vk) {
3281      |->BC_ISEQV_Z:
3282      |  daddu PC, PC, TMP2
3283    }
3284    |1:
3285    |  ins_next
3286    |
3287    |2:  // Check if the tags are the same and it's a table or userdata.
3288    |  xor AT, CARG3, CARG4			// Same type?
3289    |  sltiu TMP0, CARG3, LJ_TISTABUD+1		// Table or userdata?
3290    |.if MIPSR6
3291    |  seleqz TMP0, TMP0, AT
3292    |.else
3293    |  movn TMP0, r0, AT
3294    |.endif
3295    if (vk) {
3296      |  beqz TMP0, <1
3297    } else {
3298      |  beqz TMP0, ->BC_ISEQV_Z  // Reuse code from opposite instruction.
3299    }
3300    |  // Different tables or userdatas. Need to check __eq metamethod.
3301    |  // Field metatable must be at same offset for GCtab and GCudata!
3302    |.  cleartp TAB:TMP1, CARG1
3303    |  ld TAB:TMP3, TAB:TMP1->metatable
3304    if (vk) {
3305      |  beqz TAB:TMP3, <1		// No metatable?
3306      |.  nop
3307      |  lbu TMP3, TAB:TMP3->nomm
3308      |  andi TMP3, TMP3, 1<<MM_eq
3309      |  bnez TMP3, >1			// Or 'no __eq' flag set?
3310    } else {
3311      |  beqz TAB:TMP3,->BC_ISEQV_Z	// No metatable?
3312      |.  nop
3313      |  lbu TMP3, TAB:TMP3->nomm
3314      |  andi TMP3, TMP3, 1<<MM_eq
3315      |  bnez TMP3, ->BC_ISEQV_Z	// Or 'no __eq' flag set?
3316    }
3317    |.  nop
3318    |  b ->vmeta_equal			// Handle __eq metamethod.
3319    |.  li TMP0, 1-vk			// ne = 0 or 1.
3320    break;
3321
3322  case BC_ISEQS: case BC_ISNES:
3323    vk = op == BC_ISEQS;
3324    |  // RA = src*8, RD = str_const*8 (~), JMP with RD = target
3325    |  daddu RA, BASE, RA
3326    |   daddiu PC, PC, 4
3327    |  ld CARG1, 0(RA)
3328    |   dsubu RD, KBASE, RD
3329    |    lhu TMP2, -4+OFS_RD(PC)
3330    |   ld CARG2, -8(RD)		// KBASE-8-str_const*8
3331    |.if FFI
3332    |  gettp TMP0, CARG1
3333    |  li AT, LJ_TCDATA
3334    |.endif
3335    |  li TMP1, LJ_TSTR
3336    |   decode_RD4b TMP2
3337    |.if FFI
3338    |  beq TMP0, AT, ->vmeta_equal_cd
3339    |.endif
3340    |.  settp CARG2, TMP1
3341    |   lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3342    |  xor TMP1, CARG1, CARG2
3343    |   addu TMP2, TMP2, TMP3
3344    |.if MIPSR6
3345    if (vk) {
3346      |  seleqz TMP2, TMP2, TMP1
3347    } else {
3348      |  selnez TMP2, TMP2, TMP1
3349    }
3350    |.else
3351    if (vk) {
3352      |  movn TMP2, r0, TMP1
3353    } else {
3354      |  movz TMP2, r0, TMP1
3355    }
3356    |.endif
3357    |  daddu PC, PC, TMP2
3358    |  ins_next
3359    break;
3360
3361  case BC_ISEQN: case BC_ISNEN:
3362    vk = op == BC_ISEQN;
3363    |  // RA = src*8, RD = num_const*8, JMP with RD = target
3364    |  daddu RA, BASE, RA
3365    |   daddu RD, KBASE, RD
3366    |  ld CARG1, 0(RA)
3367    |   ld CARG2, 0(RD)
3368    |    lhu TMP2, OFS_RD(PC)
3369    |  gettp CARG3, CARG1
3370    |   gettp CARG4, CARG2
3371    |    daddiu PC, PC, 4
3372    |    lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3373    if (vk) {
3374      |->BC_ISEQN_Z:
3375    } else {
3376      |->BC_ISNEN_Z:
3377    }
3378    |  bne CARG3, TISNUM, >3
3379    |.   decode_RD4b TMP2
3380    |  bne CARG4, TISNUM, >6
3381    |.   addu TMP2, TMP2, TMP3
3382    |  xor AT, CARG1, CARG2
3383    |.if MIPSR6
3384    if (vk) {
3385      | seleqz TMP2, TMP2, AT
3386      |1:
3387      |  daddu PC, PC, TMP2
3388      |2:
3389    } else {
3390      |  selnez TMP2, TMP2, AT
3391      |1:
3392      |2:
3393      |  daddu PC, PC, TMP2
3394    }
3395    |.else
3396    if (vk) {
3397      | movn TMP2, r0, AT
3398      |1:
3399      |  daddu PC, PC, TMP2
3400      |2:
3401    } else {
3402      |  movz TMP2, r0, AT
3403      |1:
3404      |2:
3405      |  daddu PC, PC, TMP2
3406    }
3407    |.endif
3408    |  ins_next
3409    |
3410    |3:  // RA is not an integer.
3411    |  sltu AT, CARG3, TISNUM
3412    |.if FFI
3413    |  beqz AT, >8
3414    |.else
3415    |  beqz AT, <2
3416    |.endif
3417    |.   addu TMP2, TMP2, TMP3
3418    |  sltu AT, CARG4, TISNUM
3419    |.if FPU
3420    |  ldc1 FTMP0, 0(RA)
3421    |   ldc1 FTMP2, 0(RD)
3422    |.endif
3423    |  beqz AT, >5
3424    |.  nop
3425    |4:  // RA and RD are both numbers.
3426    |.if FPU
3427    |.if MIPSR6
3428    |  cmp.eq.d FTMP0, FTMP0, FTMP2
3429    |  dmfc1 TMP1, FTMP0
3430    |  b <1
3431    if (vk) {
3432      |.  selnez TMP2, TMP2, TMP1
3433    } else {
3434      |.  seleqz TMP2, TMP2, TMP1
3435    }
3436    |.else
3437    |  c.eq.d FTMP0, FTMP2
3438    |  b <1
3439    if (vk) {
3440      |.  movf TMP2, r0
3441    } else {
3442      |.  movt TMP2, r0
3443    }
3444    |.endif
3445    |.else
3446    |  bal ->vm_sfcmpeq
3447    |.  nop
3448    |  b <1
3449    |.if MIPSR6
3450    if (vk) {
3451      |.  selnez TMP2, TMP2, CRET1
3452    } else {
3453      |.  seleqz TMP2, TMP2, CRET1
3454    }
3455    |.else
3456    if (vk) {
3457      |.  movz TMP2, r0, CRET1
3458    } else {
3459      |.  movn TMP2, r0, CRET1
3460    }
3461    |.endif
3462    |.endif
3463    |
3464    |5:  // RA is a number, RD is not a number.
3465    |.if FFI
3466    |  bne CARG4, TISNUM, >9
3467    |.else
3468    |  bne CARG4, TISNUM, <2
3469    |.endif
3470    |  // RA is a number, RD is an integer. Convert RD to a number.
3471    |.if FPU
3472    |.  lwc1 FTMP2, LO(RD)
3473    |  b <4
3474    |.  cvt.d.w FTMP2, FTMP2
3475    |.else
3476    |.  sextw CARG2, CARG2
3477    |  bal ->vm_sfi2d_2
3478    |.  nop
3479    |  b <4
3480    |.  nop
3481    |.endif
3482    |
3483    |6:  // RA is an integer, RD is not an integer
3484    |  sltu AT, CARG4, TISNUM
3485    |.if FFI
3486    |  beqz AT, >9
3487    |.else
3488    |  beqz AT, <2
3489    |.endif
3490    |  // RA is an integer, RD is a number. Convert RA to a number.
3491    |.if FPU
3492    |.  lwc1 FTMP0, LO(RA)
3493    |   ldc1 FTMP2, 0(RD)
3494    |  b <4
3495    |   cvt.d.w FTMP0, FTMP0
3496    |.else
3497    |.  sextw CARG1, CARG1
3498    |  bal ->vm_sfi2d_1
3499    |.  nop
3500    |  b <4
3501    |.  nop
3502    |.endif
3503    |
3504    |.if FFI
3505    |8:
3506    |  li AT, LJ_TCDATA
3507    |  bne CARG3, AT, <2
3508    |.  nop
3509    |  b ->vmeta_equal_cd
3510    |.  nop
3511    |9:
3512    |  li AT, LJ_TCDATA
3513    |  bne CARG4, AT, <2
3514    |.  nop
3515    |  b ->vmeta_equal_cd
3516    |.  nop
3517    |.endif
3518    break;
3519
3520  case BC_ISEQP: case BC_ISNEP:
3521    vk = op == BC_ISEQP;
3522    |  // RA = src*8, RD = primitive_type*8 (~), JMP with RD = target
3523    |  daddu RA, BASE, RA
3524    |   srl TMP1, RD, 3
3525    |  ld TMP0, 0(RA)
3526    |    lhu TMP2, OFS_RD(PC)
3527    |   not TMP1, TMP1
3528    |  gettp TMP0, TMP0
3529    |    daddiu PC, PC, 4
3530    |.if FFI
3531    |  li AT, LJ_TCDATA
3532    |  beq TMP0, AT, ->vmeta_equal_cd
3533    |.endif
3534    |.  xor TMP0, TMP0, TMP1
3535    |  decode_RD4b TMP2
3536    |  lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3537    |  addu TMP2, TMP2, TMP3
3538    |.if MIPSR6
3539    if (vk) {
3540      |  seleqz TMP2, TMP2, TMP0
3541    } else {
3542      |  selnez TMP2, TMP2, TMP0
3543    }
3544    |.else
3545    if (vk) {
3546      |  movn TMP2, r0, TMP0
3547    } else {
3548      |  movz TMP2, r0, TMP0
3549    }
3550    |.endif
3551    |  daddu PC, PC, TMP2
3552    |  ins_next
3553    break;
3554
3555  /* -- Unary test and copy ops ------------------------------------------- */
3556
3557  case BC_ISTC: case BC_ISFC: case BC_IST: case BC_ISF:
3558    |  // RA = dst*8 or unused, RD = src*8, JMP with RD = target
3559    |  daddu RD, BASE, RD
3560    |   lhu TMP2, OFS_RD(PC)
3561    |  ld TMP0, 0(RD)
3562    |   daddiu PC, PC, 4
3563    |  gettp TMP0, TMP0
3564    |  sltiu TMP0, TMP0, LJ_TISTRUECOND
3565    if (op == BC_IST || op == BC_ISF) {
3566      |   decode_RD4b TMP2
3567      |   lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3568      |   addu TMP2, TMP2, TMP3
3569      |.if MIPSR6
3570      if (op == BC_IST) {
3571	|  selnez TMP2, TMP2, TMP0;
3572      } else {
3573	|  seleqz TMP2, TMP2, TMP0;
3574      }
3575      |.else
3576      if (op == BC_IST) {
3577	|  movz TMP2, r0, TMP0
3578      } else {
3579	|  movn TMP2, r0, TMP0
3580      }
3581      |.endif
3582      |  daddu PC, PC, TMP2
3583    } else {
3584      |  ld CRET1, 0(RD)
3585      if (op == BC_ISTC) {
3586	|  beqz TMP0, >1
3587      } else {
3588	|  bnez TMP0, >1
3589      }
3590      |.  daddu RA, BASE, RA
3591      |   decode_RD4b TMP2
3592      |   lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
3593      |   addu TMP2, TMP2, TMP3
3594      |  sd CRET1, 0(RA)
3595      |   daddu PC, PC, TMP2
3596      |1:
3597    }
3598    |  ins_next
3599    break;
3600
3601  case BC_ISTYPE:
3602    |  // RA = src*8, RD = -type*8
3603    |  daddu TMP2, BASE, RA
3604    |  srl TMP1, RD, 3
3605    |  ld TMP0, 0(TMP2)
3606    |  ins_next1
3607    |  gettp TMP0, TMP0
3608    |  daddu AT, TMP0, TMP1
3609    |  bnez AT, ->vmeta_istype
3610    |.  ins_next2
3611    break;
3612  case BC_ISNUM:
3613    |  // RA = src*8, RD = -(TISNUM-1)*8
3614    |  daddu TMP2, BASE, RA
3615    |  ld TMP0, 0(TMP2)
3616    |  ins_next1
3617    |  checknum TMP0, ->vmeta_istype
3618    |.  ins_next2
3619    break;
3620
3621  /* -- Unary ops --------------------------------------------------------- */
3622
3623  case BC_MOV:
3624    |  // RA = dst*8, RD = src*8
3625    |  daddu RD, BASE, RD
3626    |   daddu RA, BASE, RA
3627    |  ld CRET1, 0(RD)
3628    |  ins_next1
3629    |  sd CRET1, 0(RA)
3630    |  ins_next2
3631    break;
3632  case BC_NOT:
3633    |  // RA = dst*8, RD = src*8
3634    |  daddu RD, BASE, RD
3635    |   daddu RA, BASE, RA
3636    |  ld TMP0, 0(RD)
3637    |   li AT, LJ_TTRUE
3638    |  gettp TMP0, TMP0
3639    |  sltu TMP0, AT, TMP0
3640    |  addiu TMP0, TMP0, 1
3641    |  dsll TMP0, TMP0, 47
3642    |  not TMP0, TMP0
3643    |  ins_next1
3644    |   sd TMP0, 0(RA)
3645    |  ins_next2
3646    break;
3647  case BC_UNM:
3648    |  // RA = dst*8, RD = src*8
3649    |  daddu RB, BASE, RD
3650    |  ld CARG1, 0(RB)
3651    |    daddu RA, BASE, RA
3652    |  gettp CARG3, CARG1
3653    |  bne CARG3, TISNUM, >2
3654    |.  lui TMP1, 0x8000
3655    |  sextw CARG1, CARG1
3656    |  beq CARG1, TMP1, ->vmeta_unm	// Meta handler deals with -2^31.
3657    |.  negu CARG1, CARG1
3658    |  zextw CARG1, CARG1
3659    |  settp CARG1, TISNUM
3660    |1:
3661    |  ins_next1
3662    |   sd CARG1, 0(RA)
3663    |  ins_next2
3664    |2:
3665    |  sltiu AT, CARG3, LJ_TISNUM
3666    |  beqz AT, ->vmeta_unm
3667    |.  dsll TMP1, TMP1, 32
3668    |  b <1
3669    |.  xor CARG1, CARG1, TMP1
3670    break;
3671  case BC_LEN:
3672    |  // RA = dst*8, RD = src*8
3673    |  daddu CARG2, BASE, RD
3674    |   daddu RA, BASE, RA
3675    |  ld TMP0, 0(CARG2)
3676    |  gettp TMP1, TMP0
3677    |  daddiu AT, TMP1, -LJ_TSTR
3678    |  bnez AT, >2
3679    |.  cleartp STR:CARG1, TMP0
3680    |   lw CRET1, STR:CARG1->len
3681    |1:
3682    |  settp CRET1, TISNUM
3683    |  ins_next1
3684    |  sd CRET1, 0(RA)
3685    |  ins_next2
3686    |2:
3687    |  daddiu AT, TMP1, -LJ_TTAB
3688    |  bnez AT, ->vmeta_len
3689    |.  nop
3690#if LJ_52
3691    |  ld TAB:TMP2, TAB:CARG1->metatable
3692    |  bnez TAB:TMP2, >9
3693    |.  nop
3694    |3:
3695#endif
3696    |->BC_LEN_Z:
3697    |  load_got lj_tab_len
3698    |  call_intern lj_tab_len		// (GCtab *t)
3699    |.  nop
3700    |  // Returns uint32_t (but less than 2^31).
3701    |  b <1
3702    |.  nop
3703#if LJ_52
3704    |9:
3705    |  lbu TMP0, TAB:TMP2->nomm
3706    |  andi TMP0, TMP0, 1<<MM_len
3707    |  bnez TMP0, <3			// 'no __len' flag set: done.
3708    |.  nop
3709    |  b ->vmeta_len
3710    |.  nop
3711#endif
3712    break;
3713
3714  /* -- Binary ops -------------------------------------------------------- */
3715
3716    |.macro fpmod, a, b, c
3717    |  bal ->vm_floor		// floor(b/c)
3718    |.  div.d FARG1, b, c
3719    |  mul.d a, FRET1, c
3720    |  sub.d a, b, a		// b - floor(b/c)*c
3721    |.endmacro
3722
3723    |.macro sfpmod
3724    |  daddiu sp, sp, -16
3725    |
3726    |  load_got __divdf3
3727    |  sd CARG1, 0(sp)
3728    |  call_extern
3729    |.  sd CARG2, 8(sp)
3730    |
3731    |  load_got floor
3732    |  call_extern
3733    |.  move CARG1, CRET1
3734    |
3735    |  load_got __muldf3
3736    |  move CARG1, CRET1
3737    |  call_extern
3738    |.  ld CARG2, 8(sp)
3739    |
3740    |  load_got __subdf3
3741    |  ld CARG1, 0(sp)
3742    |  call_extern
3743    |.  move CARG2, CRET1
3744    |
3745    |  daddiu sp, sp, 16
3746    |.endmacro
3747
3748    |.macro ins_arithpre, label
3749    ||vk = ((int)op - BC_ADDVN) / (BC_ADDNV-BC_ADDVN);
3750    |  // RA = dst*8, RB = src1*8, RC = src2*8 | num_const*8
3751    ||switch (vk) {
3752    ||case 0:
3753    |   decode_RB8a RB, INS
3754    |   decode_RB8b RB
3755    |    decode_RDtoRC8 RC, RD
3756    |   // RA = dst*8, RB = src1*8, RC = num_const*8
3757    |   daddu RB, BASE, RB
3758    |.if "label" ~= "none"
3759    |   b label
3760    |.endif
3761    |.   daddu RC, KBASE, RC
3762    ||  break;
3763    ||case 1:
3764    |   decode_RB8a RC, INS
3765    |   decode_RB8b RC
3766    |    decode_RDtoRC8 RB, RD
3767    |   // RA = dst*8, RB = num_const*8, RC = src1*8
3768    |   daddu RC, BASE, RC
3769    |.if "label" ~= "none"
3770    |   b label
3771    |.endif
3772    |.   daddu RB, KBASE, RB
3773    ||  break;
3774    ||default:
3775    |   decode_RB8a RB, INS
3776    |   decode_RB8b RB
3777    |    decode_RDtoRC8 RC, RD
3778    |   // RA = dst*8, RB = src1*8, RC = src2*8
3779    |   daddu RB, BASE, RB
3780    |.if "label" ~= "none"
3781    |   b label
3782    |.endif
3783    |.   daddu RC, BASE, RC
3784    ||  break;
3785    ||}
3786    |.endmacro
3787    |
3788    |.macro ins_arith, intins, fpins, fpcall, label
3789    |  ins_arithpre none
3790    |
3791    |.if "label" ~= "none"
3792    |label:
3793    |.endif
3794    |
3795    |// Used in 5.
3796    |  ld CARG1, 0(RB)
3797    |   ld CARG2, 0(RC)
3798    |  gettp TMP0, CARG1
3799    |   gettp TMP1, CARG2
3800    |
3801    |.if "intins" ~= "div"
3802    |
3803    |  // Check for two integers.
3804    |  sextw CARG3, CARG1
3805    |  bne TMP0, TISNUM, >5
3806    |.  sextw CARG4, CARG2
3807    |  bne TMP1, TISNUM, >5
3808    |
3809    |.if "intins" == "addu"
3810    |.  intins CRET1, CARG3, CARG4
3811    |  xor TMP1, CRET1, CARG3		// ((y^a) & (y^b)) < 0: overflow.
3812    |  xor TMP2, CRET1, CARG4
3813    |  and TMP1, TMP1, TMP2
3814    |  bltz TMP1, ->vmeta_arith
3815    |.  daddu RA, BASE, RA
3816    |.elif "intins" == "subu"
3817    |.  intins CRET1, CARG3, CARG4
3818    |  xor TMP1, CRET1, CARG3		// ((y^a) & (a^b)) < 0: overflow.
3819    |  xor TMP2, CARG3, CARG4
3820    |  and TMP1, TMP1, TMP2
3821    |  bltz TMP1, ->vmeta_arith
3822    |.  daddu RA, BASE, RA
3823    |.elif "intins" == "mult"
3824    |.if MIPSR6
3825    |.  nop
3826    |  mul CRET1, CARG3, CARG4
3827    |  muh TMP2, CARG3, CARG4
3828    |.else
3829    |.  intins CARG3, CARG4
3830    |  mflo CRET1
3831    |  mfhi TMP2
3832    |.endif
3833    |  sra TMP1, CRET1, 31
3834    |  bne TMP1, TMP2, ->vmeta_arith
3835    |.  daddu RA, BASE, RA
3836    |.else
3837    |.  load_got lj_vm_modi
3838    |  beqz CARG4, ->vmeta_arith
3839    |.  daddu RA, BASE, RA
3840    |  move CARG1, CARG3
3841    |  call_extern
3842    |.  move CARG2, CARG4
3843    |.endif
3844    |
3845    |  zextw CRET1, CRET1
3846    |  settp CRET1, TISNUM
3847    |  ins_next1
3848    |  sd CRET1, 0(RA)
3849    |3:
3850    |  ins_next2
3851    |
3852    |.endif
3853    |
3854    |5:  // Check for two numbers.
3855    |  .FPU ldc1 FTMP0, 0(RB)
3856    |  sltu AT, TMP0, TISNUM
3857    |   sltu TMP0, TMP1, TISNUM
3858    |  .FPU ldc1 FTMP2, 0(RC)
3859    |   and AT, AT, TMP0
3860    |   beqz AT, ->vmeta_arith
3861    |.   daddu RA, BASE, RA
3862    |
3863    |.if FPU
3864    |  fpins FRET1, FTMP0, FTMP2
3865    |.elif "fpcall" == "sfpmod"
3866    |  sfpmod
3867    |.else
3868    |  load_got fpcall
3869    |  call_extern
3870    |.  nop
3871    |.endif
3872    |
3873    |  ins_next1
3874    |.if "intins" ~= "div"
3875    |  b <3
3876    |.endif
3877    |.if FPU
3878    |.  sdc1 FRET1, 0(RA)
3879    |.else
3880    |.  sd CRET1, 0(RA)
3881    |.endif
3882    |.if "intins" == "div"
3883    |  ins_next2
3884    |.endif
3885    |
3886    |.endmacro
3887
3888  case BC_ADDVN: case BC_ADDNV: case BC_ADDVV:
3889    |  ins_arith addu, add.d, __adddf3, none
3890    break;
3891  case BC_SUBVN: case BC_SUBNV: case BC_SUBVV:
3892    |  ins_arith subu, sub.d, __subdf3, none
3893    break;
3894  case BC_MULVN: case BC_MULNV: case BC_MULVV:
3895    |  ins_arith mult, mul.d, __muldf3, none
3896    break;
3897  case BC_DIVVN:
3898    |  ins_arith div, div.d, __divdf3, ->BC_DIVVN_Z
3899    break;
3900  case BC_DIVNV: case BC_DIVVV:
3901    |  ins_arithpre ->BC_DIVVN_Z
3902    break;
3903  case BC_MODVN:
3904    |  ins_arith modi, fpmod, sfpmod, ->BC_MODVN_Z
3905    break;
3906  case BC_MODNV: case BC_MODVV:
3907    |  ins_arithpre ->BC_MODVN_Z
3908    break;
3909  case BC_POW:
3910    |  ins_arithpre none
3911    |  ld CARG1, 0(RB)
3912    |   ld CARG2, 0(RC)
3913    |  gettp TMP0, CARG1
3914    |   gettp TMP1, CARG2
3915    |  sltiu TMP0, TMP0, LJ_TISNUM
3916    |   sltiu TMP1, TMP1, LJ_TISNUM
3917    |  and AT, TMP0, TMP1
3918    |  load_got pow
3919    |  beqz AT, ->vmeta_arith
3920    |.  daddu RA, BASE, RA
3921    |.if FPU
3922    |  ldc1 FARG1, 0(RB)
3923    |  ldc1 FARG2, 0(RC)
3924    |.endif
3925    |  call_extern
3926    |.  nop
3927    |  ins_next1
3928    |.if FPU
3929    |  sdc1 FRET1, 0(RA)
3930    |.else
3931    |  sd CRET1, 0(RA)
3932    |.endif
3933    |  ins_next2
3934    break;
3935
3936  case BC_CAT:
3937    |  // RA = dst*8, RB = src_start*8, RC = src_end*8
3938    |  decode_RB8a RB, INS
3939    |  decode_RB8b RB
3940    |   decode_RDtoRC8 RC, RD
3941    |  dsubu CARG3, RC, RB
3942    |   sd BASE, L->base
3943    |  daddu CARG2, BASE, RC
3944    |  move MULTRES, RB
3945    |->BC_CAT_Z:
3946    |  load_got lj_meta_cat
3947    |  srl CARG3, CARG3, 3
3948    |   sd PC, SAVE_PC
3949    |  call_intern lj_meta_cat		// (lua_State *L, TValue *top, int left)
3950    |.  move CARG1, L
3951    |  // Returns NULL (finished) or TValue * (metamethod).
3952    |  bnez CRET1, ->vmeta_binop
3953    |.  ld BASE, L->base
3954    |  daddu RB, BASE, MULTRES
3955    |  ld CRET1, 0(RB)
3956    |   daddu RA, BASE, RA
3957    |  ins_next1
3958    |  sd CRET1, 0(RA)
3959    |  ins_next2
3960    break;
3961
3962  /* -- Constant ops ------------------------------------------------------ */
3963
3964  case BC_KSTR:
3965    |  // RA = dst*8, RD = str_const*8 (~)
3966    |  dsubu TMP1, KBASE, RD
3967    |  ins_next1
3968    |   li TMP2, LJ_TSTR
3969    |  ld TMP0, -8(TMP1)		// KBASE-8-str_const*8
3970    |  daddu RA, BASE, RA
3971    |   settp TMP0, TMP2
3972    |  sd TMP0, 0(RA)
3973    |  ins_next2
3974    break;
3975  case BC_KCDATA:
3976    |.if FFI
3977    |  // RA = dst*8, RD = cdata_const*8 (~)
3978    |  dsubu TMP1, KBASE, RD
3979    |  ins_next1
3980    |  ld TMP0, -8(TMP1)		// KBASE-8-cdata_const*8
3981    |   li TMP2, LJ_TCDATA
3982    |  daddu RA, BASE, RA
3983    |   settp TMP0, TMP2
3984    |  sd TMP0, 0(RA)
3985    |  ins_next2
3986    |.endif
3987    break;
3988  case BC_KSHORT:
3989    |  // RA = dst*8, RD = int16_literal*8
3990    |   sra RD, INS, 16
3991    |  daddu RA, BASE, RA
3992    |   zextw RD, RD
3993    |  ins_next1
3994    |   settp RD, TISNUM
3995    |   sd RD, 0(RA)
3996    |  ins_next2
3997    break;
3998  case BC_KNUM:
3999    |  // RA = dst*8, RD = num_const*8
4000    |  daddu RD, KBASE, RD
4001    |   daddu RA, BASE, RA
4002    |  ld CRET1, 0(RD)
4003    |  ins_next1
4004    |  sd CRET1, 0(RA)
4005    |  ins_next2
4006    break;
4007  case BC_KPRI:
4008    |  // RA = dst*8, RD = primitive_type*8 (~)
4009    |   daddu RA, BASE, RA
4010    |  dsll TMP0, RD, 44
4011    |  not TMP0, TMP0
4012    |  ins_next1
4013    |   sd TMP0, 0(RA)
4014    |  ins_next2
4015    break;
4016  case BC_KNIL:
4017    |  // RA = base*8, RD = end*8
4018    |  daddu RA, BASE, RA
4019    |  sd TISNIL, 0(RA)
4020    |   daddiu RA, RA, 8
4021    |  daddu RD, BASE, RD
4022    |1:
4023    |  sd TISNIL, 0(RA)
4024    |  slt AT, RA, RD
4025    |  bnez AT, <1
4026    |.  daddiu RA, RA, 8
4027    |  ins_next_
4028    break;
4029
4030  /* -- Upvalue and function ops ------------------------------------------ */
4031
4032  case BC_UGET:
4033    |  // RA = dst*8, RD = uvnum*8
4034    |  ld LFUNC:RB, FRAME_FUNC(BASE)
4035    |   daddu RA, BASE, RA
4036    |  cleartp LFUNC:RB
4037    |  daddu RD, RD, LFUNC:RB
4038    |  ld UPVAL:RB, LFUNC:RD->uvptr
4039    |  ins_next1
4040    |  ld TMP1, UPVAL:RB->v
4041    |  ld CRET1, 0(TMP1)
4042    |   sd CRET1, 0(RA)
4043    |  ins_next2
4044    break;
4045  case BC_USETV:
4046    |  // RA = uvnum*8, RD = src*8
4047    |  ld LFUNC:RB, FRAME_FUNC(BASE)
4048    |   daddu RD, BASE, RD
4049    |  cleartp LFUNC:RB
4050    |  daddu RA, RA, LFUNC:RB
4051    |  ld UPVAL:RB, LFUNC:RA->uvptr
4052    |   ld CRET1, 0(RD)
4053    |  lbu TMP3, UPVAL:RB->marked
4054    |   ld CARG2, UPVAL:RB->v
4055    |  andi TMP3, TMP3, LJ_GC_BLACK	// isblack(uv)
4056    |  lbu TMP0, UPVAL:RB->closed
4057    |   gettp TMP2, CRET1
4058    |   sd CRET1, 0(CARG2)
4059    |  li AT, LJ_GC_BLACK|1
4060    |  or TMP3, TMP3, TMP0
4061    |  beq TMP3, AT, >2			// Upvalue is closed and black?
4062    |.  daddiu TMP2, TMP2, -(LJ_TNUMX+1)
4063    |1:
4064    |  ins_next
4065    |
4066    |2:  // Check if new value is collectable.
4067    |  sltiu AT, TMP2, LJ_TISGCV - (LJ_TNUMX+1)
4068    |  beqz AT, <1			// tvisgcv(v)
4069    |.  cleartp GCOBJ:CRET1, CRET1
4070    |  lbu TMP3, GCOBJ:CRET1->gch.marked
4071    |  andi TMP3, TMP3, LJ_GC_WHITES	// iswhite(v)
4072    |  beqz TMP3, <1
4073    |.  load_got lj_gc_barrieruv
4074    |  // Crossed a write barrier. Move the barrier forward.
4075    |  call_intern lj_gc_barrieruv	// (global_State *g, TValue *tv)
4076    |.  daddiu CARG1, DISPATCH, GG_DISP2G
4077    |  b <1
4078    |.  nop
4079    break;
4080  case BC_USETS:
4081    |  // RA = uvnum*8, RD = str_const*8 (~)
4082    |  ld LFUNC:RB, FRAME_FUNC(BASE)
4083    |   dsubu TMP1, KBASE, RD
4084    |  cleartp LFUNC:RB
4085    |  daddu RA, RA, LFUNC:RB
4086    |  ld UPVAL:RB, LFUNC:RA->uvptr
4087    |   ld STR:TMP1, -8(TMP1)		// KBASE-8-str_const*8
4088    |  lbu TMP2, UPVAL:RB->marked
4089    |   ld CARG2, UPVAL:RB->v
4090    |   lbu TMP3, STR:TMP1->marked
4091    |  andi AT, TMP2, LJ_GC_BLACK	// isblack(uv)
4092    |   lbu TMP2, UPVAL:RB->closed
4093    |   li TMP0, LJ_TSTR
4094    |   settp TMP1, TMP0
4095    |  bnez AT, >2
4096    |.  sd TMP1, 0(CARG2)
4097    |1:
4098    |  ins_next
4099    |
4100    |2:  // Check if string is white and ensure upvalue is closed.
4101    |  beqz TMP2, <1
4102    |.  andi AT, TMP3, LJ_GC_WHITES	// iswhite(str)
4103    |  beqz AT, <1
4104    |.  load_got lj_gc_barrieruv
4105    |  // Crossed a write barrier. Move the barrier forward.
4106    |  call_intern lj_gc_barrieruv	// (global_State *g, TValue *tv)
4107    |.  daddiu CARG1, DISPATCH, GG_DISP2G
4108    |  b <1
4109    |.  nop
4110    break;
4111  case BC_USETN:
4112    |  // RA = uvnum*8, RD = num_const*8
4113    |  ld LFUNC:RB, FRAME_FUNC(BASE)
4114    |   daddu RD, KBASE, RD
4115    |  cleartp LFUNC:RB
4116    |  daddu RA, RA, LFUNC:RB
4117    |  ld UPVAL:RB, LFUNC:RA->uvptr
4118    |   ld CRET1, 0(RD)
4119    |  ld TMP1, UPVAL:RB->v
4120    |  ins_next1
4121    |   sd CRET1, 0(TMP1)
4122    |  ins_next2
4123    break;
4124  case BC_USETP:
4125    |  // RA = uvnum*8, RD = primitive_type*8 (~)
4126    |  ld LFUNC:RB, FRAME_FUNC(BASE)
4127    |   dsll TMP0, RD, 44
4128    |  cleartp LFUNC:RB
4129    |  daddu RA, RA, LFUNC:RB
4130    |   not TMP0, TMP0
4131    |  ld UPVAL:RB, LFUNC:RA->uvptr
4132    |  ins_next1
4133    |  ld TMP1, UPVAL:RB->v
4134    |   sd TMP0, 0(TMP1)
4135    |  ins_next2
4136    break;
4137
4138  case BC_UCLO:
4139    |  // RA = level*8, RD = target
4140    |  ld TMP2, L->openupval
4141    |  branch_RD			// Do this first since RD is not saved.
4142    |  load_got lj_func_closeuv
4143    |   sd BASE, L->base
4144    |  beqz TMP2, >1
4145    |.  move CARG1, L
4146    |  call_intern lj_func_closeuv	// (lua_State *L, TValue *level)
4147    |.  daddu CARG2, BASE, RA
4148    |  ld BASE, L->base
4149    |1:
4150    |  ins_next
4151    break;
4152
4153  case BC_FNEW:
4154    |  // RA = dst*8, RD = proto_const*8 (~) (holding function prototype)
4155    |  load_got lj_func_newL_gc
4156    |  dsubu TMP1, KBASE, RD
4157    |  ld CARG3, FRAME_FUNC(BASE)
4158    |   ld CARG2, -8(TMP1)		// KBASE-8-tab_const*8
4159    |    sd BASE, L->base
4160    |    sd PC, SAVE_PC
4161    |  cleartp CARG3
4162    |  // (lua_State *L, GCproto *pt, GCfuncL *parent)
4163    |  call_intern lj_func_newL_gc
4164    |.  move CARG1, L
4165    |  // Returns GCfuncL *.
4166    |   li TMP0, LJ_TFUNC
4167    |  ld BASE, L->base
4168    |  ins_next1
4169    |   settp CRET1, TMP0
4170    |  daddu RA, BASE, RA
4171    |   sd CRET1, 0(RA)
4172    |  ins_next2
4173    break;
4174
4175  /* -- Table ops --------------------------------------------------------- */
4176
4177  case BC_TNEW:
4178  case BC_TDUP:
4179    |  // RA = dst*8, RD = (hbits|asize)*8 | tab_const*8 (~)
4180    |  ld TMP0, DISPATCH_GL(gc.total)(DISPATCH)
4181    |  ld TMP1, DISPATCH_GL(gc.threshold)(DISPATCH)
4182    |   sd BASE, L->base
4183    |   sd PC, SAVE_PC
4184    |  sltu AT, TMP0, TMP1
4185    |  beqz AT, >5
4186    |1:
4187    if (op == BC_TNEW) {
4188      |  load_got lj_tab_new
4189      |  srl CARG2, RD, 3
4190      |  andi CARG2, CARG2, 0x7ff
4191      |  li TMP0, 0x801
4192      |  addiu AT, CARG2, -0x7ff
4193      |   srl CARG3, RD, 14
4194      |.if MIPSR6
4195      |  seleqz TMP0, TMP0, AT
4196      |  selnez CARG2, CARG2, AT
4197      |  or CARG2, CARG2, TMP0
4198      |.else
4199      |  movz CARG2, TMP0, AT
4200      |.endif
4201      |  // (lua_State *L, int32_t asize, uint32_t hbits)
4202      |  call_intern lj_tab_new
4203      |.  move CARG1, L
4204      |  // Returns Table *.
4205    } else {
4206      |  load_got lj_tab_dup
4207      |  dsubu TMP1, KBASE, RD
4208      |  move CARG1, L
4209      |  call_intern lj_tab_dup		// (lua_State *L, Table *kt)
4210      |.  ld CARG2, -8(TMP1)		// KBASE-8-str_const*8
4211      |  // Returns Table *.
4212    }
4213    |   li TMP0, LJ_TTAB
4214    |  ld BASE, L->base
4215    |  ins_next1
4216    |  daddu RA, BASE, RA
4217    |   settp CRET1, TMP0
4218    |   sd CRET1, 0(RA)
4219    |  ins_next2
4220    |5:
4221    |  load_got lj_gc_step_fixtop
4222    |  move MULTRES, RD
4223    |  call_intern lj_gc_step_fixtop	// (lua_State *L)
4224    |.  move CARG1, L
4225    |  b <1
4226    |.  move RD, MULTRES
4227    break;
4228
4229  case BC_GGET:
4230    |  // RA = dst*8, RD = str_const*8 (~)
4231  case BC_GSET:
4232    |  // RA = src*8, RD = str_const*8 (~)
4233    |  ld LFUNC:TMP2, FRAME_FUNC(BASE)
4234    |   dsubu TMP1, KBASE, RD
4235    |   ld STR:RC, -8(TMP1)		// KBASE-8-str_const*8
4236    |  cleartp LFUNC:TMP2
4237    |  ld TAB:RB, LFUNC:TMP2->env
4238    if (op == BC_GGET) {
4239      |  b ->BC_TGETS_Z
4240    } else {
4241      |  b ->BC_TSETS_Z
4242    }
4243    |.  daddu RA, BASE, RA
4244    break;
4245
4246  case BC_TGETV:
4247    |  // RA = dst*8, RB = table*8, RC = key*8
4248    |  decode_RB8a RB, INS
4249    |  decode_RB8b RB
4250    |   decode_RDtoRC8 RC, RD
4251    |  daddu CARG2, BASE, RB
4252    |   daddu CARG3, BASE, RC
4253    |  ld TAB:RB, 0(CARG2)
4254    |   ld TMP2, 0(CARG3)
4255    |   daddu RA, BASE, RA
4256    |  checktab TAB:RB, ->vmeta_tgetv
4257    |   gettp TMP3, TMP2
4258    |  bne TMP3, TISNUM, >5		// Integer key?
4259    |.  lw TMP0, TAB:RB->asize
4260    |  sextw TMP2, TMP2
4261    |   ld TMP1, TAB:RB->array
4262    |  sltu AT, TMP2, TMP0
4263    |   sll TMP2, TMP2, 3
4264    |  beqz AT, ->vmeta_tgetv		// Integer key and in array part?
4265    |.  daddu TMP2, TMP1, TMP2
4266    |  ld AT, 0(TMP2)
4267    |  beq AT, TISNIL, >2
4268    |.   ld CRET1, 0(TMP2)
4269    |1:
4270    |  ins_next1
4271    |   sd CRET1, 0(RA)
4272    |  ins_next2
4273    |
4274    |2:  // Check for __index if table value is nil.
4275    |  ld TAB:TMP2, TAB:RB->metatable
4276    |  beqz TAB:TMP2, <1		// No metatable: done.
4277    |.  nop
4278    |  lbu TMP0, TAB:TMP2->nomm
4279    |  andi TMP0, TMP0, 1<<MM_index
4280    |  bnez TMP0, <1			// 'no __index' flag set: done.
4281    |.  nop
4282    |  b ->vmeta_tgetv
4283    |.  nop
4284    |
4285    |5:
4286    |  li AT, LJ_TSTR
4287    |  bne TMP3, AT, ->vmeta_tgetv
4288    |.  cleartp RC, TMP2
4289    |  b ->BC_TGETS_Z			// String key?
4290    |.  nop
4291    break;
4292  case BC_TGETS:
4293    |  // RA = dst*8, RB = table*8, RC = str_const*8 (~)
4294    |  decode_RB8a RB, INS
4295    |  decode_RB8b RB
4296    |   decode_RC8a RC, INS
4297    |  daddu CARG2, BASE, RB
4298    |   decode_RC8b RC
4299    |  ld TAB:RB, 0(CARG2)
4300    |   dsubu CARG3, KBASE, RC
4301    |  daddu RA, BASE, RA
4302    |   ld STR:RC, -8(CARG3)		// KBASE-8-str_const*8
4303    |  checktab TAB:RB, ->vmeta_tgets1
4304    |->BC_TGETS_Z:
4305    |  // TAB:RB = GCtab *, STR:RC = GCstr *, RA = dst*8
4306    |  lw TMP0, TAB:RB->hmask
4307    |   lw TMP1, STR:RC->sid
4308    |    ld NODE:TMP2, TAB:RB->node
4309    |  and TMP1, TMP1, TMP0		// idx = str->sid & tab->hmask
4310    |  sll TMP0, TMP1, 5
4311    |  sll TMP1, TMP1, 3
4312    |  subu TMP1, TMP0, TMP1
4313    |   li TMP3, LJ_TSTR
4314    |  daddu NODE:TMP2, NODE:TMP2, TMP1	// node = tab->node + (idx*32-idx*8)
4315    |   settp STR:RC, TMP3		// Tagged key to look for.
4316    |1:
4317    |  ld CARG1, NODE:TMP2->key
4318    |   ld CRET1, NODE:TMP2->val
4319    |    ld NODE:TMP1, NODE:TMP2->next
4320    |  bne CARG1, RC, >4
4321    |.  ld TAB:TMP3, TAB:RB->metatable
4322    |  beq CRET1, TISNIL, >5		// Key found, but nil value?
4323    |.  nop
4324    |3:
4325    |  ins_next1
4326    |   sd CRET1, 0(RA)
4327    |  ins_next2
4328    |
4329    |4:  // Follow hash chain.
4330    |  bnez NODE:TMP1, <1
4331    |.  move NODE:TMP2, NODE:TMP1
4332    |  // End of hash chain: key not found, nil result.
4333    |
4334    |5:  // Check for __index if table value is nil.
4335    |  beqz TAB:TMP3, <3		// No metatable: done.
4336    |.  move CRET1, TISNIL
4337    |  lbu TMP0, TAB:TMP3->nomm
4338    |  andi TMP0, TMP0, 1<<MM_index
4339    |  bnez TMP0, <3			// 'no __index' flag set: done.
4340    |.  nop
4341    |  b ->vmeta_tgets
4342    |.  nop
4343    break;
4344  case BC_TGETB:
4345    |  // RA = dst*8, RB = table*8, RC = index*8
4346    |  decode_RB8a RB, INS
4347    |  decode_RB8b RB
4348    |  daddu CARG2, BASE, RB
4349    |   decode_RDtoRC8 RC, RD
4350    |  ld TAB:RB, 0(CARG2)
4351    |   daddu RA, BASE, RA
4352    |  srl TMP0, RC, 3
4353    |  checktab TAB:RB, ->vmeta_tgetb
4354    |  lw TMP1, TAB:RB->asize
4355    |   ld TMP2, TAB:RB->array
4356    |  sltu AT, TMP0, TMP1
4357    |  beqz AT, ->vmeta_tgetb
4358    |.  daddu RC, TMP2, RC
4359    |  ld AT, 0(RC)
4360    |  beq AT, TISNIL, >5
4361    |.  ld CRET1, 0(RC)
4362    |1:
4363    |  ins_next1
4364    |   sd CRET1, 0(RA)
4365    |  ins_next2
4366    |
4367    |5:  // Check for __index if table value is nil.
4368    |  ld TAB:TMP2, TAB:RB->metatable
4369    |  beqz TAB:TMP2, <1		// No metatable: done.
4370    |.  nop
4371    |  lbu TMP1, TAB:TMP2->nomm
4372    |  andi TMP1, TMP1, 1<<MM_index
4373    |  bnez TMP1, <1			// 'no __index' flag set: done.
4374    |.  nop
4375    |  b ->vmeta_tgetb			// Caveat: preserve TMP0 and CARG2!
4376    |.  nop
4377    break;
4378  case BC_TGETR:
4379    |  // RA = dst*8, RB = table*8, RC = key*8
4380    |  decode_RB8a RB, INS
4381    |  decode_RB8b RB
4382    |   decode_RDtoRC8 RC, RD
4383    |  daddu RB, BASE, RB
4384    |   daddu RC, BASE, RC
4385    |  ld TAB:CARG1, 0(RB)
4386    |   lw CARG2, LO(RC)
4387    |    daddu RA, BASE, RA
4388    |  cleartp TAB:CARG1
4389    |  lw TMP0, TAB:CARG1->asize
4390    |   ld TMP1, TAB:CARG1->array
4391    |  sltu AT, CARG2, TMP0
4392    |   sll TMP2, CARG2, 3
4393    |  beqz AT, ->vmeta_tgetr		// In array part?
4394    |.  daddu CRET1, TMP1, TMP2
4395    |   ld CARG2, 0(CRET1)
4396    |->BC_TGETR_Z:
4397    |  ins_next1
4398    |   sd CARG2, 0(RA)
4399    |  ins_next2
4400    break;
4401
4402  case BC_TSETV:
4403    |  // RA = src*8, RB = table*8, RC = key*8
4404    |  decode_RB8a RB, INS
4405    |  decode_RB8b RB
4406    |   decode_RDtoRC8 RC, RD
4407    |  daddu CARG2, BASE, RB
4408    |   daddu CARG3, BASE, RC
4409    |  ld RB, 0(CARG2)
4410    |   ld TMP2, 0(CARG3)
4411    |  daddu RA, BASE, RA
4412    |  checktab RB, ->vmeta_tsetv
4413    |  checkint TMP2, >5
4414    |.  sextw RC, TMP2
4415    |  lw TMP0, TAB:RB->asize
4416    |   ld TMP1, TAB:RB->array
4417    |  sltu AT, RC, TMP0
4418    |   sll TMP2, RC, 3
4419    |  beqz AT, ->vmeta_tsetv		// Integer key and in array part?
4420    |.  daddu TMP1, TMP1, TMP2
4421    |  ld TMP0, 0(TMP1)
4422    |   lbu TMP3, TAB:RB->marked
4423    |  beq TMP0, TISNIL, >3
4424    |.  ld CRET1, 0(RA)
4425    |1:
4426    |   andi AT, TMP3, LJ_GC_BLACK	// isblack(table)
4427    |  bnez AT, >7
4428    |.  sd CRET1, 0(TMP1)
4429    |2:
4430    |  ins_next
4431    |
4432    |3:  // Check for __newindex if previous value is nil.
4433    |  ld TAB:TMP2, TAB:RB->metatable
4434    |  beqz TAB:TMP2, <1		// No metatable: done.
4435    |.  nop
4436    |  lbu TMP2, TAB:TMP2->nomm
4437    |  andi TMP2, TMP2, 1<<MM_newindex
4438    |  bnez TMP2, <1			// 'no __newindex' flag set: done.
4439    |.  nop
4440    |  b ->vmeta_tsetv
4441    |.  nop
4442    |
4443    |5:
4444    |  gettp AT, TMP2
4445    |  daddiu AT, AT, -LJ_TSTR
4446    |  bnez AT, ->vmeta_tsetv
4447    |.  nop
4448    |  b ->BC_TSETS_Z			// String key?
4449    |.  cleartp STR:RC, TMP2
4450    |
4451    |7:  // Possible table write barrier for the value. Skip valiswhite check.
4452    |  barrierback TAB:RB, TMP3, TMP0, <2
4453    break;
4454  case BC_TSETS:
4455    |  // RA = src*8, RB = table*8, RC = str_const*8 (~)
4456    |  decode_RB8a RB, INS
4457    |  decode_RB8b RB
4458    |  daddu CARG2, BASE, RB
4459    |   decode_RC8a RC, INS
4460    |    ld TAB:RB, 0(CARG2)
4461    |   decode_RC8b RC
4462    |   dsubu CARG3, KBASE, RC
4463    |   ld RC, -8(CARG3)		// KBASE-8-str_const*8
4464    |  daddu RA, BASE, RA
4465    |   cleartp STR:RC
4466    |  checktab TAB:RB, ->vmeta_tsets1
4467    |->BC_TSETS_Z:
4468    |  // TAB:RB = GCtab *, STR:RC = GCstr *, RA = BASE+src*8
4469    |  lw TMP0, TAB:RB->hmask
4470    |   lw TMP1, STR:RC->sid
4471    |    ld NODE:TMP2, TAB:RB->node
4472    |   sb r0, TAB:RB->nomm		// Clear metamethod cache.
4473    |  and TMP1, TMP1, TMP0		// idx = str->sid & tab->hmask
4474    |  sll TMP0, TMP1, 5
4475    |  sll TMP1, TMP1, 3
4476    |  subu TMP1, TMP0, TMP1
4477    |   li TMP3, LJ_TSTR
4478    |  daddu NODE:TMP2, NODE:TMP2, TMP1	// node = tab->node + (idx*32-idx*8)
4479    |   settp STR:RC, TMP3		// Tagged key to look for.
4480    |.if FPU
4481    |   ldc1 FTMP0, 0(RA)
4482    |.else
4483    |   ld CRET1, 0(RA)
4484    |.endif
4485    |1:
4486    |  ld TMP0, NODE:TMP2->key
4487    |   ld CARG2, NODE:TMP2->val
4488    |    ld NODE:TMP1, NODE:TMP2->next
4489    |  bne TMP0, RC, >5
4490    |.    lbu TMP3, TAB:RB->marked
4491    |   beq CARG2, TISNIL, >4		// Key found, but nil value?
4492    |.   ld TAB:TMP0, TAB:RB->metatable
4493    |2:
4494    |  andi AT, TMP3, LJ_GC_BLACK	// isblack(table)
4495    |  bnez AT, >7
4496    |.if FPU
4497    |.  sdc1 FTMP0, NODE:TMP2->val
4498    |.else
4499    |.  sd CRET1, NODE:TMP2->val
4500    |.endif
4501    |3:
4502    |  ins_next
4503    |
4504    |4:  // Check for __newindex if previous value is nil.
4505    |  beqz TAB:TMP0, <2		// No metatable: done.
4506    |.  nop
4507    |  lbu TMP0, TAB:TMP0->nomm
4508    |  andi TMP0, TMP0, 1<<MM_newindex
4509    |  bnez TMP0, <2			// 'no __newindex' flag set: done.
4510    |.  nop
4511    |  b ->vmeta_tsets
4512    |.  nop
4513    |
4514    |5:  // Follow hash chain.
4515    |  bnez NODE:TMP1, <1
4516    |.  move NODE:TMP2, NODE:TMP1
4517    |  // End of hash chain: key not found, add a new one
4518    |
4519    |  // But check for __newindex first.
4520    |  ld TAB:TMP2, TAB:RB->metatable
4521    |  beqz TAB:TMP2, >6		// No metatable: continue.
4522    |.  daddiu CARG3, DISPATCH, DISPATCH_GL(tmptv)
4523    |  lbu TMP0, TAB:TMP2->nomm
4524    |  andi TMP0, TMP0, 1<<MM_newindex
4525    |  beqz TMP0, ->vmeta_tsets		// 'no __newindex' flag NOT set: check.
4526    |6:
4527    |  load_got lj_tab_newkey
4528    |  sd RC, 0(CARG3)
4529    |   sd BASE, L->base
4530    |  move CARG2, TAB:RB
4531    |   sd PC, SAVE_PC
4532    |  call_intern lj_tab_newkey	// (lua_State *L, GCtab *t, TValue *k
4533    |.  move CARG1, L
4534    |  // Returns TValue *.
4535    |  ld BASE, L->base
4536    |.if FPU
4537    |  b <3				// No 2nd write barrier needed.
4538    |.  sdc1 FTMP0, 0(CRET1)
4539    |.else
4540    |  ld CARG1, 0(RA)
4541    |  b <3				// No 2nd write barrier needed.
4542    |.  sd CARG1, 0(CRET1)
4543    |.endif
4544    |
4545    |7:  // Possible table write barrier for the value. Skip valiswhite check.
4546    |  barrierback TAB:RB, TMP3, TMP0, <3
4547    break;
4548  case BC_TSETB:
4549    |  // RA = src*8, RB = table*8, RC = index*8
4550    |  decode_RB8a RB, INS
4551    |  decode_RB8b RB
4552    |  daddu CARG2, BASE, RB
4553    |   decode_RDtoRC8 RC, RD
4554    |  ld TAB:RB, 0(CARG2)
4555    |   daddu RA, BASE, RA
4556    |  srl TMP0, RC, 3
4557    |  checktab RB, ->vmeta_tsetb
4558    |  lw TMP1, TAB:RB->asize
4559    |   ld TMP2, TAB:RB->array
4560    |  sltu AT, TMP0, TMP1
4561    |  beqz AT, ->vmeta_tsetb
4562    |.  daddu RC, TMP2, RC
4563    |  ld TMP1, 0(RC)
4564    |   lbu TMP3, TAB:RB->marked
4565    |  beq TMP1, TISNIL, >5
4566    |1:
4567    |.  ld CRET1, 0(RA)
4568    |  andi AT, TMP3, LJ_GC_BLACK	// isblack(table)
4569    |  bnez AT, >7
4570    |.   sd CRET1, 0(RC)
4571    |2:
4572    |  ins_next
4573    |
4574    |5:  // Check for __newindex if previous value is nil.
4575    |  ld TAB:TMP2, TAB:RB->metatable
4576    |  beqz TAB:TMP2, <1		// No metatable: done.
4577    |.  nop
4578    |  lbu TMP1, TAB:TMP2->nomm
4579    |  andi TMP1, TMP1, 1<<MM_newindex
4580    |  bnez TMP1, <1			// 'no __newindex' flag set: done.
4581    |.  nop
4582    |  b ->vmeta_tsetb			// Caveat: preserve TMP0 and CARG2!
4583    |.  nop
4584    |
4585    |7:  // Possible table write barrier for the value. Skip valiswhite check.
4586    |  barrierback TAB:RB, TMP3, TMP0, <2
4587    break;
4588  case BC_TSETR:
4589    |  // RA = dst*8, RB = table*8, RC = key*8
4590    |  decode_RB8a RB, INS
4591    |  decode_RB8b RB
4592    |   decode_RDtoRC8 RC, RD
4593    |  daddu CARG1, BASE, RB
4594    |   daddu CARG3, BASE, RC
4595    |  ld TAB:CARG2, 0(CARG1)
4596    |   lw CARG3, LO(CARG3)
4597    |  cleartp TAB:CARG2
4598    |  lbu TMP3, TAB:CARG2->marked
4599    |   lw TMP0, TAB:CARG2->asize
4600    |    ld TMP1, TAB:CARG2->array
4601    |  andi AT, TMP3, LJ_GC_BLACK	// isblack(table)
4602    |  bnez AT, >7
4603    |.  daddu RA, BASE, RA
4604    |2:
4605    |  sltu AT, CARG3, TMP0
4606    |   sll TMP2, CARG3, 3
4607    |  beqz AT, ->vmeta_tsetr		// In array part?
4608    |.  daddu CRET1, TMP1, TMP2
4609    |->BC_TSETR_Z:
4610    |  ld CARG1, 0(RA)
4611    |  ins_next1
4612    |  sd CARG1, 0(CRET1)
4613    |  ins_next2
4614    |
4615    |7:  // Possible table write barrier for the value. Skip valiswhite check.
4616    |  barrierback TAB:CARG2, TMP3, CRET1, <2
4617    break;
4618
4619  case BC_TSETM:
4620    |  // RA = base*8 (table at base-1), RD = num_const*8 (start index)
4621    |  daddu RA, BASE, RA
4622    |1:
4623    |   daddu TMP3, KBASE, RD
4624    |  ld TAB:CARG2, -8(RA)		// Guaranteed to be a table.
4625    |    addiu TMP0, MULTRES, -8
4626    |   lw TMP3, LO(TMP3)		// Integer constant is in lo-word.
4627    |    beqz TMP0, >4			// Nothing to copy?
4628    |.    srl CARG3, TMP0, 3
4629    |  cleartp CARG2
4630    |  addu CARG3, CARG3, TMP3
4631    |  lw TMP2, TAB:CARG2->asize
4632    |   sll TMP1, TMP3, 3
4633    |    lbu TMP3, TAB:CARG2->marked
4634    |   ld CARG1, TAB:CARG2->array
4635    |  sltu AT, TMP2, CARG3
4636    |  bnez AT, >5
4637    |.  daddu TMP2, RA, TMP0
4638    |   daddu TMP1, TMP1, CARG1
4639    |  andi TMP0, TMP3, LJ_GC_BLACK	// isblack(table)
4640    |3:  // Copy result slots to table.
4641    |   ld CRET1, 0(RA)
4642    |    daddiu RA, RA, 8
4643    |  sltu AT, RA, TMP2
4644    |   sd CRET1, 0(TMP1)
4645    |  bnez AT, <3
4646    |.   daddiu TMP1, TMP1, 8
4647    |  bnez TMP0, >7
4648    |.  nop
4649    |4:
4650    |  ins_next
4651    |
4652    |5:  // Need to resize array part.
4653    |  load_got lj_tab_reasize
4654    |   sd BASE, L->base
4655    |   sd PC, SAVE_PC
4656    |  move BASE, RD
4657    |  call_intern lj_tab_reasize	// (lua_State *L, GCtab *t, int nasize)
4658    |.  move CARG1, L
4659    |  // Must not reallocate the stack.
4660    |  move RD, BASE
4661    |  b <1
4662    |.  ld BASE, L->base	// Reload BASE for lack of a saved register.
4663    |
4664    |7:  // Possible table write barrier for any value. Skip valiswhite check.
4665    |  barrierback TAB:CARG2, TMP3, TMP0, <4
4666    break;
4667
4668  /* -- Calls and vararg handling ----------------------------------------- */
4669
4670  case BC_CALLM:
4671    |  // RA = base*8, (RB = (nresults+1)*8,) RC = extra_nargs*8
4672    |  decode_RDtoRC8 NARGS8:RC, RD
4673    |  b ->BC_CALL_Z
4674    |.  addu NARGS8:RC, NARGS8:RC, MULTRES
4675    break;
4676  case BC_CALL:
4677    |  // RA = base*8, (RB = (nresults+1)*8,) RC = (nargs+1)*8
4678    |  decode_RDtoRC8 NARGS8:RC, RD
4679    |->BC_CALL_Z:
4680    |  move TMP2, BASE
4681    |  daddu BASE, BASE, RA
4682    |   ld LFUNC:RB, 0(BASE)
4683    |   daddiu BASE, BASE, 16
4684    |  addiu NARGS8:RC, NARGS8:RC, -8
4685    |  checkfunc RB, ->vmeta_call
4686    |  ins_call
4687    break;
4688
4689  case BC_CALLMT:
4690    |  // RA = base*8, (RB = 0,) RC = extra_nargs*8
4691    |  addu NARGS8:RD, NARGS8:RD, MULTRES	// BC_CALLT gets RC from RD.
4692    |  // Fall through. Assumes BC_CALLT follows.
4693    break;
4694  case BC_CALLT:
4695    |  // RA = base*8, (RB = 0,) RC = (nargs+1)*8
4696    |  daddu RA, BASE, RA
4697    |  ld RB, 0(RA)
4698    |   move NARGS8:RC, RD
4699    |    ld TMP1, FRAME_PC(BASE)
4700    |   daddiu RA, RA, 16
4701    |  addiu NARGS8:RC, NARGS8:RC, -8
4702    |  checktp CARG3, RB, -LJ_TFUNC, ->vmeta_callt
4703    |->BC_CALLT_Z:
4704    |  andi TMP0, TMP1, FRAME_TYPE	// Caveat: preserve TMP0 until the 'or'.
4705    |   lbu TMP3, LFUNC:CARG3->ffid
4706    |  bnez TMP0, >7
4707    |.  xori TMP2, TMP1, FRAME_VARG
4708    |1:
4709    |  sd RB, FRAME_FUNC(BASE)		// Copy function down, but keep PC.
4710    |  sltiu AT, TMP3, 2		// (> FF_C) Calling a fast function?
4711    |  move TMP2, BASE
4712    |  move RB, CARG3
4713    |  beqz NARGS8:RC, >3
4714    |.  move TMP3, NARGS8:RC
4715    |2:
4716    |   ld CRET1, 0(RA)
4717    |    daddiu RA, RA, 8
4718    |  addiu TMP3, TMP3, -8
4719    |   sd CRET1, 0(TMP2)
4720    |  bnez TMP3, <2
4721    |.   daddiu TMP2, TMP2, 8
4722    |3:
4723    |  or TMP0, TMP0, AT
4724    |  beqz TMP0, >5
4725    |.  nop
4726    |4:
4727    |  ins_callt
4728    |
4729    |5:  // Tailcall to a fast function with a Lua frame below.
4730    |  lw INS, -4(TMP1)
4731    |  decode_RA8a RA, INS
4732    |  decode_RA8b RA
4733    |  dsubu TMP1, BASE, RA
4734    |  ld TMP1, -32(TMP1)
4735    |  cleartp LFUNC:TMP1
4736    |  ld TMP1, LFUNC:TMP1->pc
4737    |  b <4
4738    |.  ld KBASE, PC2PROTO(k)(TMP1)	// Need to prepare KBASE.
4739    |
4740    |7:  // Tailcall from a vararg function.
4741    |  andi AT, TMP2, FRAME_TYPEP
4742    |  bnez AT, <1			// Vararg frame below?
4743    |.  dsubu TMP2, BASE, TMP2		// Relocate BASE down.
4744    |  move BASE, TMP2
4745    |  ld TMP1, FRAME_PC(TMP2)
4746    |  b <1
4747    |.  andi TMP0, TMP1, FRAME_TYPE
4748    break;
4749
4750  case BC_ITERC:
4751    |  // RA = base*8, (RB = (nresults+1)*8, RC = (nargs+1)*8 ((2+1)*8))
4752    |  move TMP2, BASE			// Save old BASE fir vmeta_call.
4753    |  daddu BASE, BASE, RA
4754    |  ld RB, -24(BASE)
4755    |   ld CARG1, -16(BASE)
4756    |    ld CARG2, -8(BASE)
4757    |  li NARGS8:RC, 16			// Iterators get 2 arguments.
4758    |  sd RB, 0(BASE)			// Copy callable.
4759    |   sd CARG1, 16(BASE)		// Copy state.
4760    |    sd CARG2, 24(BASE)		// Copy control var.
4761    |   daddiu BASE, BASE, 16
4762    |  checkfunc RB, ->vmeta_call
4763    |  ins_call
4764    break;
4765
4766  case BC_ITERN:
4767    |.if JIT and ENDIAN_LE
4768    |  hotloop
4769    |.endif
4770    |->vm_IITERN:
4771    |  // RA = base*8, (RB = (nresults+1)*8, RC = (nargs+1)*8 (2+1)*8)
4772    |  daddu RA, BASE, RA
4773    |  ld TAB:RB, -16(RA)
4774    |   lw RC, -8+LO(RA)		// Get index from control var.
4775    |  cleartp TAB:RB
4776    |   daddiu PC, PC, 4
4777    |  lw TMP0, TAB:RB->asize
4778    |   ld TMP1, TAB:RB->array
4779    |  dsll CARG3, TISNUM, 47
4780    |1:  // Traverse array part.
4781    |  sltu AT, RC, TMP0
4782    |  beqz AT, >5			// Index points after array part?
4783    |.  sll TMP3, RC, 3
4784    |  daddu TMP3, TMP1, TMP3
4785    |  ld CARG1, 0(TMP3)
4786    |     lhu RD, -4+OFS_RD(PC)
4787    |   or TMP2, RC, CARG3
4788    |  beq CARG1, TISNIL, <1		// Skip holes in array part.
4789    |.  addiu RC, RC, 1
4790    |   sd TMP2, 0(RA)
4791    |  sd CARG1, 8(RA)
4792    |     lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
4793    |     decode_RD4b RD
4794    |     daddu RD, RD, TMP3
4795    |   sw RC, -8+LO(RA)		// Update control var.
4796    |     daddu PC, PC, RD
4797    |3:
4798    |  ins_next
4799    |
4800    |5:  // Traverse hash part.
4801    |  lw TMP1, TAB:RB->hmask
4802    |  subu RC, RC, TMP0
4803    |   ld TMP2, TAB:RB->node
4804    |6:
4805    |  sltu AT, TMP1, RC		// End of iteration? Branch to ITERL+1.
4806    |  bnez AT, <3
4807    |.  sll TMP3, RC, 5
4808    |   sll RB, RC, 3
4809    |   subu TMP3, TMP3, RB
4810    |  daddu NODE:TMP3, TMP3, TMP2
4811    |  ld CARG1, 0(NODE:TMP3)
4812    |     lhu RD, -4+OFS_RD(PC)
4813    |  beq CARG1, TISNIL, <6		// Skip holes in hash part.
4814    |.  addiu RC, RC, 1
4815    |  ld CARG2, NODE:TMP3->key
4816    |     lui TMP3, (-(BCBIAS_J*4 >> 16) & 65535)
4817    |  sd CARG1, 8(RA)
4818    |    addu RC, RC, TMP0
4819    |     decode_RD4b RD
4820    |     addu RD, RD, TMP3
4821    |  sd CARG2, 0(RA)
4822    |     daddu PC, PC, RD
4823    |  b <3
4824    |.  sw RC, -8+LO(RA)		// Update control var.
4825    break;
4826
4827  case BC_ISNEXT:
4828    |  // RA = base*8, RD = target (points to ITERN)
4829    |  daddu RA, BASE, RA
4830    |    srl TMP0, RD, 1
4831    |  ld CFUNC:CARG1, -24(RA)
4832    |    daddu TMP0, PC, TMP0
4833    |   ld CARG2, -16(RA)
4834    |   ld CARG3, -8(RA)
4835    |    lui TMP2, (-(BCBIAS_J*4 >> 16) & 65535)
4836    |  checkfunc CFUNC:CARG1, >5
4837    |  gettp CARG2, CARG2
4838    |  daddiu CARG2, CARG2, -LJ_TTAB
4839    |  lbu TMP1, CFUNC:CARG1->ffid
4840    |  daddiu CARG3, CARG3, -LJ_TNIL
4841    |  or AT, CARG2, CARG3
4842    |  daddiu TMP1, TMP1, -FF_next_N
4843    |  or AT, AT, TMP1
4844    |  bnez AT, >5
4845    |.  lui TMP1, (LJ_KEYINDEX >> 16)
4846    |  daddu PC, TMP0, TMP2
4847    |  ori TMP1, TMP1, (LJ_KEYINDEX & 0xffff)
4848    |  dsll TMP1, TMP1, 32
4849    |  sd TMP1, -8(RA)
4850    |1:
4851    |  ins_next
4852    |5:  // Despecialize bytecode if any of the checks fail.
4853    |  li TMP3, BC_JMP
4854    |   li TMP1, BC_ITERC
4855    |  sb TMP3, -4+OFS_OP(PC)
4856    |   daddu PC, TMP0, TMP2
4857    |.if JIT
4858    |  lb TMP0, OFS_OP(PC)
4859    |  li AT, BC_ITERN
4860    |  bne TMP0, AT, >6
4861    |.  lhu TMP2, OFS_RD(PC)
4862    |.endif
4863    |  b <1
4864    |.  sb TMP1, OFS_OP(PC)
4865    |.if JIT
4866    |6:  // Unpatch JLOOP.
4867    |  ld TMP0, DISPATCH_J(trace)(DISPATCH)
4868    |   sll TMP2, TMP2, 3
4869    |  daddu TMP0, TMP0, TMP2
4870    |  ld TRACE:TMP2, 0(TMP0)
4871    |  lw TMP0, TRACE:TMP2->startins
4872    |   li AT, -256
4873    |  and TMP0, TMP0, AT
4874    |  or TMP0, TMP0, TMP1
4875    |  b <1
4876    |.  sw TMP0, 0(PC)
4877    |.endif
4878    break;
4879
4880  case BC_VARG:
4881    |  // RA = base*8, RB = (nresults+1)*8, RC = numparams*8
4882    |  ld TMP0, FRAME_PC(BASE)
4883    |  decode_RDtoRC8 RC, RD
4884    |   decode_RB8a RB, INS
4885    |  daddu RC, BASE, RC
4886    |   decode_RB8b RB
4887    |   daddu RA, BASE, RA
4888    |  daddiu RC, RC, FRAME_VARG
4889    |   daddu TMP2, RA, RB
4890    |  daddiu TMP3, BASE, -16		// TMP3 = vtop
4891    |  dsubu RC, RC, TMP0		// RC = vbase
4892    |  // Note: RC may now be even _above_ BASE if nargs was < numparams.
4893    |  beqz RB, >5			// Copy all varargs?
4894    |.  dsubu TMP1, TMP3, RC
4895    |  daddiu TMP2, TMP2, -16
4896    |1:  // Copy vararg slots to destination slots.
4897    |  ld CARG1, 0(RC)
4898    |  sltu AT, RC, TMP3
4899    |    daddiu RC, RC, 8
4900    |.if MIPSR6
4901    |  selnez CARG1, CARG1, AT
4902    |  seleqz AT, TISNIL, AT
4903    |  or CARG1, CARG1, AT
4904    |.else
4905    |  movz CARG1, TISNIL, AT
4906    |.endif
4907    |  sd CARG1, 0(RA)
4908    |  sltu AT, RA, TMP2
4909    |  bnez AT, <1
4910    |.   daddiu RA, RA, 8
4911    |3:
4912    |  ins_next
4913    |
4914    |5:  // Copy all varargs.
4915    |  ld TMP0, L->maxstack
4916    |  blez TMP1, <3			// No vararg slots?
4917    |.  li MULTRES, 8			// MULTRES = (0+1)*8
4918    |  daddu TMP2, RA, TMP1
4919    |  sltu AT, TMP0, TMP2
4920    |  bnez AT, >7
4921    |.  daddiu MULTRES, TMP1, 8
4922    |6:
4923    |  ld CRET1, 0(RC)
4924    |   daddiu RC, RC, 8
4925    |  sd CRET1, 0(RA)
4926    |  sltu AT, RC, TMP3
4927    |  bnez AT, <6			// More vararg slots?
4928    |.  daddiu RA, RA, 8
4929    |  b <3
4930    |.  nop
4931    |
4932    |7:  // Grow stack for varargs.
4933    |  load_got lj_state_growstack
4934    |   sd RA, L->top
4935    |  dsubu RA, RA, BASE
4936    |   sd BASE, L->base
4937    |  dsubu BASE, RC, BASE		// Need delta, because BASE may change.
4938    |   sd PC, SAVE_PC
4939    |  srl CARG2, TMP1, 3
4940    |  call_intern lj_state_growstack	// (lua_State *L, int n)
4941    |.  move CARG1, L
4942    |  move RC, BASE
4943    |  ld BASE, L->base
4944    |  daddu RA, BASE, RA
4945    |  daddu RC, BASE, RC
4946    |  b <6
4947    |.  daddiu TMP3, BASE, -16
4948    break;
4949
4950  /* -- Returns ----------------------------------------------------------- */
4951
4952  case BC_RETM:
4953    |  // RA = results*8, RD = extra_nresults*8
4954    |  addu RD, RD, MULTRES		// MULTRES >= 8, so RD >= 8.
4955    |  // Fall through. Assumes BC_RET follows.
4956    break;
4957
4958  case BC_RET:
4959    |  // RA = results*8, RD = (nresults+1)*8
4960    |  ld PC, FRAME_PC(BASE)
4961    |   daddu RA, BASE, RA
4962    |    move MULTRES, RD
4963    |1:
4964    |  andi TMP0, PC, FRAME_TYPE
4965    |  bnez TMP0, ->BC_RETV_Z
4966    |.  xori TMP1, PC, FRAME_VARG
4967    |
4968    |->BC_RET_Z:
4969    |  // BASE = base, RA = resultptr, RD = (nresults+1)*8, PC = return
4970    |   lw INS, -4(PC)
4971    |    daddiu TMP2, BASE, -16
4972    |    daddiu RC, RD, -8
4973    |  decode_RA8a TMP0, INS
4974    |   decode_RB8a RB, INS
4975    |  decode_RA8b TMP0
4976    |   decode_RB8b RB
4977    |   daddu TMP3, TMP2, RB
4978    |  beqz RC, >3
4979    |.  dsubu BASE, TMP2, TMP0
4980    |2:
4981    |   ld CRET1, 0(RA)
4982    |    daddiu RA, RA, 8
4983    |  daddiu RC, RC, -8
4984    |   sd CRET1, 0(TMP2)
4985    |  bnez RC, <2
4986    |.   daddiu TMP2, TMP2, 8
4987    |3:
4988    |  daddiu TMP3, TMP3, -8
4989    |5:
4990    |  sltu AT, TMP2, TMP3
4991    |  bnez AT, >6
4992    |.  ld LFUNC:TMP1, FRAME_FUNC(BASE)
4993    |  ins_next1
4994    |  cleartp LFUNC:TMP1
4995    |  ld TMP1, LFUNC:TMP1->pc
4996    |  ld KBASE, PC2PROTO(k)(TMP1)
4997    |  ins_next2
4998    |
4999    |6:  // Fill up results with nil.
5000    |  sd TISNIL, 0(TMP2)
5001    |  b <5
5002    |.  daddiu TMP2, TMP2, 8
5003    |
5004    |->BC_RETV_Z:  // Non-standard return case.
5005    |  andi TMP2, TMP1, FRAME_TYPEP
5006    |  bnez TMP2, ->vm_return
5007    |.  nop
5008    |  // Return from vararg function: relocate BASE down.
5009    |  dsubu BASE, BASE, TMP1
5010    |  b <1
5011    |.  ld PC, FRAME_PC(BASE)
5012    break;
5013
5014  case BC_RET0: case BC_RET1:
5015    |  // RA = results*8, RD = (nresults+1)*8
5016    |  ld PC, FRAME_PC(BASE)
5017    |   daddu RA, BASE, RA
5018    |    move MULTRES, RD
5019    |  andi TMP0, PC, FRAME_TYPE
5020    |  bnez TMP0, ->BC_RETV_Z
5021    |.  xori TMP1, PC, FRAME_VARG
5022    |  lw INS, -4(PC)
5023    |   daddiu TMP2, BASE, -16
5024    if (op == BC_RET1) {
5025      |  ld CRET1, 0(RA)
5026    }
5027    |  decode_RB8a RB, INS
5028    |   decode_RA8a RA, INS
5029    |  decode_RB8b RB
5030    |   decode_RA8b RA
5031    |   dsubu BASE, TMP2, RA
5032    if (op == BC_RET1) {
5033      |  sd CRET1, 0(TMP2)
5034    }
5035    |5:
5036    |  sltu AT, RD, RB
5037    |  bnez AT, >6
5038    |.  ld TMP1, FRAME_FUNC(BASE)
5039    |  ins_next1
5040    |  cleartp LFUNC:TMP1
5041    |  ld TMP1, LFUNC:TMP1->pc
5042    |  ld KBASE, PC2PROTO(k)(TMP1)
5043    |  ins_next2
5044    |
5045    |6:  // Fill up results with nil.
5046    |  daddiu TMP2, TMP2, 8
5047    |  daddiu RD, RD, 8
5048    |  b <5
5049    if (op == BC_RET1) {
5050      |.  sd TISNIL, 0(TMP2)
5051    } else {
5052      |.  sd TISNIL, -8(TMP2)
5053    }
5054    break;
5055
5056  /* -- Loops and branches ------------------------------------------------ */
5057
5058  case BC_FORL:
5059    |.if JIT
5060    |  hotloop
5061    |.endif
5062    |  // Fall through. Assumes BC_IFORL follows.
5063    break;
5064
5065  case BC_JFORI:
5066  case BC_JFORL:
5067#if !LJ_HASJIT
5068    break;
5069#endif
5070  case BC_FORI:
5071  case BC_IFORL:
5072    |  // RA = base*8, RD = target (after end of loop or start of loop)
5073    vk = (op == BC_IFORL || op == BC_JFORL);
5074    |  daddu RA, BASE, RA
5075    |  ld CARG1, FORL_IDX*8(RA)		// IDX CARG1 - CARG3 type
5076    |  gettp CARG3, CARG1
5077    if (op != BC_JFORL) {
5078      |  srl RD, RD, 1
5079      |  lui TMP2, (-(BCBIAS_J*4 >> 16) & 65535)
5080      |  daddu TMP2, RD, TMP2
5081    }
5082    if (!vk) {
5083      |  ld CARG2, FORL_STOP*8(RA)	// STOP CARG2 - CARG4 type
5084      |  ld CRET1, FORL_STEP*8(RA)	// STEP CRET1 - CRET2 type
5085      |  gettp CARG4, CARG2
5086      |  bne CARG3, TISNUM, >5
5087      |.  gettp CRET2, CRET1
5088      |  bne CARG4, TISNUM, ->vmeta_for
5089      |.  sextw CARG3, CARG1
5090      |  bne CRET2, TISNUM, ->vmeta_for
5091      |.  sextw CARG2, CARG2
5092      |  dext AT, CRET1, 31, 0
5093      |  slt CRET1, CARG2, CARG3
5094      |  slt TMP1, CARG3, CARG2
5095      |.if MIPSR6
5096      |  selnez TMP1, TMP1, AT
5097      |  seleqz CRET1, CRET1, AT
5098      |  or CRET1, CRET1, TMP1
5099      |.else
5100      |  movn CRET1, TMP1, AT
5101      |.endif
5102    } else {
5103      |  bne CARG3, TISNUM, >5
5104      |.  ld CARG2, FORL_STEP*8(RA)	// STEP CARG2 - CARG4 type
5105      |    ld CRET1, FORL_STOP*8(RA)	// STOP CRET1 - CRET2 type
5106      |  sextw TMP3, CARG1
5107      |   sextw CARG2, CARG2
5108      |    sextw CRET1, CRET1
5109      |  addu CARG1, TMP3, CARG2
5110      |  xor TMP0, CARG1, TMP3
5111      |  xor TMP1, CARG1, CARG2
5112      |  and TMP0, TMP0, TMP1
5113      |  slt TMP1, CARG1, CRET1
5114      |  slt CRET1, CRET1, CARG1
5115      |  slt AT, CARG2, r0
5116      |   slt TMP0, TMP0, r0		// ((y^a) & (y^b)) < 0: overflow.
5117      |.if MIPSR6
5118      |  selnez TMP1, TMP1, AT
5119      |  seleqz CRET1, CRET1, AT
5120      |  or CRET1, CRET1, TMP1
5121      |.else
5122      |  movn CRET1, TMP1, AT
5123      |.endif
5124      |   or CRET1, CRET1, TMP0
5125      |  zextw CARG1, CARG1
5126      |  settp CARG1, TISNUM
5127    }
5128    |1:
5129    if (op == BC_FORI) {
5130      |.if MIPSR6
5131      |  selnez TMP2, TMP2, CRET1
5132      |.else
5133      |  movz TMP2, r0, CRET1
5134      |.endif
5135      |  daddu PC, PC, TMP2
5136    } else if (op == BC_JFORI) {
5137      |  daddu PC, PC, TMP2
5138      |  lhu RD, -4+OFS_RD(PC)
5139    } else if (op == BC_IFORL) {
5140      |.if MIPSR6
5141      |  seleqz TMP2, TMP2, CRET1
5142      |.else
5143      |  movn TMP2, r0, CRET1
5144      |.endif
5145      |  daddu PC, PC, TMP2
5146    }
5147    if (vk) {
5148      |  sd CARG1, FORL_IDX*8(RA)
5149    }
5150    |  ins_next1
5151    |  sd CARG1, FORL_EXT*8(RA)
5152    |2:
5153    if (op == BC_JFORI) {
5154      |  beqz CRET1, =>BC_JLOOP
5155      |.  decode_RD8b RD
5156    } else if (op == BC_JFORL) {
5157      |  beqz CRET1, =>BC_JLOOP
5158    }
5159    |  ins_next2
5160    |
5161    |5:  // FP loop.
5162    |.if FPU
5163    if (!vk) {
5164      |  ldc1 f0, FORL_IDX*8(RA)
5165      |   ldc1 f2, FORL_STOP*8(RA)
5166      |  sltiu TMP0, CARG3, LJ_TISNUM
5167      |  sltiu TMP1, CARG4, LJ_TISNUM
5168      |  sltiu AT, CRET2, LJ_TISNUM
5169      |   ld TMP3, FORL_STEP*8(RA)
5170      |  and TMP0, TMP0, TMP1
5171      |  and AT, AT, TMP0
5172      |  beqz AT, ->vmeta_for
5173      |.  slt TMP3, TMP3, r0
5174      |.if MIPSR6
5175      |   dmtc1 TMP3, FTMP2
5176      |  cmp.lt.d FTMP0, f0, f2
5177      |  cmp.lt.d FTMP1, f2, f0
5178      |  sel.d FTMP2, FTMP1, FTMP0
5179      |  b <1
5180      |.  dmfc1 CRET1, FTMP2
5181      |.else
5182      |  c.ole.d 0, f0, f2
5183      |  c.ole.d 1, f2, f0
5184      |  li CRET1, 1
5185      |  movt CRET1, r0, 0
5186      |  movt AT, r0, 1
5187      |  b <1
5188      |.  movn CRET1, AT, TMP3
5189      |.endif
5190    } else {
5191      |  ldc1 f0, FORL_IDX*8(RA)
5192      |   ldc1 f4, FORL_STEP*8(RA)
5193      |    ldc1 f2, FORL_STOP*8(RA)
5194      |   ld TMP3, FORL_STEP*8(RA)
5195      |  add.d f0, f0, f4
5196      |.if MIPSR6
5197      |   slt TMP3, TMP3, r0
5198      |   dmtc1 TMP3, FTMP2
5199      |  cmp.lt.d FTMP0, f0, f2
5200      |  cmp.lt.d FTMP1, f2, f0
5201      |  sel.d FTMP2, FTMP1, FTMP0
5202      |  dmfc1 CRET1, FTMP2
5203      if (op == BC_IFORL) {
5204	|  seleqz TMP2, TMP2, CRET1
5205	|  daddu PC, PC, TMP2
5206      }
5207      |.else
5208      |  c.ole.d 0, f0, f2
5209      |  c.ole.d 1, f2, f0
5210      |   slt TMP3, TMP3, r0
5211      |  li CRET1, 1
5212      |  li AT, 1
5213      |  movt CRET1, r0, 0
5214      |  movt AT, r0, 1
5215      |  movn CRET1, AT, TMP3
5216      if (op == BC_IFORL) {
5217	|  movn TMP2, r0, CRET1
5218	|  daddu PC, PC, TMP2
5219      }
5220      |.endif
5221      |  sdc1 f0, FORL_IDX*8(RA)
5222      |  ins_next1
5223      |  b <2
5224      |.  sdc1 f0, FORL_EXT*8(RA)
5225    }
5226    |.else
5227    if (!vk) {
5228      |  sltiu TMP0, CARG3, LJ_TISNUM
5229      |  sltiu TMP1, CARG4, LJ_TISNUM
5230      |  sltiu AT, CRET2, LJ_TISNUM
5231      |  and TMP0, TMP0, TMP1
5232      |  and AT, AT, TMP0
5233      |  beqz AT, ->vmeta_for
5234      |.  nop
5235      |  bal ->vm_sfcmpolex
5236      |.  lw TMP3, FORL_STEP*8+HI(RA)
5237      |  b <1
5238      |.  nop
5239    } else {
5240      |  load_got __adddf3
5241      |  call_extern
5242      |.  sw TMP2, TMPD
5243      |  ld CARG2, FORL_STOP*8(RA)
5244      |  move CARG1, CRET1
5245      if ( op == BC_JFORL ) {
5246	|  lhu RD, -4+OFS_RD(PC)
5247	|  decode_RD8b RD
5248      }
5249      |  bal ->vm_sfcmpolex
5250      |.  lw TMP3, FORL_STEP*8+HI(RA)
5251      |  b <1
5252      |.  lw TMP2, TMPD
5253    }
5254    |.endif
5255    break;
5256
5257  case BC_ITERL:
5258    |.if JIT
5259    |  hotloop
5260    |.endif
5261    |  // Fall through. Assumes BC_IITERL follows.
5262    break;
5263
5264  case BC_JITERL:
5265#if !LJ_HASJIT
5266    break;
5267#endif
5268  case BC_IITERL:
5269    |  // RA = base*8, RD = target
5270    |  daddu RA, BASE, RA
5271    |  ld TMP1, 0(RA)
5272    |  beq TMP1, TISNIL, >1		// Stop if iterator returned nil.
5273    |.  nop
5274    if (op == BC_JITERL) {
5275      |  b =>BC_JLOOP
5276      |.  sd TMP1, -8(RA)
5277    } else {
5278      |  branch_RD			// Otherwise save control var + branch.
5279      |  sd TMP1, -8(RA)
5280    }
5281    |1:
5282    |  ins_next
5283    break;
5284
5285  case BC_LOOP:
5286    |  // RA = base*8, RD = target (loop extent)
5287    |  // Note: RA/RD is only used by trace recorder to determine scope/extent
5288    |  // This opcode does NOT jump, it's only purpose is to detect a hot loop.
5289    |.if JIT
5290    |  hotloop
5291    |.endif
5292    |  // Fall through. Assumes BC_ILOOP follows.
5293    break;
5294
5295  case BC_ILOOP:
5296    |  // RA = base*8, RD = target (loop extent)
5297    |  ins_next
5298    break;
5299
5300  case BC_JLOOP:
5301    |.if JIT
5302    |  // RA = base*8 (ignored), RD = traceno*8
5303    |  ld TMP1, DISPATCH_J(trace)(DISPATCH)
5304    |   li AT, 0
5305    |  daddu TMP1, TMP1, RD
5306    |  // Traces on MIPS don't store the trace number, so use 0.
5307    |   sd AT, DISPATCH_GL(vmstate)(DISPATCH)
5308    |  ld TRACE:TMP2, 0(TMP1)
5309    |   sd BASE, DISPATCH_GL(jit_base)(DISPATCH)
5310    |  ld TMP2, TRACE:TMP2->mcode
5311    |   sd L, DISPATCH_GL(tmpbuf.L)(DISPATCH)
5312    |  jr TMP2
5313    |.  daddiu JGL, DISPATCH, GG_DISP2G+32768
5314    |.endif
5315    break;
5316
5317  case BC_JMP:
5318    |  // RA = base*8 (only used by trace recorder), RD = target
5319    |  branch_RD
5320    |  ins_next
5321    break;
5322
5323  /* -- Function headers -------------------------------------------------- */
5324
5325  case BC_FUNCF:
5326    |.if JIT
5327    |  hotcall
5328    |.endif
5329  case BC_FUNCV:  /* NYI: compiled vararg functions. */
5330    |  // Fall through. Assumes BC_IFUNCF/BC_IFUNCV follow.
5331    break;
5332
5333  case BC_JFUNCF:
5334#if !LJ_HASJIT
5335    break;
5336#endif
5337  case BC_IFUNCF:
5338    |  // BASE = new base, RA = BASE+framesize*8, RB = LFUNC, RC = nargs*8
5339    |  ld TMP2, L->maxstack
5340    |   lbu TMP1, -4+PC2PROTO(numparams)(PC)
5341    |    ld KBASE, -4+PC2PROTO(k)(PC)
5342    |  sltu AT, TMP2, RA
5343    |  bnez AT, ->vm_growstack_l
5344    |.  sll TMP1, TMP1, 3
5345    if (op != BC_JFUNCF) {
5346      |  ins_next1
5347    }
5348    |2:
5349    |  sltu AT, NARGS8:RC, TMP1		// Check for missing parameters.
5350    |  bnez AT, >3
5351    |.  daddu AT, BASE, NARGS8:RC
5352    if (op == BC_JFUNCF) {
5353      |  decode_RD8a RD, INS
5354      |  b =>BC_JLOOP
5355      |.  decode_RD8b RD
5356    } else {
5357      |  ins_next2
5358    }
5359    |
5360    |3:  // Clear missing parameters.
5361    |  sd TISNIL, 0(AT)
5362    |  b <2
5363    |.  addiu NARGS8:RC, NARGS8:RC, 8
5364    break;
5365
5366  case BC_JFUNCV:
5367#if !LJ_HASJIT
5368    break;
5369#endif
5370    |  NYI  // NYI: compiled vararg functions
5371    break;  /* NYI: compiled vararg functions. */
5372
5373  case BC_IFUNCV:
5374    |  // BASE = new base, RA = BASE+framesize*8, RB = LFUNC, RC = nargs*8
5375    |   li TMP0, LJ_TFUNC
5376    |   daddu TMP1, BASE, RC
5377    |  ld TMP2, L->maxstack
5378    |   settp LFUNC:RB, TMP0
5379    |  daddu TMP0, RA, RC
5380    |   sd LFUNC:RB, 0(TMP1)		// Store (tagged) copy of LFUNC.
5381    |   daddiu TMP3, RC, 16+FRAME_VARG
5382    |  sltu AT, TMP0, TMP2
5383    |    ld KBASE, -4+PC2PROTO(k)(PC)
5384    |  beqz AT, ->vm_growstack_l
5385    |.  sd TMP3, 8(TMP1)		// Store delta + FRAME_VARG.
5386    |  lbu TMP2, -4+PC2PROTO(numparams)(PC)
5387    |   move RA, BASE
5388    |   move RC, TMP1
5389    |  ins_next1
5390    |  beqz TMP2, >3
5391    |.  daddiu BASE, TMP1, 16
5392    |1:
5393    |  ld TMP0, 0(RA)
5394    |  sltu AT, RA, RC			// Less args than parameters?
5395    |  move CARG1, TMP0
5396    |.if MIPSR6
5397    |  selnez TMP0, TMP0, AT
5398    |  seleqz TMP3, TISNIL, AT
5399    |  or TMP0, TMP0, TMP3
5400    |  seleqz TMP3, CARG1, AT
5401    |  selnez CARG1, TISNIL, AT
5402    |  or CARG1, CARG1, TMP3
5403    |.else
5404    |  movz TMP0, TISNIL, AT		// Clear missing parameters.
5405    |  movn CARG1, TISNIL, AT		// Clear old fixarg slot (help the GC).
5406    |.endif
5407    |    addiu TMP2, TMP2, -1
5408    |  sd TMP0, 16(TMP1)
5409    |    daddiu TMP1, TMP1, 8
5410    |  sd CARG1, 0(RA)
5411    |  bnez TMP2, <1
5412    |.   daddiu RA, RA, 8
5413    |3:
5414    |  ins_next2
5415    break;
5416
5417  case BC_FUNCC:
5418  case BC_FUNCCW:
5419    |  // BASE = new base, RA = BASE+framesize*8, RB = CFUNC, RC = nargs*8
5420    if (op == BC_FUNCC) {
5421      |  ld CFUNCADDR, CFUNC:RB->f
5422    } else {
5423      |  ld CFUNCADDR, DISPATCH_GL(wrapf)(DISPATCH)
5424    }
5425    |  daddu TMP1, RA, NARGS8:RC
5426    |  ld TMP2, L->maxstack
5427    |   daddu RC, BASE, NARGS8:RC
5428    |  sd BASE, L->base
5429    |  sltu AT, TMP2, TMP1
5430    |   sd RC, L->top
5431    |    li_vmstate C
5432    if (op == BC_FUNCCW) {
5433      |  ld CARG2, CFUNC:RB->f
5434    }
5435    |  bnez AT, ->vm_growstack_c	// Need to grow stack.
5436    |.  move CARG1, L
5437    |  jalr CFUNCADDR			// (lua_State *L [, lua_CFunction f])
5438    |.   st_vmstate
5439    |  // Returns nresults.
5440    |  ld BASE, L->base
5441    |   sll RD, CRET1, 3
5442    |  ld TMP1, L->top
5443    |    li_vmstate INTERP
5444    |  ld PC, FRAME_PC(BASE)		// Fetch PC of caller.
5445    |   dsubu RA, TMP1, RD		// RA = L->top - nresults*8
5446    |    sd L, DISPATCH_GL(cur_L)(DISPATCH)
5447    |  b ->vm_returnc
5448    |.   st_vmstate
5449    break;
5450
5451  /* ---------------------------------------------------------------------- */
5452
5453  default:
5454    fprintf(stderr, "Error: undefined opcode BC_%s\n", bc_names[op]);
5455    exit(2);
5456    break;
5457  }
5458}
5459
5460static int build_backend(BuildCtx *ctx)
5461{
5462  int op;
5463
5464  dasm_growpc(Dst, BC__MAX);
5465
5466  build_subroutines(ctx);
5467
5468  |.code_op
5469  for (op = 0; op < BC__MAX; op++)
5470    build_ins(ctx, (BCOp)op, op);
5471
5472  return BC__MAX;
5473}
5474
5475/* Emit pseudo frame-info for all assembler functions. */
5476static void emit_asm_debug(BuildCtx *ctx)
5477{
5478  int fcofs = (int)((uint8_t *)ctx->glob[GLOB_vm_ffi_call] - ctx->code);
5479  int i;
5480  switch (ctx->mode) {
5481  case BUILD_elfasm:
5482    fprintf(ctx->fp, "\t.section .debug_frame,\"\",@progbits\n");
5483    fprintf(ctx->fp,
5484	".Lframe0:\n"
5485	"\t.4byte .LECIE0-.LSCIE0\n"
5486	".LSCIE0:\n"
5487	"\t.4byte 0xffffffff\n"
5488	"\t.byte 0x1\n"
5489	"\t.string \"\"\n"
5490	"\t.uleb128 0x1\n"
5491	"\t.sleb128 -4\n"
5492	"\t.byte 31\n"
5493	"\t.byte 0xc\n\t.uleb128 29\n\t.uleb128 0\n"
5494	"\t.align 2\n"
5495	".LECIE0:\n\n");
5496    fprintf(ctx->fp,
5497	".LSFDE0:\n"
5498	"\t.4byte .LEFDE0-.LASFDE0\n"
5499	".LASFDE0:\n"
5500	"\t.4byte .Lframe0\n"
5501	"\t.8byte .Lbegin\n"
5502	"\t.8byte %d\n"
5503	"\t.byte 0xe\n\t.uleb128 %d\n"
5504	"\t.byte 0x9f\n\t.sleb128 2*5\n"
5505	"\t.byte 0x9e\n\t.sleb128 2*6\n",
5506	fcofs, CFRAME_SIZE);
5507    for (i = 23; i >= 16; i--)
5508      fprintf(ctx->fp, "\t.byte %d\n\t.uleb128 %d\n", 0x80+i, 2*(30-i));
5509#if !LJ_SOFTFP
5510    for (i = 31; i >= 24; i--)
5511      fprintf(ctx->fp, "\t.byte %d\n\t.uleb128 %d\n", 0x80+32+i, 2*(46-i));
5512#endif
5513    fprintf(ctx->fp,
5514	"\t.align 2\n"
5515	".LEFDE0:\n\n");
5516#if LJ_HASFFI
5517    fprintf(ctx->fp,
5518	".LSFDE1:\n"
5519	"\t.4byte .LEFDE1-.LASFDE1\n"
5520	".LASFDE1:\n"
5521	"\t.4byte .Lframe0\n"
5522	"\t.4byte lj_vm_ffi_call\n"
5523	"\t.4byte %d\n"
5524	"\t.byte 0x9f\n\t.uleb128 2*1\n"
5525	"\t.byte 0x90\n\t.uleb128 2*2\n"
5526	"\t.byte 0xd\n\t.uleb128 0x10\n"
5527	"\t.align 2\n"
5528	".LEFDE1:\n\n", (int)ctx->codesz - fcofs);
5529#endif
5530#if !LJ_NO_UNWIND
5531    /* NYI */
5532#endif
5533    break;
5534  default:
5535    break;
5536  }
5537}
5538
5539