Ported CP/M 2.2 to pc (32k version)

This commit is contained in:
Dreaded_X 2020-09-11 19:14:44 +02:00
parent 85fd914e40
commit 0066dcaa1e
19 changed files with 5982 additions and 44 deletions

251
bin/DISKDEF.LIB Normal file
View File

@ -0,0 +1,251 @@
; CP/M 2.0 disk re-definition library
;
; Copyright (c) 1979
; Digital Research
; Box 579
; Pacific Grove, CA
; 93950
;
; CP/M logical disk drives are defined using the
; macros given below, where the sequence of calls
; is:
;
; disks n
; diskdef parameter-list-0
; diskdef parameter-list-1
; ...
; diskdef parameter-list-n
; endef
;
; where n is the number of logical disk drives attached
; to the CP/M system, and parameter-list-i defines the
; characteristics of the ith drive (i=0,1,...,n-1)
;
; each parameter-list-i takes the form
; dn,fsc,lsc,[skf],bls,dks,dir,cks,ofs,[0]
; where
; dn is the disk number 0,1,...,n-1
; fsc is the first sector number (usually 0 or 1)
; lsc is the last sector number on a track
; skf is optional "skew factor" for sector translate
; bls is the data block size (1024,2048,...,16384)
; dks is the disk size in bls increments (word)
; dir is the number of directory elements (word)
; cks is the number of dir elements to checksum
; ofs is the number of tracks to skip (word)
; [0] is an optional 0 which forces 16K/directory entry
;
; for convenience, the form
; dn,dm
; defines disk dn as having the same characteristics as
; a previously defined disk dm.
;
; a standard four drive CP/M system is defined by
; disks 4
; diskdef 0,1,26,6,1024,243,64,64,2
; dsk set 0
; rept 3
; dsk set dsk+1
; diskdef %dsk,0
; endm
; endef
;
; the value of "begdat" at the end of assembly defines the
; beginning of the uninitialize ram area above the bios,
; while the value of "enddat" defines the next location
; following the end of the data area. the size of this
; area is given by the value of "datsiz" at the end of the
; assembly. note that the allocation vector will be quite
; large if a large disk size is defined with a small block
; size.
;
dskhdr macro dn
;; define a single disk header list
dpe&dn: dw xlt&dn,0000h ;translate table
dw 0000h,0000h ;scratch area
dw dirbuf,dpb&dn ;dir buff,parm block
dw csv&dn,alv&dn ;check, alloc vectors
endm
;
disks macro nd
;; define nd disks
ndisks set nd ;;for later reference
dpbase equ $ ;base of disk parameter blocks
;; generate the nd elements
dsknxt set 0
rept nd
dskhdr %dsknxt
dsknxt set dsknxt+1
endm
endm
;
dpbhdr macro dn
dpb&dn equ $ ;disk parm block
endm
;
ddb macro data,comment
;; define a db statement
db data comment
endm
;
ddw macro data,comment
;; define a dw statement
dw data comment
endm
;
gcd macro m,n
;; greatest common divisor of m,n
;; produces value gcdn as result
;; (used in sector translate table generation)
gcdm set m ;;variable for m
gcdn set n ;;variable for n
gcdr set 0 ;;variable for r
rept 65535
gcdx set gcdm/gcdn
gcdr set gcdm - gcdx*gcdn
if gcdr = 0
exitm
endif
gcdm set gcdn
gcdn set gcdr
endm
endm
;
diskdef macro dn,fsc,lsc,skf,bls,dks,dir,cks,ofs,k16
;; generate the set statements for later tables
if nul lsc
;; current disk dn same as previous fsc
dpb&dn equ dpb&fsc ;equivalent parameters
als&dn equ als&fsc ;same allocation vector size
css&dn equ css&fsc ;same checksum vector size
xlt&dn equ xlt&fsc ;same translate table
else
secmax set lsc-(fsc) ;;sectors 0...secmax
sectors set secmax+1;;number of sectors
als&dn set (dks)/8 ;;size of allocation vector
if ((dks) mod 8) ne 0
als&dn set als&dn+1
endif
css&dn set (cks)/4 ;;number of checksum elements
;; generate the block shift value
blkval set bls/128 ;;number of sectors/block
blkshf set 0 ;;counts right 0's in blkval
blkmsk set 0 ;;fills with 1's from right
rept 16 ;;once for each bit position
if blkval=1
exitm
endif
;; otherwise, high order 1 not found yet
blkshf set blkshf+1
blkmsk set (blkmsk shl 1) or 1
blkval set blkval/2
endm
;; generate the extent mask byte
blkval set bls/1024 ;;number of kilobytes/block
extmsk set 0 ;;fill from right with 1's
rept 16
if blkval=1
exitm
endif
;; otherwise more to shift
extmsk set (extmsk shl 1) or 1
blkval set blkval/2
endm
;; may be double byte allocation
if (dks) > 256
extmsk set (extmsk shr 1)
endif
;; may be optional [0] in last position
if not nul k16
extmsk set k16
endif
;; now generate directory reservation bit vector
dirrem set dir ;;# remaining to process
dirbks set bls/32 ;;number of entries per block
dirblk set 0 ;;fill with 1's on each loop
rept 16
if dirrem=0
exitm
endif
;; not complete, iterate once again
;; shift right and add 1 high order bit
dirblk set (dirblk shr 1) or 8000h
if dirrem > dirbks
dirrem set dirrem-dirbks
else
dirrem set 0
endif
endm
dpbhdr dn ;;generate equ $
ddw %sectors,<;sec per track>
ddb %blkshf,<;block shift>
ddb %blkmsk,<;block mask>
ddb %extmsk,<;extnt mask>
ddw %(dks)-1,<;disk size-1>
ddw %(dir)-1,<;directory max>
ddb %dirblk shr 8,<;alloc0>
ddb %dirblk and 0ffh,<;alloc1>
ddw %(cks)/4,<;check size>
ddw %ofs,<;offset>
;; generate the translate table, if requested
if nul skf
xlt&dn equ 0 ;no xlate table
else
if skf = 0
xlt&dn equ 0 ;no xlate table
else
;; generate the translate table
nxtsec set 0 ;;next sector to fill
nxtbas set 0 ;;moves by one on overflow
gcd %sectors,skf
;; gcdn = gcd(sectors,skew)
neltst set sectors/gcdn
;; neltst is number of elements to generate
;; before we overlap previous elements
nelts set neltst ;;counter
xlt&dn equ $ ;translate table
rept sectors ;;once for each sector
if sectors < 256
ddb %nxtsec+(fsc)
else
ddw %nxtsec+(fsc)
endif
nxtsec set nxtsec+(skf)
if nxtsec >= sectors
nxtsec set nxtsec-sectors
endif
nelts set nelts-1
if nelts = 0
nxtbas set nxtbas+1
nxtsec set nxtbas
nelts set neltst
endif
endm
endif ;;end of nul fac test
endif ;;end of nul bls test
endm
;
defds macro lab,space
lab: ds space
endm
;
lds macro lb,dn,val
defds lb&dn,%val&dn
endm
;
endef macro
;; generate the necessary ram data areas
begdat equ $
dirbuf: ds 128 ;directory access buffer
dsknxt set 0
rept ndisks ;;once for each disk
lds alv,%dsknxt,als
lds csv,%dsknxt,css
dsknxt set dsknxt+1
endm
enddat equ $
datsiz equ $-begdat
;; db 0 at this point forces hex record
endm
;


BIN
bin/ED.COM Normal file

Binary file not shown.

BIN
bin/LOAD.COM Normal file

Binary file not shown.

BIN
bin/MAC.COM Normal file

Binary file not shown.

BIN
bin/MBASIC.COM Normal file

Binary file not shown.

BIN
bin/STAT.COM Normal file

Binary file not shown.

10
bin/disks.asm Normal file
View File

@ -0,0 +1,10 @@
MACLIB DISKDEF
DISKS 4
DISKDEF 0, 0, 127, 0, 1024, 64, 64, 1
DISKDEF 1,0
DISKDEF 2,0
DISKDEF 3,0
ENDDEF


96
build.py Executable file
View File

