Rename blockdev's API routines to GetB/PutB

The goal is to avoid mixing those routines with "character devices"
(acia, vpd, kbd) which aren't block devices and have routines that
have different expectations.

This is a first step to fixing #64.
This commit is contained in:
Virgil Dupras 2019-10-30 16:59:35 -04:00
parent 38333e9e07
commit b745f49186
33 changed files with 280 additions and 279 deletions

View File

@ -9,7 +9,7 @@
; is reached on the block device. ; is reached on the block device.
; *** Requirements *** ; *** Requirements ***
; blkGetC ; blkGetB
; parseArgs ; parseArgs
; ;
; *** Includes *** ; *** Includes ***

View File

@ -7,7 +7,7 @@
; *** Variables *** ; *** Variables ***
.equ AT28W_MAXBYTES AT28W_RAMSTART .equ AT28W_MAXBYTES AT28W_RAMSTART
.equ AT28W_RAMEND AT28W_MAXBYTES+2 .equ AT28W_RAMEND @+2
; *** Code *** ; *** Code ***
at28wMain: at28wMain:
@ -33,7 +33,7 @@ at28wInner:
; BC is zero, default to 0x2000 (8k, the size of the AT28) ; BC is zero, default to 0x2000 (8k, the size of the AT28)
ld bc, 0x2000 ld bc, 0x2000
.loop: .loop:
call blkGetC call blkGetB
jr nz, .loopend jr nz, .loopend
ld (hl), a ld (hl), a
ld e, a ; save expected data for verification ld e, a ; save expected data for verification

View File

@ -4,14 +4,14 @@
; Number of lines currently in the buffer ; Number of lines currently in the buffer
.equ BUF_LINECNT BUF_RAMSTART .equ BUF_LINECNT BUF_RAMSTART
; List of pointers to strings in scratchpad ; List of pointers to strings in scratchpad
.equ BUF_LINES BUF_LINECNT+2 .equ BUF_LINES @+2
; Points to the end of the scratchpad, that is, one byte after the last written ; Points to the end of the scratchpad, that is, one byte after the last written
; char in it. ; char in it.
.equ BUF_PADEND BUF_LINES+ED_BUF_MAXLINES*2 .equ BUF_PADEND @+ED_BUF_MAXLINES*2
; The in-memory scratchpad ; The in-memory scratchpad
.equ BUF_PAD BUF_PADEND+2 .equ BUF_PAD @+2
.equ BUF_RAMEND BUF_PAD+ED_BUF_PADMAXLEN .equ BUF_RAMEND @+ED_BUF_PADMAXLEN
; *** Code *** ; *** Code ***
@ -25,7 +25,7 @@ bufInit:
; init pad end in case we have an empty file. ; init pad end in case we have an empty file.
ld (BUF_PADEND), hl ld (BUF_PADEND), hl
.loop: .loop:
call ioGetC call ioGetB
jr nz, .loopend jr nz, .loopend
or a ; null? hum, weird. same as LF or a ; null? hum, weird. same as LF
jr z, .lineend jr z, .lineend

View File

@ -13,9 +13,9 @@
; An address is a one byte type and a two bytes line number (0-indexed) ; An address is a one byte type and a two bytes line number (0-indexed)
.equ CMD_ADDR1 CMD_RAMSTART .equ CMD_ADDR1 CMD_RAMSTART
.equ CMD_ADDR2 CMD_ADDR1+3 .equ CMD_ADDR2 @+3
.equ CMD_TYPE CMD_ADDR2+3 .equ CMD_TYPE @+3
.equ CMD_RAMEND CMD_TYPE+1 .equ CMD_RAMEND @+1
; *** Code *** ; *** Code ***
@ -89,11 +89,11 @@ cmdParse:
jr z, .dot jr z, .dot
cp '$' cp '$'
jr z, .eof jr z, .eof
; inline parseDecimalDigit ; inline parseDecimalDigit
add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff
sub 0xff-9 ; maps to 0-9 and carries if not a digit sub 0xff-9 ; maps to 0-9 and carries if not a digit
jr c, .notHandled jr c, .notHandled
; straight number ; straight number
ld a, ABSOLUTE ld a, ABSOLUTE
@ -125,11 +125,11 @@ cmdParse:
inc hl ; advance cmd cursor inc hl ; advance cmd cursor
ld a, (hl) ld a, (hl)
ld de, 1 ; if .pmNoSuffix ld de, 1 ; if .pmNoSuffix
; inline parseDecimalDigit ; inline parseDecimalDigit
add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff
sub 0xff-9 ; maps to 0-9 and carries if not a digit sub 0xff-9 ; maps to 0-9 and carries if not a digit
jr c, .pmNoSuffix jr c, .pmNoSuffix
call .parseDecimalM ; --> DE call .parseDecimalM ; --> DE
.pmNoSuffix: .pmNoSuffix:
@ -157,11 +157,11 @@ cmdParse:
.loop: .loop:
inc hl inc hl
ld a, (hl) ld a, (hl)
; inline parseDecimalDigit ; inline parseDecimalDigit
add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff add a, 0xff-'9' ; maps '0'-'9' onto 0xf6-0xff
sub 0xff-9 ; maps to 0-9 and carries if not a digit sub 0xff-9 ; maps to 0-9 and carries if not a digit
jr nc, .loop jr nc, .loop
; We're at the first non-digit char. Let's save it because we're going ; We're at the first non-digit char. Let's save it because we're going
; to temporarily replace it with a null. ; to temporarily replace it with a null.

View File

@ -9,10 +9,10 @@
; Handle of the target file ; Handle of the target file
.equ IO_FILE_HDL IO_RAMSTART .equ IO_FILE_HDL IO_RAMSTART
; block device targeting IO_FILE_HDL ; block device targeting IO_FILE_HDL
.equ IO_BLK IO_FILE_HDL+FS_HANDLE_SIZE .equ IO_BLK @+FS_HANDLE_SIZE
; Buffer for lines read from I/O. ; Buffer for lines read from I/O.
.equ IO_LINE IO_BLK+BLOCKDEV_SIZE .equ IO_LINE @+BLOCKDEV_SIZE
.equ IO_RAMEND IO_LINE+IO_MAXLEN+1 ; +1 for null .equ IO_RAMEND @+IO_MAXLEN+1 ; +1 for null
; *** Code *** ; *** Code ***
; Given a file name in (HL), open that file in (IO_FILE_HDL) and open a blkdev ; Given a file name in (HL), open that file in (IO_FILE_HDL) and open a blkdev
@ -25,26 +25,26 @@ ioInit:
ld de, IO_BLK ld de, IO_BLK
ld hl, .blkdev ld hl, .blkdev
jp blkSet jp blkSet
.fsGetC: .fsGetB:
ld ix, IO_FILE_HDL ld ix, IO_FILE_HDL
jp fsGetC jp fsGetB
.fsPutC: .fsPutB:
ld ix, IO_FILE_HDL ld ix, IO_FILE_HDL
jp fsPutC jp fsPutB
.blkdev: .blkdev:
.dw .fsGetC, .fsPutC .dw .fsGetB, .fsPutB
ioGetC: ioGetB:
push ix push ix
ld ix, IO_BLK ld ix, IO_BLK
call _blkGetC call _blkGetB
pop ix pop ix
ret ret
ioPutC: ioPutB:
push ix push ix
ld ix, IO_BLK ld ix, IO_BLK
call _blkPutC call _blkPutB
pop ix pop ix
ret ret
@ -76,14 +76,14 @@ ioPutLine:
ld a, (hl) ld a, (hl)
or a or a
jr z, .loopend ; null, we're finished jr z, .loopend ; null, we're finished
call ioPutC call ioPutB
jr nz, .error jr nz, .error
inc hl inc hl
jr .loop jr .loop
.loopend: .loopend:
; Wrote the whole line, write ending LF ; Wrote the whole line, write ending LF
ld a, 0x0a ld a, 0x0a
call ioPutC call ioPutB
jr z, .end ; success jr z, .end ; success
; continue to error ; continue to error
.error: .error:

View File

@ -25,16 +25,16 @@
; *** Requirements *** ; *** Requirements ***
; BLOCKDEV_SIZE ; BLOCKDEV_SIZE
; FS_HANDLE_SIZE ; FS_HANDLE_SIZE
; _blkGetC ; _blkGetB
; _blkPutC ; _blkPutB
; _blkSeek ; _blkSeek
; _blkTell ; _blkTell
; addHL ; addHL
; cpHLDE ; cpHLDE
; fsFindFN ; fsFindFN
; fsOpen ; fsOpen
; fsGetC ; fsGetB
; fsPutC ; fsPutB
; fsSetSize ; fsSetSize
; intoHL ; intoHL
; printstr ; printstr
@ -46,7 +46,7 @@
; *** Variables *** ; *** Variables ***
; ;
.equ ED_CURLINE ED_RAMSTART .equ ED_CURLINE ED_RAMSTART
.equ ED_RAMEND ED_CURLINE+2 .equ ED_RAMEND @+2
edMain: edMain:
; because ed only takes a single string arg, we can use HL directly ; because ed only takes a single string arg, we can use HL directly

View File

@ -4,15 +4,15 @@
; sectors. Collapse OS doesn't have a random number generator, so we'll simply ; sectors. Collapse OS doesn't have a random number generator, so we'll simply
; rely on initial SRAM value, which tend is random enough for our purpose. ; rely on initial SRAM value, which tend is random enough for our purpose.
; ;
; How it works is simple. From its designated RAMSTART, it calls PutC until it ; How it works is simple. From its designated RAMSTART, it calls PutB until it
; reaches the end of RAM (0xffff). Then, it starts over and this time it reads ; reaches the end of RAM (0xffff). Then, it starts over and this time it reads
; every byte and compares. ; every byte and compares.
; ;
; If there's an error, prints out where. ; If there's an error, prints out where.
; ;
; *** Requirements *** ; *** Requirements ***
; sdcPutC ; sdcPutB
; sdcGetC ; sdcGetB
; printstr ; printstr
; printHexPair ; printHexPair
; ;

View File

@ -9,7 +9,7 @@ sdctMain:
; we set DE to 12 instead of zero ; we set DE to 12 instead of zero
push de ; <| push de ; <|
ld de, 12 ; | ld de, 12 ; |
call sdcPutC ; | call sdcPutB ; |
pop de ; <| pop de ; <|
jr nz, .error jr nz, .error
inc hl inc hl
@ -30,7 +30,7 @@ sdctMain:
.rLoop: .rLoop:
push de ; <| push de ; <|
ld de, 12 ; | ld de, 12 ; |
call sdcGetC ; | call sdcGetB ; |
pop de ; <| pop de ; <|
jr nz, .error jr nz, .error
ex de, hl ex de, hl

View File

@ -54,7 +54,7 @@ handleDB:
or a ; cp 0 or a ; cp 0
jr nz, .overflow ; not zero? overflow jr nz, .overflow ; not zero? overflow
ld a, l ld a, l
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
.stopStrLit: .stopStrLit:
call readComma call readComma
@ -84,7 +84,7 @@ handleDB:
or a ; when we encounter 0, that was what used to or a ; when we encounter 0, that was what used to
jr z, .stopStrLit ; be our closing quote. Stop. jr z, .stopStrLit ; be our closing quote. Stop.
; Normal character, output ; Normal character, output
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
jr .stringLiteral jr .stringLiteral
@ -98,10 +98,10 @@ handleDW:
jr nz, .badarg jr nz, .badarg
push ix \ pop hl push ix \ pop hl
ld a, l ld a, l
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
ld a, h ld a, h
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
call readComma call readComma
jr z, .loop jr z, .loop
@ -208,7 +208,7 @@ handleFIL:
or c or c
jr z, .loopend jr z, .loopend
xor a xor a
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
dec bc dec bc
jr .loop jr .loop
@ -314,7 +314,7 @@ getDirectiveID:
; Parse directive specified in A (D_* const) with args in I/O and act in ; Parse directive specified in A (D_* const) with args in I/O and act in
; an appropriate manner. If the directive results in writing data at its ; an appropriate manner. If the directive results in writing data at its
; current location, that data is directly written through ioPutC. ; current location, that data is directly written through ioPutB.
; Each directive has the same return value pattern: Z on success, not-Z on ; Each directive has the same return value pattern: Z on success, not-Z on
; error, A contains the error number (ERR_*). ; error, A contains the error number (ERR_*).
parseDirective: parseDirective:

View File

