Added function strtok to module stringx

This commit is contained in:
Curtis F Kaylor 2020-10-11 14:45:01 -04:00
parent acd1cbe3c3
commit 2767158d30
24 changed files with 513 additions and 75 deletions

View File

@ -16,11 +16,13 @@ RTNKEY EQU $0D ;Return/Enter Key (Carriage Return)
.HEXH EQU $29 ;
.YSAVE EQU $2A ;Y Register Storage
.MODE EQU $2B ;Mode: Store, Examine, Block Examine
.BUFFER EQU $200 ;Input Buffer
.IN EQU $200 ;Input Buffer
;Standard Library Variables
SRCPTR EQU $30 ;Source String Pointer (stdio.a02)
SRCLO EQU $30 ;Source String Pointer (stdio.a02)
SRCHI EQU $31
DSTPTR EQU $32 ;Destination String Pointer (string.a02)
DSTLO EQU $32 ;Destination String Pointer (string.a02)
DSTHI EQU $33
BFRLO EQU $34 ;Work Buffer Pointer
@ -48,6 +50,11 @@ STKSHI EQU $4D
STKELO EQU $4E ;Stack End Address
STKEHI EQU $4F
SYSBFP EQU $50 ;Position in System Buffer
SYSBFL EQU 128 ;System Buffer Size (128 Bytes)
SYSBFR EQU .IN ;System Buffer (Input Buffer
;PIA 6820 Registers
.KBD EQU $D010 ;Keyboard Data
.KBDCR EQU $D011 ;Keyboard Control Register
@ -100,3 +107,5 @@ NEWLIN: LDA #$0D ;Load C/R into Accumulator
JMP PUTCHR ; and Print it
INCLUDE "../include/putstr.a02" ;PUTSTR routine
ENDSUBROUTINE

View File

@ -4,6 +4,7 @@
#define DELKEY $5F //Delete/Backspace Key
#define ESCKEY $1B //Escape/Stop Key
#define RTNKEY $0D //Return/Enter Key
#define SYSBFL 128 //System Buffer Length
/* Standard Library Variables */
char srclo,srchi; //Source String Pointer for Library Functions
@ -17,8 +18,9 @@ char blklen; //Block Segment Length
char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stack End Address
char random, rdseed; //Pseudo-Random Number Generator
char temp0, temp1, temp2, temp3; //Temporary Variables
char sysbfr[], sysbfp; //System String Buffer and Position
//Monitor Subroutines
void echo(); //Print Character in Accumulator

View File

@ -8,29 +8,38 @@ ESCKEY EQU $1B ;Escape/Stop Key (Escape)
RTNKEY EQU $0D ;Return/Enter Key (Return)
;Zero Page Variables (*=System Variable)
DSTLO EQU $06 ;Destination Pointer
DSTPTR EQU $06 ;Destination Pointer [Unused]
DSTLO EQU $06
DSTHI EQU $07
BLKLO EQU $08 ;Block Segment Pointer (block.a02)
BLKLO EQU $08 ;Block Segment Pointer [Unused]
BLKHI EQU $09
STKLO EQU $1D ;Stack Pointer (stack.a02)
STKHI EQU $1E
SYSBFP EQU $1D ;Stack Pointer [Unused]
; $1E ;Unused
STKLO EQU $2E ;Stack Pointer [Tape Read Work Area]
STKHI EQU $2F
RANDOM EQU $1F ;Random Number
INVFLG EQU $32 ;*Inverse Flag: $3F=Blinking, $7F=Inverse, $FF=Normal
SRCLO EQU $71 ;Source Pointer
.INVFLG EQU $32 ;*Inverse Flag: $3F=Blinking, $7F=Inverse, $FF=Normal
SRCPTR EQU $71 ;Source Pointer [Temporary Register]
SRCLO EQU $71
SRCHI EQU $72
RDSEED EQU $E3 ;Random Seed
BLKSLO EQU $EB ;Block Start Address
BLKSHI EQU $ED
BLKELO EQU $ED ;Block End Address
BLKSLO EQU $EB ;Block Start Address [Unused]
BLKSHI EQU $EC
BLKELO EQU $ED ;Block End Address [Unused]
BLKEHI EQU $EE
BLKLEN EQU $EF ;Block Segment Length
BFRLO EQU $FA ;Work Buffer Pointer
BLKLEN EQU $EF ;Block Segment Length [Unused]
BFRLO EQU $FA ;Work Buffer Pointer [Unused]
BFRHI EQU $FB
TEMP0 EQU $FC ;Temporary Storage
TEMP0 EQU $FC ;Temporary Variables [Unused]
TEMP1 EQU $FD
TEMP2 EQU $FE
TEMP3 EQU $FF
;System Variables
SYSBFL EQU 255 ;System Buffer Size [88 Bytes]
SYSBFR EQU $0300 ;System Buffer [Keyboard Buffer]
;I/O Locations
.KBD EQU $C000 ;Keyboard Data
.AKD EQU $C010 ;Keyboard Strobe Register

View File

@ -4,6 +4,7 @@
#define DELKEY $08 //Delete/Backspace Key
#define ESCKEY $1B //Escape/Stop Key
#define RTNKEY $0D //Return/Enter Key
#define SYSBFL 255 //System Buffer Length
/* Standard Library Pointers */
char srclo,srchi; //Source String Pointer for Library Functions
@ -20,6 +21,7 @@ char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char temp0, temp1, temp2, temp3; //Temporary Variables
char sysbfr[], sysbfp; //System String Buffer and Position
/* Platform Specific Variables */
char invflg; //Video Invert Mask

View File

@ -9,8 +9,10 @@ RTNKEY EQU $0D ;Return/Enter Key (RETURN)
XMBANK EQU $0A ;Extended Memory Bank (Load/Verify Flag)
XADRLO EQU $0B ;Ext Memory Address LSB (Text Index/Array Size)
XADRHI EQU $0C ;Ext Memory Address MSB (Array Dimension Fkags)
SRCPTR EQU $22 ;Source Pointer [Temporary Pointers]
SRCLO EQU $22 ;Source Pointer LSB [Temporary Pointers]
SRCHI EQU $23 ;Source Pointer MSB [Temporary Pointers]
DSTPTR EQU $24 ;Destination Pointer [Temporary Pointers]
DSTLO EQU $24 ;Destination Pointer LSB [Temporary Pointers]
DSTHI EQU $25 ;Destination Pointer MSB [Temporary Pointers]
BLKLO EQU $26 ;Block Pointer LSB [Floating Point Work Area]
@ -26,7 +28,9 @@ TEMP2 EQU $FD ;Temporary Variable [Unused Byte]
TEMP3 EQU $FE ;Temporary Variable [Unused Byte]
;System Variables
USER3 EQU $0313 ;Free Byte for User Programs
SYSBFL EQU 88 ;System Buffer Size [88 Bytes]
SYSBFR EQU $0200 ;System Buffer [Keyboard Buffer]
SYSBFP EQU $0313 ;Position in System Buffer [Free Byte]
BLKSLO EQU $0334 ;Block Start LSB [Unused Byte]
BLKSHI EQU $0335 ;Block Start MSB [Unused Byte]

View File

@ -4,6 +4,7 @@
#define DELKEY $14 //Delete/Backspace Key (DEL)
#define ESCKEY $03 //Escape/Break Key (STOP)
#define RTNKEY $0D //Return/Enter Key (RETURN)
#define SYSBFL 88 //System Buffer Length
/* Standard Library Pointers */
char srclo,srchi; //Source String Pointer for Library Functions
@ -17,9 +18,10 @@ char blkslo, blkshi; //Block Start Address
char blkelo, blkehi; //Block End Address
char blklen; //Block Segment Length
char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char stkelo, stkehi; //Stack End Address
char random, rdseed; //Pseudo-Random Number Generator
char temp0, temp1, temp2, temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
/* System Subroutines */
void delchr(); //Delete previous character

View File

@ -40,11 +40,17 @@ STKSHI EQU $4D
STKELO EQU $4E ;Stack End Address
STKEHI EQU $4F
SYSBFP EQU $50 ;Position in System Buffer
SYSBFL EQU 128 ;System Buffer Size (Max String Size)
SYSBFR EQU $0200 ;System Buffer
;Memory Mapped I/O
_KBHIT EQU $FFF0 ;Is a Key Pressed
_GETCH EQU $FFF1 ;Read Keyboard (Blocking)
ORG $0200 ;START at RAM midpoint
ORG $0400 ;START at RAM midpoint
START: JMP MAIN ;Execute Program
@ -80,5 +86,7 @@ PUTCHR EQU $FFE3 ;Emulator CHROUT Routine
EXIT EQU $FFEC ;Emulator SHUTDN Routine
FSCMD EQU $FFE6 ;run6502 File System Command Routine
INCLUDE "../include/prbyte.a02" ;PRBYTE and PRHEX routines
INCLUDE "../include/putstr.a02" ;PUTSTR routine

View File

@ -4,6 +4,7 @@
#define DELKEY $08 //Delete/Backspace Key
#define ESCKEY $18 //Escape/Stop Key
#define RTNKEY $0D //Return/Enter Key
#define SYSBFL 128 //System Buffer Length
//Library Pointer Variables
zeropage int srcptr, dstptr, bfrptr, blkptr;
@ -12,7 +13,6 @@ char dstlo,dsthi; //Destination String Pointer for Library Functions
char bfrlo,bfrhi; //Buffer Pointer for Library Functions
char blklo,blkhi; //Block Segment Pointer
char stklo,stkhi; //Stack Pointer
//Library Variables
char blkslo, blkshi; //Block Start Address
char blkelo, blkehi; //Block End Address
@ -21,6 +21,7 @@ char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char temp0, temp1, temp2, temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
//Memory Mapped I/O
char putcon; //Write Character to Console

View File

@ -1,20 +1,21 @@
;c02 library stddef.h02 assembly language subroutines
;Requires External Zero Page Variables
;DSTLO, DSTHI, SRCLO, SRCHI
;External Variables
;TEMP0, TEMP1, TEMP2
;Requires External Zero Page Variables DSTPTR, SRCPTR
;and External Variables TEMP0, TEMP1, TEMP2 (system header)
SUBROUTINE STDDEF
;Constant Definitions
STRSIZ EQU 128 ;Maximum String Size
TRUE EQU $FF ;Returned for Success or Failure
FALSE EQU $00 ;by some Library Routines
;savdst() - Save Destination Pointer
SAVDST: JSR GETDST ;Load Destination Pointer
JMP SAVRXY ;Save X & Y Registers
BVC SAVRXY ;Save X & Y Registers
;savsrc() - Save Source Pointer
SAVSRC: JSR GETSRC ;Load Destination Pointer
JMP SAVRXY ;Save X & Y Registers
BVC SAVRXY ;Save X & Y Registers
;Save Registers
SAVREG: STA TEMP0 ;Save Accumulater
@ -23,44 +24,60 @@ SAVRXY: STX TEMP1 ;Save X Index
RTS
;Restore Registers
RESREG: LDA TEMP0 ;Load Accumlator
RESRXY: LDX TEMP1 ;Load X Index
LDY TEMP2 ;Load Y Index
RESREG: LDA TEMP0 ;Load Accumulator
RESRXY: LDX TEMP1 ;Load X Index
LDY TEMP2 ;Load Y Index
RTS
;Set Destination Pointer to System Buffer
SETDSB: JSR GETBFR ;Get Buffer Address
BVC SETDST
;Set Destination Pointer to Source Pointer
SETDSS: JSR GETSRC ;Get Destination Pointer
JMP SETDST ;Store in Source Pointer
SETDSS: JSR GETSRC ;Get Destination Pointer
BVC SETDST ;Store in Source Pointer
;Restore Destination Pointer
RESDST: JSR RESRXY ;Load Address and Drop into SETDST
RESDST: JSR RESRXY ;Load Address and Drop into SETDST
;Initialize Destination Pointer
SETDST: STX DSTLO ;Store Destination Pointer
STY DSTHI
SETDST: STX DSTPTR ;Store Destination Pointer
STY DSTPTR+1
RTS
;Restore Source Pointer
RESSRC: JSR RESRXY ;Load Saved Address
JMP SETSRC ;Set Source Pointer
RESSRC: JSR RESRXY ;Load Saved Address
BVC SETSRC ;Set Source Pointer
;Set Source Pointer to System Buffer
SETSRB: JSR GETBFR ;Get Buffer Address
BVC SETSRC
;Set Source Pointer to Destination Pointer
SETSRD: JSR GETDST ;Get Destination Point and fall into SETSRC
SETSRD: JSR GETDST ;Get Destination Point and fall into SETSRC
;Initialize Source Pointer and Index
SETSRC: STX SRCLO ;Store Source Pointer
STY SRCHI
LDY #$00 ;Initialize Index Into String
SETSRC: STX SRCPTR ;Store Source Pointer
STY SRCPTR+1
LDY #$00 ;Initialize Index Into String
RTS
;Retrieve System Buffer Address
GETBFR: LDX #<SYSBFR
LDY #>SYSBFR
CLV ;Clear Overflow Flag for BVC
RTS
;Retrieve Source String Pointer
GETDST: LDX DSTLO
LDY DSTHI
GETDST: LDX DSTPTR
LDY DSTPTR+1
CLV ;Clear Overflow Flag for BVC
RTS
;Retrieve Source String Pointer
GETSRC: LDX SRCLO
LDY SRCHI
GETSRC: LDX SRCPTR
LDY SRCPTR+1
CLV ;Clear Overflow Flag for BVC
RTS
;Add TEMP1,TEMP2 to X,Y
@ -85,16 +102,20 @@ SUBTXY: TXA
;Decrement X,Y Register Pair
DECRXY: CPY #0
BNE DECRXZ
BNE .SKIP
DEY
DECRXZ: DEX
.SKIP DEX
RTS
;Increment X,Y Register Pair
INCRXY: INX
BNE INCRXZ
BNE .RETURN
INY
INCRXZ: RTS
.RETURN RTS
;Set Source Pointer to Buffer Location and Add Accumulator
SETDBA: LDA SYSBFP ;Get Buffer Position
JSR SETDSB ;Set Destination to Buffer Address
;Add Accumulator to Destination Address
ADDDSA: TAX ;Move Accumulator to Argument LSB
@ -103,9 +124,14 @@ ADDDSA: TAX ;Move Accumulator to Argument LSB
;Add to Destination Address
;Args: Y,X = MSB,LSB of Integer to Add
;Affects: A,Y,X
ADDDST: LDA #DSTLO ;Set Index to Destination Pointer
ADDDST: LDA #DSTPTR ;Set Index to Destination Pointer
BNE ADDZPW ;and Execute ADDZPW
;Set Source Pointer to System Buffer Position
SETSBP: LDA SYSBFP ;Load Position in Buffer
BMI .RETURN ;If Greater than 127, Return
JSR SETSRB ;Set Source Pointer to Buffer Address
;Add Accumulator to Source Address
ADDSRA: TAX ;Move Accumulator to Argument LSB
LDY #0 ;Clear Argument MSB
@ -113,7 +139,7 @@ ADDSRA: TAX ;Move Accumulator to Argument LSB
;Add to Source Address
;Args: Y,X = MSB,LSB of Integer to Add
;Affects: A,Y,X
ADDSRC: LDA #SRCLO ;Set Index and Drop into ADDZPW
ADDSRC: LDA #SRCPTR ;Set Index and Drop into ADDZPW
;Add to Zero Page Word
;Args: A = Address of Zero Page Word
@ -130,3 +156,4 @@ ADDZPW: STA TEMP3 ;Save Zero Page Address
STA 1,X ;and Save Result
RTS
ENDSUBROUTINE

View File

@ -47,7 +47,7 @@ STRCMR: RTS ;
; 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)
STRCHA: STA TEMP3 ;Save Search Character (alternate entry point)
STRCHL: LDA (SRCLO),Y ;Get Next Character
BEQ STRCLC ;If NUL, Return $FF and Carry Clear
CMP TEMP3 ;Compare Character
@ -83,6 +83,11 @@ STRLEX: TYA ;Transfer Index to Accumulator
;Affects: N,Z
STRDST EQU SETDST ;Aliased to System Header function
;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
;strcat(&s) Concatenate String (to Destination String)
;Requires: DSTLO, DSTHI - Pointer to destination string
;Args: X,Y = Pointer to source string