@ -0,0 +1,96 @@
#!/usr/bin/env python3
import math
pageSize = 128
sectorsPerTrack = 256
blockSize = 16384
maxDirs = 128
dirBlocks = 1
out = open('.build/disk.img', 'wb')
def addBootloader(name):
loader = open(name, 'rb')
b = loader.read()
if len(b) > pageSize:
raise RuntimeError("Bootloader binary cannot be larger than one page")
out.seek(0)
out.write(b)
def addOS(cpmName, biosName):
cpm = open(cpmName, 'rb')
bios = open(biosName, 'rb')
b = cpm.read()
out.seek(pageSize)
out.write(b)
b = bios.read()
out.seek(pageSize + 0x1600)
out.write(b)
def seekBlock(i):
# Blocks start at track 1, sector 0
out.seek(pageSize*sectorsPerTrack + i*blockSize)
def initDirs():
seekBlock(0)
out.write(bytearray(([0xe5] + [0x00] * 31) * maxDirs))
fileCounter = 0
def addFile(filename, n, t):
global fileCounter
if fileCounter > maxDirs:
raise RuntimeError("Max dir entries has been reached")
fileCounter += 1
if len(n) > 8:
raise RuntimeError("Filename cannot be longer than 8")
if len(t) > 3:
raise RuntimeError("Filetype cannot be longer than 3")
f = open(filename, 'rb')
b = f.read()
seekBlock(0)
out.seek(32*fileCounter, 1)
# Write user (assume 0 for now)
out.write(bytearray(1))
# Write the name
out.write(n.upper().encode("ascii"))
out.write((" " * (8-len(n))).encode("ascii"))
# Write the type
out.write(t.upper().encode("ascii"))
out.write((" " * (3-len(t))).encode("ascii"))
# Write extend (assume no extend for now)
out.write(bytearray(2))
# Reserved byte
out.write(bytearray(1))
# Number of records (Again assuming no extends <128)
out.write(math.ceil(len(b)/128).to_bytes(1, byteorder='little'))
# We are assuming one block per file for now, so we can use fileCounter
out.write(fileCounter.to_bytes(2, byteorder='little'))
seekBlock(fileCounter)
out.write(b)
addBootloader('.build/loader.bin')
addOS('.build/cpm22.bin', '.build/bios.bin')
initDirs()
addFile(".build/MONITOR.COM", "MONITOR", "COM")
addFile("bin/STAT.COM", "STAT", "COM")

View File

@ -1,2 +1,8 @@
#!/bin/bash
mkdir -p .build && zasm -i src/rom_monitor.z80 -o .build/rom_monitor.bin
mkdir -p .build && zasm -w -i src/rom_monitor.z80 -o .build/rom_monitor.bin
mkdir -p .build && zasm -i src/ram_monitor.z80 -o .build/ram_monitor.bin
mkdir -p .build && zasm -i src/cpm22.z80 -o .build/cpm22.bin
mkdir -p .build && zasm -i src/bios.z80 -o .build/bios.bin
mkdir -p .build && zasm -i src/putsys.z80 -o .build/putsys.bin
mkdir -p .build && zasm -i src/loader.z80 -o .build/loader.bin
mkdir -p .build && zasm -i src/MONITOR.z80 -o .build/MONITOR.COM

BIN
cpm22-b.zip Normal file

Binary file not shown.

696
src/MONITOR.z80 Normal file
View File

