ARM: Add support to call Lua functions and return from them.
[luajit-2.0.git] / src / buildvm_arm.dasc
blob650aa31c82c5e4ccc9853a6a4ed5ff7e9859857a
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
96 |// Instruction fetch.
97 |.macro ins_NEXT1
98 |  ldrb OP, [PC]
99 |.endmacro
100 |.macro ins_NEXT2
101 |   ldr INS, [PC], #4
102 |.endmacro
103 |// Instruction decode+dispatch.
104 |.macro ins_NEXT3
105 |  ldr OP, [DISPATCH, OP, lsl #2]
106 |   decode_RA8 RA, INS
107 |   decode_RD RC, INS
108 |  bx OP
109 |.endmacro
110 |.macro ins_NEXT
111 |  ins_NEXT1
112 |  ins_NEXT2
113 |  ins_NEXT3
114 |.endmacro
116 |// Instruction footer.
117 |.if 1
118 |  // Replicated dispatch. Less unpredictable branches, but higher I-Cache use.
119 |  .define ins_next, ins_NEXT
120 |  .define ins_next_, ins_NEXT
121 |  .define ins_next1, ins_NEXT1
122 |  .define ins_next2, ins_NEXT2
123 |  .define ins_next3, ins_NEXT3
124 |.else
125 |  // Common dispatch. Lower I-Cache use, only one (very) unpredictable branch.
126 |  // Affects only certain kinds of benchmarks (and only with -j off).
127 |  .macro ins_next
128 |    b ->ins_next
129 |  .endmacro
130 |  .macro ins_next1
131 |  .endmacro
132 |  .macro ins_next2
133 |  .endmacro
134 |  .macro ins_next3
135 |    b ->ins_next
136 |  .endmacro
137 |  .macro ins_next_
138 |  ->ins_next:
139 |    ins_NEXT
140 |  .endmacro
141 |.endif
143 |// Avoid register name substitution for field name.
144 #define field_pc        pc
146 |// Call decode and dispatch.
147 |.macro ins_callt
148 |  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, FRAME_PC(BASE) = PC
149 |  ldr PC, LFUNC:CARG3->field_pc
150 |  ldrb OP, [PC]
151 |   ldr INS, [PC], #4
152 |  ldr OP, [DISPATCH, OP, lsl #2]
153 |   decode_RA8 RA, INS
154 |   add RA, RA, BASE
155 |  bx OP
156 |.endmacro
158 |.macro ins_call
159 |  // BASE = new base, CARG3 = LFUNC/CFUNC, RC = nargs*8, PC = caller PC
160 |  str PC, [BASE, FRAME_PC]
161 |  ins_callt
162 |.endmacro
164 |//-----------------------------------------------------------------------
166 |// Macros to test operand types.
167 |.macro checktp, reg, tp; cmn reg, #-tp; .endmacro
168 |.macro checkstr, reg, target; checktp reg, LJ_TSTR; bne target; .endmacro
169 |.macro checktab, reg, target; checktp reg, LJ_TTAB; bne target; .endmacro
170 |.macro checkfunc, reg, target; checktp reg, LJ_TFUNC; bne target; .endmacro
172 |// Assumes DISPATCH is relative to GL.
173 #define DISPATCH_GL(field)      (GG_DISP2G + (int)offsetof(global_State, field))
174 #define DISPATCH_J(field)       (GG_DISP2J + (int)offsetof(jit_State, field))
176 #define PC2PROTO(field)  ((int)offsetof(GCproto, field)-(int)sizeof(GCproto))
178 |.macro hotloop
179 |  NYI
180 |.endmacro
182 |.macro hotcall
183 |  NYI
184 |.endmacro
186 |// Set current VM state.
187 |.macro mv_vmstate, reg, st; mvn reg, #LJ_VMST_..st; .endmacro
188 |.macro st_vmstate, reg; str reg, [DISPATCH, #DISPATCH_GL(vmstate)]; .endmacro
190 |//-----------------------------------------------------------------------
192 /* Generate subroutines used by opcodes and other parts of the VM. */
193 /* The .code_sub section should be last to help static branch prediction. */
194 static void build_subroutines(BuildCtx *ctx)
196   |.code_sub
197   |
198   |//-----------------------------------------------------------------------
199   |//-- Return handling ----------------------------------------------------
200   |//-----------------------------------------------------------------------
201   |
202   |->vm_returnp:
203   |  // See vm_return. Also: RB = previous base.
204   |  tst PC, #FRAME_P
205   |  beq ->cont_dispatch
206   |
207   |  // Return from pcall or xpcall fast func.
208   |  ldr PC, [RB, FRAME_PC]             // Fetch PC of previous frame.
209   |   mvn CARG2, #~LJ_TTRUE
210   |  mov BASE, RB
211   |  // Prepending may overwrite the pcall frame, so do it at the end.
212   |   str CARG2, [RA, FRAME_PC]         // Prepend true to results.
213   |  sub RA, RA, #8
214   |
215   |->vm_returnc:
216   |  add RC, RC, #8                     // RC = (nresults+1)*8.
217   |   ands CARG1, PC, #FRAME_TYPE
218   |  str RC, SAVE_MULTRES
219   |   beq ->BC_RET_Z                    // Handle regular return to Lua.
220   |
221   |->vm_return:
222   |  // BASE = base, RA = resultptr, RC/MULTRES = (nresults+1)*8, PC = return
223   |  // CARG1 = PC & FRAME_TYPE
224   |  bic RB, PC, #FRAME_TYPEP
225   |   cmp CARG1, #FRAME_C
226   |  sub RB, BASE, RB                   // RB = previous base.
227   |   bne ->vm_returnp
228   |
229   |  str RB, L->base
230   |   ldr KBASE, SAVE_NRES
231   |    mv_vmstate CARG4, C
232   |   sub BASE, BASE, #8
233   |  subs CARG3, RC, #8
234   |   lsl KBASE, KBASE, #3              // KBASE = (nresults_wanted+1)*8
235   |    st_vmstate CARG4
236   |  beq >2
237   |1:
238   |  subs CARG3, CARG3, #8
239   |   ldrd CARG12, [RA], #8
240   |   strd CARG12, [BASE], #8
241   |  bne <1
242   |2:
243   |  cmp KBASE, RC                      // More/less results wanted?
244   |  bne >6
245   |3:
246   |  str BASE, L->top                   // Store new top.
247   |
248   |->vm_leave_cp:
249   |  ldr RC, SAVE_CFRAME                // Restore previous C frame.
250   |   mov CRET1, #0                     // Ok return status for vm_pcall.
251   |  str RC, L->cframe
252   |
253   |->vm_leave_unw:
254   |  restoreregs_ret
255   |
256   |6:
257   |  blt >7                             // Less results wanted?
258   |  // More results wanted. Check stack size and fill up results with nil.
259   |  ldr CARG3, L->maxstack
260   |   mvn CARG2, #~LJ_TNIL
261   |  cmp BASE, CARG3
262   |  bhs >8
263   |   str CARG2, [BASE, #4]
264   |  add RC, RC, #8
265   |  add BASE, BASE, #8
266   |  b <2
267   |
268   |7:  // Less results wanted.
269   |  sub CARG1, RC, KBASE
270   |  cmp KBASE, #0                      // LUA_MULTRET+1 case?
271   |  subne BASE, BASE, CARG1            // Either keep top or shrink it.
272   |  b <3
273   |
274   |8:  // Corner case: need to grow stack for filling up results.
275   |  // This can happen if:
276   |  // - A C function grows the stack (a lot).
277   |  // - The GC shrinks the stack in between.
278   |  // - A return back from a lua_call() with (high) nresults adjustment.
279   |  str BASE, L->top                   // Save current top held in BASE (yes).
280   |  mov CARG2, KBASE
281   |  mov CARG1, L
282   |  bl extern lj_state_growstack       // (lua_State *L, int n)
283   |  ldr BASE, L->top                   // Need the (realloced) L->top in BASE.
284   |  b <2
285   |
286   |->vm_unwind_c:                       // Unwind C stack, return from vm_pcall.
287   |  NYI
288   |->vm_unwind_c_eh:                    // Landing pad for external unwinder.
289   |  NYI
290   |
291   |->vm_unwind_ff:                      // Unwind C stack, return from ff pcall.
292   |  NYI
293   |->vm_unwind_ff_eh:                   // Landing pad for external unwinder.
294   |  NYI
295   |
296   |//-----------------------------------------------------------------------
297   |//-- Grow stack for calls -----------------------------------------------
298   |//-----------------------------------------------------------------------
299   |
300   |->vm_growstack_c:                    // Grow stack for C function.
301   |  NYI
302   |
303   |->vm_growstack_l:                    // Grow stack for Lua function.
304   |  NYI
305   |
306   |//-----------------------------------------------------------------------
307   |//-- Entry points into the assembler VM ---------------------------------
308   |//-----------------------------------------------------------------------
309   |
310   |->vm_resume:                         // Setup C frame and resume thread.
311   |  NYI
312   |
313   |->vm_pcall:                          // Setup protected C frame and enter VM.
314   |  // (lua_State *L, TValue *base, int nres1, ptrdiff_t ef)
315   |  saveregs
316   |  mov PC, #FRAME_CP
317   |  str CARG4, SAVE_ERRF
318   |  b >1
319   |
320   |->vm_call:                           // Setup C frame and enter VM.
321   |  // (lua_State *L, TValue *base, int nres1)
322   |  saveregs
323   |  mov PC, #FRAME_C
324   |
325   |1:  // Entry point for vm_pcall above (PC = ftype).
326   |  ldr RC, L:CARG1->cframe
327   |   str CARG3, SAVE_NRES
328   |    mov L, CARG1
329   |   str CARG1, SAVE_L
330   |    mov BASE, CARG2
331   |  str sp, L->cframe                  // Add our C frame to cframe chain.
332   |    ldr DISPATCH, L->glref           // Setup pointer to dispatch table.
333   |   str CARG1, SAVE_PC                // Any value outside of bytecode is ok.
334   |  str RC, SAVE_CFRAME
335   |    add DISPATCH, DISPATCH, #GG_G2DISP
336   |
337   |3:  // Entry point for vm_cpcall/vm_resume (BASE = base, PC = ftype).
338   |  ldr RB, L->base                    // RB = old base (for vmeta_call).
339   |   ldr CARG1, L->top
340   |    mov MASKR8, #255
341   |  add PC, PC, BASE
342   |    lsl MASKR8, MASKR8, #3           // MASKR8 = 255*8.
343   |  sub PC, PC, RB                     // PC = frame delta + frame type
344   |    mv_vmstate CARG2, INTERP
345   |   sub NARGS8:RC, CARG1, BASE
346   |    st_vmstate CARG2
347   |
348   |->vm_call_dispatch:
349   |  // RB = old base, BASE = new base, RC = nargs*8, PC = caller PC
350   |  ldrd CARG34, [BASE, FRAME_FUNC]
351   |  checkfunc CARG4, ->vmeta_call
352   |
353   |->vm_call_dispatch_f:
354   |  ins_call
355   |  // BASE = new base, RC = nargs*8
356   |
357   |->vm_cpcall:                         // Setup protected C frame, call C.
358   |  // (lua_State *L, lua_CFunction func, void *ud, lua_CPFunction cp)
359   |  saveregs
360   |  mov L, CARG1
361   |   ldr RA, L:CARG1->stack
362   |  str CARG1, SAVE_L
363   |   ldr RB, L->top
364   |  str CARG1, SAVE_PC                 // Any value outside of bytecode is ok.
365   |  ldr RC, L->cframe
366   |   sub RA, RA, RB                    // Compute -savestack(L, L->top).
367   |  str sp, L->cframe                  // Add our C frame to cframe chain.
368   |  mov RB, #0
369   |   str RA, SAVE_NRES                 // Neg. delta means cframe w/o frame.
370   |  str RB, SAVE_ERRF                  // No error function.
371   |  str RC, SAVE_CFRAME
372   |  blx CARG4                  // (lua_State *L, lua_CFunction func, void *ud)
373   |   ldr DISPATCH, L->glref            // Setup pointer to dispatch table.
374   |  movs BASE, CRET1
375   |    mov PC, #FRAME_CP
376   |   add DISPATCH, DISPATCH, #GG_G2DISP
377   |  bne <3                             // Else continue with the call.
378   |  b ->vm_leave_cp                    // No base? Just remove C frame.
379   |
380   |//-----------------------------------------------------------------------
381   |//-- Metamethod handling ------------------------------------------------
382   |//-----------------------------------------------------------------------
383   |
384   |//-- Continuation dispatch ----------------------------------------------
385   |
386   |->cont_dispatch:
387   |  NYI
388   |
389   |->cont_cat:
390   |  NYI
391   |
392   |//-- Table indexing metamethods -----------------------------------------
393   |
394   |->vmeta_tgets:
395   |  NYI
396   |
397   |->vmeta_tgetb:
398   |  NYI
399   |
400   |->vmeta_tgetv:
401   |  NYI
402   |
403   |//-----------------------------------------------------------------------
404   |
405   |->vmeta_tsets:
406   |  NYI
407   |
408   |->vmeta_tsetb:
409   |  NYI
410   |
411   |->vmeta_tsetv:
412   |  NYI
413   |
414   |//-- Comparison metamethods ---------------------------------------------
415   |
416   |->vmeta_comp:
417   |  NYI
418   |
419   |->cont_nop:
420   |  NYI
421   |
422   |->cont_ra:                           // RA = resultptr
423   |  NYI
424   |
425   |->cont_condt:                        // RA = resultptr
426   |  NYI
427   |
428   |->cont_condf:                        // RA = resultptr
429   |  NYI
430   |
431   |->vmeta_equal:
432   |  NYI
433   |
434   |//-- Arithmetic metamethods ---------------------------------------------
435   |
436   |->vmeta_arith_vn:
437   |  NYI
438   |
439   |->vmeta_arith_nv:
440   |  NYI
441   |
442   |->vmeta_unm:
443   |  NYI
444   |
445   |->vmeta_arith_vv:
446   |  NYI
447   |
448   |->vmeta_binop:
449   |  NYI
450   |
451   |->vmeta_len:
452   |  NYI
453   |
454   |//-- Call metamethod ----------------------------------------------------
455   |
456   |->vmeta_call:                        // Resolve and call __call metamethod.
457   |  NYI
458   |
459   |->vmeta_callt:                       // Resolve __call for BC_CALLT.
460   |  NYI
461   |
462   |//-- Argument coercion for 'for' statement ------------------------------
463   |
464   |->vmeta_for:
465   |  NYI
466   |
467   |//-----------------------------------------------------------------------
468   |//-- Fast functions -----------------------------------------------------
469   |//-----------------------------------------------------------------------
470   |
471   |.macro .ffunc, name
472   |->ff_ .. name:
473   |.endmacro
474   |
475   |.macro .ffunc_1, name
476   |->ff_ .. name:
477   |  NYI
478   |.endmacro
479   |
480   |.macro .ffunc_2, name
481   |->ff_ .. name:
482   |  NYI
483   |.endmacro
484   |
485   |.macro .ffunc_n, name
486   |  .ffunc_1 name
487   |  NYI
488   |.endmacro
489   |
490   |.macro .ffunc_nn, name
491   |  .ffunc_2 name
492   |  NYI
493   |.endmacro
494   |
495   |.macro ffgccheck
496   |  NYI
497   |.endmacro
498   |
499   |//-- Base library: checks -----------------------------------------------
500   |
501   |.ffunc assert
502   |  NYI
503   |
504   |.ffunc type
505   |  NYI
506   |
507   |//-- Base library: getters and setters ---------------------------------
508   |
509   |.ffunc_1 getmetatable
510   |  NYI
511   |
512   |.ffunc_2 setmetatable
513   |  NYI
514   |
515   |.ffunc rawget
516   |  NYI
517   |
518   |//-- Base library: conversions ------------------------------------------
519   |
520   |.ffunc tonumber
521   |  NYI
522   |
523   |.ffunc_1 tostring
524   |  NYI
525   |
526   |//-- Base library: iterators -------------------------------------------
527   |
528   |.ffunc next
529   |  NYI
530   |
531   |.ffunc_1 pairs
532   |  NYI
533   |
534   |.ffunc_2 ipairs_aux
535   |  NYI
536   |
537   |.ffunc_1 ipairs
538   |  NYI
539   |
540   |//-- Base library: catch errors ----------------------------------------
541   |
542   |.ffunc pcall
543   |  NYI
544   |
545   |.ffunc_2 xpcall
546   |  NYI
547   |
548   |//-- Coroutine library --------------------------------------------------
549   |
550   |.macro coroutine_resume_wrap, resume
551   |.if resume
552   |.ffunc_1 coroutine_resume
553   |.else
554   |.ffunc coroutine_wrap_aux
555   |.endif
556   |  NYI
557   |.endmacro
558   |
559   |  coroutine_resume_wrap 1            // coroutine.resume
560   |  coroutine_resume_wrap 0            // coroutine.wrap
561   |
562   |.ffunc coroutine_yield
563   |  NYI
564   |
565   |//-- Math library -------------------------------------------------------
566   |
567   |.ffunc_n math_abs
568   |  NYI
569   |
570   |->fff_restv:
571   |  NYI
572   |
573   |->fff_res1:
574   |  NYI
575   |
576   |->fff_res:
577   |  NYI
578   |
579   |.macro math_extern, func
580   |  .ffunc math_ .. func
581   |  NYI
582   |.endmacro
583   |
584   |.macro math_extern2, func
585   |  .ffunc math_ .. func
586   |  NYI
587   |.endmacro
588   |
589   |.macro math_round, func
590   |  .ffunc math_ .. func
591   |  NYI
592   |.endmacro
593   |
594   |  math_round floor
595   |  math_round ceil
596   |
597   |  math_extern sqrt
598   |  math_extern log
599   |  math_extern log10
600   |  math_extern exp
601   |  math_extern sin
602   |  math_extern cos
603   |  math_extern tan
604   |  math_extern asin
605   |  math_extern acos
606   |  math_extern atan
607   |  math_extern sinh
608   |  math_extern cosh
609   |  math_extern tanh
610   |  math_extern2 pow
611   |  math_extern2 atan2
612   |  math_extern2 fmod
613   |
614   |->ff_math_deg:
615   |.ffunc_n math_rad
616   |  NYI
617   |
618   |.ffunc math_ldexp
619   |  NYI
620   |
621   |.ffunc math_frexp
622   |  NYI
623   |
624   |.ffunc math_modf
625   |  NYI
626   |
627   |.macro math_minmax, name, cmpop
628   |  .ffunc_1 name
629   |  NYI
630   |.endmacro
631   |
632   |  math_minmax math_min, NYI
633   |  math_minmax math_max, NYI
634   |
635   |//-- String library -----------------------------------------------------
636   |
637   |.ffunc_1 string_len
638   |  NYI
639   |
640   |.ffunc string_byte                   // Only handle the 1-arg case here.
641   |  NYI
642   |
643   |.ffunc string_char                   // Only handle the 1-arg case here.
644   |  NYI
645   |
646   |.ffunc string_sub
647   |  NYI
648   |
649   |.ffunc string_rep                    // Only handle the 1-char case inline.
650   |  NYI
651   |
652   |.ffunc string_reverse
653   |  NYI
654   |
655   |.macro ffstring_case, name, lo
656   |  .ffunc name
657   |  NYI
658   |.endmacro
659   |
660   |ffstring_case string_lower, 65
661   |ffstring_case string_upper, 97
662   |
663   |//-- Table library ------------------------------------------------------
664   |
665   |.ffunc_1 table_getn
666   |  NYI
667   |
668   |//-- Bit library --------------------------------------------------------
669   |
670   |.macro .ffunc_bit, name
671   |  .ffunc_n bit_..name
672   |  NYI
673   |.endmacro
674   |
675   |.ffunc_bit tobit
676   |  NYI
677   |->fff_resbit:
678   |  NYI
679   |
680   |.macro .ffunc_bit_op, name, ins
681   |  .ffunc_bit name
682   |  NYI
683   |.endmacro
684   |
685   |.ffunc_bit_op band, and
686   |.ffunc_bit_op bor, or
687   |.ffunc_bit_op bxor, xor
688   |
689   |.ffunc_bit bswap
690   |  NYI
691   |
692   |.ffunc_bit bnot
693   |  NYI
694   |
695   |.macro .ffunc_bit_sh, name, ins, shmod
696   |  .ffunc_nn bit_..name
697   |  NYI
698   |.endmacro
699   |
700   |.ffunc_bit_sh lshift, NYI, 1
701   |.ffunc_bit_sh rshift, NYI, 1
702   |.ffunc_bit_sh arshift, NYI, 1
703   |.ffunc_bit_sh rol, NYI, 2
704   |.ffunc_bit_sh ror, NYI, 0
705   |
706   |//-----------------------------------------------------------------------
707   |
708   |->fff_fallback:                      // Call fast function fallback handler.
709   |  NYI
710   |
711   |->fff_gcstep:                        // Call GC step function.
712   |  NYI
713   |
714   |//-----------------------------------------------------------------------
715   |//-- Special dispatch targets -------------------------------------------
716   |//-----------------------------------------------------------------------
717   |
718   |->vm_record:                         // Dispatch target for recording phase.
719 #if LJ_HASJIT
720   |  NYI
721 #endif
722   |
723   |->vm_rethook:                        // Dispatch target for return hooks.
724   |  NYI
725   |
726   |->vm_inshook:                        // Dispatch target for instr/line hooks.
727   |  NYI
728   |
729   |->cont_hook:                         // Continue from hook yield.
730   |  NYI
731   |
732   |->vm_hotloop:                        // Hot loop counter underflow.
733 #if LJ_HASJIT
734   |  NYI
735 #endif
736   |
737   |->vm_callhook:                       // Dispatch target for call hooks.
738   |  NYI
739   |
740   |->vm_hotcall:                        // Hot call counter underflow.
741   |  NYI
742   |
743   |//-----------------------------------------------------------------------
744   |//-- Trace exit handler -------------------------------------------------
745   |//-----------------------------------------------------------------------
746   |
747   |->vm_exit_handler:
748 #if LJ_HASJIT
749   |  NYI
750 #endif
751   |->vm_exit_interp:
752 #if LJ_HASJIT
753   |  NYI
754 #endif
755   |
756   |//-----------------------------------------------------------------------
757   |//-- Math helper functions ----------------------------------------------
758   |//-----------------------------------------------------------------------
759   |
760   |// FP value rounding. Called by math.floor/math.ceil fast functions
761   |// and from JIT code.
762   |//
763   |.macro vm_round, name, mode
764   |->name:
765   |  NYI
766   |.endmacro
767   |
768   |  vm_round vm_floor, 0
769   |  vm_round vm_ceil,  1
770 #if LJ_HASJIT
771   |  vm_round vm_trunc, 2
772 #else
773   |->vm_trunc:
774 #endif
775   |
776   |->vm_powi:
777 #if LJ_HASJIT
778   |  NYI
779 #endif
780   |
781   |->vm_foldfpm:
782 #if LJ_HASJIT
783   |  NYI
784 #endif
785   |
786   |// Callable from C: double lj_vm_foldarith(double x, double y, int op)
787   |// Compute x op y for basic arithmetic operators (+ - * / % ^ and unary -)
788   |// and basic math functions. ORDER ARITH
789   |->vm_foldarith:
790   |  NYI
791   |
792   |//-----------------------------------------------------------------------
793   |//-- Miscellaneous functions --------------------------------------------
794   |//-----------------------------------------------------------------------
795   |
796   |//-----------------------------------------------------------------------
797   |//-- FFI helper functions -----------------------------------------------
798   |//-----------------------------------------------------------------------
799   |
800   |->vm_ffi_call:
801 #if LJ_HASFFI
802   |  NYI
803 #endif
804   |
805   |//-----------------------------------------------------------------------
808 /* Generate the code for a single instruction. */
809 static void build_ins(BuildCtx *ctx, BCOp op, int defop)
811   int vk = 0;
812   |=>defop:
814   switch (op) {
816   /* -- Comparison ops ---------------------------------------------------- */
818   /* Remember: all ops branch for a true comparison, fall through otherwise. */
820   case BC_ISLT: case BC_ISGE: case BC_ISLE: case BC_ISGT:
821     |  NYI
822     break;
824   case BC_ISEQV: case BC_ISNEV:
825     vk = op == BC_ISEQV;
826     |  NYI
827     break;
829   case BC_ISEQS: case BC_ISNES:
830     vk = op == BC_ISEQS;
831     |  NYI
832     break;
834   case BC_ISEQN: case BC_ISNEN:
835     vk = op == BC_ISEQN;
836     |  NYI
837     break;
839   case BC_ISEQP: case BC_ISNEP:
840     vk = op == BC_ISEQP;
841     |  NYI
842     break;
844   /* -- Unary test and copy ops ------------------------------------------- */
846   case BC_ISTC: case BC_ISFC: case BC_IST: case BC_ISF:
847     |  NYI
848     break;
850   /* -- Unary ops --------------------------------------------------------- */
852   case BC_MOV:
853     |  NYI
854     break;
855   case BC_NOT:
856     |  NYI
857     break;
858   case BC_UNM:
859     |  NYI
860     break;
861   case BC_LEN:
862     |  NYI
863     break;
865   /* -- Binary ops -------------------------------------------------------- */
867   case BC_ADDVN: case BC_ADDNV: case BC_ADDVV:
868     |  NYI
869     break;
870   case BC_SUBVN: case BC_SUBNV: case BC_SUBVV:
871     |  NYI
872     break;
873   case BC_MULVN: case BC_MULNV: case BC_MULVV:
874     |  NYI
875     break;
876   case BC_DIVVN: case BC_DIVNV: case BC_DIVVV:
877     |  NYI
878     break;
879   case BC_MODVN:
880     |  NYI
881     break;
882   case BC_MODNV: case BC_MODVV:
883     |  NYI
884     break;
885   case BC_POW:
886     |  NYI
887     break;
889   case BC_CAT:
890     |  NYI
891     break;
893   /* -- Constant ops ------------------------------------------------------ */
895   case BC_KSTR:
896     |  NYI
897     break;
898   case BC_KCDATA:
899 #if LJ_HASFFI
900     |  NYI
901 #endif
902     break;
903   case BC_KSHORT:
904     |  NYI
905     break;
906   case BC_KNUM:
907     |  NYI
908     break;
909   case BC_KPRI:
910     |  NYI
911     break;
912   case BC_KNIL:
913     |  NYI
914     break;
916   /* -- Upvalue and function ops ------------------------------------------ */
918   case BC_UGET:
919     |  NYI
920     break;
921   case BC_USETV:
922     |  NYI
923     break;
924   case BC_USETS:
925     |  NYI
926     break;
927   case BC_USETN:
928     |  NYI
929     break;
930   case BC_USETP:
931     |  NYI
932     break;
934   case BC_UCLO:
935     |  NYI
936     break;
938   case BC_FNEW:
939     |  NYI
940     break;
942   /* -- Table ops --------------------------------------------------------- */
944   case BC_TNEW:
945   case BC_TDUP:
946     |  NYI
947     break;
949   case BC_GGET:
950   case BC_GSET:
951     |  NYI
952     break;
954   case BC_TGETV:
955     |  NYI
956     break;
957   case BC_TGETS:
958     |  NYI
959     break;
960   case BC_TGETB:
961     |  NYI
962     break;
964   case BC_TSETV:
965     |  NYI
966     break;
967   case BC_TSETS:
968     |  NYI
969     break;
970   case BC_TSETB:
971     |  NYI
972     break;
974   case BC_TSETM:
975     |  NYI
976     break;
978   /* -- Calls and vararg handling ----------------------------------------- */
980   case BC_CALLM:
981     |  NYI
982     break;
983   case BC_CALL:
984     |  NYI
985     break;
987   case BC_CALLMT:
988     |  NYI
989     break;
990   case BC_CALLT:
991     |  NYI
992     break;
994   case BC_ITERC:
995     |  NYI
996     break;
998   case BC_ITERN:
999     |  NYI
1000     break;
1002   case BC_ISNEXT:
1003     |  NYI
1004     break;
1006   case BC_VARG:
1007     |  NYI
1008     break;
1010   /* -- Returns ----------------------------------------------------------- */
1012   case BC_RETM:
1013     |  NYI
1014     break;
1016   case BC_RET:
1017     |  // RA = results*8, RC = nresults+1
1018     |  ldr PC, [BASE, FRAME_PC]
1019     |   lsl RC, RC, #3
1020     |    add RA, BASE, RA
1021     |   str RC, SAVE_MULTRES
1022     |1:
1023     |  ands CARG1, PC, #FRAME_TYPE
1024     |   eor CARG2, PC, #FRAME_VARG
1025     |   ldreq INS, [PC, #-4]
1026     |  bne ->BC_RETV2_Z
1027     |
1028     |->BC_RET_Z:
1029     |  // BASE = base, RA = resultptr, RC = (nresults+1)*8, PC = return
1030     |  NYI
1031     |
1032     |->BC_RETV1_Z:  // Non-standard return case.
1033     |  add RA, BASE, RA
1034     |->BC_RETV2_Z:
1035     |  tst CARG2, #FRAME_TYPEP
1036     |  bne ->vm_return
1037     |  // Return from vararg function: relocate BASE down.
1038     |  sub BASE, BASE, CARG2
1039     |  ldr PC, [BASE, FRAME_PC]
1040     |  b <1
1041     break;
1043   case BC_RET0: case BC_RET1:
1044     |  // RA = results*8, RC = nresults+1
1045     |  ldr PC, [BASE, FRAME_PC]
1046     |   lsl RC, RC, #3
1047     |   str RC, SAVE_MULTRES
1048     |  ands CARG1, PC, #FRAME_TYPE
1049     |   eor CARG2, PC, #FRAME_VARG
1050     |   ldreq INS, [PC, #-4]
1051     |  bne ->BC_RETV1_Z
1052     if (op == BC_RET1) {
1053       |  ldrd CARG12, [BASE, RA]
1054     }
1055     |  sub CARG4, BASE, #8
1056     |   decode_RA8 RA, INS
1057     if (op == BC_RET1) {
1058       |  strd CARG12, [CARG4]
1059     }
1060     |  sub BASE, CARG4, RA
1061     |   decode_RB8 RB, INS
1062     |  ldr LFUNC:CARG1, [BASE, FRAME_FUNC]
1063     |5:
1064     |  cmp RB, RC
1065     |  bhi >6
1066     |  ldr CARG2, LFUNC:CARG1->field_pc
1067     |   ins_next1
1068     |   ins_next2
1069     |  ldr KBASE, [CARG2, #PC2PROTO(k)]
1070     |   ins_next3
1071     |
1072     |6:  // Fill up results with nil.
1073     |  sub CARG2, CARG4, #4
1074     |  mvn CARG3, #~LJ_TNIL
1075     |  str CARG3, [CARG2, RC]
1076     |  add RC, RC, #8
1077     |  b <5
1078     break;
1080   /* -- Loops and branches ------------------------------------------------ */
1082   case BC_FORL:
1083 #if LJ_HASJIT
1084     |  hotloop
1085 #endif
1086     |  // Fall through. Assumes BC_IFORL follows.
1087     break;
1089   case BC_JFORI:
1090   case BC_JFORL:
1091 #if !LJ_HASJIT
1092     break;
1093 #endif
1094   case BC_FORI:
1095   case BC_IFORL:
1096     vk = (op == BC_IFORL || op == BC_JFORL);
1097     |  NYI
1098     break;
1100   case BC_ITERL:
1101 #if LJ_HASJIT
1102     |  hotloop
1103 #endif
1104     |  // Fall through. Assumes BC_IITERL follows.
1105     break;
1107   case BC_JITERL:
1108 #if !LJ_HASJIT
1109     break;
1110 #endif
1111   case BC_IITERL:
1112     |  NYI
1113     break;
1115   case BC_LOOP:
1116     |  NYI
1117     break;
1119   case BC_ILOOP:
1120     |  NYI
1121     break;
1123   case BC_JLOOP:
1124 #if LJ_HASJIT
1125     |  NYI
1126 #endif
1127     break;
1129   case BC_JMP:
1130     |  NYI
1131     break;
1133   /* -- Function headers -------------------------------------------------- */
1135   case BC_FUNCF:
1136 #if LJ_HASJIT
1137     |  hotcall
1138 #endif
1139   case BC_FUNCV:  /* NYI: compiled vararg functions. */
1140     |  // Fall through. Assumes BC_IFUNCF/BC_IFUNCV follow.
1141     break;
1143   case BC_JFUNCF:
1144 #if !LJ_HASJIT
1145     break;
1146 #endif
1147   case BC_IFUNCF:
1148     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
1149     |  ldr CARG1, L->maxstack
1150     |   ldrb CARG2, [PC, #-4+PC2PROTO(numparams)]
1151     |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
1152     |  cmp RA, CARG1
1153     |  bhi ->vm_growstack_l
1154     |  ins_next1
1155     |  ins_next2
1156     |2:
1157     |  cmp NARGS8:RC, CARG2, lsl #3     // Check for missing parameters.
1158     |  ble >3
1159     if (op == BC_JFUNCF) {
1160       |  NYI
1161     } else {
1162       |  ins_next3
1163     }
1164     |
1165     |3:  // Clear missing parameters.
1166     |  mvn CARG1, #~LJ_TNIL
1167     |  str CARG1, [BASE, NARGS8:RC]
1168     |  add NARGS8:RC, NARGS8:RC, #8
1169     |  b <2
1170     break;
1172   case BC_JFUNCV:
1173 #if !LJ_HASJIT
1174     break;
1175 #endif
1176     |  NYI  // NYI: compiled vararg functions
1177     break;  /* NYI: compiled vararg functions. */
1179   case BC_IFUNCV:
1180     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = LFUNC, RC = nargs*8
1181     |  ldr CARG1, L->maxstack
1182     |   add CARG4, BASE, RC
1183     |  add RA, RA, RC
1184     |   str LFUNC:CARG3, [CARG4]        // Store copy of LFUNC.
1185     |   add CARG2, RC, #8+FRAME_VARG
1186     |    ldr KBASE, [PC, #-4+PC2PROTO(k)]
1187     |  cmp RA, CARG1
1188     |   str CARG2, [CARG4, #4]          // Store delta + FRAME_VARG.
1189     |  bhs ->vm_growstack_l
1190     |  ldrb RB, [PC, #-4+PC2PROTO(numparams)]
1191     |   mov RA, BASE
1192     |   mov RC, CARG4
1193     |  cmp RB, #0
1194     |   add BASE, CARG4, #8
1195     |  beq >3
1196     |  mvn CARG3, #~LJ_TNIL
1197     |1:
1198     |  cmp RA, RC                       // Less args than parameters?
1199     |   ldrdlo CARG12, [RA], #8
1200     |   mvnhs CARG2, CARG3
1201     |    strlo CARG3, [RA, #-4]         // Clear old fixarg slot (help the GC).
1202     |2:
1203     |  subs RB, RB, #1
1204     |   strd CARG12, [CARG4, #8]!
1205     |  bne <1
1206     |3:
1207     |  ins_next
1208     break;
1210   case BC_FUNCC:
1211   case BC_FUNCCW:
1212     |  // BASE = new base, RA = BASE+framesize*8, CARG3 = CFUNC, RC = nargs*8
1213     if (op == BC_FUNCC) {
1214       |  ldr CARG4, CFUNC:CARG3->f
1215     } else {
1216       |  ldr CARG4, [DISPATCH, #DISPATCH_GL(wrapf)]
1217     }
1218     |   add CARG2, RA, NARGS8:RC
1219     |   ldr CARG1, L->maxstack
1220     |  add RC, BASE, NARGS8:RC
1221     |    str BASE, L->base
1222     |   cmp CARG2, CARG1
1223     |  str RC, L->top
1224     if (op == BC_FUNCCW) {
1225       |  ldr CARG2, CFUNC:CARG3->f
1226     }
1227     |    mv_vmstate CARG3, C
1228     |  mov CARG1, L
1229     |   bhi ->vm_growstack_c            // Need to grow stack.
1230     |    st_vmstate CARG3
1231     |  blx CARG4                        // (lua_State *L [, lua_CFunction f])
1232     |  // Returns nresults.
1233     |  ldr BASE, L->base
1234     |    mv_vmstate CARG3, INTERP
1235     |   ldr CRET2, L->top
1236     |   lsl RC, CRET1, #3
1237     |    st_vmstate CARG3
1238     |  ldr PC, [BASE, FRAME_PC]
1239     |   sub RA, CRET2, RC               // RA = L->top - nresults*8
1240     |  b ->vm_returnc
1241     break;
1243   /* ---------------------------------------------------------------------- */
1245   default:
1246     fprintf(stderr, "Error: undefined opcode BC_%s\n", bc_names[op]);
1247     exit(2);
1248     break;
1249   }
1252 static int build_backend(BuildCtx *ctx)
1254   int op;
1256   dasm_growpc(Dst, BC__MAX);
1258   build_subroutines(ctx);
1260   |.code_op
1261   for (op = 0; op < BC__MAX; op++)
1262     build_ins(ctx, (BCOp)op, op);
1264   return BC__MAX;
1267 /* Emit pseudo frame-info for all assembler functions. */
1268 static void emit_asm_debug(BuildCtx *ctx)
1270   int i;
1271   switch (ctx->mode) {
1272   case BUILD_elfasm:
1273     fprintf(ctx->fp, "\t.section .debug_frame,\"\",%%progbits\n");
1274     fprintf(ctx->fp,
1275         ".Lframe0:\n"
1276         "\t.long .LECIE0-.LSCIE0\n"
1277         ".LSCIE0:\n"
1278         "\t.long 0xffffffff\n"
1279         "\t.byte 0x1\n"
1280         "\t.string \"\"\n"
1281         "\t.uleb128 0x1\n"
1282         "\t.sleb128 -4\n"
1283         "\t.byte 0xe\n"                         /* Return address is in lr. */
1284         "\t.byte 0xc\n\t.uleb128 0xd\n\t.uleb128 0\n"   /* def_cfa sp */
1285         "\t.align 2\n"
1286         ".LECIE0:\n\n");
1287     fprintf(ctx->fp,
1288         ".LSFDE0:\n"
1289         "\t.long .LEFDE0-.LASFDE0\n"
1290         ".LASFDE0:\n"
1291         "\t.long .Lframe0\n"
1292         "\t.long .Lbegin\n"
1293         "\t.long %d\n"
1294         "\t.byte 0xe\n\t.uleb128 %d\n"          /* def_cfa_offset */
1295         "\t.byte 0x8e\n\t.uleb128 1\n",         /* Restore lr. */
1296         (int)ctx->codesz, CFRAME_SIZE);
1297     for (i = 11; i >= 4; i--)  /* Restore r4-r11. */
1298       fprintf(ctx->fp, "\t.byte %d\n\t.uleb128 %d\n", 0x80+i, 2+(11-i));
1299     fprintf(ctx->fp,
1300         "\t.align 2\n"
1301         ".LEFDE0:\n\n");
1302     /* NYI: emit ARM.exidx. */
1303     break;
1304   default:
1305     break;
1306   }