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