fat16 working

This commit is contained in:
Dennis Gunia
2024-01-25 00:12:46 +01:00
parent 507eb3a017
commit 488efa3907
33 changed files with 10561 additions and 6941 deletions

View File

@@ -53,7 +53,7 @@ TermInit_copy_loop:
ld hl, TmsFont
call TmsTextMode ; initialize text mode
ld a, TmsDarkGreen ; set colors
ld a, TmsDarkRed ; set colors
call TmsBackground
ld a, TmsWhite
call TmsTextColor

View File

@@ -1,6 +1,6 @@
:10800000CD0880C90104000021E04001048011E492
:10801000400A770323E5ED52E1C21180CDF18121C1
:10802000E084CD37833E0CCD9C823E0FCD4D843E07
:10802000E084CD37833E06CD9C823E0FCD4D843E0D
:10803000001E00CD6084216981CD77843E001E043E
:10804000CD6084C93AE1405F3AE040CD6084C9F533
:10805000C50AF6002807CD608003C35180C1F1C96D

File diff suppressed because it is too large Load Diff

View File

@@ -1,6 +1,6 @@
!8000 CD 08 80 C9 01 04 00 00 21 E0 40 01 04 80 11 E4
!8010 40 0A 77 03 23 E5 ED 52 E1 C2 11 80 CD F1 81 21
!8020 E0 84 CD 37 83 3E 0C CD 9C 82 3E 0F CD 4D 84 3E
!8020 E0 84 CD 37 83 3E 06 CD 9C 82 3E 0F CD 4D 84 3E
!8030 00 1E 00 CD 60 84 21 69 81 CD 77 84 3E 00 1E 04
!8040 CD 60 84 C9 3A E1 40 5F 3A E0 40 CD 60 84 C9 F5
!8050 C5 0A F6 00 28 07 CD 60 80 03 C3 51 80 C1 F1 C9

View File

@@ -11,7 +11,7 @@ OP_SELDSK:
jr c,_OP_SELDSK_INVALID
cp 4
jr nc, _OP_SELDSK_INVALID
call 0x8000
call ideif_drv_sel
ret
_OP_SELDSK_INVALID:
@@ -22,5 +22,17 @@ _OP_SELDSK_INVALID:
CALL beep
ret
OP_DIR:
CALL fat_print_directory
ret
OP_CD:
call fat_cd_single
ret
_OP_SELDSK_INVALID_STR:
db 10,13,"Invalid drive letter",10,13,0
db 10,13,"Invalid drive letter",10,13,0
OP_FSEXEC:
call fat_exec
ret

View File

@@ -13,6 +13,9 @@ COMMAND_LUT:
db "rst", 0,0x00,0x00 ;soft reset
db "lsdsk", 0,[OP_LSDSK], [OP_LSDSK]>>8 ;list disks
db "seldsk ", 0,[OP_SELDSK], [OP_SELDSK]>>8 ;select disk
db "cd ", 0 , [OP_CD], [OP_CD]>>8 ;Read time
db "ls", 0 , [OP_DIR], [OP_DIR]>>8 ;Read time
db "run ", 0 , [OP_FSEXEC], [OP_FSEXEC]>>8 ;Read time
db "$", 0, [OP_EXEC], [OP_EXEC]>>8 ;jump to addr
db "i", 0, [OP_IO_IN], [OP_IO_IN]>>8 ;Read port
db "o", 0, [OP_IO_OUT], [OP_IO_OUT]>>8 ;Write port
@@ -20,14 +23,14 @@ COMMAND_LUT:
db "?", 0, [OP_DUMP], [OP_DUMP]>>8 ;Print memory
db 0xFF ;End of Table
IN_BUFFER .equ var_buffer
COMMAND:
call print_newLine
ld hl,[var_dir]
call print_str
ld a,'>'
call print_char
xor a ;reset buffer len
ld (var_buffer_len),a
ld (var_buffer_len),a ;set buffer len to 0
COMMAND_READ:
call read_char
jp z, COMMAND_READ ;wait for input
@@ -40,7 +43,7 @@ COMMAND_READ:
push af
; a contains latest char
ld hl,[var_buffer]
ld hl,[var_input]
ld d,0
ld a,(var_buffer_len)
ld e,a
@@ -65,7 +68,7 @@ COMMAND_BACKSPACE:
ld (var_buffer_len),a ;and store it
ld e,a ;load de with decremented value
ld d,0
ld hl,[var_buffer]
ld hl,[var_input]
add hl,de ;hl now contains pointer to last position in buffer
xor a ; store null byte to current location
ld (hl),a
@@ -81,7 +84,7 @@ COMMAND_PROCESS:
;compare
LD HL,[COMMAND_LUT] ;Lookup table
COMMAND_PROCESS_LOOP:
LD DE,[var_buffer] ;Buffer
LD DE,[var_input] ;Buffer
LD A,(HL) ;Load first byte of entry
CP 0xFF
JP Z,COMMAND_PROCESS_NOT_FOUND ;if first byte is 0xFF, End is reached

View File

@@ -132,6 +132,24 @@ _read_bcd_invalid
ld a, 0xFF
ret
print_32_hex:
ld a,(ix+3)
call print_a_hex
ld a,(ix+2)
call print_a_hex
ld a,(ix+1)
call print_a_hex
ld a,(ix+0)
call print_a_hex
ret
print_16_hex:
ld a,(ix+1)
call print_a_hex
ld a,(ix+0)
call print_a_hex
ret
;MSG_CRSR_0:
; db 0x1B, "[?25h",0
@@ -154,4 +172,66 @@ A_RTS_ON:
out (CS_SIO_A_C),A
ld a,0EAh ;DTR active, TX 8bit, BREAK off, TX on, RTS active
out (CS_SIO_A_C),A
ret
;------------------------------------------------------------------------------
; PRINTINLINE
;
; String output function
;
; Prints in-line data (bytes immediately following the PRINTINLINE call)
; until a string terminator is encountered (0 - null char).
;------------------------------------------------------------------------------
PRINTINLINE:
EX (SP),HL ; PUSH HL and put RET ADDress into HL
PUSH AF
PUSH BC
nxtILC:
LD A,(HL)
CP 0
JR Z,endPrint
CALL print_char
INC HL
JR nxtILC
endPrint:
INC HL ; Get past "null" terminator
POP BC
POP AF
EX (SP),HL ; PUSH new RET ADDress on stack and restore HL
RET
print_reg:
push af
push de
push bc
push hl
push af
call PRINTINLINE
db 10,13,"A: ",0
pop af
call print_a_hex
call PRINTINLINE
db 10,13,"BC: ",0
ld a,b
call print_a_hex
ld a,c
call print_a_hex
call PRINTINLINE
db 10,13,"DE: ",0
ld a,d
call print_a_hex
ld a,e
call print_a_hex
pop af
call PRINTINLINE
db 10,13,"HL: ",0
ld a,h
call print_a_hex
ld a,l
call print_a_hex
call print_newLine
pop hl
pop bc
pop de
pop af
ret

View File

@@ -0,0 +1,622 @@
; VARS
phase MEM_IDE_FSBUFFER
MEM_FAT_RESERVED: ; Reserved sectors (2byte)
defs 2
MEM_FAT_AMOUNT: ; Amount of FATs (1byte)
defs 1
MEM_FAT_SECTORS: ; Length of FAT (2byte)
defs 2
MEM_FAT_CLUSTERLEN: ; Length of Cluster (1byte)
defs 1
MEM_FAT_COUNT1: ; Counter Var for reading FAT (2byte)
defs 1
MEM_FAT_TMPPOINTER: ; Temporary working pointer
defs 4
MEM_FAT_DATASTART: ; Start of data area
defs 4
MEM_FAT_ROOTSTART: ; Start of Root directory
defs 4
MEM_FAT_FILEREMAIN: ; Remaining sectors in file
defs 4
MEM_FAT_DIRSEC: ; Sectors per directory
defs 2
MEM_FAT_TMPFNAME: ; Temporary filename
defs 16
MEM_FAT_CURDIR: ; Current Directory
defs 80
MEM_FAT_OF0_ATTRIBUTE: ;Current file attribute
defw 0
MEM_FAT_OF0_CCLUST: ;Current cluster of file
defw 0
MEM_FAT_OF0_FATSEC: ;Current sector in FAT
defs 4
MEM_FAT_OF0_DATSEC: ;Current sector in Data
defs 4
MEM_FAT_OF0_DATREM: ;Remaining bytes in Data
defs 4
MEM_FAT_CURRDIR: ;Current directory
defs 4
MEM_FAT_EXEC_CURR:
defw 0
MEM_FAT_EXEC_COUNT:
defw 0
MEM_FAT_EXEC_START:
defw 0
dephase
;-------------------------------------
; Get FAT Root-Table position
;-------------------------------------
fat_get_root_table:
call fat_reset_pointer ;reset fat pointer
; Load first sector on active partition
LD HL, MEM_IDE_POINTER ; pointer to LBA address
LD A,1 ;read 1 sector
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
; check for valid Boot sector
ld a,(MEM_IDE_BUFFER)
cp 0xEB ;first byte should be 0xEB
jp nz, _fat_get_root_table_invalid
; Read and store FS Properties
LD IX,MEM_IDE_BUFFER
LD A,(IX+0x0D)
LD (MEM_FAT_CLUSTERLEN),A
LD A,(IX+0x0E)
LD (MEM_FAT_RESERVED),A
LD A,(IX+0x0F)
LD (MEM_FAT_RESERVED+1),A
LD A,(IX+0x10)
LD (MEM_FAT_AMOUNT),A
LD A,(IX+0x16)
LD (MEM_FAT_SECTORS),A
LD A,(IX+0x17)
LD (MEM_FAT_SECTORS+1),A
;Get Data Start Sector
;calculate fat length
ld bc,(MEM_FAT_SECTORS)
ld a,(MEM_FAT_AMOUNT) ;add fat to cluster number
ld d,0
ld e,a
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_ROOTSTART
ld (MEM_FAT_ROOTSTART+0),hl
ld (MEM_FAT_ROOTSTART+2),bc
;add offset (reserved sectors)
ld hl,(MEM_IDE_BUFFER +0x0E) ; load sectors into hl
ld (MEM_FAT_TMPPOINTER), hl
xor a
ld (MEM_FAT_TMPPOINTER+2),a
ld (MEM_FAT_TMPPOINTER+3),a
ld bc,[MEM_FAT_ROOTSTART]
ld de,[MEM_FAT_TMPPOINTER]
call _fat_math_add32 ;MEM_FAT_ROOTSTART now contains the first sector
;of the Root directory
;add offset (partition location)
call ideif_get_drv_pointer
inc ix
inc ix
push ix
pop de ;copy poiter to hl
ld bc,[MEM_FAT_ROOTSTART]
call _fat_math_add32 ;MEM_FAT_OF0_DATSEC now contains the first sector
;of the cluster
;copy value from MEM_FAT_ROOTSTART to MEM_IDE_POINTER
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
;copy value from MEM_FAT_ROOTSTART to MEM_IDE_POINTER
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_DATASTART
ldi
ldi
ldi
ldi
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
;add offset to data area
;multiply cluster by length of cluster
;calculate sectors for root dir
ld hl,(MEM_IDE_BUFFER+0x11) ;load Maximum root directory entries
ld a,h
ld l,a
xor a ;set a 0, clear carry flag
ld h,a ;shift right by 8 bit = /512
;last step: multiply by 16
ex de,hl
ld bc,16
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_TMPPOINTER
ld (MEM_FAT_TMPPOINTER+0),hl
ld (MEM_FAT_TMPPOINTER+2),bc
ld (MEM_FAT_DIRSEC),hl
; add offset to MEM_FAT_DATASTART
ld de,[MEM_FAT_TMPPOINTER]
ld bc,[MEM_FAT_DATASTART]
call _fat_math_add32 ;MEM_FAT_DATASTART now contains the correct sector
;at teh beginnig of the data area
;done all FS vars populated
;navigate to root directory
ld a,'\'
ld(MEM_FAT_CURDIR),a
xor a
ld(MEM_FAT_CURDIR+1),a
ret
_fat_get_root_table_invalid:
call PRINTINLINE
db 10,13,"Cannot find boot sector.",10,13,0
call ideif_get_drv_pointer
ld (ix+0),0x02
ret
;-------------------------------------
; fat_getfatsec
;
; gets sector in FAT table for the cluster stored in MEM_FAT_OF0_CCLUST
;
; store result in MEM_FAT_OF0_FATSEC
; stores next cluster in MEM_FAT_OF0_CCLUST
;-------------------------------------
fat_getfatsec:
ld HL,(MEM_FAT_OF0_CCLUST) ;load cluster
ld a,h ;if not 0x0000
or l
jp nz, _fat_getfatsec_notroot
;if 0x0000, goto root directory
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_OF0_DATSEC
ldi ;quick and dirty hack to go back to root directory
ldi
ldi
ldi
ret
_fat_getfatsec_notroot:
ld HL,(MEM_FAT_OF0_CCLUST) ;load cluster
;each sector contains 256 clusters
;first 8bits are not needed (/256)
ld a,h ;divide by 256
ld l,a
xor a
ld h,a
ld bc,(MEM_FAT_RESERVED) ;add reserved sectors
add hl,bc
ld(MEM_FAT_OF0_FATSEC+0),hl;store sector
xor a
ld(MEM_FAT_OF0_FATSEC+2),a
ld(MEM_FAT_OF0_FATSEC+3),a
call ideif_get_drv_pointer
inc ix
inc ix
push ix
pop de ;copy poiter to hl
ld bc,[MEM_FAT_OF0_FATSEC]
call _fat_math_add32 ;MEM_FAT_OF0_FATSEC now contains the correct sector
;in the FAT
;read FAT sector
ld hl,MEM_FAT_OF0_FATSEC ;read next sector
ld b,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
;calculate data sector
;multiply cluster by length of cluster
xor a ;clear carry
ld a,(MEM_FAT_CLUSTERLEN)
ld b,0
ld c,a
ld de,(MEM_FAT_OF0_CCLUST) ;load cluster number
dec de ; sub 2 becaus fat starts at 3
dec de
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_OF0_DATSEC
ld (MEM_FAT_OF0_DATSEC+0),hl
ld (MEM_FAT_OF0_DATSEC+2),bc
; add start of data region to addr
ld bc,[MEM_FAT_OF0_DATSEC]
ld de,[MEM_FAT_DATASTART]
call _fat_math_add32 ;MEM_FAT_OF0_FATSEC now contains the correct sector
;in the FAT
;MEM_FAT_OF0_DATSEC now has the first sector of the selected cluster
;reset MEM_FAT_OF0_DATREM to default cluster length
ld a,(MEM_FAT_CLUSTERLEN)
ld l,a
ld h,0
ld (MEM_FAT_OF0_DATREM), hl
;get next cluster
;calculate offset address
ld a,(MEM_FAT_OF0_CCLUST)
RLA ;shift to left (x2)
ld l, a
ld a,0
RLA ;shift in carry flag
ld h,a
ld de,MEM_IDE_BUFFER
add hl,de
;copy pointer (hl to de)
ld de,MEM_FAT_OF0_CCLUST
ldi ;copy byte for next cluster from FAT
ldi
ret
;store data
;-------------------------------------
; fat_readfilesec
;
; reads single sector of file
; must run fat_readfilesec before to initialize
; if a ix 0x00, success
; if a is 0xFF, end reached
;
; DE contains destination address
;-------------------------------------
fat_readfilesec:
;call fat_print_dbg
ld hl,[MEM_FAT_OF0_DATSEC]
ld b,1
;LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector ;read sectore
ld hl,[MEM_FAT_OF0_DATSEC] ;increment pointer to next sector
call _fat_increment_32 ;***
ld hl,(MEM_FAT_OF0_DATREM) ;reduce counter
xor a
ld de,1
sbc hl,de ;decrement counter
ld (MEM_FAT_OF0_DATREM),hl ;store decremented counter
ret nz ;when not zero, exit function
;if zero:
ld a, 0xFF ;preload error code
ld hl,(MEM_FAT_OF0_CCLUST) ;check next chunk
ld de,0xFFFF ;end mark
sbc hl,de ;if Z match
ret z ;If 0xFFFF, end is reched. Return
;if next cluster available:
xor a
call fat_getfatsec ; read next cluster information
ret
;-------------------------------------
; fat_openfile
; search for entry in current directory
;
; DE pointer to file name
; sets:
; - MEM_FAT_OF0_CCLUST
; - MEM_FAT_OF0_ATTRIBUTE
; - MEM_FAT_FILEREMAIN
; if a is 0x00, success
; if a is 0xFF, end reached
;-------------------------------------
fat_openfile:
PUSH DE
;MEM_FAT_TMPFNAME now has valid text to compare
LD HL,[MEM_FAT_TMPFNAME]
call format_filename_fat16
POP DE
fat_openfile_noprepare:
PUSH DE
;prepare pointer
ld hl,MEM_FAT_CURRDIR
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
LD A,(MEM_FAT_DIRSEC) ;init counter for FAT sectors
LD (MEM_FAT_COUNT1),A
LD HL,MEM_IDE_POINTER ;read first sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
_fat_lfs_loop:
LD DE,[MEM_FAT_TMPFNAME]
CALL compare_filename
JR C, _fat_lfs_loop_compare_match ;on match
; prepare next entry
DEC C ;next sector after 16 entries
JR Z,_fat_lfs_loop_compare_next_sector
LD DE, 32 ;length of entry
ADD HL,DE ;increment
JP _fat_lfs_loop
_fat_lfs_loop_compare_next_sector:
ld hl,[MEM_IDE_POINTER]
call _fat_increment_32 ;increment sector
LD A,(MEM_FAT_COUNT1) ; decrement sector count (max FAT length)
DEC A
LD (MEM_FAT_COUNT1),A
JP Z, _fat_lfs_loop_compare_end ; if DE is 0, mmax is reached. End here
;call print_a_hex
LD HL,MEM_IDE_POINTER ;read next sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
ld a,(HL)
or a
jp z, _fat_lfs_loop_compare_end ;skip empty sectors
JP _fat_lfs_loop
_fat_lfs_loop_compare_end:
POP DE
ld a,0xFF
RET
_fat_lfs_loop_compare_match:
; get entry
POP DE
; HL points to Start of Table item
PUSH HL
POP IX
; get important information
ld a,(ix+0x1B) ;first cluster number
ld (MEM_FAT_OF0_CCLUST+1),a
ld a,(ix+0x1A)
ld (MEM_FAT_OF0_CCLUST+0),a
ld a,(ix+0x0B)
ld (MEM_FAT_OF0_ATTRIBUTE+0),a
xor a ;clear carry ;set MEM_FAT_OF0_DATREM to remaining sectors
ld a,(ix+0x1F) ;cluste length shift by 256
rra
ld (MEM_FAT_FILEREMAIN+2),a
ld a,(ix+0x1E)
rra
ld (MEM_FAT_FILEREMAIN+1),a
ld a,(ix+0x1D)
rra
ld (MEM_FAT_FILEREMAIN+0),a
ld a,0
ld (MEM_FAT_FILEREMAIN+3),a
call fat_getfatsec ;get sector information
xor a
RET
;=================== UTIL Functions ===========================
; 32 Bit addition to pointer
; HL has value
;deprecated!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
_fat_math_sector_add_16:
ld (MEM_FAT_TMPPOINTER), hl
xor a
ld (MEM_FAT_TMPPOINTER+2),a
ld (MEM_FAT_TMPPOINTER+3),a
ld de,[MEM_FAT_TMPPOINTER]
ld bc,[MEM_IDE_POINTER]
call _fat_math_add32
ret
;deprecated!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
;hl contains pointer
_fat_increment_32
ld a,(HL) ; byte 0
add 1
ld (hl),a
inc hl
ld a,(HL) ; byte 1
adc 0
ld (hl),a
inc hl
ld a,(HL) ; byte 2
adc 0
ld (hl),a
inc hl
ld a,(HL) ; byte 3
adc 0
ld (hl),a
ret
;bc contains pointer to a (also result)
;de contains pointer to b
_fat_math_add32
push hl
push bc
push de
ld a,(de) ; load lower 16bit for B int from (DE) to HL
ld l,a
inc de
ld a,(de)
ld h,a
inc de
; HL, DE dirty
ld a,(bc) ; load lower 16bit for A int from (BC) to DE
ld e,a
inc bc
ld a,(bc)
ld d,a
; HL now contains A, DE now contains D
add hl,de ;add lower bytes, store carry
pop de ;restore pointers
pop bc ;both now cointain first byte of long-value
ld a,l ;store lower result in (bc)
ld (bc),a
inc bc
ld a,h
ld (bc),a
inc bc
inc de ;also increment de to next byte
inc de
; DE and HL now start at the upper byte
push bc
push de
ld a,(de) ; load upper 16bit for B
ld l,a
inc de
ld a,(de)
ld h,a
inc de
ld a,(bc) ; load upper 16bit for A
ld e,a
inc bc
ld a,(bc)
ld d,a
adc hl,de ;add upper bytes, store carry
pop de
pop bc
ld a,l ;store lower result in (bc)
ld(bc),a
inc bc
ld a,h
ld(bc),a
pop hl
ret
; Multiply 16-bit values (with 32-bit result)
; Operands BC, DE
; Result -> BCHL
_fat_math_mul32:
ld a,c
ld c,b
ld hl,0
ld b,16
_fat_math_mul32_l:
add hl,hl
rla
rl c
jr nc,_fat_math_mul32_noadd
add hl,de
adc a,0
jp nc,_fat_math_mul32_noadd
inc c
_fat_math_mul32_noadd:
djnz _fat_math_mul32_l
ld b,c
ld c,a
ret
; reset LBA pointer to first sector in selected partition
fat_reset_pointer:
call ideif_get_drv_pointer
inc ix
inc ix
push ix
pop hl ;copy poiter to hl
ld de, MEM_IDE_POINTER
jr fat_copy_lba_pointer
; resets LBA pointer (4-byte) to partition start
; HL = from here
; DE = to this destimation
fat_copy_lba_pointer:
PUSH BC
LD B,0
LD C,4
LDIR
POP BC
ret
; compares filenames
; HL points to name1
; DE points to name2
; Carry is set if match
; Destroys DE, AF
compare_filename:
PUSH HL
push BC
LD B, 11 ;Counter
_compare_filename_loop:
LD A,(DE)
LD C,A
LD A,(HL)
INC HL
INC DE
XOR C ;check if identical (should return 0)
JR NZ, _compare_filename_nomatch
djnz _compare_filename_loop ;if not last, continue
POP BC
POP HL
SCF
RET
_compare_filename_nomatch:
POP BC
POP HL
XOR A ; clear carry flag
RET
; formats filename to 8+3 format
; DE points to source filename to string
; HL points to destination
format_filename_fat16:
LD B, 11 ;counter
PUSH HL
LD A, ' '
_format_filename_fat16_clean:
LD (HL),A
INC HL
DJNZ _format_filename_fat16_clean
POP HL ; continue with copy
LD B, 13
_format_filename_fat16_loop:
LD A, (DE) ; load byte
OR A
RET Z ;exit on 0byte
DEC B ;reduce counter
RET Z ;exit after 12 bytes 8+.+3
CP '.' ; check if dot
JR NZ, _format_filename_fat16_loop_copy ; if not continue as usual
INC DE ;else skip char
_format_filename_fat16_loop_skip_8:
LD A,B
CP 5
JR C, _format_filename_fat16_loop
INC HL
DEC B
JR _format_filename_fat16_loop_skip_8
_format_filename_fat16_loop_copy:
LD A, (DE) ; load byte
LD (HL), A ; copy byte
INC HL
INC DE
JP _format_filename_fat16_loop