@ -0,0 +1,696 @@
#target bin
;RAM monitor for a system with serial interface and IDE disk and memory expansion board.
;This program to be loaded by CP/M at 0100h, then it copies itself to memory at DC00h.
;Assumes serial port has been initialized by ROM monitor.
;Assumes the UART data port address is 02h and control/status address is 03h
;Assumes memory configuration is all-RAM
;
;The subroutines use these variables in RAM, same area as ROM monitor:
current_location: equ 0x7100 ;word variable in RAM
line_count: equ 0x7102 ;byte variable in RAM
byte_count: equ 0x7103 ;byte variable in RAM
value_pointer: equ 0x7104 ;word variable in RAM
current_value: equ 0x7106 ;word variable in RAM
buffer: equ 0x7108 ;buffer in RAM -- up to stack area
;Will use stack of calling program (CP/M) which is re-initialized at re-boot.
;
;
;
;Code to start program and move to higher memory
;
#code BOOT, 0x0100
ld hl,code_origin ;start of code to transfer
ld bc,code_end-code_start+1 ;length of code to transfer
ld de,07200h ;target of transfer
ldir ;Z80 transfer instruction
jp 07200h
code_origin: ;address of first byte of code before transfer
;
#code MAIN, 0x7200
code_start: jp monitor_start
;
;Puts a single char (byte value) on serial output
;Call with char to send in A register. Uses B register
write_char: ld b,a ;store char
write_char_loop: in a,(3) ;check if OK to send
and 001h ;check TxRDY bit
jp z,write_char_loop ;loop if not set
ld a,b ;get char back
out (2),a ;send to output
ret ;returns with char in a
;
;Subroutine to write a zero-terminated string to serial output
;Pass address of string in HL register
;No error checking
write_string: in a,(3) ;read status
and 001h ;check TxRDY bit
jp z,write_string ;loop if not set
ld a,(hl) ;get char from string
and a ;check if 0
ret z ;yes, finished
out (2),a ;no, write char to output
inc hl ;next char in string
jp write_string ;start over
;
;Binary loader. Receive a binary file, place in memory.
;Address of load passed in HL, length of load (= file length) in BC
bload: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,bload ;not ready, loop
in a,(2)
ld (hl),a
inc hl
dec bc ;byte counter
ld a,b ;need to test BC this way because
or c ;dec rp instruction does not change flags
jp nz,bload
ret
;
;Binary dump to port. Send a stream of binary data from memory to serial output
;Address of dump passed in HL, length of dump in BC
bdump: in a,(3) ;get status
and 001h ;check TxRDY bit
jp z,bdump ;not ready, loop
ld a,(hl)
out (2),a
inc hl
dec bc
ld a,b ;need to test this way because
or c ;dec rp instruction does not change flags
jp nz,bdump
ret
;
;Subroutine to get a string from serial input, place in buffer.
;Buffer address passed in HL reg.
;Uses A,BC,DE,HL registers (including calls to other subroutines).
;Line entry ends by hitting return key. Return char not included in string (replaced by zero).
;Backspace editing OK. No error checking.
;
get_line: ld c,000h ;line position
ld a,h ;put original buffer address in de
ld d,a ;after this don't need to preserve hl
ld a,l ;subroutines called don't use de
ld e,a
get_line_next_char: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,get_line_next_char ;not ready, loop
in a,(2) ;get char
cp 00dh ;check if return
ret z ;yes, normal exit
cp 07fh ;check if backspace (VT102 keys)
jp z,get_line_backspace ;yes, jump to backspace routine
cp 008h ;check if backspace (ANSI keys)
jp z,get_line_backspace ;yes, jump to backspace
call write_char ;put char on screen
ld (de),a ;store char in buffer
inc de ;point to next space in buffer
inc c ;inc counter
ld a,000h
ld (de),a ;leaves a zero-terminated string in buffer
jp get_line_next_char
get_line_backspace: ld a,c ;check current position in line
cp 000h ;at beginning of line?
jp z,get_line_next_char ;yes, ignore backspace, get next char
dec de ;no, erase char from buffer
dec c ;back up one
ld a,000h ;put a zero in buffer where the last char was
ld (de),a
ld hl,erase_char_string ;ANSI sequence to delete one char from line
call write_string ;transmits sequence to backspace and erase char
jp get_line_next_char
;
;Creates a two-char hex string from the byte value passed in register A
;Location to place string passed in HL
;String is zero-terminated, stored in 3 locations starting at HL
;Also uses registers b,d, and e
byte_to_hex_string: ld b,a ;store original byte
srl a ;shift right 4 times, putting
srl a ;high nybble in low-nybble spot
srl a ;and zeros in high-nybble spot
srl a
ld d,000h ;prepare for 16-bit addition
ld e,a ;de contains offset
push hl ;temporarily store string target address
ld hl,hex_char_table ;use char table to get high-nybble character
add hl,de ;add offset to start of table
ld a,(hl) ;get char
pop hl ;get string target address
ld (hl),a ;store first char of string
inc hl ;point to next string target address
ld a,b ;get original byte back from reg b
and 00fh ;mask off high-nybble
ld e,a ;d still has 000h, now de has offset
push hl ;temp store string target address
ld hl,hex_char_table ;start of table
add hl,de ;add offset
ld a,(hl) ;get char
pop hl ;get string target address
ld (hl),a ;store second char of string
inc hl ;point to third location
ld a,000h ;zero to terminate string
ld (hl),a ;store the zero
ret ;done
;
;Converts a single ASCII hex char to a nybble value
;Pass char in reg A. Letter numerals must be upper case.
;Return nybble value in low-order reg A with zeros in high-order nybble if no error.
;Return 0ffh in reg A if error (char not a valid hex numeral).
;Also uses b, c, and hl registers.
hex_char_to_nybble: ld hl,hex_char_table
ld b,00fh ;no. of valid characters in table - 1.
ld c,000h ;will be nybble value
hex_to_nybble_loop: cp (hl) ;character match here?
jp z,hex_to_nybble_ok ;match found, exit
dec b ;no match, check if at end of table
jp m,hex_to_nybble_err ;table limit exceded, exit with error
inc c ;still inside table, continue search
inc hl
jp hex_to_nybble_loop
hex_to_nybble_ok: ld a,c ;put nybble value in a
ret
hex_to_nybble_err: ld a,0ffh ;error value
ret
;
;Converts a hex character pair to a byte value
;Called with location of high-order char in HL
;If no error carry flag clear, returns with byte value in register A, and
;HL pointing to next mem location after char pair.
;If error (non-hex char) carry flag set, HL pointing to invalid char
hex_to_byte: ld a,(hl) ;location of character pair
push hl ;store hl (hex_char_to_nybble uses it)
call hex_char_to_nybble
pop hl ;returns with nybble value in a reg, or 0ffh if error
cp 0ffh ;non-hex character?
jp z,hex_to_byte_err ;yes, exit with error
sla a ;no, move low order nybble to high side
sla a
sla a
sla a
ld d,a ;store high-nybble
inc hl ;get next character of the pair
ld a,(hl)
push hl ;store hl
call hex_char_to_nybble
pop hl
cp 0ffh ;non-hex character?
jp z,hex_to_byte_err ;yes, exit with error
or d ;no, combine with high-nybble
inc hl ;point to next memory location after char pair
scf
ccf ;no-error exit (carry = 0)
ret
hex_to_byte_err: scf ;error, carry flag set
ret
hex_char_table: defm "0123456789ABCDEF" ;ASCII hex table
;
;Subroutine to get a two-byte address from serial input.
;Returns with address value in HL
;Uses locations in RAM for buffer and variables
address_entry: ld hl,buffer ;location for entered string
call get_line ;returns with address string in buffer
ld hl,buffer ;location of stored address entry string
call hex_to_byte ;will get high-order byte first
jp c, address_entry_error ;if error, jump
ld (current_location+1),a ;store high-order byte, little-endian
ld hl,buffer+2 ;point to low-order hex char pair
call hex_to_byte ;get low-order byte
jp c, address_entry_error ;jump if error
ld (current_location),a ;store low-order byte in lower memory
ld hl,(current_location) ;put memory address in hl
ret
address_entry_error: ld hl,address_error_msg
call write_string
jp address_entry
;
;Subroutine to get a decimal string, return a word value
;Calls decimal_string_to_word subroutine
decimal_entry: ld hl,buffer
call get_line ;returns with DE pointing to terminating zero
ld hl,buffer
call decimal_string_to_word
ret nc ;no error, return with word in hl
ld hl,decimal_error_msg ;error, try again
call write_string
jp decimal_entry
;
;Subroutine to convert a decimal string to a word value
;Call with address of string in HL, pointer to end of string in DE
;Carry flag set if error (non-decimal char)
;Carry flag clear, word value in HL if no error.
decimal_string_to_word: ld b,d
ld c,e ;use BC as string pointer
ld (current_location),hl ;store addr. of start of buffer in RAM word variable
ld hl,000h ;starting value zero
ld (current_value),hl
ld hl,decimal_place_value ;pointer to values
ld (value_pointer),hl
decimal_next_char: dec bc ;next char in string (moving right to left)
ld hl,(current_location) ;check if at end of decimal string
scf ;get ready to subtract de from buffer addr.
ccf ;set carry to zero (clear)
sbc hl,bc ;keep going if bc > or = hl (buffer address)
jp c,decimal_continue ;borrow means bc > hl
jp z,decimal_continue ;z means bc = hl
ld hl,(current_value) ;return if de < buffer address (no borrow)
scf ;get value back from RAM variable
ccf
ret ;return with carry clear, value in hl
decimal_continue: ld a,(bc) ;next char in string (right to left)
sub 030h ;ASCII value of zero char
jp m,decimal_error ;error if char value less than 030h
cp 00ah ;error if byte value > or = 10 decimal
jp p,decimal_error ;a reg now has value of decimal numeral
ld hl,(value_pointer) ;get value to add an put in de
ld e,(hl) ;little-endian (low byte in low memory)
inc hl
ld d,(hl)
inc hl ;hl now points to next value
ld (value_pointer),hl
ld hl,(current_value) ;get back current value
decimal_add: dec a ;add loop to increase total value
jp m,decimal_add_done ;end of multiplication
add hl,de
jp decimal_add
decimal_add_done: ld (current_value),hl
jp decimal_next_char
decimal_error: scf
ret
jp decimal_add
decimal_place_value: defw 1,10,100,1000,10000
;
;Memory dump
;Displays a 256-byte block of memory in 16-byte rows.
;Called with address of start of block in HL
memory_dump: ld (current_location),hl ;store address of block to be displayed
ld a,000h
ld (byte_count),a ;initialize byte count
ld (line_count),a ;initialize line count
jp dump_new_line
dump_next_byte: ld hl,(current_location) ;get byte address from storage,
ld a,(hl) ;get byte to be converted to string
inc hl ;increment address and
ld (current_location),hl ;store back
ld hl,buffer ;location to store string
call byte_to_hex_string ;convert
ld hl,buffer ;display string
call write_string
ld a,(byte_count) ;next byte
inc a
jp z,dump_done ;stop when 256 bytes displayed
ld (byte_count),a ;not finished yet, store
ld a,(line_count) ;end of line (16 characters)?
cp 00fh ;yes, start new line
jp z,dump_new_line
inc a ;no, increment line count
ld (line_count),a
ld a,020h ;print space
call write_char
jp dump_next_byte ;continue
dump_new_line: ld a,000h ;reset line count to zero
ld (line_count),a
call write_newline
ld hl,(current_location) ;location of start of line
ld a,h ;high byte of address
ld hl, buffer
call byte_to_hex_string ;convert
ld hl,buffer
call write_string ;write high byte
ld hl,(current_location)
ld a,l ;low byte of address
ld hl, buffer
call byte_to_hex_string ;convert
ld hl,buffer
call write_string ;write low byte
ld a,020h ;space
call write_char
jp dump_next_byte ;now write 16 bytes
dump_done: ld a,000h
ld hl,buffer
ld (hl),a ;clear buffer of last string
call write_newline
ret
;
;Memory load
;Loads RAM memory with bytes entered as hex characters
;Called with address to start loading in HL
;Displays entered data in 16-byte rows.
memory_load: ld (current_location),hl
ld hl,data_entry_msg
call write_string
jp load_new_line
load_next_char: call get_char
cp 00dh ;return?
jp z,load_done ;yes, quit
ld (buffer),a
call get_char
cp 00dh ;return?
jp z,load_done ;yes, quit
ld (buffer+1),a
ld hl,buffer
call hex_to_byte
jp c,load_data_entry_error ;non-hex character
ld hl,(current_location) ;get byte address from storage,
ld (hl),a ;store byte
inc hl ;increment address and
ld (current_location),hl ;store back
ld a,(buffer)
call write_char
ld a,(buffer+1)
call write_char
ld a,(line_count) ;end of line (16 characters)?
cp 00fh ;yes, start new line
jp z,load_new_line
inc a ;no, increment line count
ld (line_count),a
ld a,020h ;print space
call write_char
jp load_next_char ;continue
load_new_line: ld a,000h ;reset line count to zero
ld (line_count),a
call write_newline
jp load_next_char ;continue
load_data_entry_error: call write_newline
ld hl,data_error_msg
call write_string
ret
load_done: call write_newline
ret
;
;Get one ASCII character from the serial port.
;Returns with char in A reg. No error checking.
get_char: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,get_char ;not ready, loop
in a,(2) ;get char
ret
;
;Subroutine to start a new line
write_newline: ld a,00dh ;ASCII carriage return character
call write_char
ld a,00ah ;new line (line feed) character
call write_char
ret
;
;Subroutine to read one disk sector (128 bytes)
;Address to place data passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_read:
rd_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,rd_status_loop_1 ;loop until not busy
rd_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,rd_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,20h ;Read sector command
out (0fh),a
rd_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,rd_wait_for_DRQ_set ;loop until bit set
rd_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,rd_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
read_loop: in a,(08h) ;get data
ld (hl),a
inc hl
in a,(0fh) ;check status
and 08h ;DRQ bit
jp nz,read_loop ;loop until cleared
ret
;
;Subroutine to write one disk sector (128 bytes)
;Address of data to write to disk passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_write:
wr_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,wr_status_loop_1 ;loop until not busy
wr_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,wr_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,30h ;Write sector command
out (0fh),a
wr_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,wr_wait_for_DRQ_set ;loop until bit set
write_loop: ld a,(hl)
out (08h),a ;write data
inc hl
in a,(0fh) ;read status
and 08h ;check DRQ bit
jp nz,write_loop ;write until bit cleared
wr_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,wr_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
ret
;
;Strings used in subroutines
length_entry_string: defm "Enter length of file to load (decimal): ",0
dump_entry_string: defm "Enter no. of bytes to dump (decimal): ",0
LBA_entry_string: defm "Enter LBA (decimal, 0 to 65535): ",0
erase_char_string: defm 008h,01bh,"[K",000h ;ANSI sequence for backspace, erase to end of line.
address_entry_msg: defm "Enter 4-digit hex address (use upper-case A through F): ",0
address_error_msg: defm 13,10,"Error: invalid hex character, try again: ",0
data_entry_msg: defm "Enter hex bytes, hit return when finished.",13,10,0
data_error_msg: defm "Error: invalid hex byte.",13,10,0
decimal_error_msg: defm 13,10,"Error: invalid decimal number, try again: ",0
;
;Simple monitor program for CPUville Z80 computer with serial interface.
monitor_start: call write_newline ;routine program return here to avoid re-initialization of port
ld a,03eh ;cursor symbol
call write_char
ld hl,buffer
call get_line ;get monitor input string (command)
call write_newline
call parse ;interprets command, returns with address to jump to in HL
jp (hl)
;
;Parses an input line stored in buffer for available commands as described in parse table.
;Returns with address of jump to action for the command in HL
parse: ld bc,parse_table ;bc is pointer to parse_table
parse_start: ld a,(bc) ;get pointer to match string from parse table
ld e,a
inc bc
ld a,(bc)
ld d,a ;de will is pointer to strings for matching
ld a,(de) ;get first char from match string
or 000h ;zero?
jp z,parser_exit ;yes, exit no_match
ld hl,buffer ;no, parse input string
match_loop: cp (hl) ;compare buffer char with match string char
jp nz,no_match ;no match, go to next match string
or 000h ;end of strings (zero)?
jp z,parser_exit ;yes, matching string found
inc de ;match so far, point to next char in match string
ld a,(de) ;get next character from match string
inc hl ;and point to next char in input string
jp match_loop ;check for match
no_match: inc bc ;skip over jump target to
inc bc
inc bc ;get address of next matching string
jp parse_start
parser_exit: inc bc ;skip to address of jump for match
ld a,(bc)
ld l,a
inc bc
ld a,(bc)
ld h,a ;returns with jump address in hl
ret
;
;Actions to be taken on match
;
;Memory dump program
;Input 4-digit hexadecimal address
;Calls memory_dump subroutine
dump_jump: ld hl,dump_message ;Display greeting
call write_string
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry ;returns with address in HL
call write_newline
call memory_dump
jp monitor_start
;
;Hex loader, displays formatted input
load_jump: ld hl,load_message ;Display greeting
call write_string ;get address to load
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry
call write_newline
call memory_load
jp monitor_start
;
;Jump and run do the same thing: get an address and jump to it.
run_jump: ld hl,run_message ;Display greeting
call write_string
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry
jp (hl)
;
;Help and ? do the same thing, display the available commands
help_jump: ld hl,help_message
call write_string
ld bc,parse_table ;table with pointers to command strings
help_loop: ld a,(bc) ;displays the strings for matching commands,
ld l,a ;getting the string addresses from the
inc bc ;parse table
ld a,(bc) ;pass address of string to hl through a reg
ld h,a
ld a,(hl) ;hl now points to start of match string
or 000h ;exit if no_match string
jp z,help_done
push bc ;write_char uses b register
ld a,020h ;space char
call write_char
pop bc
call write_string ;writes match string
inc bc ;pass over jump address in table
inc bc
inc bc
jp help_loop
help_done: jp monitor_start
;
;Binary file load. Need both address to load and length of file
bload_jump: ld hl,bload_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,length_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld hl,bload_ready_message
call write_string
pop hl
call bload
jp monitor_start
;
;Binary memory dump. Need address of start of dump and no. bytes
bdump_jump: ld hl,bdump_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,dump_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld hl,bdump_ready_message
call write_string
call get_char
pop hl
call bdump
jp monitor_start
;Disk read. Need memory address to place data, LBA of sector to read
diskrd_jump: ld hl,diskrd_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,LBA_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld e,00h
pop hl
call disk_read
jp monitor_start
diskwr_jump: ld hl,diskwr_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,LBA_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld e,00h
pop hl
call disk_write
jp monitor_start
exit_jump: jp 0000h ; Exit CP/M
;Prints message for no match to entered command
no_match_jump: ld hl,no_match_message
call write_string
ld hl, buffer
call write_string
jp monitor_start
;
;Monitor data structures:
;
monitor_message: defm 13,10,"ROM ver. 8",13,10,0
no_match_message: defm "? ",0
help_message: defm "Commands implemented:",13,10,0
dump_message: defm "Displays a 256-byte block of memory.",13,10,0
load_message: defm "Enter hex bytes starting at memory location.",13,10,0
run_message: defm "Will jump to (execute) program at address entered.",13,10,0
bload_message: defm "Loads a binary file into memory.",13,10,0
bload_ready_message: defm 13,10,"Ready to receive, start transfer.",0
bdump_message: defm "Dumps binary data from memory to serial port.",13,10,0
bdump_ready_message: defm 13,10,"Ready to send, hit any key to start.",0
diskrd_message: defm "Reads one sector from disk to memory.",13,10,0
diskwr_message: defm "Writes one sector from memory to disk.",13,10,0
;Strings for matching:
dump_string: defm "dump",0
load_string: defm "load",0
jump_string: defm "jump",0
run_string: defm "run",0
question_string: defm "?",0
help_string: defm "help",0
bload_string: defm "bload",0
bdump_string: defm "bdump",0
diskrd_string: defm "diskrd",0
diskwr_string: defm "diskwr",0
exit_string: defm "exit",0
no_match_string: defm 0,0
;Table for matching strings to jumps
parse_table: defw dump_string,dump_jump,load_string,load_jump
defw jump_string,run_jump,run_string,run_jump
defw question_string,help_jump,help_string,help_jump
defw bload_string,bload_jump,bdump_string,bdump_jump
defw diskrd_string,diskrd_jump,diskwr_string,diskwr_jump
defw exit_string,exit_jump
defw no_match_string,no_match_jump
code_end:
end

