In PowerPC libem, use the new features of our assembler.

The new features are the hi16/lo16 and ha16/lo16 syntax for
relocations, and the extended mnemonics like "blr".

Use ha16/lo16 to load some double floats with 2 instructions (lis/lfd)
instead of 3 (lis/ori/lfd).

Use the extended names for branches, comparisons, and bit rotations,
so I can more easily read the code.  The new names often encode the
same machine instructions as the old names, except in a few places
where I changed the instructions.

Stop using andi. when we don't need to set cr0.  In inn.s, I change
andi. to extrwi to extract the same bits.  In los.s and sts.s, I
change "andi. r3, r3, ~3" to "clrrwi r3, r3, 2".  This avoids setting
cr0 and also stops clearing the high 16 bits of r3.

In csa.s, los.s, sts.s, I change some comparisons and right shifts
from signed to unsigned (cmplw, cmplwi, srwi), because the sizes are
unsigned.  In inn.s, the right shift can be signed (sraw) or unsigned
(srw), but I use srw because we don't need the carry bit.

In fef8.s, I save an instruction by using rlwinm instead of addis/andc
to rlwinm to clear a field.  The code no longer kills r7.  In both
fef8.s and fif8.s, I remove the list of killed registers.

Also remove some whitespace from ends of lines.
This commit is contained in:
George Koehler 2017-01-23 17:16:39 -05:00
parent a41b6f0458
commit 032bcffef6
26 changed files with 184 additions and 300 deletions

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Index into a bounds-checked array. ! Index into a bounds-checked array.
@ -20,19 +13,20 @@
.define .aar4 .define .aar4
.aar4: .aar4:
li32 r0, .trap_earray lis r0, hi16[.trap_earray]
ori r0, r0, lo16[.trap_earray]
mtspr ctr, r0 ! load CTR with trap address mtspr ctr, r0 ! load CTR with trap address
lwz r0, 0(r3) lwz r0, 0(r3)
subf. r4, r0, r4 ! adjust range subf. r4, r0, r4 ! adjust range
bcctr IFTRUE, LT, 0 ! check lower bound bltctr ! check lower bound
lwz r0, 4(r3) lwz r0, 4(r3)
cmpl cr0, 0, r4, r3 cmplw r4, r3
bcctr IFFALSE, LT, 0 ! check upper bound bgectr ! check upper bound
lwz r0, 8(r3) lwz r0, 8(r3)
mullw r4, r4, r0 ! scale index mullw r4, r4, r0 ! scale index
add r3, r4, r5 ! calculate element address add r3, r4, r5 ! calculate element address
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Set intersection. ! Set intersection.
@ -12,7 +10,7 @@
mr r4, sp ! r4 = ptr to set a mr r4, sp ! r4 = ptr to set a
add r5, sp, r3 ! r5 = ptr to set b add r5, sp, r3 ! r5 = ptr to set b
rlwinm r6, r3, 30, 2, 31 srwi r6, r3, 2
mtspr ctr, r6 ! ctr = r3 / 4 mtspr ctr, r6 ! ctr = r3 / 4
1: 1:
lwz r7, 0(r4) lwz r7, 0(r4)
@ -21,6 +19,6 @@
stw r8, 0(r5) stw r8, 0(r5)
addi r4, r4, 4 addi r4, r4, 4
addi r5, r5, 4 addi r5, r5, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
add sp, sp, r3 add sp, sp, r3
bclr ALWAYS, 0, 0 blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Converts a 64-bit double into a 32-bit integer. ! Converts a 64-bit double into a 32-bit integer.
@ -17,4 +10,4 @@
fctiwz f0, f0 fctiwz f0, f0
stfd f0, 0(sp) stfd f0, 0(sp)
addi sp, sp, 4 addi sp, sp, 4
bclr ALWAYS, 0, 0 ! ...and return blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Converts a 64-bit double into a 32-bit unsigned integer. ! Converts a 64-bit double into a 32-bit unsigned integer.
@ -13,16 +6,16 @@
.define .cfu8 .define .cfu8
.cfu8: .cfu8:
li32 r3, .fd_00000000 lis r3, ha16[.fd_00000000]
lfd f0, 0(r3) ! f0 = 0.0 lfd f0, lo16[.fd_00000000](r3) ! f0 = 0.0
lfd f1, 0(sp) ! value to be converted lfd f1, 0(sp) ! value to be converted
li32 r3, .fd_FFFFFFFF lis r3, ha16[.fd_FFFFFFFF]
lfd f3, 0(r3) ! f3 = 0xFFFFFFFF lfd f3, lo16[.fd_FFFFFFFF](r3) ! f3 = 0xFFFFFFFF
li32 r3, .fd_80000000 lis r3, ha16[.fd_80000000]
lfd f4, 0(r3) ! f4 = 0x80000000 lfd f4, lo16[.fd_80000000](r3) ! f4 = 0x80000000
fsel f2, f1, f1, f0 fsel f2, f1, f1, f0
fsub f5, f3, f1 fsub f5, f3, f1
@ -35,10 +28,10 @@
stfd f2, 0(sp) stfd f2, 0(sp)
addi sp, sp, 4 addi sp, sp, 4
bclr IFTRUE, LT, 0 bltlr
lwz r3, 0(sp) lwz r3, 0(sp)
xoris r3, r3, 0x8000 xoris r3, r3, 0x8000
stw r3, 0(sp) stw r3, 0(sp)
bclr ALWAYS, 0, 0 blr