View File

@@ -0,0 +1,366 @@
;-------------------------------------
; Print current fat directory of MEM_FAT_CURRDIR
;-------------------------------------
fat_print_directory:
ld hl,MEM_FAT_CURRDIR
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
LD DE,(MEM_FAT_SECTORS)
LD (MEM_FAT_COUNT1),DE
LD HL,MEM_IDE_POINTER ;read first sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
call PRINTINLINE
db 10,13," Filename Cluster Size",10,13,0
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
_fat_print_directory_loop: ;loop over each entry (32byte)
LD A,(HL) ; check first byte
PUSH HL ;backup start of entry
POP IX
PUSH HL
;ignore unwanted entries
CP 0x41 ;skip invisible
JP Z, _fat_print_directory_loop_next
CP 0xE5 ;skip deleted
JP Z, _fat_print_directory_loop_next
CP 0x00 ;reached end
JP Z, _fat_print_directory_loop_break
;check file attribute
ld a,(IX+0x0B)
cp 0x10 ;if subdirectors
jp z, _fat_print_directory_dir ;print dir
;else print file
_fat_print_directory_loop_file
;print filename
ld a,' '
call print_char
ld a,' '
call print_char
LD B,8
call print_str_fixed
ld A,'.'
call print_char
LD B,3
call print_str_fixed
call PRINTINLINE
db " 0x",0
;first cluster number
ld a,(ix+0x1B)
call print_a_hex
ld a,(ix+0x1A)
call print_a_hex
call PRINTINLINE
db " 0x",0
ld a,(ix+0x1F)
call print_a_hex
ld a,(ix+0x1E)
call print_a_hex
ld a,(ix+0x1D)
call print_a_hex
ld a,(ix+0x1C)
call print_a_hex
call print_newLine
jr _fat_print_directory_loop_next
_fat_print_directory_dir
ld a,'D'
call print_char
ld a,' '
call print_char
LD B,8
call print_str_fixed
call PRINTINLINE
db " 0x",0
;first cluster number
ld a,(ix+0x1B)
call print_a_hex
ld a,(ix+0x1A)
call print_a_hex
call print_newLine
jr _fat_print_directory_loop_next
_fat_print_directory_loop_next: ; read next entry
DEC C ;next sector after 32 entries
JR Z,_fat_print_directory_loop_next_sector
POP HL ;restore start
LD DE, 32 ;length of entry
ADD HL,DE ;increment
JP _fat_print_directory_loop
_fat_print_directory_loop_next_sector: ; end fo sector. read next sector from disk
POP HL ;clear stack from old hl
LD H,0
LD L,1
call _fat_math_sector_add_16 ;increment sector
LD DE,(MEM_FAT_COUNT1) ; decrement sector count (max FAT length)
DEC DE
LD (MEM_FAT_COUNT1),DE
LD A,D
OR E
RET Z ; if DE is 0, mmax is reached. End here
LD HL,MEM_IDE_POINTER ;read next sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
JP _fat_print_directory_loop
_fat_print_directory_loop_break
POP HL
ret
;-------------------------------------
; Changes current fat directory of MEM_FAT_CURRDIR
; input is relativ path
; DE points to path
;-------------------------------------
fat_cd_single:
push de
; check if user wants to go back (input = '..')
ld a,(de)
cp '.'
jr nz, _fat_cd_navigate; if not, skip
inc de ;check next
ld a,(de)
cp '.'
jr nz, _fat_cd_navigate; if not, skip
ld a,(var_dir+79) ;last byte contains depth
or a; Test if 0
jp z, _fat_cd_navigate_error ;cannot go back any more (already at root)
; check if .. exists in directory
ld a,'.' ;prepare filename buffer
ld hl,[MEM_FAT_TMPFNAME]
ld (hl),a
inc hl
ld (hl),a
inc hl
ld a,0x20 ;clear char 3-11
ld b,11
_fat_cd_navigate_goback_fl:
ld (hl),a
inc hl
djnz _fat_cd_navigate_goback_fl ;fill loop end
call fat_openfile_noprepare ;load file table (only 1st sector needed)
or a ;check for error
jp nz, _fat_cd_navigate_error ;entry not found exception
; find end of path
ld hl,[var_dir+3] ;current position
ld bc,76
ld a,0x00 ;termination char
cpir ;find end
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;hl is now at end of string
ld bc,76
ld a,'\' ;seperation char
cpdr ;serach backwards for "/"
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;hl is now at end of string
inc hl
xor a
ld (hl),a ;set termination char
inc hl
ld (hl),a ;set termination char
ld a,(var_dir+79)
dec a
ld (var_dir+79),a ;decrement dir depth counter
pop de
ld hl,[var_dir+2]
ld a,'\'
ld (hl),a ;set first /
ld hl,MEM_FAT_OF0_DATSEC ;setup directory pointer
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
ret
_fat_cd_navigate
pop de ;get pointer to directory namme
push de ;and re-store it for next use
call fat_openfile ;find 'file' in current directory
_fat_cd_navigate_findsec
or a
jp nz, _fat_cd_navigate_error ;entry not found
ld a, (MEM_FAT_OF0_ATTRIBUTE)
cp 0x10
jp nz, _fat_cd_navigate_errfile
ld a,(var_dir+79)
inc a
ld (var_dir+79),a ;increment dir depth counter
ld hl,[var_dir+2] ;load start of path string
ld a,0 ;load termination char
ld bc,76 ;max length of string
cpir ;find end of path string
dec hl
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;HL now has last element, BC has remaining max length
ld a,(var_dir+79) ;last byte contains depth
cp 1 ;if first path, skip /
jr z, _fat_cd_navigate_findsec_skipslash
ld a,'\'
ld (hl),a
inc hl
_fat_cd_navigate_findsec_skipslash
pop de ;get argument from stack
ex de,hl
push de ;store start to stack
;HL now has start of input string, DE has end of current path
ld bc,09 ;maximum length of directory name +1
_fat_cd_navigate_l2: ;copy new subdirectory
ldi ;copy
jp po,_fat_cd_navigate_inerrorS ;in case of error, abort
ld a,(hl) ;check next char
cp '\' ;end at '\'
jr z, _fat_cd_navigate_end ;else next byte
or a ;or and at 0x00
jr z, _fat_cd_navigate_end ;else next byte
jr _fat_cd_navigate_l2
_fat_cd_navigate_end:
xor a
ld (de),a ;set last byte to 0x00 (termination)
ld hl,MEM_FAT_OF0_DATSEC
;setup directory pointer
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
pop de ;stack cleanup
ret
_fat_cd_navigate_error:
ld hl,[_fat_cd_navigate_error_str]
call print_str
pop de
ret
_fat_cd_navigate_inerrorS: ;with path reset
pop de ;restore former path
dec de ;change pointer to remove previous '\' as well
xor a ;clear a to 0x00
ld (de),a ;set last byte to 0x00 (termination)
jr _fat_cd_navigate_inerrore
_fat_cd_navigate_inerror: ;without path reset
pop de
_fat_cd_navigate_inerrore:
ld hl,[_fat_cd_navigate_inputerr_str]
call print_str
ret
_fat_cd_navigate_errfile:
pop de
ld hl,[_fat_cd_navigate_errfile_str]
call print_str
ret
_fat_cd_navigate_error_str:
db 10,13,"No such directory!",10,13,0
_fat_cd_navigate_inputerr_str:
db 10,13,"Invalid input!",10,13,0
_fat_cd_navigate_errfile_str:
db 10,13,"Cannot cd to file!",10,13,0
fat_exec:
push de
;DE has pointer to arguments
call fat_openfile
or a
jp nz, _fat_exec_notfound ;if not found, abort
;call fat_print_dbg
;load header
ld de, MEM_IDE_BUFFER
call fat_readfilesec
;ld hl, MEM_IDE_BUFFER ;print sector
;ld b,0x20
;call dump_pretty
ld a,(MEM_IDE_BUFFER)
cp 0xC3
jp nz, _fat_exec_notexec
call PRINTINLINE
db 10,13,"Loading ",0
ld hl,[var_input+6]
call print_str
call PRINTINLINE
db " to 0x",0
;get start address
ld bc,(MEM_IDE_BUFFER + 10)
ld a,b
call print_a_hex
ld a,c
call print_a_hex
call PRINTINLINE
db " ... ",0
;bc has start addr
ld (MEM_FAT_EXEC_CURR),bc
ld (MEM_FAT_EXEC_START),bc
;get amount of sectors to load
ld hl,(MEM_IDE_BUFFER + 14)
ld l,h
srl l
ld h,0 ;divide by 512
inc hl ;increment because first sector is always loaded
; hl contains sector count
ld (MEM_FAT_EXEC_COUNT), hl
pop de ; restore filename
call fat_openfile ;reset file information
;start reading
_fat_exec_readloop1:
ld de,(MEM_FAT_EXEC_CURR)
call fat_readfilesec
ld hl,(MEM_FAT_EXEC_CURR)
ld de,512
add hl,de
ld (MEM_FAT_EXEC_CURR),hl
ld hl,(MEM_FAT_EXEC_COUNT)
dec hl
ld (MEM_FAT_EXEC_COUNT),hl
ld a,h
or l
jr z, _fat_exec_read_done
jr _fat_exec_readloop1
_fat_exec_read_done:
call PRINTINLINE
db "Load complete!",10,13,0
ld hl,(MEM_FAT_EXEC_START)
jp (hl)
_fat_exec_notfound:
pop de
call PRINTINLINE
db 10,13,"File not found!",10,13,0
ret
_fat_exec_notexec:
pop de
call PRINTINLINE
db 10,13,"File is not an executable!",10,13,0
ret

View File

