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