View File

@ -2,7 +2,7 @@
* string - String Handling Routines for C02 *
*********************************************/
/* Find Charaacter in String *
/* Find Character in String *
* Args: c - Character to find *
* &s - String to search *
* Returns: c in s *

View File

@ -1,6 +1,8 @@
; C02 library stringx.h02 assembly language subroutines
; Requires the subroutines and definitions from string.asm
SUBROUTINE STRINGX
;Common Code - Initialize Variables
STRXSI: JSR SETSRC ;Initialize Source String
STY TEMP1 ;Save Destination Pointer
@ -73,3 +75,56 @@ STRSPL: JSR STRXSL ;and Search for Character in Source String
BPL STRSPL ; and Loop if < 128
BMI STRXSP ;Else Return Position
;strtok(c, &s) - Split String by Specified Character
;Args: A = Delimiter, 0 = Set String to Tokenize
; X,Y = Address of Argument String
;Sets: DSTPTR = Address of Argument String
; or Address of System Buffer (A=0)
; SRCPTR = Address of System Buffer Location
; or Address of Argument String (A=0)
; TEMP0 = Delimiter Character
;Populates: SYSBFR - String to Tokenize
;Returns: A = Length of Token
; Y = New Buffer Position, $FF = End of String
; X = End of String Flag, $00 or $FF
STRTOK: ORA #0
BNE .STRTOK ;If Delimiter is NUL
STA SYSBFP ; Initialize System Buffer Position
JMP STRCPB ; Copy String to System Buffer and Return
.STRTOK STA TEMP0 ;Save Delimiter Character
JSR SETDST ;Set Destination to String Address
JSR SETSBP ;Set Source to Current Buffer Position
BPL .STCOPY ;If at End of Buffer
LDA #0
TAY ;Set Destination String to ""
STA (DSTPTR),Y ;and Return String Length 0
RTS
.STCOPY LDY #0 ;Initialize Index
LDX #0 ;Clear End of String Flag
.STLOOP LDA (SRCPTR),Y ;Get Character from Source String
BNE .STSKIP ;If End of String
DEX ; Set End of Buffer Flag
BMI .STDONE ; and Finish Up
.STSKIP CMP TEMP0 ;
BEQ .STDONE ;If Not Delimiter Character
STA (DSTPTR),Y ; Copy to Destination String
INY ; Increment Index
CPY #SYSBFL ; If Less Than Buffer Size
BCC .STLOOP ; Loop
DEX ;Else Set End of Buffer Flag
.STDONE LDA #0 ;Terminate String
STA (DSTLO),Y ;
.STRTN STY TEMP0 ;Save String Length
INY ;Increment Past Delimiter
TYA ; and Add to Buffer Position
CLC
ADC SYSBFP
STA SYSBFP ;Save New Buffer Position
CPX #0 ;If End of Buffer Flag is Set
BPL .STRTRN
STX SYSBFP ; Set Buffer Position to 255
.STRTRN LDA TEMP0 ;Return String Length
RTS
ENDSUBROUTINE

View File

@ -4,24 +4,23 @@
/* Find Span of Characters not matching String *
* Args: &s - String of characters to match *
* Uses: String to parse specified by strdst() *
* Uses: String to parse specified by setdst() *
* Sets: temp1 - Result *
* Returns: Number of consecutive characters in *
* Destination that are not in Source */
char strbrk();
char strcsp(); //Alias
/* Find Span of Characters matching String *
* Args: &s - String of characters to match *
* Uses: String to parse specified by strdst() *
* Sets: temp1 - Result *
* Returns: Number of consecutive characters in *
* Destination that are also in Source */
/* Find Span of Characters matching String *
* Setup: setdst(s) - String to Search *
* Args: int &m - String to match *
* Returns: Number of consecutive characters *
* in m that are also in s */
char strspn();
/* Find First Character matching String *
* Args: &s - String of characters to match *
* Uses: String to parse specified by strdst() *
* Uses: String to parse specified by setdst() *
* Sets: temp1 - Result *
* Returns: Position of first character in *
* Destination that is also in Source *

View File

@ -6,8 +6,10 @@ ESCKEY EQU $03 ;Escape/Stop Key (RUN/STOP)
RTNKEY EQU $0D ;Return/Enter Key (RETURN)
;Zero Page Locations
SRCPTR EQU $22 ;Source Pointer LSB [Temporary Pointers]
SRCLO EQU $22 ;Source Pointer LSB [Temporary Pointers]
SRCHI EQU $23 ;Source Pointer MSB [Temporary Pointers]
DSTPTR EQU $24 ;Destination Pointer LSB [Temporary Pointers]
DSTLO EQU $24 ;Destination Pointer LSB [Temporary Pointers]
DSTHI EQU $25 ;Destination Pointer MSB [Temporary Pointers]
BLKLO EQU $26 ;Block Pointer LSB [Floating Point Work Area]
@ -23,10 +25,12 @@ TEMP2 EQU $FD ;Temporary Variable [Unused Byte]
TEMP3 EQU $FE ;Temporary Variable [Unused Byte]
;System Variables
SYSBFL EQU 88 ;System Buffer Size [88 Bytes]
SYSBFR EQU $0200 ;System Buffer [Keyboard Buffer]
USER0 EQU $0310 ;Free Byte for User Programs
USER1 EQU $0311 ;Free Byte for User Programs
USER2 EQU $0312 ;Free Byte for User Programs
USER3 EQU $0313 ;Free Byte for User Programs
SYSBFP EQU $0313 ;Position in System Buffer [Free Byte]
BLKSLO EQU $0334 ;Block Start LSB [Unused Byte]
BLKSHI EQU $0335 ;Block Start MSB [Unused Byte]

60
include/vic/float.a02 Normal file
View File

@ -0,0 +1,60 @@
;VIC20 BASIC Floating Point Functions
;pival - PI Expressed as a Five-Byte Floating Point Number
PIVAL EQU $CEA8
maxint EQU $D1A5 ;The Constant -32768 in Five-Byte Floating Point Format
ayint EQU $D1AA ;Convert Floating Point to Signed Integer in A and Y
intidx EQU $D1B2 ;Convert Floating Point Subscript to a Positive Integer
fpint EQU $D1BF ;Convert Floating Point Number to Signed Integer
makfp EQU $D391 ;Convert 16-Bit Signed Integer to Floating Pointers
fpadr EQU $D7F7 ;Convert Floating Point to Unsigned Two-Byte Integer
fpsubm EQU $D850 ;Subtract FAC1 from a Number in Memory
fpsub EQU $D853 ;Subtract FAC2 from FAC1
fpaddm EQU $D867 ;Add FAC1 to a Number in Memory
fpaddh EQU $D86A ;Add FAC1 to FAC2
normlz EQU $D8FE ;Normalize Floating Point Accumulator #1
comfac EQU $D947 ;Replace FAC1 with Its 2's Complement
denorm EQU $D983 ;Denormalize Exponents of FAC1 and FAC2
fpcone EQU $D9BC ;Floating Point Constant with a Value of 1
dolog EQU $D9EA ;Perform LOG
fpmult EQU $DA28 ;Multiply FAC1 with FAC2
fpmltb EQU $DA59 ;Multiply Byte Subroutine
lodarg EQU $DA8C ;Move Floating Point Number from Memory into FAC2
multen EQU $DAE2 ;Multiply FAC1 by 10
fpcten EQU $BAF9 ;The Constant 10 in Five-Byte Floating Format
divten EQU $DAFE ;Divide FAC1 by 10
fpdivm EQU $DB0F ;Divide a Number in Memory by FAC1
fpdivm EQU $DB12 ;Divide FAC2 by FAC1
lodfac EQU $DBA2 ;Move Floating Point Number from Memory to FAC1
strfac EQU $DBD4 ;Move Floating Point Number from FAC1 to Memory
argfac EQU $DBFC ;Move Floating Point Number from FAC2 to FAC1
rndmov EQU $DC0C ;Round and Move Floating Point Number from FAC1 to FAC2
facarg EQU $DC0F ;Move Floating Point Number from FAC1 to FAC2
round EQU $DC1B ;Round FAC1 by Adjusting Rounding Byte
sgnfac EQU $DC2B ;Put Sign of FAC1 into A Register
dosgn EQU $DC39 ;Perform SGN
bytfp EQU $DC3C ;Convert Signed Byte in A Register to Floating Point
doabs EQU $DC58 ;Perform ABS
cmpfac EQU $DC5B ;Compare FAC1 to Memory
fpint EQU $DC9B ;Convert FAC1 to 32-bit Signed Integer in $62-$65
doint EQU $DCCC ;Perform INT
ascfp EQU $DCF3 ;Convert ASCII String to Floating Point Number
addbyt EQU $DD7E ;Add Signed Byte in A Register to FAC1
fpasc EQU $DDDD ;Convert Contents of FAC1 to ASCII String
dosqr EQU $DF71 ;Perform SQR
expont EQU $DF7B ;Perform ^
negfac EQU $DFB4 ;Perform - (Unary Minus)
doexp EQU $DFED ;Perform EXP
dorrnd EQU $E094 ;Perform RND
docos EQU $E261 ;Perform COS
dosin EQU $E268 ;Perform SIN
dotan EQU $E2B1 ;Perform TAN

41
include/vic/sounds.a02 Normal file
View File

@ -0,0 +1,41 @@
; C02 sounds library assembly routines for VIC-20
;beep() - Produce System Beep Sound
;Affects: A,Y
BEEP NOP ;Sound Bell
;Uses VIA Timer 2...
BEEPD: JSR $EF96 ;Delay YX Milliseconds
DEX
BPL BEEPD
DEY
BPL BEEPD
RTS
BEEPX: LDX #3 ;Turn off all Sound
BEEPXL: LDA #0 ;Store 0 in all four
STA $900A,X ; VIC Sound Registers
DEX
BPL BEEPXL
RTS
;bomb() - Produce System Explosion Sound
;Affects: None
BOMB: RTS ;Function Not Available
;shoot() - Produce Shooting Sound
;Affects: None
SHOT: RTS ;Function Not Available
;tick() - Produce System Tick Sound
;Affects: None
TICK: LDA $C030 ;Click Speaker Once
RTS
;tock() - Produce System Tock Sound
;Affects: None
TOCK: RTS ;Function Not Available
;zap() - Produce System Zap Sound
;Affects: None
ZAP: RTS ;Function Not Available

42
include/vic/template.h02 Normal file
View File

@ -0,0 +1,42 @@
/*********************************************************
* vector - 6502 Interrupt Vector Manipulation Functions *
*********************************************************/
/* Get Maskable Interrupt Address *
* Returns: $00 If Address can be *
* modified, otherwise $FF *
* Address MSB *
* Address LSB */
char getirq();
/* Get Non-Maskable Interrupt Address *
* Returns: $00 If Address can be *
* modified, otherwise $FF *
* Address MSB *
* Address LSB */
char getnmi();
/* Get "Reset" Interrupt Address *
* Returns: $00 If Address can be *
* modified, otherwise $FF *
* Address MSB *
* Address LSB */
char getrst();
/* Set Maskable Interrupt Address */
* Args: &d - New Interrupt Address *
* Returns: $00 If Successful, *
* otherwise $FF */
char setirq();
/* Set Non-Maskable Interrupt Address */
* Args: &d - New Interrupt Address *
* Returns: $00 If Successful, *
* otherwise $FF */
char setnmi();
/* Set "Reset" Interrupt Address */
* Args: &d - New Interrupt Address *
* Returns: $00 If Successful, *
* otherwise $FF */
char setrst();