@@ -0,0 +1,77 @@
fat_print_dbg:
call PRINTINLINE
db 10,13,"PTR.MEM_IDE_POINTER: 0x",0
ld ix,MEM_IDE_POINTER
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_IDE_PARTITION: 0x",0
ld ix,MEM_IDE_PARTITION
call print_32_hex
call PRINTINLINE
db 10,13,"PTR.MEM_FAT_TMPPOINTER: 0x",0
ld ix,MEM_FAT_TMPPOINTER
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_FAT_DATASTART: 0x",0
ld ix,MEM_FAT_DATASTART
call print_32_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_RESERVED: 0x",0
ld ix,MEM_FAT_RESERVED
call print_16_hex
call PRINTINLINE
db " | VAL.MEM_FAT_AMOUNT: 0x",0
ld a,(MEM_FAT_AMOUNT)
call print_a_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_SECTORS: 0x",0
ld ix,MEM_FAT_SECTORS
call print_16_hex
call PRINTINLINE
db " | VAL.MEM_FAT_COUNT1: 0x",0
ld a,(MEM_FAT_COUNT1)
call print_a_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_OF0_CCLUST: 0x",0
ld ix,MEM_FAT_OF0_CCLUST
call print_16_hex
call PRINTINLINE
db " | PTR.MEM_FAT_OF0_FATSEC: 0x",0
ld ix,MEM_FAT_OF0_FATSEC
call print_32_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_OF0_DATSEC: 0x",0
ld ix,MEM_FAT_OF0_DATSEC
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_FAT_OF0_DATREM: 0x",0
ld ix,MEM_FAT_OF0_DATREM
call print_16_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_ROOTSTART: 0x",0
ld ix,MEM_FAT_ROOTSTART
call print_32_hex
call PRINTINLINE
db " | VAL.MEM_FAT_CLUSTERLEN: 0x",0
ld a,(MEM_FAT_CLUSTERLEN)
call print_a_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_FILEREMAIN: 0x",0
ld ix,MEM_FAT_FILEREMAIN
call print_32_hex
call PRINTINLINE
db " | VAL.MEM_FAT_DIRSEC: 0x",0
ld ix,MEM_FAT_DIRSEC
call print_16_hex
call print_newLine
ret

View File

@@ -130,7 +130,7 @@ ide_regread_8:
; HL contains destination address
;------------------------------------------------------------------------------
ide_readsector_256:
LD C,255 ;Setup counter for 256 words
LD C,0 ;Setup counter for 256 words
ide_readsector_256_waitloop:
LD B, IDE_REG_CMDSTS
@@ -147,32 +147,27 @@ ide_readsector_256_waitloop:
OR IDE_RD ;Set Read bit
OUT (CS_PIA_PC), A ;Write Read to bit controll lines
NOP
NOP
NOP
;NOP
;NOP
IN A,(CS_PIA_PB) ;Load 16-Bit data to buffer
LD (HL), A
INC HL
IN A,(CS_PIA_PA)
LD (HL), A
INC HL
LD A,C
OR A
JP Z,ide_readsector_256_done
DEC C
RET Z
JR ide_readsector_256_waitloop
ide_readsector_256_done:
RET
ide_readsector_512_inv:
LD C,255 ;Setup counter for 256 words
LD C,0 ;Setup counter for 256 words
LD DE, 4096 ;Timeout counter
ide_readsector_512_inv_waitloop:
DEC DE
LD A,D
OR E
JP Z, ide_readsector_timeout
;timeout checked. continue
LD B, IDE_REG_CMDSTS
CALL ide_regread_8
BIT 0,a ;Error Bit set.
@@ -180,15 +175,17 @@ ide_readsector_512_inv_waitloop:
BIT 3,a ;DRQ Bit set. If set, disk has data
JR Z, ide_readsector_512_inv_waitloop ;If not set, wait
LD DE, 2048 ;Timeout counter
LD A, 10010010b ;CommandByte-A, Mode 0, PA IN, PC Out, PB IN
OUT (CS_PIA_CR), A ;Set Data direction to IN
LD A, IDE_REG_DATA ;CS0 and A=0 -> I/O register
OUT (CS_PIA_PC), A ;set register
OR IDE_RD ;Set Read bit
OUT (CS_PIA_PC), A ;Write Read to bit controll lines
;NOP
;NOP
NOP
NOP
NOP
IN A,(CS_PIA_PA) ;Load 16-Bit data to buffer
LD (HL), A
INC HL
@@ -196,10 +193,8 @@ ide_readsector_512_inv_waitloop:
LD (HL), A
INC HL
LD A,C
OR A
JP Z,ide_readsector_256_done
DEC C
RET Z
JR ide_readsector_512_inv_waitloop
ide_readsector_timeout:

View File

@@ -389,6 +389,7 @@ ideif_init_all:
;
; Reads A*512 byte sector into memory
; HL contains pointer to LBA address
; DE contains destination location
; A contains sector count
;------------------------------------------------------------------------------
read_lba_sector:
@@ -416,10 +417,59 @@ read_lba_sector:
LD A,IDE_CMD_READSEC ;send read command
LD B,IDE_REG_CMDSTS
CALL ide_regwrite_8
LD HL,MEM_IDE_BUFFER ;set read/write buffer start address
;LD HL,MEM_IDE_BUFFER ;set read/write buffer start address
EX DE,HL ;transfer destination in DE to HL
call ide_readsector_512_inv ;read 256 words from device
ret
;------------------------------------------------------------------------------
; ideif_drv_sel
;
; Select drive from table
; Prepare variables
;
; A contains drive number
;------------------------------------------------------------------------------
ideif_drv_sel:
ld (MEM_IDE_SELECTED),a
push af
call ideif_get_drv_pointer ;test if drive is marked as available
ld a,(ix+0)
or a
jp nz, _ideif_drv_sel_fail ;if not-> fail
call fat_get_root_table ;else get root table
ld hl,[_ideif_drv_sel_pstr] ;print success message
call print_str
pop af
add 69
ld (var_dir),a ;store drive letter
call print_char
ld a, ':'
ld (var_dir+1),a
ld a, '\'
ld (var_dir+2),a
xor a ;set dir to empty
ld (var_dir+3),a
ld (var_dir+79),a ;set depth counter
ld hl,[_ideif_drv_sel_sstr0]
call print_str
ret
_ideif_drv_sel_fail:
ld hl,[_ideif_drv_sel_pstr]
call print_str
pop af
add 69
call print_char
ld hl,[_ideif_drv_sel_fstr0]
call print_str
xor a ;set dir to empty
ld (var_dir),a
LD DE,0x20
LD BC,0x70
CALL beep
ret
@@ -446,4 +496,12 @@ _ideif_prnt_devtable_sFF:
_ideif_prnt_devtable_master:
db "Master ",0
_ideif_prnt_devtable_slave:
db "Slave ",0
db "Slave ",0
_ideif_drv_sel_pstr:
db 10,13,"Drive ",0
_ideif_drv_sel_fstr0:
db ": not ready",10,13,0
_ideif_drv_sel_sstr0:
db ": selected",10,13,0
_ideif_drv_sel_syn:
db 10,13,"Invalid drive letter",10,13,0

View File