344
src/bios.z80 Normal file
View File

@ -0,0 +1,344 @@
; skeletal cbios for first level of CP/M 2.0 alteration
;
ccp: equ 6400h ;base of ccp
bdos: equ 6C06h ;bdos entry
bios: equ 7A00h ;base of bios
cdisk: equ 0004h ;address of current disk number 0=a,... l5=p
iobyte: equ 0003h ;intel i/o byte
disks: equ 04h ;number of disks in the system
;
org bios ;origin of this program
nsects: equ ($-ccp)/128 ;warm start sector count
;
; jump vector for individual subroutines
;
JP boot ;cold start
wboote: JP wboot ;warm start
JP const ;console status
JP conin ;console character in
JP conout ;console character out
JP list ;list character out
JP punch ;punch character out
JP reader ;reader character out
JP home ;move head to home position
JP seldsk ;select disk
JP settrk ;set track number
JP setsec ;set sector number
JP setdma ;set dma address
JP read ;read disk
JP write ;write disk
JP listst ;return list status
JP sectran ;sector translate
;
; fixed data tables for four-drive standard
; ibm-compatible 8" disks
; no translations
;
; disk Parameter header for disk 00
dpbase: defw 0000h, 0000h
defw 0000h, 0000h
defw dirbf, dpbd0
defw chk00, all00
; disk parameter header for disk 01
defw 0000h, 0000h
defw 0000h, 0000h
defw dirbf, dpblk
defw chk01, all01
; disk parameter header for disk 02
defw 0000h, 0000h
defw 0000h, 0000h
defw dirbf, dpblk
defw chk02, all02
; disk parameter header for disk 03
defw 0000h, 0000h
defw 0000h, 0000h
defw dirbf, dpblk
defw chk03, all03
;
; sector translate vector
trans: defm 1, 7, 13, 19 ;sectors 1, 2, 3, 4
defm 25, 5, 11, 17 ;sectors 5, 6, 7, 6
defm 23, 3, 9, 15 ;sectors 9, 10, 11, 12
defm 21, 2, 8, 14 ;sectors 13, 14, 15, 16
defm 20, 26, 6, 12 ;sectors 17, 18, 19, 20
defm 18, 24, 4, 10 ;sectors 21, 22, 23, 24
defm 16, 22 ;sectors 25, 26
;
dpbd0: ;disk parameter block for all disks.
defw 256 ;sectors per track
defm 7 ;block shift factor
defm 127 ;block mask
defm 7 ;null mask
defw 511 ;disk size-1
defw 127 ;directory max
defm 128 ;alloc 0
defm 0 ;alloc 1
defw 0 ;check size
defw 1 ;track offset
dpblk: ;disk parameter block for all disks.
defw 256 ;sectors per track
defm 7 ;block shift factor
defm 127 ;block mask
defm 7 ;null mask
defw 511 ;disk size-1
defw 127 ;directory max
defm 128 ;alloc 0
defm 0 ;alloc 1
defw 0 ;check size
defw 0 ;track offset
;
; end of fixed tables
;
; individual subroutines to perform each function
boot: ;simplest case is to just perform parameter initialization
XOR a ;zero in the accum
LD (iobyte),A ;clear the iobyte
LD (cdisk),A ;select disk zero
JP gocpm ;initialize and go to cp/m
;
wboot: ;simplest case is to read the disk until all sectors loaded
LD sp, 80h ;use space below buffer for stack
LD c, 0 ;select disk 0
call seldsk
call home ;go to track 00
;
LD b, nsects ;b counts * of sectors to load
LD c, 0 ;c has the current track number
LD d, 1 ;d has the next sector to read
; note that we begin by reading track 0, sector 2 since sector 1
; contains the cold start loader, which is skipped in a warm start
LD HL, ccp ;base of cp/m (initial load point)
load1: ;load one more sector
PUSH BC ;save sector count, current track
PUSH DE ;save next sector to read
PUSH HL ;save dma address
LD c, d ;get sector address to register C
call setsec ;set sector address from register C
pop BC ;recall dma address to b, C
PUSH BC ;replace on stack for later recall
call setdma ;set dma address from b, C
;
; drive set to 0, track set, sector set, dma address set
call read
CP 00h ;any errors?
JP NZ,wboot ;retry the entire boot if an error occurs
;
; no error, move to next sector
pop HL ;recall dma address
LD DE, 128 ;dma=dma+128
ADD HL,DE ;new dma address is in h, l
pop DE ;recall sector address
pop BC ;recall number of sectors remaining, and current trk
DEC b ;sectors=sectors-1
JP Z,gocpm ;transfer to cp/m if all have been loaded
;
; more sectors remain to load, check for track change
INC d
LD a,d ;sector=128?, if so, change tracks
CP 128
JP C,load1 ;carry generated if sector<128
;
; end of current track, go to next track
LD d, 1 ;begin with first sector of next track
INC c ;track=track+1
;
; save register state, and change tracks
PUSH BC
PUSH DE
PUSH HL
call settrk ;track address set from register c
pop HL
pop DE
pop BC
JP load1 ;for another sector
;
; end of load operation, set parameters and go to cp/m
gocpm:
LD a, 0c3h ;c3 is a jmp instruction
LD (0),A ;for jmp to wboot
LD HL, wboote ;wboot entry point
LD (1),HL ;set address field for jmp at 0
;
LD (5),A ;for jmp to bdos
LD HL, bdos ;bdos entry point
LD (6),HL ;address field of Jump at 5 to bdos
;
LD BC, 80h ;default dma address is 80h
call setdma
;
; ei ;enable the interrupt system
LD A,(cdisk) ;get current disk number
cp disks ;see if valid disk number
jp c,diskok ;disk valid, go to ccp
ld a,0 ;invalid disk, change to disk 0
diskok: LD c, a ;send to the ccp
JP ccp ;go to cp/m for further processing
;
;
; simple i/o handlers (must be filled in by user)
; in each case, the entry point is provided, with space reserved
; to insert your own code
;
const: ;console status, return 0ffh if character ready, 00h if not
in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,no_char
ld a,0ffh ;char ready
ret
no_char:ld a,00h ;no char
ret
;
conin: ;console character into register a
in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,conin ;loop until char ready
in a,(2) ;get char
AND 7fh ;strip parity bit
ret
;
conout: ;console character output from register c
in a,(3)
and 001h ;check TxRDY bit
jp z,conout ;loop until port ready
ld a,c ;get the char
out (2),a ;out to port
ret
;
list: ;list character from register c
LD a, c ;character to register a
ret ;null subroutine
;
listst: ;return list status (0 if not ready, 1 if ready)
XOR a ;0 is always ok to return
ret
;
punch: ;punch character from register C
LD a, c ;character to register a
ret ;null subroutine
;
;
reader: ;reader character into register a from reader device
LD a, 1ah ;enter end of file for now (replace later)
AND 7fh ;remember to strip parity bit
ret
;
;
; i/o drivers for the disk follow
; for now, we will simply store the parameters away for use
; in the read and write subroutines
;
home: ;move to the track 00 position of current drive
; translate this call into a settrk call with Parameter 00
LD c, 0 ;select track 0
call settrk
ret ;we will move to 00 on first read/write
;
seldsk: ;select disk given by register c
LD HL, 0000h ;error return code
LD a, c
out (0dh),a ;lba bits 16 - 23, use 16 to 20 for "disk"
CP disks ;must be between 0 and 3
RET NC ;no carry if 4, 5,...
LD l, a ;l=disk number 0, 1, 2, 3
LD h, 0 ;high order zero
ADD HL,HL ;*2
ADD HL,HL ;*4
ADD HL,HL ;*8
ADD HL,HL ;*16 (size of each header)
LD DE, dpbase
ADD HL,DE ;hl=,dpbase (diskno*16) Note typo here in original source.
ret
;
settrk: ;set track given by register c
LD a, c
out (0ch),a ;lba bits 8 - 15 = "track"
ret
;
setsec: ;set sector given by register c
LD a, c
out (0bh),a ;lba bits 0 - 7 = "sector"
ret
;
;
sectran:
;translate the sector given by bc using the
;translate table given by de
EX DE,HL ;hl=.trans
ADD HL,BC ;hl=.trans (sector)
ret ;debug no translation
LD l, (hl) ;l=trans (sector)
LD h, 0 ;hl=trans (sector)
ret ;with value in hl
;
setdma: ;set dma address given by registers b and c
LD l, c ;low order address
LD h, b ;high order address
LD (dmaad),HL ;save the address
ret
;
read:
;Read one CP/M sector from disk.
;Return a 00h in register a if the operation completes properly, and 0lh if an error occurs during the read.
;Disk number in 'diskno'
;Track number in 'track'
;Sector number in 'sector'
;Dma address in 'dmaad' (0-65535)
;
ld hl,(dmaad) ;memory location to place data read from disk
ld a,20h ;Read sector command
out (0fh),a
rd_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,rd_wait_for_DRQ_set ;loop until bit set
read_loop: in a,(08h) ;get data
ld (hl),a
inc hl
in a,(0fh) ;check status
and 08h ;DRQ bit
jp nz,read_loop ;loop until clear
ret
write:
;Write one CP/M sector to disk.
;Return a 00h in register a if the operation completes properly, and 0lh if an error occurs during the read or write
;Disk number in 'diskno'
;Track number in 'track'
;Sector number in 'sector'
;Dma address in 'dmaad' (0-65535)
ld hl,(dmaad) ;memory location of data to write
ld a,30h ;Write sector command
out (0fh),a
wr_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,wr_wait_for_DRQ_set ;loop until bit set
write_loop: ld a,(hl)
out (08h),a ;write data
inc hl
in a,(0fh) ;read status
and 08h ;check DRQ bit
jp nz,write_loop ;write until bit cleared
ret
;
; the remainder of the cbios is reserved uninitialized
; data area, and does not need to be a Part of the
; system memory image (the space must be available,
; however, between"begdat" and"enddat").
;
dmaad: defs 2 ;direct memory address
;
; scratch ram area for bdos use
begdat: equ $ ;beginning of data area
dirbf: defs 128 ;scratch directory area
all00: defs 31 ;allocation vector 0
all01: defs 31 ;allocation vector 1
all02: defs 31 ;allocation vector 2
all03: defs 31 ;allocation vector 3
chk00: defs 16 ;check vector 0
chk01: defs 16 ;check vector 1
chk02: defs 16 ;check vector 2
chk03: defs 16 ;check vector 3
;
enddat: equ $ ;end of data area
datsiz: equ $-begdat; ;size of data area
end

