1
0
mirror of https://github.com/RevCurtisP/C02.git synced 2024-11-22 16:34:15 +00:00
C02/include/string.a02

221 lines
8.7 KiB
Plaintext
Raw Normal View History

2018-01-28 18:30:49 +00:00
; C02 library string.h02 assembly language subroutines
; Requires external routines SETSRC and SETDST
; Requires the following RAM locations be defined
; external zero page byte pairs SRCPTR and DSTPTR
2018-01-28 18:30:49 +00:00
; and external bytes TEMP0 and TEMP1
SUBROUTINE STRING
;strapd(c, s) - Append charecter c to string s
;Args: A = Character to be appended
; X,Y = Pointer to string
2020-09-08 15:51:30 +00:00
;Affects N,Z
;Returns A,Y = New String Length
STRAPD: STA TEMP0 ;Save Character to Append
JSR STRLEN ;Get Length of String
BMI .RETFLS ;Return 255 if > 127
2020-09-08 15:51:30 +00:00
LDA TEMP0 ;Restore Character to Append
.APDLOP STA (SRCPTR),Y ;Store at End of String
BEQ .LENEND ;Exit if NUL
2020-09-08 15:51:30 +00:00
INY ;Increment Past New Character
LDA #0 ;Set Character to NUL
BEQ .APDLOP ;and Append to String
2020-09-08 15:51:30 +00:00
;strppd(c, s) - Prepend Charecter to String
;Args: A = Character to be appended
; X,Y = Pointer to string
;Sets: N,Z
;Returns A = Insterted Character
STRPPD: STA TEMP0 ;Save Character to Append
JSR STRLEN ;Get Length of String
BMI .RETFLS ;Return 255 if > 127
INY ;Bump up string length
TYA ;Push string length onto stack
PHA
.PPDLOP DEY ;Copy Preceding Chacter
LDA (SRCPTR),Y
INY ;into Currebt Position
STA (SRCPTR),Y
DEY ;Move to Preceding Position
BNE .PPDLOP ;and Loop
LDA TEMP0 ;Retrieve Character
STA (SRCPTR),Y ;and Store in Position 0
PLA ;Retrieve new string length
BEQ .RETORA ;Set Flags and Return`
2018-01-28 18:30:49 +00:00
;strcmp(&s) - Compare String (to Destination String)
;Requires: DSTPTR - Pointer to destination string
2018-01-28 18:30:49 +00:00
;Args: X,Y = Pointer to source string
;Sets: SRCPTR = Pointer to string
2018-01-28 18:30:49 +00:00
;Affects N,Z
;Returns A=$01 and C=1 if Destination > Source
; A=$00 and Z=1, C=1 if Destination = Source
; A=$FF and C=0 if Destination < Source
; Y=Position of first character that differs
STRCMP: JSR SETSRC ;Initialize Source String
.CMPLOP LDA (DSTPTR),Y ;Load Destination Character
CMP (SRCPTR),Y ;Compare Against Source Character
BNE .CMPEND ;If Equal
ORA (SRCPTR),Y ; OR with Source Character
BEQ .RETURN ; If Both are 0, Return 0
2018-01-28 18:30:49 +00:00
INY ; Increment Offset
BPL .CMPLOP ; and Loop if < 128
.CMPEND BCC .RETFLS ;If Source < Destination, Return $FF & Carry Clear
2018-01-28 18:30:49 +00:00
LDA #$01 ;Else Return 1 and Carry Set
.RETURN RTS
2018-01-28 18:30:49 +00:00
;strchr(c, &s) - Find First Occurance of Character in String
;Args: A = Character to look for
; X,Y = Pointer to string to search in
;Sets: SRCPTR = Pointer to string
2019-03-23 01:18:49 +00:00
; TEMP3 = Character being searched for
2018-01-28 18:30:49 +00:00
;Affects: N,Z
;Returns: A = Position in string, C=1 if found
; A = $FF, C=0 if not found
; Y = Position of last character scanned
STRCHR: JSR SETSRC ;Initialize Source String
STRCHA: STA TEMP3 ;Save Search Character (alternate entry point)
.CHRLOP LDA (SRCPTR),Y ;Get Next Character
BEQ .CLCFLS ;If NUL, Return $FF and Carry Clear
2019-03-23 01:18:49 +00:00
CMP TEMP3 ;Compare Character
BEQ .LENEND ;If Found, Return Index
2018-01-28 18:30:49 +00:00
INY ;Increment Counter and Loop if < 128
BPL .CHRLOP ;Else Return $FF and Carry Clear
.CLCFLS CLC ;Clear Carry
.RETFLS LDA #$FF ;Load -1 into Accumulater
2018-01-28 18:30:49 +00:00
RTS ;and Return
2020-09-08 15:51:30 +00:00
;strapd(c, &s) - Append Character to String
;Args: A = Character to Append
; X,Y = Pointer to String
;Sets: SRCPTR, SRCPTR+1 - Pointer to String
2018-01-28 18:30:49 +00:00
;strlen(&s) - Return Length of String
;Args: X,Y - Pointer to string
;Sets: SRCPTR = Pointer to source string
2018-01-28 18:30:49 +00:00
;Returns: A,Y = Length of string
2018-07-25 23:00:46 +00:00
; N,Z based on A
2018-01-28 18:30:49 +00:00
STRLEN: JSR SETSRC ;Initialize Source String
.LENLOP LDA (SRCPTR),Y ;Get Next Character
BEQ .LENEND ;If <> NUL
2018-01-28 18:30:49 +00:00
INY ; Increment Index
BPL .LENLOP ; and Loop if < 128
.LENEND TYA ;Transfer Index to Accumulator
.RETORA ORA #0 ;Set N and Z flags
2018-01-28 18:30:49 +00:00
RTS ;and Return
;strcpb(&s) - Copy String to System Buffer
STRCPB: JSR SETSRC ;Set Source Pointer to String Address
JSR SETDSB ;Set Destination Pointer to System Buffer
BVC STRCPA ;Execute String Copy
2018-01-28 18:30:49 +00:00
;strcat(&s) Concatenate String (to Destination String)
;Requires: DSTPTR - Pointer to destination string
2018-01-28 18:30:49 +00:00
;Args: X,Y = Pointer to source string
;Sets: SRCPTR = Pointer to source string
2019-03-23 01:18:49 +00:00
; TEMP3 = Length of source prior to concatenation
2018-01-28 18:30:49 +00:00
;Affects: C,N,Z
;Returns: A,Y = Total length of concatenated string
STRCAT: JSR SETSRC ;Initialize Source String
.CATLOP LDA (DSTPTR),Y ;Find end of Destination String
BEQ .CATEND ;
2018-01-28 18:30:49 +00:00
INY ;
BPL .CATLOP ;
.CATEND STY TEMP3 ;Subtract Destination String Length
LDA SRCPTR ; from Source String Pointer
2018-01-28 18:30:49 +00:00
SEC
2019-03-23 01:18:49 +00:00
SBC TEMP3
STA SRCPTR
LDA SRCPTR+1
2018-01-28 18:30:49 +00:00
SBC #$00
STA SRCPTR+1
JMP .CPYLOP ;Execute String Copy
2018-01-28 18:30:49 +00:00
;strcpy(&s) - Copy String (to Destination String)
;Requires: DSTPTR - Pointer to destination string
2018-01-28 18:30:49 +00:00
;Args: X,Y = Pointer to source string
;Sets: SRCPTR = Pointer to source string
2018-01-28 18:30:49 +00:00
;Affects: N,Z
2018-08-14 18:14:32 +00:00
;Returns: A,Y = Number of characters copied
2020-09-08 15:51:30 +00:00
STRCPA: LDY #0 ;Alternate entry point
BEQ .CPYLOP ;for when Source already set
2018-01-28 18:30:49 +00:00
STRCPY: JSR SETSRC ;Initialize Source String
.CPYLOP LDA (SRCPTR),Y ;Get Character from Source String
STA (DSTPTR),Y ;Copy to Destination String
BEQ .CPYEND ;If <> NUL
2018-01-28 18:30:49 +00:00
INY ; Increment Index
BPL .CPYLOP ; and Loop if < 128
.CPYEND TYA ;Transfer Index to Accumulator
2018-01-28 18:30:49 +00:00
RTS ;and Return
;strcut(n, &s) - Copy from Position n to End of Source (into Destination)
;Requires: DSTPTR - Pointer to destination string
2018-01-28 18:30:49 +00:00
;Args: A = Starting position in start string
; X,Y = Pointer to source string
;Sets: SRCPTR = Pointer to specified position in source string
2018-01-28 18:30:49 +00:00
;Affects: N,Z
;Returns: A,Y = Length of copied string
STRCUT: JSR SETSRC ;Initialize Source String
CLC
ADC SRCPTR ;Move Source Pointer
STA SRCPTR ; to Specified Position in String
BCC .CPYLOP
INC SRCPTR+1
JMP .CPYLOP ;and Jump Into String Copy Loop
2018-01-28 18:30:49 +00:00
;strstr(&s) - Search for String (in Destination String)
;Requires: DSTPTR - Pointer to destination string
2018-01-28 18:30:49 +00:00
;Args: X,Y = Pointer to search string
;Sets: DSTPTR = Pointer to position in source string
2018-01-28 18:30:49 +00:00
; End of string if not found
; SRCPTR = Pointer to source string
2019-03-23 01:18:49 +00:00
; TEMP3 = Last position checked in destination string
2018-01-28 18:30:49 +00:00
;Affects: N,Z
;Returns: A = Position, C=1 if found
; A = $FF, C=0 if not found
; Y = Last position checked in source string
STRSTR: JSR SETSRC ;Initialize Source String
2019-03-23 01:18:49 +00:00
STY TEMP3 ;Initialize Position
.STRLOP LDY #$00; ;Initialize Compare Offset
LDA (DSTPTR),Y ;Get Start Character in Destination
BEQ .CLCFLS ;If NUL return $FF and Carry Clear
JSR .CMPLOP ;Jump into Compare Loop
BEQ .STREND ;If Not Equal
BMI .STRNXT ; If Source is Greater
LDA (SRCPTR),Y ; If at End of Source String
BEQ .STREND ; Return Current Position
.STRNXT INC TEMP3 ; Else Increment Position
BMI .CLCFLS ; If > 127 return $FF and Carry Clear
INC DSTPTR ; Increment Source Pointer
BNE .STRLOP
INC DSTPTR+1 ; If not End of Memory
BNE .STRLOP ; Loop
BEQ .CLCFLS ; Else return $FF and Carry Clear
.STREND SEC ;Else Set Carry
2019-03-23 01:18:49 +00:00
LDA TEMP3 ; Load Position
2018-01-28 18:30:49 +00:00
RTS ; and Return
;strrch(c, &s) - Find Last Occurance Character in String
;Args: A = Character to look for
; X,Y = Pointer to string to search in
;Sets: SRCPTR = Pointer to string
2019-03-23 01:18:49 +00:00
; TEMP3 = Character being searched for
2018-01-28 18:30:49 +00:00
;Affects: Y,C,N,Z
2019-03-23 01:18:49 +00:00
;Returns: A,X = Position of last occurance in string
; $FF if not found
; Y = Length of String
2018-01-28 18:30:49 +00:00
STRRCH: JSR SETSRC ;Initialize Source String
2019-03-23 01:18:49 +00:00
STA TEMP3; ;Save Search Character (alternate entry point)
LDX #$FF ;Initialize Position
.RCHLOP LDA (SRCPTR),Y ;Get Next Character
BEQ .RCHEND ;If NUL, Exit with Position
2019-03-23 01:18:49 +00:00
CMP TEMP3 ;Compare Character
BNE .RCHNXT ;If Found
2019-03-23 01:18:49 +00:00
TYA ; Store Counter
TAX
.RCHNXT INY ;Increment Counter
BPL .RCHLOP ; and Loop if < 128
.RCHEND TXA ;Copy Position to Accumulater
2018-01-28 18:30:49 +00:00
RTS ; and Return
ENDSUBROUTINE