@@ -85,8 +85,10 @@ var_scratch:
defs 16 ;16 bytes space for scratch vars
var_ps2mem:
defs 16 ;16 bytes space for scratch vars
var_buffer:
defb 0 ;var lentgh
var_dir:
defs 80
var_input:
defs 80
var_idebuffer:
defs 768
@@ -116,7 +118,6 @@ BOOT_PHASE0: ;Setup Hardware
ld (var_curseron),a
ld a, " "
ld (var_curserchar),a
;Initialize Console (Serial-Port)
call CONSOLE_INIT
@@ -134,7 +135,10 @@ BOOT_PHASE1_LOOP:
pop hl
jp nz, BOOT_PHASE1_LOOP
;template copy done
xor a ;set dir to empty
ld (var_dir),a
ld (var_dir+1),a
BOOT_PHASE2: ;Hardware initialized.
; Print banner
call print_clear
@@ -177,6 +181,8 @@ BOOT_PHASE2: ;Hardware initialized.
.include "cmd_date.s"
.include "cmd_disk.s"
.include "post.s"
.include "fat16.s"
.include "fat16_cmd.s"
;================================================================
; Strings

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@@ -2,27 +2,27 @@
;Do not make any changes here!
ADDR_RTC equ 0xD0
A_RTS_OFF equ 0x152
A_RTS_ON equ 0x15B
A_RTS_OFF equ 0x17F
A_RTS_ON equ 0x188
BOOT_PHASE0 equ 0x50
BOOT_PHASE1 equ 0x6E
BOOT_PHASE1_LOOP equ 0x77
BOOT_PHASE2 equ 0x82
COMMAND equ 0x17EB
COMMAND_BACKSPACE equ 0x1826
COMMAND_LUT equ 0x176B
COMMAND_PROCESS equ 0x184C
COMMAND_PROCESS_FOUND equ 0x1887
COMMAND_PROCESS_LOOP equ 0x184F
COMMAND_PROCESS_LOOP_STR1 equ 0x1858
COMMAND_PROCESS_LOOP_STR2 equ 0x186E
COMMAND_PROCESS_NEXT_ENTRY equ 0x1873
COMMAND_PROCESS_NEXT_ENTRYI equ 0x1872
COMMAND_PROCESS_NOT_FOUND equ 0x187E
COMMAND_READ equ 0x17F7
CONSOLE_INIT equ 0x9E
CONSOLE_INIT_CTC equ 0x9E
CONSOLE_INIT_SIO equ 0xA6
BOOT_PHASE2 equ 0x89
COMMAND equ 0x1915
COMMAND_BACKSPACE equ 0x1956
COMMAND_LUT equ 0x1883
COMMAND_PROCESS equ 0x197C
COMMAND_PROCESS_FOUND equ 0x19B7
COMMAND_PROCESS_LOOP equ 0x197F
COMMAND_PROCESS_LOOP_STR1 equ 0x1988
COMMAND_PROCESS_LOOP_STR2 equ 0x199E
COMMAND_PROCESS_NEXT_ENTRY equ 0x19A3
COMMAND_PROCESS_NEXT_ENTRYI equ 0x19A2
COMMAND_PROCESS_NOT_FOUND equ 0x19AE
COMMAND_READ equ 0x1927
CONSOLE_INIT equ 0xA5
CONSOLE_INIT_CTC equ 0xA5
CONSOLE_INIT_SIO equ 0xAD
CS_APU_CTRL equ 0xF9
CS_APU_DATA equ 0xF8
CS_BANK equ 0x00
@@ -43,18 +43,18 @@ CS_SIO_A_C equ 0x09
CS_SIO_A_D equ 0x08
CS_SIO_B_C equ 0x0B
CS_SIO_B_D equ 0x0A
DHEX_TO_BYTE equ 0x164
DHEX_TO_BYTE_FAILED equ 0x180
ERR_SYNTAX equ 0x189D
EXEC_RST_08 equ 0xD04
EXEC_RST_10 equ 0xD08
EXEC_RST_18 equ 0xD14
HEX_TO_BIN equ 0x184
HEX_TO_BIN_2 equ 0x192
HEX_TO_INVALID_2 equ 0x199
DHEX_TO_BYTE equ 0x1F6
DHEX_TO_BYTE_FAILED equ 0x212
ERR_SYNTAX equ 0x19CD
EXEC_RST_08 equ 0xD96
EXEC_RST_10 equ 0xD9A
EXEC_RST_18 equ 0xDA6
HEX_TO_BIN equ 0x216
HEX_TO_BIN_2 equ 0x224
HEX_TO_INVALID_2 equ 0x22B
IDE_CMD_IDENT equ 0xEC
IDE_CMD_READSEC equ 0x20
IDE_DEV_TABLE equ 0x1275
IDE_DEV_TABLE equ 0x12FA
IDE_RD equ 0x40
IDE_REG_ALTSTS equ 0x16
IDE_REG_CMDSTS equ 0x0F
@@ -75,7 +75,6 @@ IDE_WR equ 0x20
IIC_CLK equ 0x01
IIC_DATA equ 0x02
INT_VEC equ 0x1B
IN_BUFFER equ 0x402B
IO_AY0_ADDR equ 0x40
IO_AY0_DATA equ 0x41
IO_AY1_ADDR equ 0x42
@@ -97,42 +96,67 @@ IO_RTC_SEC1 equ 0x21
IO_RTC_WEEK equ 0x2C
IO_RTC_YEAR1 equ 0x2B
IO_RTC_YERR0 equ 0x2A
MEM_IDE_BUFFER equ 0x4117
MEM_IDE_DEVICE equ 0x402C
MEM_IDE_DEV_TABLE equ 0x4036
MEM_IDE_FSBUFFER equ 0x4317
MEM_IDE_PARTITION equ 0x402E
MEM_IDE_POINTER equ 0x4032
MEM_IDE_SELECTED equ 0x4076
MEM_IDE_STATUS equ 0x402D
MEM_IDE_STRING_0 equ 0x4077
MEM_IDE_STRING_1 equ 0x409F
MEM_IDE_STRING_2 equ 0x40C7
MEM_IDE_STRING_3 equ 0x40EF
MSG_CLEAR equ 0x14A
NOT_IMPLEMENTED equ 0x1896
OP_CALL equ 0x18F8
OP_CLR equ 0x1A8C
OP_DASM equ 0x1979
OP_DUMP equ 0x1918
OP_EXEC equ 0x18DF
OP_IIC_IN equ 0x1A40
OP_IIC_OUT equ 0x19E0
OP_IO_IN equ 0x19A9
OP_IO_OUT equ 0x19BF
OP_LSDSK equ 0x1CA1
OP_RTIME equ 0x1A90
OP_SELDSK equ 0x1CA5
OP_SET equ 0x1948
OP_STIME equ 0x1C28
POST_CHECK_APU equ 0x1D12
POST_CHECK_IDE_30 equ 0x1D3D
POST_CHECK_IDE_40 equ 0x1D50
POST_CHECK_PIO equ 0x1CED
POST_START equ 0x1CDD
POST_TEST_RTC equ 0x1D6A
MEM_FAT_AMOUNT equ 0x43B8
MEM_FAT_CLUSTERLEN equ 0x43BB
MEM_FAT_COUNT1 equ 0x43BC
MEM_FAT_CURDIR equ 0x43DF
MEM_FAT_CURRDIR equ 0x443F
MEM_FAT_DATASTART equ 0x43C1
MEM_FAT_DIRSEC equ 0x43CD
MEM_FAT_EXEC_COUNT equ 0x4445
MEM_FAT_EXEC_CURR equ 0x4443
MEM_FAT_EXEC_START equ 0x4447
MEM_FAT_FILEREMAIN equ 0x43C9
MEM_FAT_OF0_ATTRIBUTE equ 0x442F
MEM_FAT_OF0_CCLUST equ 0x4431
MEM_FAT_OF0_DATREM equ 0x443B
MEM_FAT_OF0_DATSEC equ 0x4437
MEM_FAT_OF0_FATSEC equ 0x4433
MEM_FAT_RESERVED equ 0x43B6
MEM_FAT_ROOTSTART equ 0x43C5
MEM_FAT_SECTORS equ 0x43B9
MEM_FAT_TMPFNAME equ 0x43CF
MEM_FAT_TMPPOINTER equ 0x43BD
MEM_IDE_BUFFER equ 0x41B6
MEM_IDE_DEVICE equ 0x40CB
MEM_IDE_DEV_TABLE equ 0x40D5
MEM_IDE_FSBUFFER equ 0x43B6
MEM_IDE_PARTITION equ 0x40CD
MEM_IDE_POINTER equ 0x40D1
MEM_IDE_SELECTED equ 0x4115
MEM_IDE_STATUS equ 0x40CC
MEM_IDE_STRING_0 equ 0x4116
MEM_IDE_STRING_1 equ 0x413E
MEM_IDE_STRING_2 equ 0x4166
MEM_IDE_STRING_3 equ 0x418E
MSG_CLEAR equ 0x177
NOT_IMPLEMENTED equ 0x19C6
OP_CALL equ 0x1A28
OP_CD equ 0x1DF8
OP_CLR equ 0x1BBC
OP_DASM equ 0x1AA9
OP_DIR equ 0x1DF4
OP_DUMP equ 0x1A48
OP_EXEC equ 0x1A0F
OP_FSEXEC equ 0x1E15
OP_IIC_IN equ 0x1B70
OP_IIC_OUT equ 0x1B10
OP_IO_IN equ 0x1AD9
OP_IO_OUT equ 0x1AEF
OP_LSDSK equ 0x1DD1
OP_RTIME equ 0x1BC0
OP_SELDSK equ 0x1DD5
OP_SET equ 0x1A78
OP_STIME equ 0x1D58
POST_CHECK_APU equ 0x1E4E
POST_CHECK_IDE_30 equ 0x1E79
POST_CHECK_IDE_40 equ 0x1E8C
POST_CHECK_PIO equ 0x1E29
POST_START equ 0x1E19
POST_TEST_RTC equ 0x1EA6
PRG_RAM_START equ 0x4110
PRG_RAM_TOP equ 0xFF00
PRINTINLINE equ 0x191
PROG_MEM_START equ 0x4000
PROG_ROM_START equ 0x100
RST_00 equ 0x00
@@ -141,316 +165,379 @@ RST_10 equ 0x10
RST_18 equ 0x18
STACK_RAM_TOP equ 0xFFFF
START_ROM equ 0x00
STRCONV_BYTES_TO_HEX equ 0x19B
STRCONV_BYTES_TO_HEX_1 equ 0x1AA
STRCONV_BYTES_TO_HEX_2 equ 0x1B4
STR_Banner_Start equ 0x1E6F
STR_PD_HEADER equ 0x1724
STRCONV_BYTES_TO_HEX equ 0x22D
STRCONV_BYTES_TO_HEX_1 equ 0x23C
STRCONV_BYTES_TO_HEX_2 equ 0x246
STR_Banner_Start equ 0x264F
STR_PD_HEADER equ 0x183C
SYS_BUF_START equ 0x4010
SYS_RAM_START equ 0x4000
VAR_CONSOLE_BAUD equ 0x18
VAR_CONSOLE_CONF equ 0x0F
VDP_MEM equ 0x80
VDP_REG equ 0x81
_COMMAND_PROCESS_FOUND equ 0x1895
_OP_CALL equ 0x1917
_OP_IIC_ACK_ERR equ 0x1A25
_OP_IIC_ACK_ERR_str equ 0x1A2C
_OP_IIC_IN_LOOP equ 0x1A72
_OP_IIC_IN_LOOP_TEXT equ 0x1A7F
_OP_IIC_OUT_LOOP equ 0x19F6
_OP_IIC_OUT_SEND equ 0x1A12
_OP_RTIME_NN equ 0x1A93
_OP_RTIME_RD_CMD equ 0x1B4B
_OP_SELDSK_INVALID equ 0x1CB4
_OP_SELDSK_INVALID_STR equ 0x1CC4
_OP_SET_LOOP equ 0x1960
_OP_STIME_INVALID equ 0x1BEE
_OP_STIME_PROMPT equ 0x1C05
_OP_STIME_PROMPT_ERR equ 0x1C1D
_OP_STIME_STR_DAY equ 0x1B4C
_OP_STIME_STR_HOUR equ 0x1B9D
_OP_STIME_STR_MIN equ 0x1BB8
_OP_STIME_STR_MON equ 0x1B67
_OP_STIME_STR_SEC equ 0x1BD3
_OP_STIME_STR_YEAR equ 0x1B82
_POST_CHECK_APU_FAILED equ 0x1D31
_POST_CHECK_IDE_FAILED equ 0x1D63
_POST_CHECK_PIO_FAILED equ 0x1D06
_POST_TEST_RTC_INVALID equ 0x1DA4
_POST_TEST_RTC_NOTFOUND equ 0x1D9D
_STR_NOT_FOUND equ 0x18B8
_STR_NOT_IMPLEMENTED equ 0x18A4
_STR_SYNTAX equ 0x18CC
_beep_pause_l1 equ 0xD30
_ideif_init_drive_found equ 0x13E9
_ideif_init_drive_loop equ 0x13D1
_ideif_init_drive_nodrv equ 0x13E4
_ideif_init_drive_prt_fnd equ 0x1454
_ideif_init_drive_prt_l1 equ 0x1442
_ideif_init_drive_prt_ln equ 0x144C
_ideif_prnt_devtable_hdr equ 0x1510
_ideif_prnt_devtable_l1 equ 0x12E1
_ideif_prnt_devtable_l1_e2 equ 0x13A7
_ideif_prnt_devtable_l1_es equ 0x1326
_ideif_prnt_devtable_l1_ms equ 0x13A4
_ideif_prnt_devtable_l1_nxt equ 0x12EE
_ideif_prnt_devtable_l1_s00 equ 0x1314
_ideif_prnt_devtable_l1_s01 equ 0x1319
_ideif_prnt_devtable_l1_s02 equ 0x131E
_ideif_prnt_devtable_l1_sFF equ 0x1323
_ideif_prnt_devtable_l1_sel equ 0x12EC
_ideif_prnt_devtable_master equ 0x1574
_ideif_prnt_devtable_s00 equ 0x1548
_ideif_prnt_devtable_s01 equ 0x1553
_ideif_prnt_devtable_s02 equ 0x155E
_ideif_prnt_devtable_sFF equ 0x1569
_ideif_prnt_devtable_slave equ 0x157C
_read_bcd_invalid equ 0x147
_shift4 equ 0x1C9C
beep equ 0xD17
beep_loop equ 0xD19
beep_pause equ 0xD2F
dasm_00 equ 0x91C
dasm_01 equ 0xC08
dasm_02 equ 0x9A2
dasm_03 equ 0xBDA
dasm_08 equ 0xA1F
dasm_09 equ 0xBAD
dasm_0A equ 0x984
dasm_0B equ 0xBF1
dasm_10 equ 0x964
dasm_12 equ 0x9AD
dasm_18 equ 0x927
dasm_1A equ 0x98E
dasm_20 equ 0x941
dasm_22 equ 0xC4E
dasm_27 equ 0x9E7
dasm_28 equ 0x93A
dasm_2A equ 0xC1F
dasm_2F equ 0x9EB
dasm_30 equ 0x932
dasm_32 equ 0x9B8
dasm_37 equ 0x9F7
dasm_38 equ 0x92B
dasm_3A equ 0x998
dasm_3F equ 0x9F3
dasm_76 equ 0x9FB
dasm_80C6 equ 0xA78
dasm_BE equ 0xA15
dasm_C3 equ 0x920
dasm_C88E equ 0xA9E
dasm_C9 equ 0x970
dasm_CD equ 0x96A
dasm_D9 equ 0xA2C
dasm_DD equ 0x952
dasm_DD_01 equ 0xC0F
dasm_DD_09 equ 0xBC8
dasm_DD_22 equ 0xC64
dasm_DD_23 equ 0xBDF
dasm_DD_2A equ 0xC36
dasm_DD_2B equ 0xBF6
dasm_DD_34 equ 0xB78
dasm_DD_35 equ 0xB95
dasm_DD_86 equ 0xA80
dasm_DD_8E equ 0xAA6
dasm_DD_96 equ 0xAC9
dasm_DD_9E equ 0xAE9
dasm_DD_A6 equ 0xB0A
dasm_DD_AE equ 0xB41
dasm_DD_B6 equ 0xB26
dasm_DD_BE equ 0xB5D
dasm_DD_E1 equ 0xCB6
dasm_DD_E3 equ 0xA3C
dasm_DD_E5 equ 0xCA0
dasm_DD_F9 equ 0xC86
dasm_E1 equ 0xCB0
dasm_E3 equ 0xA30
dasm_E5 equ 0xC9A
dasm_E9 equ 0x949
dasm_ED_42 equ 0xBBF
dasm_ED_43 equ 0xC5A
dasm_ED_44 equ 0x9EF
dasm_ED_45 equ 0x97A
dasm_ED_46 equ 0xA06
dasm_ED_4A equ 0xBB6
dasm_ED_4B equ 0xC2B
dasm_ED_4D equ 0x975
dasm_ED_56 equ 0xA0B
dasm_ED_5E equ 0xA10
dasm_ED_A0 equ 0xA54
dasm_ED_A1 equ 0xA66
dasm_ED_A8 equ 0xA5D
dasm_ED_A9 equ 0xA6F
dasm_ED_B0 equ 0xA58
dasm_ED_B1 equ 0xA6A
dasm_ED_B8 equ 0xA61
dasm_ED_B9 equ 0xA73
dasm_F3 equ 0xA00
dasm_F9 equ 0xC7C
dasm_FB equ 0xA03
dasm_FD equ 0x95B
dasm_FD_01 equ 0xC17
dasm_FD_09 equ 0xBD1
dasm_FD_22 equ 0xC70
dasm_FD_23 equ 0xBE8
dasm_FD_2A equ 0xC42
dasm_FD_2B equ 0xBFF
dasm_FD_34 equ 0xB84
dasm_FD_35 equ 0xBA1
dasm_FD_86 equ 0xA8F
dasm_FD_8E equ 0xAB5
dasm_FD_96 equ 0xAD5
dasm_FD_9E equ 0xAF7
dasm_FD_A6 equ 0xB16
dasm_FD_AE equ 0xB4D
dasm_FD_B6 equ 0xB31
dasm_FD_BE equ 0xB68
dasm_FD_E1 equ 0xCBE
dasm_FD_E3 equ 0xA48
dasm_FD_E5 equ 0xCA8
dasm_FD_F9 equ 0xC90
dasm_FF equ 0x97F
dasm_UU equ 0xCC6
dasm_UW equ 0xCCA
dasm__AND equ 0xB05
dasm__CP equ 0xB59
dasm__DEC equ 0xB90
dasm__ED_47 equ 0x9D7
dasm__ED_4F equ 0x9DF
dasm__ED_57 equ 0x9C7
dasm__ED_5F equ 0x9CF
dasm__INC equ 0xB73
dasm__LD equ 0x9C3
dasm__OR equ 0xB22
dasm__SBC equ 0xAE1
dasm__SUB equ 0xAC4
dasm__XOR equ 0xB3C
dasm_opcode_table equ 0x4C4
dasm_print16hex_addr equ 0x2F1
dasm_print8hex equ 0x309
dasm_printFlags_table equ 0xCCF
dasm_printRegister8_table equ 0xCDF
dasm_printRegister8_table_HL equ 0xCFF
dasm_printRegisterIX_table equ 0xCE7
dasm_printRegisterIY_table equ 0xCEF
dasm_printRegisterSP_table equ 0xCF7
disassemble equ 0x1B5
disassemble_continue equ 0x29B
disassemble_err equ 0x28B
disassemble_next equ 0x1B9
disassemble_print_opcode_params_end equ 0x288
disassemble_print_opcode_params_loop equ 0x234
disassemble_print_opcode_raw equ 0x1F6
disassemble_print_opcode_raw_fill equ 0x20A
disassemble_table_first_match equ 0x2CD
disassemble_table_found equ 0x2E7
disassemble_table_notfound equ 0x2EB
disassemble_table_seek equ 0x2A9
disassemble_table_seek_loop equ 0x2AD
dump_pretty equ 0x16C9
dump_pretty_ascii equ 0x16F3
dump_pretty_ascii_cont equ 0x1711
dump_pretty_ascii_loop equ 0x16FB
dump_pretty_ascii_none equ 0x170C
dump_pretty_col equ 0x16E6
dump_pretty_end equ 0x1723
dump_pretty_nextrow equ 0x1717
dump_pretty_row equ 0x16D1
ide_printerror equ 0xE04
ide_readsector_256 equ 0xD83
ide_readsector_256_done equ 0xDB2
ide_readsector_256_waitloop equ 0xD85
ide_readsector_512_inv equ 0xDB3
ide_readsector_512_inv_waitloop equ 0xDB8
ide_readsector_timeout equ 0xDEE
ide_regread_8 equ 0xD65
ide_regwrite_8 equ 0xD49
ide_reset equ 0xD3C
ide_writesector_256 equ 0xE03
ideif_get_drv_pointer equ 0x1497
ideif_init_all equ 0x14AB
ideif_init_devtable equ 0x12B5
ideif_init_drive equ 0x13C8
ideif_prnt_devtable equ 0x12D3
iic_init equ 0x15DD
iic_read_ack equ 0x161C
iic_receive_buffer equ 0x15AE
iic_receive_buffer_done equ 0x15D1
iic_receive_buffer_err equ 0x15D7
iic_receive_buffer_loop equ 0x15BF
iic_receive_byte equ 0x16A2
iic_receive_byte_loop equ 0x16AF
iic_send_ack equ 0x1642
iic_send_buffer equ 0x1584
iic_send_buffer_done equ 0x15A2
iic_send_buffer_err equ 0x15A8
iic_send_buffer_loop equ 0x1594
iic_send_byte equ 0x167C
iic_send_byte_loop equ 0x1688
iic_send_ebit equ 0x15FB
iic_send_nack equ 0x165F
iic_send_sbit equ 0x15E6
_COMMAND_PROCESS_FOUND equ 0x19C5
_OP_CALL equ 0x1A47
_OP_IIC_ACK_ERR equ 0x1B55
_OP_IIC_ACK_ERR_str equ 0x1B5C
_OP_IIC_IN_LOOP equ 0x1BA2
_OP_IIC_IN_LOOP_TEXT equ 0x1BAF
_OP_IIC_OUT_LOOP equ 0x1B26
_OP_IIC_OUT_SEND equ 0x1B42
_OP_RTIME_NN equ 0x1BC3
_OP_RTIME_RD_CMD equ 0x1C7B
_OP_SELDSK_INVALID equ 0x1DE4
_OP_SELDSK_INVALID_STR equ 0x1DFC
_OP_SET_LOOP equ 0x1A90
_OP_STIME_INVALID equ 0x1D1E
_OP_STIME_PROMPT equ 0x1D35
_OP_STIME_PROMPT_ERR equ 0x1D4D
_OP_STIME_STR_DAY equ 0x1C7C
_OP_STIME_STR_HOUR equ 0x1CCD
_OP_STIME_STR_MIN equ 0x1CE8
_OP_STIME_STR_MON equ 0x1C97
_OP_STIME_STR_SEC equ 0x1D03
_OP_STIME_STR_YEAR equ 0x1CB2
_POST_CHECK_APU_FAILED equ 0x1E6D
_POST_CHECK_IDE_FAILED equ 0x1E9F
_POST_CHECK_PIO_FAILED equ 0x1E42
_POST_TEST_RTC_INVALID equ 0x1EE0
_POST_TEST_RTC_NOTFOUND equ 0x1ED9
_STR_NOT_FOUND equ 0x19E8
_STR_NOT_IMPLEMENTED equ 0x19D4
_STR_SYNTAX equ 0x19FC
_beep_pause_l1 equ 0xDC2
_compare_filename_loop equ 0x2313
_compare_filename_nomatch equ 0x2321
_fat_cd_navigate equ 0x24C4
_fat_cd_navigate_end equ 0x250A
_fat_cd_navigate_errfile equ 0x2532
_fat_cd_navigate_errfile_str equ 0x2564
_fat_cd_navigate_error equ 0x251C
_fat_cd_navigate_error_str equ 0x253A
_fat_cd_navigate_findsec equ 0x24C9
_fat_cd_navigate_findsec_skipslash equ 0x24F5
_fat_cd_navigate_goback_fl equ 0x2480
_fat_cd_navigate_inerror equ 0x252A
_fat_cd_navigate_inerrorS equ 0x2524
_fat_cd_navigate_inerrore equ 0x252B
_fat_cd_navigate_inputerr_str equ 0x2551
_fat_cd_navigate_l2 equ 0x24FB
_fat_exec_notexec equ 0x262B
_fat_exec_notfound equ 0x2612
_fat_exec_read_done equ 0x25FA
_fat_exec_readloop1 equ 0x25DC
_fat_get_root_table_invalid equ 0x210B
_fat_getfatsec_notroot equ 0x214A
_fat_increment_32 equ 0x2299
_fat_lfs_loop equ 0x2211
_fat_lfs_loop_compare_end equ 0x224B
_fat_lfs_loop_compare_match equ 0x224F
_fat_lfs_loop_compare_next_sector equ 0x2223
_fat_math_add32 equ 0x22AD
_fat_math_mul32 equ 0x22DE
_fat_math_mul32_l equ 0x22E5
_fat_math_mul32_noadd equ 0x22F2
_fat_math_sector_add_16 equ 0x2285
_fat_print_directory_dir equ 0x2401
_fat_print_directory_loop equ 0x2394
_fat_print_directory_loop_break equ 0x245E
_fat_print_directory_loop_file equ 0x23B0
_fat_print_directory_loop_next equ 0x242C
_fat_print_directory_loop_next_sector equ 0x2437
_format_filename_fat16_clean equ 0x232A
_format_filename_fat16_loop equ 0x2331
_format_filename_fat16_loop_copy equ 0x2344
_format_filename_fat16_loop_skip_8 equ 0x233B
_ideif_drv_sel_fail equ 0x15AB
_ideif_drv_sel_fstr0 equ 0x1668
_ideif_drv_sel_pstr equ 0x165F
_ideif_drv_sel_sstr0 equ 0x1676
_ideif_drv_sel_syn equ 0x1683
_ideif_init_drive_found equ 0x146E
_ideif_init_drive_loop equ 0x1456
_ideif_init_drive_nodrv equ 0x1469
_ideif_init_drive_prt_fnd equ 0x14D9
_ideif_init_drive_prt_l1 equ 0x14C7
_ideif_init_drive_prt_ln equ 0x14D1
_ideif_prnt_devtable_hdr equ 0x15EB
_ideif_prnt_devtable_l1 equ 0x1366
_ideif_prnt_devtable_l1_e2 equ 0x142C
_ideif_prnt_devtable_l1_es equ 0x13AB
_ideif_prnt_devtable_l1_ms equ 0x1429
_ideif_prnt_devtable_l1_nxt equ 0x1373
_ideif_prnt_devtable_l1_s00 equ 0x1399
_ideif_prnt_devtable_l1_s01 equ 0x139E
_ideif_prnt_devtable_l1_s02 equ 0x13A3
_ideif_prnt_devtable_l1_sFF equ 0x13A8
_ideif_prnt_devtable_l1_sel equ 0x1371
_ideif_prnt_devtable_master equ 0x164F
_ideif_prnt_devtable_s00 equ 0x1623
_ideif_prnt_devtable_s01 equ 0x162E
_ideif_prnt_devtable_s02 equ 0x1639
_ideif_prnt_devtable_sFF equ 0x1644
_ideif_prnt_devtable_slave equ 0x1657
_read_bcd_invalid equ 0x14E
_shift4 equ 0x1DCC
beep equ 0xDA9
beep_loop equ 0xDAB
beep_pause equ 0xDC1
compare_filename equ 0x230F
dasm_00 equ 0x9AE
dasm_01 equ 0xC9A
dasm_02 equ 0xA34
dasm_03 equ 0xC6C
dasm_08 equ 0xAB1
dasm_09 equ 0xC3F
dasm_0A equ 0xA16
dasm_0B equ 0xC83
dasm_10 equ 0x9F6
dasm_12 equ 0xA3F
dasm_18 equ 0x9B9
dasm_1A equ 0xA20
dasm_20 equ 0x9D3
dasm_22 equ 0xCE0
dasm_27 equ 0xA79
dasm_28 equ 0x9CC
dasm_2A equ 0xCB1
dasm_2F equ 0xA7D
dasm_30 equ 0x9C4
dasm_32 equ 0xA4A
dasm_37 equ 0xA89
dasm_38 equ 0x9BD
dasm_3A equ 0xA2A
dasm_3F equ 0xA85
dasm_76 equ 0xA8D
dasm_80C6 equ 0xB0A
dasm_BE equ 0xAA7
dasm_C3 equ 0x9B2
dasm_C88E equ 0xB30
dasm_C9 equ 0xA02
dasm_CD equ 0x9FC
dasm_D9 equ 0xABE
dasm_DD equ 0x9E4
dasm_DD_01 equ 0xCA1
dasm_DD_09 equ 0xC5A
dasm_DD_22 equ 0xCF6
dasm_DD_23 equ 0xC71
dasm_DD_2A equ 0xCC8
dasm_DD_2B equ 0xC88
dasm_DD_34 equ 0xC0A
dasm_DD_35 equ 0xC27
dasm_DD_86 equ 0xB12
dasm_DD_8E equ 0xB38
dasm_DD_96 equ 0xB5B
dasm_DD_9E equ 0xB7B
dasm_DD_A6 equ 0xB9C
dasm_DD_AE equ 0xBD3
dasm_DD_B6 equ 0xBB8
dasm_DD_BE equ 0xBEF
dasm_DD_E1 equ 0xD48
dasm_DD_E3 equ 0xACE
dasm_DD_E5 equ 0xD32
dasm_DD_F9 equ 0xD18
dasm_E1 equ 0xD42
dasm_E3 equ 0xAC2
dasm_E5 equ 0xD2C
dasm_E9 equ 0x9DB
dasm_ED_42 equ 0xC51
dasm_ED_43 equ 0xCEC
dasm_ED_44 equ 0xA81
dasm_ED_45 equ 0xA0C
dasm_ED_46 equ 0xA98
dasm_ED_4A equ 0xC48
dasm_ED_4B equ 0xCBD
dasm_ED_4D equ 0xA07
dasm_ED_56 equ 0xA9D
dasm_ED_5E equ 0xAA2
dasm_ED_A0 equ 0xAE6
dasm_ED_A1 equ 0xAF8
dasm_ED_A8 equ 0xAEF
dasm_ED_A9 equ 0xB01
dasm_ED_B0 equ 0xAEA
dasm_ED_B1 equ 0xAFC
dasm_ED_B8 equ 0xAF3
dasm_ED_B9 equ 0xB05
dasm_F3 equ 0xA92
dasm_F9 equ 0xD0E
dasm_FB equ 0xA95
dasm_FD equ 0x9ED
dasm_FD_01 equ 0xCA9
dasm_FD_09 equ 0xC63
dasm_FD_22 equ 0xD02
dasm_FD_23 equ 0xC7A
dasm_FD_2A equ 0xCD4
dasm_FD_2B equ 0xC91
dasm_FD_34 equ 0xC16
dasm_FD_35 equ 0xC33
dasm_FD_86 equ 0xB21
dasm_FD_8E equ 0xB47
dasm_FD_96 equ 0xB67
dasm_FD_9E equ 0xB89
dasm_FD_A6 equ 0xBA8
dasm_FD_AE equ 0xBDF
dasm_FD_B6 equ 0xBC3
dasm_FD_BE equ 0xBFA
dasm_FD_E1 equ 0xD50
dasm_FD_E3 equ 0xADA
dasm_FD_E5 equ 0xD3A
dasm_FD_F9 equ 0xD22
dasm_FF equ 0xA11
dasm_UU equ 0xD58
dasm_UW equ 0xD5C
dasm__AND equ 0xB97
dasm__CP equ 0xBEB
dasm__DEC equ 0xC22
dasm__ED_47 equ 0xA69
dasm__ED_4F equ 0xA71
dasm__ED_57 equ 0xA59
dasm__ED_5F equ 0xA61
dasm__INC equ 0xC05
dasm__LD equ 0xA55
dasm__OR equ 0xBB4
dasm__SBC equ 0xB73
dasm__SUB equ 0xB56
dasm__XOR equ 0xBCE
dasm_opcode_table equ 0x556
dasm_print16hex_addr equ 0x383
dasm_print8hex equ 0x39B
dasm_printFlags_table equ 0xD61
dasm_printRegister8_table equ 0xD71
dasm_printRegister8_table_HL equ 0xD91
dasm_printRegisterIX_table equ 0xD79
dasm_printRegisterIY_table equ 0xD81
dasm_printRegisterSP_table equ 0xD89
disassemble equ 0x247
disassemble_continue equ 0x32D
disassemble_err equ 0x31D
disassemble_next equ 0x24B
disassemble_print_opcode_params_end equ 0x31A
disassemble_print_opcode_params_loop equ 0x2C6
disassemble_print_opcode_raw equ 0x288
disassemble_print_opcode_raw_fill equ 0x29C
disassemble_table_first_match equ 0x35F
disassemble_table_found equ 0x379
disassemble_table_notfound equ 0x37D
disassemble_table_seek equ 0x33B
disassemble_table_seek_loop equ 0x33F
dump_pretty equ 0x17E1
dump_pretty_ascii equ 0x180B
dump_pretty_ascii_cont equ 0x1829
dump_pretty_ascii_loop equ 0x1813
dump_pretty_ascii_none equ 0x1824
dump_pretty_col equ 0x17FE
dump_pretty_end equ 0x183B
dump_pretty_nextrow equ 0x182F
dump_pretty_row equ 0x17E9
endPrint equ 0x19F
fat_cd_single equ 0x2460
fat_copy_lba_pointer equ 0x2306
fat_exec equ 0x257B
fat_get_root_table equ 0x203E
fat_getfatsec equ 0x2133
fat_openfile equ 0x21E4
fat_openfile_noprepare equ 0x21EC
fat_print_directory equ 0x234B
fat_readfilesec equ 0x21B9
fat_reset_pointer equ 0x22F7
format_filename_fat16 equ 0x2325
ide_printerror equ 0xE89
ide_readsector_256 equ 0xE15
ide_readsector_256_waitloop equ 0xE17
ide_readsector_512_inv equ 0xE3E
ide_readsector_512_inv_waitloop equ 0xE43
ide_readsector_timeout equ 0xE73
ide_regread_8 equ 0xDF7
ide_regwrite_8 equ 0xDDB
ide_reset equ 0xDCE
ide_writesector_256 equ 0xE88
ideif_drv_sel equ 0x1573
ideif_get_drv_pointer equ 0x151C
ideif_init_all equ 0x1530
ideif_init_devtable equ 0x133A
ideif_init_drive equ 0x144D
ideif_prnt_devtable equ 0x1358
iic_init equ 0x16F5
iic_read_ack equ 0x1734
iic_receive_buffer equ 0x16C6
iic_receive_buffer_done equ 0x16E9
iic_receive_buffer_err equ 0x16EF
iic_receive_buffer_loop equ 0x16D7
iic_receive_byte equ 0x17BA
iic_receive_byte_loop equ 0x17C7
iic_send_ack equ 0x175A
iic_send_buffer equ 0x169C
iic_send_buffer_done equ 0x16BA
iic_send_buffer_err equ 0x16C0
iic_send_buffer_loop equ 0x16AC
iic_send_byte equ 0x1794
iic_send_byte_loop equ 0x17A0
iic_send_ebit equ 0x1713
iic_send_nack equ 0x1777
iic_send_sbit equ 0x16FE
mon_var_template equ 0x44
mon_var_template_end equ 0x370
param_01 equ 0x317
param_02 equ 0x33E
param_03 equ 0x35B
param_03_done equ 0x393
param_03_neg equ 0x37C
param_04 equ 0x397
param_04_i equ 0x3A7
param_05 equ 0x3AD
param_06 equ 0x3BA
param_07 equ 0x3D4
param_08 equ 0x3E1
param_09 equ 0x3F6
param_09_0A equ 0x3FC
param_0A equ 0x3ED
param_10 equ 0x40B
param_11 equ 0x41B
param_11_12 equ 0x42A
param_11_12_all equ 0x44A
param_11_12_def equ 0x43D
param_11_12_ix equ 0x442
param_11_12_iy equ 0x447
param_12 equ 0x423
param_13 equ 0x45B
param_80 equ 0x47A
param_80_seek equ 0x481
param_81 equ 0x471
param_comma equ 0x4B5
param_printRegister equ 0x490
param_printRegisterA equ 0x4AE
param_printRegisterHL equ 0x4A6
print_a_hex equ 0x107
print_bcd equ 0x119
print_char equ 0xD7
print_clear equ 0xEA
print_newLine equ 0xF1
print_str equ 0xDF
print_str_end equ 0xE9
print_str_fixed equ 0x1763
print_wait_out equ 0xFC
read_bcd equ 0x131
read_char equ 0x11F
read_lba_sector equ 0x14BE
str_dev_done equ 0x1508
str_dev_waitready equ 0x14F0
str_error_start equ 0xE37
str_error_start1 equ 0xE54
str_error_start2 equ 0xE5D
str_error_time equ 0xE66
str_post_apu equ 0x1DFC
str_post_ide_30 equ 0x1DAB
str_post_ide_40 equ 0x1DC6
str_post_nd equ 0x1E32
str_post_ok equ 0x1E6A
str_post_pio equ 0x1DE1
str_post_rtc equ 0x1E17
str_post_rtc_iv equ 0x1E40
mon_var_template_end equ 0x40F
nxtILC equ 0x194
param_01 equ 0x3A9
param_02 equ 0x3D0
param_03 equ 0x3ED
param_03_done equ 0x425
param_03_neg equ 0x40E
param_04 equ 0x429
param_04_i equ 0x439
param_05 equ 0x43F
param_06 equ 0x44C
param_07 equ 0x466
param_08 equ 0x473
param_09 equ 0x488
param_09_0A equ 0x48E
param_0A equ 0x47F
param_10 equ 0x49D
param_11 equ 0x4AD
param_11_12 equ 0x4BC
param_11_12_all equ 0x4DC
param_11_12_def equ 0x4CF
param_11_12_ix equ 0x4D4
param_11_12_iy equ 0x4D9
param_12 equ 0x4B5
param_13 equ 0x4ED
param_80 equ 0x50C
param_80_seek equ 0x513
param_81 equ 0x503
param_comma equ 0x547
param_printRegister equ 0x522
param_printRegisterA equ 0x540
param_printRegisterHL equ 0x538
print_16_hex equ 0x16A
print_32_hex equ 0x151
print_a_hex equ 0x10E
print_bcd equ 0x120
print_char equ 0xDE
print_clear equ 0xF1
print_newLine equ 0xF8
print_reg equ 0x1A4
print_str equ 0xE6
print_str_end equ 0xF0
print_str_fixed equ 0x187B
print_wait_out equ 0x103
read_bcd equ 0x138
read_char equ 0x126
read_lba_sector equ 0x1543
str_dev_done equ 0x15E3
str_dev_waitready equ 0x15CB
str_error_start equ 0xEBC
str_error_start1 equ 0xED9
str_error_start2 equ 0xEE2
str_error_time equ 0xEEB
str_post_apu equ 0x1F38
str_post_ide_30 equ 0x1EE7
str_post_ide_40 equ 0x1F02
str_post_nd equ 0x1F6E
str_post_ok equ 0x1FA6
str_post_pio equ 0x1F1D
str_post_rtc equ 0x1F53
str_post_rtc_iv equ 0x1F7C
var_apu_present equ 0x400A
var_buffer equ 0x402B
var_buffer_len equ 0x4000
var_bytes_count equ 0x411A
var_curserchar equ 0x4006
@@ -459,7 +546,9 @@ var_curseron equ 0x4005
var_curserstate equ 0x4004
var_curserx equ 0x4002
var_cursery equ 0x4003
var_idebuffer equ 0x402C
var_dir equ 0x402B
var_idebuffer equ 0x40CB
var_input equ 0x407B
var_last_char equ 0x4001
var_opcode equ 0x4114
var_opcode_length equ 0x4116