3738
src/cpm22.z80 Normal file

File diff suppressed because it is too large Load Diff

30
src/loader.z80 Normal file
View File

@ -0,0 +1,30 @@
;Retrieves CP/M from disk and loads it in memory starting at E400h
;Uses calls to ROM subroutine for disk read.
;Reads track 0, sectors 2 to 26, then track 1, sectors 1 to 25
;This program is loaded into LBA sector 0 of disk, read to loc. 0800h by ROM disk_read subroutine, and executed.
#target bin
#code _HOME, 0x1100
hstbuf equ 0x1200 ;will put 256-byte raw sector here
disk_read equ 0x0296 ;subroutine in 2K ROM
cpm equ 0x7A00 ;CP/M cold start entry in BIOS
main:
ld c,1 ;LBA bits 0 to 7
ld b,0 ;LBA bits 8 to 15
ld e,0 ;LBA bits 16 to 23
ld hl,0x6400 ; Memory address -- start of CCP
loop:
call disk_read ;subroutine in ROM
ld a,c
cp 50
jp z,done
inc a
ld c,a
jp loop
done:
out (1),a ;switch memory config to all-RAM
jp cpm ;to BIOS cold start entry

56
src/putsys.z80 Normal file
View File

@ -0,0 +1,56 @@
;Copies the memory image of CP/M loaded at E400h onto tracks 0 and 1 of the first CP/M disk
;Load and run from ROM monitor
;Uses calls to BIOS, in memory at FA00h
;Writes track 0, sectors 2 to 26, then track 1, sectors 1 to 25
#target bin
#code _HOME, 0x1400
_bios equ 0x7A00
seldsk equ _bios+0x1b
settrk equ _bios+0x1e
setsec equ _bios+0x21
setdma equ _bios+0x24
write equ _bios+0x2a
monitor_warm_start equ 0x0433 ;Return to ROM monitor
main:
ld c,00h ;CP/M disk a
call seldsk
;Write track 0, sectors 2 to 51
ld a,1 ;starting sector
ld (sector),a
ld hl, 0x6400 ;start of CCP
ld (address),hl
ld c,0 ;CP/M track
call settrk
wr_trk_0_loop:
ld a,(sector)
ld c,a ;CP/M sector
call setsec
ld bc,(address) ;memory location
call setdma
call write
ld a,(sector)
cp 50 ;done:
jp z,done ;yes
inc a ;no, next sector
ld (sector),a
ld hl,(address)
ld de,128
add hl,de
ld (address),hl
jp wr_trk_0_loop
done:
jp 0x0000
sector:
db 00h
address:
dw 0000h
end

687
src/ram_monitor.z80 Normal file
View File

