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