ARM: Add tostring() fast function.
[luajit-2.0.git] / src / buildvm_arm.dasc
blobbcfc538799bcf026420bba59767d613b05d70053
1 |// Low-level VM code for ARM CPUs.
2 |// Bytecode interpreter, fast functions and helper functions.
3 |// Copyright (C) 2005-2011 Mike Pall. See Copyright Notice in luajit.h
5 |.arch arm
6 |.section code_op, code_sub
8 |.actionlist build_actionlist
9 |.globals GLOB_
10 |.globalnames globnames
11 |.externnames extnames
13 |// Note: The ragged indentation of the instructions is intentional.
14 |//       The starting columns indicate data dependencies.
16 |//-----------------------------------------------------------------------
18 |// Fixed register assignments for the interpreter.
20 |// The following must be C callee-save (but BASE is often refetched).
21 |.define BASE,          r4      // Base of current Lua stack frame.
22 |.define KBASE,         r5      // Constants of current Lua function.
23 |.define PC,            r6      // Next PC.
24 |.define DISPATCH,      r7      // Opcode dispatch table.
25 |.define LREG,          r8      // Register holding lua_State (also in SAVE_L).
26 |.define MASKR8,        r9      // 255*8 constant for fast bytecode decoding.
28 |// The following temporaries are not saved across C calls, except for RA/RC.
29 |.define RA,            r10     // Callee-save.
30 |.define RC,            r11     // Callee-save.
31 |.define RB,            r12
32 |.define OP,            r12     // Overlaps RB, must not be lr.
33 |.define INS,           lr
35 |// Calling conventions. Also used as temporaries.
36 |.define CARG1,         r0
37 |.define CARG2,         r1
38 |.define CARG3,         r2
39 |.define CARG4,         r3
40 |.define CARG12,        r0      // For 1st soft-fp double.
41 |.define CARG34,        r2      // For 2nd soft-fp double.
43 |.define CRET1,         r0
44 |.define CRET2,         r1
46 |// Stack layout while in interpreter. Must match with lj_frame.h.
47 |.define CFRAME_SPACE,  #28
48 |.define SAVE_ERRF,     [sp, #24]
49 |.define SAVE_NRES,     [sp, #20]
50 |.define SAVE_CFRAME,   [sp, #16]
51 |.define SAVE_L,        [sp, #12]
52 |.define SAVE_PC,       [sp, #8]
53 |.define SAVE_MULTRES,  [sp, #4]
54 |.define ARG5,          [sp]
56 |.macro saveregs
57 |  push {r4, r5, r6, r7, r8, r9, r10, r11, lr}
58 |  sub sp, sp, CFRAME_SPACE
59 |.endmacro
60 |.macro restoreregs_ret
61 |  add sp, sp, CFRAME_SPACE
62 |  pop {r4, r5, r6, r7, r8, r9, r10, r11, pc}
63 |.endmacro
65 |// Type definitions. Some of these are only used for documentation.
66 |.type L,               lua_State,      LREG
67 |.type GL,              global_State
68 |.type TVALUE,          TValue
69 |.type GCOBJ,           GCobj
70 |.type STR,             GCstr
71 |.type TAB,             GCtab
72 |.type LFUNC,           GCfuncL
73 |.type CFUNC,           GCfuncC
74 |.type PROTO,           GCproto
75 |.type UPVAL,           GCupval
76 |.type NODE,            Node
77 |.type NARGS8,          int
78 |.type TRACE,           GCtrace
80 |//-----------------------------------------------------------------------
82 |// Trap for not-yet-implemented parts.
83 |.macro NYI; ud; .endmacro
85 |//-----------------------------------------------------------------------
87 |// Access to frame relative to BASE.
88 |.define FRAME_FUNC,    #-8
89 |.define FRAME_PC,      #-4
91 |.macro decode_RA8, dst, ins; and dst, MASKR8, ins, lsr #5; .endmacro
92 |.macro decode_RB8, dst, ins; and dst, MASKR8, ins, lsr #21; .endmacro
93 |.macro decode_RC8, dst, ins; and dst, MASKR8, ins, lsr #13; .endmacro
94 |.macro decode_RD, dst, ins; lsr dst, ins, #16; .endmacro
95 |.macro decode_OP, dst, ins; and dst, ins, #255; .endmacro
97 |// Instruction fetch.
98 |.macro ins_NEXT1
99 |  ldrb OP, [PC]
100 |.endmacro
101 |.macro ins_NEXT2
102 |   ldr INS, [PC], #4
103 |.endmacro
104 |// Instruction decode+dispatch.
105 |.macro ins_NEXT3
106 |  ldr OP, [DISPATCH, OP, lsl #2]
107 |   decode_RA8 RA, INS
108 |   decode_RD RC, INS
109 |  bx OP
110 |.endmacro
111 |.macro ins_NEXT
112 |  ins_NEXT1
113 |  ins_NEXT2
114 |  ins_NEXT3
115 |.endmacro
117 |// Instruction footer.
118 |.if 1
119 |  // Replicated dispatch. Less unpredictable branches, but higher I-Cache use.
120 |  .define ins_next, ins_NEXT
121 |  .define ins_next_, ins_NEXT
122 |  .define ins_next1, ins_NEXT1
123 |  .define ins_next2, ins_NEXT2
124 |  .define ins_next3, ins_NEXT3
125 |.else
126 |  // Common dispatch. Lower I-Cache use, only one (very) unpredictable branch.
127 |  // Affects only certain kinds of benchmarks (and only with -j off).
128 |  .macro ins_next
129 |    b ->ins_next
130 |  .endmacro
131 |  .macro ins_next1
132 |  .endmacro
133 |  .macro ins_next2
134 |  .endmacro
135 |  .macro ins_next3
136 |    b ->ins_next
137 |  .endmacro
138 |  .macro ins_next_
139 |  ->ins_next:
140 |    ins_NEXT
141 |  .endmacro
142 |.endif
144 |// Avoid register name substitution for field name.
145 #define field_pc        pc
147 |// Call decode and dispatch.
148 |.macro ins_callt
149 |  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
150 |  ldr PC, LFUNC:CARG3->field_pc
151 |  ldrb OP, [PC]  // STALL: load PC. early PC.
152 |   ldr INS, [PC], #4
153 |  ldr OP, [DISPATCH, OP, lsl #2]  // STALL: load OP. early OP.
154 |   decode_RA8 RA, INS
155 |   add RA, RA, BASE
156 |  bx OP
157 |.endmacro
159 |.macro ins_call
160 |  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, PC = caller PC
161 |  str PC, [BASE, FRAME_PC]
162 |  ins_callt  // STALL: locked PC.
163 |.endmacro
165 |//-----------------------------------------------------------------------
167 |// Macros to test operand types.
168 |.macro checktp, reg, tp; cmn reg, #-tp; .endmacro
169 |.macro checktpeq, reg, tp; cmneq reg, #-tp; .endmacro
170 |.macro checkstr, reg, target; checktp reg, LJ_TSTR; bne target; .endmacro
171 |.macro checktab, reg, target; checktp reg, LJ_TTAB; bne target; .endmacro
172 |.macro checkfunc, reg, target; checktp reg, LJ_TFUNC; bne target; .endmacro
174 |// Assumes DISPATCH is relative to GL.
175 #define DISPATCH_GL(field)      (GG_DISP2G + (int)offsetof(global_State, field))
176 #define DISPATCH_J(field)       (GG_DISP2J + (int)offsetof(jit_State, field))
178 #define PC2PROTO(field)  ((int)offsetof(GCproto, field)-(int)sizeof(GCproto))
180 |.macro hotloop
181 |  NYI
182 |.endmacro
184 |.macro hotcall
185 |  NYI
186 |.endmacro
188 |// Set current VM state.
189 |.macro mv_vmstate, reg, st; mvn reg, #LJ_VMST_..st; .endmacro
190 |.macro st_vmstate, reg; str reg, [DISPATCH, #DISPATCH_GL(vmstate)]; .endmacro
192 |//-----------------------------------------------------------------------
194 #if !LJ_DUALNUM
195 #error "Only dual-number mode supported for ARM target"
196 #endif
198 /* Generate subroutines used by opcodes and other parts of the VM. */
199 /* The .code_sub section should be last to help static branch prediction. */
200 static void build_subroutines(BuildCtx *ctx)
202   |.code_sub
203   |
204   |//-----------------------------------------------------------------------
205   |//-- Return handling ----------------------------------------------------
206   |//-----------------------------------------------------------------------
207   |
208   |->vm_returnp:
209   |  // See vm_return. Also: RB = previous base.
210   |  tst PC, #FRAME_P
211   |  beq ->cont_dispatch
212   |
213   |  // Return from pcall or xpcall fast func.
214   |  ldr PC, [RB, FRAME_PC]             // Fetch PC of previous frame.
215   |   mvn CARG2, #~LJ_TTRUE
216   |  mov BASE, RB
217   |  // Prepending may overwrite the pcall frame, so do it at the end.
218   |   str CARG2, [RA, FRAME_PC]         // Prepend true to results.
219   |  sub RA, RA, #8
220   |
221   |->vm_returnc:
222   |  add RC, RC, #8                     // RC = (nresults+1)*8.
223   |   ands CARG1, PC, #FRAME_TYPE
224   |  str RC, SAVE_MULTRES
225   |   beq ->BC_RET_Z                    // Handle regular return to Lua.
226   |
227   |->vm_return:
228   |  // BASE = base, RA = resultptr, RC/MULTRES = (nresults+1)*8, PC = return
229   |  // CARG1 = PC & FRAME_TYPE
230   |  bic RB, PC, #FRAME_TYPEP
231   |   cmp CARG1, #FRAME_C
232   |  sub RB, BASE, RB                   // RB = previous base.
233   |   bne ->vm_returnp
234   |
235   |  str RB, L->base
236   |   ldr KBASE, SAVE_NRES
237   |    mv_vmstate CARG4, C
238   |   sub BASE, BASE, #8
239   |  subs CARG3, RC, #8
240   |   lsl KBASE, KBASE, #3              // KBASE = (nresults_wanted+1)*8
241   |    st_vmstate CARG4
242   |  beq >2
243   |1:
244   |  subs CARG3, CARG3, #8
245   |   ldrd CARG12, [RA], #8
246   |   strd CARG12, [BASE], #8
247   |  bne <1
248   |2:
249   |  cmp KBASE, RC                      // More/less results wanted?
250   |  bne >6
251   |3:
252   |  str BASE, L->top                   // Store new top.
253   |
254   |->vm_leave_cp:
255   |  ldr RC, SAVE_CFRAME                // Restore previous C frame.
256   |   mov CRET1, #0                     // Ok return status for vm_pcall.
257   |  str RC, L->cframe
258   |
259   |->vm_leave_unw:
260   |  restoreregs_ret
261   |
262   |6:
263   |  blt >7                             // Less results wanted?
264   |  // More results wanted. Check stack size and fill up results with nil.
265   |  ldr CARG3, L->maxstack
266   |   mvn CARG2, #~LJ_TNIL
267   |  cmp BASE, CARG3
268   |  bhs >8
269   |   str CARG2, [BASE, #4]
270   |  add RC, RC, #8
271   |  add BASE, BASE, #8
272   |  b <2
273   |
274   |7:  // Less results wanted.
275   |  sub CARG1, RC, KBASE
276   |  cmp KBASE, #0                      // LUA_MULTRET+1 case?
277   |  subne BASE, BASE, CARG1            // Either keep top or shrink it.
278   |  b <3
279   |
280   |8:  // Corner case: need to grow stack for filling up results.
281   |  // This can happen if:
282   |  // - A C function grows the stack (a lot).
283   |  // - The GC shrinks the stack in between.
284   |  // - A return back from a lua_call() with (high) nresults adjustment.
285   |  str BASE, L->top                   // Save current top held in BASE (yes).
286   |  mov CARG2, KBASE
287   |  mov CARG1, L
288   |  bl extern lj_state_growstack       // (lua_State *L, int n)
289   |  ldr BASE, L->top                   // Need the (realloced) L->top in BASE.
290   |  b <2
291   |
292   |->vm_unwind_c:                       // Unwind C stack, return from vm_pcall.
293   |  NYI
294   |->vm_unwind_c_eh:                    // Landing pad for external unwinder.
295   |  NYI
296   |
297   |->vm_unwind_ff:                      // Unwind C stack, return from ff pcall.
298   |  NYI
299   |->vm_unwind_ff_eh:                   // Landing pad for external unwinder.
300   |  NYI
301   |
302   |//-----------------------------------------------------------------------
303   |//-- Grow stack for calls -----------------------------------------------
304   |//-----------------------------------------------------------------------
305   |
306   |->vm_growstack_c:                    // Grow stack for C function.
307   |  NYI
308   |
309   |->vm_growstack_l:                    // Grow stack for Lua function.
310   |  NYI
311   |
312   |//-----------------------------------------------------------------------
313   |//-- Entry points into the assembler VM ---------------------------------
314   |//-----------------------------------------------------------------------
315   |
316   |->vm_resume:                         // Setup C frame and resume thread.
317   |  NYI
318   |
319   |->vm_pcall:                          // Setup protected C frame and enter VM.
320   |  // (lua_State *L, TValue *base, int nres1, ptrdiff_t ef)
321   |  saveregs
322   |  mov PC, #FRAME_CP
323   |  str CARG4, SAVE_ERRF
324   |  b >1
325   |
326   |->vm_call:                           // Setup C frame and enter VM.
327   |  // (lua_State *L, TValue *base, int nres1)
328   |  saveregs
329   |  mov PC, #FRAME_C
330   |
331   |1:  // Entry point for vm_pcall above (PC = ftype).
332   |  ldr RC, L:CARG1->cframe
333   |   str CARG3, SAVE_NRES
334   |    mov L, CARG1
335   |   str CARG1, SAVE_L
336   |    mov BASE, CARG2
337   |  str sp, L->cframe                  // Add our C frame to cframe chain.
338   |    ldr DISPATCH, L->glref           // Setup pointer to dispatch table.
339   |   str CARG1, SAVE_PC                // Any value outside of bytecode is ok.
340   |  str RC, SAVE_CFRAME
341   |    add DISPATCH, DISPATCH, #GG_G2DISP
342   |
343   |3:  // Entry point for vm_cpcall/vm_resume (BASE = base, PC = ftype).
344   |  ldr RB, L->base                    // RB = old base (for vmeta_call).
345   |   ldr CARG1, L->top
346   |    mov MASKR8, #255
347   |  add PC, PC, BASE
348   |    lsl MASKR8, MASKR8, #3           // MASKR8 = 255*8.
349   |  sub PC, PC, RB                     // PC = frame delta + frame type
350   |    mv_vmstate CARG2, INTERP
351   |   sub NARGS8:RC, CARG1, BASE
352   |    st_vmstate CARG2
353   |
354   |->vm_call_dispatch:
355   |  // RB = old base, BASE = new base, RC = nargs*8, PC = caller PC
356   |  ldrd CARG34, [BASE, FRAME_FUNC]
357   |  checkfunc CARG4, ->vmeta_call
358   |
359   |->vm_call_dispatch_f:
360   |  ins_call
361   |  // BASE = new base, RC = nargs*8
362   |
363   |->vm_cpcall:                         // Setup protected C frame, call C.
364   |  // (lua_State *L, lua_CFunction func, void *ud, lua_CPFunction cp)
365   |  saveregs
366   |  mov L, CARG1
367   |   ldr RA, L:CARG1->stack
368   |  str CARG1, SAVE_L
369   |   ldr RB, L->top
370   |  str CARG1, SAVE_PC                 // Any value outside of bytecode is ok.
371   |  ldr RC, L->cframe
372   |   sub RA, RA, RB                    // Compute -savestack(L, L->top).
373   |  str sp, L->cframe                  // Add our C frame to cframe chain.
374   |  mov RB, #0
375   |   str RA, SAVE_NRES                 // Neg. delta means cframe w/o frame.
376   |  str RB, SAVE_ERRF                  // No error function.
377   |  str RC, SAVE_CFRAME
378   |  blx CARG4                  // (lua_State *L, lua_CFunction func, void *ud)
379   |   ldr DISPATCH, L->glref            // Setup pointer to dispatch table.
380   |  movs BASE, CRET1
381   |    mov PC, #FRAME_CP
382   |   add DISPATCH, DISPATCH, #GG_G2DISP
383   |  bne <3                             // Else continue with the call.
384   |  b ->vm_leave_cp                    // No base? Just remove C frame.
385   |
386   |//-----------------------------------------------------------------------
387   |//-- Metamethod handling ------------------------------------------------
388   |//-----------------------------------------------------------------------
389   |
390   |//-- Continuation dispatch ----------------------------------------------
391   |
392   |->cont_dispatch:
393   |  NYI
394   |
395   |->cont_cat:
396   |  NYI
397   |
398   |//-- Table indexing metamethods -----------------------------------------
399   |
400   |->vmeta_tgets:
401   |  NYI
402   |
403   |->vmeta_tgetb:
404   |  NYI
405   |
406   |->vmeta_tgetv:
407   |  NYI
408   |
409   |//-----------------------------------------------------------------------
410   |
411   |->vmeta_tsets:
412   |  NYI
413   |
414   |->vmeta_tsetb:
415   |  NYI
416   |
417   |->vmeta_tsetv:
418   |  NYI
419   |
420   |//-- Comparison metamethods ---------------------------------------------
421   |
422   |->vmeta_comp:
423   |  NYI
424   |
425   |->cont_nop:
426   |  ins_next
427   |
428   |->cont_ra:                           // RA = resultptr
429   |  NYI
430   |
431   |->cont_condt:                        // RA = resultptr
432   |  NYI
433   |
434   |->cont_condf:                        // RA = resultptr
435   |  NYI
436   |
437   |->vmeta_equal:
438   |  NYI
439   |
440   |//-- Arithmetic metamethods ---------------------------------------------
441   |
442   |->vmeta_arith_vn:
443   |  decode_RB8 RB, INS
444   |   decode_RC8 RC, INS
445   |  add CARG3, BASE, RB
446   |   add CARG4, KBASE, RC
447   |  b >1
448   |
449   |->vmeta_arith_nv:
450   |  decode_RB8 RB, INS
451   |   decode_RC8 RC, INS
452   |  add CARG4, BASE, RB
453   |   add CARG3, KBASE, RC
454   |  b >1
455   |
456   |->vmeta_unm:
457   |  add CARG3, BASE, RC
458   |  add CARG4, BASE, RC
459   |  b >1
460   |
461   |->vmeta_arith_vv:
462   |  decode_RB8 RB, INS
463   |   decode_RC8 RC, INS
464   |  add CARG3, BASE, RB
465   |   add CARG4, BASE, RC
466   |1:
467   |  decode_OP OP, INS
468   |   add CARG2, BASE, RA
469   |    str BASE, L->base
470   |   mov CARG1, L
471   |    str PC, SAVE_PC
472   |  str OP, ARG5
473   |  bl extern lj_meta_arith  // (lua_State *L, TValue *ra,*rb,*rc, BCReg op)
474   |  // Returns NULL (finished) or TValue * (metamethod).
475   |  cmp CRET1, #0
476   |  beq ->cont_nop
477   |
478   |  // Call metamethod for binary op.
479   |->vmeta_binop:
480   |  // BASE = old base, CRET1 = new base, stack = cont/func/o1/o2
481   |  NYI
482   |
483   |->vmeta_len:
484   |  NYI
485   |
486   |//-- Call metamethod ----------------------------------------------------
487   |
488   |->vmeta_call:                        // Resolve and call __call metamethod.
489   |  NYI
490   |
491   |->vmeta_callt:                       // Resolve __call for BC_CALLT.
492   |  NYI
493   |
494   |//-- Argument coercion for 'for' statement ------------------------------
495   |
496   |->vmeta_for:
497   |  mov CARG1, L
498   |   str BASE, L->base
499   |  mov CARG2, RA
500   |   str PC, SAVE_PC
501   |  bl extern lj_meta_for      // (lua_State *L, TValue *base)
502 #if LJ_HASJIT
503   |   ldrb OP, [PC, #-4]
504 #endif
505   |  ldr INS, [PC, #-4]
506 #if LJ_HASJIT
507   |   cmp OP, #BC_JFORI
508 #endif
509   |  decode_RA8 RA, INS
510   |  decode_RD RC, INS
511 #if LJ_HASJIT
512   |   beq =>BC_JFORI
513 #endif
514   |  b =>BC_FORI
515   |
516   |//-----------------------------------------------------------------------
517   |//-- Fast functions -----------------------------------------------------
518   |//-----------------------------------------------------------------------
519   |
520   |.macro .ffunc, name
521   |->ff_ .. name:
522   |.endmacro
523   |
524   |.macro .ffunc_1, name
525   |->ff_ .. name:
526   |  ldrd CARG12, [BASE]
527   |   cmp NARGS8:RC, #8
528   |   blo ->fff_fallback
529   |.endmacro
530   |
531   |.macro .ffunc_2, name
532   |->ff_ .. name:
533   |  ldrd CARG12, [BASE]
534   |   ldrd CARG34, [BASE, #8]
535   |    cmp NARGS8:RC, #16
536   |    blo ->fff_fallback
537   |.endmacro
538   |
539   |.macro .ffunc_n, name
540   |  .ffunc_1 name
541   |  NYI
542   |.endmacro
543   |
544   |.macro .ffunc_nn, name
545   |  .ffunc_2 name
546   |  NYI
547   |.endmacro
548   |
549   |.macro ffgccheck
550   |  NYI
551   |.endmacro
552   |
553   |//-- Base library: checks -----------------------------------------------
554   |
555   |.ffunc assert
556   |  NYI
557   |
558   |.ffunc type
559   |  NYI
560   |
561   |//-- Base library: getters and setters ---------------------------------
562   |
563   |.ffunc_1 getmetatable
564   |  NYI
565   |
566   |.ffunc_2 setmetatable
567   |  NYI
568   |
569   |.ffunc rawget
570   |  NYI
571   |
572   |//-- Base library: conversions ------------------------------------------
573   |
574   |.ffunc tonumber
575   |  NYI
576   |
577   |.ffunc_1 tostring
578   |  // Only handles the string or number case inline.
579   |  checktp CARG2, LJ_TSTR
580   |  // A __tostring method in the string base metatable is ignored.
581   |  beq ->fff_restv
582   |  // Handle numbers inline, unless a number base metatable is present.
583   |  ldr CARG4, [DISPATCH, #DISPATCH_GL(gcroot[GCROOT_BASEMT_NUM])]
584   |   mov CARG1, L
585   |  checktp CARG2, LJ_TISNUM
586   |  cmpls CARG4, #0
587   |  bhi ->fff_fallback
588   |  str BASE, L->base
589   |   mov CARG2, BASE
590   |  str PC, SAVE_PC
591   |  bl extern lj_str_fromnumber        // (lua_State *L, cTValue *o)
592   |  // Returns GCstr *.
593   |  ldr BASE, L->base
594   |  mvn CARG2, #~LJ_TSTR
595   |  b ->fff_restv
596   |
597   |//-- Base library: iterators -------------------------------------------
598   |
599   |.ffunc next
600   |  NYI
601   |
602   |.ffunc_1 pairs
603   |  NYI
604   |
605   |.ffunc_2 ipairs_aux
606   |  NYI
607   |
608   |.ffunc_1 ipairs
609   |  NYI
610   |
611   |//-- Base library: catch errors ----------------------------------------
612   |
613   |.ffunc pcall
614   |  NYI
615   |
616   |.ffunc_2 xpcall
617   |  NYI
618   |
619   |//-- Coroutine library --------------------------------------------------
620   |
621   |.macro coroutine_resume_wrap, resume
622   |.if resume
623   |.ffunc_1 coroutine_resume
624   |.else
625   |.ffunc coroutine_wrap_aux
626   |.endif
627   |  NYI
628   |.endmacro
629   |
630   |  coroutine_resume_wrap 1            // coroutine.resume
631   |  coroutine_resume_wrap 0            // coroutine.wrap
632   |
633   |.ffunc coroutine_yield
634   |  NYI
635   |
636   |//-- Math library -------------------------------------------------------
637   |
638   |.ffunc_n math_abs
639   |  NYI
640   |
641   |->fff_restv:
642   |  // CARG12 = TValue result.
643   |  ldr PC, [BASE, FRAME_PC]
644   |  strd CARG12, [BASE, #-8]
645   |->fff_res1:
646   |  // PC = return.
647   |  mov RC, #(1+1)*8
648   |->fff_res:
649   |  // RC = (nresults+1)*8, PC = return.
650   |  ands CARG1, PC, #FRAME_TYPE
651   |  ldreq INS, [PC, #-4]
652   |   str RC, SAVE_MULTRES
653   |  sub RA, BASE, #8
654   |  bne ->vm_return
655   |  decode_RB8 RB, INS
656   |5:
657   |  cmp RB, RC                         // More results expected?
658   |  bhi >6
659   |  decode_RA8 CARG1, INS
660   |   ins_next1
661   |   ins_next2
662   |  // Adjust BASE. KBASE is assumed to be set for the calling frame.
663   |  sub BASE, RA, CARG1
664   |   ins_next3
665   |
666   |6:  // Fill up results with nil.
667   |  add CARG2, RA, RC
668   |  mvn CARG1, #~LJ_TNIL
669   |   add RC, RC, #8
670   |  str CARG1, [CARG2, #-4]
671   |  b <5
672   |
673   |.macro math_extern, func
674   |  .ffunc math_ .. func
675   |  NYI
676   |.endmacro
677   |
678   |.macro math_extern2, func
679   |  .ffunc math_ .. func
680   |  NYI
681   |.endmacro
682   |
683   |.macro math_round, func
684   |  .ffunc math_ .. func
685   |  NYI
686   |.endmacro
687   |
688   |  math_round floor
689   |  math_round ceil
690   |
691   |  math_extern sqrt
692   |  math_extern log
693   |  math_extern log10
694   |  math_extern exp
695   |  math_extern sin
696   |  math_extern cos
697   |  math_extern tan
698   |  math_extern asin
699   |  math_extern acos
700   |  math_extern atan
701   |  math_extern sinh
702   |  math_extern cosh
703   |  math_extern tanh
704   |  math_extern2 pow
705   |  math_extern2 atan2
706   |  math_extern2 fmod
707   |
708   |->ff_math_deg:
709   |.ffunc_n math_rad
710   |  NYI
711   |
712   |.ffunc math_ldexp
713   |  NYI
714   |
715   |.ffunc math_frexp
716   |  NYI
717   |
718   |.ffunc math_modf
719   |  NYI
720   |
721   |.macro math_minmax, name, cmpop
722   |  .ffunc_1 name
723   |  NYI
724   |.endmacro
725   |
726   |  math_minmax math_min, NYI
727   |  math_minmax math_max, NYI
728   |
729   |//-- String library -----------------------------------------------------
730   |
731   |.ffunc_1 string_len
732   |  NYI
733   |
734   |.ffunc string_byte                   // Only handle the 1-arg case here.
735   |  NYI
736   |
737   |.ffunc string_char                   // Only handle the 1-arg case here.
738   |  NYI
739   |
740   |.ffunc string_sub
741   |  NYI
742   |
743   |.ffunc string_rep                    // Only handle the 1-char case inline.
744   |  NYI
745   |
746   |.ffunc string_reverse
747   |  NYI
748   |
749   |.macro ffstring_case, name, lo
750   |  .ffunc name
751   |  NYI
752   |.endmacro
753   |
754   |ffstring_case string_lower, 65
755   |ffstring_case string_upper, 97
756   |
757   |//-- Table library ------------------------------------------------------
758   |
759   |.ffunc_1 table_getn
760   |  NYI
761   |
762   |//-- Bit library --------------------------------------------------------
763   |
764   |.macro .ffunc_bit, name
765   |  .ffunc_n bit_..name
766   |  NYI
767   |.endmacro
768   |
769   |.ffunc_bit tobit
770   |  NYI
771   |->fff_resbit:
772   |  NYI
773   |
774   |.macro .ffunc_bit_op, name, ins
775   |  .ffunc_bit name
776   |  NYI
777   |.endmacro
778   |
779   |.ffunc_bit_op band, and
780   |.ffunc_bit_op bor, or
781   |.ffunc_bit_op bxor, eor
782   |
783   |.ffunc_bit bswap
784   |  NYI
785   |
786   |.ffunc_bit bnot
787   |  NYI
788   |
789   |.macro .ffunc_bit_sh, name, ins, shmod
790   |  .ffunc_nn bit_..name
791   |  NYI
792   |.endmacro
793   |
794   |.ffunc_bit_sh lshift, NYI, 1
795   |.ffunc_bit_sh rshift, NYI, 1
796   |.ffunc_bit_sh arshift, NYI, 1
797   |.ffunc_bit_sh rol, NYI, 2
798   |.ffunc_bit_sh ror, NYI, 0
799   |
800   |//-----------------------------------------------------------------------
801   |
802   |->fff_fallback:                      // Call fast function fallback handler.
803   |  // BASE = new base, RC = nargs*8
804   |   ldr CARG3, [BASE, FRAME_FUNC]
805   |  ldr CARG2, L->maxstack
806   |  add CARG1, BASE, NARGS8:RC
807   |    ldr PC, [BASE, FRAME_PC]         // Fallback may overwrite PC.
808   |  str CARG1, L->top
809   |   ldr CARG3, CFUNC:CARG3->f
810   |    str BASE, L->base
811   |  add CARG1, CARG1, #8*LUA_MINSTACK
812   |    str PC, SAVE_PC                  // Redundant (but a defined value).
813   |  cmp CARG1, CARG2
814   |   mov CARG1, L
815   |  bhi >5                             // Need to grow stack.
816   |   blx CARG3                         // (lua_State *L)
817   |  // Either throws an error, or recovers and returns -1, 0 or nresults+1.
818   |  cmp CRET1, #0
819   |   lsl RC, CRET1, #3
820   |   sub RA, BASE, #8
821   |  bgt ->fff_res                      // Returned nresults+1?
822   |1:  // Returned 0 or -1: retry fast path.
823   |   ldr CARG1, L->top
824   |    ldr LFUNC:CARG3, [BASE, FRAME_FUNC]
825   |   sub NARGS8:RC, CARG1, BASE
826   |  bne >2                             // Returned -1?
827   |  ins_callt                          // Returned 0: retry fast path.
828   |
829   |2:  // Reconstruct previous base for vmeta_call during tailcall.
830   |  ands CARG1, PC, #FRAME_TYPE
831   |   bic CARG2, PC, #FRAME_TYPEP
832   |  ldreq INS, [PC, #-4]
833   |  andeq CARG2, MASKR8, INS, lsr #5   // Conditional decode_RA8.
834   |  sub RB, BASE, CARG2
835   |  b ->vm_call_dispatch               // Resolve again for tailcall.
836   |
837   |5:  // Grow stack for fallback handler.
838   |  mov CARG2, #LUA_MINSTACK
839   |  bl extern lj_state_growstack       // (lua_State *L, int n)
840   |  ldr BASE, L->base
841   |  cmp CARG1, CARG1                   // Set zero-flag to force retry.
842   |  b <1
843   |
844   |->fff_gcstep:                        // Call GC step function.
845   |  NYI
846   |
847   |//-----------------------------------------------------------------------
848   |//-- Special dispatch targets -------------------------------------------
849   |//-----------------------------------------------------------------------
850   |
851   |->vm_record:                         // Dispatch target for recording phase.
852 #if LJ_HASJIT
853   |  NYI
854 #endif
855   |
856   |->vm_rethook:                        // Dispatch target for return hooks.
857   |  NYI
858   |
859   |->vm_inshook:                        // Dispatch target for instr/line hooks.
860   |  NYI
861   |
862   |->cont_hook:                         // Continue from hook yield.
863   |  NYI
864   |
865   |->vm_hotloop:                        // Hot loop counter underflow.
866 #if LJ_HASJIT
867   |  NYI
868 #endif
869   |
870   |->vm_callhook:                       // Dispatch target for call hooks.
871   |  NYI
872   |
873   |->vm_hotcall:                        // Hot call counter underflow.
874   |  NYI
875   |
876   |//-----------------------------------------------------------------------
877   |//-- Trace exit handler -------------------------------------------------
878   |//-----------------------------------------------------------------------
879   |
880   |->vm_exit_handler:
881 #if LJ_HASJIT
882   |  NYI
883 #endif
884   |->vm_exit_interp:
885 #if LJ_HASJIT
886   |  NYI
887 #endif
888   |
889   |//-----------------------------------------------------------------------
890   |//-- Math helper functions ----------------------------------------------
891   |//-----------------------------------------------------------------------
892   |
893   |// FP value rounding. Called by math.floor/math.ceil fast functions
894   |// and from JIT code.
895   |//
896   |.macro vm_round, name, mode
897   |->name:
898   |  NYI
899   |.endmacro
900   |
901   |  vm_round vm_floor, 0
902   |  vm_round vm_ceil,  1
903 #if LJ_HASJIT
904   |  vm_round vm_trunc, 2
905 #else
906   |->vm_trunc:
907 #endif
908   |
909   |->vm_mod:
910   |  NYI
911   |
912   |->vm_powi:
913 #if LJ_HASJIT
914   |  NYI
915 #endif
916   |
917   |->vm_foldfpm:
918 #if LJ_HASJIT
919   |  NYI
920 #endif
921   |
922   |// Callable from C: double lj_vm_foldarith(double x, double y, int op)
923   |// Compute x op y for basic arithmetic operators (+ - * / % ^ and unary -)
924   |// and basic math functions. ORDER ARITH
925   |->vm_foldarith:
926   |  ldr OP, [sp]
927   |  cmp OP, #1
928   |  blo extern __aeabi_dadd
929   |  beq extern __aeabi_dsub
930   |  cmp OP, #3
931   |  blo extern __aeabi_dmul
932   |  beq extern __aeabi_ddiv
933   |  cmp OP, #5
934   |  blo ->vm_mod
935   |  beq extern pow
936   |  cmp OP, #7
937   |  eorlo CARG2, CARG2, #0x80000000
938   |  biceq CARG2, CARG2, #0x80000000
939   |  bxls lr
940   |  NYI  // Other operations only needed by JIT compiler.
941   |
942   |//-----------------------------------------------------------------------
943   |//-- Miscellaneous functions --------------------------------------------
944   |//-----------------------------------------------------------------------
945   |
946   |//-----------------------------------------------------------------------
947   |//-- FFI helper functions -----------------------------------------------
948   |//-----------------------------------------------------------------------
949   |
950   |->vm_ffi_call:
951 #if LJ_HASFFI
952   |  NYI
953 #endif
954   |
955   |//-----------------------------------------------------------------------
958 /* Generate the code for a single instruction. */
959 static void build_ins(BuildCtx *ctx, BCOp op, int defop)
961   int vk = 0;
962   |=>defop:
964   switch (op) {
966   /* -- Comparison ops ---------------------------------------------------- */
968   /* Remember: all ops branch for a true comparison, fall through otherwise. */
970   case BC_ISLT: case BC_ISGE: case BC_ISLE: case BC_ISGT:
971     |  NYI
972     break;
974   case BC_ISEQV: case BC_ISNEV:
975     vk = op == BC_ISEQV;
976     |  NYI
977     break;
979   case BC_ISEQS: case BC_ISNES:
980     vk = op == BC_ISEQS;
981     |  NYI
982     break;
984   case BC_ISEQN: case BC_ISNEN:
985     vk = op == BC_ISEQN;
986     |  NYI
987     break;
989   case BC_ISEQP: case BC_ISNEP:
990     vk = op == BC_ISEQP;
991     |  NYI
992     break;
994   /* -- Unary test and copy ops ------------------------------------------- */
996   case BC_ISTC: case BC_ISFC: case BC_IST: case BC_ISF:
997     |  NYI
998     break;
1000   /* -- Unary ops --------------------------------------------------------- */
1002   case BC_MOV:
1003     |  // RA = dst*8, RC = src
1004     |  lsl RC, RC, #3
1005     |   ins_next1
1006     |  ldrd CARG12, [BASE, RC]
1007     |   ins_next2
1008     |  strd CARG12, [BASE, RA]
1009     |   ins_next3
1010     break;
1011   case BC_NOT:
1012     |  // RA = dst*8, RC = src
1013     |  add RC, BASE, RC, lsl #3
1014     |   ins_next1
1015     |  ldr CARG1, [RC, #4]
1016     |   add RA, BASE, RA
1017     |   ins_next2
1018     |  checktp CARG1, LJ_TTRUE
1019     |  mvnls CARG2, #~LJ_TFALSE
1020     |  mvnhi CARG2, #~LJ_TTRUE
1021     |  str CARG2, [RA, #4]
1022     |   ins_next3
1023     break;
1024   case BC_UNM:
1025     |  // RA = dst*8, RC = src
1026     |  lsl RC, RC, #3
1027     |  ldrd CARG12, [BASE, RC]
1028     |   ins_next1
1029     |   ins_next2
1030     |  checktp CARG2, LJ_TISNUM
1031     |  bne >5
1032     |  rsbs CARG1, CARG1, #0
1033     |  bvs >4
1034     |9:
1035     |  strd CARG12, [BASE, RA]
1036     |   ins_next3
1037     |4:
1038     |  mov CARG2, #0x01e00000  // 2^31.
1039     |  mov CARG1, #0
1040     |  orr CARG2, CARG2, #0x40000000
1041     |  b <9
1042     |5:
1043     |  bhi ->vmeta_unm
1044     |  add CARG2, CARG2, #0x80000000
1045     |  b <9
1046     break;
1047   case BC_LEN:
1048     |  // RA = dst*8, RC = src
1049     |  lsl RC, RC, #3
1050     |  ldrd CARG12, [BASE, RC]
1051     |  checkstr CARG2, >2
1052     |  ldr CARG1, STR:CARG1->len
1053     |1:
1054     |  mvn CARG2, #~LJ_TISNUM
1055     |   ins_next1
1056     |   ins_next2
1057     |  strd CARG12, [BASE, RA]
1058     |   ins_next3
1059     |2:
1060     |  checktab CARG2, ->vmeta_len
1061     |  bl extern lj_tab_len             // (GCtab *t)
1062     |  // Returns uint32_t (but less than 2^31).
1063     |  b <1
1064     break;
1066   /* -- Binary ops -------------------------------------------------------- */
1068     |.macro ins_arithcheck, cond, ncond, target
1069     ||if (vk == 1) {
1070     |   cmn CARG4, #-LJ_TISNUM
1071     |    cmn..cond CARG2, #-LJ_TISNUM
1072     ||} else {
1073     |   cmn CARG2, #-LJ_TISNUM
1074     |    cmn..cond CARG4, #-LJ_TISNUM
1075     ||}
1076     |  b..ncond target
1077     |.endmacro
1078     |.macro ins_arithcheck_int, target
1079     |  ins_arithcheck eq, ne, target
1080     |.endmacro
1081     |.macro ins_arithcheck_num, target
1082     |  ins_arithcheck lo, hs, target
1083     |.endmacro
1084     |
1085     |.macro ins_arithpre
1086     |  decode_RB8 RB, INS
1087     |   decode_RC8 RC, INS
1088     |  // RA = dst*8, RB = src1*8, RC = src2*8 | num_const*8
1089     ||vk = ((int)op - BC_ADDVN) / (BC_ADDNV-BC_ADDVN);
1090     ||switch (vk) {
1091     ||case 0:
1092     |   ldrd CARG12, [BASE, RB]
1093     |    ldrd CARG34, [KBASE, RC]
1094     ||  break;
1095     ||case 1:
1096     |   ldrd CARG34, [BASE, RB]
1097     |    ldrd CARG12, [KBASE, RC]
1098     ||  break;
1099     ||default:
1100     |   ldrd CARG12, [BASE, RB]
1101     |    ldrd CARG34, [BASE, RC]
1102     ||  break;
1103     ||}
1104     |.endmacro
1105     |
1106     |.macro ins_arithfallback, ins
1107     ||switch (vk) {
1108     ||case 0:
1109     |   ins ->vmeta_arith_vn
1110     ||  break;
1111     ||case 1:
1112     |   ins ->vmeta_arith_nv
1113     ||  break;
1114     ||default:
1115     |   ins ->vmeta_arith_vv
1116     ||  break;
1117     ||}
1118     |.endmacro
1119     |
1120     |.macro ins_arithdn, intins, fpcall
1121     |  ins_arithpre
1122     |   ins_next1
1123     |  ins_arithcheck_int >5
1124     |.if "intins" == "smull"
1125     |  smull CARG1, RC, CARG3, CARG1
1126     |  cmp RC, CARG1, asr #31
1127     |  ins_arithfallback bne
1128     |.else
1129     |  intins CARG1, CARG1, CARG3
1130     |  ins_arithfallback bvs
1131     |.endif
1132     |4:
1133     |   ins_next2
1134     |  strd CARG12, [BASE, RA]
1135     |   ins_next3
1136     |5:  // FP variant.
1137     |  ins_arithfallback ins_arithcheck_num
1138     |  bl fpcall
1139     |   ins_next1
1140     |  b <4
1141     |.endmacro
1142     |
1143     |.macro ins_arithfp, fpcall
1144     |  ins_arithpre
1145     ||if (op == BC_MODVN) {
1146     |  ->BC_MODVN_Z:
1147     ||}
1148     |  ins_arithfallback ins_arithcheck_num
1149     |  bl fpcall
1150     |   ins_next1
1151     |   ins_next2
1152     |  strd CARG12, [BASE, RA]
1153     |   ins_next3
1154     |.endmacro
1156   case BC_ADDVN: case BC_ADDNV: case BC_ADDVV:
1157     |  ins_arithdn adds, extern __aeabi_dadd
1158     break;
1159   case BC_SUBVN: case BC_SUBNV: case BC_SUBVV:
1160     |  ins_arithdn subs, extern __aeabi_dsub
1161     break;
1162   case BC_MULVN: case BC_MULNV: case BC_MULVV:
1163     |  ins_arithdn smull, extern __aeabi_dmul
1164     break;
1165   case BC_DIVVN: case BC_DIVNV: case BC_DIVVV:
1166     |  ins_arithfp extern __aeabi_ddiv
1167     break;
1168   case BC_MODVN:
1169     |  // NYI: integer arithmetic.
1170     |  // Note: __aeabi_idivmod is unsuitable. It uses trunc, not floor.
1171     |  ins_arithfp ->vm_mod
1172     break;
1173   case BC_MODNV: case BC_MODVV:
1174     |  ins_arithpre
1175     |  b ->BC_MODVN_Z
1176     break;
1177   case BC_POW:
1178     |  // NYI: (partial) integer arithmetic.
1179     |  ins_arithfp extern pow
1180     break;
1182   case BC_CAT:
1183     |  NYI
1184     break;
1186   /* -- Constant ops ------------------------------------------------------ */
1188   case BC_KSTR:
1189     |  // RA = dst*8, RC = str_const (~)
1190     |  mvn RC, RC
1191     |   ins_next1
1192     |  ldr CARG1, [KBASE, RC, lsl #2]
1193     |   ins_next2
1194     |  mvn CARG2, #~LJ_TSTR
1195     |  strd CARG12, [BASE, RA]
1196     |   ins_next3
1197     break;
1198   case BC_KCDATA:
1199 #if LJ_HASFFI
1200     |  NYI
1201 #endif
1202     break;
1203   case BC_KSHORT:
1204     |  // RA = dst*8, (RC = int16_literal)
1205     |  mov CARG1, INS, asr #16                  // Refetch sign-extended reg.
1206     |  mvn CARG2, #~LJ_TISNUM
1207     |   ins_next1
1208     |   ins_next2
1209     |  strd CARG12, [BASE, RA]
1210     |   ins_next3
1211     break;
1212   case BC_KNUM:
1213     |  // RA = dst*8, RC = num_const
1214     |  lsl RC, RC, #3
1215     |   ins_next1
1216     |  ldrd CARG12, [KBASE, RC]
1217     |   ins_next2
1218     |  strd CARG12, [BASE, RA]
1219     |   ins_next3
1220     break;
1221   case BC_KPRI:
1222     |  // RA = dst*8, RC = primitive_type (~)
1223     |  add RA, BASE, RA
1224     |  mvn RC, RC
1225     |   ins_next1
1226     |   ins_next2
1227     |  str RC, [RA, #4]
1228     |   ins_next3
1229     break;
1230   case BC_KNIL:
1231     |  // RA = base*8, RC = end
1232     |  add RA, BASE, RA
1233     |   add RC, BASE, RC, lsl #3
1234     |  mvn CARG1, #~LJ_TNIL
1235     |  str CARG1, [RA, #4]
1236     |   add RA, RA, #8
1237     |1:
1238     |  str CARG1, [RA, #4]
1239     |  cmp RA, RC
1240     |   add RA, RA, #8
1241     |  blt <1
1242     |  ins_next_
1243     break;
1245   /* -- Upvalue and function ops ------------------------------------------ */
1247   case BC_UGET:
1248     |  NYI
1249     break;
1250   case BC_USETV:
1251     |  NYI
1252     break;
1253   case BC_USETS:
1254     |  NYI
1255     break;
1256   case BC_USETN:
1257     |  NYI
1258     break;
1259   case BC_USETP:
1260     |  NYI
1261     break;
1263   case BC_UCLO:
1264     |  NYI
1265     break;
1267   case BC_FNEW:
1268     |  NYI
1269     break;
1271   /* -- Table ops --------------------------------------------------------- */
1273   case BC_TNEW:
1274   case BC_TDUP:
1275     |  // RA = dst*8, RC = (hbits|asize) | tab_const (~)
1276     if (op == BC_TDUP) {
1277       |  mvn RC, RC
1278     }
1279     |  ldr CARG3, [DISPATCH, #DISPATCH_GL(gc.total)]
1280     |   ldr CARG4, [DISPATCH, #DISPATCH_GL(gc.threshold)]
1281     |    str BASE, L->base
1282     |    str PC, SAVE_PC
1283     |  cmp CARG3, CARG4
1284     |  bhs >5
1285     |1:
1286     |  mov CARG1, L
1287     if (op == BC_TNEW) {
1288       |  lsl CARG2, RC, #21
1289       |   lsr CARG3, RC, #11
1290       |  asr RC, CARG2, #21
1291       |  lsr CARG2, CARG2, #21
1292       |  cmn RC, #1
1293       |  addeq CARG2, CARG2, #2
1294       |  bl extern lj_tab_new  // (lua_State *L, int32_t asize, uint32_t hbits)
1295       |  // Returns GCtab *.
1296     } else {
1297       |  ldr CARG2, [KBASE, RC, lsl #2]
1298       |  bl extern lj_tab_dup  // (lua_State *L, Table *kt)
1299       |  // Returns GCtab *.
1300     }
1301     |  ldr BASE, L->base
1302     |  mvn CARG2, #~LJ_TTAB
1303     |   ins_next1
1304     |   ins_next2
1305     |  strd CARG12, [BASE, RA]
1306     |   ins_next3
1307     |5:
1308     |  bl extern lj_gc_step_fixtop  // (lua_State *L)
1309     |  b <1
1310     break;
1312   case BC_GGET:
1313     |  // RA = dst*8, RC = str_const (~)
1314   case BC_GSET:
1315     |  // RA = dst*8, RC = str_const (~)
1316     |  ldr LFUNC:CARG2, [BASE, FRAME_FUNC]
1317     |   mvn RC, RC
1318     |  ldr TAB:CARG1, LFUNC:CARG2->env
1319     |   ldr STR:RC, [KBASE, RC, lsl #2]
1320     if (op == BC_GGET) {
1321       |  b ->BC_TGETS_Z
1322     } else {
1323       |  b ->BC_TSETS_Z
1324     }
1325     break;
1327   case BC_TGETV:
1328     |  NYI
1329     break;
1330   case BC_TGETS:
1331     |  decode_RB8 RB, INS
1332     |   and RC, RC, #255
1333     |  // RA = dst*8, RB = table*8, RC = str_const (~)
1334     |  ldrd CARG12, [BASE, RB]
1335     |   mvn RC, RC
1336     |   ldr STR:RC, [KBASE, RC, lsl #2]  // STALL: early RC.
1337     |  checktab CARG2, ->vmeta_tgets
1338     |->BC_TGETS_Z:
1339     |  // (TAB:RB =) TAB:CARG1 = GCtab *, STR:RC = GCstr *, RA = dst*8
1340     |  ldr CARG3, TAB:CARG1->hmask
1341     |   ldr CARG4, STR:RC->hash
1342     |    ldr NODE:INS, TAB:CARG1->node
1343     |     mov TAB:RB, TAB:CARG1
1344     |  and CARG3, CARG3, CARG4                  // idx = str->hash & tab->hmask
1345     |  add CARG3, CARG3, CARG3, lsl #1
1346     |    add NODE:INS, NODE:INS, CARG3, lsl #3  // node = tab->node + idx*3*8
1347     |1:
1348     |  ldrd CARG12, NODE:INS->key  // STALL: early NODE:INS.
1349     |   ldrd CARG34, NODE:INS->val
1350     |    ldr NODE:INS, NODE:INS->next
1351     |  cmp CARG1, STR:RC
1352     |  checktpeq CARG2, LJ_TSTR
1353     |  bne >4
1354     |   checktp CARG4, LJ_TNIL
1355     |   beq >5
1356     |3:
1357     |   ins_next1
1358     |   ins_next2
1359     |  strd CARG34, [BASE, RA]
1360     |   ins_next3
1361     |
1362     |4:  // Follow hash chain.
1363     |  cmp NODE:INS, #0
1364     |  bne <1
1365     |  // End of hash chain: key not found, nil result.
1366     |
1367     |5:  // Check for __index if table value is nil.
1368     |  ldr TAB:CARG1, TAB:RB->metatable
1369     |   mov CARG3, #0  // Optional clear of undef. value (during load stall).
1370     |   mvn CARG4, #~LJ_TNIL
1371     |  cmp TAB:CARG1, #0
1372     |  beq <3                                   // No metatable: done.
1373     |  ldrb CARG2, TAB:CARG1->nomm
1374     |  tst CARG2, #1<<MM_index
1375     |  bne <3                                   // 'no __index' flag set: done.
1376     |  b ->vmeta_tgets
1377     break;
1378   case BC_TGETB:
1379     |  NYI
1380     break;
1382   case BC_TSETV:
1383     |  NYI
1384     break;
1385   case BC_TSETS:
1386     |->BC_TSETS_Z:
1387     |  NYI
1388     break;
1389   case BC_TSETB:
1390     |  NYI
1391     break;
1393   case BC_TSETM:
1394     |  NYI
1395     break;
1397   /* -- Calls and vararg handling ----------------------------------------- */
1399   case BC_CALLM:
1400     |  // RA = base*8, (RB = nresults+1,) RC = extra_nargs
1401     |  ldr CARG1, SAVE_MULTRES
1402     |  decode_RC8 NARGS8:RC, INS
1403     |  add NARGS8:RC, NARGS8:RC, CARG1
1404     |  b ->BC_CALL_Z
1405     break;
1406   case BC_CALL:
1407     |  // RA = base*8, (RB = nresults+1,) RC = nargs+1
1408     |  decode_RC8 NARGS8:RC, INS
1409     |->BC_CALL_Z:
1410     |  mov RB, BASE                     // Save old BASE for vmeta_call.
1411     |  ldrd CARG34, [BASE, RA]!
1412     |   sub NARGS8:RC, NARGS8:RC, #8
1413     |   add BASE, BASE, #8
1414     |  checkfunc CARG4, ->vmeta_call
1415     |  ins_call
1416     break;
1418   case BC_CALLMT:
1419     |  NYI
1420     break;
1421   case BC_CALLT:
1422     |  NYI
1423     break;
1425   case BC_ITERC:
1426     |  // RA = base*8, (RB = nresults+1, RC = nargs+1 (2+1))
1427     |  add RA, BASE, RA
1428     |   mov RB, BASE                    // Save old BASE for vmeta_call.
1429     |  ldrd CARG34, [RA, #-16]
1430     |   ldrd CARG12, [RA, #-8]
1431     |    add BASE, RA, #8
1432     |  strd CARG34, [RA, #8]            // Copy state.
1433     |   strd CARG12, [RA, #16]          // Copy control var.
1434     |  // STALL: locked CARG34.
1435     |  ldrd LFUNC:CARG34, [RA, #-24]
1436     |    mov NARGS8:RC, #16             // Iterators get 2 arguments.
1437     |  // STALL: load CARG34.
1438     |  strd LFUNC:CARG34, [RA]          // Copy callable.
1439     |  checkfunc CARG4, ->vmeta_call
1440     |  ins_call
1441     break;
1443   case BC_ITERN:
1444     |  // RA = base*8, (RB = nresults+1, RC = nargs+1 (2+1))
1445 #if LJ_HASJIT
1446     |  // NYI: add hotloop, record BC_ITERN.
1447 #endif
1448     |  add RA, BASE, RA
1449     |  ldr TAB:RB, [RA, #-16]
1450     |  ldr CARG1, [RA, #-8]             // Get index from control var.
1451     |  ldr INS, TAB:RB->asize
1452     |   ldr CARG2, TAB:RB->array
1453     |    add PC, PC, #4
1454     |1:  // Traverse array part.
1455     |  subs RC, CARG1, INS
1456     |   add CARG3, CARG2, CARG1, lsl #3
1457     |  bhs >5                           // Index points after array part?
1458     |   ldrd CARG34, [CARG3]
1459     |   checktp CARG4, LJ_TNIL
1460     |   addeq CARG1, CARG1, #1          // Skip holes in array part.
1461     |   beq <1
1462     |  ldrh RC, [PC, #-2]
1463     |   mvn CARG2, #~LJ_TISNUM
1464     |    strd CARG34, [RA, #8]
1465     |  add RC, PC, RC, lsl #2
1466     |    add RB, CARG1, #1
1467     |   strd CARG12, [RA]
1468     |  sub PC, RC, #0x20000
1469     |    str RB, [RA, #-8]              // Update control var.
1470     |3:
1471     |  ins_next
1472     |
1473     |5:  // Traverse hash part.
1474     |  ldr CARG4, TAB:RB->hmask
1475     |   ldr NODE:RB, TAB:RB->node
1476     |6:
1477     |   add CARG1, RC, RC, lsl #1
1478     |  cmp RC, CARG4                    // End of iteration? Branch to ITERL+1.
1479     |   add NODE:CARG3, NODE:RB, CARG1, lsl #3  // node = tab->node + idx*3*8
1480     |  bhi <3
1481     |   ldrd CARG12, NODE:CARG3->val
1482     |   checktp CARG2, LJ_TNIL
1483     |   add RC, RC, #1
1484     |   beq <6                          // Skip holes in hash part.
1485     |  ldrh RB, [PC, #-2]
1486     |   add RC, RC, INS
1487     |    ldrd CARG34, NODE:CARG3->key
1488     |   str RC, [RA, #-8]               // Update control var.
1489     |   strd CARG12, [RA, #8]
1490     |  add RC, PC, RB, lsl #2
1491     |  sub PC, RC, #0x20000
1492     |    strd CARG34, [RA]
1493     |  b <3
1494     break;
1496   case BC_ISNEXT:
1497     |  // RA = base*8, RD = target (points to ITERN)
1498     |  add RA, BASE, RA
1499     |     add RC, PC, RC, lsl #2
1500     |  ldrd CFUNC:CARG12, [RA, #-24]
1501     |   ldr CARG3, [RA, #-12]
1502     |    ldr CARG4, [RA, #-4]
1503     |  checktp CARG2, LJ_TFUNC
1504     |  ldrbeq CARG1, CFUNC:CARG1->ffid
1505     |   checktpeq CARG3, LJ_TTAB
1506     |    checktpeq CARG4, LJ_TNIL
1507     |  cmpeq CARG1, #FF_next_N
1508     |     subeq PC, RC, #0x20000
1509     |  bne >5
1510     |   ins_next1
1511     |   ins_next2
1512     |  mov CARG1, #0
1513     |  str CARG1, [RA, #-8]             // Initialize control var.
1514     |1:
1515     |   ins_next3
1516     |5:  // Despecialize bytecode if any of the checks fail.
1517     |  mov CARG1, #BC_JMP
1518     |   mov OP, #BC_ITERC
1519     |  strb CARG1, [PC, #-4]
1520     |   sub PC, RC, #0x20000
1521     |   strb OP, [PC]                   // Subsumes ins_next1.
1522     |   ins_next2
1523     |  b <1
1524     break;
1526   case BC_VARG:
1527     |  NYI
1528     break;
1530   /* -- Returns ----------------------------------------------------------- */
1532   case BC_RETM:
1533     |  // RA = results*8, RC = extra results
1534     |  ldr CARG1, SAVE_MULTRES
1535     |   ldr PC, [BASE, FRAME_PC]
1536     |    add RA, BASE, RA
1537     |  add RC, CARG1, RC, lsl #3
1538     |  b ->BC_RETM_Z
1539     break;
1541   case BC_RET:
1542     |  // RA = results*8, RC = nresults+1
1543     |  ldr PC, [BASE, FRAME_PC]
1544     |   lsl RC, RC, #3
1545     |    add RA, BASE, RA
1546     |->BC_RETM_Z:
1547     |   str RC, SAVE_MULTRES
1548     |1:
1549     |  ands CARG1, PC, #FRAME_TYPE
1550     |   eor CARG2, PC, #FRAME_VARG
1551     |  bne ->BC_RETV2_Z
1552     |
1553     |->BC_RET_Z:
1554     |  // BASE = base, RA = resultptr, RC = (nresults+1)*8, PC = return
1555     |  ldr INS, [PC, #-4]
1556     |  subs CARG4, RC, #8
1557     |   sub CARG3, BASE, #8
1558     |  beq >3
1559     |2:
1560     |  ldrd CARG12, [RA], #8
1561     |   add BASE, BASE, #8
1562     |   subs CARG4, CARG4, #8
1563     |  strd CARG12, [BASE, #-16]
1564     |   bne <2
1565     |3:
1566     |  decode_RA8 RA, INS
1567     |  sub BASE, CARG3, RA
1568     |   decode_RB8 RB, INS
1569     |  ldr LFUNC:CARG1, [BASE, FRAME_FUNC]
1570     |5:
1571     |  cmp RB, RC                       // More results expected?
1572     |  bhi >6
1573     |  ldr CARG2, LFUNC:CARG1->field_pc
1574     |   ins_next1
1575     |   ins_next2
1576     |  ldr KBASE, [CARG2, #PC2PROTO(k)]
1577     |   ins_next3
1578     |
1579     |6:  // Fill up results with nil.
1580     |  mvn CARG2, #~LJ_TNIL
1581     |  sub BASE, BASE, #8
1582     |   add RC, RC, #8
1583     |  str CARG2, [BASE, #-12]
1584     |  b <5
1585     |
1586     |->BC_RETV1_Z:  // Non-standard return case.
1587     |  add RA, BASE, RA
1588     |->BC_RETV2_Z:
1589     |  tst CARG2, #FRAME_TYPEP
1590     |  bne ->vm_return
1591     |  // Return from vararg function: relocate BASE down.
1592     |  sub BASE, BASE, CARG2
1593     |  ldr PC, [BASE, FRAME_PC]
1594     |  b <1
1595     break;
1597   case BC_RET0: case BC_RET1:
1598     |  // RA = results*8, RC = nresults+1
1599     |  ldr PC, [BASE, FRAME_PC]
1600     |   lsl RC, RC, #3
1601     |   str RC, SAVE_MULTRES
1602     |  ands CARG1, PC, #FRAME_TYPE
1603     |   eor CARG2, PC, #FRAME_VARG
1604     |   ldreq INS, [PC, #-4]
1605     |  bne ->BC_RETV1_Z
1606     if (op == BC_RET1) {
1607       |  ldrd CARG12, [BASE, RA]
1608     }
1609     |  sub CARG4, BASE, #8
1610     |   decode_RA8 RA, INS
1611     if (op == BC_RET1) {
1612       |  strd CARG12, [CARG4]
1613     }
1614     |  sub BASE, CARG4, RA
1615     |   decode_RB8 RB, INS
1616     |  ldr LFUNC:CARG1, [BASE, FRAME_FUNC]
1617     |5:
1618     |  cmp RB, RC
1619     |  bhi >6
1620     |  ldr CARG2, LFUNC:CARG1->field_pc
1621     |   ins_next1
1622     |   ins_next2
1623     |  ldr KBASE, [CARG2, #PC2PROTO(k)]
1624     |   ins_next3
1625     |
1626     |6:  // Fill up results with nil.
1627     |  sub CARG2, CARG4, #4
1628     |  mvn CARG3, #~LJ_TNIL
1629     |  str CARG3, [CARG2, RC]
1630     |  add RC, RC, #8
1631     |  b <5
1632     break;
1634   /* -- Loops and branches ------------------------------------------------ */
1636   |.define FOR_IDX,  [RA];      .define FOR_TIDX,  [RA, #4]
1637   |.define FOR_STOP, [RA, #8];  .define FOR_TSTOP, [RA, #12]
1638   |.define FOR_STEP, [RA, #16]; .define FOR_TSTEP, [RA, #20]
1639   |.define FOR_EXT,  [RA, #24]; .define FOR_TEXT,  [RA, #28]
1641   case BC_FORL:
1642 #if LJ_HASJIT
1643     |  hotloop
1644 #endif
1645     |  // Fall through. Assumes BC_IFORL follows.
1646     break;
1648   case BC_JFORI:
1649   case BC_JFORL:
1650 #if !LJ_HASJIT
1651     break;
1652 #endif
1653   case BC_FORI:
1654   case BC_IFORL:
1655     |  // RA = base*8, RC = target (after end of loop or start of loop)
1656     vk = (op == BC_IFORL || op == BC_JFORL);
1657     |  ldrd CARG12, [RA, BASE]!
1658     |   add RC, PC, RC, lsl #2
1659     if (!vk) {
1660       |  ldrd CARG34, FOR_STOP
1661       |   checktp CARG2, LJ_TISNUM
1662       |  ldr RB, FOR_TSTEP
1663       |   bne >5
1664       |  checktp CARG4, LJ_TISNUM
1665       |   ldr CARG4, FOR_STEP
1666       |  checktpeq RB, LJ_TISNUM
1667       |  bne ->vmeta_for
1668       |  cmp CARG4, #0
1669       |  blt >4
1670       |  cmp CARG1, CARG3
1671     } else {
1672       |  ldrd CARG34, FOR_STEP
1673       |   checktp CARG2, LJ_TISNUM
1674       |   bne >5
1675       |  adds CARG1, CARG1, CARG3
1676       |   ldr CARG4, FOR_STOP
1677       if (op == BC_IFORL) {
1678         |  addvs RC, PC, #0x20000               // Overflow: prevent branch.
1679       } else {
1680         |  NYI
1681       }
1682       |  cmp CARG3, #0
1683       |  blt >4
1684       |  cmp CARG1, CARG4
1685     }
1686     |1:
1687     if (op == BC_FORI) {
1688       |  subgt PC, RC, #0x20000
1689     } else if (op == BC_JFORI) {
1690       |  NYI
1691     } else if (op == BC_IFORL) {
1692       |  suble PC, RC, #0x20000
1693     } else {
1694       |  NYI
1695     }
1696     if (vk) {
1697       |  strd CARG12, FOR_IDX
1698     }
1699     |   ins_next1
1700     |   ins_next2
1701     |  strd CARG12, FOR_EXT
1702     |3:
1703     |   ins_next3
1704     |
1705     |4:  // Invert check for negative step.
1706     if (!vk) {
1707       |  cmp CARG3, CARG1
1708     } else {
1709       |  cmp CARG4, CARG1
1710     }
1711     |  b <1
1712     |
1713     |5:  // FP loop.
1714     if (!vk) {
1715       |  cmnlo CARG4, #-LJ_TISNUM
1716       |  cmnlo RB, #-LJ_TISNUM
1717       |  bhs ->vmeta_for
1718       |  cmp RB, #0
1719       |   strd CARG12, FOR_IDX
1720       |  blt >8
1721     } else {
1722       |  cmp CARG4, #0
1723       |  blt >8
1724       |  bl extern __aeabi_dadd
1725       |   strd CARG12, FOR_IDX
1726       |  ldrd CARG34, FOR_STOP
1727       |   strd CARG12, FOR_EXT
1728     }
1729     |6:
1730     |  bl extern __aeabi_cdcmple
1731     if (op == BC_FORI) {
1732       |  subhi PC, RC, #0x20000
1733     } else if (op == BC_JFORI) {
1734       |  NYI
1735     } else if (op == BC_IFORL) {
1736       |  subls PC, RC, #0x20000
1737     } else {
1738       |  NYI
1739     }
1740     |  ins_next1
1741     |  ins_next2
1742     |  b <3
1743     |
1744     |8:  // Invert check for negative step.
1745     if (vk) {
1746       |  bl extern __aeabi_dadd
1747       |  strd CARG12, FOR_IDX
1748       |  strd CARG12, FOR_EXT
1749     }
1750     |  mov CARG3, CARG1
1751     |  mov CARG4, CARG2
1752     |  ldrd CARG12, FOR_STOP
1753     |  b <6
1754     break;
1756   case BC_ITERL:
1757 #if LJ_HASJIT
1758     |  hotloop
1759 #endif
1760     |  // Fall through. Assumes BC_IITERL follows.
1761     break;
1763   case BC_JITERL:
1764 #if !LJ_HASJIT
1765     break;
1766 #endif
1767   case BC_IITERL:
1768     |  // RA = base*8, RC = target
1769     |  ldrd CARG12, [RA, BASE]!
1770     if (op == BC_JITERL) {
1771       |  NYI
1772     } else {
1773       |   add RC, PC, RC, lsl #2
1774       |  // STALL: load CARG12.
1775       |  cmn CARG2, #-LJ_TNIL           // Stop if iterator returned nil.
1776       |  subne PC, RC, #0x20000         // Otherwise save control var + branch.
1777       |  strdne CARG12, [RA, #-8]
1778     }
1779     |  ins_next
1780     break;
1782   case BC_LOOP:
1783     |  // RA = base*8, RC = target (loop extent)
1784     |  // Note: RA/RC is only used by trace recorder to determine scope/extent
1785     |  // This opcode does NOT jump, it's only purpose is to detect a hot loop.
1786 #if LJ_HASJIT
1787     |  hotloop
1788 #endif
1789     |  // Fall through. Assumes BC_ILOOP follows.
1790     break;
1792   case BC_ILOOP:
1793     |  // RA = base*8, RC = target (loop extent)
1794     |  ins_next
1795     break;
1797   case BC_JLOOP:
1798 #if LJ_HASJIT
1799     |  NYI
1800 #endif
1801     break;
1803   case BC_JMP:
1804     |  // RA = base*8 (only used by trace recorder), RC = target
1805     |  add RC, PC, RC, lsl #2
1806     |  sub PC, RC, #0x20000
1807     |  ins_next
1808     break;
1810   /* -- Function headers -------------------------------------------------- */
1812   case BC_FUNCF:
1813 #if LJ_HASJIT
1814     |  hotcall
1815 #endif
1816   case BC_FUNCV:  /* NYI: compiled vararg functions. */
1817     |  // Fall through. Assumes BC_IFUNCF/BC_IFUNCV follow.
1818     break;
1820   case BC_JFUNCF:
1821 #if !LJ_HASJIT
1822     break;
1823 #endif
1824   case BC_IFUNCF:
1825     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
1826     |  ldr CARG1, L->maxstack
1827     |   ldrb CARG2, [PC, #-4+PC2PROTO(numparams)]
1828     |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
1829     |  cmp RA, CARG1
1830     |  bhi ->vm_growstack_l
1831     |  ins_next1
1832     |  ins_next2
1833     |2:
1834     |  cmp NARGS8:RC, CARG2, lsl #3     // Check for missing parameters.
1835     |  ble >3
1836     if (op == BC_JFUNCF) {
1837       |  NYI
1838     } else {
1839       |  ins_next3
1840     }
1841     |
1842     |3:  // Clear missing parameters.
1843     |  mvn CARG1, #~LJ_TNIL
1844     |  str CARG1, [BASE, NARGS8:RC]
1845     |  add NARGS8:RC, NARGS8:RC, #8
1846     |  b <2
1847     break;
1849   case BC_JFUNCV:
1850 #if !LJ_HASJIT
1851     break;
1852 #endif
1853     |  NYI  // NYI: compiled vararg functions
1854     break;  /* NYI: compiled vararg functions. */
1856   case BC_IFUNCV:
1857     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
1858     |  ldr CARG1, L->maxstack
1859     |   add CARG4, BASE, RC
1860     |  add RA, RA, RC
1861     |   str LFUNC:CARG3, [CARG4]        // Store copy of LFUNC.
1862     |   add CARG2, RC, #8+FRAME_VARG
1863     |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
1864     |  cmp RA, CARG1
1865     |   str CARG2, [CARG4, #4]          // Store delta + FRAME_VARG.
1866     |  bhs ->vm_growstack_l
1867     |  ldrb RB, [PC, #-4+PC2PROTO(numparams)]
1868     |   mov RA, BASE
1869     |   mov RC, CARG4
1870     |  cmp RB, #0
1871     |   add BASE, CARG4, #8
1872     |  beq >3
1873     |  mvn CARG3, #~LJ_TNIL
1874     |1:
1875     |  cmp RA, RC                       // Less args than parameters?
1876     |   ldrdlo CARG12, [RA], #8
1877     |   movhs CARG2, CARG3
1878     |    strlo CARG3, [RA, #-4]         // Clear old fixarg slot (help the GC).
1879     |2:
1880     |  subs RB, RB, #1
1881     |   strd CARG12, [CARG4, #8]!
1882     |  bne <1
1883     |3:
1884     |  ins_next
1885     break;
1887   case BC_FUNCC:
1888   case BC_FUNCCW:
1889     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = CFUNC, RC = nargs*8
1890     if (op == BC_FUNCC) {
1891       |  ldr CARG4, CFUNC:CARG3->f
1892     } else {
1893       |  ldr CARG4, [DISPATCH, #DISPATCH_GL(wrapf)]
1894     }
1895     |   add CARG2, RA, NARGS8:RC
1896     |   ldr CARG1, L->maxstack
1897     |  add RC, BASE, NARGS8:RC
1898     |    str BASE, L->base
1899     |   cmp CARG2, CARG1
1900     |  str RC, L->top
1901     if (op == BC_FUNCCW) {
1902       |  ldr CARG2, CFUNC:CARG3->f
1903     }
1904     |    mv_vmstate CARG3, C
1905     |  mov CARG1, L
1906     |   bhi ->vm_growstack_c            // Need to grow stack.
1907     |    st_vmstate CARG3
1908     |  blx CARG4                        // (lua_State *L [, lua_CFunction f])
1909     |  // Returns nresults.
1910     |  ldr BASE, L->base
1911     |    mv_vmstate CARG3, INTERP
1912     |   ldr CRET2, L->top
1913     |   lsl RC, CRET1, #3
1914     |    st_vmstate CARG3
1915     |  ldr PC, [BASE, FRAME_PC]
1916     |   sub RA, CRET2, RC               // RA = L->top - nresults*8
1917     |  b ->vm_returnc
1918     break;
1920   /* ---------------------------------------------------------------------- */
1922   default:
1923     fprintf(stderr, "Error: undefined opcode BC_%s\n", bc_names[op]);
1924     exit(2);
1925     break;
1926   }
1929 static int build_backend(BuildCtx *ctx)
1931   int op;
1933   dasm_growpc(Dst, BC__MAX);
1935   build_subroutines(ctx);
1937   |.code_op
1938   for (op = 0; op < BC__MAX; op++)
1939     build_ins(ctx, (BCOp)op, op);
1941   return BC__MAX;
1944 /* Emit pseudo frame-info for all assembler functions. */
1945 static void emit_asm_debug(BuildCtx *ctx)
1947   int i;
1948   switch (ctx->mode) {
1949   case BUILD_elfasm:
1950     fprintf(ctx->fp, "\t.section .debug_frame,\"\",%%progbits\n");
1951     fprintf(ctx->fp,
1952         ".Lframe0:\n"
1953         "\t.long .LECIE0-.LSCIE0\n"
1954         ".LSCIE0:\n"
1955         "\t.long 0xffffffff\n"
1956         "\t.byte 0x1\n"
1957         "\t.string \"\"\n"
1958         "\t.uleb128 0x1\n"
1959         "\t.sleb128 -4\n"
1960         "\t.byte 0xe\n"                         /* Return address is in lr. */
1961         "\t.byte 0xc\n\t.uleb128 0xd\n\t.uleb128 0\n"   /* def_cfa sp */
1962         "\t.align 2\n"
1963         ".LECIE0:\n\n");
1964     fprintf(ctx->fp,
1965         ".LSFDE0:\n"
1966         "\t.long .LEFDE0-.LASFDE0\n"
1967         ".LASFDE0:\n"
1968         "\t.long .Lframe0\n"
1969         "\t.long .Lbegin\n"
1970         "\t.long %d\n"
1971         "\t.byte 0xe\n\t.uleb128 %d\n"          /* def_cfa_offset */
1972         "\t.byte 0x8e\n\t.uleb128 1\n",         /* Restore lr. */
1973         (int)ctx->codesz, CFRAME_SIZE);
1974     for (i = 11; i >= 4; i--)  /* Restore r4-r11. */
1975       fprintf(ctx->fp, "\t.byte %d\n\t.uleb128 %d\n", 0x80+i, 2+(11-i));
1976     fprintf(ctx->fp,
1977         "\t.align 2\n"
1978         ".LEFDE0:\n\n");
1979     /* NYI: emit ARM.exidx. */
1980     break;
1981   default:
1982     break;
1983   }