View file

@ -1,9 +1,4 @@
# .sect .text; .sect .rom; .sect .data; .sect .bss
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
@ -24,12 +19,12 @@
lfd f0, 0(sp) ! load value lfd f0, 0(sp) ! load value
li32 r3, pivot lis r3, ha16[pivot]
lfd f1, 0(r3) ! load pivot value lfd f1, lo16[pivot](r3) ! load pivot value
fsub f0, f0, f1 ! adjust fsub f0, f0, f1 ! adjust
stfd f0, 0(sp) ! save value again... stfd f0, 0(sp) ! save value again...
bclr ALWAYS, 0, 0 ! ...and return blr ! ...and return
.sect .rom .sect .rom
pivot: pivot:

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Compare sets a, b. ! Compare sets a, b.
@ -12,21 +10,21 @@
mr r4, sp ! r4 = ptr to set a mr r4, sp ! r4 = ptr to set a
add r5, sp, r3 ! r5 = ptr to set b add r5, sp, r3 ! r5 = ptr to set b
mr r6, r3 ! r6 = size mr r6, r3 ! r6 = size
rlwinm r3, r3, 30, 2, 31 srwi r3, r3, 2
mtspr ctr, r3 ! ctr = size / 4 mtspr ctr, r3 ! ctr = size / 4
1: 1:
lwz r7, 0(r4) lwz r7, 0(r4)
lwz r8, 0(r5) lwz r8, 0(r5)
cmp cr0, 0, r7, r8 ! compare words in sets cmpw cr0, r7, r8 ! compare words in sets
addi r4, r4, 4 addi r4, r4, 4
addi r5, r5, 4 addi r5, r5, 4
bc IFFALSE, EQ, 2f ! branch if not equal bne cr0, 2f ! branch if not equal
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
addi r3, r0, 0 ! equal: return 0 addi r3, r0, 0 ! equal: return 0
b 3f b 3f
2: 2:
addi r3, r0, 1 ! not equal: return 1 addi r3, r0, 1 ! not equal: return 1
3: 3:
rlwinm r6, r6, 1, 0, 30 ! r6 = size * 2 slwi r6, r6, 1 ! r6 = size * 2
add sp, sp, r6 ! remove sets from stack add sp, sp, r6 ! remove sets from stack
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Set complement. ! Set complement.
@ -11,12 +9,12 @@
addi sp, sp, 4 addi sp, sp, 4
mr r4, sp ! r4 = pointer to set a mr r4, sp ! r4 = pointer to set a
rlwinm r5, r3, 30, 2, 31 srwi r5, r3, 2
mtspr ctr, r5 ! ctr = r3 / 4 mtspr ctr, r5 ! ctr = r3 / 4
1: 1:
lwz r6, 0(r4) lwz r6, 0(r4)
nor r6, r6, r6 ! complement of word nor r6, r6, r6 ! complement of word
stw r6, 0(r4) stw r6, 0(r4)
addi r4, r4, 4 addi r4, r4, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
bclr ALWAYS, 0, 0 blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! this is not a subroutine, but just a ! this is not a subroutine, but just a
@ -25,23 +18,17 @@
lwz r5, 4(r3) ! fetch lower bound lwz r5, 4(r3) ! fetch lower bound
subf. r4, r5, r4 ! adjust value subf. r4, r5, r4 ! adjust value
bcctr IFTRUE, LT, 0 ! jump to default if out of range bltctr ! jump to default if out of range
lwz r5, 8(r3) ! fetch range lwz r5, 8(r3) ! fetch range
cmp cr0, 0, r4, r5 cmplw r4, r5
bcctr IFTRUE, GT, 0 ! jump to default if out of range bgtctr ! jump to default if out of range
addi r3, r3, 12 ! skip header addi r3, r3, 12 ! skip header
rlwinm r4, r4, 2, 0, 31-2 ! scale value (<<2) slwi r4, r4, 2 ! scale value (<<2)
b 1f
1:
lwzx r5, r3, r4 ! load target lwzx r5, r3, r4 ! load target
b 1f
1:
mtspr ctr, r5 mtspr ctr, r5
or. r5, r5, r5 ! test it or. r5, r5, r5 ! test it
b 1f bnectr ! jump to target if non-zero
1:
bcctr IFFALSE, EQ, 0 ! jump to target if non-zero
b .trap_ecase ! otherwise trap b .trap_ecase ! otherwise trap

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! this is not a subroutine, but just a ! this is not a subroutine, but just a
@ -27,16 +20,16 @@
1: 1:
or. r6, r6, r6 ! test count or. r6, r6, r6 ! test count
bcctr IFTRUE, EQ, 0 ! exit if zero beqctr ! exit if zero
addi r6, r6, -1 ! otherwise decrement addi r6, r6, -1 ! otherwise decrement
lwzu r7, 8(r3) ! fetch target index, increment pointer lwzu r7, 8(r3) ! fetch target index, increment pointer
cmp cr0, 0, r4, r7 ! compare with value cmpw r4, r7 ! compare with value
bc IFFALSE, EQ, 1b ! if not equal, go again bne 1b ! if not equal, go again
lwz r7, 4(r3) ! fetch target address lwz r7, 4(r3) ! fetch target address
mtspr ctr, r7 mtspr ctr, r7
or. r7, r7, r7 ! test it or. r7, r7, r7 ! test it
bcctr IFFALSE, EQ, 0 ! jump to target if non-zero bnectr ! jump to target if non-zero
b .trap_ecase ! otherwise trap b .trap_ecase ! otherwise trap

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Converts a 32-bit unsigned integer into a 64-bit double. ! Converts a 32-bit unsigned integer into a 64-bit double.
@ -15,17 +8,17 @@
.cuf8: .cuf8:
addi sp, sp, -4 ! make space for the double addi sp, sp, -4 ! make space for the double
addis r3, r0, 0x4330 lis r3, 0x4330
stw r3, 0(sp) ! set high word to construct a double stw r3, 0(sp) ! set high word to construct a double
lfd f0, 0(sp) ! load value lfd f0, 0(sp) ! load value
li32 r3, pivot lis r3, ha16[pivot]
lfd f1, 0(r3) ! load pivot value lfd f1, lo16[pivot](r3) ! load pivot value
fsub f0, f0, f1 ! adjust fsub f0, f0, f1 ! adjust
stfd f0, 0(sp) ! save value again... stfd f0, 0(sp) ! save value again...
bclr ALWAYS, 0, 0 ! ...and return blr ! ...and return
.sect .rom .sect .rom
pivot: pivot:

View file

@ -1,9 +1,4 @@
# .sect .text; .sect .rom; .sect .data; .sect .bss
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .rom .sect .rom

View file

@ -1,9 +1,4 @@
# .sect .text; .sect .rom; .sect .data; .sect .bss
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .rom .sect .rom

View file

@ -1,9 +1,4 @@
# .sect .text; .sect .rom; .sect .data; .sect .bss
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .rom .sect .rom

View file

@ -1,4 +1,4 @@
#include "powerpc.h" .sect .text; .sect .rom; .sect .data; .sect .bss
.sect .text .sect .text
@ -10,46 +10,44 @@
! r3 = fraction, high word (bits 0..31) ! r3 = fraction, high word (bits 0..31)
! r4 = fraction, low word (bits 32..63) ! r4 = fraction, low word (bits 32..63)
! r5 = exponent ! r5 = exponent
! Kills: cr0 f0 f1 r6 r7
.define .fef8 .define .fef8
.fef8: .fef8:
! IEEE double-precision format: ! IEEE double-precision format:
! sign exponent fraction ! sign exponent fraction
! 0 1..11 12..63 ! 0 1..11 12..63
rlwinm r6, r3, 12, 21, 31 ! r6 = IEEE exponent extrwi r6, r3, 11, 1 ! r6 = IEEE exponent
addis r7, r0, 0x7ff0 ! r7 = exponent mask
addi r5, r6, -1022 ! r5 = true exponent addi r5, r6, -1022 ! r5 = true exponent
cmpi cr0, 0, r6, 2047 cmpwi r6, 2047
bclr IFTRUE, EQ, 0 ! return if infinity or NaN beqlr ! return if infinity or NaN
cmpi cr0, 0, r6, 0 cmpwi r6, 0
bc IFFALSE, EQ, 1f ! jump if normalized number bne 1f ! jump if normalized number
! Got denormalized number or zero, probably zero. ! Got denormalized number or zero, probably zero.
rlwinm r6, r3, 0, 12, 31 extrwi r6, r3, 22, 12
addi r5, r0, 0 ! r5 = true exponent = 0 addi r5, r0, 0 ! r5 = true exponent = 0
or. r6, r6, r4 ! r6 = high|low fraction or. r6, r6, r4 ! r6 = high|low fraction
bclr IFTRUE, EQ, 0 ! return if zero beqlr ! return if zero
! Got denormalized number, not zero. ! Got denormalized number, not zero.
stwu r4, -4(sp) stwu r4, -4(sp)
stwu r3, -4(sp) stwu r3, -4(sp)
li32 r6, _2_64
lfd f0, 0(sp) lfd f0, 0(sp)
lfd f1, 0(r6) lis r6, ha16[_2_64]
lfd f1, lo16[_2_64](r6)
fmul f0, f0, f1 ! multiply it by 2**64 fmul f0, f0, f1 ! multiply it by 2**64
stfd f0, 0(sp) stfd f0, 0(sp)
lwz r3, 0(sp) lwz r3, 0(sp)
lwz r4, 4(sp) lwz r4, 4(sp)
rlwinm r6, r3, 12, 21, 31 ! r6 = IEEE exponent extrwi r6, r3, 11, 1 ! r6 = IEEE exponent
addi sp, sp, 8 addi sp, sp, 8
addi r5, r6, -1022 - 64 ! r5 = true exponent addi r5, r6, -1022 - 64 ! r5 = true exponent
1: 1:
! Put fraction in [0.5, 1) or (-1, -0.5] by setting its ! Put fraction in [0.5, 1) or (-1, -0.5] by setting its
! exponent to true 0, IEEE 1022. ! exponent to true 0, IEEE 1022.
andc r3, r3, r7 ! clear old exponent rlwinm r3, r3, 0, 12, 0 ! clear old exponent
oris r3, r3, 1022 << 4 ! set new exponent oris r3, r3, 1022 << 4 ! set new exponent
bclr ALWAYS, 0, 0 blr
.sect .rom .sect .rom
_2_64: _2_64:

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Multiplies two double-precision floats, then splits the product into ! Multiplies two double-precision floats, then splits the product into
@ -9,7 +7,6 @@
! Yields: ! Yields:
! f1 = fraction ! f1 = fraction
! f2 = integer ! f2 = integer
! Kills: cr0 f1 f2 r3 r4 r5 r6
.define .fif8 .define .fif8
.fif8: .fif8:
@ -25,17 +22,16 @@
! 0 to 51, then the IEEE fraction has that many integer bits. ! 0 to 51, then the IEEE fraction has that many integer bits.
! (IEEE has an implicit 1 before its fraction. If the IEEE ! (IEEE has an implicit 1 before its fraction. If the IEEE
! fraction has 0 integer bits, we still have an integer.) ! fraction has 0 integer bits, we still have an integer.)
rlwinm r5, r3, 12, 21, 31 ! r5 = IEEE exponent extrwi r5, r3, 11, 1 ! r5 = IEEE exponent
addic. r5, r5, -1023 ! r5 = nr of integer bits addic. r5, r5, -1023 ! r5 = nr of integer bits
bc IFTRUE, LT, no_int blt no_int
cmpi cr0, 0, r5, 21 cmpwi r5, 21
bc IFTRUE, LT, small_int blt small_int
cmpi cr0, 0, r5, 52 cmpwi r5, 52
bc IFTRUE, LT, big_int blt big_int
! f1 is an integer without fraction. Jump to calculate ! f1 is an integer without fraction (or infinity or NaN).
! fraction f1 = f2 - f1. It will be zero (or perhaps NaN). fmr f2, f1 ! integer = f1
fmr f2, f1
b subtract b subtract
no_int: no_int:
@ -46,17 +42,17 @@ no_int:
small_int: small_int:
! f1 has r5 = 0 to 20 integer bits in the IEEE fraction. ! f1 has r5 = 0 to 20 integer bits in the IEEE fraction.
! High word has 20 - r5 fraction bits. ! High word has 20 - r5 fraction bits.
addi r6, r0, 20 li r6, 20
subf r6, r5, r6 subf r6, r5, r6
srw r3, r3, r6 srw r3, r3, r6
addi r4, r0, 0 ! clear low word li r4, 0 ! clear low word
slw r3, r3, r6 ! clear fraction in high word slw r3, r3, r6 ! clear fraction in high word
b move_int b move_int
big_int: big_int:
! f1 has r5 = 21 to 51 to integer bits. ! f1 has r5 = 21 to 51 to integer bits.
! Low word has 52 - r5 fraction bits. ! Low word has 52 - r5 fraction bits.
addi r6, r0, 52 li r6, 52
subf r6, r5, r6 subf r6, r5, r6
srw r4, r4, r6 srw r4, r4, r6
slw r4, r4, r6 ! clear fraction in low word slw r4, r4, r6 ! clear fraction in low word
@ -68,4 +64,4 @@ subtract:
fsub f1, f1, f2 ! fraction = value - integer fsub f1, f1, f2 ! fraction = value - integer
done: done:
addi sp, sp, 8 ! restore stack pointer addi sp, sp, 8 ! restore stack pointer
bclr ALWAYS, 0, 0 blr