82
include/vic/vectors.a02 Normal file
View File

@ -0,0 +1,82 @@
; C02 Interrupt Vector Assembly Language Routines for VIC-20
;getirq() - Return IRQ Interrupt Handler Address
;Returns: A = $00 - Software Definable Address
; Y = Address MSB
; X = Address LSB
GETIRQ: LDA #$00 ;Return software definable
LDX $0314 ;and Address in CINV
LDY $0315
RTS
;getbrk() - Return BRK Interrupt Handler Address
;Returns: A = $00 - Software Definable Address
; Y = Address MSB
; X = Address LSB
GETBRK: LDA #$00 ;Return software definable
LDX $0316 ;and Address in CBINV
LDY $0317
RTS
;getnmi() - Return NMI Interrupt Handler Address
;Returns: A = $00 - Software Definable Address
; Y = Address MSB
; X = Address LSB
GETNMI: LDA #$00 ;Return software definable
LDX $0318 ;and Address in CBINV
LDY $0319
RTS
;getrst() - Return RESET Interrupt Handler Address
;Returns: A = $7F - Firmware Defined Address
; Y = Address MSB
; X = Address LSB
GETRST: LDX $FFFC ;Load 6502 Interrupt Vector
LDY $FFFD ;and Fall into SETRST
;setrst() - Set RESET Interrupt Handler Address
;Args: Y = Address MSB
; X = Address LSB
;Returns: A = $7F - Failure - Can't be Changed
SETRST: LDA #$7F ;Return "Hard Coded"
RTS
;setirq() - Set IRQ Interrupt Handler Address
;Args: Y = Address MSB
; X = Address LSB
;Returns: A = $00 - Successfully Set
SETIRQ: SEI ;Disable Interrupts
STX $0314 ;Store Address in CINV
STY $0315
CLI ;Enable Interrupts
LDA #$00 ;Return "Modified"
RTS
;setrst() - Set BRK Interrupt Handler Address
;Args: Y = Address MSB
; X = Address LSB
;Returns: A = $00 - Successfully Set
SETBRK: SEI ;Disable Interrupts
STX $0316 ;Store Address in CBINV
STY $0317
CLI ;Enable Interrupts
LDA #$00 Return "Modified"
RTS
;setnmi() - Set NMI Interrupt Handler Address
;Args: Y = Address MSB
; X = Address LSB
;Returns: A = $00 - Successfully Set
SETNMI: STX $0318 ;Store Address in NMINV
STY $0319
LDA #$00 ;Return "Modified"
RTS
;xitirq - Exit from IRQ Interrupt
;Exit IRQ if not Executing System IRQ Routine
XITIRQ: PLA ;Restore Y Register
TAY
PLA ;Restore Y Register
TAX
PLA ;Restore Accumulator
RTI ;Return from Interrupt

