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