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