75
include/vic/vectors.h02 Normal file
View File

@ -0,0 +1,75 @@
/*********************************************************
* vector - 6502 Interrupt Vector Manipulation Functions *
*********************************************************/
/* Get BRK Handler Address *
* Returns: Status *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
* Address MSB *
* Address LSB */
char getbrk();
/* Get IRQ Handler Address *
* Returns: Status *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
* Address MSB *
* Address LSB */
char getirq();
/* Get NMI Handler Address *
* Returns: Status *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
* Address MSB *
* Address LSB */
char getnmi();
/* Get RESET Handler Address *
* Returns: Status *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
* Address MSB *
* Address LSB */
char getrst();
/* Set BRK Handler Address */
* Args: &d - New Address *
* Returns: Result *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
char setbrk();
/* Set IRQ Handler Address */
* Args: &d - New Address *
* Returns: Result *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
char setirq();
/* Set NMI Handler Address */
* Args: &d - New Address *
* Returns: Result *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
char setnmi();
/* Set RESET Handler Address */
* Args: &d - New Address *
* Returns: Result *
* $00 = modifiable *
* $7F = hard coded *
* $FF = unavailable *
char setrst();
/* Exit from IRQ Interrupt */
xitirq:

View File

@ -4,6 +4,7 @@
#define DELKEY $14 //Delete/Backspace Key (DEL)
#define ESCKEY $03 //Escape/Break Key (STOP)
#define RTNKEY $0D //Return/Enter Key (RETURN)
#define SYSBFL 88 //System Buffer Length
/* Standard Library Pointers */
char srclo,srchi; //Source String Pointer for Library Functions
@ -20,6 +21,7 @@ char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char temp0, temp1, temp2, temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
/* System Subroutines */
void delchr(); //Delete previous character

