Bläddra i källkod

UFD-DOS/PUN80: support random access files in PUN80

Sync UFD-DOS and PUN80 sources from the abc80sim tree.
With these changes, it is now possible to do random access (Q0$
interface) to network files over PUN80.

Don't try to autostart (RUN START80) if no BASICERR.SYS file is found;
this prevents an ERR 11 when no disk drive is present.
H. Peter Anvin 1 år sedan
förälder
incheckning
358296a732

BIN
esp32/output/max80.ino.bin


+ 3 - 3
fpga/max80.qpf

@@ -19,15 +19,15 @@
 #
 # Quartus Prime
 # Version 22.1std.2 Build 922 07/20/2023 SC Lite Edition
-# Date created = 17:24:40  October 23, 2023
+# Date created = 21:58:24  November 08, 2023
 #
 # -------------------------------------------------------------------------- #
 
 QUARTUS_VERSION = "22.1"
-DATE = "17:24:40  October 23, 2023"
+DATE = "21:58:24  November 08, 2023"
 
 # Revisions
 
-PROJECT_REVISION = "bypass"
 PROJECT_REVISION = "v1"
 PROJECT_REVISION = "v2"
+PROJECT_REVISION = "bypass"

BIN
fpga/output/bypass.jic


BIN
fpga/output/bypass.sof


BIN
fpga/output/max80.fw


BIN
fpga/output/v1.fw


BIN
fpga/output/v1.jic


BIN
fpga/output/v1.sof


BIN
fpga/output/v2.fw


BIN
fpga/output/v2.jic


BIN
fpga/output/v2.sof


+ 1 - 1
rv32/checksum.h

@@ -1,4 +1,4 @@
 #ifndef CHECKSUM_H
 #define CHECKSUM_H
-#define SDRAM_SUM 0x2cfe9df2
+#define SDRAM_SUM 0x3fd7e92f
 #endif

+ 5 - 0
rv32/roms/asmsrc/abc80/abc80.inc

@@ -122,6 +122,11 @@ defc IX_BLKWR		= 0x088a + 3*6
 defc IX_KILL		= 0x088a + 3*7
 defc IX_NAME		= 0x088a + 3*8
 
+;; DOS entry point for random file access (Q0$ interface)
+defc Q0S_SETFILE	= 0x6ffa    ;; Select file and set up Q0$
+defc Q0S_READ		= 0x6ffc    ;; Read block into Q0$
+defc Q0S_WRITE		= 0x6ffe    ;; Write block from Q0$
+
 ;; Entry points in the IEC ROM
 defc IEC_CCMD		= 0x7000    ;; Compile CMD to byte code
 defc IEC_ECMD		= 0x7003    ;; Execute CMD byte code

+ 174 - 94
rv32/roms/asmsrc/abc80/print80.inc

@@ -60,7 +60,7 @@
 	defc raw_pr = 0
 
 	;; XDx: device entries (secondary hard disk, not enough space in DOS)
-	defc xd_dev = 1
+	defc xd_dev = LARGE
 
 	;; CMD routine if in IEC area?
 	defc have_cmd = LARGE && (ROMSTART == 0x7000)
@@ -70,9 +70,54 @@
 	defc e_iec = ERR_8
 	endif
 
+	;; Allocate memory from the BASIC stack?
+	defc use_stack = AUXRAM_PRINTNET_BASE >= 0x8000
+
 	;; Device timeout
 	defc timeout = 100		; 100/50 Hz = 2 s
 