View file

@ -1,4 +1,4 @@
#include "powerpc.h" #
.sect .text .sect .text
@ -14,13 +14,13 @@
addi r5, sp, 8 /* r5 = base address of bit set */ addi r5, sp, 8 /* r5 = base address of bit set */
rlwinm r6, r4, 29, 3, 29 /* r6 = byte index of word in set */ rlwinm r6, r4, 29, 3, 29 /* r6 = byte index of word in set */
andi. r7, r4, 31 /* r7 = bit within word */ extrwi r7, r4, 5, 27 /* r7 = bit number within word */
lwzx r8, r5, r6 /* r8 = individual byte from set */ lwzx r8, r5, r6 /* r8 = individual word from set */
sraw r8, r8, r7 srw r8, r8, r7
rlwinm r8, r8, 0, 31, 31 extrwi r8, r8, 1, 31
addi sp, sp, 8 /* retract over the two words */ addi sp, sp, 8 /* retract over the two words */
add sp, sp, r3 /* retract over bitfield */ add sp, sp, r3 /* retract over bitfield */
stwu r8, -4(sp) /* push result */ stwu r8, -4(sp) /* push result */
bclr ALWAYS, 0, 0 /* return */ blr /* return */

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Set union. ! Set union.
@ -12,7 +10,7 @@
mr r4, sp ! r4 = ptr to set a mr r4, sp ! r4 = ptr to set a
add r5, sp, r3 ! r5 = ptr to set b add r5, sp, r3 ! r5 = ptr to set b
rlwinm r6, r3, 30, 2, 31 srwi r6, r3, 2
mtspr ctr, r6 ! ctr = r3 / 4 mtspr ctr, r6 ! ctr = r3 / 4
1: 1:
lwz r7, 0(r4) lwz r7, 0(r4)
@ -21,6 +19,6 @@
stw r8, 0(r5) stw r8, 0(r5)
addi r4, r4, 4 addi r4, r4, 4
addi r5, r5, 4 addi r5, r5, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
add sp, sp, r3 add sp, sp, r3
bclr ALWAYS, 0, 0 blr