@ -0,0 +1,687 @@
;RAM monitor for a system with serial interface and IDE disk and memory expansion board.
;This program to be loaded at DC00h by ROM monitor, and run from there.
;Assumes serial port has been initialized by ROM monitor.
;Assumes the UART data port address is 02h and control/status address is 03h
;
;The subroutines use these variables in RAM, same area as ROM monitor:
current_location: equ 0x1300 ;word variable in RAM
line_count: equ 0x1302 ;byte variable in RAM
byte_count: equ 0x1303 ;byte variable in RAM
value_pointer: equ 0x1304 ;word variable in RAM
current_value: equ 0x1306 ;word variable in RAM
buffer: equ 0x1308 ;buffer in RAM -- up to stack area
;Can use same stack as ROM monitor. Stack not re-initialized, listed here for information
;ROM_monitor_stack: equ 0x13ff ;upper TPA in RAM, below RAM monitor
;
;
org 01400h
out (1),a ;change memory configuration to all-RAM
jp monitor_start
;
;Puts a single char (byte value) on serial output
;Call with char to send in A register. Uses B register
write_char: ld b,a ;store char
write_char_loop: in a,(3) ;check if OK to send
and 001h ;check TxRDY bit
jp z,write_char_loop ;loop if not set
ld a,b ;get char back
out (2),a ;send to output
ret ;returns with char in a
;
;Subroutine to write a zero-terminated string to serial output
;Pass address of string in HL register
;No error checking
write_string: in a,(3) ;read status
and 001h ;check TxRDY bit
jp z,write_string ;loop if not set
ld a,(hl) ;get char from string
and a ;check if 0
ret z ;yes, finished
out (2),a ;no, write char to output
inc hl ;next char in string
jp write_string ;start over
;
;Binary loader. Receive a binary file, place in memory.
;Address of load passed in HL, length of load (= file length) in BC
bload: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,bload ;not ready, loop
in a,(2)
ld (hl),a
inc hl
dec bc ;byte counter
ld a,b ;need to test BC this way because
or c ;dec rp instruction does not change flags
jp nz,bload
ret
;
;Binary dump to port. Send a stream of binary data from memory to serial output
;Address of dump passed in HL, length of dump in BC
bdump: in a,(3) ;get status
and 001h ;check TxRDY bit
jp z,bdump ;not ready, loop
ld a,(hl)
out (2),a
inc hl
dec bc
ld a,b ;need to test this way because
or c ;dec rp instruction does not change flags
jp nz,bdump
ret
;
;Subroutine to get a string from serial input, place in buffer.
;Buffer address passed in HL reg.
;Uses A,BC,DE,HL registers (including calls to other subroutines).
;Line entry ends by hitting return key. Return char not included in string (replaced by zero).
;Backspace editing OK. No error checking.
;
get_line: ld c,000h ;line position
ld a,h ;put original buffer address in de
ld d,a ;after this don't need to preserve hl
ld a,l ;subroutines called don't use de
ld e,a
get_line_next_char: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,get_line_next_char ;not ready, loop
in a,(2) ;get char
cp 00dh ;check if return
ret z ;yes, normal exit
cp 07fh ;check if backspace (VT102 keys)
jp z,get_line_backspace ;yes, jump to backspace routine
cp 008h ;check if backspace (ANSI keys)
jp z,get_line_backspace ;yes, jump to backspace
call write_char ;put char on screen
ld (de),a ;store char in buffer
inc de ;point to next space in buffer
inc c ;inc counter
ld a,000h
ld (de),a ;leaves a zero-terminated string in buffer
jp get_line_next_char
get_line_backspace: ld a,c ;check current position in line
cp 000h ;at beginning of line?
jp z,get_line_next_char ;yes, ignore backspace, get next char
dec de ;no, erase char from buffer
dec c ;back up one
ld a,000h ;put a zero in buffer where the last char was
ld (de),a
ld hl,erase_char_string ;ANSI sequence to delete one char from line
call write_string ;transmits sequence to backspace and erase char
jp get_line_next_char
;
;Creates a two-char hex string from the byte value passed in register A
;Location to place string passed in HL
;String is zero-terminated, stored in 3 locations starting at HL
;Also uses registers b,d, and e
byte_to_hex_string: ld b,a ;store original byte
srl a ;shift right 4 times, putting
srl a ;high nybble in low-nybble spot
srl a ;and zeros in high-nybble spot
srl a
ld d,000h ;prepare for 16-bit addition
ld e,a ;de contains offset
push hl ;temporarily store string target address
ld hl,hex_char_table ;use char table to get high-nybble character
add hl,de ;add offset to start of table
ld a,(hl) ;get char
pop hl ;get string target address
ld (hl),a ;store first char of string
inc hl ;point to next string target address
ld a,b ;get original byte back from reg b
and 00fh ;mask off high-nybble
ld e,a ;d still has 000h, now de has offset
push hl ;temp store string target address
ld hl,hex_char_table ;start of table
add hl,de ;add offset
ld a,(hl) ;get char
pop hl ;get string target address
ld (hl),a ;store second char of string
inc hl ;point to third location
ld a,000h ;zero to terminate string
ld (hl),a ;store the zero
ret ;done
;
;Converts a single ASCII hex char to a nybble value
;Pass char in reg A. Letter numerals must be upper case.
;Return nybble value in low-order reg A with zeros in high-order nybble if no error.
;Return 0ffh in reg A if error (char not a valid hex numeral).
;Also uses b, c, and hl registers.
hex_char_to_nybble: ld hl,hex_char_table
ld b,00fh ;no. of valid characters in table - 1.
ld c,000h ;will be nybble value
hex_to_nybble_loop: cp (hl) ;character match here?
jp z,hex_to_nybble_ok ;match found, exit
dec b ;no match, check if at end of table
jp m,hex_to_nybble_err ;table limit exceded, exit with error
inc c ;still inside table, continue search
inc hl
jp hex_to_nybble_loop
hex_to_nybble_ok: ld a,c ;put nybble value in a
ret
hex_to_nybble_err: ld a,0ffh ;error value
ret
;
;Converts a hex character pair to a byte value
;Called with location of high-order char in HL
;If no error carry flag clear, returns with byte value in register A, and
;HL pointing to next mem location after char pair.
;If error (non-hex char) carry flag set, HL pointing to invalid char
hex_to_byte: ld a,(hl) ;location of character pair
push hl ;store hl (hex_char_to_nybble uses it)
call hex_char_to_nybble
pop hl ;returns with nybble value in a reg, or 0ffh if error
cp 0ffh ;non-hex character?
jp z,hex_to_byte_err ;yes, exit with error
sla a ;no, move low order nybble to high side
sla a
sla a
sla a
ld d,a ;store high-nybble
inc hl ;get next character of the pair
ld a,(hl)
push hl ;store hl
call hex_char_to_nybble
pop hl
cp 0ffh ;non-hex character?
jp z,hex_to_byte_err ;yes, exit with error
or d ;no, combine with high-nybble
inc hl ;point to next memory location after char pair
scf
ccf ;no-error exit (carry = 0)
ret
hex_to_byte_err: scf ;error, carry flag set
ret
hex_char_table: defm "0123456789ABCDEF" ;ASCII hex table
;
;Subroutine to get a two-byte address from serial input.
;Returns with address value in HL
;Uses locations in RAM for buffer and variables
address_entry: ld hl,buffer ;location for entered string
call get_line ;returns with address string in buffer
ld hl,buffer ;location of stored address entry string
call hex_to_byte ;will get high-order byte first
jp c, address_entry_error ;if error, jump
ld (current_location+1),a ;store high-order byte, little-endian
ld hl,buffer+2 ;point to low-order hex char pair
call hex_to_byte ;get low-order byte
jp c, address_entry_error ;jump if error
ld (current_location),a ;store low-order byte in lower memory
ld hl,(current_location) ;put memory address in hl
ret
address_entry_error: ld hl,address_error_msg
call write_string
jp address_entry
;
;Subroutine to get a decimal string, return a word value
;Calls decimal_string_to_word subroutine
decimal_entry: ld hl,buffer
call get_line ;returns with DE pointing to terminating zero
ld hl,buffer
call decimal_string_to_word
ret nc ;no error, return with word in hl
ld hl,decimal_error_msg ;error, try again
call write_string
jp decimal_entry
;
;Subroutine to convert a decimal string to a word value
;Call with address of string in HL, pointer to end of string in DE
;Carry flag set if error (non-decimal char)
;Carry flag clear, word value in HL if no error.
decimal_string_to_word: ld b,d
ld c,e ;use BC as string pointer
ld (current_location),hl ;store addr. of start of buffer in RAM word variable
ld hl,000h ;starting value zero
ld (current_value),hl
ld hl,decimal_place_value ;pointer to values
ld (value_pointer),hl
decimal_next_char: dec bc ;next char in string (moving right to left)
ld hl,(current_location) ;check if at end of decimal string
scf ;get ready to subtract de from buffer addr.
ccf ;set carry to zero (clear)
sbc hl,bc ;keep going if bc > or = hl (buffer address)
jp c,decimal_continue ;borrow means bc > hl
jp z,decimal_continue ;z means bc = hl
ld hl,(current_value) ;return if de < buffer address (no borrow)
scf ;get value back from RAM variable
ccf
ret ;return with carry clear, value in hl
decimal_continue: ld a,(bc) ;next char in string (right to left)
sub 030h ;ASCII value of zero char
jp m,decimal_error ;error if char value less than 030h
cp 00ah ;error if byte value > or = 10 decimal
jp p,decimal_error ;a reg now has value of decimal numeral
ld hl,(value_pointer) ;get value to add an put in de
ld e,(hl) ;little-endian (low byte in low memory)
inc hl
ld d,(hl)
inc hl ;hl now points to next value
ld (value_pointer),hl
ld hl,(current_value) ;get back current value
decimal_add: dec a ;add loop to increase total value
jp m,decimal_add_done ;end of multiplication
add hl,de
jp decimal_add
decimal_add_done: ld (current_value),hl
jp decimal_next_char
decimal_error: scf
ret
jp decimal_add
decimal_place_value: defw 1,10,100,1000,10000
;
;Memory dump
;Displays a 256-byte block of memory in 16-byte rows.
;Called with address of start of block in HL
memory_dump: ld (current_location),hl ;store address of block to be displayed
ld a,000h
ld (byte_count),a ;initialize byte count
ld (line_count),a ;initialize line count
jp dump_new_line
dump_next_byte: ld hl,(current_location) ;get byte address from storage,
ld a,(hl) ;get byte to be converted to string
inc hl ;increment address and
ld (current_location),hl ;store back
ld hl,buffer ;location to store string
call byte_to_hex_string ;convert
ld hl,buffer ;display string
call write_string
ld a,(byte_count) ;next byte
inc a
jp z,dump_done ;stop when 256 bytes displayed
ld (byte_count),a ;not finished yet, store
ld a,(line_count) ;end of line (16 characters)?
cp 00fh ;yes, start new line
jp z,dump_new_line
inc a ;no, increment line count
ld (line_count),a
ld a,020h ;print space
call write_char
jp dump_next_byte ;continue
dump_new_line: ld a,000h ;reset line count to zero
ld (line_count),a
call write_newline
ld hl,(current_location) ;location of start of line
ld a,h ;high byte of address
ld hl, buffer
call byte_to_hex_string ;convert
ld hl,buffer
call write_string ;write high byte
ld hl,(current_location)
ld a,l ;low byte of address
ld hl, buffer
call byte_to_hex_string ;convert
ld hl,buffer
call write_string ;write low byte
ld a,020h ;space
call write_char
jp dump_next_byte ;now write 16 bytes
dump_done: ld a,000h
ld hl,buffer
ld (hl),a ;clear buffer of last string
call write_newline
ret
;
;Memory load
;Loads RAM memory with bytes entered as hex characters
;Called with address to start loading in HL
;Displays entered data in 16-byte rows.
memory_load: ld (current_location),hl
ld hl,data_entry_msg
call write_string
jp load_new_line
load_next_char: call get_char
cp 00dh ;return?
jp z,load_done ;yes, quit
ld (buffer),a
call get_char
cp 00dh ;return?
jp z,load_done ;yes, quit
ld (buffer+1),a
ld hl,buffer
call hex_to_byte
jp c,load_data_entry_error ;non-hex character
ld hl,(current_location) ;get byte address from storage,
ld (hl),a ;store byte
inc hl ;increment address and
ld (current_location),hl ;store back
ld a,(buffer)
call write_char
ld a,(buffer+1)
call write_char
ld a,(line_count) ;end of line (16 characters)?
cp 00fh ;yes, start new line
jp z,load_new_line
inc a ;no, increment line count
ld (line_count),a
ld a,020h ;print space
call write_char
jp load_next_char ;continue
load_new_line: ld a,000h ;reset line count to zero
ld (line_count),a
call write_newline
jp load_next_char ;continue
load_data_entry_error: call write_newline
ld hl,data_error_msg
call write_string
ret
load_done: call write_newline
ret
;
;Get one ASCII character from the serial port.
;Returns with char in A reg. No error checking.
get_char: in a,(3) ;get status
and 002h ;check RxRDY bit
jp z,get_char ;not ready, loop
in a,(2) ;get char
ret
;
;Subroutine to start a new line
write_newline: ld a,00dh ;ASCII carriage return character
call write_char
ld a,00ah ;new line (line feed) character
call write_char
ret
;
;Subroutine to read one disk sector (128 bytes)
;Address to place data passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_read:
rd_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,rd_status_loop_1 ;loop until not busy
rd_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,rd_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,20h ;Read sector command
out (0fh),a
rd_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,rd_wait_for_DRQ_set ;loop until bit set
rd_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,rd_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
read_loop: in a,(08h) ;get data
ld (hl),a
inc hl
in a,(0fh) ;check status
and 08h ;DRQ bit
jp nz,read_loop ;loop until cleared
ret
;
;Subroutine to write one disk sector (128 bytes)
;Address of data to write to disk passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_write:
wr_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,wr_status_loop_1 ;loop until not busy
wr_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,wr_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,30h ;Write sector command
out (0fh),a
wr_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,wr_wait_for_DRQ_set ;loop until bit set
write_loop: ld a,(hl)
out (08h),a ;write data
inc hl
in a,(0fh) ;read status
and 08h ;check DRQ bit
jp nz,write_loop ;write until bit cleared
wr_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,wr_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
ret
;
;Strings used in subroutines
length_entry_string: defm "Enter length of file to load (decimal): ",0
dump_entry_string: defm "Enter no. of bytes to dump (decimal): ",0
LBA_entry_string: defm "Enter LBA (decimal, 0 to 65535): ",0
erase_char_string: defm 008h,01bh,"[K",000h ;ANSI sequence for backspace, erase to end of line.
address_entry_msg: defm "Enter 4-digit hex address (use upper-case A through F): ",0
address_error_msg: defm 13,10,"Error: invalid hex character, try again: ",0
data_entry_msg: defm "Enter hex bytes, hit return when finished.",13,10,0
data_error_msg: defm "Error: invalid hex byte.",13,10,0
decimal_error_msg: defm 13,10,"Error: invalid decimal number, try again: ",0
;
;Simple monitor program for CPUville Z80 computer with serial interface.
monitor_start: call write_newline ;routine program return here to avoid re-initialization of port
ld a,03eh ;cursor symbol
call write_char
ld hl,buffer
call get_line ;get monitor input string (command)
call write_newline
call parse ;interprets command, returns with address to jump to in HL
jp (hl)
;
;Parses an input line stored in buffer for available commands as described in parse table.
;Returns with address of jump to action for the command in HL
parse: ld bc,parse_table ;bc is pointer to parse_table
parse_start: ld a,(bc) ;get pointer to match string from parse table
ld e,a
inc bc
ld a,(bc)
ld d,a ;de will is pointer to strings for matching
ld a,(de) ;get first char from match string
or 000h ;zero?
jp z,parser_exit ;yes, exit no_match
ld hl,buffer ;no, parse input string
match_loop: cp (hl) ;compare buffer char with match string char
jp nz,no_match ;no match, go to next match string
or 000h ;end of strings (zero)?
jp z,parser_exit ;yes, matching string found
inc de ;match so far, point to next char in match string
ld a,(de) ;get next character from match string
inc hl ;and point to next char in input string
jp match_loop ;check for match
no_match: inc bc ;skip over jump target to
inc bc
inc bc ;get address of next matching string
jp parse_start
parser_exit: inc bc ;skip to address of jump for match
ld a,(bc)
ld l,a
inc bc
ld a,(bc)
ld h,a ;returns with jump address in hl
ret
;
;Actions to be taken on match
;
;Memory dump program
;Input 4-digit hexadecimal address
;Calls memory_dump subroutine
dump_jump: ld hl,dump_message ;Display greeting
call write_string
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry ;returns with address in HL
call write_newline
call memory_dump
jp monitor_start
;
;Hex loader, displays formatted input
load_jump: ld hl,load_message ;Display greeting
call write_string ;get address to load
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry
call write_newline
call memory_load
jp monitor_start
;
;Jump and run do the same thing: get an address and jump to it.
run_jump: ld hl,run_message ;Display greeting
call write_string
ld hl,address_entry_msg ;get ready to get address
call write_string
call address_entry
jp (hl)
;
;Help and ? do the same thing, display the available commands
help_jump: ld hl,help_message
call write_string
ld bc,parse_table ;table with pointers to command strings
help_loop: ld a,(bc) ;displays the strings for matching commands,
ld l,a ;getting the string addresses from the
inc bc ;parse table
ld a,(bc) ;pass address of string to hl through a reg
ld h,a
ld a,(hl) ;hl now points to start of match string
or 000h ;exit if no_match string
jp z,help_done
push bc ;write_char uses b register
ld a,020h ;space char
call write_char
pop bc
call write_string ;writes match string
inc bc ;pass over jump address in table
inc bc
inc bc
jp help_loop
help_done: jp monitor_start
;
;Binary file load. Need both address to load and length of file
bload_jump: ld hl,bload_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,length_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld hl,bload_ready_message
call write_string
pop hl
call bload
jp monitor_start
;
;Binary memory dump. Need address of start of dump and no. bytes
bdump_jump: ld hl,bdump_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,dump_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld hl,bdump_ready_message
call write_string
call get_char
pop hl
call bdump
jp monitor_start
;Disk read. Need memory address to place data, LBA of sector to read
diskrd_jump: ld hl,diskrd_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,LBA_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld e,00h
pop hl
call disk_read
jp monitor_start
diskwr_jump: ld hl,diskwr_message
call write_string
ld hl,address_entry_msg
call write_string
call address_entry
call write_newline
push hl
ld hl,LBA_entry_string
call write_string
call decimal_entry
ld b,h
ld c,l
ld e,00h
pop hl
call disk_write
jp monitor_start
boot_jump: ld hl,1100h
ld bc,0000h
ld e,00h
call disk_read
out (0),a ;CP/M loader uses ROM routine to read disk
jp 1100h
;Prints message for no match to entered command
no_match_jump: ld hl,no_match_message
call write_string
ld hl, buffer
call write_string
jp monitor_start
;
;Monitor data structures:
;
monitor_message: defm 13,10,"ROM ver. 8",13,10,0
no_match_message: defm "? ",0
help_message: defm "Commands implemented:",13,10,0
dump_message: defm "Displays a 256-byte block of memory.",13,10,0
load_message: defm "Enter hex bytes starting at memory location.",13,10,0
run_message: defm "Will jump to (execute) program at address entered.",13,10,0
bload_message: defm "Loads a binary file into memory.",13,10,0
bload_ready_message: defm 13,10,"Ready to receive, start transfer.",0
bdump_message: defm "Dumps binary data from memory to serial port.",13,10,0
bdump_ready_message: defm 13,10,"Ready to send, hit any key to start.",0
diskrd_message: defm "Reads one sector from disk to memory.",13,10,0
diskwr_message: defm "Writes one sector from memory to disk.",13,10,0
;Strings for matching:
dump_string: defm "dump",0
load_string: defm "load",0
jump_string: defm "jump",0
run_string: defm "run",0
question_string: defm "?",0
help_string: defm "help",0
bload_string: defm "bload",0
bdump_string: defm "bdump",0
diskrd_string: defm "diskrd",0
diskwr_string: defm "diskwr",0
boot_string: defm "boot",0
no_match_string: defm 0,0
;Table for matching strings to jumps
parse_table: defw dump_string,dump_jump,load_string,load_jump
defw jump_string,run_jump,run_string,run_jump
defw question_string,help_jump,help_string,help_jump
defw bload_string,bload_jump,bdump_string,bdump_jump
defw diskrd_string,diskrd_jump,diskwr_string,diskwr_jump
defw boot_string,boot_jump
defw no_match_string,no_match_jump