View File

@@ -7,24 +7,42 @@ MEM_FAT_AMOUNT: ; Amount of FATs (1byte)
defs 1
MEM_FAT_SECTORS: ; Length of FAT (2byte)
defs 2
MEM_FAT_CLUSTERLEN: ; Length of Cluster (1byte)
defs 1
MEM_FAT_COUNT1: ; Counter Var for reading FAT (2byte)
defs 1
MEM_FAT_TMPPOINTER: ; Temporary working pointer
defs 4
MEM_FAT_TMPPOINTER1: ; Temporary working pointer
MEM_FAT_DATASTART: ; Start of data area
defs 4
MEM_FAT_ROOTSTART: ; Start of Root directory
defs 4
MEM_FAT_FILEREMAIN: ; Remaining sectors in file
defs 4
MEM_FAT_DIRSEC: ; Sectors per directory
defs 2
MEM_FAT_TMPFNAME: ; Temporary filename
defs 16
MEM_FAT_CURDIR: ; Current Directory
defs 80
MEM_FAT_OF0_ATTRIBUTE: ;Current file attribute
defw 0
MEM_FAT_OF0_CCLUST: ;Current cluster of file
defw 0
MEM_FAT_OF0_FATSEC: ;Current sector in FAT
defs 4
MEM_FAT_OF0_DATSEC: ;Current sector in Data
defs 4
MEM_FAT_OF0_DATREM: ;Remaining sector in Data
defs 2
MEM_FAT_OF0_DATREM: ;Remaining bytes in Data
defs 4
MEM_FAT_CURRDIR: ;Current directory
defs 4
MEM_FAT_EXEC_CURR:
defw 0
MEM_FAT_EXEC_COUNT:
defw 0
MEM_FAT_EXEC_START:
defw 0
dephase
@@ -34,10 +52,10 @@ MEM_FAT_OF0_DATREM: ;Remaining sector in Data
fat_get_root_table:
call fat_reset_pointer ;reset fat pointer
;call fat_print_dbg
; Load first sector on active partition
LD HL, MEM_IDE_POINTER ; pointer to LBA address
LD A,1 ;read 1 sector
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
; check for valid Boot sector
@@ -45,13 +63,10 @@ fat_get_root_table:
cp 0xEB ;first byte should be 0xEB
jp nz, _fat_get_root_table_invalid
;debug sector
;ld hl, MEM_IDE_BUFFER
;ld b,20
;call dump_pretty
; Read and store FS Properties
LD IX,MEM_IDE_BUFFER
LD A,(IX+0x0D)
LD (MEM_FAT_CLUSTERLEN),A
LD A,(IX+0x0E)
LD (MEM_FAT_RESERVED),A
LD A,(IX+0x0F)
@@ -63,28 +78,95 @@ fat_get_root_table:
LD A,(IX+0x17)
LD (MEM_FAT_SECTORS+1),A
;Get Root FAT
LD A, (MEM_FAT_SECTORS+1) ; load FAT Sector size to DE
LD D,A
LD A, (MEM_FAT_SECTORS)
LD E,A
XOR A ; clear HL
LD H,A
LD L,A
LD A,(MEM_FAT_AMOUNT) ; Load counter for multiplication
LD B,A
_fat_get_root_table_loop: ; multiply
ADD HL,DE
DJNZ _fat_get_root_table_loop
;Get Data Start Sector
;calculate fat length
ld bc,(MEM_FAT_SECTORS)
ld a,(MEM_FAT_AMOUNT) ;add fat to cluster number
ld d,0
ld e,a
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_ROOTSTART
ld (MEM_FAT_ROOTSTART+0),hl
ld (MEM_FAT_ROOTSTART+2),bc
; add reserved sectors
LD D,0
LD A,(MEM_FAT_RESERVED)
LD E,A
ADD HL,DE
;add offset (reserved sectors)
ld hl,(MEM_IDE_BUFFER +0x0E) ; load sectors into hl
ld (MEM_FAT_TMPPOINTER), hl
xor a
ld (MEM_FAT_TMPPOINTER+2),a
ld (MEM_FAT_TMPPOINTER+3),a
ld bc,[MEM_FAT_ROOTSTART]
ld de,[MEM_FAT_TMPPOINTER]
call _fat_math_add32 ;MEM_FAT_ROOTSTART now contains the first sector
;of the Root directory
;add offset (partition location)
call ideif_get_drv_pointer
inc ix
inc ix
push ix
pop de ;copy poiter to hl
ld bc,[MEM_FAT_ROOTSTART]
call _fat_math_add32 ;MEM_FAT_OF0_DATSEC now contains the first sector
;of the cluster
;copy value from MEM_FAT_ROOTSTART to MEM_IDE_POINTER
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
;copy value from MEM_FAT_ROOTSTART to MEM_IDE_POINTER
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_DATASTART
ldi
ldi
ldi
ldi
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
;add offset to data area
;multiply cluster by length of cluster
;calculate sectors for root dir
ld hl,(MEM_IDE_BUFFER+0x11) ;load Maximum root directory entries
ld a,h
ld l,a
xor a ;set a 0, clear carry flag
ld h,a ;shift right by 8 bit = /512
;last step: multiply by 16
ex de,hl
ld bc,16
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_TMPPOINTER
ld (MEM_FAT_TMPPOINTER+0),hl
ld (MEM_FAT_TMPPOINTER+2),bc
ld (MEM_FAT_DIRSEC),hl
; add offset to MEM_FAT_DATASTART
ld de,[MEM_FAT_TMPPOINTER]
ld bc,[MEM_FAT_DATASTART]
call _fat_math_add32 ;MEM_FAT_DATASTART now contains the correct sector
;at teh beginnig of the data area
;done all FS vars populated
;navigate to root directory
ld a,'\'
ld(MEM_FAT_CURDIR),a
xor a
ld(MEM_FAT_CURDIR+1),a
; add
call _fat_math_sector_add_16
ret
_fat_get_root_table_invalid:
@@ -95,14 +177,21 @@ _fat_get_root_table_invalid:
ret
;-------------------------------------
; Print current fat directory of MEM_IDE_POINTER
; Print current fat directory of MEM_FAT_CURRDIR
;-------------------------------------
fat_print_directory:
ld hl,MEM_FAT_CURRDIR
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
LD DE,(MEM_FAT_SECTORS)
LD (MEM_FAT_COUNT1),DE
LD HL,MEM_IDE_POINTER ;read first sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
call PRINTINLINE
@@ -209,6 +298,8 @@ _fat_print_directory_loop_next_sector: ; end fo sector. read next sector from d
LD HL,MEM_IDE_POINTER ;read next sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
@@ -226,83 +317,165 @@ _fat_print_directory_loop_break_dirty
; call print_str ;print
ret
;-------------------------------------
; FAT locate file startcluster
;
; DE pointer to file name
;-------------------------------------
fat_lfs:
PUSH DE
LD HL,[MEM_FAT_TMPFNAME] ; prepare filename
CALL format_filename_fat16
LD A,16 ;init counter for FAT sectors
LD (MEM_FAT_COUNT1),A
LD HL,MEM_IDE_POINTER ;read first sector
LD B,1
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
_fat_lfs_loop:
POP DE
PUSH DE
CALL compare_filename
JR C, _fat_lfs_loop_compare_match ;on match
; prepare next entry
DEC C ;next sector after 16 entries
JR Z,_fat_lfs_loop_compare_next_sector
LD DE, 32 ;length of entry
ADD HL,DE ;increment
JP _fat_lfs_loop
_fat_lfs_loop_compare_next_sector:
LD H,0
LD L,1
call _fat_math_sector_add_16 ;increment sector
LD A,(MEM_FAT_COUNT1) ; decrement sector count (max FAT length)
DEC A
LD (MEM_FAT_COUNT1),A
JP Z, _fat_lfs_loop_compare_end ; if DE is 0, mmax is reached. End here
;call print_a_hex
LD HL,MEM_IDE_POINTER ;read next sector
LD B,1
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
JP _fat_lfs_loop
_fat_lfs_loop_compare_end:
POP DE
LD HL, [str_file_notfound]
CALL print_str ;print
RET
_fat_lfs_loop_compare_match:
; get entry
POP DE
LD B,8
call print_str_fixed
ld A,'.'
call print_char
LD B,3
call print_str_fixed
LD HL, [str_file_found]
CALL print_str ;print
RET
; fat change directory
; relative path
; DE pointer to path
fat_cd_single:
push de
; check if user wants to go back (input = '..')
ld a,(de)
cp '.'
jr nz, _fat_cd_navigate; if not, skip
inc de ;check next
ld a,(de)
cp '.'
jr nz, _fat_cd_navigate; if not, skip
ld a,(var_dir+79) ;last byte contains depth
or a; Test if 0
jp z, _fat_cd_navigate_error ;cannot go back any more (already at root)
; check if .. exists in directory
ld a,'.' ;prepare filename buffer
ld hl,[MEM_FAT_TMPFNAME]
ld (hl),a
inc hl
ld (hl),a
inc hl
ld a,0x20 ;clear char 3-11
ld b,11
_fat_cd_navigate_goback_fl:
ld (hl),a
inc hl
djnz _fat_cd_navigate_goback_fl ;fill loop end
call fat_openfile_noprepare ;load file table (only 1st sector needed)
or a ;check for error
jp nz, _fat_cd_navigate_error ;entry not found exception
; find end of path
ld hl,[var_dir+3] ;current position
ld bc,76
ld a,0x00 ;termination char
cpir ;find end
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;hl is now at end of string
ld bc,76
ld a,'\' ;seperation char
cpdr ;serach backwards for "/"
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;hl is now at end of string
inc hl
xor a
ld (hl),a ;set termination char
inc hl
ld (hl),a ;set termination char
ld a,(var_dir+79)
dec a
ld (var_dir+79),a ;decrement dir depth counter
pop de
ld hl,[var_dir+2]
ld a,'\'
ld (hl),a ;set first /
ld hl,MEM_FAT_OF0_DATSEC ;setup directory pointer
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
ret
_fat_cd_navigate
pop de ;get pointer to directory namme
push de ;and re-store it for next use
call fat_openfile ;find 'file' in current directory
_fat_cd_navigate_findsec
or a
jp nz, _fat_cd_navigate_error ;entry not found
ld a, (MEM_FAT_OF0_ATTRIBUTE)
cp 0x10
jp nz, _fat_cd_navigate_errfile
ld a,(var_dir+79)
inc a
ld (var_dir+79),a ;increment dir depth counter
ld hl,[var_dir+2] ;load start of path string
ld a,0 ;load termination char
ld bc,76 ;max length of string
cpir ;find end of path string
dec hl
jp po,_fat_cd_navigate_inerror ;in case of error, abort
;HL now has last element, BC has remaining max length
ld a,(var_dir+79) ;last byte contains depth
cp 1 ;if first path, skip /
jr z, _fat_cd_navigate_findsec_skipslash
ld a,'\'
ld (hl),a
inc hl
_fat_cd_navigate_findsec_skipslash
pop de ;get argument from stack
ex de,hl
push de ;store start to stack
;HL now has start of input string, DE has end of current path
ld bc,09 ;maximum length of directory name +1
_fat_cd_navigate_l2: ;copy new subdirectory
ldi ;copy
jp po,_fat_cd_navigate_inerrorS ;in case of error, abort
ld a,(hl) ;check next char
cp '\' ;end at '\'
jr z, _fat_cd_navigate_end ;else next byte
or a ;or and at 0x00
jr z, _fat_cd_navigate_end ;else next byte
jr _fat_cd_navigate_l2
_fat_cd_navigate_end:
xor a
ld (de),a ;set last byte to 0x00 (termination)
ld hl,MEM_FAT_OF0_DATSEC
;setup directory pointer
ld de,MEM_FAT_CURRDIR
ldi
ldi
ldi
ldi
pop de ;stack cleanup
ret
_fat_cd_navigate_error:
ld hl,[_fat_cd_navigate_error_str]
call print_str
pop de
ret
_fat_cd_navigate_inerrorS: ;with path reset
pop de ;restore former path
dec de ;change pointer to remove previous '\' as well
xor a ;clear a to 0x00
ld (de),a ;set last byte to 0x00 (termination)
jr _fat_cd_navigate_inerrore
_fat_cd_navigate_inerror: ;without path reset
pop de
_fat_cd_navigate_inerrore:
ld hl,[_fat_cd_navigate_inputerr_str]
call print_str
ret
_fat_cd_navigate_errfile:
pop de
ld hl,[_fat_cd_navigate_errfile_str]
call print_str
ret
_fat_cd_navigate_error_str:
db 10,13,"No such directory!",10,13,0
_fat_cd_navigate_inputerr_str:
db 10,13,"Invalid input!",10,13,0
_fat_cd_navigate_errfile_str:
db 10,13,"Cannot cd to file!",10,13,0
;=================== UTIL Functions ===========================
; 32 Bit addition to pointer
; HL has value
;deprecated!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
_fat_math_sector_add_16:
ld (MEM_FAT_TMPPOINTER), hl
xor a
@@ -313,7 +486,26 @@ _fat_math_sector_add_16:
ld bc,[MEM_IDE_POINTER]
call _fat_math_add32
ret
;deprecated!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
;hl contains pointer
_fat_increment_32
ld a,(HL) ; byte 0
add 1
ld (hl),a
inc hl
ld a,(HL) ; byte 1
adc 0
ld (hl),a
inc hl
ld a,(HL) ; byte 2
adc 0
ld (hl),a
inc hl
ld a,(HL) ; byte 3
adc 0
ld (hl),a
ret
;bc contains pointer to a (also result)
;de contains pointer to b
_fat_math_add32
@@ -369,6 +561,30 @@ _fat_math_add32
pop hl
ret
; Multiply 16-bit values (with 32-bit result)
; Operands BC, DE
; Result -> BCHL
_fat_math_mul32:
ld a,c
ld c,b
ld hl,0
ld b,16
_fat_math_mul32_l:
add hl,hl
rla
rl c
jr nc,_fat_math_mul32_noadd
add hl,de
adc a,0
jp nc,_fat_math_mul32_noadd
inc c
_fat_math_mul32_noadd:
djnz _fat_math_mul32_l
ld b,c
ld c,a
ret
; reset LBA pointer to first sector in selected partition
fat_reset_pointer:
call ideif_get_drv_pointer
@@ -390,73 +606,3 @@ fat_copy_lba_pointer:
POP BC
ret
; compares filenames
; HL points to name1
; DE points to name2
; Carry is set if match
; Destroys DE, AF
compare_filename:
PUSH HL
PUSH BC
LD B, 11 ;Counter
_compare_filename_loop:
LD A,(DE)
LD C,A
LD A,(HL)
XOR C ;check if identical (should return 0)
JR NZ, _compare_filename_nomatch
DEC B ;decrement counter
JR NZ, _compare_filename_loop ;if not last, continue
POP BC ;if last, it matches
POP HL
SCF
RET
_compare_filename_nomatch:
POP BC
POP HL
SCF
CCF
RET
; formats filename to 8+3 format
; DE points to source filename to string
; HL points to destination
format_filename_fat16:
LD B, 11 ;counter
PUSH HL
XOR A
_format_filename_fat16_clean:
LD (HL),A
INC HL
DJNZ _format_filename_fat16_clean
POP HL ; continue with copy
LD B, 13
_format_filename_fat16_loop:
LD A, (DE) ; load byte
OR A
RET Z ;exit on 0byte
DEC B ;reduce counter
RET Z ;exit after 12 bytes 8+.+3
CP '.' ; check if dot
JR NZ, _format_filename_fat16_loop_copy ; if not continue as usual
INC DE ;else skip char
_format_filename_fat16_loop_skip_8:
LD A,B
CP 5
JR C, _format_filename_fat16_loop
INC HL
DEC B
JR _format_filename_fat16_loop_skip_8
_format_filename_fat16_loop_copy:
LD A, (DE) ; load byte
LD (HL), A ; copy byte
INC HL
INC DE
JP _format_filename_fat16_loop
str_file_notfound:
db "File not found!",13,10,0
str_file_found:
db " File located!",13,10,0

