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