View File

@ -394,36 +394,22 @@ write_newline: ld a,00dh ;ASCII carriage return character
call write_char
ret
;
;Subroutine to read one disk sector (256 bytes)
;Subroutine to read one disk sector (128 bytes)
;Address to place data passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_read:
rd_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,rd_status_loop_1 ;loop until not busy
rd_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,rd_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,20h ;Read sector command
out (0fh),a
rd_wait_for_DRQ_set: in a,(0fh) ;read status
and 08h ;DRQ bit
jp z,rd_wait_for_DRQ_set ;loop until bit set
rd_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,rd_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
read_loop: in a,(08h) ;get data
ld (hl),a
inc hl
@ -432,27 +418,17 @@ read_loop: in a,(08h) ;get data
jp nz,read_loop ;loop until cleared
ret
;
;Subroutine to write one disk sector (256 bytes)
;Subroutine to write one disk sector (128 bytes)
;Address of data to write to disk passed in HL
;LBA bits 0 to 7 passed in C, bits 8 to 15 passed in B
;LBA bits 16 to 23 passed in E
disk_write:
wr_status_loop_1: in a,(0fh) ;check status
and 80h ;check BSY bit
jp nz,wr_status_loop_1 ;loop until not busy
wr_status_loop_2: in a,(0fh) ;check status
and 40h ;check DRDY bit
jp z,wr_status_loop_2 ;loop until ready
ld a,01h ;number of sectors = 1
out (0ah),a ;sector count register
ld a,c
out (0bh),a ;lba bits 0 - 7
ld a,b
out (0ch),a ;lba bits 8 - 15
ld a,e
out (0dh),a ;lba bits 16 - 23
ld a,11100000b ;LBA mode, select drive 0
out (0eh),a ;drive/head register
ld a,30h ;Write sector command
out (0fh),a
wr_wait_for_DRQ_set: in a,(0fh) ;read status
@ -464,18 +440,13 @@ write_loop: ld a,(hl)
in a,(0fh) ;read status
and 08h ;check DRQ bit
jp nz,write_loop ;write until bit cleared
wr_wait_for_BSY_clear: in a,(0fh)
and 80h
jp nz,wr_wait_for_BSY_clear
in a,(0fh) ;clear INTRQ
ret
;
;Strings used in subroutines
length_entry_string: defm "Enter length of file to load (decimal): ",0
dump_entry_string: defm "Enter no. of bytes to dump (decimal): ",0
LBA_entry_string: defm "Enter LBA (decimal, 0 to 65535): ",0
;; erase_char_string: defm 008h,01bh,"[K",000h ;ANSI sequence for backspace, erase to end of line.
erase_char_string: defm 008h
erase_char_string: defm 008h,01bh,"[K",000h ;ANSI sequence for backspace, erase to end of line.
address_entry_msg: defm "Enter 4-digit hex address (use upper-case A through F): ",0
address_error_msg: defm 13,10,"Error: invalid hex character, try again: ",0
data_entry_msg: defm "Enter hex bytes, hit return when finished.",13,10,0
@ -654,11 +625,11 @@ diskwr_jump: ld hl,diskwr_message
pop hl
call disk_write
jp monitor_warm_start
cpm_jump: ld hl,0800h
boot_jump: ld hl,1100h
ld bc,0000h
ld e,00h
call disk_read
jp 0800h
jp 1100h
;Prints message for no match to entered command
no_match_jump: ld hl,no_match_message
call write_string
@ -668,7 +639,7 @@ no_match_jump: ld hl,no_match_message
;
;Monitor data structures:
;
monitor_message: defm 13,10,"ROM ver. 8",13,10,0
monitor_message: defm 13,10,"ROM Ver. 9",13,10,0
no_match_message: defm "? ",0
help_message: defm "Commands implemented:",13,10,0
dump_message: defm "Displays a 256-byte block of memory.",13,10,0
@ -691,7 +662,7 @@ bload_string: defm "bload",0
bdump_string: defm "bdump",0
diskrd_string: defm "diskrd",0
diskwr_string: defm "diskwr",0
cpm_string: defm "cpm",0
boot_string: defm "boot",0
no_match_string: defm 0,0
;Table for matching strings to jumps
parse_table: defw dump_string,dump_jump,load_string,load_jump
@ -699,6 +670,6 @@ parse_table: defw dump_string,dump_jump,load_string,load_jump
defw question_string,help_jump,help_string,help_jump
defw bload_string,bload_jump,bdump_string,bdump_jump
defw diskrd_string,diskrd_jump,diskwr_string,diskwr_jump
defw cpm_string,cpm_jump
defw boot_string,boot_jump
defw no_match_string,no_match_jump

