]> gitweb.factorcode.org Git - factor.git/blob - basis/cpu/ppc/ppc.factor
cpu.ppc: final fix
[factor.git] / basis / cpu / ppc / ppc.factor
1 ! Copyright (C) 2005, 2010 Slava Pestov.
2 ! See http://factorcode.org/license.txt for BSD license.
3 USING: accessors assocs sequences kernel combinators make math
4 math.order math.ranges system namespaces locals layouts words
5 alien alien.accessors alien.c-types alien.data literals cpu.architecture
6 cpu.ppc.assembler cpu.ppc.assembler.backend compiler.cfg.registers
7 compiler.cfg.instructions compiler.cfg.comparisons
8 compiler.codegen.fixup compiler.cfg.intrinsics
9 compiler.cfg.stack-frame compiler.cfg.build-stack-frame
10 compiler.units compiler.constants compiler.codegen vm ;
11 FROM: cpu.ppc.assembler => B ;
12 FROM: layouts => cell ;
13 FROM: math => float ;
14 IN: cpu.ppc
15
16 ! PowerPC register assignments:
17 ! r2-r12: integer vregs
18 ! r13: data stack
19 ! r14: retain stack
20 ! r15: VM pointer
21 ! r16-r29: integer vregs
22 ! r30: integer scratch
23 ! f0-f29: float vregs
24 ! f30: float scratch
25
26 ! Add some methods to the assembler that are useful to us
27 M: label (B) [ 0 ] 2dip (B) rc-relative-ppc-3 label-fixup ;
28 M: label BC [ 0 BC ] dip rc-relative-ppc-2 label-fixup ;
29
30 enable-float-intrinsics
31
32 <<
33 \ ##integer>float t frame-required? set-word-prop
34 \ ##float>integer t frame-required? set-word-prop
35 >>
36
37 M: ppc machine-registers
38     {
39         { int-regs $[ 2 12 [a,b] 16 29 [a,b] append ] }
40         { float-regs $[ 0 29 [a,b] ] }
41     } ;
42
43 CONSTANT: scratch-reg 30
44 CONSTANT: fp-scratch-reg 30
45
46 M: ppc %load-immediate ( reg n -- ) swap LOAD ;
47
48 M: ppc %load-reference ( reg obj -- )
49     [ 0 swap LOAD32 ] [ rc-absolute-ppc-2/2 rel-immediate ] bi* ;
50
51 M: ppc %alien-global ( register symbol dll -- )
52     [ 0 swap LOAD32 ] 2dip rc-absolute-ppc-2/2 rel-dlsym ;
53
54 CONSTANT: ds-reg 13
55 CONSTANT: rs-reg 14
56 CONSTANT: vm-reg 15
57
58 : %load-vm-addr ( reg -- ) vm-reg MR ;
59
60 M: ppc %vm-field ( dst field -- )
61     [ vm-reg ] dip vm-field-offset LWZ ;
62
63 M: ppc %vm-field-ptr ( dst field -- )
64     [ vm-reg ] dip vm-field-offset ADDI ;
65
66 GENERIC: loc-reg ( loc -- reg )
67
68 M: ds-loc loc-reg drop ds-reg ;
69 M: rs-loc loc-reg drop rs-reg ;
70
71 : loc>operand ( loc -- reg n )
72     [ loc-reg ] [ n>> cells neg ] bi ; inline
73
74 M: ppc %peek loc>operand LWZ ;
75 M: ppc %replace loc>operand STW ;
76
77 :: (%inc) ( n reg -- ) reg reg n cells ADDI ; inline
78
79 M: ppc %inc-d ( n -- ) ds-reg (%inc) ;
80 M: ppc %inc-r ( n -- ) rs-reg (%inc) ;
81
82 HOOK: reserved-area-size os ( -- n )
83
84 ! The start of the stack frame contains the size of this frame
85 ! as well as the currently executing code block
86 : factor-area-size ( -- n ) 2 cells ; foldable
87 : next-save ( n -- i ) cell - ; foldable
88 : xt-save ( n -- i ) 2 cells - ; foldable
89
90 ! Next, we have the spill area as well as the FFI parameter area.
91 ! It is safe for them to overlap, since basic blocks with FFI calls
92 ! will never spill -- indeed, basic blocks with FFI calls do not
93 ! use vregs at all, and the FFI call is a stack analysis sync point.
94 ! In the future this will change and the stack frame logic will
95 ! need to be untangled somewhat.
96
97 : param@ ( n -- x ) reserved-area-size + ; inline
98
99 : param-save-size ( -- n ) 8 cells ; foldable
100
101 : local@ ( n -- x )
102     reserved-area-size param-save-size + + ; inline
103
104 : spill@ ( n -- offset )
105     spill-offset local@ ;
106
107 ! Some FP intrinsics need a temporary scratch area in the stack
108 ! frame, 8 bytes in size. This is in the param-save area so it
109 ! does not overlap with spill slots.
110 : scratch@ ( n -- offset )
111     factor-area-size + ;
112
113 ! GC root area
114 : gc-root@ ( n -- offset )
115     gc-root-offset local@ ;
116
117 ! Finally we have the linkage area
118 HOOK: lr-save os ( -- n )
119
120 M: ppc stack-frame-size ( stack-frame -- i )
121     (stack-frame-size)
122     param-save-size +
123     reserved-area-size +
124     factor-area-size +
125     4 cells align ;
126
127 M: ppc %call ( word -- ) 0 BL rc-relative-ppc-3 rel-word-pic ;
128
129 M: ppc %jump ( word -- )
130     0 6 LOAD32 4 rc-absolute-ppc-2/2 rel-here
131     0 B rc-relative-ppc-3 rel-word-pic-tail ;
132
133 M: ppc %jump-label ( label -- ) B ;
134 M: ppc %return ( -- ) BLR ;
135
136 M:: ppc %dispatch ( src temp -- )
137     0 temp LOAD32
138     3 cells rc-absolute-ppc-2/2 rel-here
139     temp temp src LWZX
140     temp MTCTR
141     BCTR ;
142
143 M: ppc %slot ( dst obj slot -- ) swapd LWZX ;
144 M: ppc %slot-imm ( dst obj slot tag -- ) slot-offset LWZ ;
145 M: ppc %set-slot ( src obj slot -- ) swapd STWX ;
146 M: ppc %set-slot-imm ( src obj slot tag -- ) slot-offset STW ;
147
148 M:: ppc %string-nth ( dst src index temp -- )
149     [
150         "end" define-label
151         temp src index ADD
152         dst temp string-offset LBZ
153         0 dst HEX: 80 CMPI
154         "end" get BLT
155         temp src string-aux-offset LWZ
156         temp temp index ADD
157         temp temp index ADD
158         temp temp byte-array-offset LHZ
159         temp temp 7 SLWI
160         dst dst temp XOR
161         "end" resolve-label
162     ] with-scope ;
163
164 M:: ppc %set-string-nth-fast ( ch obj index temp -- )
165     temp obj index ADD
166     ch temp string-offset STB ;
167
168 M: ppc %add     ADD ;
169 M: ppc %add-imm ADDI ;
170 M: ppc %sub     swap SUBF ;
171 M: ppc %sub-imm SUBI ;
172 M: ppc %mul     MULLW ;
173 M: ppc %mul-imm MULLI ;
174 M: ppc %and     AND ;
175 M: ppc %and-imm ANDI ;
176 M: ppc %or      OR ;
177 M: ppc %or-imm  ORI ;
178 M: ppc %xor     XOR ;
179 M: ppc %xor-imm XORI ;
180 M: ppc %shl     SLW ;
181 M: ppc %shl-imm swapd SLWI ;
182 M: ppc %shr     SRW ;
183 M: ppc %shr-imm swapd SRWI ;
184 M: ppc %sar     SRAW ;
185 M: ppc %sar-imm SRAWI ;
186 M: ppc %not     NOT ;
187 M: ppc %neg     NEG ;
188
189 :: overflow-template ( label dst src1 src2 insn -- )
190     0 0 LI
191     0 MTXER
192     dst src2 src1 insn call
193     label BO ; inline
194
195 M: ppc %fixnum-add ( label dst src1 src2 -- )
196     [ ADDO. ] overflow-template ;
197
198 M: ppc %fixnum-sub ( label dst src1 src2 -- )
199     [ SUBFO. ] overflow-template ;
200
201 M: ppc %fixnum-mul ( label dst src1 src2 -- )
202     [ MULLWO. ] overflow-template ;
203
204 M: ppc %add-float FADD ;
205 M: ppc %sub-float FSUB ;
206 M: ppc %mul-float FMUL ;
207 M: ppc %div-float FDIV ;
208
209 M:: ppc %integer>float ( dst src -- )
210     HEX: 4330 scratch-reg LIS
211     scratch-reg 1 0 scratch@ STW
212     scratch-reg src MR
213     scratch-reg dup HEX: 8000 XORIS
214     scratch-reg 1 4 scratch@ STW
215     dst 1 0 scratch@ LFD
216     scratch-reg 4503601774854144.0 %load-reference
217     fp-scratch-reg scratch-reg float-offset LFD
218     dst dst fp-scratch-reg FSUB ;
219
220 M:: ppc %float>integer ( dst src -- )
221     fp-scratch-reg src FCTIWZ
222     fp-scratch-reg 1 0 scratch@ STFD
223     dst 1 4 scratch@ LWZ ;
224
225 M: ppc %copy ( dst src rep -- )
226     2over eq? [ 3drop ] [
227         {
228             { int-rep [ MR ] }
229             { double-rep [ FMR ] }
230         } case
231     ] if ;
232
233 GENERIC: float-function-param* ( dst src -- )
234
235 M: spill-slot float-function-param* [ 1 ] dip n>> spill@ LFD ;
236 M: integer float-function-param* FMR ;
237
238 : float-function-param ( i src -- )
239     [ float-regs param-regs nth ] dip float-function-param* ;
240
241 : float-function-return ( reg -- )
242     float-regs return-reg double-rep %copy ;
243
244 M:: ppc %unary-float-function ( dst src func -- )
245     0 src float-function-param
246     func f %alien-invoke
247     dst float-function-return ;
248
249 M:: ppc %binary-float-function ( dst src1 src2 func -- )
250     0 src1 float-function-param
251     1 src2 float-function-param
252     func f %alien-invoke
253     dst float-function-return ;
254
255 ! Internal format is always double-precision on PowerPC
256 M: ppc %single>double-float double-rep %copy ;
257 M: ppc %double>single-float FRSP ;
258
259 M: ppc %unbox-alien ( dst src -- )
260     alien-offset LWZ ;
261
262 M:: ppc %unbox-any-c-ptr ( dst src -- )
263     [
264         "end" define-label
265         0 dst LI
266         ! Is the object f?
267         0 src \ f type-number CMPI
268         "end" get BEQ
269         ! Compute tag in dst register
270         dst src tag-mask get ANDI
271         ! Is the object an alien?
272         0 dst alien type-number CMPI
273         ! Add an offset to start of byte array's data
274         dst src byte-array-offset ADDI
275         "end" get BNE
276         ! If so, load the offset and add it to the address
277         dst src alien-offset LWZ
278         "end" resolve-label
279     ] with-scope ;
280
281 : alien@ ( n -- n' ) cells alien type-number - ;
282
283 M:: ppc %box-alien ( dst src temp -- )
284     [
285         "f" define-label
286         dst \ f type-number %load-immediate
287         0 src 0 CMPI
288         "f" get BEQ
289         dst 5 cells alien temp %allot
290         temp \ f type-number %load-immediate
291         temp dst 1 alien@ STW
292         temp dst 2 alien@ STW
293         src dst 3 alien@ STW
294         src dst 4 alien@ STW
295         "f" resolve-label
296     ] with-scope ;
297
298 M:: ppc %box-displaced-alien ( dst displacement base temp base-class -- )
299     ! This is ridiculous
300     [
301         "end" define-label
302         "not-f" define-label
303         "not-alien" define-label
304
305         ! If displacement is zero, return the base
306         dst base MR
307         0 displacement 0 CMPI
308         "end" get BEQ
309
310         ! Displacement is non-zero, we're going to be allocating a new
311         ! object
312         dst 5 cells alien temp %allot
313
314         ! Set expired to f
315         temp \ f type-number %load-immediate
316         temp dst 2 alien@ STW
317
318         ! Is base f?
319         0 base \ f type-number CMPI
320         "not-f" get BNE
321
322         ! Yes, it is f. Fill in new object
323         base dst 1 alien@ STW
324         displacement dst 3 alien@ STW
325         displacement dst 4 alien@ STW
326
327         "end" get B
328
329         "not-f" resolve-label
330
331         ! Check base type
332         temp base tag-mask get ANDI
333
334         ! Is base an alien?
335         0 temp alien type-number CMPI
336         "not-alien" get BNE
337
338         ! Yes, it is an alien. Set new alien's base to base.base
339         temp base 1 alien@ LWZ
340         temp dst 1 alien@ STW
341
342         ! Compute displacement
343         temp base 3 alien@ LWZ
344         temp temp displacement ADD
345         temp dst 3 alien@ STW
346
347         ! Compute address
348         temp base 4 alien@ LWZ
349         temp temp displacement ADD
350         temp dst 4 alien@ STW
351
352         ! We are done
353         "end" get B
354
355         ! Is base a byte array? It has to be, by now...
356         "not-alien" resolve-label
357
358         base dst 1 alien@ STW
359         displacement dst 3 alien@ STW
360         temp base byte-array-offset ADDI
361         temp temp displacement ADD
362         temp dst 4 alien@ STW
363
364         "end" resolve-label
365     ] with-scope ;
366
367 M: ppc %alien-unsigned-1 LBZ ;
368 M: ppc %alien-unsigned-2 LHZ ;
369
370 M: ppc %alien-signed-1 [ dup ] 2dip LBZ dup EXTSB ;
371 M: ppc %alien-signed-2 LHA ;
372
373 M: ppc %alien-cell LWZ ;
374
375 M: ppc %alien-float LFS ;
376 M: ppc %alien-double LFD ;
377
378 M: ppc %set-alien-integer-1 -rot STB ;
379 M: ppc %set-alien-integer-2 -rot STH ;
380
381 M: ppc %set-alien-cell -rot STW ;
382
383 M: ppc %set-alien-float -rot STFS ;
384 M: ppc %set-alien-double -rot STFD ;
385
386 : load-zone-ptr ( reg -- )
387     "nursery" %vm-field-ptr ;
388
389 : load-allot-ptr ( nursery-ptr allot-ptr -- )
390     [ drop load-zone-ptr ] [ swap 0 LWZ ] 2bi ;
391
392 :: inc-allot-ptr ( nursery-ptr allot-ptr n -- )
393     scratch-reg allot-ptr n data-alignment get align ADDI
394     scratch-reg nursery-ptr 0 STW ;
395
396 :: store-header ( dst class -- )
397     class type-number tag-header scratch-reg LI
398     scratch-reg dst 0 STW ;
399
400 : store-tagged ( dst tag -- )
401     dupd type-number ORI ;
402
403 M:: ppc %allot ( dst size class nursery-ptr -- )
404     nursery-ptr dst load-allot-ptr
405     nursery-ptr dst size inc-allot-ptr
406     dst class store-header
407     dst class store-tagged ;
408
409 : load-cards-offset ( dst -- )
410     0 swap LOAD32 rc-absolute-ppc-2/2 rel-cards-offset ;
411
412 : load-decks-offset ( dst -- )
413     0 swap LOAD32 rc-absolute-ppc-2/2 rel-decks-offset ;
414
415 :: (%write-barrier) ( temp1 temp2 -- )
416     card-mark scratch-reg LI
417
418     ! Mark the card
419     temp1 temp1 card-bits SRWI
420     temp2 load-cards-offset
421     temp1 scratch-reg temp2 STBX
422
423     ! Mark the card deck
424     temp1 temp1 deck-bits card-bits - SRWI
425     temp2 load-decks-offset
426     temp1 scratch-reg temp2 STBX ;
427
428 M:: ppc %write-barrier ( src slot temp1 temp2 -- )
429     temp1 src slot ADD
430     temp1 temp2 (%write-barrier) ;
431
432 M:: ppc %write-barrier-imm ( src slot temp1 temp2 -- )
433     temp1 src slot ADDI
434     temp1 temp2 (%write-barrier) ;
435
436 M:: ppc %check-nursery ( label size temp1 temp2 -- )
437     temp2 load-zone-ptr
438     temp1 temp2 0 LWZ
439     temp2 temp2 2 cells LWZ
440     temp1 temp1 size ADDI
441     ! is here >= end?
442     temp1 0 temp2 CMP
443     label BLE ;
444
445 M:: ppc %save-gc-root ( gc-root register -- )
446     register 1 gc-root gc-root@ STW ;
447
448 M:: ppc %load-gc-root ( gc-root register -- )
449     register 1 gc-root gc-root@ LWZ ;
450
451 M:: ppc %call-gc ( gc-root-count temp -- )
452     3 1 gc-root-base local@ ADDI
453     gc-root-count 4 LI
454     5 %load-vm-addr
455     "inline_gc" f %alien-invoke ;
456
457 M: ppc %prologue ( n -- )
458     0 11 LOAD32 rc-absolute-ppc-2/2 rel-this
459     0 MFLR
460     {
461         [ [ 1 1 ] dip neg ADDI ]
462         [ [ 11 1 ] dip xt-save STW ]
463         [ 11 LI ]
464         [ [ 11 1 ] dip next-save STW ]
465         [ [ 0 1 ] dip lr-save + STW ]
466     } cleave ;
467
468 M: ppc %epilogue ( n -- )
469     #! At the end of each word that calls a subroutine, we store
470     #! the previous link register value in r0 by popping it off
471     #! the stack, set the link register to the contents of r0,
472     #! and jump to the link register.
473     [ [ 0 1 ] dip lr-save + LWZ ]
474     [ [ 1 1 ] dip ADDI ] bi
475     0 MTLR ;
476
477 :: (%boolean) ( dst temp branch1 branch2 -- )
478     "end" define-label
479     dst \ f type-number %load-immediate
480     "end" get branch1 execute( label -- )
481     branch2 [ "end" get branch2 execute( label -- ) ] when
482     dst \ t %load-reference
483     "end" get resolve-label ; inline
484
485 :: %boolean ( dst cc temp -- )
486     cc negate-cc order-cc {
487         { cc<  [ dst temp \ BLT f (%boolean) ] }
488         { cc<= [ dst temp \ BLE f (%boolean) ] }
489         { cc>  [ dst temp \ BGT f (%boolean) ] }
490         { cc>= [ dst temp \ BGE f (%boolean) ] }
491         { cc=  [ dst temp \ BEQ f (%boolean) ] }
492         { cc/= [ dst temp \ BNE f (%boolean) ] }
493     } case ;
494
495 : (%compare) ( src1 src2 -- ) [ 0 ] dip CMP ; inline
496 : (%compare-imm) ( src1 src2 -- ) [ 0 ] 2dip CMPI ; inline
497 : (%compare-float-unordered) ( src1 src2 -- ) [ 0 ] dip FCMPU ; inline
498 : (%compare-float-ordered) ( src1 src2 -- ) [ 0 ] dip FCMPO ; inline
499
500 :: (%compare-float) ( src1 src2 cc compare -- branch1 branch2 )
501     cc {
502         { cc<    [ src1 src2 \ compare execute( a b -- ) \ BLT f     ] }
503         { cc<=   [ src1 src2 \ compare execute( a b -- ) \ BLT \ BEQ ] }
504         { cc>    [ src1 src2 \ compare execute( a b -- ) \ BGT f     ] }
505         { cc>=   [ src1 src2 \ compare execute( a b -- ) \ BGT \ BEQ ] }
506         { cc=    [ src1 src2 \ compare execute( a b -- ) \ BEQ f     ] }
507         { cc<>   [ src1 src2 \ compare execute( a b -- ) \ BLT \ BGT ] }
508         { cc<>=  [ src1 src2 \ compare execute( a b -- ) \ BNO f     ] }
509         { cc/<   [ src1 src2 \ compare execute( a b -- ) \ BGE f     ] }
510         { cc/<=  [ src1 src2 \ compare execute( a b -- ) \ BGT \ BO  ] }
511         { cc/>   [ src1 src2 \ compare execute( a b -- ) \ BLE f     ] }
512         { cc/>=  [ src1 src2 \ compare execute( a b -- ) \ BLT \ BO  ] }
513         { cc/=   [ src1 src2 \ compare execute( a b -- ) \ BNE f     ] }
514         { cc/<>  [ src1 src2 \ compare execute( a b -- ) \ BEQ \ BO  ] }
515         { cc/<>= [ src1 src2 \ compare execute( a b -- ) \ BO  f     ] }
516     } case ; inline
517
518 M: ppc %compare [ (%compare) ] 2dip %boolean ;
519
520 M: ppc %compare-imm [ (%compare-imm) ] 2dip %boolean ;
521
522 M:: ppc %compare-float-ordered ( dst src1 src2 cc temp -- )
523     src1 src2 cc negate-cc \ (%compare-float-ordered) (%compare-float) :> ( branch1 branch2 )
524     dst temp branch1 branch2 (%boolean) ;
525
526 M:: ppc %compare-float-unordered ( dst src1 src2 cc temp -- )
527     src1 src2 cc negate-cc \ (%compare-float-unordered) (%compare-float) :> ( branch1 branch2 )
528     dst temp branch1 branch2 (%boolean) ;
529
530 :: %branch ( label cc -- )
531     cc order-cc {
532         { cc<  [ label BLT ] }
533         { cc<= [ label BLE ] }
534         { cc>  [ label BGT ] }
535         { cc>= [ label BGE ] }
536         { cc=  [ label BEQ ] }
537         { cc/= [ label BNE ] }
538     } case ;
539
540 M:: ppc %compare-branch ( label src1 src2 cc -- )
541     src1 src2 (%compare)
542     label cc %branch ;
543
544 M:: ppc %compare-imm-branch ( label src1 src2 cc -- )
545     src1 src2 (%compare-imm)
546     label cc %branch ;
547
548 :: (%branch) ( label branch1 branch2 -- )
549     label branch1 execute( label -- )
550     branch2 [ label branch2 execute( label -- ) ] when ; inline
551
552 M:: ppc %compare-float-ordered-branch ( label src1 src2 cc -- )
553     src1 src2 cc \ (%compare-float-ordered) (%compare-float) :> ( branch1 branch2 )
554     label branch1 branch2 (%branch) ;
555
556 M:: ppc %compare-float-unordered-branch ( label src1 src2 cc -- )
557     src1 src2 cc \ (%compare-float-unordered) (%compare-float) :> ( branch1 branch2 )
558     label branch1 branch2 (%branch) ;
559
560 : load-from-frame ( dst n rep -- )
561     {
562         { int-rep [ [ 1 ] dip LWZ ] }
563         { float-rep [ [ 1 ] dip LFS ] }
564         { double-rep [ [ 1 ] dip LFD ] }
565         { stack-params [ [ 0 1 ] dip LWZ [ 0 1 ] dip param@ STW ] }
566     } case ;
567
568 : next-param@ ( n -- reg x )
569     2 1 stack-frame get total-size>> LWZ
570     [ 2 ] dip param@ ;
571
572 : store-to-frame ( src n rep -- )
573     {
574         { int-rep [ [ 1 ] dip STW ] }
575         { float-rep [ [ 1 ] dip STFS ] }
576         { double-rep [ [ 1 ] dip STFD ] }
577         { stack-params [ [ [ 0 ] dip next-param@ LWZ 0 1 ] dip STW ] }
578     } case ;
579
580 M: ppc %spill ( src rep dst -- )
581     swap [ n>> spill@ ] dip store-to-frame ;
582
583 M: ppc %reload ( dst rep src -- )
584     swap [ n>> spill@ ] dip load-from-frame ;
585
586 M: ppc %loop-entry ;
587
588 M: int-regs return-reg drop 3 ;
589 M: int-regs param-regs drop { 3 4 5 6 7 8 9 10 } ;
590 M: float-regs return-reg drop 1 ;
591
592 M:: ppc %save-param-reg ( stack reg rep -- )
593     reg stack local@ rep store-to-frame ;
594
595 M:: ppc %load-param-reg ( stack reg rep -- )
596     reg stack local@ rep load-from-frame ;
597
598 M: ppc %pop-stack ( n -- )
599     [ 3 ] dip <ds-loc> loc>operand LWZ ;
600
601 M: ppc %push-stack ( -- )
602     ds-reg ds-reg 4 ADDI
603     int-regs return-reg ds-reg 0 STW ;
604
605 M: ppc %push-context-stack ( -- )
606     11 "ctx" %vm-field
607     12 11 "datastack" context-field-offset LWZ
608     12 12 4 ADDI
609     12 11 "datastack" context-field-offset STW
610     int-regs return-reg 12 0 STW ;
611
612 M: ppc %pop-context-stack ( -- )
613     11 "ctx" %vm-field
614     12 11 "datastack" context-field-offset LWZ
615     int-regs return-reg 12 0 LWZ
616     12 12 4 SUBI
617     12 11 "datastack" context-field-offset STW ;
618
619 M: ppc %unbox ( n rep func -- )
620     ! Value must be in r3
621     4 %load-vm-addr
622     ! Call the unboxer
623     f %alien-invoke
624     ! Store the return value on the C stack
625     over [ [ reg-class-of return-reg ] keep %save-param-reg ] [ 2drop ] if ;
626
627 M: ppc %unbox-long-long ( n func -- )
628     4 %load-vm-addr
629     ! Call the unboxer
630     f %alien-invoke
631     ! Store the return value on the C stack
632     [
633         [ [ 3 1 ] dip local@ STW ]
634         [ [ 4 1 ] dip cell + local@ STW ] bi
635     ] when* ;
636
637 M: ppc %unbox-large-struct ( n c-type -- )
638     ! Value must be in r3
639     ! Compute destination address and load struct size
640     [ [ 4 1 ] dip local@ ADDI ] [ heap-size 5 LI ] bi*
641     6 %load-vm-addr
642     ! Call the function
643     "to_value_struct" f %alien-invoke ;
644
645 M:: ppc %box ( n rep func -- )
646     ! If the source is a stack location, load it into freg #0.
647     ! If the source is f, then we assume the value is already in
648     ! freg #0.
649     n [ 0 rep reg-class-of param-reg rep %load-param-reg ] when*
650     rep double-rep? 5 4 ? %load-vm-addr
651     func f %alien-invoke ;
652
653 M: ppc %box-long-long ( n func -- )
654     [
655         [
656             [ [ 3 1 ] dip local@ LWZ ]
657             [ [ 4 1 ] dip cell + local@ LWZ ] bi
658         ] when*
659         5 %load-vm-addr
660     ] dip f %alien-invoke ;
661
662 : struct-return@ ( n -- n )
663     [ stack-frame get params>> ] unless* local@ ;
664
665 M: ppc %prepare-box-struct ( -- )
666     #! Compute target address for value struct return
667     3 1 f struct-return@ ADDI
668     3 1 0 local@ STW ;
669
670 M: ppc %box-large-struct ( n c-type -- )
671     ! If n = f, then we're boxing a returned struct
672     ! Compute destination address and load struct size
673     [ [ 3 1 ] dip struct-return@ ADDI ] [ heap-size 4 LI ] bi*
674     5 %load-vm-addr
675     ! Call the function
676     "from_value_struct" f %alien-invoke ;
677
678 M:: ppc %restore-context ( temp1 temp2 -- )
679     temp1 "ctx" %vm-field
680     temp2 1 stack-frame get total-size>> ADDI
681     temp2 temp1 "callstack-bottom" context-field-offset STW
682     ds-reg temp1 "datastack" context-field-offset LWZ
683     rs-reg temp1 "retainstack" context-field-offset LWZ ;
684
685 M:: ppc %save-context ( temp1 temp2 -- )
686     temp1 "ctx" %vm-field
687     1 temp1 "callstack-top" context-field-offset STW
688     ds-reg temp1 "datastack" context-field-offset STW
689     rs-reg temp1 "retainstack" context-field-offset STW ;
690
691 M: ppc %alien-invoke ( symbol dll -- )
692     [ 11 ] 2dip %alien-global 11 MTLR BLRL ;
693
694 M: ppc %alien-callback ( quot -- )
695     3 4 %restore-context
696     3 swap %load-reference
697     4 3 quot-entry-point-offset LWZ
698     4 MTLR
699     BLRL
700     3 4 %save-context ;
701
702 M: ppc %prepare-alien-indirect ( -- )
703     3 ds-reg 0 LWZ
704     ds-reg ds-reg 4 SUBI
705     4 %load-vm-addr
706     "pinned_alien_offset" f %alien-invoke
707     16 3 MR ;
708
709 M: ppc %alien-indirect ( -- )
710     16 MTLR BLRL ;
711
712 M: ppc %callback-value ( ctype -- )
713     ! Save top of data stack
714     3 ds-reg 0 LWZ
715     3 1 0 local@ STW
716     3 %load-vm-addr
717     ! Restore data/call/retain stacks
718     "unnest_stacks" f %alien-invoke
719     ! Restore top of data stack
720     3 1 0 local@ LWZ
721     ! Unbox former top of data stack to return registers
722     unbox-return ;
723
724 M: ppc immediate-arithmetic? ( n -- ? ) -32768 32767 between? ;
725
726 M: ppc immediate-bitwise? ( n -- ? ) 0 65535 between? ;
727
728 M: ppc return-struct-in-registers? ( c-type -- ? )
729     c-type return-in-registers?>> ;
730
731 M: ppc %box-small-struct ( c-type -- )
732     #! Box a <= 16-byte struct returned in r3:r4:r5:r6
733     heap-size 7 LI
734     8 %load-vm-addr
735     "from_medium_struct" f %alien-invoke ;
736
737 : %unbox-struct-1 ( -- )
738     ! Alien must be in r3.
739     4 %load-vm-addr
740     "alien_offset" f %alien-invoke
741     3 3 0 LWZ ;
742
743 : %unbox-struct-2 ( -- )
744     ! Alien must be in r3.
745     4 %load-vm-addr
746     "alien_offset" f %alien-invoke
747     4 3 4 LWZ
748     3 3 0 LWZ ;
749
750 : %unbox-struct-4 ( -- )
751     ! Alien must be in r3.
752     4 %load-vm-addr
753     "alien_offset" f %alien-invoke
754     6 3 12 LWZ
755     5 3 8 LWZ
756     4 3 4 LWZ
757     3 3 0 LWZ ;
758
759 M: ppc %nest-stacks ( -- )
760     3 %load-vm-addr
761     "nest_stacks" f %alien-invoke ;
762
763 M: ppc %unnest-stacks ( -- )
764     3 %load-vm-addr
765     "unnest_stacks" f %alien-invoke ;
766
767 M: ppc %unbox-small-struct ( size -- )
768     heap-size cell align cell /i {
769         { 1 [ %unbox-struct-1 ] }
770         { 2 [ %unbox-struct-2 ] }
771         { 4 [ %unbox-struct-4 ] }
772     } case ;
773
774 enable-float-functions
775
776 USE: vocabs.loader
777
778 {
779     { [ os macosx? ] [ "cpu.ppc.macosx" require ] }
780     { [ os linux? ] [ "cpu.ppc.linux" require ] }
781 } cond
782
783 "complex-double" c-type t >>return-in-registers? drop