mirror of
https://github.com/RevCurtisP/C02.git
synced 2025-04-22 00:37:19 +00:00
Replaced testsl.c02, testslib.c02 with slibtest.c02 and debugged stdlib.a02
This commit is contained in:
parent
4d460ce581
commit
902347db57
@ -3,15 +3,17 @@
|
||||
; external zero page locations SRCLO and SRCHI
|
||||
; and external locations RANDOM, RDSEED, TEMP0, TEMP1, and TEMP2.
|
||||
|
||||
SUBROUTINE STDLIB
|
||||
|
||||
;abs(n) - Get ABSolute Value
|
||||
;Args: A = Number to get Absolute Value Of
|
||||
;Affects: C, N, Z
|
||||
;Returns: A = Absolute Value of Argument
|
||||
ABS: CMP #$80 ;If Negative (High Bit Set)
|
||||
BCC ABSX ; Carry will Already be Set
|
||||
BCC .ABSX ; Carry will Already be Set
|
||||
EOR #$FF ; One's Complement
|
||||
ADC #$00 ; and Increment (Carry set by CMP)
|
||||
ABSX: RTS
|
||||
.ABSX RTS
|
||||
|
||||
;max(m,n) - Get MAXimum of Two Numbers
|
||||
;Args: A,Y = Numbers to Compare
|
||||
@ -20,9 +22,9 @@ ABSX: RTS
|
||||
;Returns: A = Larger of the Two Arguments
|
||||
MAX: STY TEMP0 ;Save Second Parameter
|
||||
CMP TEMP0 ;If First Parameter
|
||||
BCC MAXX ; Greater than Second Parameter
|
||||
BCC .MAXX ; Greater than Second Parameter
|
||||
TYA ;Copy Second Parameter into Accumulator
|
||||
MAXX: RTS
|
||||
.MAXX RTS
|
||||
|
||||
;min(m,n) - Get MINimum Get MAXimum of Two Numbers
|
||||
;Args: A,Y = Numbers to Compare
|
||||
@ -31,9 +33,9 @@ MAXX: RTS
|
||||
;Returns: A = Smaller of the Two Arguments
|
||||
MIN: STY TEMP0 ;Save Second Parameter
|
||||
CMP TEMP0 ;If First Parameter
|
||||
BCS MINX ; Less than Second Parameter
|
||||
BCS .MINX ; Less than Second Parameter
|
||||
TYA ;Copy Second Parameter into Accumulator
|
||||
MINX: RTS
|
||||
.MINX RTS
|
||||
|
||||
;mult(m,n) - MULTiply Two Numbers
|
||||
;Args: A = Multiplicand
|
||||
@ -48,13 +50,13 @@ MULT: STA TEMP0 ;Store Multiplicand
|
||||
STY TEMP1 ;Store Multiplier
|
||||
;Multiply TEMP0 times TEMP1
|
||||
MULTT: LDA #$00 ;Initialize Accumulator
|
||||
BEQ MULTE ;Enter Loop
|
||||
MULTA: CLC
|
||||
BEQ .MULTE ;Enter Loop
|
||||
.MULTA CLC
|
||||
ADC TEMP0 ;Add Multiplicand
|
||||
MULTL: ASL TEMP0 ;Shift Multiplicand Left
|
||||
MULTE: LSR TEMP1 ;Shift Multiplier Right
|
||||
BCS MULTA ;If Bit Shifted Out, Add Multiplicand
|
||||
BNE MULTL ;Loop if Any 1 Bits Left
|
||||
.MULTL ASL TEMP0 ;Shift Multiplicand Left
|
||||
.MULTE LSR TEMP1 ;Shift Multiplier Right
|
||||
BCS .MULTA ;If Bit Shifted Out, Add Multiplicand
|
||||
BNE .MULTL ;Loop if Any 1 Bits Left
|
||||
LDY TEMP2 ;Load Y with MSB
|
||||
TAX ;and Copy LSB to X
|
||||
RTS
|
||||
@ -73,13 +75,13 @@ DIV: STA TEMP0 ;Store Dividend
|
||||
DIVT: LDA #$00 ;Clear Accumulator
|
||||
LDX #$07 ;Load Loop Counter
|
||||
CLC
|
||||
DIVL: ROL TEMP0 ;Shift Bit Out of Dividend
|
||||
.DIVL ROL TEMP0 ;Shift Bit Out of Dividend
|
||||
ROL ; into Accumulator
|
||||
CMP TEMP1 ;If Accumulator
|
||||
BCC DIVS ; >= Divisor
|
||||
BCC .DIVS ; >= Divisor
|
||||
SBC TEMP1 ;Subtract Divisor
|
||||
DIVS: DEX ;Decrement Counter
|
||||
BPL DIVL ; and Loop
|
||||
.DIVS DEX ;Decrement Counter
|
||||
BPL .DIVL ; and Loop
|
||||
ROL TEMP0 ;Shift Result into Dividend
|
||||
TAY ;Copy Remainder to Y Register
|
||||
LDA TEMP0 ;Load Result into Accumulator
|
||||
@ -90,9 +92,9 @@ DIVS: DEX ;Decrement Counter
|
||||
;Affects A,N,Z,C
|
||||
RAND: LDA RANDOM ;Load Last Result
|
||||
ASL ;Shift the Seed
|
||||
BCC RANDX ;If a one was shifted out
|
||||
BCC .RANDX ;If a one was shifted out
|
||||
EOR #$1D ; Twiddle the bite
|
||||
RANDX: STA RANDOM ;Save the Seed
|
||||
.RANDX STA RANDOM ;Save the Seed
|
||||
RTS
|
||||
|
||||
;Seed Pseudo-Random Number Generator
|
||||
@ -100,25 +102,71 @@ RANDX: STA RANDOM ;Save the Seed
|
||||
;Affects A,N,Z,C
|
||||
;Sets RANDOM
|
||||
RANDS: ORA #$00 ;If Passed Value not 0
|
||||
BNE RANDX ; Store in Seed and Return
|
||||
BNE .RANDX ; Store in Seed and Return
|
||||
LDA RDSEED ;Load System Generated Seed
|
||||
BNE RANDX ;If Not 0, Store and Return
|
||||
BNE .RANDX ;If Not 0, Store and Return
|
||||
ADC #$01 ;Else Add 1 or 2
|
||||
BNE RANDX ; then Store and Return
|
||||
BNE .RANDX ; then Store and Return
|
||||
|
||||
;Return A Shifted Y Bytes to the Left
|
||||
;Affects A,Y,N,Z,C
|
||||
;Affects A,Y,N,Z,C
|
||||
SHIFTL: ASL ;Shift Byte to Left
|
||||
DEY ;Decrement Counter
|
||||
BNE SHIFTL ; and Loop if Not 0
|
||||
;swap(byte) - Swap Low and High Nybbles in Byte
|
||||
;Args: A = Byte to Swap
|
||||
;Affects Y,N,Z,C
|
||||
;Returns: A = Swapped Byte
|
||||
SWAP: LDY #4 ;Set Count to 4 and Rotate Left
|
||||
|
||||
;rotatl(byte,count) - Rotate byte by count Bits to the Left
|
||||
;Args = Byte to Rotate
|
||||
;Y = Number of Bits to Rotate
|
||||
;Affects X,Y,N,Z,C
|
||||
;Returns: A = Rotated Byte
|
||||
ROTATL: INY ;Pre-Increment Counter
|
||||
.ROTALL DEY ;Decrement Counter
|
||||
BEQ .ROTATX ;If Not Zero
|
||||
ASL ; Shift Left One Bit
|
||||
ADC #0 ; Copy Carry into Bit 0
|
||||
BNE .ROTALL ; If Not Zero, Loop
|
||||
.ROTATX RTS
|
||||
|
||||
;rotatr(byte,count) - Shift byte by count Bits to the Right
|
||||
;Args = Byte to Rotate
|
||||
;Y = Number of Bits to Rotate
|
||||
;Affects Y,N,Z,C
|
||||
;Returns: A = Rotated Byte
|
||||
ROTATR: INY ;Pre-Increment Counter
|
||||
.ROTALR DEY ;Decrement Counter
|
||||
BEQ .ROTATX ;If Not Zero
|
||||
LSR ; Shift Right One Bit
|
||||
BCC .ROTATS ; If Carry Set
|
||||
ORA #$80 ; Copy Carry into Bit 7
|
||||
.ROTATS BNE .ROTALR ; If Not Zero, Loop
|
||||
RTS
|
||||
|
||||
;Return A Shifted Y Bytes to the Right
|
||||
;Affects A,Y,N,Z,C
|
||||
SHIFTR: LSR ;Shift Byte to Right
|
||||
DEY ;Decrement Counter
|
||||
BNE SHIFTR ; and Loop if Not 0
|
||||
SHFTL4: LDY #4; ;Set Count to 4 and Shift Left
|
||||
|
||||
;shiftl(byte,count) - Shift byte by Count bits to the Left
|
||||
;Args = Byte to Shift
|
||||
;Y = Number of Bits to Rotate
|
||||
;Affects Y,N,Z,C
|
||||
;Returns: A = Shifted Byte
|
||||
SHIFTL: INY ;Pre-Increment Counter
|
||||
.SHIFLL DEY ;Decrement Counter
|
||||
BEQ .SHIFTX ;If Not Zero
|
||||
ASL ; Shift Byte to Left
|
||||
BNE .SHIFLL ; and Loop if Not 0
|
||||
.SHIFTX RTS
|
||||
|
||||
SHFTR4: LDY #4; ;Set Count to 4 and Shift Right
|
||||
|
||||
;shiftr(byte,count) - Shift byte by Count bits to the Right
|
||||
;Args = Byte to Shift
|
||||
;Y = Number of Bits to Rotate
|
||||
;Affects Y,N,Z,C
|
||||
;Returns: A = Shifted Byte
|
||||
SHIFTR: INY ;Pre-Increment Counter
|
||||
.SHIFLR DEY ;Decrement Counter
|
||||
BEQ .SHIFTX ;If Not Zero
|
||||
LSR ; Shift Byte to Right
|
||||
BNE .SHIFLR ; and Loop if Not 0
|
||||
RTS
|
||||
|
||||
;atoc(&s) - ASCII string TO Character
|
||||
@ -130,11 +178,11 @@ SHIFTR: LSR ;Shift Byte to Right
|
||||
; Y = Number of Digits
|
||||
ATOC: JSR SETSRC ;Initialize Source String
|
||||
STY TEMP0 ;Initialize Result
|
||||
ATOCL: LDA (SRCLO),Y ;Get Next Character
|
||||
.ATOCL LDA (SRCLO),Y ;Get Next Character
|
||||
CMP #$30 ;If Less Than '0'
|
||||
BCC ATOCX ; Exit
|
||||
BCC .ATOCX ; Exit
|
||||
CMP #$3A ;If Greater Than '9'
|
||||
BCS ATOCX ; Exit
|
||||
BCS .ATOCX ; Exit
|
||||
AND #$0F ;Convert to Binary Nybble
|
||||
STA TEMP1 ; and Save It
|
||||
LDA TEMP0 ;Load Result
|
||||
@ -145,8 +193,8 @@ ATOCL: LDA (SRCLO),Y ;Get Next Character
|
||||
ADC TEMP1 ;Add Saved Nybble
|
||||
STA TEMP0 ; and Store Result
|
||||
INY ;Increment Index
|
||||
BPL ATOCL ; and Loop
|
||||
ATOCX: LDA TEMP0 ;Load Result
|
||||
BPL .ATOCL ; and Loop
|
||||
.ATOCX LDA TEMP0 ;Load Result
|
||||
RTS ;And Return
|
||||
|
||||
;ctoa(n) - Character TO ASCII string
|
||||
@ -161,19 +209,19 @@ CTOA: JSR SETDST ;Initialize Source String
|
||||
LDY #0 ;Initialize Index into String
|
||||
JSR CUBCD ;Convert Accumulator to Unpacked BCD
|
||||
LDA TEMP2 ;Get MSB
|
||||
BEQ CTOA1 ;If Not Zero
|
||||
JSR CTOAN ; Convert Low Nybble
|
||||
CTOA1: LDA TEMP1 ;Get Low Byte
|
||||
BNE CTOA2 ;If Not Zero
|
||||
BEQ .CTOA1 ;If Not Zero
|
||||
JSR .CTOAN ; Convert Low Nybble
|
||||
.CTOA1 LDA TEMP1 ;Get Low Byte
|
||||
BNE .CTOA2 ;If Not Zero
|
||||
CMP TEMP2 ; and Hundreds
|
||||
BEQ CTOA3 ; not Zero
|
||||
CTOA2: JSR CTOAN ; Convert It
|
||||
CTOA3: LDA TEMP0 ;Get Low Byte
|
||||
JSR CTOAN ;and Convert Low Nybble
|
||||
BEQ .CTOA3 ; not Zero
|
||||
.CTOA2 JSR .CTOAN ; Convert It
|
||||
.CTOA3 LDA TEMP0 ;Get Low Byte
|
||||
JSR .CTOAN ;and Convert Low Nybble
|
||||
LDA #$00
|
||||
BEQ CTOAX ;Terminate String
|
||||
CTOAN: ORA #$30 ;Convert to ASCII digit
|
||||
CTOAX: STA (DSTLO),Y ;Store in String
|
||||
BEQ .CTOAX ;Terminate String
|
||||
.CTOAN ORA #$30 ;Convert to ASCII digit
|
||||
.CTOAX STA (DSTLO),Y ;Store in String
|
||||
INY ;and Increment Offset
|
||||
TYA ;Copy String Length to Accumulator
|
||||
RTS
|
||||
@ -207,23 +255,22 @@ UPBCD: LDA TEMP1 ;Get Low Byte
|
||||
; TEMP2 = Hundreds Digit
|
||||
;Returns: A = Hundreds Digit
|
||||
; X = 0
|
||||
CVBCD: STA TEMP0 ;Save Binary Value
|
||||
CVBCDT: LDA #0 ;Clear BCD Bytes
|
||||
STA TEMP1
|
||||
STA TEMP2
|
||||
LDX #8 ;Process 8 bits of Binary
|
||||
PHP ;Save Status Register
|
||||
SEI ;Disable Interupts
|
||||
SED ;Set Decimal Mode
|
||||
CVBCDL: ASL TEMP0 ;Shift High Bit into Carry
|
||||
LDA TEMP1 ;Add BCD Low Byte to Itself
|
||||
ADC TEMP1 ; Plus Bit Shifted out of Binary
|
||||
STA TEMP1 ; Effectively Multiplying It by 2
|
||||
LDA TEMP2 ;Add BCD MSB to Itself
|
||||
ADC TEMP2 ; Plus Bit Shifted out of Low Byte
|
||||
STA TEMP2 ; Effectively Multiplying It by 2
|
||||
DEX ;Decrement Counter and
|
||||
BNE CVBCDL ; Process Next Bit
|
||||
PLP ;Restore Status Register
|
||||
CVBCD: STA TEMP0 ;Save Binary Value
|
||||
CVBCDT: LDA #0 ;Clear BCD Bytes
|
||||
STA TEMP1
|
||||
STA TEMP2
|
||||
LDX #8 ;Process 8 bits of Binary
|
||||
PHP ;Save Status Register
|
||||
SEI ;Disable Interupts
|
||||
SED ;Set Decimal Mode
|
||||
.CVBCDL ASL TEMP0 ;Shift High Bit into Carry
|
||||
LDA TEMP1 ;Add BCD Low Byte to Itself
|
||||
ADC TEMP1 ; Plus Bit Shifted out of Binary
|
||||
STA TEMP1 ; Effectively Multiplying It by 2
|
||||
LDA TEMP2 ;Add BCD MSB to Itself
|
||||
ADC TEMP2 ; Plus Bit Shifted out of Low Byte
|
||||
STA TEMP2 ; Effectively Multiplying It by 2
|
||||
DEX ;Decrement Counter and
|
||||
BNE .CVBCDL ; Process Next Bit
|
||||
PLP ;Restore Status Register
|
||||
RTS
|
||||
|
||||
|
231
test/slibtest.c02
Normal file
231
test/slibtest.c02
Normal file
@ -0,0 +1,231 @@
|
||||
/**************************************************
|
||||
* TESTSLIB - Test Library stdlib.h02 for py65mon *
|
||||
**************************************************/
|
||||
|
||||
//Specify System Header using -H option
|
||||
#include <stddef.h02>
|
||||
#include <stdlib.h02>
|
||||
|
||||
char aa, yy, xx;
|
||||
|
||||
void prtcma(aa) {putchr(','); prbyte(aa);}
|
||||
void prtlin() {putstr(); newlin();}
|
||||
void prtok() {prtlin(" OK");}
|
||||
void prtopr(aa,yy,xx) {prbyte(aa); putchr(yy); prbyte(xx); putchr("=");}
|
||||
|
||||
main:
|
||||
|
||||
tstabs: //Test abs()
|
||||
char onum, anum, cnum;
|
||||
|
||||
putstr("ABS()");
|
||||
onum = 0;
|
||||
do { //test abs() positive numbers
|
||||
anum = abs(onum);
|
||||
if (onum <> anum) goto abserr;
|
||||
onum++;
|
||||
} while (onum < $80);
|
||||
do { //test abs() negative numbers
|
||||
anum = abs(onum);
|
||||
cnum = -onum;
|
||||
if (anum <> cnum) goto abserr;
|
||||
onum++;
|
||||
} while (onum);
|
||||
prtok();
|
||||
|
||||
tstmnx: //Test min() and max()
|
||||
char lnum, rnum, nnum, xnum;
|
||||
|
||||
putstr("MAX(), MIN()");
|
||||
lnum = 0; do {
|
||||
rnum = 0; do {
|
||||
xnum = max(lnum,rnum);
|
||||
nnum = min(lnum,rnum);
|
||||
if (lnum > rnum) {
|
||||
if (xnum <> lnum) maxerr();
|
||||
if (nnum <> rnum) minerr();
|
||||
} else {
|
||||
if (xnum <> rnum) maxerr();
|
||||
if (nnum <> lnum) minerr();
|
||||
}
|
||||
} while (rnum);
|
||||
} while (lnum);
|
||||
prtok();
|
||||
|
||||
tstmlt: //Test mult()
|
||||
char mltplr, mltpnd, acmlsb, acmmsb, acmlst;
|
||||
char prodct, ovrflw;
|
||||
|
||||
putstr("MULT()");
|
||||
mltplr = 1;
|
||||
do {
|
||||
if (!mltplr & $F) putchr('.');
|
||||
mltpnd = 1; acmlst = 0;
|
||||
acmlsb = 0; acmmsb = 0;
|
||||
do {
|
||||
acmlsb = acmlsb + mltplr;
|
||||
if (acmlsb<acmlst) acmmsb++;
|
||||
acmlst = acmlsb;
|
||||
prodct,ovrflw = mult(mltplr,mltpnd);
|
||||
if (prodct <> acmlsb) goto mlterr;
|
||||
mltpnd++;
|
||||
} while (mltpnd);
|
||||
mltplr++;
|
||||
} while (mltplr);
|
||||
prtok();
|
||||
|
||||
tstdiv: //Test div()
|
||||
char maxmpd, divdnd, divisr, quotnt;
|
||||
|
||||
putstr("DIV()");
|
||||
mltplr = 255;
|
||||
maxmpd = 1;
|
||||
drloop:
|
||||
mltpnd = 1;
|
||||
acmlsb = 0;
|
||||
ddloop:
|
||||
acmlsb = acmlsb + mltplr;
|
||||
prodct = mult(mltplr, mltpnd);
|
||||
quotnt = div(prodct, mltpnd);
|
||||
if (quotnt <> mltplr) goto derror;
|
||||
mltpnd++;
|
||||
if (mltpnd < maxmpd) goto ddloop;
|
||||
mltplr>>;
|
||||
maxmpd<<;
|
||||
if (mltplr <> 0) goto drloop;
|
||||
prtok();
|
||||
|
||||
tstrnd: //Test rand() and rands()
|
||||
char countr, rndnum, rndtbl[255];
|
||||
|
||||
putstr("RAND()");
|
||||
rands(1); //Seed Random Number Generator;
|
||||
|
||||
countr = 0;
|
||||
|
||||
riloop:
|
||||
rndtbl[countr] = 0;
|
||||
countr++;
|
||||
if (countr <> 0) goto riloop;
|
||||
|
||||
rnloop:
|
||||
rndnum = rand();
|
||||
if (rndtbl[rndnum] > 0) goto rnderr;
|
||||
rndtbl[rndnum] = $FF;
|
||||
countr++;
|
||||
if (countr < 255) goto rnloop;
|
||||
prtok();
|
||||
|
||||
tstros: //Test rotatl(), rotatr(), swap()
|
||||
char lbyte, rbyte, obyte, sbyte, tbyte, scount;
|
||||
|
||||
putstr("ROTATL(), SHIFTL()");
|
||||
obyte = 0;
|
||||
do {
|
||||
if (!obyte & $F) putchr('.');
|
||||
scount = 0; sbyte = obyte; tbyte = obyte;
|
||||
do {
|
||||
rbyte = rotatl(obyte, scount); if (rbyte <> tbyte) goto rtlerr;
|
||||
lbyte = shiftl(obyte, scount); if (lbyte <> sbyte) goto shlerr;
|
||||
sbyte<<;
|
||||
temp0 = tbyte; tbyte<<; if (temp0:-) tbyte++;
|
||||
scount++; if (scount == 8) scount = $F8;
|
||||
} while (scount);
|
||||
obyte ++;
|
||||
} while (obyte);
|
||||
prtok();
|
||||
|
||||
putstr("ROTATR(), SHIFTR()");
|
||||
obyte = 0;
|
||||
do {
|
||||
if (!obyte & $F) putchr('.');
|
||||
scount = 0; sbyte = obyte; tbyte = obyte;
|
||||
do {
|
||||
rbyte = rotatr(obyte, scount); if (rbyte <> tbyte) goto rtrerr;
|
||||
lbyte = shiftr(obyte, scount); if (lbyte <> sbyte) goto shrerr;
|
||||
sbyte>>;
|
||||
temp0 = tbyte; tbyte>>; if (temp0 & 1) tbyte = tbyte | $80;
|
||||
scount++; if (scount == 8) scount = $F8;
|
||||
} while (scount);
|
||||
obyte ++;
|
||||
} while (obyte);
|
||||
prtok();
|
||||
|
||||
putstr("SWAP()");
|
||||
lbyte=0; do {
|
||||
rbyte = 0; do {
|
||||
obyte = lbyte & $f0; obyte = rbyte & $0f + lbyte;
|
||||
tbyte = lbyte & $0f; tbyte = rbyte & $f0 + lbyte;
|
||||
sbyte = swap(obyte);
|
||||
if (sbyte <> tbyte) goto swperr;
|
||||
rbyte = rbyte + $11;
|
||||
} while (rbyte & $0f);
|
||||
} while (lbyte & $0f);
|
||||
prtok();
|
||||
|
||||
tstc2a: //Test ctoa();
|
||||
char srcchr, dstchr, tststr[4];
|
||||
|
||||
putstr("ATOC(), CTOA()");
|
||||
srcchr = 0; do {
|
||||
ctoa(srcchr, &tststr);
|
||||
dstchr = atoc(&tststr);
|
||||
if (srcchr <> dstchr) goto c2aerr;
|
||||
srcchr++;
|
||||
} while (srcchr);
|
||||
prtok();
|
||||
|
||||
goto exit;
|
||||
|
||||
abserr:
|
||||
putstr("ABS("); prbyte(onum); putstr(")="); prbyte(anum); prtcma(cnum); newlin();
|
||||
goto exit;
|
||||
|
||||
maxerr:
|
||||
putstr("MAX("); prbyte(lnum); prtcma(rnum); putstr(")="); prbyte(xnum); newlin();
|
||||
goto exit;
|
||||
|
||||
minerr:
|
||||
putstr("MIN("); prbyte(lnum); prtcma(rnum); putstr(")="); prbyte(nnum); newlin();
|
||||
goto exit;
|
||||
|
||||
mlterr:
|
||||
newlin(); prtopr(mltplr,'*',mltpnd); prbyte(prodct); prtcma(acmlsb); newlin();
|
||||
goto exit;
|
||||
|
||||
derror:
|
||||
newlin(); prtopr(divdnd,'/',divisr); prbyte(quotnt); prtcma(mltplr); newlin();
|
||||
goto exit;
|
||||
|
||||
rnderr:
|
||||
newlin(); putstr("RAND()="); prbyte(rndnum); prtcma(countr); newlin();
|
||||
goto exit;
|
||||
|
||||
rtlerr:
|
||||
newlin(); putstr("ROTATL("); prbyte(obyte); prtcma(scount); putstr(")=");
|
||||
prbyte(rbyte); prtcma(tbyte); newlin();
|
||||
goto exit;
|
||||
|
||||
rtrerr:
|
||||
newlin(); putstr("ROTATR("); prbyte(obyte); prtcma(scount); putstr(")=");
|
||||
prbyte(rbyte); prtcma(tbyte); newlin();
|
||||
goto exit;
|
||||
|
||||
shlerr:
|
||||
newlin(); putstr("SHIFTL("); prbyte(obyte); prtcma(scount); putstr(")=");
|
||||
prbyte(lbyte); prtcma(sbyte); newlin();
|
||||
goto exit;
|
||||
|
||||
shrerr:
|
||||
newlin(); putstr("SHIFTR("); prbyte(obyte); prtcma(scount); putstr(")=");
|
||||
prbyte(lbyte); prtcma(sbyte); newlin();
|
||||
goto exit;
|
||||
|
||||
swperr:
|
||||
newlin(); putstr("SWAP("); prbyte(obyte); putstr(")=");
|
||||
prbyte(sbyte); prtcma(tbyte); newlin();
|
||||
goto exit;
|
||||
|
||||
c2aerr:
|
||||
putstr("CTOA("); prbyte(srcchr); putstr(")="); prbyte(dstchr); newlin();
|
||||
goto exit;
|
220
test/testsl.c02
220
test/testsl.c02
@ -1,220 +0,0 @@
|
||||
/************************************************
|
||||
* TESTSL - Test Library stdlib.h02 for py65mon *
|
||||
************************************************/
|
||||
|
||||
//Specify System Header using -H option
|
||||
#include <stddef.h02>
|
||||
#include <stdlib.h02>
|
||||
|
||||
main:
|
||||
|
||||
tstabs: //Test abs()
|
||||
char onum, anum, cnum;
|
||||
|
||||
prchr('A');
|
||||
prchr('B');
|
||||
prchr('S');
|
||||
prchr(' ');
|
||||
|
||||
//test abs() positive numbers
|
||||
onum = 0;
|
||||
aploop:
|
||||
anum = abs(onum);
|
||||
if (onum <> anum) goto abserr;
|
||||
onum++;
|
||||
if (onum < $80) goto aploop;
|
||||
|
||||
//test abs() negative numbers
|
||||
anloop:
|
||||
anum = abs(onum);
|
||||
cnum = -onum;
|
||||
if (anum <> cnum) goto abserr;
|
||||
onum++;
|
||||
if (onum > $00) goto anloop;
|
||||
prchr('O');
|
||||
prchr('K');
|
||||
newlin();
|
||||
|
||||
tstmlt: //Test mult()
|
||||
char mltplr, mltpnd, acmlsb, acmmsb, acmlst;
|
||||
char prodct, ovrflw;
|
||||
|
||||
mltplr = 1;
|
||||
mrloop:
|
||||
prbyte(mltplr);
|
||||
mltpnd = 1; acmlst = 0;
|
||||
acmlsb = 0; acmmsb = 0;
|
||||
mdloop:
|
||||
acmlsb = acmlsb + mltplr;
|
||||
if (acmlsb<acmlst) acmmsb++;
|
||||
acmlst = acmlsb;
|
||||
prodct,ovrflw = mult(mltplr,mltpnd);
|
||||
if (prodct <> acmlsb) goto merror;
|
||||
//if (ovrflw <> acmmsb) goto merror;
|
||||
mltpnd++;
|
||||
if (mltpnd > 0) goto mdloop;
|
||||
mltplr++;
|
||||
if (mltplr > 0) goto mrloop;
|
||||
newlin();
|
||||
prchr('M');
|
||||
prchr('U');
|
||||
prchr('L');
|
||||
prchr('T');
|
||||
prchr(' ');
|
||||
prchr('O');
|
||||
prchr('K');
|
||||
newlin();
|
||||
|
||||
tstdiv: //Test div()
|
||||
char maxmpd, divdnd, divisr, quotnt;
|
||||
|
||||
mltplr = 255;
|
||||
maxmpd = 1;
|
||||
drloop:
|
||||
prbyte(mltplr);
|
||||
mltpnd = 1;
|
||||
acmlsb = 0;
|
||||
ddloop:
|
||||
prbyte(mltpnd);
|
||||
acmlsb = acmlsb + mltplr;
|
||||
prodct = mult(mltplr, mltpnd);
|
||||
quotnt = div(prodct, mltpnd);
|
||||
if (quotnt <> mltplr) goto derror;
|
||||
mltpnd++;
|
||||
if (mltpnd < maxmpd) goto ddloop;
|
||||
newlin();
|
||||
mltplr>>;
|
||||
maxmpd<<;
|
||||
if (mltplr <> 0) goto drloop;
|
||||
newlin();
|
||||
prchr('D');
|
||||
prchr('I');
|
||||
prchr('V');
|
||||
prchr(' ');
|
||||
prchr('O');
|
||||
prchr('K');
|
||||
newlin();
|
||||
|
||||
|
||||
tstrnd: //Test rand() and rands()
|
||||
char countr, rndnum, rndtbl[255];
|
||||
|
||||
rands(1); //Seed Random Number Generator;
|
||||
|
||||
countr = 0;
|
||||
|
||||
riloop:
|
||||
rndtbl[countr] = 0;
|
||||
countr++;
|
||||
if (countr <> 0) goto riloop;
|
||||
|
||||
rnloop:
|
||||
rndnum = rand();
|
||||
if (rndtbl[rndnum] > 0) goto rnderr;
|
||||
rndtbl[rndnum] = $FF;
|
||||
prbyte(rndnum);
|
||||
prchr(' ');
|
||||
countr++;
|
||||
if (countr < 255) goto rnloop;
|
||||
newlin();
|
||||
prchr('R');
|
||||
prchr('A');
|
||||
prchr('N');
|
||||
prchr('D');
|
||||
prchr(' ');
|
||||
prchr('O');
|
||||
prchr('K');
|
||||
newlin();
|
||||
|
||||
tstc2a: //Test ctoa();
|
||||
char srcchr, dstchr, tststr[4];
|
||||
|
||||
srcchr = 0;
|
||||
caloop:
|
||||
prbyte(srcchr);
|
||||
prchr(' ');
|
||||
ctoa(srcchr, &tststr);
|
||||
dstchr = atoc(&tststr);
|
||||
if (srcchr <> dstchr) goto c2aerr;
|
||||
srcchr++;
|
||||
if (srcchr <> 0) goto caloop;
|
||||
newlin();
|
||||
prchr('C');
|
||||
prchr('T');
|
||||
prchr('O');
|
||||
prchr('A');
|
||||
prchr(' ');
|
||||
prchr('O');
|
||||
prchr('K');
|
||||
newlin();
|
||||
|
||||
|
||||
goto exit;
|
||||
|
||||
abserr:
|
||||
prchr('A');
|
||||
prchr('B');
|
||||
prchr('S');
|
||||
prchr('(');
|
||||
prbyte(onum);
|
||||
prchr(')');
|
||||
prchr('=');
|
||||
prbyte(anum);
|
||||
prchr(',');
|
||||
prbyte(cnum);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
merror:
|
||||
newlin();
|
||||
prbyte(mltplr);
|
||||
prchr('*');
|
||||
prbyte(mltpnd);
|
||||
prchr('=');
|
||||
//prbyte(ovrflw);
|
||||
prbyte(prodct);
|
||||
prchr(',');
|
||||
//prbyte(acmmsb);
|
||||
prbyte(acmlsb);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
derror:
|
||||
newlin();
|
||||
prbyte(divdnd);
|
||||
prchr('/');
|
||||
prbyte(divisr);
|
||||
prchr('=');
|
||||
prbyte(quotnt);
|
||||
prchr(',');
|
||||
prbyte(mltplr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
rnderr:
|
||||
prchr('R');
|
||||
prchr('A');
|
||||
prchr('N');
|
||||
prchr('D');
|
||||
prchr('(');
|
||||
prchr(')');
|
||||
prchr('=');
|
||||
prbyte(rndnum);
|
||||
prchr(',');
|
||||
prbyte(countr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
c2aerr:
|
||||
prchr('C');
|
||||
prchr('T');
|
||||
prchr('O');
|
||||
prchr('A');
|
||||
prchr('(');
|
||||
prbyte(srcchr);
|
||||
prchr(')');
|
||||
prchr('=');
|
||||
prbyte(dstchr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
@ -1,199 +0,0 @@
|
||||
/**************************************************
|
||||
* TESTSLIB - Test Library stdlib.h02 for py65mon *
|
||||
**************************************************/
|
||||
|
||||
//Specify System Header using -H option
|
||||
#include <stddef.h02>
|
||||
#include <stdlib.h02>
|
||||
|
||||
void prtcma() {putchr(',');}
|
||||
void prtlin() {putstr(); newlin();}
|
||||
void prtok() {prtlin(" OK");}
|
||||
|
||||
main:
|
||||
|
||||
//goto tstcvb;
|
||||
|
||||
tstabs: //Test abs()
|
||||
char onum, anum, cnum;
|
||||
putstr("ABS()");
|
||||
|
||||
//test abs() positive numbers
|
||||
onum = 0;
|
||||
aploop:
|
||||
anum = abs(onum);
|
||||
if (onum <> anum) goto abserr;
|
||||
onum++;
|
||||
if (onum < $80) goto aploop;
|
||||
|
||||
//test abs() negative numbers
|
||||
anloop:
|
||||
anum = abs(onum);
|
||||
cnum = -onum;
|
||||
if (anum <> cnum) goto abserr;
|
||||
onum++;
|
||||
if (onum > $00) goto anloop;
|
||||
prtok();
|
||||
|
||||
tstmlt: //Test mult()
|
||||
char mltplr, mltpnd, acmlsb, acmmsb, acmlst;
|
||||
char prodct, ovrflw;
|
||||
|
||||
putstr("MULT()");
|
||||
mltplr = 1;
|
||||
mrloop:
|
||||
mltpnd = 1; acmlst = 0;
|
||||
acmlsb = 0; acmmsb = 0;
|
||||
mdloop:
|
||||
acmlsb = acmlsb + mltplr;
|
||||
if (acmlsb<acmlst) acmmsb++;
|
||||
acmlst = acmlsb;
|
||||
prodct,ovrflw = mult(mltplr,mltpnd);
|
||||
if (prodct <> acmlsb) goto merror;
|
||||
mltpnd++;
|
||||
if (mltpnd > 0) goto mdloop;
|
||||
mltplr++;
|
||||
if (mltplr > 0) goto mrloop;
|
||||
prtok();
|
||||
|
||||
tstdiv: //Test div()
|
||||
char maxmpd, divdnd, divisr, quotnt;
|
||||
|
||||
putstr("DIV()");
|
||||
mltplr = 255;
|
||||
maxmpd = 1;
|
||||
drloop:
|
||||
mltpnd = 1;
|
||||
acmlsb = 0;
|
||||
ddloop:
|
||||
acmlsb = acmlsb + mltplr;
|
||||
prodct = mult(mltplr, mltpnd);
|
||||
quotnt = div(prodct, mltpnd);
|
||||
if (quotnt <> mltplr) goto derror;
|
||||
mltpnd++;
|
||||
if (mltpnd < maxmpd) goto ddloop;
|
||||
mltplr>>;
|
||||
maxmpd<<;
|
||||
if (mltplr <> 0) goto drloop;
|
||||
prtok();
|
||||
|
||||
tstrnd: //Test rand() and rands()
|
||||
char countr, rndnum, rndtbl[255];
|
||||
|
||||
putstr("RAND()");
|
||||
rands(1); //Seed Random Number Generator;
|
||||
|
||||
countr = 0;
|
||||
|
||||
riloop:
|
||||
rndtbl[countr] = 0;
|
||||
countr++;
|
||||
if (countr <> 0) goto riloop;
|
||||
|
||||
rnloop:
|
||||
rndnum = rand();
|
||||
if (rndtbl[rndnum] > 0) goto rnderr;
|
||||
rndtbl[rndnum] = $FF;
|
||||
countr++;
|
||||
if (countr < 255) goto rnloop;
|
||||
prtok();
|
||||
|
||||
tstcvb: //Test cvbcd()
|
||||
char cvbchr,cvblo,cvbhi;
|
||||
|
||||
goto tstc2a;
|
||||
putstr("CVBCD()");
|
||||
cvbchr = 0; cvblo = 0; cvbhi = 0;
|
||||
cvloop:
|
||||
cvbcd(cvbchr);
|
||||
getchr();
|
||||
if (temp1 <> cvblo or temp2 <> cvbhi) goto cvberr;
|
||||
cvblo++;
|
||||
if (cvblo & $0f > 9) {
|
||||
cvblo = cvblo & $f0 + $10;
|
||||
if (cvblo >= $a0) {
|
||||
cvblo = cvblo & $0f;
|
||||
cvbhi++;
|
||||
}
|
||||
}
|
||||
cvbchr++;
|
||||
if (cvbchr) goto cvloop;
|
||||
prtok();
|
||||
|
||||
tstc2a: //Test ctoa();
|
||||
char srcchr, dstchr, tststr[4];
|
||||
|
||||
putstr("CTOA()");
|
||||
srcchr = 0;
|
||||
caloop:
|
||||
ctoa(srcchr, &tststr);
|
||||
dstchr = atoc(&tststr);
|
||||
if (srcchr <> dstchr) goto c2aerr;
|
||||
srcchr++;
|
||||
if (srcchr <> 0) goto caloop;
|
||||
prtok();
|
||||
|
||||
goto exit;
|
||||
|
||||
abserr:
|
||||
putstr("ABS(");
|
||||
prbyte(onum);
|
||||
putchr(')');
|
||||
putchr('=');
|
||||
prbyte(anum);
|
||||
putchr(',');
|
||||
prbyte(cnum);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
merror:
|
||||
newlin();
|
||||
prbyte(mltplr);
|
||||
putchr('*');
|
||||
prbyte(mltpnd);
|
||||
putchr('=');
|
||||
//prbyte(ovrflw);
|
||||
prbyte(prodct);
|
||||
putchr(',');
|
||||
//prbyte(acmmsb);
|
||||
prbyte(acmlsb);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
derror:
|
||||
newlin();
|
||||
prbyte(divdnd);
|
||||
putchr('/');
|
||||
prbyte(divisr);
|
||||
putchr('=');
|
||||
prbyte(quotnt);
|
||||
putchr(',');
|
||||
prbyte(mltplr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
rnderr:
|
||||
putstr("RAND()=");
|
||||
prbyte(rndnum);
|
||||
putchr(',');
|
||||
prbyte(countr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
cvberr:
|
||||
putstr(" !CVBCD(");
|
||||
prbyte(cvbchr);
|
||||
putstr(")=$");
|
||||
prbyte(TEMP2);
|
||||
prbyte(TEMP1);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
||||
c2aerr:
|
||||
putstr(" !CTOA(");
|
||||
prbyte(srcchr);
|
||||
putstr(")=");
|
||||
prbyte(dstchr);
|
||||
newlin();
|
||||
goto exit;
|
||||
|
Loading…
x
Reference in New Issue
Block a user