2020-10-16 02:58:12 +00:00
|
|
|
; C02 module intlib.h02 assembly language subroutines
|
2022-04-04 23:47:16 +00:00
|
|
|
; Requires external zero page words DSTPTR, SRCPTR,
|
|
|
|
; external bytes TEMP0, TEMP1, TEMP2, and TEMP3, and
|
|
|
|
; external words INTACC, INTARG, and INTOVR.
|
|
|
|
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2020-10-06 16:30:20 +00:00
|
|
|
SUBROUTINE INTLIB
|
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;iacc(i) - Set Integer Accumulator to i
|
|
|
|
;Args: Y,X = Argument
|
|
|
|
;Sets: INTACC = Y,X
|
|
|
|
IACC: STX INTACC
|
|
|
|
STY INTACC+1
|
|
|
|
RTS
|
|
|
|
|
|
|
|
;Set Integer Argument
|
|
|
|
.SETARG STX INTARG
|
|
|
|
STY INTARG+1
|
|
|
|
RTS
|
|
|
|
|
|
|
|
;Clear Integer Overflow
|
|
|
|
;Sets: INTOVR = 0
|
|
|
|
;Returns A = 0
|
|
|
|
.CLROVR LDA #0
|
|
|
|
STA INTOVR
|
|
|
|
STA INTOVR+1
|
|
|
|
RTS
|
|
|
|
|
|
|
|
;iabs(i) - Get Integer ABSolute Value
|
2019-05-27 21:12:10 +00:00
|
|
|
;Args: Y,X = Integer to get Absolute Value Of
|
|
|
|
;Sets: TEMP1, TEMP2
|
|
|
|
;Affects: C, N, Z
|
|
|
|
;Returns: A = Absolute Value of Argument
|
|
|
|
IABS: CPY #$80 ;If Negative (High Bit Set)
|
2020-10-06 16:30:20 +00:00
|
|
|
BCC .RETURN ; Carry will Already be Set
|
2019-05-27 21:12:10 +00:00
|
|
|
JSR SAVRXY ; Copy LSB, MSB to TEMP1. TEMP2
|
|
|
|
LDA #0 ; Subtract LSB
|
|
|
|
SBC TEMP1 ; from 0
|
|
|
|
TAX ; and Copy to X Register
|
|
|
|
LDA #0 ; Subtract MSB
|
|
|
|
SBC TEMP2 ; from 0
|
|
|
|
TAY ; and Copy to Y Register
|
2020-10-06 16:30:20 +00:00
|
|
|
.RETURN RTS
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2020-09-08 15:51:30 +00:00
|
|
|
;imax(i) - Get MAXimum of Two Integers
|
|
|
|
;Args: Y,X = Second Integer
|
2022-04-04 23:47:16 +00:00
|
|
|
;Uses: INTACC = First Integer
|
2019-05-27 21:12:10 +00:00
|
|
|
;Affects: N,Z,C
|
2020-09-08 15:51:30 +00:00
|
|
|
;Returns: Y,X = Larger of the Two Arguments
|
2022-04-04 23:47:16 +00:00
|
|
|
IMAX: CPY INTACC+1 ;If Y < INTACC MSB
|
|
|
|
BCC .GETACC ; Return INTACC
|
|
|
|
CPX INTACC ;IF X >= INTACC LSB
|
|
|
|
BCS .IMSET ; Set INTACC to and Return Argument
|
|
|
|
.GETACC LDX INTACC ;Return Integer Accumulator
|
|
|
|
LDY INTACC+1
|
|
|
|
RTS
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2020-09-08 15:51:30 +00:00
|
|
|
;imin(i) - Get MINimum of Two Integers
|
|
|
|
;Args: Y,X = Second Integer
|
2022-04-04 23:47:16 +00:00
|
|
|
;Uses: INTACC = First Integer
|
|
|
|
;Sets: IINTACC = Result
|
2019-05-27 21:12:10 +00:00
|
|
|
;Affects: N,Z,C
|
2020-09-08 15:51:30 +00:00
|
|
|
;Returns: Y,X = Larger of the Two Arguments
|
2022-04-04 23:47:16 +00:00
|
|
|
IMIN: CPY INTACC+1 ;If Y < INTACC+1
|
2020-10-06 16:30:20 +00:00
|
|
|
BCC .RETURN ; Return Argument
|
2022-04-04 23:47:16 +00:00
|
|
|
BNE .GETACC ;If Y > INTACC+1
|
|
|
|
CPX INTACC ;or X >= INTACC
|
|
|
|
BCS .GETACC ; Return INTACC
|
|
|
|
.IMSET JMP IACC ;Else Set INTACC to and Return Argument
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;iaddc(c,i) - Integer ADD Char c to int i
|
|
|
|
IADDC: JSR IACC ;Store Integer in Accumulator
|
|
|
|
LDY #0 ;Set Argument MSB to 0
|
2020-09-08 15:51:30 +00:00
|
|
|
TAX ;Copy Byte to LSB and drop into IADD
|
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;iand(d) - Integer ADD g + d
|
2019-05-27 21:12:10 +00:00
|
|
|
;Args: Y,X = Addend
|
2022-04-04 23:47:16 +00:00
|
|
|
;Requires: IACC(g) - Augend
|
|
|
|
;Sets: INTACC = Result
|
|
|
|
;Affects: Z
|
|
|
|
;Returns: Y,X = Sum
|
|
|
|
;IAND: TXA ;AND Argument LSB
|
|
|
|
; AND IACC ;with Accumulator LSB
|
|
|
|
; TAX
|
|
|
|
; TYA ;AND Argument MSB
|
|
|
|
; AND IACC+1 ;with Accumulator MSB
|
|
|
|
; TAY
|
|
|
|
; JMP IACC ;Set INTACC to And Return Result
|
|
|
|
|
|
|
|
;iadd(d) - Integer ADD g + d
|
|
|
|
;Args: Y,X = Addend
|
|
|
|
;Requires: IACC(g) - Augend
|
|
|
|
;Sets: INTACC = Sum
|
|
|
|
;Affects: Z
|
|
|
|
;Returns: A,C = Carry
|
2020-10-06 16:30:20 +00:00
|
|
|
; Y,X = Sum
|
2019-05-27 21:12:10 +00:00
|
|
|
; N = Sign of Result
|
2022-04-04 23:47:16 +00:00
|
|
|
IADD: CLC ;Clear Carry for Addition
|
|
|
|
TXA ;Add Addend LSB
|
|
|
|
ADC INTACC ;to Augend LSB
|
|
|
|
TAX ;and Copy to X
|
|
|
|
TYA ;Add Addend MSB
|
|
|
|
ADC INTACC+1 ;to Augebd MSB
|
|
|
|
TAY ;and Copy to Y
|
|
|
|
PHP ;Save Result Flags
|
|
|
|
LDA #0 ;Clear CHR Result to 0
|
|
|
|
STA INTOVR+1 ; and Clear Overflow MSB
|
|
|
|
ROL ;Rotate Carry Flag into CHR Result
|
|
|
|
STA INTOVR ; and store in INTOVR
|
|
|
|
PLP ;Restore Result Flags
|
|
|
|
JMP IACC ;Set INTACC to And Return Result
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;ineg(i) - Integer NEGate int i
|
|
|
|
;Args: Y,X = Integer to Negate
|
|
|
|
;Sets: INTACC = Result
|
|
|
|
; INTARG = Argument
|
|
|
|
;Returns: Y,X = Negated Integer
|
|
|
|
; N = Sign of Result
|
|
|
|
INEG: LDA #0 ;Set Minuend to Zero
|
|
|
|
STA INTACC
|
|
|
|
STA INTACC+1
|
|
|
|
|
|
|
|
;isub(s) - Integer SUBtract m - s
|
2019-05-27 21:12:10 +00:00
|
|
|
;Args: Y,X = Subtrahend
|
2022-04-04 23:47:16 +00:00
|
|
|
;Requires: IACC(m) - Minuend
|
|
|
|
;Sets: INTACC = Difference
|
|
|
|
; INTARG = Subtrahend
|
|
|
|
;Affects: Z
|
|
|
|
;Returns: A,C = Carry
|
2020-10-06 16:30:20 +00:00
|
|
|
; Y,X = Difference
|
2019-05-27 21:12:10 +00:00
|
|
|
; N = Sign of Result
|
2022-04-04 23:47:16 +00:00
|
|
|
ISUB: JSR .SETARG ;Store Subtrahend in INTARG
|
|
|
|
SEC ;Set Carry for Subtraction
|
|
|
|
LDA INTACC ;Load Minuend LSB
|
|
|
|
SBC INTARG ;Subtract Subtrahend LSB
|
|
|
|
TAX ;Copy Difference LSB to X
|
|
|
|
LDA INTACC+1 ;Load Minuend MSB
|
|
|
|
SBC INTARG+1 ;Subtract Subtrahend MSB
|
|
|
|
TAY ;Copy Difference MSB to Y
|
|
|
|
PHP ;Save Result Flags
|
|
|
|
LDA #0 ;Set Overflow Byte to 0
|
|
|
|
SBC #0 ;and Subtract Carry
|
|
|
|
PLP ;Restore Result Flags
|
|
|
|
JMP IACC ;Set INTACC to And Return Result
|
|
|
|
|
|
|
|
;imultc(c,m) - Multiply Int m by Char c
|
|
|
|
;Args: A - Multiplicand
|
|
|
|
; Y,X - Multiplier
|
|
|
|
;Sets: INTACC - Product MSB, LSB
|
|
|
|
IMULTC: STA INTACC ;Set Integer Accumulator to int(A)
|
|
|
|
LDA #0
|
|
|
|
STA INTACC+1 ;and execute IMULT
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;imult(m) = MULTiply Integer n * Integer m
|
|
|
|
;Args: Y,X = Multiplier
|
|
|
|
;Uses: INTACC = Multiplicand
|
|
|
|
;Sets: INTACC = Product MSB, LSB
|
|
|
|
;Sets: INTOVR = Product MSB, LSB
|
|
|
|
;Destroys: TEMP0,TEMP1,TEMP2,TEMP3
|
|
|
|
;Affects: C,Z,N
|
2020-10-06 16:30:20 +00:00
|
|
|
;Returns: A,Y,X = 24 Bit Product
|
2022-04-04 23:47:16 +00:00
|
|
|
IMULT: JSR .SETARG ;Save Multiplier
|
|
|
|
LDY #0
|
|
|
|
STY INTOVR ;Clear Upper Bits of Product
|
|
|
|
STY INTOVR+1
|
2020-09-08 15:51:30 +00:00
|
|
|
LDX #16 ;Rotate Through 16 Bits
|
2022-04-04 23:47:16 +00:00
|
|
|
.MSHFTR LSR INTARG+1 ;Divide Multiplier by 2
|
|
|
|
ROR INTARG
|
2020-10-06 16:30:20 +00:00
|
|
|
BCC .MROTR ;If Shifted out Bit is 1
|
2022-04-04 23:47:16 +00:00
|
|
|
LDA INTACC ; Add Multiplicand
|
2020-09-08 15:51:30 +00:00
|
|
|
CLC ; to Upper Half of Product
|
2022-04-04 23:47:16 +00:00
|
|
|
ADC INTOVR
|
|
|
|
STA INTOVR
|
|
|
|
LDA INTOVR+1
|
|
|
|
ADC INTACC+1
|
|
|
|
STA INTOVR+1
|
|
|
|
.MROTR ROR INTOVR+1
|
|
|
|
ROR INTOVR
|
|
|
|
ROR TEMP1
|
2020-09-08 15:51:30 +00:00
|
|
|
ROR TEMP0
|
|
|
|
DEX ;Decrement Counter
|
2020-10-06 16:30:20 +00:00
|
|
|
BNE .MSHFTR ;and Process Next Bit
|
2022-04-04 23:47:16 +00:00
|
|
|
LDA INTOVR ;Get Bits 16-24 of Result
|
|
|
|
LDY TEMP1 ;Get Bits 8-15 of Result
|
|
|
|
LDX TEMP0 ;Get Bits 0-7 of Result
|
|
|
|
JMP IACC ;Store Y,X in INTACC and Return in Y,X
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;imod(d) - Integer MODulus d % s
|
2020-09-08 15:51:30 +00:00
|
|
|
;Args: Y,X - Divisor
|
2022-04-04 23:47:16 +00:00
|
|
|
;Requires: IACC(d) = Dividend
|
|
|
|
;Sets: INTARG = Divisor
|
|
|
|
; INTACC, INTOVR = Modulus
|
2020-09-08 15:51:30 +00:00
|
|
|
;Affects: A,C,Z,N
|
2022-04-04 23:47:16 +00:00
|
|
|
;Returns: Y,X = 16 Bit Modulus
|
|
|
|
IMOD: JSR IDIV ;Do Division
|
|
|
|
LDX INTOVR ;get Remainder
|
|
|
|
LDY INTOVR+1 l
|
|
|
|
JMP IACC ;Store in INTACC and Return in Y,X
|
2020-10-06 16:30:20 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;idiv(s) - Integer DIVide d / s
|
2020-10-06 16:30:20 +00:00
|
|
|
;Args: Y,X - Divisor
|
2022-04-04 23:47:16 +00:00
|
|
|
;Requires: IACC(d) = Dividend
|
|
|
|
;Sets: INTARG = Divisor
|
|
|
|
; INTACC = Quotient
|
|
|
|
; INTOVR = Remainder
|
2020-10-06 16:30:20 +00:00
|
|
|
;Affects: A,C,Z,N
|
2022-04-04 23:47:16 +00:00
|
|
|
;Returns: Y,X = 16 Bit Quotient
|
|
|
|
IDIV: JSR .SETARG ;Save Divisor
|
|
|
|
LDY #0
|
|
|
|
STY INTOVR
|
|
|
|
STY INTOVR+1
|
2020-09-08 15:51:30 +00:00
|
|
|
LDX #16 ;repeat for each bit: ...
|
2022-04-04 23:47:16 +00:00
|
|
|
.IDLOOP ASL INTACC ;dividend lb & hb*2, msb -> Carry
|
|
|
|
ROL INTACC+1
|
|
|
|
ROL INTOVR ;remainder lb & hb * 2 + msb from carry
|
|
|
|
ROL INTOVR+1
|
|
|
|
LDA INTOVR
|
2020-09-08 15:51:30 +00:00
|
|
|
SEC
|
2022-04-04 23:47:16 +00:00
|
|
|
SBC INTARG ;subtract divisor to see if it fits in
|
2020-09-08 15:51:30 +00:00
|
|
|
TAY ;lb result -> Y, for we may need it later
|
2022-04-04 23:47:16 +00:00
|
|
|
LDA INTOVR+1
|
|
|
|
SBC INTARG+1
|
2020-10-06 16:30:20 +00:00
|
|
|
BCC .IDSKIP ;if carry=0 then divisor didn't fit in yet
|
2022-04-04 23:47:16 +00:00
|
|
|
STA INTOVR+1 ;else save substraction result as new remainder,
|
|
|
|
STY INTOVR
|
|
|
|
INC INTACC ;and INCrement result cause divisor fit in 1 times
|
2020-10-06 16:30:20 +00:00
|
|
|
.IDSKIP DEX
|
|
|
|
BNE .IDLOOP
|
2022-04-04 23:47:16 +00:00
|
|
|
JMP .GETACC ;Return Integer Accumulator
|
2019-05-27 21:12:10 +00:00
|
|
|
|
|
|
|
;ishftl(n,i) - Shift Integer i to the Left n Bits
|
2022-04-04 23:47:16 +00:00
|
|
|
;Args: A = Number of Bits to Shift
|
|
|
|
; Y,X = Integer Value to Shift
|
|
|
|
;Sets: INTACC = Bits 0 to 15 of Result
|
|
|
|
; INTOVR = Bits 16 to 31 of Result
|
|
|
|
;Sets: INTACC = Shifted Intger
|
|
|
|
;Affects: N,Z,C
|
|
|
|
;Returns: A = LSB of Underflow
|
2020-10-06 16:30:20 +00:00
|
|
|
; Y,X = Shifted Integer
|
2022-04-04 23:47:16 +00:00
|
|
|
ISHFTL: JSR IACC ;Save Argument in INTACC
|
|
|
|
LDX #0 ;Clear Overflow
|
|
|
|
STX INTOVR
|
|
|
|
STX INTOVR
|
|
|
|
TAX ;Set Counter to Number of Bits
|
|
|
|
BEQ .LSDONE ;If Zero, Return 0
|
|
|
|
.LSLOOP ASL INTACC ;Shift Bits 0-7 to Left
|
|
|
|
ROL INTACC+1 ;Rotate Bits 8-15 to Left
|
|
|
|
ROL INTOVR ;Rotate Bits 16-23 to Left
|
|
|
|
ROL INTOVR+1 ;Rotate Bits 24-31 to Left
|
|
|
|
DEX ;Decrement Counter
|
2020-10-06 16:30:20 +00:00
|
|
|
BNE .LSLOOP ; and Loop if Not 0
|
2022-04-04 23:47:16 +00:00
|
|
|
LDA INTOVR ;Return Bits 16-23 in A
|
|
|
|
.LSDONE JMP .GETACC ;and Bits 0-15 in Y,X
|
2019-05-27 21:12:10 +00:00
|
|
|
|
|
|
|
;ishftr(n,i) - Shift Integer i to the Right n Bits
|
2022-04-04 23:47:16 +00:00
|
|
|
;Args: A = Number of Bits to Shift
|
|
|
|
; Y,X = Integer Value to Shift
|
|
|
|
;Sets: INTACC = Bits 0 to 15 of Result
|
|
|
|
; INTOVR = Bits -1 to -16 of Result
|
|
|
|
;Sets: INTACC = Shifted Intger
|
|
|
|
;Affects: N,Z,C
|
|
|
|
;Returns: A = MSB of Underflow
|
|
|
|
; Y,X = Shifted Result
|
|
|
|
ISHFTR: JSR IACC ;Save Argument in INTACC
|
|
|
|
LDX #0 ;Clear Overflow
|
|
|
|
STX INTOVR
|
|
|
|
STX INTOVR
|
|
|
|
TAX ;Set Counter to Number of Bits
|
|
|
|
BEQ .RSDONE ;If Zero, Return Argument
|
|
|
|
.RSLOOP LSR INTACC+1 ;Shift MSB to Right
|
|
|
|
ROR INTACC ;Rotate LSB to Right
|
|
|
|
ROR INTOVR+1 ;Rotate Underflow MSB
|
|
|
|
ROR INTOVR ;Rotate Underflow LSB
|
|
|
|
DEX ;Decrement Counter
|
2020-10-06 16:30:20 +00:00
|
|
|
BNE .RSLOOP ; and Loop if Not 0
|
2022-04-04 23:47:16 +00:00
|
|
|
LDA INTOVR+1 ;Return Underflow MSB in A
|
|
|
|
.RSDONE JMP .GETACC ;and Result in Y,X
|
2019-05-27 21:12:10 +00:00
|
|
|
|
|
|
|
;atoi(&s) - ASCII string TO Integer
|
|
|
|
;Args: Y,X = Address of String to Convert
|
2022-04-04 23:47:16 +00:00
|
|
|
;Sets: INTACC = Integer Value
|
|
|
|
;Affects: TEMP0,TEMP1,TEMP2
|
2019-05-27 21:12:10 +00:00
|
|
|
;Returns: A = Number of Digits
|
|
|
|
; Y,X = Integer Value
|
|
|
|
ATOI: JSR SETSRC ;Initialize Source String
|
|
|
|
STY TEMP1 ;Initialize Result
|
|
|
|
STY TEMP2
|
2022-04-04 23:47:16 +00:00
|
|
|
.AILOOP LDA (SRCPTR),Y ;Get Next Character
|
2019-05-27 21:12:10 +00:00
|
|
|
CMP #$30 ;If Less Than '0'
|
2020-10-06 16:30:20 +00:00
|
|
|
BCC .AIDONE ; Exit
|
2019-05-27 21:12:10 +00:00
|
|
|
CMP #$3A ;If Greater Than '9'
|
2020-10-06 16:30:20 +00:00
|
|
|
BCS .AIDONE ; Exit
|
2019-05-27 21:12:10 +00:00
|
|
|
AND #$0F ;Convert to Binary Nybble
|
|
|
|
STA TEMP0 ; and Save It
|
|
|
|
LDA TEMP1 ;Load Result
|
|
|
|
LDX TEMP2
|
|
|
|
ASL TEMP1 ;Multiply by 5 by
|
|
|
|
ROL TEMP2
|
|
|
|
ASL TEMP1 ; Multiplying by 4
|
|
|
|
ROL TEMP2
|
|
|
|
CLC ; And Adding Itself
|
|
|
|
ADC TEMP1
|
|
|
|
STA TEMP1
|
|
|
|
TXA
|
|
|
|
ADC TEMP2
|
|
|
|
STA TEMP2
|
|
|
|
ASL TEMP1 ;Multiply that by 2
|
|
|
|
ROL TEMP2
|
|
|
|
LDA TEMP0 ;Get Saved Nybble
|
|
|
|
CLC ;and Add to Result
|
|
|
|
ADC TEMP1 ;Add Saved Nybble
|
|
|
|
STA TEMP1 ; and Store Result
|
|
|
|
LDA #0
|
|
|
|
ADC TEMP2
|
|
|
|
STA TEMP2
|
|
|
|
INY ;Increment Index
|
2020-10-06 16:30:20 +00:00
|
|
|
BPL .AILOOP ; and Loop
|
|
|
|
.AIDONE TYA ;Return Number of Digits
|
2022-04-04 23:47:16 +00:00
|
|
|
.RESRXY JSR RESRXY ;and Integer Value
|
|
|
|
JMP IACC
|
2019-05-27 21:12:10 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;itoa(&d) - Integer TO ASCII string
|
|
|
|
;Args: Y,X = Address of Destination String
|
|
|
|
;Uses: INTACC = Integer to Convert
|
2020-10-16 02:58:12 +00:00
|
|
|
;Uses: DSTPTR = Destination String
|
2020-10-06 16:30:20 +00:00
|
|
|
;Affects: X
|
2019-05-27 21:12:10 +00:00
|
|
|
;Returns: A,Y = Length of String
|
2022-04-04 23:47:16 +00:00
|
|
|
ITOA: JSR SETDST ;Store String Pointer Agrumenr
|
|
|
|
JSR .GETACC ;Load INTACC
|
|
|
|
JSR CVIBCD ;Convert Integer to Packed BCD
|
2019-05-27 21:12:10 +00:00
|
|
|
LDY #0 ;Initialize Index into String
|
|
|
|
STY TEMP3
|
2020-10-06 16:30:20 +00:00
|
|
|
.ITOAA LDY #4 ;Set Initial Digit Number
|
|
|
|
.IAZERO JSR UPBCDI ;Unpack Digit Y
|
|
|
|
BNE .IASKIP ;If Zero
|
2020-09-08 15:51:30 +00:00
|
|
|
DEY ; Decrement Digit Number
|
2020-10-06 16:30:20 +00:00
|
|
|
BNE .IAZERO ; If Not Zero Loop
|
2022-04-04 23:47:16 +00:00
|
|
|
BEQ .IASKIP ; Else Branch into .IALOOP
|
2020-10-06 16:30:20 +00:00
|
|
|
.IALOOP JSR UPBCDI ;Unpack Digit #Y
|
|
|
|
.IASKIP TAX ;Save Digit in X
|
2022-04-04 23:47:16 +00:00
|
|
|
TYA ;Push Unpack Index into Stack
|
2019-05-27 21:12:10 +00:00
|
|
|
PHA
|
|
|
|
TXA ;and Restore Digit
|
|
|
|
ORA #$30 ;Convert Digit to ASCII
|
2022-04-04 23:47:16 +00:00
|
|
|
LDY TEMP3 ;Get Index into String
|
2020-10-16 02:58:12 +00:00
|
|
|
STA (DSTPTR),Y ;and Store in String
|
2019-05-27 21:12:10 +00:00
|
|
|
INC TEMP3 ;Increment Index into String
|
|
|
|
PLA ;Pull Digit Number off Stack
|
|
|
|
TAY
|
|
|
|
DEY ;Decrement Digit Number
|
2022-04-04 23:47:16 +00:00
|
|
|
BPL .IALOOP ;Loop if >= Zero
|
2019-05-27 21:12:10 +00:00
|
|
|
LDA #0 ;Terminate String
|
2020-10-16 02:58:12 +00:00
|
|
|
STA (DSTPTR),Y
|
2019-05-27 21:12:10 +00:00
|
|
|
TYA ;Return String Length
|
2022-04-04 23:47:16 +00:00
|
|
|
JMP .GETACC ;and INTACC
|
|
|
|
|
2019-05-27 21:12:10 +00:00
|
|
|
|
|
|
|
;upbcdi() - UnPack digits from BCD Integer
|
|
|
|
; Assumes that TEMP0, TEMP1, and TEMP2
|
|
|
|
; are in consecutive memory locations
|
|
|
|
;Args: Y = Digit Number to Unpack (0-5)
|
|
|
|
;Uses: TEMP0 = Low Byte
|
|
|
|
; TEMP1 = Middle Byte
|
|
|
|
; TEMP2 = High Nybble
|
2020-10-06 16:30:20 +00:00
|
|
|
;Affects: X,N,Z
|
2019-05-27 21:12:10 +00:00
|
|
|
;Returns: A = Unpacked Digit
|
2020-10-06 16:30:20 +00:00
|
|
|
UPBCDI: PHP
|
|
|
|
TYA ;Divide Digit Number by 2,
|
|
|
|
LSR ; Setting Carry
|
|
|
|
TAX ; if Digit Number is Odd
|
|
|
|
LDA TEMP0,X ;Load BCD Byte
|
|
|
|
BCC .UPSKIP ;If Digit Number is Odd
|
|
|
|
LSR ; Shift High Nybble to Low Nybble
|
|
|
|
LSR
|
|
|
|
LSR
|
|
|
|
LSR
|
|
|
|
.UPSKIP PLP
|
|
|
|
AND #$0F ;Strip Off High Nybble
|
2019-05-27 21:12:10 +00:00
|
|
|
RTS
|
|
|
|
|
|
|
|
;cvibcd(int) - ConVert Integer to packed Binary Coded Decimal
|
|
|
|
;Args: Y,X - Integer to Convert
|
|
|
|
;Sets: TEMP0 = Tens and Ones Digit
|
2020-09-08 15:51:30 +00:00
|
|
|
; TEMP1 = Thousands and Hundreds Digit
|
|
|
|
; TEMP2 = Ten-Thousands Digit
|
2020-10-06 16:30:20 +00:00
|
|
|
;Affects: A
|
2022-04-04 23:47:16 +00:00
|
|
|
CVIBCD: JSR IACC ;Store Argument
|
|
|
|
LDA #0 ;Clear BCD Bytes
|
2019-05-27 21:12:10 +00:00
|
|
|
STA TEMP0
|
|
|
|
STA TEMP1
|
|
|
|
STA TEMP2
|
|
|
|
PHP ;Save Status Register
|
|
|
|
SEI ;Disable Interrupts
|
|
|
|
SED ;Set Decimal Mode
|
|
|
|
LDY #16 ;Process 16 bits of Binary
|
2022-04-04 23:47:16 +00:00
|
|
|
.CVLOOP ASL INTACC ;Shift High Bit Into Carry
|
|
|
|
ROL INTACC+1
|
2019-05-27 21:12:10 +00:00
|
|
|
LDA TEMP0 ;Add 6 Digit BCD Number Itself
|
|
|
|
ADC TEMP0 ; Effectively Multiplying It by 2
|
|
|
|
STA TEMP0 ; and Adding in the Shifted Out Bit
|
|
|
|
LDA TEMP1
|
|
|
|
ADC TEMP1
|
|
|
|
STA TEMP1
|
|
|
|
LDA TEMP2
|
|
|
|
ADC TEMP2
|
|
|
|
STA TEMP2
|
|
|
|
DEY ;Decrement Counter and
|
2020-10-06 16:30:20 +00:00
|
|
|
BNE .CVLOOP ; Process Next Bit
|
2019-05-27 21:12:10 +00:00
|
|
|
PLP ;Restore Status Register
|
2020-09-08 15:51:30 +00:00
|
|
|
RTS
|
2020-10-06 16:30:20 +00:00
|
|
|
|
2022-04-04 23:47:16 +00:00
|
|
|
;icmp(j) - Compare Int i to Int j
|
|
|
|
;Requires: IACC(i) - int to compare against
|
|
|
|
;Args: X,Y = int to compare
|
|
|
|
; N based on return value of A
|
|
|
|
;Returns A=$01 and C=1 if INTACC > Arg
|
|
|
|
; A=$00 and Z=1, C=1 if INTACC = Arg
|
|
|
|
; A=$FF and C=0 if INTACC < Arg
|
|
|
|
ICMP: CPY INTACC+1 ;Compare MSBs
|
|
|
|
BCC .GT ;INTACC < Y,X
|
|
|
|
BNE .LT ;INTACC > Y,X
|
|
|
|
CPX INTACC ;Compare LSBs
|
|
|
|
BCC .GT ;INTACC < Y,X
|
|
|
|
BNE .LT ;INTACC > Y,X
|
|
|
|
LDA #0
|
|
|
|
RTS ;Return INTACC = YX
|
|
|
|
.LT LDA #$FF
|
|
|
|
RTS ;Return INTACC < YX
|
|
|
|
.GT LDA #1
|
|
|
|
RTS ;Return INTACC > YX
|
|
|
|
|
2020-10-06 16:30:20 +00:00
|
|
|
ENDSUBROUTINE
|