View File

@ -6,6 +6,7 @@
#define DELKEY $14 //Delete/Backspace Key (DEL)
#define ESCKEY $03 //Escape/Stop Key (STOP)
#define RTNKEY $0D //Return/Enter Key (RETURN)
#define SYSBFL 88 //System Buffer Length
//Library Pointer Variables
char srclo,srchi; //Source String Pointer for Library Functions
@ -21,6 +22,7 @@ char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char temp0, temp1, temp2, temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
//System Subroutines
char polkey(); //Poll Console for character

View File

@ -6,6 +6,7 @@
#define DELKEY $14 //Delete/Backspace Key (DEL)
#define ESCKEY $03 //Escape/Stop Key (STOP)
#define RTNKEY $0D //Return/Enter Key (RETURN)
#define SYSBFL 88 //System Buffer Length
//Library Pointer Variables
char srclo,srchi; //Source String Pointer for Library Functions
@ -21,6 +22,7 @@ char stkslo, stkshi; //Stack Start Address
char stkelo, stkehi; //Stsck End Address
char random, rdseed; //Pseudo-Random Number Generation
char temp0, temp1, temp2, temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
//System Subroutines
char polkey(); //Poll Console for character

View File

@ -6,9 +6,9 @@ DELKEY EQU $14 ;Delete/Backspace Key (Delete)
ESCKEY EQU $03 ;Escape/Stop Key (RUN/STOP)
RTNKEY EQU $0D ;Return/Enter Key (RETURN)
;Zero Page System Variables - x16emu Release 34 Memory Map
;UNUSED $00-$01 ;Available to User
; $02-$52 ;Used by Basic graphics commands
; $00-$01 ;Miscellaneous Pointer
; $02-$21 ;ABI Registers
; $22-$52 ;Used by Basic graphics commands
XMBANK EQU $53 ;Extended Memory Bank
XADRLO EQU $54 ;Ext Memory Address LSB
XADRHI EQU $55 ;Ext Memory Address MSB
@ -30,12 +30,16 @@ TEMP0 EQU $64 ;Temporary Variable
TEMP1 EQU $65 ;Temporary Variable
TEMP2 EQU $66 ;Temporary Variable
TEMP3 EQU $67 ;Temporary Variable
; $68-7F ;Available to User
SYSBFP EQU $68 ;Position in System Buffer [Free Byte]
; $69-7F ;Available to User
; $80-$83 ;Used by Kernal and DOS
; $A4-$A8 ;Reserved for KERNAL/DOS/BASIC
; $A9-$FF ;Used by BASIC
;Other Variables - Top of Extended System RAM Area
;Other Constants
SYSBFL EQU 128 ;System Buffer Length
;Other Variables - User Storage Area
SYSBFR EQU $0700 ;System Buffer
BLKSLO EQU $07F4 ;Block Start LSB
BLKSHI EQU $07F5 ;Block Start MSB
BLKELO EQU $07F6 ;Block End LSB
@ -92,5 +96,5 @@ DELCHR: LDA #DELKEY ;Load Delete Character
NEWLIN: LDA #RTNKEY ;Load Return Character
JMP PUTCHR ;Print and Return
INCLUDE "../include/prbyte.a02" ;PRBYTE and PRHEX routine
INCLUDE "../include/putstr.a02" ;PUTSTR routine
INCLUDE "prbyte.a02" ;PRBYTE and PRHEX routine
INCLUDE "putstr.a02" ;PUTSTR routine