View File

@@ -11,10 +11,23 @@
; store result in MEM_FAT_OF0_FATSEC
; stores next cluster in MEM_FAT_OF0_CCLUST
fat_getfatsec:
ld HL,(MEM_FAT_OF0_CCLUST) ;load cluster
ld a,h ;if not 0x0000
or l
jp nz, _fat_getfatsec_notroot
;if 0x0000, goto root directory
ld hl,MEM_FAT_ROOTSTART
ld de,MEM_FAT_OF0_DATSEC
ldi ;quick and dirty hack to go back to root directory
ldi
ldi
ldi
ret
_fat_getfatsec_notroot:
ld HL,(MEM_FAT_OF0_CCLUST) ;load cluster
;each sector contains 256 clusters
;first 8bits are not needed (/256)
ld a,h ;divide by 256
ld l,a
xor a
@@ -22,7 +35,7 @@ fat_getfatsec:
ld bc,(MEM_FAT_RESERVED) ;add reserved sectors
add hl,bc
ld(MEM_FAT_OF0_FATSEC+0),hl;store sector to MEM_FAT_TMPPOINTER1
ld(MEM_FAT_OF0_FATSEC+0),hl;store sector
xor a
ld(MEM_FAT_OF0_FATSEC+2),a
ld(MEM_FAT_OF0_FATSEC+3),a
@@ -36,17 +49,40 @@ fat_getfatsec:
call _fat_math_add32 ;MEM_FAT_OF0_FATSEC now contains the correct sector
;in the FAT
call fat_print_dbg
;read FAT sector
ld hl,MEM_FAT_OF0_FATSEC ;read next sector
ld b,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
ld hl, MEM_IDE_BUFFER
ld b,20
call dump_pretty
;calculate data sector
;multiply cluster by length of cluster
xor a ;clear carry
ld a,(MEM_FAT_CLUSTERLEN)
ld b,0
ld c,a
ld de,(MEM_FAT_OF0_CCLUST) ;load cluster number
dec de ; sub 2 becaus fat starts at 3
dec de
call _fat_math_mul32
; BCHL contains result -> store to PTR.MEM_FAT_OF0_DATSEC
ld (MEM_FAT_OF0_DATSEC+0),hl
ld (MEM_FAT_OF0_DATSEC+2),bc
; add start of data region to addr
ld bc,[MEM_FAT_OF0_DATSEC]
ld de,[MEM_FAT_DATASTART]
call _fat_math_add32 ;MEM_FAT_OF0_FATSEC now contains the correct sector
;in the FAT
;MEM_FAT_OF0_DATSEC now has the first sector of the selected cluster
;reset MEM_FAT_OF0_DATREM to default cluster length
ld a,(MEM_FAT_CLUSTERLEN)
ld l,a
ld h,0
ld (MEM_FAT_OF0_DATREM), hl
;get next cluster
;calculate offset address
ld a,(MEM_FAT_OF0_CCLUST)
RLA ;shift to left (x2)
@@ -56,14 +92,234 @@ fat_getfatsec:
ld h,a
ld de,MEM_IDE_BUFFER
add hl,de
;copy pointer
;copy pointer (hl to de)
ld de,MEM_FAT_OF0_CCLUST
ldi ;copy byte for next cluster from FAT
ldi
call fat_print_dbg
ret
;store data
; reads single sector of file
; must run fat_readfilesec before to initialize
; if a ix 0x00, success
; if a is 0xFF, end reached
fat_readfilesec:
call fat_print_dbg
ld hl,[MEM_FAT_OF0_DATSEC]
ld b,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector ;read sectore
ld hl,[MEM_FAT_OF0_DATSEC] ;increment pointer to next sector
call _fat_increment_32 ;***
ld hl,(MEM_FAT_OF0_DATREM) ;reduce counter
xor a
ld de,1
sbc hl,de ;decrement counter
ld (MEM_FAT_OF0_DATREM),hl ;store decremented counter
ret nz ;when not zero, exit function
;if zero:
ld a, 0xFF ;preload error code
ld hl,(MEM_FAT_OF0_CCLUST) ;check next chunk
ld de,0xFFFF ;end mark
sbc hl,de ;if Z match
ret z ;If 0xFFFF, end is reched. Return
;if next cluster available:
xor a
call fat_getfatsec ; read next cluster information
ret
;-------------------------------------
; FAT open file
;
; DE pointer to file name
;-------------------------------------
fat_openfile:
PUSH DE
;MEM_FAT_TMPFNAME now has valid text to compare
LD HL,[MEM_FAT_TMPFNAME]
call format_filename_fat16
POP DE
fat_openfile_noprepare:
PUSH DE
;prepare pointer
ld hl,MEM_FAT_CURRDIR
ld de,MEM_IDE_POINTER
ldi
ldi
ldi
ldi
LD A,(MEM_FAT_DIRSEC) ;init counter for FAT sectors
LD (MEM_FAT_COUNT1),A
LD HL,MEM_IDE_POINTER ;read first sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
;LD HL,MEM_IDE_BUFFER ;Dump IDE Buffer
;LD B,32
;call dump_pretty
;LD HL,MEM_FAT_TMPFNAME ;Dump IDE Buffer
;LD B,1
;call dump_pretty
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
_fat_lfs_loop:
LD DE,[MEM_FAT_TMPFNAME]
CALL compare_filename
JR C, _fat_lfs_loop_compare_match ;on match
; prepare next entry
DEC C ;next sector after 16 entries
JR Z,_fat_lfs_loop_compare_next_sector
LD DE, 32 ;length of entry
ADD HL,DE ;increment
JP _fat_lfs_loop
_fat_lfs_loop_compare_next_sector:
ld hl,[MEM_IDE_POINTER]
call _fat_increment_32 ;increment sector
LD A,(MEM_FAT_COUNT1) ; decrement sector count (max FAT length)
DEC A
LD (MEM_FAT_COUNT1),A
JP Z, _fat_lfs_loop_compare_end ; if DE is 0, mmax is reached. End here
;call print_a_hex
LD HL,MEM_IDE_POINTER ;read next sector
LD B,1
LD DE, MEM_IDE_BUFFER ;where to store data?
call read_lba_sector
LD HL, MEM_IDE_BUFFER ;set buffer start
LD C,16 ;set entries counter
ld a,(HL)
or a
jp z, _fat_lfs_loop_compare_end ;skip empty sectors
JP _fat_lfs_loop
_fat_lfs_loop_compare_end:
POP DE
;LD HL, [str_file_notfound]
;CALL print_str ;print
ld a,0xFF
RET
_fat_lfs_loop_compare_match:
; get entry
POP DE
; HL points to Start of Table item
PUSH HL
POP IX
; get important information
ld a,(ix+0x1B) ;first cluster number
ld (MEM_FAT_OF0_CCLUST+1),a
ld a,(ix+0x1A)
ld (MEM_FAT_OF0_CCLUST+0),a
ld a,(ix+0x0B)
ld (MEM_FAT_OF0_ATTRIBUTE+0),a
xor a ;clear carry ;set MEM_FAT_OF0_DATREM to remaining sectors
ld a,(ix+0x1F) ;cluste length shift by 256
rra
ld (MEM_FAT_FILEREMAIN+2),a
ld a,(ix+0x1E)
rra
ld (MEM_FAT_FILEREMAIN+1),a
ld a,(ix+0x1D)
rra
ld (MEM_FAT_FILEREMAIN+0),a
ld a,0
ld (MEM_FAT_FILEREMAIN+3),a
call fat_getfatsec ;get sector information
;call print_newLine
;LD B,8
;call print_str_fixed
;ld A,'.'
;call print_char
;LD B,3
;call print_str_fixed
;LD HL, [str_file_found]
;CALL print_str ;print
xor a
RET
; compares filenames
; HL points to name1
; DE points to name2
; Carry is set if match
; Destroys DE, AF
compare_filename:
PUSH HL
push BC
LD B, 11 ;Counter
_compare_filename_loop:
LD A,(DE)
LD C,A
LD A,(HL)
INC HL
INC DE
XOR C ;check if identical (should return 0)
JR NZ, _compare_filename_nomatch
djnz _compare_filename_loop ;if not last, continue
POP BC
POP HL
SCF
RET
_compare_filename_nomatch:
POP BC
POP HL
XOR A ; clear carry flag
RET
; formats filename to 8+3 format
; DE points to source filename to string
; HL points to destination
format_filename_fat16:
LD B, 11 ;counter
PUSH HL
LD A, ' '
_format_filename_fat16_clean:
LD (HL),A
INC HL
DJNZ _format_filename_fat16_clean
POP HL ; continue with copy
LD B, 13
_format_filename_fat16_loop:
LD A, (DE) ; load byte
OR A
RET Z ;exit on 0byte
DEC B ;reduce counter
RET Z ;exit after 12 bytes 8+.+3
CP '.' ; check if dot
JR NZ, _format_filename_fat16_loop_copy ; if not continue as usual
INC DE ;else skip char
_format_filename_fat16_loop_skip_8:
LD A,B
CP 5
JR C, _format_filename_fat16_loop
INC HL
DEC B
JR _format_filename_fat16_loop_skip_8
_format_filename_fat16_loop_copy:
LD A, (DE) ; load byte
LD (HL), A ; copy byte
INC HL
INC DE
JP _format_filename_fat16_loop
str_file_notfound:
db "File not found!",13,10,0
str_file_found:
db " File located!",13,10,0

