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