mirror of
https://github.com/RevCurtisP/C02.git
synced 2025-02-17 21:30:34 +00:00
Updated stdio and stdiox to reference DSTPTR and SRCPTR
This commit is contained in:
parent
2767158d30
commit
af26c34c76
@ -1,8 +1,10 @@
|
|||||||
; C02 library stdio.h02 assembly language subroutines
|
; C02 library stdio.h02 assembly language subroutines
|
||||||
; Requires external routines GETKEY, PRCHR, DELCHR, NEWLIN, and SETSRC
|
; Requires external routines GETKEY, PRCHR, DELCHR, NEWLIN, and SETSRC
|
||||||
; external zero page locations SRCLO and SRCHI
|
; external zero page location SRCPTR
|
||||||
; and external constants DELKEY, ESCKEY, and RTNKEY
|
; and external constants DELKEY, ESCKEY, and RTNKEY
|
||||||
|
|
||||||
|
SUBROUTINE STDIO
|
||||||
|
|
||||||
;char getc() - GET Character from keyborad
|
;char getc() - GET Character from keyborad
|
||||||
;Sets: System Dependent
|
;Sets: System Dependent
|
||||||
;Uses: System Dependent
|
;Uses: System Dependent
|
||||||
@ -20,36 +22,36 @@ PUTC EQU PUTCHR ;Alias to external PUTCHR Routine
|
|||||||
|
|
||||||
;char gets(&s) - GET String input from keyboard
|
;char gets(&s) - GET String input from keyboard
|
||||||
;Args: Y,X = Address of String
|
;Args: Y,X = Address of String
|
||||||
;Sets: SRCLO,SRCLHI = Address of String
|
;Sets: SRCPTR = Address of String
|
||||||
;Uses: TEMP3
|
;Uses: TEMP3
|
||||||
;Affects: X,N,Z,C
|
;Affects: X,N,Z,C
|
||||||
;Returns: A,Y = Number of Characters in String
|
;Returns: A,Y = Number of Characters in String
|
||||||
GETS: JSR SETSRC ;Initialize Source String
|
GETS: JSR SETSRC ;Initialize Source String
|
||||||
GETSL: STY TEMP3 ;Save Y Index
|
.GSLOOP STY TEMP3 ;Save Y Index
|
||||||
JSR GETC ;Get Keypress
|
JSR GETC ;Get Keypress
|
||||||
CMP #DELKEY ;If Delete
|
CMP #DELKEY ;If Delete
|
||||||
BNE GETSE ;Then
|
BNE .GSESC ;Then
|
||||||
TYA ; If Offset is Zero
|
TYA ; If Offset is Zero
|
||||||
BEQ GETSL ; Get Next Character
|
BEQ .GSLOOP ; Get Next Character
|
||||||
DEY ; Else Decrement Offset
|
DEY ; Else Decrement Offset
|
||||||
JSR DELCHR ; Delete Previous Character
|
JSR DELCHR ; Delete Previous Character
|
||||||
JMP GETSL ; and Get Next Character
|
JMP .GSLOOP ; and Get Next Character
|
||||||
GETSE: CMP #ESCKEY ;Else If Escape
|
.GSESC CMP #ESCKEY ;Else If Escape
|
||||||
BNE GETSC ;Then
|
BNE .GSCR ;Then
|
||||||
LDY #$FF ; Return -1
|
LDY #$FF ; Return -1
|
||||||
BNE GETSY
|
BNE .GSRTNY
|
||||||
GETSC: CMP #RTNKEY ;Else If Not Carriage Return
|
.GSCR CMP #RTNKEY ;Else If Not Carriage Return
|
||||||
BEQ GETSX
|
BEQ .GSDONE
|
||||||
JSR PUTC ; Echo Character
|
JSR PUTC ; Echo Character
|
||||||
LDY TEMP3 ;Restore Y Index
|
LDY TEMP3 ;Restore Y Index
|
||||||
STA (SRCLO),Y ; Store Character at offset
|
STA (SRCPTR),Y ; Store Character at offset
|
||||||
INY ; increment offset and
|
INY ; increment offset and
|
||||||
BPL GETSL ; loop if less than 128
|
BPL .GSLOOP ; loop if less than 128
|
||||||
GETSX: JSR NEWLIN ;Else Advance Cursor to Next Line
|
.GSDONE JSR NEWLIN ;Else Advance Cursor to Next Line
|
||||||
LDY TEMP3 ;Restore Y Index
|
LDY TEMP3 ;Restore Y Index
|
||||||
LDA #$00 ; Terminate String
|
LDA #$00 ; Terminate String
|
||||||
STA (SRCLO),Y ; and
|
STA (SRCPTR),Y ; and
|
||||||
GETSY: TYA ; Return String Length
|
.GSRTNY TYA ; Return String Length
|
||||||
RTS
|
RTS
|
||||||
|
|
||||||
;char puts(&s) - PUT String to screen
|
;char puts(&s) - PUT String to screen
|
||||||
@ -63,18 +65,18 @@ PUTS: LDA #$00 ;Set Start Position to 0
|
|||||||
;char putsub(n, &s) - PUT SUBstring to screen
|
;char putsub(n, &s) - PUT SUBstring to screen
|
||||||
;Args: A = Starting Position in String
|
;Args: A = Starting Position in String
|
||||||
; Y,X = Address of String
|
; Y,X = Address of String
|
||||||
;Sets: SRCLO,SRCLHI = Address of String
|
;Sets: SRCPTR = Address of String
|
||||||
;Calls: PUTC
|
;Calls: PUTC
|
||||||
;Affects: N,Z,C
|
;Affects: N,Z,C
|
||||||
;Returns: A,Y = Number of Characters in String
|
;Returns: A,Y = Number of Characters in String
|
||||||
PUTSUB: JSR SETSRC ;Initialize Source String
|
PUTSUB: JSR SETSRC ;Initialize Source String
|
||||||
TAY ;Initialize character offset
|
TAY ;Initialize character offset
|
||||||
PUTSUL: LDA (SRCLO),Y ;Read next character in string
|
.PSLOOP LDA (SRCPTR),Y ;Read next character in string
|
||||||
BEQ PUTSUX ;If Not 0
|
BEQ .PSDONE ;If Not 0
|
||||||
JSR PUTC ; Print character at offset,
|
JSR PUTC ; Print character at offset,
|
||||||
INY ; increment offset, and
|
INY ; increment offset, and
|
||||||
BPL PUTSUL ; loop if less than 128
|
BPL .PSLOOP ; loop if less than 128
|
||||||
PUTSUX: TYA ;Return number of
|
.PSDONE TYA ;Return number of
|
||||||
RTS ; characters printed
|
RTS ; characters printed
|
||||||
|
|
||||||
;char putln(&s) - PUT LiNe to screen
|
;char putln(&s) - PUT LiNe to screen
|
||||||
@ -82,3 +84,5 @@ PUTSUX: TYA ;Return number of
|
|||||||
;Calls: PUTS and NEWLIN
|
;Calls: PUTS and NEWLIN
|
||||||
PUTLN: JSR PUTS ;Write string to screen
|
PUTLN: JSR PUTS ;Write string to screen
|
||||||
JMP NEWLIN ;Execute external NEWLINe routine and return
|
JMP NEWLIN ;Execute external NEWLINe routine and return
|
||||||
|
|
||||||
|
ENDSUBROUTINE
|
@ -2,34 +2,45 @@
|
|||||||
* stdio - Standard I/O Routines for C02 *
|
* stdio - Standard I/O Routines for C02 *
|
||||||
*****************************************/
|
*****************************************/
|
||||||
|
|
||||||
/* Read Character from Keyboard *
|
/* Get Character
|
||||||
* Waits for Keypress *
|
* Waits for key to be pressed *
|
||||||
* Returns: ASCII value of Key */
|
* and Returns ASCII key value *
|
||||||
|
* Returns: char c = Key Value */
|
||||||
char getc();
|
char getc();
|
||||||
|
|
||||||
/* Write Character to Screen *
|
/* Put Character *
|
||||||
* Args: c - ASCII character to write */
|
* Prints Character on Screen *
|
||||||
|
* Args: char c - Character to Print */
|
||||||
void putc();
|
void putc();
|
||||||
|
|
||||||
/* Read String from Keyboard *
|
/* Get String
|
||||||
* Buffers string until C/R is pressed *
|
* Reads String from Keyboard, up *
|
||||||
* Args: &s - string read from keyboard *
|
* to 128 characters until the Return *
|
||||||
* Returns: length of string */
|
* key is pressed. If the Escape key *
|
||||||
|
* is pressed, input is aborted and *
|
||||||
|
* the string is set to "" *
|
||||||
|
* Args: int &s - string to read *
|
||||||
|
* Returns: char n - Length of String *
|
||||||
|
* $FF = Escape Pressed */
|
||||||
char gets();
|
char gets();
|
||||||
|
|
||||||
/* Write String to Screen *
|
/* Put String
|
||||||
* Args: &s - string to print from *
|
* Prints String on Screen *
|
||||||
* Returns: ending position in string */
|
* Args: int &s - String to Print *
|
||||||
|
* Returns: char n - Characters Printed */
|
||||||
char puts();
|
char puts();
|
||||||
|
|
||||||
/* Write Partial String to Screen *
|
/* Put Substring *
|
||||||
* Args: n - starting position in string *
|
* Prints String to Screen starting *
|
||||||
* &s - string to print from *
|
* at specified position *
|
||||||
* Returns: ending position in string */
|
* Args: char p - Starting Position *
|
||||||
|
* int &s - String to Print *
|
||||||
|
* Returns: char e - Ending Position */
|
||||||
char putsub();
|
char putsub();
|
||||||
|
|
||||||
/* Write String to Screen and Move *
|
/* Put Line *
|
||||||
* Cursor to Beginning of Next Line *
|
* Prints String on Screen and moves *
|
||||||
* Args: &s - string to print to screen *
|
* cursor to beginning of next line *
|
||||||
* Returns: number of characters printed */
|
* Args: int &s - String to Print *
|
||||||
|
* Returns: char n - Characters Printed */
|
||||||
char putln();
|
char putln();
|
||||||
|
@ -1,7 +1,8 @@
|
|||||||
; C02 library stdiox.h02 assembly language subroutines
|
; C02 library stdiox.h02 assembly language subroutines
|
||||||
|
|
||||||
ANYKEP: DC "PRESS ANY KEY...",0
|
SUBROUTINE STDIOX
|
||||||
|
|
||||||
|
.ANYKEY BYTE "PRESS ANY KEY...",0
|
||||||
;
|
;
|
||||||
;char anykey(nls) - wait for character with ANY KEY prompt
|
;char anykey(nls) - wait for character with ANY KEY prompt
|
||||||
;Args: A = Print Newlines (0 = No, otherwise Yes)
|
;Args: A = Print Newlines (0 = No, otherwise Yes)
|
||||||
@ -9,8 +10,8 @@ ANYKEP: DC "PRESS ANY KEY...",0
|
|||||||
;Affects: C,N,Z
|
;Affects: C,N,Z
|
||||||
;Returns: A = Character code of keypress
|
;Returns: A = Character code of keypress
|
||||||
ANYKEY: JSR NEWLIN ;Start at Beginning of Next Line
|
ANYKEY: JSR NEWLIN ;Start at Beginning of Next Line
|
||||||
.NONL LDY #>ANYKEP ;Load Prompt High Byte
|
.NONL LDY #>.ANYKEY ;Load Prompt High Byte
|
||||||
LDX #<ANYKEP ;Load Prompt Low Byte
|
LDX #<.ANYKEY ;Load Prompt Low Byte
|
||||||
;Drop into GETCPR
|
;Drop into GETCPR
|
||||||
|
|
||||||
;char getcpr(nls, &s) - GET Character with PRompt
|
;char getcpr(nls, &s) - GET Character with PRompt
|
||||||
@ -35,15 +36,15 @@ GETCPR: JSR PUTS ;Print Prompt
|
|||||||
;Args: A = number to print
|
;Args: A = number to print
|
||||||
;Destroys: TEMP0, TEMP1
|
;Destroys: TEMP0, TEMP1
|
||||||
;Affects: A,Y,C,N,X
|
;Affects: A,Y,C,N,X
|
||||||
PUTBIN: LDY #$FF ;Set Bitmask to All 1's
|
PUTBIN: LDY #$FF ;Set Bit Mask to All 1's
|
||||||
|
|
||||||
;void putmsk(b) - PUT bitMaSK
|
;void putmsk(b) - PUT Bit Mask
|
||||||
;Args: A = byte to print
|
;Args: A = byte to print
|
||||||
; Y = Bitmask
|
; Y = Bit Mask
|
||||||
;Destroys: TEMP0, TEMP1
|
;Destroys: TEMP0, TEMP1
|
||||||
;Affects: A,Y,C,N,X
|
;Affects: A,Y,C,N,X
|
||||||
PUTMSK: STA TEMP2 ;Save Byte
|
PUTMSK: STA TEMP2 ;Save Byte
|
||||||
STY TEMP1 ;Save Bitmask
|
STY TEMP1 ;Save Bit Mask
|
||||||
LDX #8 ;Print 8 Binary Digits
|
LDX #8 ;Print 8 Binary Digits
|
||||||
.MASKL LDA #0 ;Clear Accumulator
|
.MASKL LDA #0 ;Clear Accumulator
|
||||||
ASL TEMP2 ;Shift Top Bit Out of Byte
|
ASL TEMP2 ;Shift Top Bit Out of Byte
|
||||||
@ -128,11 +129,11 @@ PUTDGT: ORA #$30 ;Convert to ASCII digit
|
|||||||
;puthex(b) - PUT HEXadecimal
|
;puthex(b) - PUT HEXadecimal
|
||||||
PUTHEX EQU PRBYTE ;Print Byte as Hexadecimal
|
PUTHEX EQU PRBYTE ;Print Byte as Hexadecimal
|
||||||
|
|
||||||
;putinr(&.HEXW) - PUT INteger Right justified
|
;putinr(i) - PUT INteger Right justified
|
||||||
PUTINR: SEC ;Mode = Justified
|
PUTINR: SEC ;Mode = Justified
|
||||||
BCS .PUTINT ;Print Integer
|
BCS .PUTINT ;Print Integer
|
||||||
|
|
||||||
;putint(&.HEXW) - PUT INTeger
|
;putint(i) - PUT INTeger
|
||||||
PUTINT: CLC ;Mode = Not Justified
|
PUTINT: CLC ;Mode = Not Justified
|
||||||
.PUTINT JSR CVIBCD ;Convert Integer to Packed BCD
|
.PUTINT JSR CVIBCD ;Convert Integer to Packed BCD
|
||||||
LDY #4 ;Set Initial Digit Number
|
LDY #4 ;Set Initial Digit Number
|
||||||
@ -170,20 +171,20 @@ PUTSQB: JSR SAVRXY ;Save Address
|
|||||||
; X = Value Low Byte
|
; X = Value Low Byte
|
||||||
;Calls: PUTHEX = Print Byte
|
;Calls: PUTHEX = Print Byte
|
||||||
; SAVRXY = Save X and Y Registers
|
; SAVRXY = Save X and Y Registers
|
||||||
; .PUTWRD = Put .HEXW (Alternate Entry Point)
|
; PUTWRT = Put .HEXW (Alternate Entry Point)
|
||||||
;Affects: A,Y,X,N,Z,C
|
;Affects: A,Y,X,N,Z,C
|
||||||
PUTEXH: JSR SAVRXY ;Save High and Low Bytes
|
PUTEXH: JSR SAVRXY ;Save High and Low Bytes
|
||||||
JSR PUTHEX ;Print Extended Byte
|
JSR PUTHEX ;Print Extended Byte
|
||||||
JMP .PUTWRD ;Print High and Low Bytes
|
JMP PUTWRT ;Print TEMP2, TEMP1 as HEX word
|
||||||
|
|
||||||
;putwrd(&.HEXW) - PUT .HEXW
|
;putwrd(&HEXW) - PUT WORD
|
||||||
;Args: Y = .HEXW MSB
|
;Args: Y = .HEXW MSB
|
||||||
; X = .HEXW LSB
|
; X = .HEXW LSB
|
||||||
;Calls: PUTHEX = Print Byte
|
;Calls: PUTHEX = Print Byte
|
||||||
; SAVRXY = Save X and Y Registers
|
; SAVRXY = Save X and Y Registers
|
||||||
;Affects: A,Y,X,N,Z,C
|
;Affects: A,Y,X,N,Z,C
|
||||||
PUTWRD: JSR SAVRXY ;Save .HEXW
|
PUTWRD: JSR SAVRXY ;Save .HEXW
|
||||||
.PUTWRD LDA TEMP2 ;Load .HEXW MSB
|
PUTWRT: LDA TEMP2 ;Load .HEXW MSB
|
||||||
JSR PUTHEX ;Print as Hexadecimal
|
JSR PUTHEX ;Print as Hexadecimal
|
||||||
LDA TEMP1 ;Load .HEXW LSB
|
LDA TEMP1 ;Load .HEXW LSB
|
||||||
JMP PUTHEX ;Print and Return`
|
JMP PUTHEX ;Print and Return`
|
||||||
@ -205,14 +206,14 @@ PUTRPT: JSR PUTCHR ;Print Space Character
|
|||||||
;void printf(b, &s) - PRINT Formatted byte and/or string
|
;void printf(b, &s) - PRINT Formatted byte and/or string
|
||||||
;Args: A = byte to format
|
;Args: A = byte to format
|
||||||
; Y,X = address of formatting string
|
; Y,X = address of formatting string
|
||||||
;Uses: DSTLO,DSTHI = Address of %S string
|
;Uses: DSTPTR = Address of %S string
|
||||||
;Sets: SRCLO,SRCHI = Address of formatting string
|
;Sets: SRCPTR = Address of formatting string
|
||||||
; TEMP3 - number to format
|
; TEMP3 - number to format
|
||||||
;Destroys: TEMP0,TEMP1,TEMP2
|
;Destroys: TEMP0,TEMP1,TEMP2
|
||||||
;Returns: A,Y = Total number of characters printed
|
;Returns: A,Y = Total number of characters printed
|
||||||
PRINTF: STA TEMP3 ;Save Byte to Format
|
PRINTF: STA TEMP3 ;Save Byte to Format
|
||||||
JSR SETSRC ;Initialize Source String
|
JSR SETSRC ;Initialize Source String
|
||||||
.FLOOP LDA (SRCLO),Y ;Read next character in string
|
.FLOOP LDA (SRCPTR),Y ;Read next character in string
|
||||||
BEQ .FDONE ;If Not 0
|
BEQ .FDONE ;If Not 0
|
||||||
CMP #'%' ; If Format Specified
|
CMP #'%' ; If Format Specified
|
||||||
BEQ .FEVAL ; Jump to Formatter
|
BEQ .FEVAL ; Jump to Formatter
|
||||||
@ -223,7 +224,7 @@ PRINTF: STA TEMP3 ;Save Byte to Format
|
|||||||
RTS ; characters printed
|
RTS ; characters printed
|
||||||
;Process Format Specifier
|
;Process Format Specifier
|
||||||
.FEVAL: INY ;Increment Offset
|
.FEVAL: INY ;Increment Offset
|
||||||
LDA (SRCLO),Y ;Get Formatting Character
|
LDA (SRCPTR),Y ;Get Formatting Character
|
||||||
BEQ .FDONE ;If NUL, then Exit
|
BEQ .FDONE ;If NUL, then Exit
|
||||||
CMP #'%' ;If Percent Sign
|
CMP #'%' ;If Percent Sign
|
||||||
BEQ .FPUTC ; Print it and Continue
|
BEQ .FPUTC ; Print it and Continue
|
||||||
@ -325,3 +326,5 @@ PUTDST LDY #0 ;Initialize character offset
|
|||||||
BPL .DLOOP ; loop if less than 128
|
BPL .DLOOP ; loop if less than 128
|
||||||
.DRETY TYA ;Return number of
|
.DRETY TYA ;Return number of
|
||||||
RTS ; characters printed
|
RTS ; characters printed
|
||||||
|
|
||||||
|
ENDSUBROUTINE
|
||||||
|
@ -2,78 +2,113 @@
|
|||||||
* stdiox - Extended I/O Routines for C02 *
|
* stdiox - Extended I/O Routines for C02 *
|
||||||
******************************************/
|
******************************************/
|
||||||
|
|
||||||
/* Display "Press any key to continue" *
|
/* Any Key *
|
||||||
* prompt and wait fo keypress *
|
* Displays "Press any key to continue" *
|
||||||
* Returns: ASCII value of key pressed */
|
* prompt and wait for key to be pressed *
|
||||||
|
* Returns: char c - ASCII Value of Key */
|
||||||
void anykey();
|
void anykey();
|
||||||
|
|
||||||
/* Display prompt and wait for keypress *
|
/* Get Character with Prompt *
|
||||||
* Args: &s - string to display *
|
* Displays prompt and waits for key *
|
||||||
* Returns: ASCII value of key pressed */
|
* to be pressed *
|
||||||
|
* Args: int &s - Prompt *
|
||||||
|
* Returns: char c - ASCII Value of Key */
|
||||||
void getcpr();
|
void getcpr();
|
||||||
|
|
||||||
/* Print Formatted Byte to Screen *
|
/* Print Formatted *
|
||||||
* Args: b - byte to format *
|
* Prints char value, and/or contents *
|
||||||
* &s - formatting string */
|
* of dstptr on screen formatted by *
|
||||||
|
* Args: char c - Character to Format *
|
||||||
|
* int &s - Formatting String */
|
||||||
void printf();
|
void printf();
|
||||||
|
|
||||||
/* Print Byte as Binary Number *
|
/* Put Binary *
|
||||||
* Args: b - Number to print */
|
* Prints byte as binary number *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putbin();
|
void putbin();
|
||||||
|
|
||||||
/* Print Byte as Decimal Number *
|
/* Put Decimal *
|
||||||
* Args: b - Number to print */
|
* Prints byte as decimal number *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putdec();
|
void putdec();
|
||||||
|
|
||||||
/* Print Byte Zero Filled Modulo 100 *
|
/* Put Decimal Hundred *
|
||||||
* Args: b - Number to print */
|
* Prints Byte Modulo 100 as two *
|
||||||
|
* digit zero-filled decimal number *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putdeh();
|
void putdeh();
|
||||||
|
|
||||||
/* Print Byte as Left Justified Decimal *
|
/* Put Decimal Left Justified *
|
||||||
* Args: b - Number to print */
|
* Prints byte as decimal number, *
|
||||||
|
* right-padded with spaces, for a *
|
||||||
|
* total of three charcaters *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putdel();
|
void putdel();
|
||||||
|
|
||||||
/* Print Byte as Right Justified Decimal *
|
/* Put Decimal Right Justified *
|
||||||
* Args: b - Number to print */
|
* Prints byte as decimal number, *
|
||||||
|
* left-padded with spaces, for a *
|
||||||
|
* total of three charcaters *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putder();
|
void putder();
|
||||||
|
|
||||||
/* Print Byte as Zero Filled Decimal Number *
|
/* Put Decimal Zero-Filled *
|
||||||
* Args: b - Number to print */
|
* Prints byte as decimal number, *
|
||||||
|
* left-padded with zeroes, for a *
|
||||||
|
* total of three charcaters *
|
||||||
|
* Args: char b - Number to Print */
|
||||||
void putdez();
|
void putdez();
|
||||||
|
|
||||||
/* Print Destination String */
|
/* Print Destination String *
|
||||||
|
* Prints string with *
|
||||||
|
* address in dstptr *
|
||||||
|
* Return: char n: Characters Printed */
|
||||||
void putdst();
|
void putdst();
|
||||||
|
|
||||||
/* Print Extended Hexadecimal Number *
|
/* Put Extended Hexadecimal *
|
||||||
|
* Prints 24-bit value as six digit *
|
||||||
|
* hexadecimal number *
|
||||||
* Args: char n - High Byte *
|
* Args: char n - High Byte *
|
||||||
* int w - Middle and Low Bytes */
|
* int w - Middle and Low Bytes */
|
||||||
void putexh();
|
void putexh();
|
||||||
|
|
||||||
/* Print Byte as Hexadecimal Number *
|
/* Put Hexadecimal *
|
||||||
* Args: b - Number to print */
|
* Prints byte as two digit *
|
||||||
|
* hexadecimal number *
|
||||||
|
* Args: char b - Byte to Print */
|
||||||
void puthex();
|
void puthex();
|
||||||
|
|
||||||
/* Print Word as Decimal Number *
|
/* Put Integer *
|
||||||
* Args: int w - Number to print */
|
* Prints word as decimal number *
|
||||||
|
* Args: int w - Word to Print */
|
||||||
void putint();
|
void putint();
|
||||||
|
|
||||||
void putwrd();
|
/* Put Mask *
|
||||||
/* Print Byte as Masked Bits *
|
* Prints byte as binary number *
|
||||||
* Args: b - Byte to print *
|
* with bits specified by mask *
|
||||||
* m - Bitmask */
|
* Args: char b - Byte to Print *
|
||||||
|
* char m - Bit Mask */
|
||||||
void putmsk();
|
void putmsk();
|
||||||
|
|
||||||
/* Print Nybble as Hexadecimal Number *
|
/* Put Nybble *
|
||||||
* Args: b - Number to print */
|
* Prints low nybble of byte *
|
||||||
|
* as hexadecimal digit *
|
||||||
|
* Args: char b - Byte to Print */
|
||||||
void putnyb();
|
void putnyb();
|
||||||
|
|
||||||
/* Print a Space Character */
|
/* Put Space *
|
||||||
|
* Prints a space character */
|
||||||
void putspc();
|
void putspc();
|
||||||
|
|
||||||
/* Print Word as Three Hex Digits *
|
/* Put Sesquibyte *
|
||||||
* Args: int w - Number to print */
|
* Prints low three nybbles of word *
|
||||||
|
* as three hexadecimal digits *
|
||||||
|
* Args: int w - Word to Print */
|
||||||
void putsqb();
|
void putsqb();
|
||||||
|
|
||||||
/* Print Word as Hexadecimal Number *
|
/* Put Word *
|
||||||
* Args: int w - Number to print */
|
* Prints word as four-digit *
|
||||||
|
* hexadecimal number *
|
||||||
|
* Args: int w - Word to Print */
|
||||||
void putwrd();
|
void putwrd();
|
||||||
|
|
||||||
|
@ -1,31 +0,0 @@
|
|||||||
/**********************************************
|
|
||||||
* TESTIO - Test Library stdio.h for py65mon *
|
|
||||||
**********************************************/
|
|
||||||
|
|
||||||
#include <py65.h02>
|
|
||||||
#include <stddef.h02>
|
|
||||||
#include <stdio.h02>
|
|
||||||
|
|
||||||
char key; //Key read from keyboard
|
|
||||||
char len; //Length of input output string
|
|
||||||
char str[128]; //String to read/write
|
|
||||||
|
|
||||||
main:
|
|
||||||
putln("Press any key to continue");
|
|
||||||
key = getc(); //Wait for key press
|
|
||||||
newlin(); //Advance cursor to next line
|
|
||||||
|
|
||||||
putln("Type lines followed by carriage-return");
|
|
||||||
putln("press Escape key to end");
|
|
||||||
|
|
||||||
while () {
|
|
||||||
putc('>');
|
|
||||||
len = gets(&str); //Read string from keybaord
|
|
||||||
if (len == $FF) //If entry was aborted
|
|
||||||
break ; // return to monitor
|
|
||||||
puts("You typed: "); //Print without newline
|
|
||||||
putln(&str); //print with newline
|
|
||||||
}
|
|
||||||
|
|
||||||
done:
|
|
||||||
goto exit;
|
|
34
test/siotest.c02
Normal file
34
test/siotest.c02
Normal file
@ -0,0 +1,34 @@
|
|||||||
|
/**********************************************
|
||||||
|
* TESTIO - Test Library stdio.h for py65mon *
|
||||||
|
**********************************************/
|
||||||
|
|
||||||
|
//Specify System Header using -H option
|
||||||
|
#include <stddef.h02>
|
||||||
|
#include <stdio.h02>
|
||||||
|
|
||||||
|
char key; //Key read from keyboard
|
||||||
|
char len; //Length of input output string
|
||||||
|
char str[128]; //String to read/write
|
||||||
|
|
||||||
|
main:
|
||||||
|
putsub(17, "ERROR IN PUTSUB! PRESS ANY KEY");
|
||||||
|
newlin();
|
||||||
|
key = getc(); //Wait for key press
|
||||||
|
newlin(); //Advance cursor to next line
|
||||||
|
|
||||||
|
putln("TYPE LINES, END WITH RETURN");
|
||||||
|
putln("PRESS ESCAPE KEY TO END");
|
||||||
|
|
||||||
|
while () {
|
||||||
|
putc('>');
|
||||||
|
len = gets(&str); //Read string from keybaord
|
||||||
|
if (len == $FF) //If entry was aborted
|
||||||
|
break ; // return to monitor
|
||||||
|
puts("YOU TYPED: "); //Print without newline
|
||||||
|
putln(str); //print with newline
|
||||||
|
}
|
||||||
|
|
||||||
|
putln("TEST COMPLETE");
|
||||||
|
|
||||||
|
done:
|
||||||
|
goto exit;
|
@ -1,6 +1,6 @@
|
|||||||
/***********************************************
|
/************************************
|
||||||
* TESTIOX - Test Library stdiox.h for py65mon *
|
* SIOXTEST - Test module stdiox.h *
|
||||||
***********************************************/
|
************************************/
|
||||||
|
|
||||||
//Specify System Header using -H option
|
//Specify System Header using -H option
|
||||||
#include <screen.h02>
|
#include <screen.h02>
|
Loading…
x
Reference in New Issue
Block a user