+	;; Command opcodes
+	NET_OPEN_A	= 0xa0
+	NET_OPEN_B	= 0xa1
+	NET_PREP_A	= 0xa2
+	NET_PREP_B	= 0xa3
+	NET_INPUT	= 0xa4
+	NET_GET		= 0xa5
+	NET_PRINT	= 0xa6
+	NET_CLOSE	= 0xa7
+	NET_CLOSALL	= 0xa8
+	NET_INIT	= 0xa9
+	NET_RENAME	= 0xaa
+	NET_DELETE	= 0xab
+	NET_PREAD	= 0xac
+	NET_PWRITE	= 0xad
+	NET_BLKSIZE	= 0xae
+	NET_INITSZ	= 0xaf
+	NET_SEEK0	= 0xb0
+	NET_SEEK1	= 0xb1
+	NET_SEEK2	= 0xb2
+	NET_SEEK3	= 0xb3
+	NET_SEEK4	= 0xb4
+	NET_SEEK5	= 0xb5
+	NET_SEEK6	= 0xb6
+	NET_SEEK7	= 0xb7
+	NET_SEEK8	= 0xb8
+	NET_PUT		= 0xb9
+	NET_LISTVOL	= 0xba
+	NET_CMD		= 0xbb
+
+	;; Framing bytes
+	NET_SOF		= 0xff		; Start of frame (command byte follows)
+	NET_EOF		= 0xef		; End of frame
+
+	;; Special commands for printing and debug
+	NET_PR		= 0xf3		; Begin print data mode
+	NET_PRCLOSE	= 0xfd		; End print job
+	NET_PRFF	= 0xfe		; Escape FF
+
+	;; Special command for debug console
+	NET_CON		= 0xc0
+
 	.globl _org
 	_org = ROMSTART
 
@@ -152,13 +197,13 @@ pr_print:
 pr_print_loop:
 	ld a,b
 	or c
-	ld a,0EFh
+	ld a,NET_PRETX
 	jr z,done_esc
 	ld a,(hl)
 	call send_byte
 	inc a
 	jr nz,pr_not_ff
-	ld a,0FEh
+	ld a,NET_PRFF
 	call send_byte
 pr_not_ff:
 	dec bc
@@ -167,7 +212,7 @@ pr_not_ff:
 
 pr_close:
 	call select
-	ld a,0FDh
+	ld a,NET_PREOJ
 	jr done_esc
 
 	endif
@@ -215,19 +260,19 @@ done:
 	if pra_dev
 
 pra_open:
-	ld a,0xA0
+	ld a,NET_OPEN_A
 	jr prx_open
 pra_prepare:
-	ld a,0xA2
+	ld a,NET_PREP_A
 	jr prx_open
 
 	endif
 
 prb_prepare:
-	ld a,0xA3
+	ld a,NET_PREP_B
 	jr prb_open_prepare
 prb_open:
-	ld a,0xA1
+	ld a,NET_OPEN_B
 prb_open_prepare:
 	call prb_setup_buf
 
@@ -363,7 +408,7 @@ crlf:
 
 prx_rename:
 	call select
-	ld a,0xAA
+	ld a,NET_RENAME
 	call send_cmd
 	ex de,hl			; HL -> new filename
 	ld bc,11
@@ -392,7 +437,7 @@ pra_close:
 	else
 	ld (ix+5),b
 	endif
-	ld a,0xA7
+	ld a,NET_CLOSE
 prx_simple_command:			; Just command and response, no data
 	call send_cmd
 prx_reply_done:				; Reply, then done
@@ -401,7 +446,7 @@ done2:
 	jp done
 
 prx_delete:
-	ld a,0xAB
+	ld a,NET_DELETE
 	call select
 	jr prx_simple_command
 
@@ -415,7 +460,7 @@ pra_print:
 	endif
 
 output_common:
-	ld a,0xA6
+	ld a,NET_PRINT
 prx_length_command:
 	call send_cmd
 	call send_word
@@ -426,7 +471,7 @@ prx_length_command:
 
 pra_input:
 	call select
-	ld a,0xA4			; INPUT
+	ld a,NET_INPUT			; INPUT
 
 	endif
 
@@ -437,10 +482,9 @@ pra_input:
 input_command:
 	call send_cmd
 	call recv_reply
-	call recv_byte
-	ld e,a
-	call recv_byte
-	ld d,a
+	ex de,hl
+	call recv_word
+	ex de,hl
 	; Now HL -> target buf; DE -> expected byte count;
 	; BC -> buffer size
 prai_loop:
@@ -466,26 +510,20 @@ prbr_protoerr:
 prb_rdblk:
 	call select
 prb_rdblk_nosel:
-	ld a,0xA5
-	call send_cmd
-	ld b,253
-	ld a,b
-	call send_byte
-	xor a
-	call send_byte
+	ld a,NET_PREAD
+	call send_cmd_blkno
 	call recv_reply
-	call recv_byte
-	cp b
-	jr nz,prbr_protoerr
-	call recv_byte
-	and a
-	jr nz,prbr_protoerr
 	call prb_getbufaddr
-	push hl
+	ex de,hl
+	call recv_word
+	sbc hl,bc
+	jr nz,prbr_protoerr
+	ld b,c
+	push de
 prbr_recv:
 	call recv_byte
-	ld (hl),a
-	inc hl
+	ld (de),a
+	inc de
 	djnz prbr_recv
 	pop hl			; HL -> buf address
 	jp done_ok
@@ -542,10 +580,10 @@ pbi_err:
 	scf
 	jr pbi_return
 pbi_overlong:
-	ld a,128 + 20	        ; Line too long
+	ld a,128 + 20		; Line too long
 	jr pbi_err
 pbi_badchar:
-	ld a,128 + 58	        ; Bad character
+	ld a,128 + 58		; Bad character
 	jr pbi_err
 pbi_lf:				; Convert to CR and EOL, but don't eat LF
 	ld (hl),13
@@ -594,17 +632,16 @@ pbi_eofbuf:
 	ld (hl),a
 	ret
 
-	; Write a binary output block.  Similar to
-	; pra_print, but with a few different buffer
-	; management bits.
+	; Write a binary output block.
 prb_wrblk:
 	call select
+	ld a,NET_PWRITE
+	call send_cmd_blkno
 	call prb_getbufaddr
 	ld bc,253
-	call output_common
+	call send_buf
 	call prb_empty_buf
-done3:
-	jp done
+	jp recv_reply
 
 	;; Blocking PRINT without converting to ABC-DOS text format.
 	;; This simply stuffs a buffer full of the PRINT contents;
@@ -658,11 +695,11 @@ pbp_allbuf:
 
 	;; Get the address of the DOS file description corresponding
 	;; to the allocated buffer.
-	;; Returns with B = 0, C = DOSBUF*16, HL = DOS file description
+	;; Returns with B = 0, C = DOSBUF*16, HL = DOS file description+1
 prb_dosfd:
 	ld b,0
 	ld c,(ix+12)
-	ld hl,0xFD41
+	ld hl,DOSFD0 + 1
 	add hl,bc
 	ret
 
@@ -674,6 +711,11 @@ prb_setup_buf:
 	push hl
 	call DOSALLOCBUF	; Allocate buffer
 	call DOSBUFINIT		; Initialize buffer pointers
+	call prb_dosfd
+	inc hl			; Next block number <- 1
+	ld (hl),1
+	inc hl
+	ld (hl),a		; A = 0
 	pop hl
 	pop bc
 	pop af
@@ -690,10 +732,12 @@ prb_empty_buf:			; Returns with A=0, HL->buf
 	pop af
 	ret
 
-;;; Load the address of the start of the current buffer into HL
+;;; Load the address of the start of the current buffer into HL,
+;;; and the buffer size (253) into BC.
 prb_getbufaddr:
 	ld l,3
 	ld h,(ix+9)
+	ld bc,253
 	ret
 
 	;; Send a command header, A = command
@@ -710,6 +754,24 @@ send_cmd:
 	pop bc
 	ret
 
+	;; Send a command header, A = command, then the block
+	;; number taken from the DOS file descriptor. Clobbers
+	;; BC and HL, and increments the block number.
+send_cmd_blkno:
+	call send_cmd
+	call prb_dosfd
+	inc hl
+	ld c,(hl)
+	inc hl
+	ld b,(hl)
+	inc bc			; Next block
+	ld (hl),b
+	dec hl
+	ld (hl),c
+	dec bc			; Point back to the original block
+	dec bc			; DOS block numbers are 1-based
+	;; Fall through
+
 	;; Send a word in BC, preserves AF
 send_word:
 	push af
