]> gitweb.factorcode.org Git - factor.git/blob - basis/bootstrap/assembler/arm.64.factor
arm: notes
[factor.git] / basis / bootstrap / assembler / arm.64.factor
1 ! Copyright (C) 2020 Doug Coleman.
2 ! See http://factorcode.org/license.txt for BSD license.
3 USING: bootstrap.image.private compiler.codegen.relocation
4 compiler.constants compiler.units cpu.arm.assembler
5 cpu.arm.assembler.opcodes generic.single.private
6 kernel kernel.private layouts locals.backend
7 math math.private memory namespaces sequences slots.private
8 strings.private threads.private vocabs ;
9 IN: bootstrap.assembler.arm
10
11 8 \ cell set
12
13 big-endian off
14
15 ! Stack frame
16 ! https://docs.microsoft.com/en-us/cpp/build/arm64-exception-handling?view=vs-2019
17
18 ! x0    Volatile        Parameter/scratch register 1, result register
19 ! x1-x7 Volatile        Parameter/scratch register 2-8
20 ! x8-x15        Volatile        Scratch registers
21 ! x16-x17       Volatile        Intra-procedure-call scratch registers
22 ! x18   Non-volatile    Platform register: in kernel mode, points to KPCR for the current processor;
23 !   in user mode, points to TEB
24 ! x19-x28       Non-volatile    Scratch registers
25 ! x29/fp        Non-volatile    Frame pointer
26 ! x30/lr        Non-volatile    Link registers
27
28 : stack-frame-size ( -- n ) 4 bootstrap-cells ;
29 : volatile-regs ( -- seq ) { X0 X1 X2 X3 X4 X5 X6 X7 X8 X9 X10 X11 X12 X13 X14 X15 X16 X17 } ;
30 ! windows arm - X18 is non-volatile https://docs.microsoft.com/en-us/cpp/build/arm64-windows-abi-conventions?view=msvc-160
31 : nv-regs ( -- seq ) { X18 X19 X20 X21 X22 X23 X24 X25 X26 X27 X28 X29 X30 } ;
32
33 ! callee-save = non-volatile aka call-preserved
34
35 ! x30 is the link register (used to return from subroutines)
36 ! x29 is the frame register
37 ! x19 to x29 are callee-saved
38 ! x18 is the 'platform register', used for some operating-system-specific special purpose,
39 !   or an additional caller-saved register
40 ! x16 and x17 are the Intra-Procedure-call scratch register
41 ! x9 to x15: used to hold local variables (caller saved)
42 ! x8: used to hold indirect return value address
43 ! x0 to x7: used to hold argument values passed to a subroutine, and also hold
44 !   results returned from a subroutine
45
46
47 ! https://en.wikichip.org/wiki/arm/aarch64
48 ! Generally, X0 through X18 (volatile, can corrupt) while X19-X29 must be preserved (non-volatile)
49 ! Volatile registers' content may change over a subroutine call
50 ! non-volatile register is a type of register with contents that must be preserved over subroutine calls
51 ! Register   Role    Requirement
52 ! X0 -  X7   Parameter/result registers   Can Corrupt (volatile)
53 ! X8         Indirect result location register (volatile)
54 ! X9 -  X15  Temporary registers (volatile)
55 ! X16 - X17  Intra-procedure call temporary (volatile)
56 ! x16 - syscall reg with SVC instructioin
57 ! X18        Platform register, otherwise temporary, DONT USE (volatile)
58
59 ! X19 - X29    Callee-saved register    Must preserve (non-volatile)
60 ! X29 - frame pointer register, must always be valid
61 ! X30    Link Register LR   Can Corrupt
62 ! X31  Stack Pointer SP
63 ! 16-byte stack alignment
64
65 ! stack walking - {fp, lr} pairs if compiled with frame pointers enabled
66
67 : arg1 ( -- reg ) X0 ;
68 : arg2 ( -- reg ) X1 ;
69 : arg3 ( -- reg ) X2 ;
70 : arg4 ( -- reg ) X3 ;
71
72 ! Red zone
73 ! windows arm64: 16 bytes https://devblogs.microsoft.com/oldnewthing/20190111-00/?p=100685
74 ! windows arm32: 8 bytes
75 ! x86/x64: 0 bytes
76 ! Apple arm64: 128 bytes https://developer.apple.com/documentation/xcode/writing_arm64_code_for_apple_platforms?language=objc
77 : red-zone-size ( -- n ) 16 ; ! 16 bytes on windows, or 128 bytes on linux? or 0?
78 ! 0 or 16 likely
79 ! no red zone on x86/x64 windows
80
81
82 ! https://github.com/MicrosoftDocs/cpp-docs/blob/master/docs/build/arm64-windows-abi-conventions.md
83
84 : shift-arg ( -- reg ) X1 ;
85 : div-arg ( -- reg ) X0 ;
86 : mod-arg ( -- reg ) X2 ;
87
88 ! caller-saved registers X9-X15
89 ! callee-saved registers X19-X29
90 : temp0 ( -- reg ) X9 ;
91 : temp1 ( -- reg ) X10 ;
92 : temp2 ( -- reg ) X11 ;
93 : temp3 ( -- reg ) X12 ;
94
95
96 ! : pic-tail-reg ( -- reg ) RBX ;
97 : return-reg ( -- reg ) X0 ;
98 : stack-reg ( -- reg ) SP ;
99 ! https://developer.arm.com/documentation/dui0801/a/Overview-of-AArch64-state/Link-registers
100 : link-reg ( -- reg ) X30 ; ! LR
101 ! : stack-frame-reg ( -- reg ) X29 ; ! FP
102 : vm-reg ( -- reg ) X28 ;
103 : ds-reg ( -- reg ) X27 ;
104 : rs-reg ( -- reg ) X26 ;
105 ! : ctx-reg ( -- reg ) R12 ;
106 ! : fixnum>slot@ ( -- ) temp0 1 SAR ;
107 ! : rex-length ( -- n ) 1 ;
108
109 ! rc-absolute-cell is just CONSTANT: 0
110 : jit-call ( name -- )
111     0 X0 MOVwi64
112     f rc-absolute-cell rel-dlsym
113     X0 BLR ;
114     ! RAX 0 MOV f rc-absolute-cell rel-dlsym
115     ! RAX CALL ;
116
117 :: jit-call-1arg ( arg1s name -- )
118     arg1s arg1 MOVr64
119     name jit-call ;
120     ! arg1 arg1s MOVr64
121     ! name jit-call ;
122
123 :: jit-call-2arg ( arg1s arg2s name -- )
124     arg1s arg1 MOVr64
125     arg2s arg2 MOVr64
126     name jit-call ;
127     ! arg1 arg1s MOV
128     ! arg2 arg2s MOV
129     ! name jit-call ;
130
131 [
132     ! pic-tail-reg 5 [RIP+] LEA
133     ! 0 JMP f rc-relative rel-word-pic-tail
134 ] JIT-WORD-JUMP jit-define
135
136 : jit-load-vm ( -- )
137     ! no-op on x86-64. in factor contexts vm-reg always contains the
138     ! vm pointer.
139     ;
140
141 : jit-load-context ( -- ) ;
142     ! ctx-reg vm-reg vm-context-offset [+] MOV ;
143
144 : jit-save-context ( -- ) ;
145     ! jit-load-context
146     ! The reason for -8 I think is because we are anticipating a CALL
147     ! instruction. After the call instruction, the contexts frame_top
148     ! will point to the origin jump address.
149     ! R11 RSP -8 [+] LEA
150     ! ctx-reg context-callstack-top-offset [+] R11 MOV
151     ! ctx-reg context-datastack-offset [+] ds-reg MOV
152     ! ctx-reg context-retainstack-offset [+] rs-reg MOV ;
153
154 ! ctx-reg must already have been loaded
155 : jit-restore-context ( -- ) ;
156     ! ds-reg ctx-reg context-datastack-offset [+] MOV
157     ! rs-reg ctx-reg context-retainstack-offset [+] MOV ;
158
159
160 [
161
162     ! ! ctx-reg is preserved across the call because it is non-volatile
163     ! ! in the C ABI
164     ! jit-save-context
165     ! ! call the primitive
166     ! arg1 vm-reg MOV
167     ! RAX 0 MOV f f rc-absolute-cell rel-dlsym
168     ! RAX CALL
169     ! jit-restore-context
170 ] JIT-PRIMITIVE jit-define
171
172
173 : jit-jump-quot ( -- )
174     quot-entry-point-offset arg1 ADR
175     arg1 BR ;
176     ! arg1 quot-entry-point-offset [+] JMP ;
177
178 : jit-call-quot ( -- )
179     quot-entry-point-offset arg1 ADR
180     arg1 BLR ;
181     ! arg1 quot-entry-point-offset [+] CALL ;
182
183 : signal-handler-save-regs ( -- regs ) { } ;
184     ! { RAX RCX RDX RBX RBP RSI RDI R8 R9 R10 R11 R12 R13 R14 R15 } ;
185
186
187 [
188     ! temp2 0 MOV f rc-absolute-cell rel-literal
189     ! temp1 temp2 CMP
190 ] PIC-CHECK-TUPLE jit-define
191
192
193
194 : jit->r ( -- )
195     1 bootstrap-cells rs-reg rs-reg ADDi64
196     -1 bootstrap-cells ds-reg rs-reg LDR-post ;
197
198 : jit-r> ( -- )
199     1 bootstrap-cells ds-reg ds-reg ADDi64
200     -1 bootstrap-cells rs-reg ds-reg LDR-post ;
201
202 : jit-2>r ( -- )
203     1 bootstrap-cells rs-reg rs-reg ADDi64
204     -1 bootstrap-cells ds-reg rs-reg LDR-post
205     1 bootstrap-cells rs-reg rs-reg ADDi64
206     -1 bootstrap-cells ds-reg rs-reg LDR-post ;
207
208 : jit-2r> ( -- )
209     1 bootstrap-cells ds-reg ds-reg ADDi64
210     -1 bootstrap-cells rs-reg ds-reg LDR-post
211     1 bootstrap-cells ds-reg ds-reg ADDi64
212     -1 bootstrap-cells rs-reg ds-reg LDR-post ;
213
214 : jit-3>r ( -- )
215     1 bootstrap-cells rs-reg rs-reg ADDi64
216     -1 bootstrap-cells ds-reg rs-reg LDR-post
217     1 bootstrap-cells rs-reg rs-reg ADDi64
218     -1 bootstrap-cells ds-reg rs-reg LDR-post
219     1 bootstrap-cells rs-reg rs-reg ADDi64
220     -1 bootstrap-cells ds-reg rs-reg LDR-post ;
221
222 : jit-3r> ( -- )
223     1 bootstrap-cells ds-reg ds-reg ADDi64
224     -1 bootstrap-cells rs-reg ds-reg LDR-post
225     1 bootstrap-cells ds-reg ds-reg ADDi64
226     -1 bootstrap-cells rs-reg ds-reg LDR-post
227     1 bootstrap-cells ds-reg ds-reg ADDi64
228     -1 bootstrap-cells rs-reg ds-reg LDR-post ;
229
230 ! Contexts
231 : jit-switch-context ( reg -- ) drop ;
232     ! ! Push a bogus return address so the GC can track this frame back
233     ! ! to the owner
234     ! 0 CALL
235
236     ! ! Make the new context the current one
237     ! ctx-reg swap MOV
238     ! vm-reg vm-context-offset [+] ctx-reg MOV
239
240     ! ! Load new stack pointer
241     ! RSP ctx-reg context-callstack-top-offset [+] MOV
242
243     ! ! Load new ds, rs registers
244     ! jit-restore-context
245
246     ! ctx-reg jit-update-tib ;
247
248 : jit-pop-context-and-param ( -- ) ;
249     ! arg1 ds-reg [] MOV
250     ! arg1 arg1 alien-offset [+] MOV
251     ! arg2 ds-reg -8 [+] MOV
252     ! ds-reg 16 SUB ;
253
254 : jit-push-param ( -- ) ;
255     ! ds-reg 8 ADD
256     ! ds-reg [] arg2 MOV ;
257
258 : jit-set-context ( -- ) ;
259     ! jit-pop-context-and-param
260     ! jit-save-context
261     ! arg1 jit-switch-context
262     ! RSP 8 ADD
263     ! jit-push-param ;
264
265 : jit-pop-quot-and-param ( -- ) ;
266     ! arg1 ds-reg [] MOV
267     ! arg2 ds-reg -8 [+] MOV
268     ! ds-reg 16 SUB ;
269
270 : jit-start-context ( -- ) ;
271     ! Create the new context in return-reg. Have to save context
272     ! twice, first before calling new_context() which may GC,
273     ! and again after popping the two parameters from the stack.
274     ! jit-save-context
275     ! vm-reg "new_context" jit-call-1arg
276
277     ! jit-pop-quot-and-param
278     ! jit-save-context
279     ! return-reg jit-switch-context
280     ! jit-push-param
281     ! jit-jump-quot ;
282
283 : jit-delete-current-context ( -- ) ;
284     ! vm-reg "delete_context" jit-call-1arg ;
285
286 [
287     ! jit->r
288     ! 0 CALL f rc-relative rel-word
289     ! jit-r>
290 ] JIT-DIP jit-define
291
292
293
294
295 [
296     ! 0 [RIP+] EAX MOV rc-relative rel-safepoint
297 ] JIT-SAFEPOINT jit-define
298
299 ! # All arm.64 subprimitives
300 {
301     { c-to-factor [
302
303             ! write()
304             ! 68 X8 MOVwi64
305             ! X2 MOVwi64
306             ! 0 SVC
307
308             ! exit(42)
309
310             ! 9999 BRK
311             ! 42 X0 MOVwi64
312             ! 93 X8 MOVwi64
313             ! 0 SVC
314
315             ! Rn Rd MOVr64 ! comment
316             arg1 arg2 MOVr64
317             vm-reg "begin_callback" jit-call-1arg
318
319             return-reg arg1 MOVr64 ! arg1 is return
320             jit-call-quot
321
322             vm-reg "end_callback" jit-call-1arg
323      ] }
324 } define-sub-primitives
325
326
327 ! {
328     ! ## Contexts
329     ! { (set-context) [ jit-set-context ] }
330     ! { (set-context-and-delete) [
331     !     jit-delete-current-context
332     !     jit-set-context
333     ! ] }
334     ! { (start-context) [ jit-start-context ] }
335     ! { (start-context-and-delete) [ jit-start-context-and-delete ] }
336
337     ! ## Entry points
338     ! { c-to-factor [
339     !     ! dst src MOV
340     !     ! arg2 arg1 MOV
341     !     ! vm-reg "begin_callback" jit-call-1arg
342
343     !     ! ! call the quotation
344     !     ! arg1 return-reg MOV
345     !     ! jit-call-quot
346
347     !     ! vm-reg "end_callback" jit-call-1arg
348
349     !     [
350
351     !         ! write()
352     !         ! 68 X8 MOVwi64
353     !         ! X2 MOVwi64
354     !         ! 0 SVC
355
356     !         ! exit(42)
357     !         9999 BRK
358     !         42 X0 MOVwi64
359     !         93 X8 MOVwi64
360     !         0 SVC
361
362             
363
364     !         ! Rn Rd MOVr64
365     !         ! arg1 arg2 MOVr64
366     !         ! vm-reg "begin_callback" jit-call-1arg
367
368     !         ! return-reg arg1 MOVr64 ! arg1 is return
369     !         ! jit-call-quot
370
371     !         ! vm-reg "end_callback" jit-call-1arg
372
373     !     ] assemble-arm %
374
375     ! ] }
376     ! { unwind-native-frames [ ] }
377
378     ! ## Math
379     ! { fixnum+ [ [ ADD ] "overflow_fixnum_add" jit-overflow ] }
380     ! { fixnum- [ [ SUB ] "overflow_fixnum_subtract" jit-overflow ] }
381     ! { fixnum* [
382     !     ds-reg 8 SUB
383     !     jit-save-context
384     !     RCX ds-reg [] MOV
385     !     RBX ds-reg 8 [+] MOV
386     !     RBX tag-bits get SAR
387     !     RAX RCX MOV
388     !     RBX IMUL
389     !     ds-reg [] RAX MOV
390     !     [ JNO ]
391     !     [
392     !         arg1 RCX MOV
393     !         arg1 tag-bits get SAR
394     !         arg2 RBX MOV
395     !         arg3 vm-reg MOV
396     !         "overflow_fixnum_multiply" jit-call
397     !     ]
398     !     jit-conditional
399     ! ] }
400
401     ! ## Misc
402     ! { fpu-state [
403     !     RSP 2 SUB
404     !     RSP [] FNSTCW
405     !     FNINIT
406     !     AX RSP [] MOV
407     !     RSP 2 ADD
408     ! ] }
409     ! { set-fpu-state [
410     !     RSP 2 SUB
411     !     RSP [] arg1 16-bit-version-of MOV
412     !     RSP [] FLDCW
413     !     RSP 2 ADD
414     ! ] }
415     ! { set-callstack [
416     !     ! Load callstack object
417     !     arg4 ds-reg [] MOV
418     !     ds-reg bootstrap-cell SUB
419     !     ! Get ctx->callstack_bottom
420     !     jit-load-context
421     !     arg1 ctx-reg context-callstack-bottom-offset [+] MOV
422     !     ! Get top of callstack object -- 'src' for memcpy
423     !     arg2 arg4 callstack-top-offset [+] LEA
424     !     ! Get callstack length, in bytes --- 'len' for memcpy
425     !     arg3 arg4 callstack-length-offset [+] MOV
426     !     arg3 tag-bits get SHR
427     !     ! Compute new stack pointer -- 'dst' for memcpy
428     !     arg1 arg3 SUB
429     !     ! Install new stack pointer
430     !     RSP arg1 MOV
431     !     ! Call memcpy; arguments are now in the correct registers
432     !     ! Create register shadow area for Win64
433     !     RSP 32 SUB
434     !     "factor_memcpy" jit-call
435     !     ! Tear down register shadow area
436     !     RSP 32 ADD
437     !     ! Return with new callstack
438     !     0 RET
439     ! ] }
440 ! } define-sub-primitives
441
442
443
444 ! C to Factor entry point
445 [
446     ! ! Optimizing compiler's side of callback accesses
447     ! ! arguments that are on the stack via the frame pointer.
448     ! ! On x86-32 fastcall, and x86-64, some arguments are passed
449     ! ! in registers, and so the only registers that are safe for
450     ! ! use here are frame-reg, nv-reg and vm-reg.
451     ! frame-reg PUSH
452     ! frame-reg stack-reg MOV
453
454     ! ! Save all non-volatile registers
455     ! nv-regs [ PUSH ] each
456
457     ! jit-save-tib
458
459     ! ! Load VM into vm-reg
460     ! vm-reg 0 MOV 0 rc-absolute-cell rel-vm
461
462     ! ! Save old context
463     ! nv-reg vm-reg vm-context-offset [+] MOV
464     ! nv-reg PUSH
465
466     ! ! Switch over to the spare context
467     ! nv-reg vm-reg vm-spare-context-offset [+] MOV
468     ! vm-reg vm-context-offset [+] nv-reg MOV
469
470     ! ! Save C callstack pointer
471     ! nv-reg context-callstack-save-offset [+] stack-reg MOV
472
473     ! ! Load Factor stack pointers
474     ! stack-reg nv-reg context-callstack-bottom-offset [+] MOV
475     ! nv-reg jit-update-tib
476     ! jit-install-seh
477
478     ! rs-reg nv-reg context-retainstack-offset [+] MOV
479     ! ds-reg nv-reg context-datastack-offset [+] MOV
480
481     ! ! Call into Factor code
482     ! link-reg 0 MOV f rc-absolute-cell rel-word
483     ! link-reg CALL
484
485     ! ! Load VM into vm-reg; only needed on x86-32, but doesn't
486     ! ! hurt on x86-64
487     ! vm-reg 0 MOV 0 rc-absolute-cell rel-vm
488
489     ! ! Load C callstack pointer
490     ! nv-reg vm-reg vm-context-offset [+] MOV
491     ! stack-reg nv-reg context-callstack-save-offset [+] MOV
492
493     ! ! Load old context
494     ! nv-reg POP
495     ! vm-reg vm-context-offset [+] nv-reg MOV
496
497     ! ! Restore non-volatile registers
498     ! jit-restore-tib
499
500     ! nv-regs <reversed> [ POP ] each
501
502     ! frame-reg POP
503
504     ! ! Callbacks which return structs, or use stdcall/fastcall/thiscall,
505     ! ! need a parameter here.
506
507     ! ! See the comment for M\ x86.32 stack-cleanup in cpu.x86.32
508     ! 0xffff RET f rc-absolute-2 rel-untagged
509 ] CALLBACK-STUB jit-define
510
511 [
512     ! ! load literal
513     ! temp0 0 MOV f rc-absolute-cell rel-literal
514     ! ! increment datastack pointer
515     ! ds-reg bootstrap-cell ADD
516     ! ! store literal on datastack
517     ! ds-reg [] temp0 MOV
518 ] JIT-PUSH-LITERAL jit-define
519
520 [
521     ! 0 CALL f rc-relative rel-word-pic
522 ] JIT-WORD-CALL jit-define
523
524 ! The *-signal-handler subprimitives are special-cased in vm/quotations.cpp
525 ! not to trigger generation of a stack frame, so they can
526 ! peform their own prolog/epilog preserving registers.
527 !
528 ! It is important that the total is 192/64 and that it matches the
529 ! constants in vm/cpu-x86.*.hpp
530 : jit-signal-handler-prolog ( -- ) ;
531     ! ! Return address already on stack -> 8/4 bytes.
532
533     ! ! Push all registers. 15 regs/120 bytes on 64bit, 7 regs/28 bytes
534     ! ! on 32bit -> 128/32 bytes.
535     ! signal-handler-save-regs [ PUSH ] each
536
537     ! ! Push flags -> 136/36 bytes
538     ! PUSHF
539
540     ! ! Register parameter area 32 bytes, unused on platforms other than
541     ! ! windows 64 bit, but including it doesn't hurt. Plus
542     ! ! alignment. LEA used so we don't dirty flags -> 192/64 bytes.
543     ! stack-reg stack-reg 7 bootstrap-cells neg [+] LEA
544
545     ! jit-load-vm ;
546
547 : jit-signal-handler-epilog ( -- ) ;
548     ! stack-reg stack-reg 7 bootstrap-cells [+] LEA
549     ! POPF
550     ! signal-handler-save-regs reverse [ POP ] each ;
551
552 [
553     ! ! load boolean
554     ! temp0 ds-reg [] MOV
555     ! ! pop boolean
556     ! ds-reg bootstrap-cell SUB
557     ! ! compare boolean with f
558     ! temp0 \ f type-number CMP
559     ! ! jump to true branch if not equal
560     ! 0 JNE f rc-relative rel-word
561     ! ! jump to false branch if equal
562     ! 0 JMP f rc-relative rel-word
563 ] JIT-IF jit-define
564
565
566 [
567     ! jit->r
568     ! 0 CALL f rc-relative rel-word
569     ! jit-r>
570 ] JIT-DIP jit-define
571
572 [
573     ! jit-2>r
574     ! 0 CALL f rc-relative rel-word
575     ! jit-2r>
576 ] JIT-2DIP jit-define
577
578 [
579     ! jit-3>r
580     ! 0 CALL f rc-relative rel-word
581     ! jit-3r>
582 ] JIT-3DIP jit-define
583
584 ! [
585 !     ! load from stack
586 !     temp0 ds-reg [] MOV
587 !     ! pop stack
588 !     ds-reg bootstrap-cell SUB
589 ! ]
590 ! [ temp0 word-entry-point-offset [+] CALL ]
591 ! [ temp0 word-entry-point-offset [+] JMP ]
592 ! \ (execute) define-combinator-primitive
593
594 [
595     ! temp0 ds-reg [] MOV
596     ! ds-reg bootstrap-cell SUB
597     ! temp0 word-entry-point-offset [+] JMP
598 ] JIT-EXECUTE jit-define
599
600 [
601     ! stack-reg stack-framrcee-size bootstrap-cell - SUB
602     stack-frame-size bootstrap-cell - stack-reg stack-reg SUBi64
603 ] JIT-PROLOG jit-define
604
605 [
606     ! stack-reg stack-frame-size bootstrap-cell - ADD
607 ] JIT-EPILOG jit-define
608
609 [
610     f RET
611 ] JIT-RETURN jit-define
612
613 ! ! ! Polymorphic inline caches
614
615 ! The PIC stubs are not permitted to touch pic-tail-reg.
616
617 ! Load a value from a stack position
618 [
619     ! temp1 ds-reg 0x7f [+] MOV f rc-absolute-1 rel-untagged
620 ] PIC-LOAD jit-define
621
622 [
623     ! temp1/32 tag-mask get AND
624 ] PIC-TAG jit-define
625
626 [
627     ! temp0 temp1 MOV
628     ! temp1/32 tag-mask get AND
629     ! temp1/32 tuple type-number CMP
630     ! [ JNE ]
631     ! [ temp1 temp0 tuple-class-offset [+] MOV ]
632     ! jit-conditional
633 ] PIC-TUPLE jit-define
634
635 [
636     ! temp1/32 0x7f CMP f rc-absolute-1 rel-untagged
637 ] PIC-CHECK-TAG jit-define
638
639 [
640     ! 0 JE f rc-relative rel-word
641 ] PIC-HIT jit-define
642
643 ! ! ! Megamorphic caches
644
645 [
646     ! ! class = ...
647     ! temp0 temp1 MOV
648     ! temp1/32 tag-mask get AND
649     ! temp1/32 tag-bits get SHL
650     ! temp1/32 tuple type-number tag-fixnum CMP
651     ! [ JNE ]
652     ! [ temp1 temp0 tuple-class-offset [+] MOV ]
653     ! jit-conditional
654     ! ! cache = ...
655     ! temp0 0 MOV f rc-absolute-cell rel-literal
656     ! ! key = hashcode(class)
657     ! temp2 temp1 MOV
658     ! bootstrap-cell 4 = [ temp2 1 SHR ] when
659     ! ! key &= cache.length - 1
660     ! temp2 mega-cache-size get 1 - bootstrap-cell * AND
661     ! ! cache += array-start-offset
662     ! temp0 array-start-offset ADD
663     ! ! cache += key
664     ! temp0 temp2 ADD
665     ! ! if(get(cache) == class)
666     ! temp0 [] temp1 CMP
667     ! [ JNE ]
668     ! [
669     !     ! megamorphic_cache_hits++
670     !     temp1 0 MOV rc-absolute-cell rel-megamorphic-cache-hits
671     !     temp1 [] 1 ADD
672     !     ! goto get(cache + bootstrap-cell)
673     !     temp0 temp0 bootstrap-cell [+] MOV
674     !     temp0 word-entry-point-offset [+] JMP
675     !     ! fall-through on miss
676     ! ] jit-conditional
677 ] MEGA-LOOKUP jit-define
678
679 ! Comparisons
680 : jit-compare ( insn -- ) drop ;
681     ! ! load t
682     ! temp3 0 MOV t rc-absolute-cell rel-literal
683     ! ! load f
684     ! temp1 \ f type-number MOV
685     ! ! load first value
686     ! temp0 ds-reg [] MOV
687     ! ! adjust stack pointer
688     ! ds-reg bootstrap-cell SUB
689     ! ! compare with second value
690     ! ds-reg [] temp0 CMP
691     ! ! move t if true
692     ! [ temp1 temp3 ] dip execute( dst src -- )
693     ! ! store
694     ! ds-reg [] temp1 MOV ;
695
696 ! Math
697 : jit-math ( insn -- ) drop ;
698     ! ! load second input
699     ! temp0 ds-reg [] MOV
700     ! ! pop stack
701     ! ds-reg bootstrap-cell SUB
702     ! ! compute result
703     ! [ ds-reg [] temp0 ] dip execute( dst src -- ) ;
704
705 : jit-fixnum-/mod ( -- ) ;
706     ! ! load second parameter
707     ! temp1 ds-reg [] MOV
708     ! ! load first parameter
709     ! div-arg ds-reg bootstrap-cell neg [+] MOV
710     ! ! make a copy
711     ! mod-arg div-arg MOV
712     ! ! sign-extend
713     ! mod-arg bootstrap-cell-bits 1 - SAR
714     ! ! divide
715     ! temp1 IDIV ;
716
717 ! # Rest of arm64 subprimitives
718 {
719     ! ! ## Fixnums
720
721     ! ! ### Add
722     ! { fixnum+fast [ \ ADD jit-math ] }
723
724     ! ! ### Bit stuff
725     ! { fixnum-bitand [ \ AND jit-math ] }
726     ! { fixnum-bitnot [
727     !     ! complement
728     !     ds-reg [] NOT
729     !     ! clear tag bits
730     !     ds-reg [] tag-mask get XOR
731     ! ] }
732     ! { fixnum-bitor [ \ OR jit-math ] }
733     ! { fixnum-bitxor [ \ XOR jit-math ] }
734     ! { fixnum-shift-fast [
735     !     ! load shift count
736     !     shift-arg ds-reg [] MOV
737     !     ! untag shift count
738     !     shift-arg tag-bits get SAR
739     !     ! adjust stack pointer
740     !     ds-reg bootstrap-cell SUB
741     !     ! load value
742     !     temp3 ds-reg [] MOV
743     !     ! make a copy
744     !     temp2 temp3 MOV
745     !     ! compute positive shift value in temp2
746     !     temp2 CL SHL
747     !     shift-arg NEG
748     !     ! compute negative shift value in temp3
749     !     temp3 CL SAR
750     !     temp3 tag-mask get bitnot AND
751     !     shift-arg 0 CMP
752     !     ! if shift count was negative, move temp0 to temp2
753     !     temp2 temp3 CMOVGE
754     !     ! push to stack
755     !     ds-reg [] temp2 MOV
756     ! ] }
757
758     ! ! ### Comparisons
759     ! { both-fixnums? [
760     !     temp0 ds-reg [] MOV
761     !     ds-reg bootstrap-cell SUB
762     !     temp0 ds-reg [] OR
763     !     temp0 tag-mask get TEST
764     !     temp0 \ f type-number MOV
765     !     temp1 1 tag-fixnum MOV
766     !     temp0 temp1 CMOVE
767     !     ds-reg [] temp0 MOV
768     ! ] }
769     ! { eq? [ \ CMOVE jit-compare ] }
770     ! { fixnum> [ \ CMOVG jit-compare ] }
771     ! { fixnum>= [ \ CMOVGE jit-compare ] }
772     ! { fixnum< [ \ CMOVL jit-compare ] }
773     ! { fixnum<= [ \ CMOVLE jit-compare ] }
774
775     ! ! ### Div/mod
776     ! { fixnum-mod [
777     !     jit-fixnum-/mod
778     !     ! adjust stack pointer
779     !     ds-reg bootstrap-cell SUB
780     !     ! push to stack
781     !     ds-reg [] mod-arg MOV
782     ! ] }
783     ! { fixnum/i-fast [
784     !     jit-fixnum-/mod
785     !     ! adjust stack pointer
786     !     ds-reg bootstrap-cell SUB
787     !     ! tag it
788     !     div-arg tag-bits get SHL
789     !     ! push to stack
790     !     ds-reg [] div-arg MOV
791     ! ] }
792     ! { fixnum/mod-fast [
793     !     jit-fixnum-/mod
794     !     ! tag it
795     !     div-arg tag-bits get SHL
796     !     ! push to stack
797     !     ds-reg [] mod-arg MOV
798     !     ds-reg bootstrap-cell neg [+] div-arg MOV
799     ! ] }
800
801     ! ! ### Mul
802     ! { fixnum*fast [
803     !     ! load second input
804     !     temp0 ds-reg [] MOV
805     !     ! pop stack
806     !     ds-reg bootstrap-cell SUB
807     !     ! load first input
808     !     temp1 ds-reg [] MOV
809     !     ! untag second input
810     !     temp0 tag-bits get SAR
811     !     ! multiply
812     !     temp0 temp1 IMUL2
813     !     ! push result
814     !     ds-reg [] temp0 MOV
815     ! ] }
816
817     ! ! ### Sub
818     ! { fixnum-fast [ \ SUB jit-math ] }
819
820     ! ! ## Locals
821     ! { drop-locals [
822     !     ! load local count
823     !     temp0 ds-reg [] MOV
824     !     ! adjust stack pointer
825     !     ds-reg bootstrap-cell SUB
826     !     ! turn local number into offset
827     !     fixnum>slot@
828     !     ! decrement retain stack pointer
829     !     rs-reg temp0 SUB
830     ! ] }
831     ! { get-local [
832     !     ! load local number
833     !     temp0 ds-reg [] MOV
834     !     ! turn local number into offset
835     !     fixnum>slot@
836     !     ! load local value
837     !     temp0 rs-reg temp0 [+] MOV
838     !     ! push to stack
839     !     ds-reg [] temp0 MOV
840     ! ] }
841     ! { load-local [ jit->r ] }
842
843     ! ! ## Objects
844     ! { slot [
845     !     ! load slot number
846     !     temp0 ds-reg [] MOV
847     !     ! adjust stack pointer
848     !     ds-reg bootstrap-cell SUB
849     !     ! load object
850     !     temp1 ds-reg [] MOV
851     !     ! turn slot number into offset
852     !     fixnum>slot@
853     !     ! mask off tag
854     !     temp1 tag-bits get SHR
855     !     temp1 tag-bits get SHL
856     !     ! load slot value
857     !     temp0 temp1 temp0 [+] MOV
858     !     ! push to stack
859     !     ds-reg [] temp0 MOV
860     ! ] }
861     ! { string-nth-fast [
862     !     ! load string index from stack
863     !     temp0 ds-reg bootstrap-cell neg [+] MOV
864     !     temp0 tag-bits get SHR
865     !     ! load string from stack
866     !     temp1 ds-reg [] MOV
867     !     ! load character
868     !     temp0 8-bit-version-of temp0 temp1 string-offset [++] MOV
869     !     temp0 temp0 8-bit-version-of MOVZX
870     !     temp0 tag-bits get SHL
871     !     ! store character to stack
872     !     ds-reg bootstrap-cell SUB
873     !     ds-reg [] temp0 MOV
874     ! ] }
875     ! { tag [
876     !     ! load from stack
877     !     temp0 ds-reg [] MOV
878     !     ! compute tag
879     !     temp0/32 tag-mask get AND
880     !     ! tag the tag
881     !     temp0/32 tag-bits get SHL
882     !     ! push to stack
883     !     ds-reg [] temp0 MOV
884     ! ] }
885
886     ! ! ## Shufflers
887
888     ! ! ### Drops
889     ! { drop [ ds-reg bootstrap-cell SUB ] }
890     ! { 2drop [ ds-reg 2 bootstrap-cells SUB ] }
891     ! { 3drop [ ds-reg 3 bootstrap-cells SUB ] }
892     ! { 4drop [ ds-reg 4 bootstrap-cells SUB ] }
893
894     ! ! ### Dups
895     ! { dup [
896     !     temp0 ds-reg [] MOV
897     !     ds-reg bootstrap-cell ADD
898     !     ds-reg [] temp0 MOV
899     ! ] }
900     ! { 2dup [
901     !     temp0 ds-reg [] MOV
902     !     temp1 ds-reg bootstrap-cell neg [+] MOV
903     !     ds-reg 2 bootstrap-cells ADD
904     !     ds-reg [] temp0 MOV
905     !     ds-reg bootstrap-cell neg [+] temp1 MOV
906     ! ] }
907     ! { 3dup [
908     !     temp0 ds-reg [] MOV
909     !     temp1 ds-reg -1 bootstrap-cells [+] MOV
910     !     temp3 ds-reg -2 bootstrap-cells [+] MOV
911     !     ds-reg 3 bootstrap-cells ADD
912     !     ds-reg [] temp0 MOV
913     !     ds-reg -1 bootstrap-cells [+] temp1 MOV
914     !     ds-reg -2 bootstrap-cells [+] temp3 MOV
915     ! ] }
916     ! { 4dup [
917     !     temp0 ds-reg [] MOV
918     !     temp1 ds-reg -1 bootstrap-cells [+] MOV
919     !     temp2 ds-reg -2 bootstrap-cells [+] MOV
920     !     temp3 ds-reg -3 bootstrap-cells [+] MOV
921     !     ds-reg 4 bootstrap-cells ADD
922     !     ds-reg [] temp0 MOV
923     !     ds-reg -1 bootstrap-cells [+] temp1 MOV
924     !     ds-reg -2 bootstrap-cells [+] temp2 MOV
925     !     ds-reg -3 bootstrap-cells [+] temp3 MOV
926     ! ] }
927     ! { dupd [
928     !     temp0 ds-reg [] MOV
929     !     temp1 ds-reg -1 bootstrap-cells [+] MOV
930     !     ds-reg [] temp1 MOV
931     !     ds-reg bootstrap-cell ADD
932     !     ds-reg [] temp0 MOV
933     ! ] }
934
935     ! ! ### Misc shufflers
936     ! { over [
937     !     temp0 ds-reg -1 bootstrap-cells [+] MOV
938     !     ds-reg bootstrap-cell ADD
939     !     ds-reg [] temp0 MOV
940     ! ] }
941     ! { pick [
942     !     temp0 ds-reg -2 bootstrap-cells [+] MOV
943     !     ds-reg bootstrap-cell ADD
944     !     ds-reg [] temp0 MOV
945     ! ] }
946
947     ! ! ### Nips
948     ! { nip [
949     !     temp0 ds-reg [] MOV
950     !     ds-reg bootstrap-cell SUB
951     !     ds-reg [] temp0 MOV
952     ! ] }
953     ! { 2nip [
954     !     temp0 ds-reg [] MOV
955     !     ds-reg 2 bootstrap-cells SUB
956     !     ds-reg [] temp0 MOV
957     ! ] }
958
959     ! ! ### Swaps
960     ! { -rot [
961     !     temp0 ds-reg [] MOV
962     !     temp1 ds-reg -1 bootstrap-cells [+] MOV
963     !     temp3 ds-reg -2 bootstrap-cells [+] MOV
964     !     ds-reg -2 bootstrap-cells [+] temp0 MOV
965     !     ds-reg -1 bootstrap-cells [+] temp3 MOV
966     !     ds-reg [] temp1 MOV
967     ! ] }
968     ! { rot [
969     !     temp0 ds-reg [] MOV
970     !     temp1 ds-reg -1 bootstrap-cells [+] MOV
971     !     temp3 ds-reg -2 bootstrap-cells [+] MOV
972     !     ds-reg -2 bootstrap-cells [+] temp1 MOV
973     !     ds-reg -1 bootstrap-cells [+] temp0 MOV
974     !     ds-reg [] temp3 MOV
975     ! ] }
976     ! { swap [
977     !     temp0 ds-reg [] MOV
978     !     temp1 ds-reg bootstrap-cell neg [+] MOV
979     !     ds-reg bootstrap-cell neg [+] temp0 MOV
980     !     ds-reg [] temp1 MOV
981     ! ] }
982     ! { swapd [
983     !     temp0 ds-reg -1 bootstrap-cells [+] MOV
984     !     temp1 ds-reg -2 bootstrap-cells [+] MOV
985     !     ds-reg -2 bootstrap-cells [+] temp0 MOV
986     !     ds-reg -1 bootstrap-cells [+] temp1 MOV
987     ! ] }
988
989     ! ! ## Signal handling
990     ! { leaf-signal-handler [
991     !     jit-signal-handler-prolog
992     !     jit-save-context
993     !     temp0 vm-reg vm-signal-handler-addr-offset [+] MOV
994     !     temp0 CALL
995     !     jit-signal-handler-epilog
996     !     ! Pop the fake leaf frame along with our return address
997     !     leaf-stack-frame-size bootstrap-cell - RET
998     ! ] }
999     ! { signal-handler [
1000     !     jit-signal-handler-prolog
1001     !     jit-save-context
1002     !     temp0 vm-reg vm-signal-handler-addr-offset [+] MOV
1003     !     temp0 CALL
1004     !     jit-signal-handler-epilog
1005     !     0 RET
1006     ! ] }
1007 } define-sub-primitives
1008
1009 [ "bootstrap.arm.64" forget-vocab ] with-compilation-unit