View File

@ -1,17 +1,18 @@
/* C02 System Header file for Commander X16 */
/* Platform Specific Settings */
#pragma zeropage $68 //Unused Zero Page - $68-$7F
#pragma zeropage $69 //Unused Zero Page - $69-$7F
/* Platform Specific Constants */
#define DELKEY $14 //Delete/Backspace Key (DEL)
#define ESCKEY $03 //Escape/Break Key (STOP)
#define RTNKEY $0D //Return/Enter Key (RETURN)
#define SYSBFL 128 //System Buffer Length
/* Standard Library Pointers */
zeropage char srclo,srchi; //Source Pointer for Library Functions
zeropage char dstlo,dsthi; //String Pointer for Library Functions
zeropage int srcptr,dstptr; //Source, Destination Pointers
zeropage int srcptr,dstptr; //Source, Destination Pointers
zeropage char bfrlo,bfrhi; //Buffer Pointer for Library Functions
zeropage char blklo,blkhi; //Block Segment Pointer
zeropage char stklo,stkhi; //Stack Pointer
@ -24,22 +25,22 @@ char blklen; //Block Segment Length
char stkslo,stkshi; //Stack Start Address
char stkelo,stkehi; //Stsck End Address
char random,rdseed; //Pseudo-Random Number Generation
char temp0,temp1,temp2,temp3; //Temporary Storage
char xmbank; //Physical Bank
char temp0,temp1,temp2,temp3; //Temporary Storage
char sysbfr[], sysbfp; //System String Buffer and Position
/* System Subroutines */
void delchr(); //Delete previous character
char getkey(); //Read ASCII character from Keyboard
char getpos(); //Get Cursor Position
char getsiz(); //Get Screen Size
void newlin(); //Advance cursor to beginning of next line
char polkey(); //Poll Keyboard for character
char putchr(); //Print ASCII character to Keyboard
char putchr(); //Print ASCII character to Screen
void prbyte(); //Print Accumulator as Hexadadecimal number
void prhex(); //Print Low Nybble of Accumulator as Hex Digit
char getchr(); //Wait for character from Keyboard
void setpos(); //Set Cursor Position
void putstr(); //Print String to Screen
//System Labels
start: //Start of Code
exit: //Return to Operating System