@@ -720,18 +782,18 @@ send_word:
 	pop af
 	ret
 
-	;; Send FF + byte; reset running checksum
+	;; Send FF + byte; reset running checksum to FF
 	;; Returns with CF = 0!
 send_esc:
 	push af
-	ld a,0FFh
+	ld a,NET_SOF
 	call send_byte
 	ld (ram_csum),a
 	pop af
 	;; Fall through
 
 	;; Send a single byte and add to running checksum
-	;; Returns with CF = 0!
+	;; Returns with A unchanged and CF = 0
 send_byte:
 	push hl
 	ld l,a
@@ -746,29 +808,58 @@ send_byte:
 	pop hl
 	ret
 
-	;; Send a buffer HL->data BC=count
-	;; On return HL advanced, BC=0, A clobbered
+	;; Send a buffer HL->data, BC=count
+	;; On return HL advanced, BC=0, AF clobbered
+	;; and ram_csum updated
+	;;
+	;; This assumes the interface is either fast enough or
+	;; buffered enough that it is not necessary to wait for
+	;; tx space after each individual transmit.
 	;;
-	; XXX: USB is fast enough that INIR/OTIR should be possible
 send_buf:
-	ld a,b
-	or c
+	ld a,c
+	or b
 	ret z
-	ld a,(hl)
-	call send_byte
-	dec bc
-	inc hl
-	jr send_buf
+	push de
+	in a,(1)
+	and 2
+	call z,wait_for_tx
+	ld a,(ram_csum)
+	ld d,b			; High part of byte count
+	inc d			; To be able to use ZF after DEC
+	ld b,c			; Low part of byte count
+	ld c,0			; Port
+1:
+	add a,(hl)		; Update checksum
+	outi			; Send byte, update B, HL
+	jr nz,1b		; ZF = 1 if last iteration
+
+	dec d			; Additional 256-byte blocks?
+	jr nz,1b
+
+	ld (ram_csum),a
+	pop de
+	ret
 
-	;; Receive a byte.  Return with C flag on timeout.
+	;; Receive a byte into A. On timeout bail to ERR 42.
+	;; Always returns with CF=0.
 recv_byte:
-	;; Optimistically...
+	;; Optimistically, assume data is there already
 	in a,(1)
 	and 0Dh
 	cp 09h
 	call nz,wait_for_rx
-	in a,(0)		; Data immediately available
-	ret			; C=0 already
+	in a,(0)		; Read data
+	ret
+
+	;; Receive a word into HL. Clobbers A.
+	;; Always returns with CF=0.
+recv_word:
+	call recv_byte
+	ld l,a
+	call recv_byte
+	ld h,a
+	ret
 
 	;; This routine waits until the status bit given in A is zero;
 	;; if the the high bits of the status are anything other than
@@ -811,7 +902,7 @@ done4:
 	jp done
 
 send_endframe:
-	ld a,0EFh		; End of frame
+	ld a,NET_EOF		; End of frame
 	call send_byte
 	ld a,(ram_csum)
 	neg			; Total checksum = 0
@@ -878,9 +969,9 @@ prc_jptable:
 
 prc_print:
 	call select
-	ld a,0xFF
+	ld a,NET_SOF
 	call send_byte
-	ld a,0xc0
+	ld a,NET_CON
 	call send_byte
 
 prc_print_loop:
@@ -929,11 +1020,11 @@ init:
 	ld sp,hl
 	push hl
 
-	ld a,0xA9		; CLOSE ALL NO REPLY
+	ld a,NET_INIT
 	call send_cmd
 	call recv_reply
 
-	ld a,0xBA		; LIST VOLUMES
+	ld a,NET_LISTVOL
 	pop hl
 	push hl
 	ld bc,4*MAX_VOLS+1	; B=0
@@ -950,26 +1041,28 @@ init:
 
 	ld de,voldevs
 	;; Are we running with auxram on the stack?
-	bit 7,d
-	jr z,1f
+	.if use_stack
 	ld (STACK),de		; Move down the user stack