View file

@ -1,6 +1,3 @@
#
#include "powerpc.h"
.sect .text .sect .text
! Load from bounds-checked array. ! Load from bounds-checked array.
@ -18,19 +15,19 @@
! r3 = ptr to element ! r3 = ptr to element
! r0 = size of element ! r0 = size of element
cmpi cr0, 0, r0, 1 cmpwi r0, 1
bc IFFALSE, EQ, 1f bne 1f
! Load 1 byte. ! Load 1 byte.
lbz r4, 0(r3) lbz r4, 0(r3)
stwu r4, -4(sp) stwu r4, -4(sp)
bclr ALWAYS, 0, 0 blr
1: 1:
cmpi cr0, 0, r0, 2 cmpwi r0, 2
bc IFFALSE, EQ, 2f bne 2f
! Load 2 bytes. ! Load 2 bytes.
lhz r4, 0(r3) lhz r4, 0(r3)
stwu r4, -4(sp) stwu r4, -4(sp)
bclr ALWAYS, 0, 0 blr
2: 2:
! Load r0 bytes, where r0 must be a positive multiple of 4. ! Load r0 bytes, where r0 must be a positive multiple of 4.
subf sp, r0, sp ! move stack pointer down subf sp, r0, sp ! move stack pointer down
@ -39,5 +36,5 @@
addic. r5, r5, -4 ! r5 -= 4 addic. r5, r5, -4 ! r5 -= 4
lwzx r4, r5, r3 lwzx r4, r5, r3
stwx r4, r5, sp stwx r4, r5, sp
bc IFTRUE, GT, 3b ! loop if r5 > 0 bgt 3b ! loop if r5 > 0
bclr ALWAYS, 0, 0 blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Loads a variable-sized structure onto the stack. ! Loads a variable-sized structure onto the stack.
@ -16,30 +9,30 @@
.los: .los:
! These sizes are handled specially. ! These sizes are handled specially.
cmpi cr0, 0, r3, 1 cmplwi r3, 1
bc IFFALSE, GT, size1 ble size1
cmpi cr0, 0, r3, 2 cmplwi r3, 2
bc IFFALSE, GT, size2 ble size2
cmpi cr0, 0, r3, 4 cmplwi r3, 4
bc IFFALSE, GT, size4 ble size4
! Variable-sized structure. ! Variable-sized structure.
addi r3, r3, 3 addi r3, r3, 3
andi. r3, r3, ~3 ! align size clrrwi r3, r3, 2 ! align size
add r4, r4, r3 ! adjust address to top of block add r4, r4, r3 ! adjust address to top of block
srawi r3, r3, 2 ! convert size to the number of words srwi r3, r3, 2 ! convert size to the number of words
mtspr ctr, r3 mtspr ctr, r3
1: 1:
lwzu r5, -4(r4) lwzu r5, -4(r4)
stwu r5, -4(sp) stwu r5, -4(sp)
bc DNZ, 0, 1b ! decrement CTR, jump if non-zero bdnz 1b ! decrement CTR, jump if non-zero
bclr ALWAYS, 0, 0 blr
size1: size1:
lbz r3, 0(r4) lbz r3, 0(r4)
@ -51,4 +44,4 @@ size4:
lwz r3, 0(r4) lwz r3, 0(r4)
1: 1:
stwu r3, -4(sp) stwu r3, -4(sp)
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Bounds check. Traps if the value is out of range. ! Bounds check. Traps if the value is out of range.
@ -12,11 +10,11 @@
addi sp, sp, 4 ! leave value on stack addi sp, sp, 4 ! leave value on stack
lwz r5, 0 (r3) lwz r5, 0 (r3)
cmp cr0, 0, r4, r5 cmpw r4, r5
bc IFTRUE, LT, .trap_erange blt .trap_erange
lwz r5, 4 (r3) lwz r5, 4 (r3)
cmp cr0, 0, r4, r5 cmpw r4, r5
bc IFTRUE, GT, .trap_erange bgt .trap_erange
bclr ALWAYS, 0, 0 blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Standard boilerplate for returning from functions. ! Standard boilerplate for returning from functions.
@ -15,5 +8,5 @@
mtspr lr, r0 mtspr lr, r0
lwz r0, 0(fp) ! our stack frame becomes invalid as soon as... lwz r0, 0(fp) ! our stack frame becomes invalid as soon as...
addi sp, fp, 8 ! ...we change sp addi sp, fp, 8 ! ...we change sp
or fp, r0, r0 mr fp, r0
bclr ALWAYS, 0, 0 blr

