fat16 working
This commit is contained in:
@@ -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
|
||||
@@ -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
|
||||
|
||||
@@ -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
|
||||
622
OperatingSystem/monitor_v2/include/fat16.s
Normal file
622
OperatingSystem/monitor_v2/include/fat16.s
Normal 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
|
||||
366
OperatingSystem/monitor_v2/include/fat16_cmd.s
Normal file
366
OperatingSystem/monitor_v2/include/fat16_cmd.s
Normal 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
|
||||
77
OperatingSystem/monitor_v2/include/fat16_dbg.s
Normal file
77
OperatingSystem/monitor_v2/include/fat16_dbg.s
Normal 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
|
||||
|
||||
@@ -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:
|
||||
|
||||
@@ -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
|
||||
|
||||
@@ -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
|
||||
|
||||
Binary file not shown.
File diff suppressed because it is too large
Load Diff
File diff suppressed because it is too large
Load Diff
@@ -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
|
||||
|
||||
Reference in New Issue
Block a user