View File

@ -2,6 +2,7 @@
import serial
import os
import sys
import time
def progressbar(it, prefix="", size=60, file=sys.stdout):
count = len(it)
@ -19,26 +20,29 @@ def progressbar(it, prefix="", size=60, file=sys.stdout):
def main():
if len(sys.argv) == 2:
# ser = serial.Serial("COM3", timeout=1, write_timeout=1)
ser = serial.Serial("/dev/ttyACM0", timeout=1, write_timeout=1)
ser = serial.Serial("/dev/ttyUSB0", timeout=1, write_timeout=1, baudrate=115200)
if ser.is_open:
# Clear out any existing input
ser.write(b'\n')
ser.readline()
time.sleep(0.002)
# Send the upload command
ser.write(b'#u\n')
print(ser.readline())
time.sleep(0.002)
path = sys.argv[1]
size = os.path.getsize(path)
ser.write([size & 0xFF])
time.sleep(0.002)
ser.write([(size >> 8) & 0xFF])
i = 0
time.sleep(0.002)
with open(path, "rb") as f:
for i in progressbar(range(size), "Upload: ", 40):
ser.write(f.read(1))
byte = f.read(1)
ser.write(byte)
time.sleep(0.002)
print(ser.readline())
ser.close()
else:

49
upload_serial.py Executable file
View File

@ -0,0 +1,49 @@
#!/usr/bin/env python3
import serial
import os
import sys
import time
def progressbar(it, prefix="", size=60, file=sys.stdout):
count = len(it)
def show(j):
x = int(size*j/count)
file.write("%s[%s%s] %i/%i\r" % (prefix, "#"*x, "."*(size-x), j, count))
file.flush()
show(0)
for i, item in enumerate(it):
yield item
show(i+1)
file.write("\n")
file.flush()
def main():
if len(sys.argv) == 2:
# ser = serial.Serial("COM3", timeout=1, write_timeout=1)
ser = serial.Serial("/dev/ttyUSB0", timeout=1, write_timeout=1, baudrate=115200)
if ser.is_open:
path = sys.argv[1]
size = os.path.getsize(path)
with open(path, "rb") as f:
for i in progressbar(range(size), "Upload: ", 40):
byte = f.read(1)
ser.write(byte)
if byte == b'#':
time.sleep(0.002)
ser.write(b'#')
time.sleep(0.002)
ser.write(b'\n')
time.sleep(0.002)
ser.close()
else:
print("Failed to open serial port")
else:
print("Please provide file to upload")
if "__main__":
main()