View file

@ -1,6 +1,3 @@
#
#include "powerpc.h"
.sect .text .sect .text
! Store to bounds-checked array. ! Store to bounds-checked array.
@ -18,21 +15,21 @@
! r3 = ptr to element ! r3 = ptr to element
! r0 = size of element ! r0 = size of element
cmpi cr0, 0, r0, 1 cmpwi r0, 1
bc IFFALSE, EQ, 1f bne 1f
! Store 1 byte. ! Store 1 byte.
lwz r4, 0(sp) lwz r4, 0(sp)
addi sp, sp, 4 addi sp, sp, 4
stb r4, 0(r3) stb r4, 0(r3)
bclr ALWAYS, 0, 0 blr
1: 1:
cmpi cr0, 0, r0, 2 cmpwi r0, 2
bc IFFALSE, EQ, 2f bne 2f
! Store 2 bytes. ! Store 2 bytes.
lwz r4, 0(sp) lwz r4, 0(sp)
addi sp, sp, 4 addi sp, sp, 4
sth r4, 0(r3) sth r4, 0(r3)
bclr ALWAYS, 0, 0 blr
2: 2:
! Store r0 bytes, where r0 must be a positive multiple of 4. ! Store r0 bytes, where r0 must be a positive multiple of 4.
or r5, r0, r0 ! index r5 = length r0 or r5, r0, r0 ! index r5 = length r0
@ -40,6 +37,6 @@
addic. r5, r5, -4 ! r5 -= 4 addic. r5, r5, -4 ! r5 -= 4
lwzx r4, r5, sp lwzx r4, r5, sp
stwx r4, r5, r3 stwx r4, r5, r3
bc IFTRUE, GT, 3b ! loop if r5 > 0 bgt 3b ! loop if r5 > 0
add sp, r0, sp ! move stack pointer up add sp, r0, sp ! move stack pointer up
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Create singleton set. ! Create singleton set.
@ -11,22 +9,22 @@
lwz r4, 4 (sp) lwz r4, 4 (sp)
addi sp, sp, 8 addi sp, sp, 8
rlwinm r7, r3, 30, 2, 31 srwi r7, r3, 2
neg r5, r3 neg r5, r3
add sp, sp, r5 ! allocate set add sp, sp, r5 ! allocate set
mr r6, sp ! r6 = ptr to set mr r6, sp ! r6 = ptr to set
mtspr ctr, r7 ! ctr = r3 / 4 mtspr ctr, r7 ! ctr = r3 / 4
1: 1:
rlwinm. r7, r4, 0, 0, 26 ! r7 = r4 & ~31 clrrwi. r7, r4, 5 ! r7 = r4 & ~31
bc IFTRUE, EQ, 2f ! branch if r4 in 0..31 beq 2f ! branch if r4 in 0..31
addi r5, r0, 0 ! no bit, word is zero li r5, 0 ! no bit, word is zero
b 3f b 3f
2: 2:
addi r5, r0, 1 li r5, 1
slw r5, r5, r4 ! yes bit, set bit in word slw r5, r5, r4 ! yes bit, set bit in word
3: 3:
stw r5, 0(r6) ! store word in set stw r5, 0(r6) ! store word in set
addi r4, r4, -32 addi r4, r4, -32
addi r6, r6, 4 addi r6, r6, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
bclr ALWAYS, 0, 0 blr