View File

@@ -1,170 +1,107 @@
.include "extern_symbols.s" ;include monitor symbols.
org 0x8000
org 0x6000
sel_dsk:
call ideif_drv_sel
call fat_print_dbg
ret
org 0x8010
call fat_print_dbg
ret
org 0x8020
call fat_print_directory
ret
org 0x8030
ld hl,0x0006
ld (MEM_FAT_OF0_CCLUST),hl
call fat_getfatsec
ret
fat_print_dbg:
call PRINTINLINE
db 10,13,"PTR.MEM_IDE_POINTER: 0x",0
ld ix,MEM_IDE_POINTER
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_IDE_PARTITION: 0x",0
ld ix,MEM_IDE_PARTITION
call print_32_hex
call PRINTINLINE
db 10,13,"PTR.MEM_FAT_TMPPOINTER: 0x",0
ld ix,MEM_FAT_TMPPOINTER
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_FAT_TMPPOINTER1: 0x",0
ld ix,MEM_FAT_TMPPOINTER1
call print_32_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_RESERVED: 0x",0
ld ix,MEM_FAT_RESERVED
call print_16_hex
call PRINTINLINE
db " | VAL.MEM_FAT_AMOUNT: 0x",0
ld a,(MEM_FAT_AMOUNT)
call print_a_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_SECTORS: 0x",0
ld ix,MEM_FAT_SECTORS
call print_16_hex
call PRINTINLINE
db " | VAL.MEM_FAT_COUNT1: 0x",0
ld a,(MEM_FAT_COUNT1)
call print_a_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_OF0_CCLUST: 0x",0
ld ix,MEM_FAT_OF0_CCLUST
call print_16_hex
call PRINTINLINE
db " | PTR.MEM_FAT_OF0_FATSEC: 0x",0
ld ix,MEM_FAT_OF0_FATSEC
call print_32_hex
call PRINTINLINE
db 10,13,"VAL.MEM_FAT_OF0_DATSEC: 0x",0
ld ix,MEM_FAT_OF0_DATSEC
call print_32_hex
call PRINTINLINE
db " | PTR.MEM_FAT_OF0_DATREM: 0x",0
ld ix,MEM_FAT_OF0_DATREM
call print_16_hex
call print_newLine
ret
print_32_hex:
ld a,(ix+3)
call print_a_hex
ld a,(ix+2)
call print_a_hex
ld a,(ix+1)
call print_a_hex
ld a,(ix+0)
call print_a_hex
ret
print_16_hex:
ld a,(ix+1)
call print_a_hex
ld a,(ix+0)
call print_a_hex
ret
; a contains drive to select
; populate fs vars as well
ideif_drv_sel:
ld (MEM_IDE_SELECTED),a
push af
call ideif_get_drv_pointer ;test if drive is marked as available
ld a,(ix+0)
MEM_FAT_EXEC_CURR .equ var_scratch+10
MEM_FAT_EXEC_COUNT .equ var_scratch+12
MEM_FAT_EXEC_START .equ var_scratch+14
fat_exec:
ld de,[var_input+6] ;prepare input like to mimic rom behaviour
push de
;DE has pointer to arguments
call fat_openfile
or a
jp nz, _ideif_drv_sel_fail ;if not-> fail
call fat_get_root_table ;else get root table
;backup tmp pointer
ld hl,(MEM_IDE_POINTER)
ld de,(MEM_IDE_PARTITION) ;use MEM_IDE_PARTITION to backup the pointer
call fat_copy_lba_pointer
ld hl,[_ideif_drv_sel_pstr] ;print success message
jp nz, _fat_exec_notfound ;if not found, abort
;call fat_print_dbg
;load header
ld de, MEM_IDE_BUFFER
call fat_readfilesec
;ld hl, MEM_IDE_BUFFER ;print sector
;ld b,0x20
;call dump_pretty
ld a,(MEM_IDE_BUFFER)
cp 0xC3
jp nz, _fat_exec_notexec
call PRINTINLINE
db 10,13,"Loading ",0
ld hl,[var_input+6]
call print_str
pop af
add 69
call print_char
ld hl,[_ideif_drv_sel_sstr0]
call print_str
ret
_ideif_drv_sel_fail:
ld hl,[_ideif_drv_sel_pstr]
call print_str
pop af
add 69
call print_char
ld hl,[_ideif_drv_sel_fstr0]
call print_str
LD DE,0x20
LD BC,0x70
CALL beep
call PRINTINLINE
db " to 0x",0
;get start address
ld bc,(MEM_IDE_BUFFER + 10)
ld a,b
call print_a_hex
ld a,c
call print_a_hex
call PRINTINLINE
db " ... ",0
;bc has start addr
ld (MEM_FAT_EXEC_CURR),bc
ld (MEM_FAT_EXEC_START),bc
;get amount of sectors to load
ld hl,(MEM_IDE_BUFFER + 14)
ld l,h
srl l
ld h,0 ;divide by 512
inc hl ;increment because first sector is always loaded
; hl contains sector count
ld (MEM_FAT_EXEC_COUNT), hl
pop de ; restore filename
call fat_openfile ;reset file information
;start reading
_fat_exec_readloop1:
ld de,(MEM_FAT_EXEC_CURR)
call fat_readfilesec
ld hl,(MEM_FAT_EXEC_CURR)
ld de,512
add hl,de
ld (MEM_FAT_EXEC_CURR),hl
ld hl,(MEM_FAT_EXEC_COUNT)
dec hl
ld (MEM_FAT_EXEC_COUNT),hl
ld a,h
or l
jr z, _fat_exec_read_done
jr _fat_exec_readloop1
_fat_exec_read_done:
call PRINTINLINE
db "Load complete!",10,13,0
ld hl,(MEM_FAT_EXEC_START)
jp (hl)
_fat_exec_notfound:
call PRINTINLINE
db 10,13,"File not found!",10,13,0
ret
_ideif_drv_sel_pstr:
db 10,13,"Drive ",0
_ideif_drv_sel_fstr0:
db ": not ready",10,13,0
_ideif_drv_sel_sstr0:
db ": selected",10,13,0
_ideif_drv_sel_syn:
db 10,13,"Invalid drive letter",10,13,0
.include "fat16.s" ;include monitor symbols.
.include "fat16_file.s" ;include monitor symbols.
_fat_exec_notexec:
call PRINTINLINE
db 10,13,"File is not an executable!",10,13,0
ret
;------------------------------------------------------------------------------
; PRINTINLINE
;
; String output function
;
; Prints in-line data (bytes immediately following the PRINTINLINE call)
; until a string terminator is encountered (0 - null char).
;------------------------------------------------------------------------------
PRINTINLINE:
EX (SP),HL ; PUSH HL and put RET ADDress into HL
PUSH AF
PUSH BC
nxtILC:
LD A,(HL)
CP 0
JR Z,endPrint
CALL print_char
INC HL
JR nxtILC
endPrint:
INC HL ; Get past "null" terminator
POP BC
POP AF
EX (SP),HL ; PUSH new RET ADDress on stack and restore HL
RET
_test_loop:
call fat_readfilesec
push af
ld hl, MEM_IDE_BUFFER ;print sector
ld b,0x20
call dump_pretty
;call PRINTINLINE
;db 10,13,"SECREAD",10,13,0
pop af
or a
jp z, _test_loop
;check if end of file
ret

View File

@@ -1,99 +1,16 @@
:07800000CD5A82CD3A80C980
:04801000CD3A80C91C
:04802000CD8583C9BE
:10803000210600223543CDBB85C9CD0C860A0D50E3
:1080400054522E4D454D5F4944455F504F494E5463
:1080500045523A20202020307800DD213240CD34B6
:1080600082CD0C8620207C20205054522E4D454D30
:108070005F4944455F504152544954494F4E3A205C
:108080002020307800DD212E40CD3482CD0C860AB0
:108090000D5054522E4D454D5F4641545F544D5046
:1080A000504F494E5445523A20307800DD211D434F
:1080B000CD3482CD0C8620207C20205054522E4D71
:1080C000454D5F4641545F544D50504F494E5445C5
:1080D00052313A20307800DD212143CD3482CD0C5D
:1080E000860A0D56414C2E4D454D5F4641545F5218
:1080F000455345525645443A202020307800DD2132
:108100001743CD4D82CD0C862020202020207C20BE
:108110002056414C2E4D454D5F4641545F414D4FD9
:10812000554E543A2020202020203078003A194320
:10813000CD0701CD0C860A0D56414C2E4D454D5FA5
:108140004641545F534543544F52533A2020202018
:10815000307800DD211A43CD4D82CD0C86202020C1
:108160002020207C202056414C2E4D454D5F46411D
:10817000545F434F554E54313A2020202020203068
:1081800078003A1C43CD0701CD0C860A0D56414CB0
:108190002E4D454D5F4641545F4F46305F43434C43
:1081A0005553543A20307800DD213543CD4D82CDF2
:1081B0000C862020202020207C20205054522E4D40
:1081C000454D5F4641545F4F46305F4641545345ED
:1081D000433A2020307800DD213743CD3482CD0C66
:1081E000860A0D56414C2E4D454D5F4641545F4F1A
:1081F00046305F4441545345433A20307800DD21F6
:108200003B43CD3482CD0C8620207C20205054521C
:108210002E4D454D5F4641545F4F46305F444154BB
:1082200052454D3A2020307800DD213F43CD4D822C
:10823000CDF100C9DD7E03CD0701DD7E02CD070152
:10824000DD7E01CD0701DD7E00CD0701C9DD7E01A8
:10825000CD0701DD7E00CD0701C9327640F5CD970F
:1082600014DD7E00B7C28882CD0B832A3240ED5BDD
:108270002E40CD548521A482CDDF00F1C645CDD757
:108280000021BB82CDDF00C921A482CDDF00F1C671
:1082900045CDD70021AD82CDDF0011200001700057
:1082A000CD170DC90A0D447269766520003A206E1B
:1082B0006F742072656164790A0D003A2073656CF1
:1082C00065637465640A0D000A0D496E76616C6918
:1082D00064206472697665206C65747465720A0D39
:1082E000000000000000000000000000000000008E
:1082F000000000000000000000000000000000007E
:108300000000000000000000000000CD4585213283
:10831000403E01CDBE143A1741FEEBC25D83DD2124
:108320001741DD7E0E321743DD7E0F321843DD7EAE
:1083300010321943DD7E16321A43DD7E17321B439D
:108340003A1B43573A1A435FAF676F3A19434719CD
:1083500010FD16003A17435F19CD0085C9CD0C8674
:108360000A0D43616E6E6F742066696E6420626FE1
:108370006F7420736563746F722E0A0D00CD9714AD
:10838000DD360002C9ED5B1A43ED531C4321324038
:108390000601CDBE14CD0C860A0D202046696C6501
:1083A0006E616D652020202020436C7573746572AA
:1083B0002053697A650A0D002117410E107EE5DD14
:1083C000E1E5FE41CA6384FEE5CA6384FE00CA9407
:1083D00084DD7E0BFE10CA31843E20CDD7003E20C6
:1083E000CDD7000608CD63173E2ECDD7000603CDAE
:1083F0006317CD0C8620307800DD7E1BCD0701DDB4
:108400007E1ACD0701CD0C862020307800DD7E1F3E
:10841000CD0701DD7E1ECD0701DD7E1DCD0701DD0F
:108420007E1CCD07013E0ACDD7003E0DCDD70018EA
:10843000323E44CDD7003E20CDD7000608CD63178D
:10844000CD0C862020202020307800DD7E1BCD073B
:1084500001DD7E1ACD07013E0ACDD7003E0DCDD7F6
:108460000018000D2808E111200019C3BD83E12682
:10847000002E01CD0085ED5B1C431BED531C437AA0
:10848000B3CA95842132400601CDBE142117410E96
:1084900010C3BD83E1C9D5212543CD73853E10327C
:1084A0001C432132400601CDBE142117410E10D1CC
:1084B000D5CD5D8538330D280711200019C3AF8451
:1084C00026002E01CD00853A1C433D321C43CAE1F3
:1084D000842132400601CDBE142117410E10C3AFD6
:1084E00084D1219885CDDF00C9D10608CD63173E20
:1084F0002ECDD7000603CD631721AA85CDDF00C995
:10850000221D43AF321F43322043111D430132402D
:10851000CD1485C9E5C5D51A6F131A67130A5F0311
:108520000A5719D1C17D02037C02031313C5D51A62
:108530006F131A67130A5F030A57ED5AD1C17D0200
:10854000037C02E1C9CD9714DD23DD23DDE5E111D4
:1085500032401800C506000E04EDB0C1C9E5C506DD
:108560000B1A4F7EA920070520F7C1E137C9C1E1E9
:10857000373FC9060BE5AF772310FCE1060D1AB7AC
:10858000C805C8FE2E200A1378FE0538F123051809
:10859000F71A772313C37E8546696C65206E6F7466
:1085A00020666F756E64210D0A002046696C652097
:1085B0006C6F6361746564210D0A002A35437C6F1A
:1085C000AF67ED4B174309223743AF323943323A95
:1085D00043CD9714DD23DD23DDE5D1013743CD14F1
:1085E00085CD3A802137430601CDBE1421174106BF
:1085F00014CDC9163A3543176F3E0017671117415E
:1086000019113543EDA0EDA0CD3A80C9E3F5C57E43
:0F861000FE002806CDD7002318F523C1F1E3C9DA
:10600000118140D5CDD321B7C29A6011B641CDA838
:10601000213AB641FEC3C2B260CD91010A0D4C6F68
:106020006164696E672000218140CDE600CD910159
:1060300020746F20307800ED4BC04178CD0E01798F
:10604000CD0E01CD9101202E2E2E2000ED431540C6
:10605000ED4319402AC4416CCB3D26002322174052
:10606000D1CDD321ED5B1540CDA8212A15401100DB
:1060700002192215402A17402B2217407CB528020E
:1060800018E2CD91014C6F616420636F6D706C6597
:106090007465210A0D002A1940E9CD91010A0D46C7
:1060A000696C65206E6F7420666F756E64210A0DD1
:1060B00000C9CD91010A0D46696C65206973206E97
:1060C0006F7420616E2065786563757461626C65BC
:1060D000210A0D00C9CDA821F521B6410620CDE148
:0760E00017F1B7CAD560C932
:00000001FF

