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