View file

@ -1,10 +1,3 @@
#
! $Source$
! $State$
! $Revision$
#include "powerpc.h"
.sect .text .sect .text
! Stores a variable-sized structure from the stack. ! Stores a variable-sized structure from the stack.
@ -18,21 +11,21 @@
lwz r5, 0(sp) lwz r5, 0(sp)
cmpi cr0, 0, r3, 1 cmplwi r3, 1
bc IFFALSE, GT, size1 ble size1
cmpi cr0, 0, r3, 2 cmplwi r3, 2
bc IFFALSE, GT, size2 ble size2
cmpi cr0, 0, r3, 4 cmplwi r3, 4
bc IFFALSE, GT, size4 ble size4
! Variable-sized structure. ! Variable-sized structure.
addi r3, r3, 3 addi r3, r3, 3
andi. r3, r3, ~3 ! align size clrrwi r3, r3, 2 ! align size
srawi r3, r3, 2 ! convert size to the number of words srwi r3, r3, 2 ! convert size to the number of words
mtspr ctr, r3 mtspr ctr, r3
1: 1:
@ -41,8 +34,8 @@
stw r5, 0(r4) stw r5, 0(r4)
addi r4, r4, 4 addi r4, r4, 4
bc DNZ, 0, 1b ! decrement CTR, jump if non-zero bdnz 1b ! decrement CTR, jump if non-zero
bclr ALWAYS, 0, 0 blr
size1: size1:
stb r5, 0(r4) stb r5, 0(r4)
@ -54,4 +47,4 @@ size4:
stw r5, 0(r4) stw r5, 0(r4)
1: 1:
addi sp, sp, 4 addi sp, sp, 4
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Set symmetric difference. ! Set symmetric difference.
@ -10,7 +8,7 @@
.xor: .xor:
mr r4, sp ! r4 = ptr to set a mr r4, sp ! r4 = ptr to set a
add r5, sp, r3 ! r5 = ptr to set b add r5, sp, r3 ! r5 = ptr to set b
rlwinm r6, r3, 30, 2, 31 srwi r6, r3, 2
mtspr ctr, r6 ! ctr = r3 / 4 mtspr ctr, r6 ! ctr = r3 / 4
1: 1:
lwz r7, 0(r4) lwz r7, 0(r4)
@ -19,6 +17,6 @@
stw r8, 0(r5) stw r8, 0(r5)
addi r4, r4, 4 addi r4, r4, 4
addi r5, r5, 4 addi r5, r5, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
add sp, sp, r3 add sp, sp, r3
bclr ALWAYS, 0, 0 blr

View file

@ -1,5 +1,3 @@
#include "powerpc.h"
.sect .text .sect .text
! Create empty set. ! Create empty set.
@ -10,8 +8,8 @@
lwz r3, 0(sp) lwz r3, 0(sp)
addi sp, sp, 4 addi sp, sp, 4
rlwinm r7, r3, 30, 2, 31 srwi r7, r3, 2
addi r4, r0, 0 ! r4 = zero li r4, 0 ! r4 = zero
neg r5, r3 neg r5, r3
add sp, sp, r5 ! allocate set add sp, sp, r5 ! allocate set
mr r6, sp ! r6 = ptr to set mr r6, sp ! r6 = ptr to set
@ -19,5 +17,5 @@
1: 1:
stw r4, 0(r6) ! store zero in set stw r4, 0(r6) ! store zero in set
addi r6, r6, 4 addi r6, r6, 4
bc DNZ, 0, 1b ! loop ctr times bdnz 1b ! loop ctr times
bclr ALWAYS, 0, 0 blr