-1:
-mk_vols:
+	.endif
+
+mk_vols:			; B = 0 on entry here
 	ld a,(hl)
 	and a
-	jr z,link_volumes		; Done
+	jp z,done		; Done
+	;; Otherwise A = voltype
 	inc hl
 	push hl
-	ld hl,7
-	add hl,de
-	ex de,hl
+	ld l,e
+	ld h,d
+	ld de,(DEVLIST)
+	ld (DEVLIST),hl
 	ld (hl),e
 	inc hl
 	ld (hl),d
 	inc hl
 	ex de,hl
 	pop hl
-	ld bc,3			; Copy volume name
+	ld c,3			; Copy volume name
 	ldir
 
 	if pra_dev
@@ -988,19 +1081,6 @@ have_voltype:
 	inc de
 	jr mk_vols
 
-link_volumes:
-	;;  A = 0 here
-	ld hl,-7
-	add hl,de
-	ld de,(DEVLIST)
-	ld (hl),e
-	inc hl
-	ld (hl),d
-	ld hl,device_list
-	ld (DEVLIST),hl
-
-	jp done
-
 notforme:
 	ld a,128+52		; Ej till denna enhet
 	scf
@@ -1201,11 +1281,12 @@ e_cmd_space_overflow:
 
 	endif			; have_cmd
 
-	_device_link = voldevs
+	;; The value to put in the BASIC device link pointer
+device_list = 3000f
 
 	.macro device name:req, jptbl:req
-	defw _device_link
-	_device_link = . - 2
+3000:
+	defw 3000f
 	defm \name
 	defw \jptbl
 	.endm
@@ -1219,6 +1300,7 @@ xd_device:
 	device "XD2", DOSJPTABLE
 	defb 0x16
 	device "XD3", DOSJPTABLE
+	defb 0x17
 	endif
 
 	if console_dev
@@ -1238,9 +1320,6 @@ pr_device:
 	device "PR ", pr_jptable
 	endif
 
-	;; The value to put in the BASIC device link pointer
-device_list = _device_link
-
 	;; Jump table for BASIC functions that are inconsistent
 new_basic_jumps:		; Checksum 9913, 10042
 	if have_cmd
@@ -1276,6 +1355,7 @@ __end:
 	section .bss
 __bss:
 voldevs:
+3000:				; Part of the device linked list
 	defs 7*MAX_VOLS		; Up to 32 volume device entries
 errsp:
 	defs 2			; SP rollback on error return

+ 34 - 1
rv32/roms/asmsrc/abc80/ufddos.inc

@@ -5,6 +5,7 @@ defc DOSBUF0		= 64786	    ;; Pointer to DOSBUF 0
 defc DISKERR		= 64789	    ;; Drive error (if any)
 defc BCSAVE		= 64797	    ;; Register save area
 defc DOSDEFDEV		= 64821	    ;; DOS default device ("   ") in RAM
+defc DOSFD0		= 64832	    ;; DOS file descriptor table
 
 ;; DOS subroutines and pointers
 defc DCWAI		= 24672	    ;; Select drive
@@ -16,6 +17,38 @@ defc DRDWEND		= 25012	    ;; Driver hook exit (when claimed)
 defc DRDWERR		= 25011	    ;; Driver hook exit on error
 defc DGETBUF		= 25098	    ;; Get address of DOSBUF B[7:4]
 defc DOSJPTABLE		= 26195	    ;; Address for disk drive jump table
+
+;;
+;; Allocate a free DOSFD and DOSBUF (ERR 19 if all full)
+;; On exit:
+;; B = (IX+12) = DOS file no = DOSFD0 offset = DOS buf no << 4
+;; C = (HL)    = byte immediately after BASIC device list entry
+;; A = 0, CF = 0, ZF = 1 (XOR A)
+;;
+;; Other registers unchanged including prime registers
+;;
 defc DOSALLOCBUF	= 26100	    ;; Allocate a DOSBUF