@ -5,9 +5,9 @@
; ;
; We don't buffer the whole source in memory, so we need our input blkdev to ; We don't buffer the whole source in memory, so we need our input blkdev to
; support Seek so we can read the file a second time. So, for input, we need ; support Seek so we can read the file a second time. So, for input, we need
; GetC and Seek. ; GetB and Seek.
; ;
; For output, we only need PutC. Output doesn't start until the second pass. ; For output, we only need PutB. Output doesn't start until the second pass.
; ;
; The goal of the second pass is to assign values to all symbols so that we ; The goal of the second pass is to assign values to all symbols so that we
; can have forward references (instructions referencing a label that happens ; can have forward references (instructions referencing a label that happens
@ -33,11 +33,11 @@
; blkSet ; blkSet
; fsFindFN ; fsFindFN
; fsOpen ; fsOpen
; fsGetC ; fsGetB
; cpHLDE ; cpHLDE
; parseArgs ; parseArgs
; _blkGetC ; _blkGetB
; _blkPutC ; _blkPutB
; _blkSeek ; _blkSeek
; _blkTell ; _blkTell
; printstr ; printstr

View File

@ -888,7 +888,7 @@ parseInstruction:
ld hl, INS_UPCODE ld hl, INS_UPCODE
.loopWrite: .loopWrite:
ld a, (hl) ld a, (hl)
call ioPutC call ioPutB
jr nz, .ioError jr nz, .ioError
inc hl inc hl
djnz .loopWrite djnz .loopWrite

View File

@ -8,7 +8,7 @@
; maintaining IO_PC and of properly disabling output on first pass. ; maintaining IO_PC and of properly disabling output on first pass.
; ;
; On top of that, this unit has the responsibility of keeping track of the ; On top of that, this unit has the responsibility of keeping track of the
; current lineno. Whenever GetC is called, we check if the fetched char is a ; current lineno. Whenever GetB is called, we check if the fetched byte is a
; newline. If it is, we increase our lineno. This unit is the best place to ; newline. If it is, we increase our lineno. This unit is the best place to
; keep track of this because we have to handle ioRecallPos. ; keep track of this because we have to handle ioRecallPos.
; ;
@ -17,7 +17,7 @@
; mechanism, that is, a way to say "you see that character I've just read? that ; mechanism, that is, a way to say "you see that character I've just read? that
; was out of my bounds. Could you make it as if I had never read it?". That ; was out of my bounds. Could you make it as if I had never read it?". That
; buffer is one character big and is made with the expectation that ioPutBack ; buffer is one character big and is made with the expectation that ioPutBack
; is always called right after a ioGetC (when it's called). ; is always called right after a ioGetB (when it's called).
; ;
; ioPutBack will mess up seek and tell offsets, so thath "put back" should be ; ioPutBack will mess up seek and tell offsets, so thath "put back" should be
; consumed before having to seek and tell. ; consumed before having to seek and tell.
@ -25,7 +25,7 @@
; That's for the general rules. ; That's for the general rules.
; ;
; Now, let's enter includes. To simplify processing, we make include mostly ; Now, let's enter includes. To simplify processing, we make include mostly
; transparent to all other units. They always read from ioGetC and a include ; transparent to all other units. They always read from ioGetB and a include
; directive should have the exact same effect as copy/pasting the contents of ; directive should have the exact same effect as copy/pasting the contents of
; the included file in the caller. ; the included file in the caller.
; ;
@ -33,7 +33,7 @@
; can include. ; can include.
; ;
; When we include, all we do here is open the file with fsOpen and set a flag ; When we include, all we do here is open the file with fsOpen and set a flag
; indicating that we're inside an include. When that flag is on, GetC, Seek and ; indicating that we're inside an include. When that flag is on, GetB, Seek and
; Tell are transparently redirected to their fs* counterpart. ; Tell are transparently redirected to their fs* counterpart.
; ;
; When we reach EOF in an included file, we transparently unset the "in include" ; When we reach EOF in an included file, we transparently unset the "in include"
@ -73,7 +73,7 @@ ioInit:
call blkSet call blkSet
jp ioResetCounters jp ioResetCounters
ioGetC: ioGetB:
ld a, (IO_PUTBACK_BUF) ld a, (IO_PUTBACK_BUF)
or a ; cp 0 or a ; cp 0
jr nz, .getback jr nz, .getback
@ -81,7 +81,7 @@ ioGetC:
jr z, .normalmode jr z, .normalmode
; We're in "include mode", read from FS ; We're in "include mode", read from FS
ld ix, IO_INCLUDE_BLK ld ix, IO_INCLUDE_BLK
call _blkGetC call _blkGetB
jr nz, .includeEOF jr nz, .includeEOF
cp 0x0a ; newline cp 0x0a ; newline
ret nz ; not newline? nothing to do ret nz ; not newline? nothing to do
@ -111,7 +111,7 @@ ioGetC:
.normalmode: .normalmode:
; normal mode, read from IN stream ; normal mode, read from IN stream
ld ix, IO_IN_BLK ld ix, IO_IN_BLK
call _blkGetC call _blkGetB
cp 0x0a ; newline cp 0x0a ; newline
ret nz ; not newline? return ret nz ; not newline? return
; inc current lineno ; inc current lineno
@ -133,14 +133,14 @@ _callIX:
jp (ix) jp (ix)
ret ret
; Put back non-zero character A into the "ioGetC stack". The next ioGetC call, ; Put back non-zero character A into the "ioGetB stack". The next ioGetB call,
; instead of reading from IO_IN_BLK, will return that character. That's the ; instead of reading from IO_IN_BLK, will return that character. That's the
; easiest way I found to handle the readWord/gotoNextLine problem. ; easiest way I found to handle the readWord/gotoNextLine problem.
ioPutBack: ioPutBack:
ld (IO_PUTBACK_BUF), a ld (IO_PUTBACK_BUF), a
ret ret
ioPutC: ioPutB:
push hl push hl
ld hl, (IO_PC) ld hl, (IO_PC)
inc hl inc hl
@ -151,7 +151,7 @@ ioPutC:
jr z, .skip jr z, .skip
pop af pop af
ld ix, IO_OUT_BLK ld ix, IO_OUT_BLK
jp _blkPutC jp _blkPutB
.skip: .skip:
pop af pop af
cp a ; ensure Z cp a ; ensure Z
@ -240,7 +240,7 @@ ioOpenInclude:
cp a ; ensure Z cp a ; ensure Z
ret ret
; Open file specified in (HL) and spit its contents through ioPutC ; Open file specified in (HL) and spit its contents through ioPutB
; Sets Z on success. ; Sets Z on success.
ioSpitBin: ioSpitBin:
call fsFindFN call fsFindFN
@ -251,9 +251,9 @@ ioSpitBin:
ld hl, 0 ld hl, 0
.loop: .loop:
ld ix, IO_BIN_HDL ld ix, IO_BIN_HDL
call fsGetC call fsGetB
jr nz, .loopend jr nz, .loopend
call ioPutC call ioPutB
inc hl inc hl
jr .loop jr .loop
.loopend: .loopend:
@ -274,12 +274,12 @@ ioLineNo:
pop af pop af
ret ret
_ioIncGetC: _ioIncGetB:
ld ix, IO_INCLUDE_HDL ld ix, IO_INCLUDE_HDL
jp fsGetC jp fsGetB
_ioIncBlk: _ioIncBlk:
.dw _ioIncGetC, unsetZ .dw _ioIncGetB, unsetZ
; call printstr followed by newline ; call printstr followed by newline
ioPrintLN: ioPrintLN:

View File

@ -128,7 +128,7 @@ zasmParseFile:
ret ret
; Parse next token and accompanying args (when relevant) in I/O, write the ; Parse next token and accompanying args (when relevant) in I/O, write the
; resulting opcode(s) through ioPutC and increases (IO_PC) by the number of ; resulting opcode(s) through ioPutB and increases (IO_PC) by the number of
; bytes written. BC is set to the result of the call to tokenize. ; bytes written. BC is set to the result of the call to tokenize.
; Sets Z if parse was successful, unset if there was an error. EOF is not an ; Sets Z if parse was successful, unset if there was an error. EOF is not an
; error. If there is an error, A is set to the corresponding error code (ERR_*). ; error. If there is an error, A is set to the corresponding error code (ERR_*).

View File

@ -74,12 +74,12 @@ isLabel:
; Read I/O as long as it's whitespace. When it's not, stop and return the last ; Read I/O as long as it's whitespace. When it's not, stop and return the last
; read char in A ; read char in A
_eatWhitespace: _eatWhitespace:
call ioGetC call ioGetB
call isSep call isSep
ret nz ret nz
jr _eatWhitespace jr _eatWhitespace
; Read ioGetC until a word starts, then read ioGetC as long as there is no ; Read ioGetB until a word starts, then read ioGetB as long as there is no
; separator and put that contents in (scratchpad), null terminated, for a ; separator and put that contents in (scratchpad), null terminated, for a
; maximum of SCRATCHPAD_SIZE-1 characters. ; maximum of SCRATCHPAD_SIZE-1 characters.
; If EOL (\n, \r or comment) or EOF is hit before we could read a word, we stop ; If EOL (\n, \r or comment) or EOF is hit before we could read a word, we stop
@ -104,7 +104,7 @@ readWord:
.loop: .loop:
ld (hl), a ld (hl), a
inc hl inc hl
call ioGetC call ioGetB
call isSepOrLineEnd call isSepOrLineEnd
jr z, .success jr z, .success
cp ',' cp ','
@ -130,7 +130,7 @@ readWord:
; inside quotes, we accept literal whitespaces, but not line ends. ; inside quotes, we accept literal whitespaces, but not line ends.
ld (hl), a ld (hl), a
inc hl inc hl
call ioGetC call ioGetB
cp '"' cp '"'
jr z, .loop ; ending the quote ends the word jr z, .loop ; ending the quote ends the word
call isLineEnd call isLineEnd
@ -143,12 +143,12 @@ readWord:
; single quote is more straightforward: we have 3 chars and we put them ; single quote is more straightforward: we have 3 chars and we put them
; right in scratchpad ; right in scratchpad
ld (hl), a ld (hl), a
call ioGetC call ioGetB
or a or a
jr z, .error jr z, .error
inc hl inc hl
ld (hl), a ld (hl), a
call ioGetC call ioGetB
cp 0x27 ; ' cp 0x27 ; '
jr nz, .error jr nz, .error
inc hl inc hl
@ -165,7 +165,7 @@ readComma:
call unsetZ call unsetZ
ret ret
; Read ioGetC until we reach the beginning of next line, skipping comments if ; Read ioGetB until we reach the beginning of next line, skipping comments if
; necessary. This skips all whitespace, \n, \r, comments until we reach the ; necessary. This skips all whitespace, \n, \r, comments until we reach the
; first non-comment character. Then, we put it back (ioPutBack) and return. ; first non-comment character. Then, we put it back (ioPutBack) and return.
; ;
@ -176,7 +176,7 @@ readComma:
gotoNextLine: gotoNextLine:
.loop1: .loop1:
; first loop is "strict", that is: we error out on non-whitespace. ; first loop is "strict", that is: we error out on non-whitespace.
call ioGetC call ioGetB
call isSepOrLineEnd call isSepOrLineEnd
ret nz ; error ret nz ; error
or a ; cp 0 or a ; cp 0
@ -189,7 +189,7 @@ gotoNextLine:
.loop2: .loop2:
; second loop is the "comment loop": anything is valid and we just run ; second loop is the "comment loop": anything is valid and we just run
; until EOL. ; until EOL.
call ioGetC call ioGetB
or a ; cp 0 or a ; cp 0
jr z, .eof jr z, .eof
cp '\' ; special case: '\' doesn't count as a line end cp '\' ; special case: '\' doesn't count as a line end
@ -201,7 +201,7 @@ gotoNextLine:
.loop3: .loop3:
; Loop 3 happens after we reach our first line sep. This means that we ; Loop 3 happens after we reach our first line sep. This means that we
; wade through whitespace until we reach a non-whitespace character. ; wade through whitespace until we reach a non-whitespace character.
call ioGetC call ioGetB
or a ; cp 0 or a ; cp 0
jr z, .eof jr z, .eof
cp 0x3b ; ';' cp 0x3b ; ';'

View File

@ -13,11 +13,11 @@ Definition of block devices happen at include time. It would look like:
BLOCKDEV_COUNT .equ 1 BLOCKDEV_COUNT .equ 1
#include "blockdev.asm" #include "blockdev.asm"
; List of devices ; List of devices
.dw aciaGetC, aciaPutC .dw sdcGetB, sdcPutB
[...] [...]
That tells `blockdev` that we're going to set up one device, that its GetC and That tells `blockdev` that we're going to set up one device, that its GetB and
PutC are the ones defined by `acia.asm`. PutB are the ones defined by `sdc.asm`.
If your block device is read-only or write-only, use dummy routines. `unsetZ` If your block device is read-only or write-only, use dummy routines. `unsetZ`
is a good choice since it will return with the `Z` flag unset, indicating an is a good choice since it will return with the `Z` flag unset, indicating an
@ -28,16 +28,16 @@ seek pointer. This seek pointer is used in shell commands described below.
## Routine definitions ## Routine definitions
Parts that implement GetC and PutC do so in a loosely-coupled manner, but Parts that implement GetB and PutB do so in a loosely-coupled manner, but
they should try to adhere to the convention, that is: they should try to adhere to the convention, that is:
**GetC**: Get the character at position specified by `HL`. If it supports 32-bit **GetB**: Get the byte at position specified by `HL`. If it supports 32-bit
addressing, `DE` contains the high-order bytes. Return the result in addressing, `DE` contains the high-order bytes. Return the result in
`A`. If there's an error (for example, address out of range), unset `A`. If there's an error (for example, address out of range), unset
`Z`. This routine is not expected to block. We expect the result to be `Z`. This routine is not expected to block. We expect the result to be
immediate. immediate.
**PutC**: The opposite of GetC. Write the character in `A` at specified **PutB**: The opposite of GetB. Write the character in `A` at specified
position. `Z` unset on error. position. `Z` unset on error.
## Shell usage ## Shell usage

View File

@ -2,34 +2,34 @@
; ;
; A block device is an abstraction over something we can read from, write to. ; A block device is an abstraction over something we can read from, write to.
; ;
; A device that fits this abstraction puts the properly hook into itself, and ; A device that fits this abstraction puts the proper hook into itself, and then
; then the glue code assigns a blockdev ID to that device. It then becomes easy ; the glue code assigns a blockdev ID to that device. It then becomes easy to
; to access arbitrary devices in a convenient manner. ; access arbitrary devices in a convenient manner.
; ;
; This module exposes a seek/tell/getc/putc API that is then re-routed to ; This module exposes a seek/tell/getb/putb API that is then re-routed to
; underlying drivers. There will eventually be more than one driver type, but ; underlying drivers. There will eventually be more than one driver type, but
; for now we sit on only one type of driver: random access driver. ; for now we sit on only one type of driver: random access driver.
; ;
; *** Random access drivers *** ; *** Random access drivers ***
; ;
; Random access drivers are expected to supply two routines: GetC and PutC. ; Random access drivers are expected to supply two routines: GetB and PutB.
; ;
; GetC: ; GetB:
; Reads one character at address specified in DE/HL and returns its value in A. ; Reads one byte at address specified in DE/HL and returns its value in A.
; Sets Z according to whether read was successful: Set if successful, unset ; Sets Z according to whether read was successful: Set if successful, unset
; if not. ; if not.
; ;
; Unsuccessful reads generally mean that requested addr is out of bounds (we ; Unsuccessful reads generally mean that requested addr is out of bounds (we
; reached EOF). ; reached EOF).
; ;
; PutC: ; PutB:
; Writes character in A at address specified in DE/HL. Sets Z according to ; Writes byte in A at address specified in DE/HL. Sets Z according to whether
; whether the operation was successful. ; the operation was successful.
; ;
; Unsuccessful writes generally mean that we're out of bounds for writing. ; Unsuccessful writes generally mean that we're out of bounds for writing.
; ;
; All routines are expected to preserve unused registers except IX which is ; All routines are expected to preserve unused registers except IX which is
; explicitly protected during GetC/PutC calls. This makes quick "handle+jump" ; explicitly protected during GetB/PutB calls. This makes quick "handle+jump"
; definitions possible. ; definitions possible.
@ -46,9 +46,9 @@
.equ BLOCKDEV_SIZE 8 .equ BLOCKDEV_SIZE 8
; *** VARIABLES *** ; *** VARIABLES ***
; Pointer to the selected block device. A block device is a 8 bytes block of ; Pointer to the selected block device. A block device is a 8 bytes block of
; memory with pointers to GetC, PutC, and a 32-bit counter, in that order. ; memory with pointers to GetB, PutB, and a 32-bit counter, in that order.
.equ BLOCKDEV_SEL BLOCKDEV_RAMSTART .equ BLOCKDEV_SEL BLOCKDEV_RAMSTART
.equ BLOCKDEV_RAMEND BLOCKDEV_SEL+BLOCKDEV_SIZE .equ BLOCKDEV_RAMEND @+BLOCKDEV_SIZE
; *** CODE *** ; *** CODE ***
; Select block index specified in A and place them in routine pointers at (DE). ; Select block index specified in A and place them in routine pointers at (DE).
@ -121,16 +121,16 @@ _blkInc:
pop af pop af
ret ret
; Reads one character from selected device and returns its value in A. ; Reads one byte from selected device and returns its value in A.
; Sets Z according to whether read was successful: Set if successful, unset ; Sets Z according to whether read was successful: Set if successful, unset
; if not. ; if not.
blkGetC: blkGetB:
push ix push ix
ld ix, BLOCKDEV_SEL ld ix, BLOCKDEV_SEL
call _blkGetC call _blkGetB
pop ix pop ix
ret ret
_blkGetC: _blkGetB:
push hl push hl
push de push de
call _blkTell call _blkTell
@ -139,20 +139,20 @@ _blkGetC:
pop hl pop hl
jr _blkInc ; advance and return jr _blkInc ; advance and return
; Writes character in A in current position in the selected device. Sets Z ; Writes byte in A in current position in the selected device. Sets Z according
; according to whether the operation was successful. ; to whether the operation was successful.
blkPutC: blkPutB:
push ix push ix
ld ix, BLOCKDEV_SEL ld ix, BLOCKDEV_SEL
call _blkPutC call _blkPutB
pop ix pop ix
ret ret
_blkPutC: _blkPutB:
push ix push ix
push hl push hl
push de push de
call _blkTell call _blkTell
inc ix ; make IX point to PutC inc ix ; make IX point to PutB
inc ix inc ix
call callIXI call callIXI
pop de pop de
@ -160,7 +160,7 @@ _blkPutC:
pop ix pop ix
jr _blkInc ; advance and return jr _blkInc ; advance and return
; Reads B chars from blkGetC and copy them in (HL). ; Reads B chars from blkGetB and copy them in (HL).
; Sets Z if successful, unset Z if there was an error. ; Sets Z if successful, unset Z if there was an error.
blkRead: blkRead:
push ix push ix
@ -172,7 +172,7 @@ _blkRead:
push hl push hl
push bc push bc
.loop: .loop:
call _blkGetC call _blkGetB
jr nz, .end ; Z already unset jr nz, .end ; Z already unset
ld (hl), a ld (hl), a
inc hl inc hl
@ -183,7 +183,7 @@ _blkRead:
pop hl pop hl
ret ret
; Writes B chars to blkPutC from (HL). ; Writes B chars to blkPutB from (HL).
; Sets Z if successful, unset Z if there was an error. ; Sets Z if successful, unset Z if there was an error.
blkWrite: blkWrite:
push ix push ix
@ -196,7 +196,7 @@ _blkWrite:
push bc push bc
.loop: .loop:
ld a, (hl) ld a, (hl)
call _blkPutC call _blkPutB
jr nz, .end ; Z already unset jr nz, .end ; Z already unset
inc hl inc hl
djnz .loop djnz .loop
@ -217,11 +217,11 @@ _blkWrite:
; (high). DE is only used for mode 0. ; (high). DE is only used for mode 0.
; ;
; When seeking to an out-of-bounds position, the resulting position will be ; When seeking to an out-of-bounds position, the resulting position will be
; one position ahead of the last valid position. Therefore, GetC after a seek ; one position ahead of the last valid position. Therefore, GetB after a seek
; to end would always fail. ; to end would always fail.
; ;
; If the device is "growable", it's possible that seeking to end when calling ; If the device is "growable", it's possible that seeking to end when calling
; PutC doesn't necessarily result in a failure. ; PutB doesn't necessarily result in a failure.
blkSeek: blkSeek:
push ix push ix
ld ix, BLOCKDEV_SEL ld ix, BLOCKDEV_SEL
@ -309,6 +309,6 @@ _blkTell:
; This label is at the end of the file on purpose: the glue file should include ; This label is at the end of the file on purpose: the glue file should include
; a list of device routine table entries just after the include. Each line ; a list of device routine table entries just after the include. Each line
; has 4 word addresses: GetC, PutC and Seek, Tell. An entry could look like: ; has 2 word addresses: GetB and PutB. An entry could look like:
; .dw mmapGetC, mmapPutC, mmapSeek, mmapTell ; .dw mmapGetB, mmapPutB
blkDevTbl: blkDevTbl:

View File

@ -50,7 +50,7 @@ blkSeekCmd:
; stop loading. ; stop loading.
; ;
; Returns a SHELL_ERR_IO_ERROR only if we couldn't read any byte (if the first ; Returns a SHELL_ERR_IO_ERROR only if we couldn't read any byte (if the first
; call to GetC failed) ; call to GetB failed)
; ;
; Example: load 42 ; Example: load 42
blkLoadCmd: blkLoadCmd:
@ -62,12 +62,12 @@ blkLoad:
ld a, (hl) ld a, (hl)
ld b, a ld b, a
ld hl, (SHELL_MEM_PTR) ld hl, (SHELL_MEM_PTR)
call blkGetC call blkGetB
jr nz, .ioError jr nz, .ioError
jr .intoLoop ; we'v already called blkGetC. don't call it jr .intoLoop ; we'v already called blkGetB. don't call it
; again. ; again.
.loop: .loop:
call blkGetC call blkGetB
.intoLoop: .intoLoop:
ld (hl), a ld (hl), a
inc hl inc hl
@ -86,7 +86,7 @@ blkLoad:
; Load the specified number of bytes (max 0x100, 0 means 0x100) from the current ; Load the specified number of bytes (max 0x100, 0 means 0x100) from the current
; memory pointer and write them to I/O. Memory pointer doesn't move. This puts ; memory pointer and write them to I/O. Memory pointer doesn't move. This puts
; chars to blkPutC. Raises error if not all bytes could be written. ; chars to blkPutB. Raises error if not all bytes could be written.
; ;
; Example: save 42 ; Example: save 42
blkSaveCmd: blkSaveCmd:
@ -101,7 +101,7 @@ blkSave:
.loop: .loop:
ld a, (hl) ld a, (hl)
inc hl inc hl
call blkPutC call blkPutB
jr nz, .ioError jr nz, .ioError
djnz .loop djnz .loop
.loopend: .loopend:

View File

@ -9,6 +9,6 @@
.equ BLOCKDEV_ERR_OUT_OF_BOUNDS 0x03 .equ BLOCKDEV_ERR_OUT_OF_BOUNDS 0x03
.equ BLOCKDEV_ERR_UNSUPPORTED 0x04 .equ BLOCKDEV_ERR_UNSUPPORTED 0x04
; IO routines (GetC, PutC) returned an error in a load/save command ; IO routines (GetB, PutB) returned an error in a load/save command
.equ SHELL_ERR_IO_ERROR 0x05 .equ SHELL_ERR_IO_ERROR 0x05

View File

@ -3,7 +3,7 @@
; Collapse OS filesystem (CFS) is not made to be convenient, but to be simple. ; Collapse OS filesystem (CFS) is not made to be convenient, but to be simple.
; This is little more than "named storage blocks". Characteristics: ; This is little more than "named storage blocks". Characteristics:
; ;
; * a filesystem sits upon a blockdev. It needs GetC, PutC, Seek. ; * a filesystem sits upon a blockdev. It needs GetB, PutB, Seek.
; * No directory. Use filename prefix to group. ; * No directory. Use filename prefix to group.
; * First block of each file has metadata. Others are raw data. ; * First block of each file has metadata. Others are raw data.
; * No FAT. Files are a chain of blocks of a predefined size. To enumerate ; * No FAT. Files are a chain of blocks of a predefined size. To enumerate
@ -98,12 +98,12 @@
; This pointer is 32 bits. 32 bits pointers are a bit awkward: first two bytes ; This pointer is 32 bits. 32 bits pointers are a bit awkward: first two bytes
; are high bytes *low byte first*, and then the low two bytes, same order. ; are high bytes *low byte first*, and then the low two bytes, same order.
; When loaded in HL/DE, the four bytes are loaded in this order: E, D, L, H ; When loaded in HL/DE, the four bytes are loaded in this order: E, D, L, H
.equ FS_START FS_BLK+BLOCKDEV_SIZE .equ FS_START @+BLOCKDEV_SIZE
; This variable below contain the metadata of the last block we moved ; This variable below contain the metadata of the last block we moved
; to. We read this data in memory to avoid constant seek+read operations. ; to. We read this data in memory to avoid constant seek+read operations.
.equ FS_META FS_START+4 .equ FS_META @+4
.equ FS_HANDLES FS_META+FS_METASIZE .equ FS_HANDLES @+FS_METASIZE
.equ FS_RAMEND FS_HANDLES+FS_HANDLE_COUNT*FS_HANDLE_SIZE .equ FS_RAMEND @+FS_HANDLE_COUNT*FS_HANDLE_SIZE
; *** DATA *** ; *** DATA ***
P_FS_MAGIC: P_FS_MAGIC:
@ -333,10 +333,10 @@ fsIsDeleted:
; we can still access the FS even if blkdev selection changes. These routines ; we can still access the FS even if blkdev selection changes. These routines
; below mimic blkdev's methods, but for our private mount. ; below mimic blkdev's methods, but for our private mount.
fsblkGetC: fsblkGetB:
push ix push ix
ld ix, FS_BLK ld ix, FS_BLK
call _blkGetC call _blkGetB
pop ix pop ix
ret ret
@ -347,10 +347,10 @@ fsblkRead:
pop ix pop ix
ret ret
fsblkPutC: fsblkPutB:
push ix push ix
ld ix, FS_BLK ld ix, FS_BLK
call _blkPutC call _blkPutB
pop ix pop ix
ret ret
@ -458,27 +458,27 @@ fsSetSize:
; cache. ; cache.
ld a, l ld a, l
ld (ix+4), a ld (ix+4), a
call fsblkPutC call fsblkPutB
ld a, h ld a, h
ld (ix+5), a ld (ix+5), a
call fsblkPutC call fsblkPutB
pop hl ; <-- lvl 1 pop hl ; <-- lvl 1
xor a ; ensure Z xor a ; ensure Z
ret ret
; Read a byte in handle at (IX) at position HL and put it into A. ; Read a byte in handle at (IX) at position HL and put it into A.
; Z is set on success, unset if handle is at the end of the file. ; Z is set on success, unset if handle is at the end of the file.
fsGetC: fsGetB:
call fsWithinBounds call fsWithinBounds
jr z, .proceed jr z, .proceed
; We want to unset Z, but also return 0 to ensure that a GetC that ; We want to unset Z, but also return 0 to ensure that a GetB that
; doesn't check Z doesn't end up with false data. ; doesn't check Z doesn't end up with false data.
xor a xor a
jp unsetZ ; returns jp unsetZ ; returns
.proceed: .proceed:
push hl push hl
call fsPlaceH call fsPlaceH
call fsblkGetC call fsblkGetB
cp a ; ensure Z cp a ; ensure Z
pop hl pop hl
ret ret
@ -486,10 +486,10 @@ fsGetC:
; Write byte A in handle (IX) at position HL. ; Write byte A in handle (IX) at position HL.
; Z is set on success, unset if handle is at the end of the file. ; Z is set on success, unset if handle is at the end of the file.
; TODO: detect end of block alloc ; TODO: detect end of block alloc
fsPutC: fsPutB:
push hl push hl
call fsPlaceH call fsPlaceH
call fsblkPutC call fsblkPutB
pop hl pop hl
; if HL is out of bounds, increase bounds ; if HL is out of bounds, increase bounds
call fsWithinBounds call fsWithinBounds

View File

@ -24,7 +24,7 @@ _mmapAddr:
pop de pop de
jp unsetZ jp unsetZ
mmapGetC: mmapGetB:
push hl push hl
call _mmapAddr call _mmapAddr
jr nz, .end jr nz, .end
@ -35,7 +35,7 @@ mmapGetC:
ret ret
mmapPutC: mmapPutB:
push hl push hl
call _mmapAddr call _mmapAddr
jr nz, .end jr nz, .end

View File

@ -16,7 +16,7 @@
; ;
; *** Variables *** ; *** Variables ***
.equ PGM_HANDLE PGM_RAMSTART .equ PGM_HANDLE PGM_RAMSTART
.equ PGM_RAMEND PGM_HANDLE+FS_HANDLE_SIZE .equ PGM_RAMEND @+FS_HANDLE_SIZE
; Routine suitable to plug into SHELL_CMDHOOK. HL points to the full cmdline. ; Routine suitable to plug into SHELL_CMDHOOK. HL points to the full cmdline.
; which has been processed to replace the first ' ' with a null char. ; which has been processed to replace the first ' ' with a null char.
@ -48,7 +48,7 @@ pgmRun:
ld hl, 0 ; addr that we read in file handle ld hl, 0 ; addr that we read in file handle
ld de, PGM_CODEADDR ; addr in mem we write to ld de, PGM_CODEADDR ; addr in mem we write to
.loop: .loop:
call fsGetC ; we use Z at end of loop call fsGetB ; we use Z at end of loop
ld (de), a ; Z preserved ld (de), a ; Z preserved
inc hl ; Z preserved in 16-bit inc hl ; Z preserved in 16-bit
inc de ; Z preserved in 16-bit inc de ; Z preserved in 16-bit

View File

@ -20,14 +20,14 @@
; ;
; SD card's lowest common denominator in terms of block size is 512 bytes, so ; SD card's lowest common denominator in terms of block size is 512 bytes, so
; that's what we deal with. To avoid wastefully reading entire blocks from the ; that's what we deal with. To avoid wastefully reading entire blocks from the
; card for one byte read ops, we buffer the last read block. If a GetC or PutC ; card for one byte read ops, we buffer the last read block. If a GetB or PutB
; operation is within that buffer, then no interaction with the SD card is ; operation is within that buffer, then no interaction with the SD card is
; necessary. ; necessary.
; ;
; As soon as a GetC or PutC operation is made that is outside the current ; As soon as a GetB or PutB operation is made that is outside the current
; buffer, we load a new block. ; buffer, we load a new block.
; ;
; When we PutC, we flag the buffer as "dirty". On the next buffer change (during ; When we PutB, we flag the buffer as "dirty". On the next buffer change (during
; an out-of-buffer request or during an explicit "flush" operation), bytes ; an out-of-buffer request or during an explicit "flush" operation), bytes
; currently in the buffer will be written to the SD card. ; currently in the buffer will be written to the SD card.
; ;
@ -37,10 +37,10 @@
; right away, in another file on the same card (zasm), on a different sector. ; right away, in another file on the same card (zasm), on a different sector.
; ;
; If we only have one buffer in this scenario, we'll end up loading a new sector ; If we only have one buffer in this scenario, we'll end up loading a new sector
; at each GetC/PutC operation and, more importantly, writing a whole block for ; at each GetB/PutB operation and, more importantly, writing a whole block for
; a few bytes each time. This will wear the card prematurely (and be very slow). ; a few bytes each time. This will wear the card prematurely (and be very slow).
; ;
; With 2 buffers, we solve the problem. Whenever GetC/PutC is called, we first ; With 2 buffers, we solve the problem. Whenever GetB/PutB is called, we first
; look if one of the buffer holds our sector. If not, we see if one of the ; look if one of the buffer holds our sector. If not, we see if one of the
; buffer is clean (not dirty). If yes, we use this one. If both are dirty or ; buffer is clean (not dirty). If yes, we use this one. If both are dirty or
; clean, we use any. This way, as long as writing isn't made to random ; clean, we use any. This way, as long as writing isn't made to random
@ -721,7 +721,7 @@ _sdcPlaceBuf:
xor a ; ensure Z xor a ; ensure Z
ret ret
sdcGetC: sdcGetB:
push hl push hl
call _sdcPlaceBuf call _sdcPlaceBuf
jr nz, .error jr nz, .error
@ -736,7 +736,7 @@ sdcGetC:
pop hl pop hl
ret ret
sdcPutC: sdcPutB:
push hl push hl
push af ; let's remember the char we put, _sdcPlaceBuf push af ; let's remember the char we put, _sdcPlaceBuf
; destroys A. ; destroys A.

View File

@ -24,7 +24,7 @@ jp aciaInt
.equ BLOCKDEV_COUNT 1 .equ BLOCKDEV_COUNT 1
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw mmapGetC, mmapPutC .dw mmapGetB, mmapPutB
.equ STDIO_RAMSTART BLOCKDEV_RAMEND .equ STDIO_RAMSTART BLOCKDEV_RAMEND
.inc "stdio.asm" .inc "stdio.asm"

View File

@ -29,8 +29,8 @@ jp aciaInt
.equ BLOCKDEV_COUNT 2 .equ BLOCKDEV_COUNT 2
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw sdcGetC, sdcPutC .dw sdcGetB, sdcPutB
.dw blk2GetC, blk2PutC .dw blk2GetB, blk2PutB
.equ STDIO_RAMSTART BLOCKDEV_RAMEND .equ STDIO_RAMSTART BLOCKDEV_RAMEND
@ -83,10 +83,10 @@ init:
; *** blkdev 2: file handle 0 *** ; *** blkdev 2: file handle 0 ***
blk2GetC: blk2GetB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsGetC jp fsGetB
blk2PutC: blk2PutB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsPutC jp fsPutB

View File

@ -27,7 +27,7 @@
jp blkSet jp blkSet
jp fsFindFN jp fsFindFN
jp fsOpen jp fsOpen
jp fsGetC jp fsGetB
jp cpHLDE ; approaching 0x38... jp cpHLDE ; approaching 0x38...
; interrupt hook ; interrupt hook
@ -37,14 +37,14 @@ jp aciaInt
; *** Jump Table (cont.) *** ; *** Jump Table (cont.) ***
jp parseArgs jp parseArgs
jp printstr jp printstr
jp _blkGetC jp _blkGetB
jp _blkPutC jp _blkPutB
jp _blkSeek jp _blkSeek
jp _blkTell jp _blkTell
jp printHexPair jp printHexPair
jp sdcGetC jp sdcGetB
jp sdcPutC jp sdcPutB
jp blkGetC jp blkGetB
.inc "err.h" .inc "err.h"
.inc "core.asm" .inc "core.asm"
@ -55,10 +55,10 @@ jp aciaInt
.equ BLOCKDEV_COUNT 4 .equ BLOCKDEV_COUNT 4
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw sdcGetC, sdcPutC .dw sdcGetB, sdcPutB
.dw blk1GetC, blk1PutC .dw blk1GetB, blk1PutB
.dw blk2GetC, blk2PutC .dw blk2GetB, blk2PutB
.dw mmapGetC, mmapPutC .dw mmapGetB, mmapPutB
.equ MMAP_START 0xe000 .equ MMAP_START 0xe000
@ -116,20 +116,20 @@ init:
; *** blkdev 1: file handle 0 *** ; *** blkdev 1: file handle 0 ***
blk1GetC: blk1GetB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsGetC jp fsGetB
blk1PutC: blk1PutB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsPutC jp fsPutB
; *** blkdev 2: file handle 1 *** ; *** blkdev 2: file handle 1 ***
blk2GetC: blk2GetB:
ld ix, FS_HANDLES+FS_HANDLE_SIZE ld ix, FS_HANDLES+FS_HANDLE_SIZE
jp fsGetC jp fsGetB
blk2PutC: blk2PutB:
ld ix, FS_HANDLES+FS_HANDLE_SIZE ld ix, FS_HANDLES+FS_HANDLE_SIZE
jp fsPutC jp fsPutB

View File

@ -5,30 +5,31 @@
; *** JUMP TABLE *** ; *** JUMP TABLE ***
.equ strncmp 0x03 .equ strncmp 0x03
.equ addDE 0x06 .equ addDE @+3
.equ addHL 0x09 .equ addHL @+3
.equ upcase 0x0c .equ upcase @+3
.equ unsetZ 0x0f .equ unsetZ @+3
.equ intoDE 0x12 .equ intoDE @+3
.equ intoHL 0x15 .equ intoHL @+3
.equ writeHLinDE 0x18 .equ writeHLinDE @+3
.equ findchar 0x1b .equ findchar @+3
.equ parseHex 0x1e .equ parseHex @+3
.equ parseHexPair 0x21 .equ parseHexPair @+3
.equ blkSel 0x24 .equ blkSel @+3
.equ blkSet 0x27 .equ blkSet @+3
.equ fsFindFN 0x2a .equ fsFindFN @+3
.equ fsOpen 0x2d .equ fsOpen @+3
.equ fsGetC 0x30 .equ fsGetB @+3
.equ cpHLDE 0x33 .equ cpHLDE @+3
; now at 0x36
.equ parseArgs 0x3b .equ parseArgs 0x3b
.equ printstr 0x3e .equ printstr @+3
.equ _blkGetC 0x41 .equ _blkGetB @+3
.equ _blkPutC 0x44 .equ _blkPutB @+3
.equ _blkSeek 0x47 .equ _blkSeek @+3
.equ _blkTell 0x4a .equ _blkTell @+3
.equ printHexPair 0x4d .equ printHexPair @+3
.equ sdcGetC 0x50 .equ sdcGetB @+3
.equ sdcPutC 0x53 .equ sdcPutB @+3
.equ blkGetC 0x56 .equ blkGetB @+3

View File

@ -22,14 +22,14 @@
jp blkSet jp blkSet
jp fsFindFN jp fsFindFN
jp fsOpen jp fsOpen
jp fsGetC jp fsGetB
jp fsPutC jp fsPutB
jp fsSetSize jp fsSetSize
jp cpHLDE jp cpHLDE
jp parseArgs jp parseArgs
jp printstr jp printstr
jp _blkGetC jp _blkGetB
jp _blkPutC jp _blkPutB
jp _blkSeek jp _blkSeek
jp _blkTell jp _blkTell
jp printcrlf jp printcrlf
@ -63,9 +63,9 @@
.equ BLOCKDEV_COUNT 3 .equ BLOCKDEV_COUNT 3
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw mmapGetC, mmapPutC .dw mmapGetB, mmapPutB
.dw f0GetC, f0PutC .dw f0GetB, f0PutB
.dw f1GetC, f1PutC .dw f1GetB, f1PutB
.equ FS_RAMSTART BLOCKDEV_RAMEND .equ FS_RAMSTART BLOCKDEV_RAMEND
@ -121,21 +121,21 @@ init:
ld (SHELL_CMDHOOK), hl ld (SHELL_CMDHOOK), hl
jp shellLoop jp shellLoop
f0GetC: f0GetB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsGetC jp fsGetB
f0PutC: f0PutB:
ld ix, FS_HANDLES ld ix, FS_HANDLES
jp fsPutC jp fsPutB
f1GetC: f1GetB:
ld ix, FS_HANDLES+FS_HANDLE_SIZE ld ix, FS_HANDLES+FS_HANDLE_SIZE
jp fsGetC jp fsGetB
f1PutC: f1PutB:
ld ix, FS_HANDLES+FS_HANDLE_SIZE ld ix, FS_HANDLES+FS_HANDLE_SIZE
jp fsPutC jp fsPutB
edCmd: edCmd:
.db "ed", 0, 0, 0b1001, 0, 0 .db "ed", 0, 0, 0b1001, 0, 0

View File

@ -30,14 +30,14 @@
.equ blkSet 0x27 .equ blkSet 0x27
.equ fsFindFN 0x2a .equ fsFindFN 0x2a
.equ fsOpen 0x2d .equ fsOpen 0x2d
.equ fsGetC 0x30 .equ fsGetB 0x30
.equ fsPutC 0x33 .equ fsPutB 0x33
.equ fsSetSize 0x36 .equ fsSetSize 0x36
.equ cpHLDE 0x39 .equ cpHLDE 0x39
.equ parseArgs 0x3c .equ parseArgs 0x3c
.equ printstr 0x3f .equ printstr 0x3f
.equ _blkGetC 0x42 .equ _blkGetB 0x42
.equ _blkPutC 0x45 .equ _blkPutB 0x45
.equ _blkSeek 0x48 .equ _blkSeek 0x48
.equ _blkTell 0x4b .equ _blkTell 0x4b
.equ printcrlf 0x4e .equ printcrlf 0x4e

View File

@ -26,14 +26,14 @@
jp blkSet jp blkSet
jp fsFindFN jp fsFindFN
jp fsOpen jp fsOpen
jp fsGetC jp fsGetB
jp fsPutC jp fsPutB
jp fsSetSize jp fsSetSize
jp cpHLDE jp cpHLDE
jp parseArgs jp parseArgs
jp printstr jp printstr
jp _blkGetC jp _blkGetB
jp _blkPutC jp _blkPutB
jp _blkSeek jp _blkSeek
jp _blkTell jp _blkTell
jp printcrlf jp printcrlf
@ -48,10 +48,10 @@
.equ BLOCKDEV_COUNT 4 .equ BLOCKDEV_COUNT 4
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw fsdevGetC, fsdevPutC .dw fsdevGetB, fsdevPutB
.dw stdoutGetC, stdoutPutC .dw stdoutGetB, stdoutPutB
.dw stdinGetC, stdinPutC .dw stdinGetB, stdinPutB
.dw mmapGetC, mmapPutC .dw mmapGetB, mmapPutB
.equ MMAP_START 0xe000 .equ MMAP_START 0xe000
@ -84,8 +84,8 @@ init:
; setup stack ; setup stack
ld hl, KERNEL_RAMEND ld hl, KERNEL_RAMEND
ld sp, hl ld sp, hl
ld hl, emulGetC ld hl, emulGetB
ld de, emulPutC ld de, emulPutB
call stdioInit call stdioInit
call fsInit call fsInit
ld a, 0 ; select fsdev ld a, 0 ; select fsdev
@ -97,17 +97,17 @@ init:
ld (SHELL_CMDHOOK), hl ld (SHELL_CMDHOOK), hl
jp shellLoop jp shellLoop
emulGetC: emulGetB:
; Blocks until a char is returned ; Blocks until a char is returned
in a, (STDIO_PORT) in a, (STDIO_PORT)
cp a ; ensure Z cp a ; ensure Z
ret ret
emulPutC: emulPutB:
out (STDIO_PORT), a out (STDIO_PORT), a
ret ret
fsdevGetC: fsdevGetB:
ld a, e ld a, e
out (FS_ADDR_PORT), a out (FS_ADDR_PORT), a
ld a, h ld a, h
@ -121,7 +121,7 @@ fsdevGetC:
cp a ; ensure Z cp a ; ensure Z
ret ret
fsdevPutC: fsdevPutB:
push af push af
ld a, e ld a, e
out (FS_ADDR_PORT), a out (FS_ADDR_PORT), a
@ -142,21 +142,21 @@ fsdevPutC:
.equ STDOUT_HANDLE FS_HANDLES .equ STDOUT_HANDLE FS_HANDLES
stdoutGetC: stdoutGetB:
ld ix, STDOUT_HANDLE ld ix, STDOUT_HANDLE
jp fsGetC jp fsGetB
stdoutPutC: stdoutPutB:
ld ix, STDOUT_HANDLE ld ix, STDOUT_HANDLE
jp fsPutC jp fsPutB
.equ STDIN_HANDLE FS_HANDLES+FS_HANDLE_SIZE .equ STDIN_HANDLE FS_HANDLES+FS_HANDLE_SIZE
stdinGetC: stdinGetB:
ld ix, STDIN_HANDLE ld ix, STDIN_HANDLE
jp fsGetC jp fsGetB
stdinPutC: stdinPutB:
ld ix, STDIN_HANDLE ld ix, STDIN_HANDLE
jp fsPutC jp fsPutB

View File

@ -19,14 +19,14 @@
.equ blkSet @+3 .equ blkSet @+3
.equ fsFindFN @+3 .equ fsFindFN @+3
.equ fsOpen @+3 .equ fsOpen @+3
.equ fsGetC @+3 .equ fsGetB @+3
.equ fsPutC @+3 .equ fsPutB @+3
.equ fsSetSize @+3 .equ fsSetSize @+3
.equ cpHLDE @+3 .equ cpHLDE @+3
.equ parseArgs @+3 .equ parseArgs @+3
.equ printstr @+3 .equ printstr @+3
.equ _blkGetC @+3 .equ _blkGetB @+3
.equ _blkPutC @+3 .equ _blkPutB @+3
.equ _blkSeek @+3 .equ _blkSeek @+3
.equ _blkTell @+3 .equ _blkTell @+3
.equ printcrlf @+3 .equ printcrlf @+3

View File

@ -24,11 +24,11 @@ jp blkSel
jp blkSet jp blkSet
jp fsFindFN jp fsFindFN
jp fsOpen jp fsOpen
jp fsGetC jp fsGetB
jp cpHLDE jp cpHLDE
jp parseArgs jp parseArgs
jp _blkGetC jp _blkGetB
jp _blkPutC jp _blkPutB
jp _blkSeek jp _blkSeek
jp _blkTell jp _blkTell
jp printstr jp printstr
@ -40,9 +40,9 @@ jp printstr
.equ BLOCKDEV_COUNT 3 .equ BLOCKDEV_COUNT 3
.inc "blockdev.asm" .inc "blockdev.asm"
; List of devices ; List of devices
.dw emulGetC, unsetZ .dw emulGetB, unsetZ
.dw unsetZ, emulPutC .dw unsetZ, emulPutB
.dw fsdevGetC, fsdevPutC .dw fsdevGetB, fsdevPutB
.equ STDIO_RAMSTART BLOCKDEV_RAMEND .equ STDIO_RAMSTART BLOCKDEV_RAMEND
.inc "stdio.asm" .inc "stdio.asm"
@ -71,7 +71,7 @@ init:
.db "0 1", 0 .db "0 1", 0
; *** I/O *** ; *** I/O ***
emulGetC: emulGetB:
; the STDIN_SEEK port works by poking it twice. First poke is for high ; the STDIN_SEEK port works by poking it twice. First poke is for high
; byte, second poke is for low one. ; byte, second poke is for low one.
ld a, h ld a, h
@ -87,7 +87,7 @@ emulGetC:
call unsetZ call unsetZ
ret ret
emulPutC: emulPutB:
out (STDIO_PORT), a out (STDIO_PORT), a
cp a ; ensure Z cp a ; ensure Z
ret ret
@ -97,7 +97,7 @@ stderrPutC:
cp a ; ensure Z cp a ; ensure Z
ret ret
fsdevGetC: fsdevGetB:
ld a, e ld a, e
out (FS_SEEK_PORT), a out (FS_SEEK_PORT), a
ld a, h ld a, h
@ -111,7 +111,7 @@ fsdevGetC:
cp a ; ensure Z cp a ; ensure Z
ret ret
fsdevPutC: fsdevPutB:
push af push af
ld a, e ld a, e
out (FS_SEEK_PORT), a out (FS_SEEK_PORT), a

View File

@ -5,25 +5,25 @@
; *** JUMP TABLE *** ; *** JUMP TABLE ***
.equ strncmp 0x03 .equ strncmp 0x03
.equ addDE 0x06 .equ addDE @+3
.equ addHL 0x09 .equ addHL @+3
.equ upcase 0x0c .equ upcase @+3
.equ unsetZ 0x0f .equ unsetZ @+3
.equ intoDE 0x12 .equ intoDE @+3
.equ intoHL 0x15 .equ intoHL @+3
.equ writeHLinDE 0x18 .equ writeHLinDE @+3
.equ findchar 0x1b .equ findchar @+3
.equ parseHex 0x1e .equ parseHex @+3
.equ parseHexPair 0x21 .equ parseHexPair @+3
.equ blkSel 0x24 .equ blkSel @+3
.equ blkSet 0x27 .equ blkSet @+3
.equ fsFindFN 0x2a .equ fsFindFN @+3
.equ fsOpen 0x2d .equ fsOpen @+3
.equ fsGetC 0x30 .equ fsGetB @+3
.equ cpHLDE 0x33 .equ cpHLDE @+3
.equ parseArgs 0x36 .equ parseArgs @+3
.equ _blkGetC 0x39 .equ _blkGetB @+3
.equ _blkPutC 0x3c .equ _blkPutB @+3
.equ _blkSeek 0x3f .equ _blkSeek @+3
.equ _blkTell 0x42 .equ _blkTell @+3
.equ printstr 0x45 .equ printstr @+3

View File

@ -9,7 +9,7 @@
.equ BLOCKDEV_ERR_OUT_OF_BOUNDS 0x03 .equ BLOCKDEV_ERR_OUT_OF_BOUNDS 0x03
.equ BLOCKDEV_ERR_UNSUPPORTED 0x04 .equ BLOCKDEV_ERR_UNSUPPORTED 0x04
; IO routines (GetC, PutC) returned an error in a load/save command ; IO routines (GetB, PutB) returned an error in a load/save command
.equ SHELL_ERR_IO_ERROR 0x05 .equ SHELL_ERR_IO_ERROR 0x05