File diff suppressed because it is too large Load Diff

View File

@@ -1,98 +1,15 @@
!8000 CD 5A 82 CD 3A 80 C9
!8010 CD 3A 80 C9
!8020 CD 85 83 C9
!8030 21 06 00 22 35 43 CD BB 85 C9 CD 0C 86 0A 0D 50
!8040 54 52 2E 4D 45 4D 5F 49 44 45 5F 50 4F 49 4E 54
!8050 45 52 3A 20 20 20 20 30 78 00 DD 21 32 40 CD 34
!8060 82 CD 0C 86 20 20 7C 20 20 50 54 52 2E 4D 45 4D
!8070 5F 49 44 45 5F 50 41 52 54 49 54 49 4F 4E 3A 20
!8080 20 20 30 78 00 DD 21 2E 40 CD 34 82 CD 0C 86 0A
!8090 0D 50 54 52 2E 4D 45 4D 5F 46 41 54 5F 54 4D 50
!80A0 50 4F 49 4E 54 45 52 3A 20 30 78 00 DD 21 1D 43
!80B0 CD 34 82 CD 0C 86 20 20 7C 20 20 50 54 52 2E 4D
!80C0 45 4D 5F 46 41 54 5F 54 4D 50 50 4F 49 4E 54 45
!80D0 52 31 3A 20 30 78 00 DD 21 21 43 CD 34 82 CD 0C
!80E0 86 0A 0D 56 41 4C 2E 4D 45 4D 5F 46 41 54 5F 52
!80F0 45 53 45 52 56 45 44 3A 20 20 20 30 78 00 DD 21
!8100 17 43 CD 4D 82 CD 0C 86 20 20 20 20 20 20 7C 20
!8110 20 56 41 4C 2E 4D 45 4D 5F 46 41 54 5F 41 4D 4F
!8120 55 4E 54 3A 20 20 20 20 20 20 30 78 00 3A 19 43
!8130 CD 07 01 CD 0C 86 0A 0D 56 41 4C 2E 4D 45 4D 5F
!8140 46 41 54 5F 53 45 43 54 4F 52 53 3A 20 20 20 20
!8150 30 78 00 DD 21 1A 43 CD 4D 82 CD 0C 86 20 20 20
!8160 20 20 20 7C 20 20 56 41 4C 2E 4D 45 4D 5F 46 41
!8170 54 5F 43 4F 55 4E 54 31 3A 20 20 20 20 20 20 30
!8180 78 00 3A 1C 43 CD 07 01 CD 0C 86 0A 0D 56 41 4C
!8190 2E 4D 45 4D 5F 46 41 54 5F 4F 46 30 5F 43 43 4C
!81A0 55 53 54 3A 20 30 78 00 DD 21 35 43 CD 4D 82 CD
!81B0 0C 86 20 20 20 20 20 20 7C 20 20 50 54 52 2E 4D
!81C0 45 4D 5F 46 41 54 5F 4F 46 30 5F 46 41 54 53 45
!81D0 43 3A 20 20 30 78 00 DD 21 37 43 CD 34 82 CD 0C
!81E0 86 0A 0D 56 41 4C 2E 4D 45 4D 5F 46 41 54 5F 4F
!81F0 46 30 5F 44 41 54 53 45 43 3A 20 30 78 00 DD 21
!8200 3B 43 CD 34 82 CD 0C 86 20 20 7C 20 20 50 54 52
!8210 2E 4D 45 4D 5F 46 41 54 5F 4F 46 30 5F 44 41 54
!8220 52 45 4D 3A 20 20 30 78 00 DD 21 3F 43 CD 4D 82
!8230 CD F1 00 C9 DD 7E 03 CD 07 01 DD 7E 02 CD 07 01
!8240 DD 7E 01 CD 07 01 DD 7E 00 CD 07 01 C9 DD 7E 01
!8250 CD 07 01 DD 7E 00 CD 07 01 C9 32 76 40 F5 CD 97
!8260 14 DD 7E 00 B7 C2 88 82 CD 0B 83 2A 32 40 ED 5B
!8270 2E 40 CD 54 85 21 A4 82 CD DF 00 F1 C6 45 CD D7
!8280 00 21 BB 82 CD DF 00 C9 21 A4 82 CD DF 00 F1 C6
!8290 45 CD D7 00 21 AD 82 CD DF 00 11 20 00 01 70 00
!82A0 CD 17 0D C9 0A 0D 44 72 69 76 65 20 00 3A 20 6E
!82B0 6F 74 20 72 65 61 64 79 0A 0D 00 3A 20 73 65 6C
!82C0 65 63 74 65 64 0A 0D 00 0A 0D 49 6E 76 61 6C 69
!82D0 64 20 64 72 69 76 65 20 6C 65 74 74 65 72 0A 0D
!82E0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!82F0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!8300 00 00 00 00 00 00 00 00 00 00 00 CD 45 85 21 32
!8310 40 3E 01 CD BE 14 3A 17 41 FE EB C2 5D 83 DD 21
!8320 17 41 DD 7E 0E 32 17 43 DD 7E 0F 32 18 43 DD 7E
!8330 10 32 19 43 DD 7E 16 32 1A 43 DD 7E 17 32 1B 43
!8340 3A 1B 43 57 3A 1A 43 5F AF 67 6F 3A 19 43 47 19
!8350 10 FD 16 00 3A 17 43 5F 19 CD 00 85 C9 CD 0C 86
!8360 0A 0D 43 61 6E 6E 6F 74 20 66 69 6E 64 20 62 6F
!8370 6F 74 20 73 65 63 74 6F 72 2E 0A 0D 00 CD 97 14
!8380 DD 36 00 02 C9 ED 5B 1A 43 ED 53 1C 43 21 32 40
!8390 06 01 CD BE 14 CD 0C 86 0A 0D 20 20 46 69 6C 65
!83A0 6E 61 6D 65 20 20 20 20 20 43 6C 75 73 74 65 72
!83B0 20 53 69 7A 65 0A 0D 00 21 17 41 0E 10 7E E5 DD
!83C0 E1 E5 FE 41 CA 63 84 FE E5 CA 63 84 FE 00 CA 94
!83D0 84 DD 7E 0B FE 10 CA 31 84 3E 20 CD D7 00 3E 20
!83E0 CD D7 00 06 08 CD 63 17 3E 2E CD D7 00 06 03 CD
!83F0 63 17 CD 0C 86 20 30 78 00 DD 7E 1B CD 07 01 DD
!8400 7E 1A CD 07 01 CD 0C 86 20 20 30 78 00 DD 7E 1F
!8410 CD 07 01 DD 7E 1E CD 07 01 DD 7E 1D CD 07 01 DD
!8420 7E 1C CD 07 01 3E 0A CD D7 00 3E 0D CD D7 00 18
!8430 32 3E 44 CD D7 00 3E 20 CD D7 00 06 08 CD 63 17
!8440 CD 0C 86 20 20 20 20 20 30 78 00 DD 7E 1B CD 07
!8450 01 DD 7E 1A CD 07 01 3E 0A CD D7 00 3E 0D CD D7
!8460 00 18 00 0D 28 08 E1 11 20 00 19 C3 BD 83 E1 26
!8470 00 2E 01 CD 00 85 ED 5B 1C 43 1B ED 53 1C 43 7A
!8480 B3 CA 95 84 21 32 40 06 01 CD BE 14 21 17 41 0E
!8490 10 C3 BD 83 E1 C9 D5 21 25 43 CD 73 85 3E 10 32
!84A0 1C 43 21 32 40 06 01 CD BE 14 21 17 41 0E 10 D1
!84B0 D5 CD 5D 85 38 33 0D 28 07 11 20 00 19 C3 AF 84
!84C0 26 00 2E 01 CD 00 85 3A 1C 43 3D 32 1C 43 CA E1
!84D0 84 21 32 40 06 01 CD BE 14 21 17 41 0E 10 C3 AF
!84E0 84 D1 21 98 85 CD DF 00 C9 D1 06 08 CD 63 17 3E
!84F0 2E CD D7 00 06 03 CD 63 17 21 AA 85 CD DF 00 C9
!8500 22 1D 43 AF 32 1F 43 32 20 43 11 1D 43 01 32 40
!8510 CD 14 85 C9 E5 C5 D5 1A 6F 13 1A 67 13 0A 5F 03
!8520 0A 57 19 D1 C1 7D 02 03 7C 02 03 13 13 C5 D5 1A
!8530 6F 13 1A 67 13 0A 5F 03 0A 57 ED 5A D1 C1 7D 02
!8540 03 7C 02 E1 C9 CD 97 14 DD 23 DD 23 DD E5 E1 11
!8550 32 40 18 00 C5 06 00 0E 04 ED B0 C1 C9 E5 C5 06
!8560 0B 1A 4F 7E A9 20 07 05 20 F7 C1 E1 37 C9 C1 E1
!8570 37 3F C9 06 0B E5 AF 77 23 10 FC E1 06 0D 1A B7
!8580 C8 05 C8 FE 2E 20 0A 13 78 FE 05 38 F1 23 05 18
!8590 F7 1A 77 23 13 C3 7E 85 46 69 6C 65 20 6E 6F 74
!85A0 20 66 6F 75 6E 64 21 0D 0A 00 20 46 69 6C 65 20
!85B0 6C 6F 63 61 74 65 64 21 0D 0A 00 2A 35 43 7C 6F
!85C0 AF 67 ED 4B 17 43 09 22 37 43 AF 32 39 43 32 3A
!85D0 43 CD 97 14 DD 23 DD 23 DD E5 D1 01 37 43 CD 14
!85E0 85 CD 3A 80 21 37 43 06 01 CD BE 14 21 17 41 06
!85F0 14 CD C9 16 3A 35 43 17 6F 3E 00 17 67 11 17 41
!8600 19 11 35 43 ED A0 ED A0 CD 3A 80 C9 E3 F5 C5 7E
!8610 FE 00 28 06 CD D7 00 23 18 F5 23 C1 F1 E3 C9
!6000 11 81 40 D5 CD D3 21 B7 C2 9A 60 11 B6 41 CD A8
!6010 21 3A B6 41 FE C3 C2 B2 60 CD 91 01 0A 0D 4C 6F
!6020 61 64 69 6E 67 20 00 21 81 40 CD E6 00 CD 91 01
!6030 20 74 6F 20 30 78 00 ED 4B C0 41 78 CD 0E 01 79
!6040 CD 0E 01 CD 91 01 20 2E 2E 2E 20 00 ED 43 15 40
!6050 ED 43 19 40 2A C4 41 6C CB 3D 26 00 23 22 17 40
!6060 D1 CD D3 21 ED 5B 15 40 CD A8 21 2A 15 40 11 00
!6070 02 19 22 15 40 2A 17 40 2B 22 17 40 7C B5 28 02
!6080 18 E2 CD 91 01 4C 6F 61 64 20 63 6F 6D 70 6C 65
!6090 74 65 21 0A 0D 00 2A 19 40 E9 CD 91 01 0A 0D 46
!60A0 69 6C 65 20 6E 6F 74 20 66 6F 75 6E 64 21 0A 0D
!60B0 00 C9 CD 91 01 0A 0D 46 69 6C 65 20 69 73 20 6E
!60C0 6F 74 20 61 6E 20 65 78 65 63 75 74 61 62 6C 65
!60D0 21 0A 0D 00 C9 CD A8 21 F5 21 B6 41 06 20 CD E1
!60E0 17 F1 B7 CA D5 60 C9

View File

@@ -0,0 +1 @@
../../monitor_v2/zout/symbols.s

View File

@@ -0,0 +1,5 @@
export OPT_GEN_SYMBOLTABLE=0
export OPT_GEN_MONFILE=1
export OPT_GEN_OBJFILE=1
export OPT_WRITEROM=0
export FILENAME=test

View File

@@ -0,0 +1,37 @@
.include "extern_symbols.s" ;include monitor symbols.
START_ADDR .EQU 0x8000
org START_ADDR
com_header:
jp com_prg
db 0x00
dw 0x00, 0x00, 0x00 ;always 0
dw [START_ADDR] ;start addr
dw [_eof] ;end of file
dw [_eof - START_ADDR] ;length
dc 48,0x00
com_prg:
ld hl,[_str]
_l1:
ld a, (hl)
or a
ret z
out (CS_SIO_A_D),a
_wait:
ld a,1
out (CS_SIO_A_C),A
in A,(CS_SIO_A_C) ;read RRx
bit 0,A
jr z,_wait
inc hl
jr _l1
_str:
db 10,13,"Hello World",10,13,0
_eof:

Binary file not shown.

Binary file not shown.

View File

@@ -0,0 +1,8 @@
:10800000C340800000000000000000806580650023
:108010000000000000000000000000000000000060
:108020000000000000000000000000000000000050
:108030000000000000000000000000000000000040
:108040002155807EB7C8D3083E01D309DB09CB4751
:1080500028F62318EE0A0D48656C6C6F20576F7276
:058060006C640A0D0034
:00000001FF

File diff suppressed because it is too large Load Diff

View File

@@ -0,0 +1,7 @@
!8000 C3 40 80 00 00 00 00 00 00 00 00 80 65 80 65 00
!8010 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!8020 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!8030 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00
!8040 21 55 80 7E B7 C8 D3 08 3E 01 D3 09 DB 09 CB 47
!8050 28 F6 23 18 EE 0A 0D 48 65 6C 6C 6F 20 57 6F 72
!8060 6C 64 0A 0D 00