+
+;;
+;; Initialize an IX map + DOSFD
+;;
+;; On entry:
+;; B = DOS file no
+;; On exit:
+;; (IX+12)   = B
+;; HL = (IX+8,9) = (IX+10,11) -> DOSBUF + 3 = DOSBUF0 + 3 + (B << 4)
+;; (HL)      = 3
+;; (IX+7)    = 132
+;; (IX+13)   = 252
+;; (IX+14)   = 0
+;; A = 0, CF = 0, ZF = 1 (XOR A)
+;;
+;; Other registers unchanged including prime registers
+;;
 defc DOSBUFINIT		= 26155	    ;; Initialize an IX map+DOS file descriptor
-defc DOSBUFREINIT	= 26159	    ;; Requires A = (ix+12), preserves BC
+
+;;
+;; Same, but takes DOS file no in A rather than B, and does not write (IX+12)
+;; Useful in that BC is preserved.
+;;
+defc DOSBUFREINIT	= 26159

+ 15 - 10
rv32/roms/asmsrc/abc80/ufddos80.asm

@@ -1255,7 +1255,11 @@ setup_stack:	pop de			; Copy return address
                 ret c                   ; 6590 .    d8
                 ld (BASICERR),a         ; 6591 2..  32 0f fe
                 ld (_DOSBUF1+3),a       ; 6594 2..  32 03 f6
-                jp autostart_setup      ; 6597 .=h  c3 3d 68
+		ret
+		;; Unreachable
+		rst 56
+		rst 56
+
 .L659a:         ;; 659a <- 6582 65ea
                 ld (DOSERRDEF),hl       ; 659a "3.  22 33 fd
                 ld hl,F0_DRVSEL         ; 659d !A.  21 41 fd
@@ -1680,12 +1684,14 @@ find_string:    ;; 67fb <- 67e3
                 pop de                  ; 6813 .    d1
                 ld sp,hl                ; 6814 .    f9
                 ret                     ; 6815 .    c9
+
 setup_memvars:
 		;; Called with HL = _DOSBUF0
                 ld (DOSBUFS),hl         ; 6819 "..  22 12 fd
 		ld hl,STACK_BASE
 		ld (STACK),hl
-		ret                     ; 681c .    c9
+		ret
+
 try_init_rom:   ;; 681d <- 6869
 		;; L = 0x4a on entry
 		ld c,(hl)		; 0x3d = DEC A - used as magic number
@@ -1713,12 +1719,7 @@ tmpixmap:       ;; 682b <- 67ac 67b5 67da
                 add hl,sp               ; 683a 9    39
                 ld sp,hl                ; 683b .    f9
                 ret                     ; 683c .    c9
-autostart_setup: ;; 683d <- 6597
-                ld hl,autostart_cmd     ; 683d !.o  21 9b 6f
-                ld de,LINE_BUF          ; 6840 .@.  11 40 fe
-                ld bc,autostart_cmd_len ; 6843 ...  01 14 00
-                ldir                    ; 6846 ..   ed b0
-                ret                     ; 6848 .    c9
+
 autostart:      ;; 6849 <- 686f
 		ld hl,(STACK)
 		ld sp,hl
@@ -1726,8 +1727,12 @@ autostart:      ;; 6849 <- 686f
                 call S_SCRATCH          ; 6849 .p.  cd 70 0a
                 call S_CHECKCTRLC       ; Clears ctrl-C, returns with A = 0
 		ld (iy+14),1            ; Command mode
-                ld hl,LINE_BUF          ; 6854 !@.  21 40 fe
-                jp S_RUNCMD		; 6858 ...  c2 f4 00
+		ld hl,autostart_cmd	; 6854 !@.  21 40 fe
+		bit 0,(iy-7)		; Only autostart if BASICERR.SYS open
+		jp z,S_NEW		; Otherwise NEW
+		jp S_RUNCMD		; 6858 ...  c2 f4 00
+
+		.org 0x85e, 0xff
 _INIT80:        ;; 685e <- 604b
                 ld (iy+42),0            ; 685e .6*. fd 36 2a 00
                 call dosinit80          ; 6862 .Ce  cd 43 65