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