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