Visual 1050 CP/M 3.0 Source Code

These are the CP/M 3.0 source files with modifications by Visual to operate on the Visual 1050.

BIOSKRNL.ASM  BOOT.ASM  BUF.LIB  CALLVERS.ASM  CHARIO.ASM  CPM3.LIB  DRIVES.ASM  DRVTBL.ASM  ECHOVERS.ASM  ENDER.ASM  INTERRUP.ASM  LABEL.ASM  LDRBOOT.ASM  LDRDRV.ASM  LDRKRNL.ASM  LDRMOVE.ASM  LDRTBL.ASM  MODEBAUD.LIB  MOVE.ASM  PORTS.LIB  PRIVATE.ASM  RANDOM.ASM  SCB.ASM  VISLIB.LIB  Z80.LIB 

BIOSKRNL.ASM

	title	'Root module of relocatable BIOS for CP/M 3.0'

	; version 1.0 15 Sept 82

true	equ -1
false	equ not true

banked	equ true 
	

;		  Copyright (C), 1982
;		 Digital Research, Inc
;		     P.O. Box 579
;		Pacific Grove, CA  93950


;   This is the invariant portion of the modular BIOS and is
;	distributed as source for informational purposes only.
;	All desired modifications should be performed by
;	adding or changing externally defined modules.
;	This allows producing "standard" I/O modules that
;	can be combined to support a particular system 
;	configuration.

cr	equ 13
lf	equ 10
bell	equ 7
ctlQ	equ 'Q'-'@'
ctlS	equ 'S'-'@'

ccp	equ 0100h	; Console Command Processor gets loaded into the TPA

	cseg		; GENCPM puts CSEG stuff in common memory


    ; variables in system data page

	extrn @covec,@civec,@aovec,@aivec,@lovec ; I/O redirection vectors
	extrn @mxtpa				; addr of system entry point
	extrn @bnkbf				; 128 byte scratch buffer

    ; initialization

	extrn ?init			; general initialization and signon
	extrn ?ldccp,?rlccp		; load & reload CCP for BOOT & WBOOT

    ; private Bios calls

	extrn	privcall

    ; user defined character I/O routines

	extrn ?ci,?co,?cist,?cost	; each take device in <B>
	extrn ?cinit			; (re)initialize device in <C>
	extrn @ctbl			; physical character device table

    ; disk communication data items

	extrn @dtbl			; table of pointers to XDPHs
	public @adrv,@rdrv,@trk,@sect	; parameters for disk I/O
	public @dma,@dbnk,@cnt		;    ''       ''   ''  ''

    ; memory control

	public @cbnk			; current bank
	extrn ?xmove,?move		; select move bank, and block move
	extrn ?bank			; select CPU bank

    ; clock support

	extrn ?time			; signal time operation

    ; general utility routines

	public ?pmsg,?pdec	; print message, print number from 0 to 65535
	public ?pderr		; print BIOS disk error message header

	maclib modebaud		; define mode bits


    ; External names for BIOS entry points

	public ?boot,?wboot,?const,?conin,?cono,?list,?auxo,?auxi
	public ?home,?sldsk,?sttrk,?stsec,?stdma,?read,?write
	public ?lists,?sctrn
	public ?conos,?auxis,?auxos,?dvtbl,?devin,?drtbl
	public ?mltio,?flush,?mov,?tim,?bnksl,?stbnk,?xmov


    ; BIOS Jump vector.

		; All BIOS routines are invoked by calling these
		;	entry points.

?boot:	jmp boot	; initial entry on cold start
?wboot:	jmp wboot	; reentry on program exit, warm start

?const:	jmp const	; return console input status
?conin:	jmp conin	; return console input character
?cono:	jmp conout	; send console output character
?list:	jmp list	; send list output character
?auxo:	jmp auxout	; send auxilliary output character
?auxi:	jmp auxin	; return auxilliary input character

?home:	jmp home	; set disks to logical home
?sldsk:	jmp seldsk	; select disk drive, return disk parameter info
?sttrk:	jmp settrk	; set disk track
?stsec:	jmp setsec	; set disk sector
?stdma:	jmp setdma	; set disk I/O memory address
?read:	jmp read	; read physical block(s)
?write:	jmp write	; write physical block(s)

?lists:	jmp listst	; return list device status
?sctrn:	jmp sectrn	; translate logical to physical sector

?conos:	jmp conost	; return console output status
?auxis:	jmp auxist	; return aux input status
?auxos:	jmp auxost	; return aux output status
?dvtbl:	jmp devtbl	; return address of device def table
?devin:	jmp ?cinit	; change baud rate of device

?drtbl:	jmp getdrv	; return address of disk drive table
?mltio:	jmp multio	; set multiple record count for disk I/O
?flush:	jmp flush	; flush BIOS maintained disk caching

?mov:	jmp ?move	; block move memory to memory
?tim:	jmp ?time	; Signal Time and Date operation
?bnksl:	jmp bnksel	; select bank for code execution and default DMA
?stbnk:	jmp setbnk	; select different bank for disk I/O DMA operations.
?xmov:	jmp ?xmove	; set source and destination banks for one operation

?priv	jmp privcall	; Reserved for system implementor

	jmp 0		; reserved for future expansion
	jmp 0		; reserved for future expansion


	; BOOT
	;	Initial entry point for system startup.

	dseg	; this part can be banked

boot:
	lxi sp,boot$stack
	mvi c,15	; initialize all 16 character devices
c$init$loop:
	push b ! call ?cinit ! pop b
	dcr c ! jp c$init$loop

	call ?init	; perform any additional system initialization
			; and print signon message

	lxi b,16*256+0 ! lxi h,@dtbl	; init all 16 logical disk drives
d$init$loop:
	push b		; save remaining count and abs drive
	mov e,m ! inx h ! mov d,m ! inx h	; grab @drv entry
	mov a,e ! ora d ! jz d$init$next	; if null, no drive
	push h					; save @drv pointer 
	xchg					; XDPH address in <HL>
	dcx h ! dcx h ! mov a,m ! sta @RDRV	; get relative drive code
	mov a,c ! sta @ADRV			; get absolute drive code
	dcx h					; point to init pointer
	mov d,m ! dcx h ! mov e,m		; get init pointer
	xchg ! call ipchl			; call init routine
	pop h					; recover @drv pointer
d$init$next:
	pop b					; recover counter and drive #
	inr c ! dcr b ! jnz d$init$loop		; and loop for each drive
	jmp boot$1

	cseg	; following in resident memory

boot$1:
	call set$jumps
	call ?ldccp				; fetch CCP for first time
	jmp ccp


	; WBOOT
	;	Entry for system restarts.

wboot:
	lxi sp,boot$stack
	call set$jumps		; initialize page zero
	call ?rlccp		; reload CCP
	jmp ccp			; then reset jmp vectors and exit to ccp


set$jumps:

  if banked
	mvi a,1 ! call ?bnksl
  endif

	mvi a,JMP
	sta 0 ! sta 5		; set up jumps in page zero
	lxi h,?wboot ! shld 1	; BIOS warm start entry
	lhld @MXTPA ! shld 6	; BDOS system call entry
	ret


		ds 64
boot$stack	equ $


	; DEVTBL
	;	Return address of character device table

devtbl:
	lxi h,@ctbl ! ret


	; GETDRV
	;	Return address of drive table

getdrv:
	lxi h,@dtbl ! ret



	; CONOUT
	;	Console Output.  Send character in <C>
	;			to all selected devices

conout:	

	lhld @covec	; fetch console output bit vector
	jmp out$scan


	; AUXOUT
	;	Auxiliary Output. Send character in <C>
	;			to all selected devices

auxout:
	lhld @aovec	; fetch aux output bit vector
	jmp out$scan


	; LIST
	;	List Output.  Send character in <C>
	;			to all selected devices.

list:
	lhld @lovec	; fetch list output bit vector

out$scan:
	mvi b,0		; start with device 0
co$next:
	dad h		; shift out next bit
	jnc not$out$device
	push h		; save the vector
	push b		; save the count and character
not$out$ready:
	call coster ! ora a ! jz not$out$ready
	pop b ! push b	; restore and resave the character and device
	call ?co	; if device selected, print it
	pop b		; recover count and character
	pop h		; recover the rest of the vector
not$out$device:
	inr b		; next device number
	mov a,h ! ora l	; see if any devices left
	jnz co$next	; and go find them...
	ret


	; CONOST
	;	Console Output Status.  Return true if
	;		all selected console output devices
	;		are ready.

conost:
	lhld @covec	; get console output bit vector
	jmp ost$scan


	; AUXOST
	;	Auxiliary Output Status.  Return true if
	;		all selected auxiliary output devices
	;		are ready.

auxost:
	lhld @aovec	; get aux output bit vector
	jmp ost$scan


	; LISTST
	;	List Output Status.  Return true if
	;		all selected list output devices
	;		are ready.

listst:
	lhld @lovec	; get list output bit vector

ost$scan:
	mvi b,0		; start with device 0
cos$next:
	dad h		; check next bit
	push h		; save the vector
	push b		; save the count
	mvi a,0FFh	; assume device ready
	cc coster	; check status for this device
	pop b		; recover count
	pop h		; recover bit vector
	ora a		; see if device ready
	rz		; if any not ready, return false
	inr b		; drop device number
	mov a,h ! ora l	; see if any more selected devices
	jnz cos$next
	ori 0FFh	; all selected were ready, return true
	ret

coster:		; check for output device ready, including optional
		;	xon/xoff support
	mov l,b ! mvi h,0	; make device code 16 bits
	push h			; save it in stack
	dad h ! dad h ! dad h	; create offset into device characteristics tbl
	lxi d,@ctbl+6 ! dad d	; make address of mode byte
	mov a,m ! ani mb$xonxoff
	pop h			; recover console number in <HL>
	jz ?cost		; not a xon device, go get output status direct
	lxi d,xofflist ! dad d	; make pointer to proper xon/xoff flag
	call cist1		; see if this keyboard has character
	mov a,m ! cnz ci1	; get flag or read key if any
	cpi ctlq ! jnz not$q	; if its a ctl-Q,
	mvi a,0FFh 		;	set the flag ready
not$q:
	cpi ctls ! jnz not$s	; if its a ctl-S,
	mvi a,00h		;	clear the flag
not$s:
	mov m,a			; save the flag
	call cost1		; get the actual output status,
	ana m			; and mask with ctl-Q/ctl-S flag
	ret			; return this as the status

cist1:			; get input status with <BC> and <HL> saved
	push b ! push h 
	call ?cist
	pop h ! pop b
	ora a
	ret

cost1:			; get output status, saving <BC> & <HL>
	push b ! push h
	call ?cost
	pop h ! pop b
	ora a
	ret

ci1:			; get input, saving <BC> & <HL>
	push b ! push h
	call ?ci
	pop h ! pop b
	ret


	; CONST
	;	Console Input Status.  Return true if
	;		any selected console input device
	;		has an available character.

const:
	lhld @civec	; get console input bit vector
	jmp ist$scan


	; AUXIST
	;	Auxiliary Input Status.  Return true if
	;		any selected auxiliary input device
	;		has an available character.

auxist:
	lhld @aivec	; get aux input bit vector

ist$scan:
	mvi b,0		; start with device 0
cis$next:
	dad h		; check next bit
	mvi a,0		; assume device not ready
	cc cist1	; check status for this device
	ora a ! rnz	; if any ready, return true
	inr b		; drop device number
	mov a,h ! ora l	; see if any more selected devices
	jnz cis$next
	xra a		; all selected were not ready, return false
	ret


	; CONIN
	;	Console Input.  Return character from first
	;		ready console input device.

conin:
	lhld @civec
	jmp in$scan


	; AUXIN
	;	Auxiliary Input.  Return character from first
	;		ready auxiliary input device.

auxin:
	lhld @aivec

in$scan:
	push h		; save bit vector
	mvi b,0
ci$next:
	dad h		; shift out next bit
	mvi a,0		; insure zero a  (nonexistant device not ready).
	cc cist1	; see if the device has a character
	ora a
	jnz ci$rdy	; this device has a character
	inr b		; else, next device
	mov a,h ! ora l	; see if any more devices
	jnz ci$next	; go look at them
	pop h		; recover bit vector
	jmp in$scan	; loop til we find a character

ci$rdy:
	pop h		; discard extra stack
	jmp ?ci


;	Utility Subroutines


ipchl:		; vectored CALL point
	pchl


?pmsg:		; print message @<HL> up to a null
		; saves <BC> & <DE>
	push b
	push d
pmsg$loop:
	mov a,m ! ora a ! jz pmsg$exit
	mov c,a ! push h
	call ?cono ! pop h
	inx h ! jmp pmsg$loop
pmsg$exit:
	pop d
	pop b
	ret

?pdec:		; print binary number 0-65535 from <HL>
	lxi b,table10! lxi d,-10000
next:
	mvi a,'0'-1
pdecl:
	push h! inr a! dad d! jnc stoploop
	inx sp! inx sp! jmp pdecl
stoploop:
	push d! push b
	mov c,a! call ?cono
	pop b! pop d
nextdigit:
	pop h
	ldax b! mov e,a! inx b
	ldax b! mov d,a! inx b
	mov a,e! ora d! jnz next
	ret

table10:
	dw	-1000,-100,-10,-1,0

?pderr:
	lxi h,drive$msg ! call ?pmsg			; error header
	lda @adrv ! adi 'A' ! mov c,a ! call ?cono	; drive code
	lxi h,track$msg ! call ?pmsg			; track header
	lhld @trk ! call ?pdec				; track number
	lxi h,sector$msg ! call ?pmsg			; sector header
	lhld @sect ! call ?pdec				; sector number
	ret


	; BNKSEL
	;	Bank Select.  Select CPU bank for further execution.

bnksel:
	sta @cbnk 			; remember current bank
	jmp ?bank			; and go exit through users
					; physical bank select routine


xofflist	db	-1,-1,-1,-1,-1,-1,-1,-1		; ctl-s clears to zero
		db	-1,-1,-1,-1,-1,-1,-1,-1



	dseg	; following resides in banked memory



;	Disk I/O interface routines


	; SELDSK
	;	Select Disk Drive.  Drive code in <C>.
	;		Invoke login procedure for drive
	;		if this is first select.  Return
	;		address of disk parameter header
	;		in <HL>

seldsk:
	mov a,c ! sta @adrv			; save drive select code
	mov l,c ! mvi h,0 ! dad h		; create index from drive code
	lxi b,@dtbl ! dad b			; get pointer to dispatch table
	mov a,m ! inx h ! mov h,m ! mov l,a	; point at disk descriptor
	ora h ! rz 				; if no entry in table, no disk
	mov a,e ! ani 1 ! jnz not$first$select	; examine login bit
	push h ! xchg				; put pointer in stack & <DE>
	lxi h,-2 ! dad d ! mov a,m ! sta @RDRV	; get relative drive
	lxi h,-6 ! dad d			; find LOGIN addr
	mov a,m ! inx h ! mov h,m ! mov l,a	; get address of LOGIN routine
	call ipchl				; call LOGIN
	pop h					; recover DPH pointer
not$first$select:
	ret


	; HOME
	;	Home selected drive.  Treated as SETTRK(0).

home:
	lxi b,0		; same as set track zero


	; SETTRK
	;	Set Track. Saves track address from <BC> 
	;		in @TRK for further operations.

settrk:
	mov l,c ! mov h,b
	shld @trk
	ret


	; SETSEC
	;	Set Sector.  Saves sector number from <BC>
	;		in @sect for further operations.

setsec:
	mov l,c ! mov h,b
	shld @sect
	ret


	; SETDMA
	;	Set Disk Memory Address.  Saves DMA address
	;		from <BC> in @DMA and sets @DBNK to @CBNK
	;		so that further disk operations take place
	;		in current bank.

setdma:
	mov l,c ! mov h,b
	shld @dma

	lda @cbnk	; default DMA bank is current bank
			; fall through to set DMA bank

	; SETBNK
	;	Set Disk Memory Bank.  Saves bank number
	;		in @DBNK for future disk data
	;		transfers.

setbnk:
	sta @dbnk
	ret


	; SECTRN
	;	Sector Translate.  Indexes skew table in <DE>
	;		with sector in <BC>.  Returns physical sector
	;		in <HL>.  If no skew table (<DE>=0) then
	;		returns physical=logical.

sectrn:
	mov l,c ! mov h,b
	mov a,d ! ora e ! rz
	xchg ! dad b ! mov l,m ! mvi h,0
	ret


	; READ
	;	Read physical record from currently selected drive.
	;		Finds address of proper read routine from
	;		extended disk parameter header (XDPH).

read:
	lhld @adrv ! mvi h,0 ! dad h	; get drive code and double it
	lxi d,@dtbl ! dad d		; make address of table entry
	mov a,m ! inx h ! mov h,m ! mov l,a	; fetch table entry
	push h				; save address of table
	lxi d,-8 ! dad d		; point to read routine address
	jmp rw$common			; use common code


	; WRITE
	;	Write physical sector from currently selected drive.
	;		Finds address of proper write routine from
	;		extended disk parameter header (XDPH).

write:
	lhld @adrv ! mvi h,0 ! dad h	; get drive code and double it
	lxi d,@dtbl ! dad d		; make address of table entry
	mov a,m ! inx h ! mov h,m ! mov l,a	; fetch table entry
	push h				; save address of table
	lxi d,-10 ! dad d		; point to write routine address

rw$common:
	mov a,m ! inx h ! mov h,m ! mov l,a	; get address of routine
	pop d				; recover address of table
	dcx d ! dcx d			; point to relative drive
	ldax d ! sta @rdrv		; get relative drive code and post it
	inx d ! inx d			; point to DPH again
	pchl				; leap to driver


	; MULTIO
	;	Set multiple sector count. Saves passed count in
	;		@CNT

multio:
	sta @cnt ! ret


	; FLUSH
	;	BIOS deblocking buffer flush.  Not implemented.

flush:
	xra a ! ret		; return with no error



	; error message components
drive$msg	db	cr,lf,bell,'BIOS Error on ',0
track$msg	db	': T-',0
sector$msg	db	', S-',0


    ; disk communication data items

@adrv	ds	1		; currently selected disk drive
@rdrv	ds	1		; controller relative disk drive
@trk	ds	2		; current track number
@sect	ds	2		; current sector number
@dma	ds	2		; current DMA address
@cnt	db	0		; record count for multisector transfer
@dbnk	db	0		; bank for DMA operations


	cseg	; common memory

@cbnk	db	0		; bank for processor operations


	end
BOOT.ASM
	title	'Boot loader module for CP/M 3.0'
	
	maclib	vislib
	maclib	buf
	maclib modebaud
	maclib ports
	maclib	z80


	public	?init,?ldccp,?rlccp,?time
	public  nint, ivect ,empty$ptr    

	extrn	?pmsg,?conin
	extrn	@civec,@covec,@aivec,@aovec,@lovec
	extrn 	@cbnk,?bnksl
	extrn	aux$in$ptr, aux$out$ptr, kb$buf$in,dsp$buf$in
	extrn	rsint, kint, firq, vert$int, dspint
	extrn	@date,@hour,@min,@sec
	extrn	kmodei

bdos 	equ	5

	if banked
tpa$bank	equ 1
	else
tpa$bank	equ 0
	endif

	dseg	; init done from banked memory
?init:
	di					; disable interrupts
	lxi h,08000h 				; hl <= device 0
	shld @covec 				; DISPLY = console output

	lxi h,04000h 				; hl <= device 1
	shld @aivec 				; AUX = auxiliary input 
	shld @aovec				; AUX = auxiliary output

	lxi h,2000h				; hl <= device 2
	shld @civec				; KB = console input

	lxi h,1000h				; hl <= device 3
	shld @lovec				; LPT = Centronics parallel ptr

; Set up interrupt vectors.  Begin by pointing them all at a null
; interrupt routine so that every interrupt is satisfied in some way.
;

	lxi d,nint				; get address of null vector
 	lxi h,ivect				; point to ivect table
ini$vec:
	mov m,e           			; store low byte of NINT
	inr l					; increment hl
	mov m,d       				; store hi byte of NINT
	inr l					; increment hl
	jrnz ini$vec				; do for all

;
; Set up interrupt mode 2 and select page
;
	IF	REAL$1050
	mvi	a,ivect/256			; get address of ivect
	dw	47EDH				; "LD I,A"
	dw	05eedh				; "IM2"
	ENDIF
;
; Set up the interrupts that are implemented
;

intset	lxi h,firq				; Floppy completion
	IF	REAL$1050
	shld	ivect+08
	ELSE
	shld ivect+2				; Point to vector
	ENDIF

	lxi h,kint				; Keyboard interrupt
	IF	REAL$1050
	shld	ivect+10
	ELSE
	shld ivect+4				; Point to vector
	ENDIF

	lxi h,rsint				; RS232 interrupt
	IF	REAL$1050
	shld	ivect+14
	ELSE
	shld ivect+16				; Point to vector
	ENDIF

	IF	REAL$1050			; display interrupt
	lxi	h,dspint			; (from 6502 side)
	shld	ivect+04			;

	lxi     h,vert$int			; Vertical retrace int
	shld	ivect+06

	ENDIF

;
; Initialize interrupt buffers
;

	lxix aux$in$ptr				; Point to aux input buff
	call empty$ptr				; fix pointers to empty

	lxix aux$out$ptr			; Point to aux output buff
	call empty$ptr				; fix pointers to empty

	lxix kb$buf$in				; Point to kbd buffer
	call empty$ptr				; fix pointers to empty

	lxix dsp$buf$in				; Point to display input
	call	empty$ptr			; fix pointers to empty

	IF	REAL$1050

	mvi	a,int$mask			; Get interrupt mask
	out	p$clk$portb			; Send  out

	mvi	a,int$initial			; Initial value
	out	int$port			; to int port
	ENDIF
	ei					; reenable interrupts

;
; Put up sign on message
;

	lxi h,signon$msg			; point to sign on msg
	call ?pmsg				; print it out
	ret	


;
; Routine Empty$ptr
;
; "Empties" buffer by pointing empty and fill pointers to same 
; location in buffer.
;
empty$ptr:
	xra a					; Clear A
	stx a,buf$empty			; store in empty ptr
	stx a,buf$fill				; and fill ptr
	ret



	page

	cseg	; boot loading most be done from resident memory
    ;	This version of the boot loader loads the CCP from a file
    ;	called CCP.COM on the system drive (A:).
?ldccp:
 
; Set up the FCB                                  
;

	xra a 
	sta ccp$fcb+15		; zero extent
	sta ccp$fcb+12		; Zero ex field
	sta ccp$fcb+32		; Zero cr field
	lxi	d,ccp$fcb	; Point to FCB

	call open		; open file 

	inr	a
	jrz no$ccp  		; If not found, check again
;
; File found.  Load into 100h.
;
	lxi d,0100h 
	call setdma		;start of TPA
	lxi d,128		;
	call setmulti		;Read 128 rec  at a time
	lxi d,ccp$fcb 
	call read		;load the thing
	IF     BANKED
;
; Now, Copy CCP to bank to bank 2 for reloading 
;
	lxi h,0100h 
	lxi b,1000h		; move 4K
	lda @cbnk 
	push psw		; save current bank
ld$1:
	mvi a,tpa$bank 
	call ?bnksl		; select TPA
	mov a,m 
	push psw		; get a byte
	mvi a,2 
	call ?bnksl		; select extra bank
	pop psw 
	mov m,a			; save the byte

	inx h 
	dcx b			; bump pointer, drop count
	mov a,b 
	ora c			; test for done
	jrnz ld$1
	pop psw 
	call ?bnksl		; restore original bank
	ENDIF
ldccp$exit:

	ret



;

no$CCP:			; here if we couldn't find the file
	lxi h,ccp$msg 
	call ?pmsg	; report this...
	call ?conin			; get a response
	jmp  ?ldccp			; and try again
?rlccp:
	IF    	BANKED
	lxi h,0100h 
	lxi b,1000h		; Moving in 4k from bank 2
rl$1:
	mvi a,2 
	call ?bnksl		; select extra bank
	mov a,m 
	push psw		; get a byte
	mvi a,tpa$bank 
	call ?bnksl	; select TPA
	pop psw 
	mov m,a		; save the byte

	inx h 
	dcx b			; bump pointer, drop count
	mov a,b 
	ora c			; test for done
	jrnz rl$1
	ret
	ELSE
	jmp	?ldccp
	ENDIF


	IF REAL$1050

	dseg

;
; This routine is called whenever the BDOS wants to either read
; or change the date and time.  On entry, if C=0, a read is
; requested.  If C=0FFH, a write is requested.  DE and HL must
; be preserved.
;
?time:
	push	h		; Save h
	push	d		; and d
	mov	a,c		; Get entry switch
	ora	a		; Is it 0?
	jnz	time$set	; No.  Check if setting time
;
; Requesting read of time and date
; First set up fields for SCB.
;

time$20:

;
; Get date from RTC.  Start with year.
;

	mvi	a,0bh		; Getting Y1
	call	get$data	;
	jrc	time$20		; If change, try again
	mov	l,c		; Move to L

	mvi	a,0ch		; Get Y10
	call	get$data	;
	jrc	time$20		; If changed, do again
	mov	h,c		; move to h
	
	call	bcd$to$hex	; Convert to hex
	sta	year		; store year

;
; Get month.
;
	mvi	a,09h		; Getting M1
	call	get$data	;
	jrc	time$20		; If change, try again
	mov	l,c		; Move to L

	mvi	a,0Ah		; Get M10
	call	get$data	;
	jrc	time$20		; If changed, do again
	mov	h,c		; move to h
	
	call	bcd$to$hex	; Convert to hex
	sta	month		; store month

;
; Get day.
;

	mvi	a,07h		; Getting D1
	call	get$data	;
	jrc	time$20		; If change, try again
	mov	l,c		; Move to L

	mvi	a,08h		; Get D10
	call	get$data	;
	jrc	time$20		; If changed, do again
	mov	h,c		; move to h
	
	call	bcd$to$hex	; Convert to hex
	sta	day 		; store day 

;
; Get hours  
;

	mvi	a,04h		; Get H1                 
	call	getdata		; Get it
	jrc	time$20		; Jump if changed
	mov	b,c		; Save in B register
	mvi	a,05h		; Get H10
	call	getdata		; 
	jrc	time$20		; Jump if changed
	mov	a,c		; Get H10
	ani	03h		; Low 2 bits only
	mov	c,a		; Put back into C
	call	pack$word	; Pack into word
	sta	@hour		; Store hour

;
; Get minutes
;

	mvi	a,02h		; Get M1                 
	call	getdata		; Get it
	jrc	time$20		; Jump if changed
	mov	b,c		; Save in B register
	mvi	a,03h		; Get M10
	call	getdata		; 
	jrc	time$20		; Jump if changed
	call	pack$word	; Put it in
	sta 	@min		; store minutes

;
; Get seconds
;

	mvi	a,0		; Get S1                 
	call	getdata		; Get it
	jrc	time$20		; Jump if changed
	mov	b,c		; Save in B register
	mvi	a,1		; Get S10
	call	getdata		; 
	jc	time$20		; Jump if changed
	call	pack$word	; pack into word
	sta	@sec		; store minutes

;
; Now, compute the number of days since 1 Jan 78.
;
	mvi	a,2		; 1978 is not leap year
	sta	leap		; so start leap count at 2

	lxi	h,0		; Initialize hl for # days
	lda	year		; Get year
	sui	78		; minus 78
	jm	time$exit 	; if less, error
	jrz	time$50		; Jump if zero
	push	psw		; save year count


time$30:
	lxi	d,365		; # days in normal year
	lda	leap		; Get leap count
	cpi	4		; Leap year?
	jrnz	time$40		; Jump if not

	inx	d    		; 366 days in a leap year
	xra	a  		; reinit leap count

time$40:
	dad	d		; add # days in year
	inr	a		; Inc leap count
	sta	leap		; store new leap count

	pop	psw		; Get year count
	dcr	a		; decrement
	jrz	time$50		; jump if zero
	push	psw		; else, save year count
	jr	time$30		; and loop again

time$50:
	lda	month		; Get month
	dcr	a		; minus 1
	jrz	time$70		; Jump if January

	dcr	a		; Else, decrement
	push h			; save # days so far
	lxi	h,month$table	; Point to month table
	mov	e,a		; move month to E
	xra	a		;
	mov	d,a		; Move 0 to D
	dad	d		; Add to beginning of table
	dad	d		; (Twice for word entries)
	mov     e,m		; Load DE with entry
	inx	h		;
	mov	d,m		;
	pop	h		; Restore days so far
	dad	d		; Add days in preceding months

;
; If year is a leap year and month is March or later, add 1 to
; number of days.
;

	lda	leap		; Get leap count
	cpi	4		; Leap year?
	jrnz	time$70		; Jump if not  

	lda	month		; Get month
	sui	3		; March or >?
	jm	time$70		; Jump if no
	inx	h		; Else, add 1 day

;
; Add in day of month
;

time$70:
	lda	day		; Get day of month
	mov	e,a		; Move to E 
	mvi	d,0		; Clear D
	dad	d		; add to date so far

;
; Update field in SCB
;

	shld	@date 		; Store SPB value
	jmp	time$exit	; and exit
;
; Pack 2 bytes into BCD word
;
pack$word:
	mov	a,c		; Get into A
	ral			; Rotate into high byte
	ral			;
	ral			;
	ral			;
	ora	b		; OR in w/H1
	ret			;

;
; Set clock using values in SPB.
;

time$set:

;
; Get hour from spb.
;

	lda	@hour		; Get hour
	push	psw		; save it
	ani	0fh		; Clear hi bits
	mov	c,a		; move to C-reg
	mvi	a,4		; Send H1
	call    put$data	;

	pop	psw		; Get hour again
	rar			; rotate into low byte
	rar			;
	rar			;
	rar			;
	ani	0fh		; Clear hi bits
	ori	08h		; Set 24 hour clock
	mov	c,a		; move to C-reg
	mvi	a,5		; Send H10
	call	put$data	;

;
; Set minutes.
;

	lda	@min		; Get minutes
	push	psw		; save it
	ani	0fh		; Clear hi bits
	mov	c,a		; move to C-reg
	mvi	a,2		; Send M1
	call    put$data	;
	pop	psw		; Get mins again

	rar			; rotate into low byte
	rar			;
	rar			;
	rar			;
	ani	0fh		; Clear hi bits
	mov	c,a		; move to C-reg
	mvi	a,3		; Send M10
	call	put$data	;

;
; Set seconds.
;

	lda	@sec		; Get seconds
	push	psw		; save it
	ani	0fh		; Clear hi bits
	mov	c,a		; move to C-reg
	mvi	a,0		; Send S1
	call    put$data	;
	pop	psw		; Get secs again
	rar			; rotate into low byte
	rar			;
	rar			;
	rar			;
	ani	0fh		; Clear hi bits
	mov	c,a		; move to C-reg
	mvi	a,1		; Send S10
	call	put$data	;

;
; Convert date in days since 1 Jan 78 to calendar date.
;

	lhld	@date		; Get date
	mvi	a,2		; Start leap count at 2
	sta	leap		;

	mvi	a,78		; Year starts at 78
	sta	year		;

time$80:
	push	h		; Save # days
	lda	leap		; Get leap count
	cpi	4		; Leap year?
	jrz	time$85		; Jump if yes

	inr	a		; Else, inc leap count
	lxi	d,365		; # days in normal year
	jr	time$87		;

time$85:
	mvi	a,1		; Reinit leap count
	lxi	d,366		; # days in leap year

time$87:
	ora	a		; Clear carry
	db	0edh,052h	; SBC HL,DE
	jm	time$90		; until negative
	jrz	time$90		; (or zero)

	sta	leap		; Store new LEAP value
	pop	d		; pop
	lda	year		; Get year count
	inr	a		; Increment it
	sta	year		; Store it again
	jr	time$80		; Loop

time$90:
	pop	h		; Restore day count
	shld	temp		; save it

;
; If this is a leap year, special considerations for Feb 29.
;

	lda	leap		; Get leap count 
	cpi	4		; Leap year?
	jrnz	time$91		; jump if not 

	xra	a		; Clear carry
	lxi	d,60		; Feb 29?
	db	0edh,052h	; Check against date
	jrz	time$98		; jump if zero
	jm	time$91		; No offset if date is <
	
	lhld	temp		; Else, offset by 1
	dcx	h		;
	shld	temp		;

time$91:
	mvi	b,001h		; Start month at 1
	mov	c,l		; Start # days
	lxi	h,month$table	;

Time$92:
	mov	e,m		; Get # days in month
	inx	h		; Increment
	mov	d,m		;
	inx	h		;

	push	h		; Save table pointer
	lhld	temp		; Get # days
	xra	a		; Clear carry
	db 	0edh,052h	; subtract
	jm	time$95		; Jump if negative
	jrz	time$95		; (or zero)

	mov	c,l		; Save # days in C-reg
	inr	b		; Increment month
	pop	h		; restore table ptr
	jr	time$92		; loop

time$95:
	mov	a,b		; Get month
	sta	month		; store

	lhld	temp		; Get # days
	mov	a,c		; Get day
	sta day			;

	pop	h		; Restore stack
	jr	time$125	;

time$98:
	mvi	a,2		; Month = Feb
	sta	month		;

	mvi	a,29		; Day = 29
	sta	day		;
	
time$125:

;
; Send year to RTC
;

	lda	year		; Get year
	call	hex$to$bcd	; Convert to BCD

	lda	ones		; Send Y1
	mov	c,a		;
	mvi	a,11		; 
	call	putdata		;

	lda	tens		; Send Y10
	mov	c,a		;
	mvi	a,12		;
	call	putdata		;

;
; Send month.
;

	lda	month		; Get month
	call	hex$to$bcd	; Convert to BCD

	lda	ones		; Send M1
	mov	c,a		;
	mvi	a,09		; 
	call	putdata		;

	lda	tens		; Send M10
	mov	c,a		;
	mvi	a,10		;
	call	putdata		;

;
; Send day.
;

	lda	day 		; Get day 
	call	hex$to$bcd	; Convert to BCD

	lda	ones		; Send D1
	mov	c,a		;
	mvi	a,07		; 
	call	putdata		;

	lda	tens		; Send D10
	mov	c,a		;
	mvi	a,08		;
	call	putdata		;


time$exit:
	di			; disable interrupts
	mvi	a,rtc$read	; Leave in READ state
	out	p$clk$control	;
	mvi	a,int$mask	; Set up int mask again
	out	p$clk$portb	;
	ei			;

	pop	d
	pop	h
	ret

; 
; This subroutine is called with bits 0-3 set up as address
; input.  Return w/C register = data.  Carry will be set if
; data changed on 2 successive reads.
;

get$data:
	push	psw		; Save Read address
	mvi	a,rtc$write	; Writing 
	di
	out	p$clk$control	; set port to out
	mvi	a,rtc$select	; device select
	out	p$clk$control	;
	
	pop	psw		; Restore read address
	out	p$clk$porta	; Send out address

	mvi	a,add$write$hi	; Set up address write
	out	p$clk$control	;

	mvi	a,add$write$lo	; Clear address write
	out	p$clk$control	;

	mvi	a,rtc$read	; Reading
	out	p$clk$control	; Set port to in

	mvi	a,rtc$select	; Chip select
	out	p$clk$control	;

	mvi	a,read$hi	; set data read high
	out 	p$clk$control	;

get$07:
	in	p$clk$portc	; Get status
	ani	0000$1000b	; Busy?
	jrz	get$07		; Loop till free

	in	p$clk$portA	; Get data
	ani	0Fh		; Clear hi bits
        
	mov	c,a		; Save in C-reg
	
	mvi	a,read$lo	; Set data read low
	out	p$clk$control	; 

	mvi	a,read$hi	; Set data read high
	out	p$clk$control	;

get$10:
	in	p$clk$portc	; Get status
	ani	0000$1000b	; Busy?
	jrz	get$10		; Loop till free

	in	p$clk$porta	; Get data again
	ani	0fh		; Clear hi bits
	cmp	c		; Data same as last?
	jrz	get$20		; Jump if yes    
	stc			; Else, set carry
get$20:
	mvi	a,read$lo	; Yes.  Set data read low
	out	p$clk$control	;
	
	mvi	a,int$mask	; Set up interrupt mask
	out	p$clk$portb	;

	mvi	a,int$initial	; Reinit int ports
	out	int$port	;

	ei			; reenable interrupts
	ret			;

;
; Write to RTC
;

put$data:

	push	psw		; Save address for write
	di			; Disable interrupts

	mvi	a,rtc$write	; Writing
	out	p$clk$control	; So set port to out
	mvi	a,rtc$select	; chip select
	out	p$clk$control	;

	pop	psw		; Restore write address
	out	p$clk$porta	; Send out address

	mvi	a,add$write$hi	; Set up address write
	out	p$clk$control	;

	mvi	a,add$write$lo	; Clear address write
	out	p$clk$control	;

	mvi	a,write$hi	; Set data write high
	out	p$clk$control	;

put$10:
	in	p$clk$portc	; Get status
	ani	0000$1000b	; Busy?
	jrz	put$10		; Loop till free

	mov	a,c		; Get data
	out	p$clk$porta	; write data

	mvi	a,write$lo	; 
	out	p$clk$control	;

	mvi	a,rtc$read	; Leave port as in
	out	p$clk$control	;

	mvi	a,int$mask	; Set up interrupt mask
	out	p$clk$portb	;

	mvi	a,int$initial	; Reinit int ports
	out	int$port	;

	ei			; reenable interrupts
	ret			;


;
; Enter with 10's digit in H, 1's digit in L.  
; Exit with hex number in A.
;

bcd$to$hex:
	mov	a,H		; Get 10's digit
	ral			; *2
	mov	d,a		; (save)
	ral			; *4
	ral			; *8
	add	d		; *10
	add	l		; + 1's digit
	ret			; it's that easy!

;
; Enter with # to be converted in A.
; Result in ONES and TENS.
;

hex$to$bcd:
	push	psw		; Save A
	xra	a		; Clear A
	lxi	h,tens		; Point to tens
	mov	m,a		; Clear TENS
	pop 	psw		; Restore A

hex$10:
	sui	10		; Subtract 10
	jm	hex$20		;

	inr	m		; Increment tens count
	jr	hex$10		;

hex$20:
	adi	10		; Add 10 back
	sta	ones		; Store result in ONES

	ret

year	ds	1
month	ds	1
day	ds	1
leap	ds	1
tens	ds	1
ones	ds	1
temp	ds	2

month$table:
	dw	31		; January
	dw	59		; February (non-leap)
	dw	90		; March
	dw	120		; April
	dw	151		; May
	dw	181		; June
	dw	212		; July
	dw	243		; August
	dw	273		; September
	dw	304		; October
	dw	334		; November

	ELSE
    ; No external clock.
?time:
	ret
	ENDIF
;
; Null interrupt handler
;
	cseg
NINT:
	IF REAL$1050
	push psw
	mvi	a,int$initial
	out	int$port
	pop psw
	ENDIF
	ei
	ret

	cseg
	; CP/M BDOS Function Interfaces

scbcall:
	mvi c,49		;Set/Get SCB 
	jmp bdos
open:
	mvi c,15 
	jmp bdos		; open file control block

setdma:
	mvi c,26 
	jmp bdos		; set data transfer address

setmulti:
	mvi c,44 
	jmp bdos		; set record count

read:
	mvi c,20 
	jmp bdos		; read records


signon$msg	db	13,10,13,10,'CP/M Version 3.0, BIOS version 1.0 '
		IF	BANKED   
		db	13,10,'***BANKED VERSION***'
		ENDIF
		db	27,';C'
		db	13,10,0

ccp$msg		db	13,10,'BIOS Err on '
ccp$drv		db	'A'
		db	': No '
		db	'CCP'
		db	'.COM file',0

ccp$fcb		db	01
destin		db     'CCP     ','COM',0,0,0,0
		ds	16
      		db	0,0,0

scbpb		db	06		; Offset to user flag
		db	00		; 0 to do a get operation
scb$val		dw	0		; (nothing)

	aseg
	IF	REAL$1050
	org 0fff0h
	ELSE
	org 0ffe0h
	ENDIF
ivect	ds	32		; 32-byte interrupt vector
	end
BUF.LIB
;
; Buffer data structure definitions:

buf$length	equ	0	; length of buf$buffer
buf$empty	equ	1	; offset of next char in buffer
buf$fill	equ	2	; offset of next free location
				; (empty=fill means buffer empty)
buf$buffer	equ	3	; start of buffer
CALLVERS.ASM
	; CALLVERS program

bdos	equ	5			; entry point for BDOS
prtstr	equ	9			; print string function
vers	equ	12			; get version function
cr	equ	0dh			; carriage return
lf	equ	0ah			; line feed

	org	100h
	mvi 	d,5			; Perform 5 times
loop:	push	d			; save counter
	mvi 	c,prtstr 
	lxi 	d,call$msg		; print call message
	call 	bdos
	mvi 	c,vers 
	call 	bdos			; try to get version #
					; CALLVERS will intercept
	mov 	a,l 
	sta	curvers
	pop 	d
	dcr 	d			; decrement counter
	jnz 	loop
	mvi 	c,0
	jmp 	bdos
call$msg:
	db	cr,lf,'**** CALLVERS **** $'
curvers	db	0
	end
CHARIO.ASM
     title 'Character I/O handler '

; CHARIO.ASM
;  Character I/O for the Modular CP/M 3 BIOS
;  This module is organized into routines to do
;  initialization, input, output, and status checks.
;
;  Copyright (c) Visual Technology, 1983
;
; Revision history
;  01 (IRN) Modified from CPM/3 Kit
;  02 (LEL) Continued modification from kit
;

	maclib vislib  	; standard defs.
	maclib Z80	; define Z80 op codes
	maclib ports	; define port addresses
	maclib modebaud	; define mode bits and baud equates
	maclib buf	; input buffer data structure


	extrn	?pmsg
	extrn	?bnksl,?wboot

	public	?cinit,?ci,?co,?cist,?cost
	public	@ctbl
	public	dsp$buf$in
	public	aux$in$ptr,aux$out$ptr, kb$buf$in
	public	dspint, kint, rsint, kmodei

$*MACRO
max$devices	equ 3
ctlz		equ 26
	cseg
	page
;
; ?cinit 
; This module is called for each of the 16 character devices, and
; initializes the devices.  Register C contains the device number.
; The routine initializes the physical character device specified 
; in register C to the baud rate contained in the appropriate entry
; of @ctbl.  This routine need not be supplied if i/o redirection
; is not implemented.  It is referenced only by the DEVICE utility.
;

?cinit:
	lxi	d,xfer$init	; jump table for ?cinit
	mov	b,c		; needs b
	jr	check$dev	; check for legality

;
; this table parallels @ctbl
;
xfer$init:
	jr	display$init	; init 6502
	jr	aux$init	; init rs-232 port
	jr	kb$init		; init keyboard port
	jr	lpt$init	; init parallel port

display$init:
lpt$init:
;
; Do nothing (set up in boot rom)                      
;
	jr	cinit$exit	; exit

kb$init:
	if	keyboard$1050
	mvi	a,kb$ir		; Internal reset
	out	p$kb$control	; 
	mvi	a,04fh		; Mode:8bits,nopar,1stop,x16
	out	p$kb$control	;
	mvi	a,15h		; err reset,rxen,txen,rts0,dtr0
	out  	p$kb$control	;
	mvi	a,48h		; enable keyclick & repeat
	sta	kmodei		; save settings
	sta	kmode		; (need both)
	out	p$kb$data	; send it out
	endif
	jr	cinit$exit	; return
aux$init:
	;
	; get default baud rate, then set it, by setting the
	; base baud rate in port c of misc. 8255, and baud rate
	; factor in 8251 chip.
	;
	mov	l,b		; get device number
	mvi	h,0		; make into word
	dad h ! dad h ! dad h	; *8 (table entry size)
	lxi	d,@ctbl+7	; character device table
	dad	d		; device baud entry
	mov	l,m		; get baud rate
	mvi	h,0		; make word
	lxi	b,baud$table	; settings to achieve baud rate
	dad	b		; entry in table

	;
	; now have pointer to baud table entry. set base rate.
	;
	di			; disable interrupts
	in	p$misc		; retain old settings
	xra	m		; get new setting
	ani	not misc$baudmask
				; clear base rate bits
	xra	m		; set new ones
	out	p$misc		; reload it

	;
	; now set base rate factor in 8251 chip.
	;
	mvi	a,com$ir	; internal reset
	out	p$aux1$control	; kick it
	mov	a,m		; get new base rate
	xri	mode$default	; default modes
	ani	mode$baudmask	; use baud rate from table
	xri	mode$default	; include defaults
	out	p$aux1$control	; kick it
	mvi	a,com$default	; reset command parameters
	out	p$aux1$control	;  to its default
	sta	rspar		; Save RS232 parameters
	ei			; enable interrupts

cinit$exit:
	ret
	page
; check$dev
;  Assumes the address of a jump table in de, and a device in b.
;  Preserves b and c.

check$dev:
	mvi	a,max$devices
	cmp	b		; b > max$devices?
	jrc	bad$device	; yes
	mov	l,b		; device to l
	mvi	h,0		; make 16 bits
	dad	h		; double it
	dad	d		; entry in jump table
	pchl

bad$device:
	xra	a
	ret

	page
; ci (b)
;  Character device input. This routine is called with the 
;  character device in register b. It returns an 8 bit
;  character with no parity.

?ci:
	lxi	d,xfer$in
	jr	check$dev

; must parallel device table
;

xfer$in:
	jr	crtin
	jr	auxin
	jr	kbin
	jr	lptin

crtin:
	lxix	dsp$buf$in	; Dsp input structure
	call	bufin		; Get character
	ei			; reenable interrupts
	ret

lptin:
	mvi	a,ctlz		; set to eof character
	ret
auxin:
	lxix	aux$in$ptr	; auxin buffer structure
	call	bufin		; get character
	ei			; enable interrupts
	ret
kbin:
	if	keyboard$1050
	lxix	kb$buf$in	; Point to keyboard buffer
	call	bufin		; Get character
	ei			; reenable interrupts
	mov	c,a		; Save character in C-reg

;
; Check caps lock
;

	lda	kmode		; Get keyboard mode byte
	ani	010h		; check caps lock
	jrz	kbin$20		; Jump if not on

	mvi	a,'a'-1		; Check if >= 'a'
	cmp	c		;
	jrnc	kbin$20		; Jump if below range
	mvi	a,'z'		; Check if <= 'z'
	cmp	c		;
	jrc	kbin$20		; Jump if above range
	mov	a,c		; Else, get character
	xri	20h		; Shift to upper case
	jr	kbin$exit	; and exit
;
; Check numeric pad
;

kbin$20
	mov	a,c		; Get keycode
	cpi	0bfh		; Numeric pad or less?
	jrnc	kbin$50		; Jump if no 
	
	cpi	83h		; Enter key?
	jrz	kbin$40		; Jump if yes

	cpi	0a0h		; Low end of numeric pad?
	jrc	kbin$50		; Jump if less

kbin$40	lda	kmode		; Test num lock
	ani	20h		;
	jrz	kbin$50		; Jump if not on

	mov	a,c		; Get keycode
	cpi	83h		; Enter key?
	mvi	a,0dh		; (assume yes)
	jrz	kbin$exit	; Jump if true
	res	7,c		; Else change to number
	jr	kbin$55		;

;
; Test other special characters
;

kbin$50	cpi	08ch		; Tab key?
	mvi	a,09h		; Yes => Control-I
	jrz	kbin$exit

kbin$55	mov	a,c		; Get keycode
kbin$exit:
	ret
	else
	lxix	kb$buf$in	; kb buffer structure
charin:	call	bufin		; returns a character
	ei
	ret
	endif
	page
; bufin (ix)
;  Ix points to buffer data.
;  Returns character in register a, after updating buffer
;  management data structure. Buffer is circular.
;  buf$empty is the offset of the next byte to return.

bufin:
spin:
	di			;
	call	?cist 		; is there a character?
	ei			;
	jrz	spin		; no, wait for one
	di			; turn off interrupts
buffer$in:
	ldx	a,buf$empty	; offset of empty in buffer
	ldx	b,buf$length	; length of buffer
	mov	c,a		; save pointer

	; add 1 mod length
	;
	inr	a		; increment buffer pointer
	cmp	b		; did we go out of bounds?
	jrnz	inbounds$i	; if not
	xra	a		; else wrap around

inbounds$i:
	stx	a,buf$empty	; save new emptying pointer
	mvi	a,buf$buffer	; offset of buffer
	add	c		; offset of character
	sta	loc$i		; save in i-stream
	ldx	a,$-$		; load character
loc$i	equ	$-1		; disp. field of ldx
	ret
	page
; cist (b)
;  Character device input status. This routine is called
;  with a device number in register b and returns false
;  if the specified device has no input character ready,
;  and true if the device has an input character to be read.

?cist:

	lxi	d,xfer$st
	jmp	check$dev

; must parallel device table
;

xfer$st:
	jr	crtst
	jr	auxst
	jr	kbst
	jr	lptst

crtst:
	lxix	dsp$buf$in	; Display input structure
	di			; disable interrupts
	call	inst		; Check input status
	ei			; reenable interrupts
	ret

lptst:
	xra	a
	ret

auxst:
	lxix	aux$in$ptr	; aux buffer structure
	di			; Disable interrupts
	call	inst		; Anything in buffer?
	ei			; reeable interrupts
	ret			; and return
	page

kbst:
	lxix	kb$buf$in	; keyboard buffer structure
	if	keyboard$1050
	di			; Disable interrupts
	call	inst		; Check input status
	ei			; reenable interrupts
	rz			; If no character, return

;
; There is a character in the buffer, but in order to know if
; it 'counts', we must get the exact character.  
;

	lxix	kb$buf$in	; Point to input buffer
	di			; disable interrupts
	ldx	b,buf$empty	; get empty pointer
	push	b  		; save it
	call	buffer$in	; Get keycode
	ldx	d,buf$empty	; Get new empty pointer
	pop	b  		; Get empty pointer
	stx	b,buf$empty	; restore it
	ei			; reenable interrupts
	
;
; Now, check for 'non-characters', ie shift and num lock.
;

	sui	80h		; Caps lock?
	jrz	kbds$1		; jump if yes
	dcr	a		; Num lock?
	jrz	kbds$2		; jump if yes
	dcr	a		; Num lock up?
	jrz	kbds$4		; jump if yes

	mvi	a,true		; Character is ok
	ret			; 

;
; Handle caps and num lock
;

kbds$1:
	lda	kmode		; Get keyboard mode
	xri	010h		; toggle caps lock
	jr	kbds$3		;

kbds$2:
	lda	kmode		; Get keyboard mode
	xri	020h		; Toggle numlock bit

kbds$3:	
	sta	kmode		; Store new settings

kbds$4:
	di			; disable interrupts
	stx	d,buf$empty	; store empty pointer
	ei			; reenable interrupts
	xra	a		; a=0 for no char
	ret
	else
	di
	call	inst
	ei	
	ret
	endif
	page
;inst(ix)
;  Ix is the input buffer structure for a character device.
;  This routine returns true if there is a character waiting,
;  false otherwise.

inst:
	ldx	a,buf$empty	; next byte to empty
	ldx	b,buf$fill	; next byte to fill
	sub	b		; same?
	rz			; yes, it's empty
	mvi	a,true		; return true
	ret
	page
; co (b)
;  Character output. This routine is called with a device number
;  in register b, and the character to be output in c. 
;  It waits until the device (or buffer) is ready to accept 
;  another character, and then sends the character.
;  The character is 8 bits, no parity.

?co:
	lxi	d,xfer$out
	jmp	check$dev

;
; must parallel device table
;

xfer$out:
	jr	disp$out
	jr	aux$out
	jr	kb$out
	jr	lpt$out

kb$out:
	xra	a
	ret
aux$out:

	call	?cost		; device ready for output?
	jrz	aux$out		; loop until ready
	lxix	aux$out$ptr	; set ix to out buffer
	di			; disable interrupts
	call	bufout		; stuff it in
	ei			;reenable interrupts
	lda	rspar		; Get RS232 parameters
	ori	com$txe		; enables transmit
	out	p$aux1$control	; aux1 control port
	ret

lpt$out:
	call	?cost		; busy
	jrz	lpt$out		; yes, spin
	mov	a,c		; get the character
	cma
	out	p$printer
	mvi	a,1		; strobe the printer
	out	p$8255$control	; to 1
	xra	a		; and back
	out	p$8255$control	; to 0
	ret

disp$out:
	call	?cost		; busy?
	jrz	disp$out	; yes, spin
	mov	a,c		; get the character
	out	p$disp$out	; send it out

	; the following uses the bit set/reset feature
	; of the 8255. 
	di
	mvi	a,0000$1110b	; reset port c bit 7
	out	p$disp$control	; to shake hands
	inr	a		; set port c bit 7
	out	p$disp$control	; to complete handshake
	ei
	ret
	page
; bufout (ix,c)
;  This routine takes the character to be sent out and
;  stuffs it into the buffer denoted by register ix.

bufout:
	ldx	a,buf$fill	; fill point in buffer
	ldx	b,buf$length	; length of buffer
	mov	d,a		; save fill point
	inr	a		; next fill point?
	cmp	b		; outside?
	jrnz	inbounds$o	; no.
	xra	a		; yes, reset

inbounds$o:
	stx	a,buf$fill 	; new fill point
	mvi	a,buf$buffer	; offset of buffer
	add	d		; old fill point
	sta	loc$o		; next byte to be sent
	stx	c,$-$		; store in buffer
loc$o	equ	$-1
	ret
	page

; cost (b)
;  Character output status. This routine is called with a 
;  device number in register b. It returns with register
;  a set to zero if the device specified cannot accept a
;  character immediately, and returns with ff otherwise.
;  B and C must be preserved.

?cost:
	lxi	d,xfer$ost
	jmp	check$dev

xfer$ost:
	jr	disp$ost
	jr	aux$ost
	jr	kb$ost
	jr	lpt$ost

kb$ost:
	xra	a
	ret
disp$ost:
	in	p$disp$c	; port c
	ani	disp$ready$rcv	; ready to receive?
	rz			; no.
ost$true:
	mvi	a,true		; return ready
	ret

aux$ost:
	lxix	aux$out$ptr	; aux xmit buffer
	di			; critical section
	ldx	d,buf$empty	; next to read
	ldx	a,buf$fill	; next to fill
	ei			; critical section

buf$full$cond:

	; this check is to see if the buffer was full.
	; a full condition is the empty pointer one
	; more than the fill pointer. Empty must always
	; be ahead of fill (modulo  buffer length since
	; circular).

	inr	a
	ldx	e,buf$length	; need to wrap?
	cmp	e		; if equal, wrap
	jrnz	inbound$ost	; not equal
	xra	a

inbound$ost:
	cmp	d		; is fill=empty?
	jrnz	ost$true	; no. not full

ost$false:
	xra	a		; yes. full.
	ret

lpt$ost:
	in	p$misc		; printer status
	ani	misc$lpt$avail	; available?
	jrz	ost$false	; no.
	in	p$misc		; if available
	ani	misc$lpt$nobusy	;   busy?
	jrz	ost$false	; yes
	jr	ost$true	; no

	page

; The entries in the following table are indexed by the
; values for baud rates in modebaud.lib
;
baud$table:
	db	baud$none			; none
	db	baud$none			; 50
	db	baud$none			; 75
	db	baud$none			; 110
	db	baud$none			; 134.5
	db	baud$none			; 150
	db	misc$base01200 or mode$div64	; 300
	db	misc$base02400 or mode$div64	; 600
	db	misc$base01200 or mode$div16	; 1200
	db	baud$none			; 1800
	db	misc$base02400 or mode$div16	; 2400
	db	baud$none			; 3600
	db	misc$base19200 or mode$div64	; 4800
	db	baud$none			; 7200
	db	misc$base09600 or mode$div16	; 9600
	db	misc$base19200 or mode$div16	; 19200


@ctbl	db 'DISPLY'	; device 0, 6502 CRT
	db mb$in$out
	db baud$none
	db 'AUX   '	; device 1, RS-232 port
	db mb$in$out+mb$serial+mb$softbaud
	db baud$1200
	db 'KB    '	; device 2, Keyboard
	db mb$input+mb$serial
	db baud$1200
	db 'LPT   '	; device 3, Centronics parallel printer
	db mb$output
	db baud$none
	db 0			; table terminator

	page
;
; Keyboard interrupt routine     
;
; Takes incoming character, checks for warm or cold boot sequences.
; If it is either one, it performs them immediately.                
; Otherwise, it stores the keycode in the buffer and performs the keyclick. 
; If there is not enough room in the buffer to store the keycode,
; the key is discarded and the keyboard will beep to indicate an error
; condition.
;
Kint:
	Push	psw			; Save A
	push	b			; and b
	push	d			; and d
	push	ix			; and ix

;
; Get keycode and check for warm or cold boot.       
;
	in	p$kb$data		; get keycode
	mov	d,a			; save in d

	if 	keyboard$1050
	cpi	08ah			; Is it warm boot?
	else
	cpi	0aah			; is it warm boot?
	endif
	jrz	kint$6 			; jump if yes
	If	keyboard$1050
	cpi	08bh			; Or cold boot?
	else
	cpi	0bah			; or cold boot?    
	endif
	jrnz	kint$10			; jump if not
	page
;
; Key is cold boot.  Jump to boot rom.          
;
	IF  	REAL$1050
	XRA 	A			; A=0
	OUT	P$BOOT			; ENABLE BOOT PROM
	ELSE
	in	0			; enable boot prom
	ENDIF
	jmp	0
;
; Key is warm boot.
;

kint$6
	mvi	a,fdc$reset		; set up for reset
	out	p$disk$control		; and do it

	IF	REAL$1050
	in	p$disk$bits		; Get current settings
	ori	0100$1111b		; Turn off motor & deselect drvs
	out	p$disk$bits		; Send out again

	mvi	a,int$initial
	out	int$port
	ei
	ENDIF
	jmp	?wboot 			;  boot

;
; Key not cold or warm boot.                                       
;
kint$10:	
	mov	a,d			; get keycode
	if	not keyboard$1050

	cpi	08eh			; Space bar?
	jrz	key$space		; jump if yes
	cpi	08dh			; Carriage return?
	jrz	key$return		;jump if yes
	cpi	08ah			; Escape?
	jrz	key$escape		; jump if yes
	cpi	08bh			; Backspace?
	jrz	key$backspace		; jump if yes
	endif
kint$11
	push	d			; save keycode
	lxix	kb$buf$in		; point to buffer
	ldx	d,buf$empty		; Get empty pointer
	ldx	a,buf$fill		; and fill pointer
	call	buf$full$cond		; check full condition
	pop	d			; restore keycode
	ora	a			; (checking resultant flag)
	jrnz	kint$30			; jump if true
;
; Keyboard buffer is full.  Beep rather than click and then exit.
;
kint$23
	call	beep    		; beep to indicate error
	jr	kint$99			; go to exit
;
; Keyboard buffer not full.  Put char into buffer.
;
kint$30	mov	c,d			; Get char into C-reg
	push	d			;
	call	bufout			; put into buffer
	pop	psw			; Get character into A
	if	not keyboard$1050
	mvi	a,kb$click		; set up to click
	out	p$kb$data		; click
	else
;
; Check for caps lock and num lock
;
	cpi	80h			; Caps lock?
	jrz	kint$80			; Jump if yes
	cpi	81h			; Num lock?
	jrz	kint$81			; Jump if yes
	endif

	jr	kint$99			; then exit


	if	keyboard$1050

;
; Handle caps lock
;

kint$80:
	lda	kmodei			; Get previous settings
	xri	010h			; Toggle caps lock
	jr	kint$90			;

;
; Handle num lock
;

kint$81:
	lda	kmodei			; Get previous setting
	xri	020h			; Toggle num lock

;
; Turn on/off keyboard leds.
;

kint$90:
	sta	kmodei			; Store new num or caps lock
	mov	h,a			; store data

kint$l:
	in	p$kb$control		; Get status
	ani	01h			; Test Tx empty
	jrz	kint$l			; loop if not
	mov	a,h			; Get data back
	out	p$kb$data		; Send to keyboard
	jr	kint$99			; then exit

	else
Key$space	mvi	d,020h		;Force to ascii
	jr 	kint$11
key$return	mvi	d,13		; Force to ascii
	jr 	kint$11
key$escape	mvi	d,27
	jr 	kint$11
key$backspace	mvi 	d,8
	jr 	kint$11
	endif
;
; Get ready to exit
;
kint$99	
	IF	REAL$1050
	mvi	a,int$initial		; Initialize
	out	int$port		; Interrupt port
	ENDIF
	pop	ix			; start popping
	pop	d			;
	pop	b			;
	pop	psw			;
	ei				; enable interrupts
	ret				; and return


;
; Display Interrupt routine     
;
; Takes incoming character from 6502 code.  This info is used for  
; keyboard info only.                                       
;
Dspint:
	Push	psw			; Save A
	push	b			; and b
	push	d			; and d
	push	ix			; and ix

;
; Get character 
;

	in	p$disp$in		; Get character
	mov	d,a 			; save it
	mvi	a,12			; Strobe
	out	p$disp$control		;
	inr	a			; then back
	out	p$disp$control		;

dspint$87:
	in	p$kb$control		; Get status
	ani	4			;
	jrz	dspint$87

;
; Get info.  Mask out the 2 leds. 
;

	mov	a,d			; Get char
	ani	1100$1111b		; minus leds
	mov	d,a			; store in d

	lda	kmode 			; Get kmodes
	ani	0011$0000b		; Keep leds only
	ora	d			; OR in
	ani	7fh			; (not bell, tho)
	sta	kmode 

	lda	kmodei			; (both)
	ani	0011$0000b		; Keep leds only
	ora	d			;
	out	p$kb$data		; Send out

	ani	7fh			; (don't save beep)
	sta	kmodei			;

;
; Get ready to exit
;
dspint$99	
	IF	REAL$1050
	out	clear$6502		; Clear 6502 interrupt
	mvi	a,int$initial		; Initialize
	out	int$port		; Interrupt port
	ENDIF
	pop	ix			; start popping
	pop	d			;
	pop	b			;
	pop	psw			;
	ei				; enable interrupts
	ret				; and return


;
; Beep routine
;
	if	keyboard$1050
beep:	ei				; Enable interrupts
	di				; But not for long
beep1:
	in	p$kb$control		; Get status
	ani	4			; Test Tx ready
	jrz	beep			; Loop if not
	lda	kmodei			; Get bits
	ori	80h			; Set bell bit
	out	p$kb$data		; Send it out
	ret

	else
beep1:
beep	mvi	d,24			; load count
beep0	in	p$kb$control		; read status
	rrc				; rotate
	jrnc	beep0			; jump if no carry
	mvi	a,kb$click		; get click code
	out 	p$kb$data		; send to keyboard
	dcr	d			; decrement count
	jrnz	beep0			; till count =0
	ret				; then return
	endif
	page


;REC/SND (RS-232) INT
;SEE IF RECEIVER OR TRANSMITTER CAUSED INT.
;  IF RECEIVER, ACCEPT CHR INTO RECEIVE FIFO.
;  IF TRANSMITTER, OUT A CHR FROM TRANSMIT FIFO;
;  IF FIFO EMPTY, TURN OFF TRANSMITTER.
RSINT:	PUSH PSW
	push  h
	push  D
	push b
	push ix

;SEE IF REC OR SND CAUSED INT.

	in p$aux1$control		; read in status
	RAR
	RAR
	jrnC SINT
;
;REC INT: CHR TO FIFO.
RINT:	
	IN p$aux1$data			; read incoming character
	MOV D,A				; save in D
;
; Check for parity error
;
	IN p$aux1$control		; get status
	bit 3,a
	jrz RINT0			;Jump if ok          

; Parity error.  Reset error condition and replace char with '?'
;
	LDA RSPAR
	ORI 010H
	OUT p$aux1$control
	ANI 0EFH
	OUT p$aux1$control		;RESET ERROR
	MVI D,'?'			;REPLACE CHAR WITH '?'

; Processing continues here.
;
RINT0:			
	push d			; save character
	lxix aux$in$ptr
	ldx d,buf$empty
	ldx a,buf$fill
	call buf$full$cond	; buffer already full?
	pop d			; (restore char)
	JrZ  rs$error		; If yes, error
	mov c,d
	call bufout		; Else, put into buffer
	jr   RS$EXIT
;
;SND INT: CHR FROM FIFO
;
SINT:
	lxix aux$out$ptr	; Point to structure
	call inst		; Anything there?
	jrnz sint0		; Jump if yes

	LDA RSPAR
	ANI 0FEH
	STA RSPAR
	OUT p$aux1$control	;SHUT OFF SND
	jr rs$exit

SINT0:	call buffer$in		; Get character from buffer

	OUT p$aux1$data		; Send it
	jr rs$exit

rs$error:
	call beep		; Make noise


rs$exit:
	IF	REAL$1050
	mvi	a,int$initial	; Initialize
	out	int$port	; Interrupt port
	ENDIF

	pop ix
	pop b
	POP D
	pop h
	POP PSW
	EI
	RET


RSPAR:	DS 1
;
; The keyboard mode byte is kept twice.  One (KMODEI) is used
; by the interrupt routine so that the led can be turned on 
; as soon as the caps or num lock key is hit.  The other
; (kmode) is used to actually effect the change to incoming characters
; as they are being processed.
;

KMODEi:	ds 1
kmode:	ds 1




	page
;
; Receive buffers

kb$length	equ	32
kb$buf$in:
	db	kb$length	; length
	db	0		; next character to take
	db	0		; next character to fill
	ds	kb$length	; buffer

aux$length	equ	32
aux$in$ptr:
	db	aux$length	; length
	db	0		; next character to take
	db	0		; next character to fill
	ds	aux$length	; buffer

dsp$length	equ	16
dsp$buf$in:
	db	dsp$length	; length
	db	0		; next character to take
	db	0		; next character to fill
	ds	dsp$length	; buffer

;
; Transmit buffers

aux$length$o	equ	16
aux$out$ptr:
	db	aux$length$o	; length
	db	0		; next character to take
	db	0		; next character to fill
	ds	aux$length$o	; buffer
bootadd	equ	0

	end
CPM3.LIB
;	Macro Definitions for CP/M3 BIOS Data Structures.

	; dtbl	<dph0,dph1,...>		- drive table

	; dph	translate$table,	- disk parameter header
	;	disk$parameter$block,
	;	checksum$size,			(optional)
	;	alloc$size			(optional)

	; skew	sectors,		- skew table
	;	skew$factor,
	;	first$sector$number

	; dpb	physical$sector$size,	- disk parameter block
	;	physical$sectors$per$track,
	;	number$tracks,
	;	block$size,
	;	number$dir$entries,
	;	track$offset,
	;	checksum$vec$size		(optional)


;	Drive Table.  Contains 16 one word entries.

dtbl macro ?list
    local ?n
?n  set 0
    irp ?drv,<?list>
?n  set ?n+1
	dw	?drv
    endm

    if ?n > 16
.' Too many drives.  Max 16 allowed'
	exitm
    endif

    if ?n < 16
	rept (16-?n)
	dw	0
	endm
    endif
 endm

dph macro ?trans,?dpb,?csize,?asize
    local ?csv,?alv
	dw ?trans		; translate table address
	db 0,0,0,0,0,0,0,0,0	; BDOS Scratch area
	db 0			; media flag
	dw ?dpb			; disk parameter block
    if not nul ?csize
	dw ?csv			; checksum vector
    else
	dw 0FFFEh		; checksum vector allocated by
    endif			; GENCPM
    if not nul ?asize
	dw ?alv			; allocation vector
    else
	dw 0FFFEh		; alloc vector allocated by GENCPM
    endif
	dw 0fffeh,0fffeh,0fffeh	; dirbcb, dtabcb, hash alloc'd
				; by GENCPM
	db 0			; hash bank

    if not nul ?csize
?csv	ds	?csize		; checksum vector
    endif
    if not nul ?asize
?alv	ds	?asize		; allocation vector
    endif

    endm

dpb macro ?psize,?pspt,?trks,?bls,?ndirs,?off,?ncks
    local ?spt,?bsh,?blm,?exm,?dsm,?drm,?al0,?al1,?cks,?psh,?psm
    local ?n
;; physical sector mask and physical sector shift
    ?psh	set 0
    ?n		set ?psize/128
    ?psm	set ?n-1
	rept 8
	?n	set ?n/2
 	    if ?n = 0 
	    exitm
	    endif
	?psh	set ?psh + 1
	endm
    ?spt	set ?pspt*(?psize/128)

    ?bsh	set 3
    ?n		set ?bls/1024
	rept 8
	?n	set ?n/2
	    if ?n = 0
	    exitm
	    endif
	?bsh	set ?bsh + 1
	endm
    ?blm	set ?bls/128-1
    ?size	set (?trks-?off)*?spt
    ?dsm	set ?size/(?bls/128)-1

    ?exm	set ?bls/1024
	if ?dsm > 255
	    if ?bls = 1024
.'Error, can''t have this size disk with 1k block size'
	    exitm
	    endif
	?exm	set ?exm/2
	endif
    ?exm	set ?exm-1
    ?all	set 0
    ?n		set (?ndirs*32+?bls-1)/?bls
	rept ?n
	?all	set (?all shr 1) or 8000h
	endm
    ?al0	set high ?all
    ?al1	set low ?all
    ?drm	set ?ndirs-1
    if not nul ?ncks
    	?cks	set ?ncks
    else
	?cks	set ?ndirs/4
    endif
	dw	?spt		; 128 byte records per track
	db	?bsh,?blm	; block shift and mask
	db	?exm		; extent mask
	dw	?dsm		; maximum block number
	dw	?drm		; maximum directory entry number
	db	?al0,?al1	; alloc vector for directory
	dw	?cks		; checksum size
	dw	?off		; offset for system tracks
	db	?psh,?psm	; physical sector size shift
				; and mask
    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

skew macro ?secs,?skf,?fsc
;;	generate the translate table
    ?nxtsec	set 0	;;next sector to fill
    ?nxtbas	set 0	;;moves by one on overflow
    gcd %?secs,?skf
    ;;	?gcdn = gcd(?secs,skew)
    ?neltst	set ?secs/?gcdn
    ;;	neltst is number of elements to generate
    ;;	before we overlap previous elements
    ?nelts	set ?neltst	;;counter
	rept ?secs	;;once for each sector
	db	?nxtsec+?fsc
	?nxtsec	set ?nxtsec+?skf
	    if ?nxtsec >= ?secs
	    ?nxtsec	set ?nxtsec-?secs
	    endif
	?nelts	set ?nelts-1
	    if ?nelts = 0
	    ?nxtbas	set ?nxtbas+1
	    ?nxtsec	set ?nxtbas
	    ?nelts	set ?neltst
	    endif
	endm
    endm
DRIVES.ASM
	title 'Diskette Handler Module'
;    CP/M-80 Version 3     --  Modular BIOS

;	Disk I/O Module 


    ; Port Address Equates

	maclib	vislib
	maclib ports
	maclib	modebaud

    ; CP/M 3 Disk definition macros

	maclib cpm3

    ; Z80 macro library instruction definitions

	maclib Z80

    ; Disk drive dispatching tables for linked BIOS

	public	fddd0,fddd1,firq,vert$int
	public u$conin$echo, error$table
    ; Variables containing parameters passed by BDOS

	extrn	@adrv,@rdrv
	extrn	@dma,@trk,@sect
	extrn	@dbnk,@cbnk

    ; System Control Block variables

	extrn	@ermde		; BDOS error mode

    ; Utility routines in standard BIOS

	extrn	?wboot		; warm boot vector
	extrn	?pmsg		; print message @<HL> up to 00, saves <BC> & <DE>
	extrn	?pdec		; print binary number in <A> from 0 to 99.
	extrn	?pderr		; print BIOS disk error header
	extrn	?conin,?cono	; con in and out
	extrn	?const		; get console status
	extrn	ivect
	extrn	?bank


cr	equ 13
lf	equ 10
bell	equ 7

	page
    ; Extended Disk Parameter Headers (XPDHs)

	CSEG

	dw	fd$write
	dw	fd$read
	dw	fd$login
	dw	fd$init
	db	0   			; relative drive zero
	db	2			; TYPE field
fddd0:              
fddd0$dpb equ $+12
	dph   trandd,dpbd0


	dw	fd$write
	dw	fd$read
	dw	fd$login
	dw	fd$init
	db	1  			; relative drive one
	db	02			; TYPE field
fddd1:              
fddd1$dpb equ $+12
	dph	trandd,dpbd1        


	CSEG	; DPB must be resident
dpbd0	
        dw     40              ;#128 byte records/track
        db     4,0fh           ;block shift mask (2K)
        db     1               ;extent  mask  
        dw     194             ;maximun  block number
        dw     127             ;max number of dir entry - 1
        db     0C0H,00h        ;alloc vector for directory
        dw     0020h           ;checksum size
        dw     2               ;offset for sys tracks
        db     2,3             ;physical sector shift (512 sector)

dpbd1	
        dw     40              ;#128 byte records/track
        db     4,0Fh           ;block shift mask (2K)
        db     1               ;extent  mask  
        dw     194             ;maximun  block number
        dw     127             ;max number of dir entry - 1
        db     0C0H,00h        ;alloc vector for directory
        dw     32              ;checksum size
        dw     2               ;offset for sys tracks
        db     2,3             ;physical sector shift (512 sector)
;
; DPB for DEC Rainbow
;
RAINDPB:
        dw     028h            ;#128 byte records/track
        db     4,0fh           ;block shift mask (2K)
        db     1               ;extent  mask  
        dw     194             ;maximun  block number
        dw     127             ;max number of dir entry - 1
        db     0C0H,00h        ;alloc vector for directory
        dw     0020h           ;checksum size
        dw     2               ;offset for sys tracks
        db     2,3             ;physical sector shift (512 sector)
;
; DPB for DEC VT180
;
VT180$dpb:
        dw     36              ;#128 byte records/track
        db     3,7             ;block shift mask (2K)
        db     0               ;extent  mask  
        dw     170             ;maximum  block number
        dw     63              ;max number of dir entry - 1
        db     0C0H,00h        ;alloc vector for directory
        dw     16              ;checksum size
        dw     2               ;offset for sys tracks
        db     2,3             ;physical sector shift (512 sector)

;
;DPB for KAYPRO II single side 48 tpi
;

kayprodpb:
	dw	28h            ;number of 128 records/track
	db	3,7	       ;block shift mask
	db	0	       ;extent mask
	dw	194	       ;max block number
	dw	63	       ;max dir entries - 1
	db      0f0h,0         ;alloc vector for directory
	dw	0010h          ;checksum size
	dw	1	       ;offset sys tracks
	db	2,3	       ;physical sector shift (512)
	

	DSEG

datbf:	ds	512

	CSEG

trandd	skew	10,1,1
rainbowskew	skew	10,2,1	; Rainbow skew factor is 2
	page

    ; Disk I/O routines for standardized BIOS interface

; Initialization entry point.

;		called for first time initialization.

	DSEG
fd$init:
	mvi a,fdc$reset		;reset
	out p$disk$control	;do it
	ret
	page

fd$login:
		; This entry is called when a logical drive is about to
		; be logged into for the purpose determining what type    
		; of disk is in use.

		; It may adjust the parameters contained in the disk
		; parameter header pointed at by <DE>
		
		; The value of XDPH-1 (TYPE field) is adjusted to reflect
		; the type of disk.  This is determined by reading the
		; disk label.

	push	d		; Save address of XDPH

;reset xdph for b: back to default condition   (support of rainbow, kaypro) 

        lda    @rdrv		;see which drive              (dpc 10-17-83)
        cpi    1              	;see if drive b                        "
	lxi	d,trandd	; (assume yes)
	lxi	h,dpbd1		;
        jrnz    login$2         ;not b:, no need to fix drive a:       "
        shld   fddd1dpb       	;restore dpb1 addr pointer in dph      "
        sded   fddd1          	;restore translate table      (dpc 10-17-83)
	jr	login$3		;

login$2:
	lxi    h,dpbd0		;
	shld	fddd0$dpb	; Restore DPB
	sded	fddd0		; Restore translate table

login$3:
	xra	a	  	;zero a
	sta	trk	      	;track zero
	sta	login$flag	; Indicate LOGIN entry
	inr     a	      	;a = 1
	sta     sect	      	;sector =  1	 			
	lxi h,datbf             ; point to dma area
 	shld	dmaadr		; store
	lxi h,fd0$access	; assume A drive
	lded @rdrv		; Get drive
	xra	a		;zero a
	mov	d,a		;zero d
	dad d			; Point to correct flag
	pop	d		; Restore address of XDPH
login$10:
	mvi a,0ffh		; flag=ff
	mov m,a			; reset last track
	sta	old$track	;
	lda @rdrv		; Get relative drive
	inr	a		; increment
	xri 0fh			; bit=0 => on
	sta select$mask		; save command
	call 	read$label	;perform read 
	jrnz	not$ok$1	; Jump if read not OK
;
; Check to see if disk has our "signature"
;
	call	ours$check
	jrz	good$exit

;
;     formats are dec rainbow 100, DEC VT180, and KAYPRO
;
; 	 
        lda     @rdrv           ;get relative drive (dpc 10-14-83)
        cpi	1		;set zero flg if zero (dpc 10-14-83)
        jrnz     not$ok$1	;not drive b: so skip (dpc 10-14-83) 
;
;now see if diskette is 96 tpi or 48 tpi
;
	mvi	a,2		;96 tpi
	sta	fddd1-1		;save in type field
	dcr     a		;acc = 1
	sta     trk		;track = 1
 	   	       		;sector = 1
	lxi	d,fddd1		;point to xdph
	call    read$label      ;perform read
	jrnz    try$vt180 	;error on read

;	Must be a RAINBOW
;
;fddd1 points to skew table address in DPH
;fddd1 -1 points to type field in DPH
;

        mvi     a,2             ;dec rainbow is single sided  96 tpi     
        sta     fddd1-1         ;store rainbow type field in dph
        lxi     h,raindpb       ;get address of rainbow dpb     (dpc 10-17-83) 
                                ;store in dpb address location of dph
login$80:
        shld    fddd1dpb        ;the DPB of b:'s DPH points to a rainbow dpb
        lxi     h,rainbowskew   ;get skew table for dec rainbow  (dpc 10-14) 
        shld    fddd1           ;overwrite old skew  table addr (dpc 10-14-83)
        jr 	good$exit       ;exit

;
;try read of VT180 single sided double density 48 tpi
;
try$vt180:
	mvi	a,0ffh		; Set last track to FF
	sta	old$track	; to force HOME on disk
	xra	a		;acc = zero
	sta     fddd1-1		;type byte = 0 so single side 48 tpi
        sta     tpi             ;force tpi to be 48 
	sta	trk		; Track=0
	sta	sect	        ;sector = 0
	lxi     d,fddd1		;get address of xdph
	call    read$label	;perform read 
	jrz	its$kaypro	;
;
; It's 48TPI.  Assume VT180 till proven otherwise.
;	
	mvi	a,0ffh
	sta	old$track
	lxi	h,vt180$dpb     ;get addr of VT180 addr
        shld    fddd1dpb        ;patch dpb addr so points to VT180's 
        lxi     h,rainbow$skew 	;(Same skew as RAINBOW)     
        shld    fddd1           ;set translate table 
	mvi	a,1 		;Sector=1 
	sta	sect		; 
	call	read$label
	jrz	good$exit	;

notok1:
	mvi     a,2		;single side 96 tpi
	sta     fddd1-1	        ;reset type field
	lxi	h,nomatch	; Error, print message
	call	?pmsg		;
	mvi	a,0ffh		;FF for error
	jr	login$exit	;
;
; Assume KAYPRO
;
its$kaypro:
	lxi	h,kayprodpb	; Get addr of KAYPRO dpb
	shld	fddd1dpb	; Store
	lxi	h,0		; No xlate
	shld	fddd1		; Set translate table

good$exit:
	xra	a		; A=0 if good
login$exit:
	ora	a		; Set flags
	ret

ours$check:
;
; Check that disk has our "signature"
;
        push    d		;save xdph 
	lxi	b,0003		; count =3
	lxi	h,datbf		; Point to signature on disk
	lxi	d,signature	; and our recognized one
ours$21:
    	ldax	d		; get signature char
	cci			; compare
	inx	d		; increment de
	jrnz	ours$90		; jump if no match
	jpe	ours$21		; if bc<>0, keep going
	
	mov	a,m		; Get next character
	cpi	'0'		; Is it '0'?
	jrz	ours$30		; If yes, it's ok
	cpi	'1'		; Is it '1'?
	jrnz	ours$90		; If not, it's bad

;
; Set up fields in TYPE field as follows:        
;  
; Bit 0 : 1=2 sides
;         0=1 side
; Bit 1 : 1=96 TPI
;         0=48 TPI
; Bits 2 - 7 : unused
;

ours$30:
	pop	d			; Restore address of XDPH
	dcx	d			; Point to type field

	lxi	h,datbf+no$of$heads	;
	mov	a,m			; Get # sides
	dcr	a			; Decrement
	mov	b,a			; Save in B

	lxi	h,datbf+tpi$offset	; Get tpi from label
	mov	a,m			;

	ora	a			; clear carry
	ral				; Move to bit 1
	ora	b			; OR with # sides
	stax	d			; store in TYPE field

;
; Move label info into appropriate DPH
;

	lxi	b,15		; # bytes to move
	lxi	h,datbf+32	; FROM address
	lxi	d,dpbd0		; Assume drive 0
	lda @rdrv		; check it
	ora	a		;
	jrz	ours$67		; Jump if drive 0
	lxi	d,dpbd1		; Set to drive 1
ours$67:
	ldir			; move
	inx	h		; skip skew
	ldi			; Then move in 2 more
	ldi			;
	xra	a		; Ret w/Z flag set
	ret
ours$90:
	pop	d		;
	ret
no$of$heads	equ	53	;Offset into label
tpi$offset	equ	11	;

signature	db	'FMT' 
nomatch	db	'***WARNING - Disk format not recognized***',13,10,0

	page


; disk READ and WRITE entry points.

		; these entries are called with the following arguments:

			; relative drive number in @rdrv (8 bits)
			; absolute drive number in @adrv (8 bits)
			; disk transfer address in @dma (16 bits)
			; disk transfer bank	in @dbnk (8 bits)
			; disk track address	in @trk (16 bits)
			; disk sector address	in @sect (16 bits)
			; pointer to XDPH in <DE>

		; they transfer the appropriate data, perform retries
		; if necessary, then return an error code in <A>
	DSEG
fd$read:
	call	read$setup		; Set up for read
	jr    rw$common

fd$write:
	call	write$setup		; Set up for write

rw$common:				; seek to correct track (if necessary),
					;	and issue 1797 command.
 
	shld operation$name		; save message for errors
	mov b,a				; put read or write into B
	xra	a			; Clear A
	sta	login$flag		; (Not logging in)
	lda	@sect			; Get sector
	sta	sect			; save it
	lhld	@dma
	shld	dmaadr

	lda	no$of$sides		; Get # sides
	ora	a 			; Check it
	jrz 	rw$26			; Jump if single-sided
	lda @trk			; get track
	ani 01h				; low bit = side
	add	a			;
	add	a			;
	add	a			; *8
rw$26	ora b				; OR in w/read or write
	sta disk$command		; save 1797 command
	page
;
; Will need to know info on last access to disk.  Move info into
; old$track        
;
	lxi h,fd0$access		; FROM address
	lded @rdrv			; Get relative drive
	xra	a			; Clear a
	mov	d,a			; Use it to clear d
	dad d				; add      
	lxi d,old$track			; TO address
fd$20	ldi				; move in track
	call	set$up$8255		; Set up 8255 command
	page

more$retries:
	mvi c,04			; allow 04 retries
retry$operation:
	push b				; save retry counter
;
; Check to see whether the motor is being turned on cold, or
; whether it is still on from a previous access.
;
	call	start$motor$timer	; Start timing
	in	p$disk$bits		; Get previous status
	push	psw			; save it

	lda	select$mask		; Get new status
	out	p$disk$bits		; Send out (turns on motor)
	pop	psw			; Get prev status
	ani	0100$0000b		; Was motor on
	jrz	check$track		; bit 6=0 means it was on
;
; Motor was off. Wait 800 ms for it to come up to speed.
;

	lxi	h,892
wait$0 
	xra	a
wait$1
	dcr	a
	jnz	wait$1			; Delay 896 uS

	dcx	h			;
	mov	a,l			;
	ora	h			;
	jrnz	wait$0			;

;
; Check current track against desired one.
;


check$track

;
; Access track
;

	lda trk ! lxi h,old$track ! cmp m
	jrz same$track			; if same track, dont seek
;
; New track (different from last one accessed)
;

new$track:				; 
	lda old$track			; get last track accessed
	out p$disk$track		; send it out
	cpi	0ffh			; first access? 
	cz home				; if yes, home
	lda trk				; point to desired track
	call seeker    			; and seek 


	lda	trk			; get track
	sta	old$track		; store as last track accessed
	jr	get$sect		; Now, access sector.         

;
; At same track as last access
;

same$track:
	out p$disk$track		; give 1797 track


;
; Now, Get sector.
;

get$sect:
	lda sect 
	out p$disk$sector		;and sector

 
;
; Save track info for drive
;

	lxi     h,fd0$access		; TO address
	lded    @rdrv			; get current drive
	xra	a			; Clear a
	mov	d,a			; Use it to clear d
	dad  d                  	;
	lxi d,old$track			; FROM address
	xchg				;
        ldi				; move in track
	JMP	SEL$DMA

	CSEG

;
; Select DMA bank for transfer
;

SEL$DMA:

	IF	BANKED   
	lda	@dbnk			; Get DMA bank
	call	?bank			; Go to it
	ENDIF

;
; Now, set up for NMI to do command.  NMI will use alternate regs
; so set them up with the apprpriate values.
;

	exaf				; exchange af and af
	exx				; and other prime regs
	push h				; save h (really h')
	push b				; save b (really b')
	push psw			; save a (really a')

	mvi c,p$disk$data		; load c with port address
	lhld dmaadr			; get buffer address
	exaf				; put into prime regs
	exx				;


	lda disk$command		; get 1797 command
	call exec$command		; Start. Wait for IREQ & read status
	sta disk$status			; save status for error messages

	exx				; save regs for a second
	exaf				;
	pop psw				; restore a (really a')
	pop b				; restore b (really b')
	pop h				; restore h (really h')
	exx				; put back into prime regs
	exaf				; put af back too

;
; Operation completed.  Status is in location disk$status.
;

	IF	BANKED   
	xra	a   			; Reselect bank 0
	call	?bank       		; 
	ENDIF
	
	pop b				; recover retry counter
	lda disk$status			; get status
	ora a     			; check status. 
	jz fd$exit			; If no error, exit          
	JMP CHK$ERROR

	DSEG

;
; Check error type.  If write protect violation or time out,
; or not ready, don't bother retrying.
;

CHK$ERROR:
	ani 1100$0000b			; Not ready or write protect?
	jnz fd$error			; jump if yes

	lda disk$status			; get status again
	ani 0001$0000b			; see if record not found error
	cnz seeker    			; if rec not found, may need to force seek

	dcr c				; decrement retry count
	jz fd$error			; If failed 4 times, exit

	mov a,c				;  
	cpi 02				; If <2 retries
	jp retry$operation		; then retry

;
; If >2 retries have already been done, force a head restore.  This
; is done by seeking track 5, then restore to assure head travel.
; This should cure persistent lint on the heads as well as seek
; errors.
;

	mvi a,5				; track 5
	call seeker    			; seek it
	call home			; home
	lda trk				; Get track back
	Call seeker    			; seek it
	jmp retry$operation		; then retry
	page
;
; Error Handling...
;

FD$ERROR:

;
; suppress error message if BDOS is returning errors to application...
;

	lda	login$flag		; Logging in?
	ora	a			; 
	jrnz	hard$err$1		; If yes, don't print msg

 	lda @ermde 
	cpi 0FFh 
	jrz hard$error

;
; Had permanent error, print message like:
;
;	 BIOS Err on d: T-nn, S-mm, <operation> <type>, Retry ?
;


	call	?pderr			; print message header

	lhld operation$name ! call ?pmsg	; last function

		; then, messages for all indicated error bits

	lda disk$status			; get status byte from last error
	cpi 0ffh			; time out error?
	jrz err$timeout			; special message
	lxi h,error$table		; point at table of message addresses
errm1:
	mov e,m ! inx h ! mov d,m ! inx h ; get next message address
	add a ! push psw		; shift left and push residual bits with status
	xchg ! cc ?pmsg ! xchg		; print message, saving table pointer
	pop psw	! jrnz errm1		; if any more bits left, continue

errm2	lxi h,error$msg ! call ?pmsg	; print "<BEL>, Retry (Y/N) ? "
	call u$conin$echo		; get operator response
	cpi 'Y' ! jz more$retries	; Yes, then retry 10 more times

;
; Error noted.  Ask user if disk should be relogged.
;
hard$error:
	lda	disk$status		; Get error value   
	ani	0100$0000b		; Write protected?
	jrnz	hard$err$1		; Jump if yes
	lxi	h,New$disk$msg		; Ask if new disk
	call	?pmsg			;
	call	U$conin$echo		; Get user response
	cpi	'Y'			; YES?
	jrnz	hard$err$1		; Jump if not
	mvi	a,0ffh			; Else, force login
	jmp	fd$exit			; then exit    

hard$err$1:				; otherwise,
	lda	disk$status		; Get status byte
	cpi	0100$0000b		; Write protect error?
	mvi a,1 			; 	return hard error to BDOS
	jnz	fd$exit			; Not write protect error
	inr	a			; Write protect error
	jmp	fd$exit
err$timeout
	lxi h,time$out			; point to timeout message
	call ?pmsg			; Display message
	jr errm2			; Ask for user response

	page

	DSEG

;
; Subroutine to seek to home track      
;
home:

	mvi a,08h				; home, hld, no verify
	jmp seek$20			;    

;
; Seeker
; This routine seeks a track in A 
;

seeker:
	push	psw			; Save destination track

	lda	tpi			; Get TPI
	ora	a			; Is it 48?
	jrnz	seek$15			; Jump if not

	
;
; Must double track info for 48tpi disks
;

	in	p$disk$track		; Read in current track
	ora	a			; Clear carry
	ral				; *2
	out	p$disk$track		; Set track reg

	pop	psw			; Get desired track
	ora	a			; clear carry
	ral				; *2
	jr	seek$16			; Seek it

seek$15:	
	pop	psw			; Restore track
seek$16:
	out p$disk$data			; send out track
	mvi a,018h			; seek, hld, verify

;
; Routines for seek and home
;

seek$20
	out p$disk$control		; send command from A
;
; Delay at least 24 uSec after command
;

	mvi a,09			;
seek$delay
	dcr a				;.
	jnz seek$delay			;

;
; Wait for completion
;

seek$30
	in p$disk$control		; get status byte
	rrc				; Ready?
	jc seek$30			; loop until ready

;
; Return with A= status byte
;

	in p$disk$control		; read in status         

;
; Delay 18mS to allow for settling time
;

	lxi d,01400h			;
seek$delay2
	dcr	e			;
	jnz seek$delay2			; 896 uS
	dcr d				;
	jnz seek$delay2			; 20*896=18 mS

	push	psw			; save status
	lda	trk			; Get trk
	out	p$disk$track		; Save in track reg
	pop	psw			; Restore status
	ret

	page

	CSEG

;
; This routine actually executes the read or write command.  An initial
; read (or write) is sent out to the controller.  Since we are not 
; doing multiple sectors, an interrupt will be generated at the end of    
; the command.  This invokes the NMI set up at the beginning of the
; routine.  Either an INI or OUTI will be performed, depending on whether
; a read or write is invoked.  This lets us read in an entire sector 
; more efficiently.  
;

exec$command:				

	out p$disk$control		; send 1797 command

;
; Wait at least 24 usec after command before doing anything.
;

	mvi a,09
exec$delay
	dcr a
	jnz exec$delay			; (delays 31 usec)

;
; Now, wait for completion, but TIME OUT after 1.2 seconds.
;

	lxi d,60000+1
exec$0
	in p$disk$control		; get status
	rrc				; check not ready flag
	jnc exec$success		; if 0, successful completion

	inx d				; (waste time)
	dcx d				;
	inx d				;
	dcx d				;

	dcx d				; decrement count
	mov a,d				;
	ora e				;
	adi 0ffh			;
	jc exec$0			; 20 us*60000=1.2 seconds

;
; Time out.  Set A=0FFH and exit.
;

	mvi a,0d0h			; Reset FDC
	out p$disk$control		; send it out

	mvi a,0ffh			; Set time out flag
	jr exec$exit

;
; Successful completion.  Return w/status byte in A.


exec$success
	in p$disk$control		; Get status byte
exec$exit
	push	psw			; Save status
	call	start$motor$timer	; Start timer   
	pop	psw			;

	ret
	page
;
; Start up motor timer
;

Start$motor$timer:
	di				; DI while changing counter
	mvi	a,127			; Start counter
	sta	motor$counter		;
	mvi	a,all$ints		; Turn on Vert int
	out	p$clk$portb		; (it will count down for us)
	ei				; EI

	RET
;
; Exit from routine.
; Must set up interrupts appropriately.
;
fd$exit:
	push psw			; save status
	
	in p$disk$track			; read track
	out p$disk$data			; write out data

;
; Restore nmi locations
;

	IF	BANKED
	lda	@dbnk			; Point to bank
	call	?bank			; Switch to it
	ENDIF

	lxi d,nmi			; Point at nmi
	lxi h,nmibuf			; and at save buffer
	lxi b,8				; load count
	ldir				; move saved data back

	IF	BANKED		
	lda	@cbnk			; Point back to code bank
	call	?bank			; Switch back
	ENDIF

	in	p$disk$bits		; Get disk bits
	ori	0000$1111b		; Deselect drive
	out	p$disk$bits		; Send out

	mvi a,0d0h			;
	out p$disk$control		; Reset disk controller    

	pop	psw
	ora	a			; set flags
	ret				; and exit!!

	DSEG

;
; Set up for reading the label
;
read$label:
	push	d		; Save addr of XDPH
	call	read$setup	; set up for read
	shld operation$name	; store for error msg
	sta	disk$command	; as command to execute
	mvi	a,0ffh
	sta	login$flag
	mvi	c,3		;allow only 3 retries
	call	retry$operation ; do it
        pop	d		;restore xdph	 
	ret

	CSEG

read$setup:
	IF	BANKED    
	lda	@dbnk
	call	?bank
	ENDIF
	call nmi$setup			; set up nmi (invarient part)
	lxi h,0a2edh			; "INI"
	shld nmi+2			; store read portion
	IF	BANKED   
	lda	@cbnk
	call	?bank
	ENDIF
	lxi h,read$msg			; point at " Read "
	mvi a,82h             		; 1797 read 
	ret

write$setup:
	IF	BANKED   
	lda	@dbnk
	call	?bank			; Switch banks
	ENDIF
	call nmi$setup			; set up nmi (invarient part)
	lxi h,0a3edh			; "OUTI"
	shld nmi+2			; store write portion
	IF	BANKED    
	lda	@cbnk			; Get CBANK back
	call	?bank			; restore it
	ENDIF
	lxi h,write$msg			; point at " Write "
	mvi a,0A2h            		; 1797 write 
	ret



;
; Set up NMI
; NMI (non-maskable interrupt) occurs at fixed location 0066h.
; During normal run time NMI does not occur, so these locations
; are normal RAM.  During diskette data transfers, NMI is
; triggered by the diskette Data Request signal, so the NMI
; locations are temporarily overlayed by intructions to process 
; the interrupt.
;
nmi	equ	0066h

nmi$setup:
	mvi	a,fdc$reset		; Reset FDC
	out	p$disk$control		;

	dcx	d			; Point to TYPE field of XDPH
	ldax	d			; Get value
	push	psw			; (save)
	ani	1			; Mask # sides
	sta	no$of$sides		; store

	pop	psw			; Get type
	ani	0000$0010b		; Mask TPI field
	rar				; Rotate into bit 0
	sta	TPI			; store

	lxi d,nmibuf			; point to storage area
	lxi h,nmi			; original values
	lxi b,8				; set up length
	ldir				; save them away

	lxi h,0d908h			; "EX AF,AF'"
	shld nmi			; beginning of nmi
	shld nmi+4			; also, end of nmi
	lxi h,045edh			; "RETN"
	shld nmi+6			; 

	mvi	a,3			; Enable FDC interrupt
	out	p$8255$control		;

	ret

	CSEG

;
; Floppy completion interrupt.
;
firq:	push psw			; save A
	in p$disk$control		; relieve interrupt
	IF	REAL$1050
	mvi	a,int$initial
	out	int$port 		; Init int port
	ENDIF
	pop	psw
	ei
	ret 

	CSEG
;
; Vertical retrace interrupt.
; Counts down until MOTOR$COUNTER=0, at which point it
; turns off the motor and masks out this interrupt.
;
VERT$INT:
	push	psw			; Save A
	push	h			; and H

	out	vert$clear		; Clear interrupt
	lxi	h,motor$counter		; Point to counter
	dcr	m			; Decrement
	jrnz	vert$exit		; Do nothing till it hits 0

	in p$disk$bits			; Get 8255 bits
	ori	0100$0000b		; Turn off motor
	out	p$disk$bits		; Send it back out

	mvi	a,int$mask		; Mask out this interrupt
	out	p$clk$portb		;

vert$exit:
	mvi	a,int$initial		; Reinit interrupt controller
	out	int$port		;

	pop	h			; Restore H
	pop	psw			; and A
	ei				; Reenable interrupts
	ret				; and return
	page

	DSEG

u$conin$echo:				; get console input, echo it
					; and shift to upper case
	call ?const ! ora a ! jrz u$c1	; see if any char already struck
	call ?conin ! jr  u$conin$echo	; yes, eat it and try again
u$c1:
	call ?conin ! push psw
	mov c,a ! call ?cono
	pop psw ! cpi 'a' ! rc
	sui 'a'-'A'			; make upper case
	push	psw			; Save character
	lxi	h,cr$lf			; Send out CR LF
	call	?pmsg			;
	pop	psw			; restore character	
	ret


;
; Set up misc 8255 command
;
; Bit 7=0; Bit 6=0 means turn motor on.
; Set up drive select in bits 0-3.

set$up$8255:
	lda	@rdrv			; get relative drive
	inr	a			; increment
	cpi	03			;
	jm	fd$40			;
	ani	06			;
	add	a			; Double it
fd$40	xri	0Fh			; bit=0 => on

	mov	b,a			; save in b
 
;
; Set up Bit 4 (side select).
; If double sided, consecutive tracks use alternate sides 
; of the disk
;
 
	lda	@trk			; Get track
	sta	trk			; store it

	lda	no$of$sides		; Get # sides
	ora	a			; Is it double sided?
	jrz	fsel$1			; Jump if not

 	lda	@trk			; get track
	push	psw			; save it
	rar				; rotate into place
	sta	trk			; store
	pop	psw			; restore track
	ani	1			; mask off other bits
	jrz	fsel$1			; If side 0, ok
	mvi	a,010h			; Else, set side 1 bit
	ora	b			; or w/b-reg
	mov	b,a			; save in b again

;
; Set up bit 5 for write precompensation.  (Write precomp is
; necessary for outer tracks, so check against constant specified
; by disk manufacturer.)
;

fsel$1	lda	trk			; get track
	lxi	h,precomp$limit		; and precomp limit
	cmp	m			; is it 
DRVTBL.ASM
	public @dtbl
	extrn fddd0,fddd1
;	extrn	winc0
	cseg

@dtbl	dw fddd0			; A drive = floppy
	dw fddd1			; B drive = floppy
	dw 0				; C drive 
	dw 0				; D drive
	dw 0     			; E drive 
	dw 0				; F drive        
;	dw winc0			; G drive 
	dw 0				; G drive
	dw 0,0,0,0,0,0,0,0,0		; drives H-P non-existant

	end
ECHOVERS.ASM
	; ECHOVERS RSX

pstring	equ	9			; string print function
cr	equ	0dh
lf	equ	0ah
;
;		RSX PREFIX STRUCTURE
;
	db	0,0,0,0,0,0		; room for serial number
	jmp	ftest			; begin of program
next	db	0c3H			; jump
        dw	0			; next module in line
prev:	dw	0			; previous module
remov:	db	0ffh			; remove flag set
nonbnk:	db	0
	db	'ECHOVERS'
space:	ds	3

ftest:					; is this function 12?
	mov 	a,c 
	cpi 	12 
	jz 	begin			; yes - intercept
        jmp 	next			; some other function 

begin:
	lxi 	h,0	
	dad 	sp 			;save stack
	shld 	ret$stack
	lxi 	sp,loc$stack

	mvi 	c,pstring 
	lxi 	d,test$msg		; print message
	call 	next			; call BDOS

	lhld 	ret$stack 		; restore user stack
	sphl
	lxi 	h,0031h			; return version number = 0031h
	ret

test$msg:
	db	cr,lf,'**** ECHOVERS **** $'
ret$stack:	
	dw	0
	ds	32			; 16 level stack
loc$stack:
	end
ENDER.ASM
	public	endtag
	dseg
endtag	equ	$
INTERRUP.ASM
	PUBLIC	INT$VECT
;
;  This module is a dummy module which is used
;  to assure that the locations starting at    
;  0FFF0h are reserved for interrupt vectors

	ASEG
	org	0fff0h

INT$VECT:
	ds	2			; Expansion interface A
	ds	2			; Expansion interface B
	ds	2			; Display processor interface
	ds	2			; Vertical Clock
	ds	2			; Floppy disk interface
	ds	2			; Keyboard interface
	ds	2			; Winchester interface
	ds	2			; Async Interface
	end
LABEL.ASM
	EXTRN	ENDTAG
; Label sector for disks for the Visual 1050              

 X EQU 0

;ANCHOR 0	/SIGNATURE
;------------------------------------------------------------------------------
; The following field said "FMT0" on the Amigo-formatted diskettes
;------------------------------------------------------------------------------
 DB 'FMT1'

;ANCHOR 4	/FORMAT

 DW 512		;SECTOR SIZE
 DB 10		;# SECTORS
 DB 1		;# HEADS
 DW 80		;# TRACKS
 DB 3		;TRANSPARENT SKEW
;------------------------------------------------------------------------------
; The following field (TPI) was not used on FMT0.  Since the byte was unused,
; it had a value of 0.  A value of 0 will be interpreted to mean 48 TPI.
; A value of 1 will be interpreted to mean 96 TPI.
;------------------------------------------------------------------------------
 DB 1		; TPI
 DB X,X,X,X
 DB X,X,X,X

;ANCHOR 20	/O.S.
; (Bytes 20-27 used by COPYSYS to generate bootable system)

 DW 2080h	;LOAD BEGIN ADDRESS
 DW ENDTAG-2080h   	;LOAD LENGTH
 DW 2080h	;JUMP ADDRESS
 DW 128		;BYTE OFFSET TO SYSTEM
 DB 1		;# HEADS
 DB X,X,X	;RESERVED

;ANCHOR 32	;Copy of CP/M Plus DPB

 DW 40		;# 128 BYTE RECORDS/TRACK
 DB 4		;LOG2(2048/128)
 DB 15		;(2048/128)-1
 DB 1		; EXM=1 
 DW 194		;(390K/2048)-1 (HIGHEST BLOCK #)
 DW 127		;(DIRS-1)
 DB 11000000B,00000000B
		;2048/32=64 DIRS/BLOCK. DIRS/64=2BLOCK 2 BIT    
 DW 32		;(DIRS)/4 (GIVES CSV SIZE)
 DW 2		;NUMBER OF SYSTEM TRACKS

 DB 1		; non-transparent skew (this field not in DPB)

 DB 2		;Physical Record shift factor 
 DB 3		;Physical Record Mask 



;(HOST-MONITOR)
 DW 2		;TRACK ORIGIN
 DB 0		;HEAD ORIGIN
 DB 1		;# HEADS
 DB X		;
;----------------------------------------------------------------------------
; The following byte was unused on under FMT0.  We will use it to tell
; how sides are to be read on a double-sided disk.  A 0 will mean 
; alternating heads.
;----------------------------------------------------------------------------
 DB X		;ORDER (Not applicable since this is single sided disk)

;ANCHOR 56	/OPTIONS

 DB 0		;STEP RATE (0=FAST..3=SLOW)
;---------------------------------------------------------------------------
; The followwing field was unused in FMT0.  In FMT1, it will be used to
; indicate the write precomp track.
;---------------------------------------------------------------------------
 DB 0ffh	;Write precomp

 DB    X,X,X,X,X,X,X,X, X,X,X,X,X,X,X,X,X,X
 DB X,X,X,X,X,X,X,X,X,X, X,X,X,X,X,X,X,X,X,X
 DB X,X,X,X,X,X,X,X,X,X, X,X,X,X,X,X,X,X,X,X
 DB X,X,X,X,X,X,X,X,X,X, X,X

;ANCHOR 128
	END
LDRBOOT.ASM
	title	'Boot loader module for CP/M 3.0'

true equ -1
false equ not true

	public	?init,?ldccp,?rlccp,?time
	public  nint, ivect 

	extrn  @civec, @covec, @aivec, @aovec, @lovec, @bnkbf
	extrn	?pmsg,?conin
	extrn 	@cbnk,?bnksl
	extrn	aux$in$ptr, aux$out$ptr, kb$buf$in

	maclib buf
	maclib modebaud
	maclib ports
	maclib z80

bdos	equ 5


	dseg	; init done from banked memory

?init:
	di					; disable interrupts
	lxi h,08000h 				; hl <= device 0
	shld @covec 				; DISPLY = console output

;
; Set up interrupt vectors.  Begin by pointing them all at a null
; interrupt routine so that every interrupt is satisfied in some way.
;

	lxi d,nint				; get address of null vector
 	lxi h,ivect				; point to ivect table
ini$vec:
	mov m,e           			; store low byte of NINT
	inr l					; increment hl
	mov m,d       				; store hi byte of NINT
	inr l					; increment hl
	jrnz ini$vec				; do for all

	IF	REAL$1050
	mvi	a,0000$0000b			; Disable all interrupts
	out	p$clk$portb			; Send it out

	mvi	a,int$initial			;
	out	int$port
	ENDIF
	ei					; reenable interrupts

	ret	


?ldccp:
?rlccp:
?time:
	ret
;
; Null interrupt handler
;
	cseg
NINT:
	IF REAL$1050
	push psw
	mvi	a,int$initial
	out	int$port
	pop psw
	ENDIF
	ei
	ret


	aseg
	org	0ffe0h           
ivect	ds	32		; 32-byte interrupt vector


	end
LDRDRV.ASM
	title 'Diskette Handler Module'
;    CP/M-80 Version 3     --  Modular BIOS

;	Disk I/O Module 


    ; Port Address Equates

	maclib	vislib
	maclib ports
	maclib	modebaud

    ; CP/M 3 Disk definition macros

	maclib cpm3

    ; Z80 macro library instruction definitions

	maclib Z80

    ; Disk drive dispatching tables for linked BIOS

	public	fddd0,fddd1
	public u$conin$echo, error$table

    ; Variables containing parameters passed by BDOS

	extrn	@adrv,@rdrv
	extrn	@dma,@trk,@sect
	extrn	@dbnk,@cbnk

    ; System Control Block variables

	extrn	@ermde		; BDOS error mode

    ; Utility routines in standard BIOS

	extrn	?wboot		; warm boot vector
	extrn	?pmsg		; print message @<HL> up to 00, saves <BC> & <DE>
	extrn	?pdec		; print binary number in <A> from 0 to 99.
	extrn	?pderr		; print BIOS disk error header
	extrn	?conin,?cono	; con in and out
	extrn	?const		; get console status
	extrn	ivect
	extrn	?bank


cr	equ 13
lf	equ 10
bell	equ 7

	page
    ; Extended Disk Parameter Headers (XPDHs)

	cseg

	dw	fd$write
	dw	fd$read
	dw	fd$login
	dw	fd$init
	db	0   			; relative drive zero
	db	2			; TYPE field
fddd0:              
	dw	trandd			; Translate table address
	db	0,0,0,0,0,0,0,0,0	; Bdos scratch area
	db	0			; Media flag
	dw	dpbd0			; Disk parameter block
	dw	0fffeh			; Checksum vector
	dw	0fffeh			; Allocation vector
	dw	dirbcb			;
	dw	datbcb			;
	dw	0fffeh			; Hash      
	db	0			; Hash bank


	dw	fd$write
	dw	fd$read
	dw	fd$login
	dw	fd$init
	db	1  			; relative drive one
	db	02			; TYPE field
fddd1:              
	dw	trandd			; Translate table address
	db	0,0,0,0,0,0,0,0,0	; Bdos scratch area
	db	0			; Media flag
	dw	dpbd1			; Disk parameter block
	dw	0fffeh			; Checksum vector
	dw	0fffeh			; Allocation vector
	dw	dirbcb
	dw	datbcb
	dw	0fffeh			; Hash      
	db	0			; Hash bank



	cseg	; DPB must be resident
dpbd0	
	dw	0028h		; #128 byte records/track
	db	04,0fh		; block shift and mask
	db	1		; extent mask
	dw	194  		; maximum block number
	dw	127		; maximum dir entry #
	db	0C0h,00h	; alloc vector for directory
	dw	32   		; checksum size
	dw	2		; offset for sys tracks
	db	2,3		; physical sector size shift

dpbd1	
	dw	0028h		; #128 byte records/track
	db	04,0fh		; block shift and mask
	db	1		; extent mask
	dw	194  		; maximum block number
	dw	127		; maximum dir entry #
	db	0C0h,00h	; alloc vector for directory
	dw	32   		; checksum size
	dw	2		; offset for sys tracks
	db	2,3		; physical sector size shift

	
	dseg

;
; Directory buffer control block
;

dirhead	dw	dirbcb

dirbcb:	db	0ffh		; DRV - Drive with record in buf
	db	0,0,0		; Rec #
	db	0		; wflg
	db	0		; Scratch byte
	dw	0		; Track
	dw	0		; Sector
	dw	dirbf		; Buffer address
	db	0		; Bank
	dw	0		; Link
	

dirbf:	ds	512
	
	cseg
;
; Data buffer control block
;

dathead	dw	datbcb

datbcb:	db	0ffh		; Drive
	db	0,0,0		; Record #
	db	0		; Wflg
	db	0		; Scratch byte
	dw	00		; Track
	dw	0		; Sector
	dw	datbf		; Buffer address
	db	0		; Bank
	dw	0		; Link

datbf:	ds	512


trandd	skew	10,1,1

	page

    ; Disk I/O routines for standardized BIOS interface

; Initialization entry point.

;		called for first time initialization.


fd$init:
	mvi a,fdc$reset		;reset
	out p$disk$control	;do it
	ret
	page

fd$login:
		; This entry is called when a logical drive is about to
		; be logged into for the purpose determining what type    
		; of disk is in use.

		; It may adjust the parameters contained in the disk
		; parameter header pointed at by <DE>
		
		; The value of XDPH-1 (TYPE field) is adjusted to reflect
		; the type of disk.  This is determined by reading the
		; disk label.

	push	d		; Save address of XDPH
	lda	@ermde		; Get error mode
	sta	save$mode	; save it
	mvi	a,0ffh		; Force to not display msgs
	sta	@ermde		; store

	lxi h,datbf             ; point to dma area
	shld	dmaadr		; store
	lxi h,fd0$access	; assume A drive
	lded @rdrv		; Get drive
	xra	a		; a=0
	mov	d,a		; Clear D
	dad d			; Point to correct flag
	pop	d		; Restore address of XDPH
login$10:
	mvi a,0ffh		; flag=ff
	mov m,a			; reset last track
	lda @rdrv		; Get relative drive
	inr	a		; increment
	xri 0fh			; bit=0 => on
	sta select$mask		; save command
	mvi	a,0ffh		; Clear "last" flags
	sta old$track		;
	xra	a		; a=0
	sta trk			; Going to Track 0
	inr	a		; a=1
	sta	sect		; Sector 1
;
; Set up for reading the label
;
	push	d		; Save addr of XDPH
	call nmi$setup		; set up nmi (invarient part)
	lxi h,0a2edh		; "INI"
	shld nmi+2		; store read portion
	lxi h,read$msg		; Point to "Read"
	shld operation$name	; store for error msg
	mvi	a,82h		; Store read 
	sta	disk$command	; as command to execute
	call	more$retries	; do it
	jrnz	bad$exit	; Jump if problem

;
; Check that disk has our "signature"
;

	lxi	b,0003		; count =3
	lxi	h,datbf		; Point to signature on disk
	lxi	d,signature	; and our recognized one
back	ldax	d		; get signature char
	cci			; compare
	inx	d		; increment de
	jrnz	notok  		; jump if no match
	jpe	back		; if bc<>0, keep going
	
	mov	a,m		; Get next character
	cpi	'0'		; Is it '0'?
	jrz	login$30	; If yes, it's ok
	cpi	'1'		; Is it '1'?
	jrnz	notok		; If not, it's bad

;
; Set up fields in TYPE field as follows:        
;  
; Bit 0 : 1=2 sides
;         0=1 side
; Bit 1 : 1=96 TPI
;         0=48 TPI
; Bit 2 : unused
; Bit 3 : unused
; Bit 4 : unused 
; Bit 5 : unused
; Bits 6-7: step rate
;

login$30:
	pop	d			; Restore address of XDPH
	dcx	d			; Point to type field

	lxi	h,datbf+no$of$heads	;
	mov	a,m			; Get # sides
	dcr	a			; Decrement
	mov	b,a			; Save in B

	lxi	h,datbf+tpi$offset	; Get tpi from label
	mov	a,m			;

	ora	a			; clear carry
	ral				; Move to bit 1
	ora	b			; OR with # sides
	mov	b,a			; Save in B

	lxi	h,datbf+step$offset	; Get step rate
	mov	a,m			;
	db      0fh			; Into bits 6&7
	db      0fh			;
	ora	b			; OR with others
	stax	d			; store in TYPE field

;
; Move label info into appropriate DPH
;

	lxi	b,15		; # bytes to move
	lxi	h,datbf+32	; FROM address
	lxi	d,dpbd0		; Assume drive 0
	lda @rdrv		; check it
	ora	a		;
	jz	login$67	; Jump if drive 0
	lxi	d,dpbd1		; Set to drive 1
login$67:
	ldir			; move
	inx	h		; skip skew
	ldi			; Then move in 2 more
	ldi			;
	jr	login$exit	; exit 

notok:
	pop	b		; Restore stack
	lxi	h,nomatch	; Error, print message
	call ?pmsg
	jr	login$exit

bad$exit:
	pop	b
login$exit:
	lda	save$mode	; Get saved value of @ermde
	sta	@ermde		; restore it
	xra	a		; Clear A
	ret

save$mode	ds	1
no$of$heads	equ	53	;Offset into label
step$offset	equ	56	;
tpi$offset	equ	11	;

signature	db	'FMT' 
nomatch	db	'***WARNING - Disk format not recognized***',13,10,0

	page

	cseg

; disk READ and WRITE entry points.

		; these entries are called with the following arguments:

			; relative drive number in @rdrv (8 bits)
			; absolute drive number in @adrv (8 bits)
			; disk transfer address in @dma (16 bits)
			; disk transfer bank	in @dbnk (8 bits)
			; disk track address	in @trk (16 bits)
			; disk sector address	in @sect (16 bits)
			; pointer to XDPH in <DE>

		; they transfer the appropriate data, perform retries
		; if necessary, then return an error code in <A>
fd$read:
	call nmi$setup			; set up nmi (invarient part)
	lxi h,0a2edh			; "INI"
	shld nmi+2			; store read portion
	lxi h,read$msg			; point at " Read "
	mvi a,82h             		; 1797 read 
	jr  rw$common

fd$write:
	call nmi$setup			; set up nmi (invarient part)
	lxi h,0a3edh			; "OUTI"
	shld nmi+2			; store write portion
	lxi h,write$msg			; point at " Write "
	mvi a,0A2h            		; 1797 write 


rw$common:				; seek to correct track (if necessary),
					;	and issue 1797 command.
 

	shld operation$name		; save message for errors
	mov b,a				; put read or write into B
	lda	@sect			; Get sector
	sta	sect			; save it
	lhld	@dma
	shld	dmaadr

	lda	no$of$sides		; Get # sides
	ora	a 			; Check it
	jrz 	rw$26			; Jump if single-sided
	lda @trk			; get track
	ani 01h				; low bit = side
	add	a			;
	add	a			;
	add	a			; *8
rw$26	ora b				; OR in w/read or write
	sta disk$command		; save 1797 command
	page
;
; Will need to know info on last access to disk.  Move info into
; old$track        
;
	lxi h,fd0$access		; FROM address
	lded @rdrv			; Get relative drive
	xra	a			; Clear a
	mov	d,a			; Use it to clear d
	dad d				; add      
	lxi d,old$track			; TO address
fd$20	ldi				; move in track
  
;
; Set up misc 8255 command
;
; Bit 7=0; Bit 6=0 means turn motor on.
; Set up drive select in bits 0-3.

	lda	@rdrv			; get relative drive
	inr	a			; increment
	cpi	03			;
	jm	fd$40			;
	ani	06			;
	add	a			; Double it
fd$40	xri	0Fh			; bit=0 => on

	mov	b,a			; save in b
 
;
; Set up Bit 4 (side select).
; If double sided, consecutive tracks use alternate sides 
; of the disk
;
 
	lda	@trk			; Get track
	sta	trk			; store it

	lda	no$of$sides		; Get # sides
	ora	a			; Is it double sided?
	jrz	fsel$1			; Jump if not

 	lda	@trk			; get track
	push	psw			; save it
	rar				; rotate into place
	sta	trk			; store
	pop	psw			; restore track
	ani	1			; mask off other bits
	jrz	fsel$1			; If side 0, ok
	mvi	a,010h			; Else, set side 1 bit
	ora	b			; or w/b-reg
	mov	b,a			; save in b again

;
; Set up bit 5 for write precompensation.  (Write precomp is
; necessary for outer tracks, so check against constant specified
; by disk manufacturer.)
;

fsel$1	lda	trk			; get track
	lxi	h,precomp$limit		; and precomp limit
	cmp	m			; is it 4 retries have already been done, force a head restore.  This
; is done by seeking track 5, then restore to assure head travel.
; This should cure persistent lint on the heads as well as seek
; errors.
;

	mvi a,5				; track 5
	call seeker    			; seek it
	call home			; home
	lda trk				; Get track back
	Call seeker    			; seek it
	jmp retry$operation		; then retry
	page
;
; Error Handling...
;

FD$ERROR:

;
; suppress error message if BDOS is returning errors to application...
;


 	lda @ermde 
	cpi 0FFh 
	jrz hard$error

;
; Had permanent error, print message like:
;
;	 BIOS Err on d: T-nn, S-mm, <operation> <type>, Retry ?
;


	call	?pderr			; print message header

	lhld operation$name ! call ?pmsg	; last function

		; then, messages for all indicated error bits

	lda disk$status			; get status byte from last error
	cpi 0ffh			; time out error?
	jz err$timeout			; special message
	lxi h,error$table		; point at table of message addresses
errm1:
	mov e,m ! inx h ! mov d,m ! inx h ; get next message address
	add a ! push psw		; shift left and push residual bits with status
	xchg ! cc ?pmsg ! xchg		; print message, saving table pointer
	pop psw	! jnz errm1		; if any more bits left, continue

errm2	lxi h,error$msg ! call ?pmsg	; print "<BEL>, Retry (Y/N) ? "
	call u$conin$echo		; get operator response
	cpi 'Y' ! jz more$retries	; Yes, then retry 10 more times
hard$error:				; otherwise,
	lda	disk$status		; Get status byte
	cpi	0100$0000b		; Write protect error?
	mvi a,1 			; 	return hard error to BDOS
	jnz	fd$exit			; Not write protect error
	inr	a			; Write protect error
	jmp	fd$exit
err$timeout
	lxi h,time$out			; point to timeout message
	call ?pmsg			; Display message
	jr errm2			; Ask for user response

	page
;
; Subroutine to seek to home track      
;
home:
	lda	step$rate		; Get step rate   
home$0
	ori 08h				; home, hld, no verify
	jmp seek$20			;    

;
; Seeker
; This routine seeks a track in A at the given step rate
;

seeker:
	push	psw			; Save destination track

	lda	tpi			; Get TPI
	ora	a			; Is it 48?
	jrnz	seek$15			; Jump if not

	
;
; Must double track info for 48tpi disks
;

	in	p$disk$track		; Read in current track
	ora	a			; Clear carry
	ral				; *2
	out	p$disk$track		; Set track reg

	pop	psw			; Get desired track
	ora	a			; clear carry
	ral				; *2
	jr	seek$16			; Seek it

seek$15:	
	pop	psw			; Restore track
seek$16:
	out p$disk$data			; send out track
	lda	step$rate		; Get step rate
	ori	018h			; seek, hld, verify

;
; Routines for seek and home
;

seek$20
	out p$disk$control		; send command from A
;
; Delay at least 24 uSec after command
;

	mvi a,09			;
seek$delay
	dcr a				;.
	jnz seek$delay			;

;
; Wait for completion
;

seek$30
	in p$disk$control		; get status byte
	rrc				; Ready?
	jc seek$30			; loop until ready

;
; Return with A= status byte
;

	in p$disk$control		; read in status         

;
; Delay 18mS to allow for settling time
;

	lxi d,01400h			;
seek$delay2
	dcr	e			;
	jnz seek$delay2			; 896 uS
	dcr d				;
	jnz seek$delay2			; 20*896=18 mS

	push	psw			; save status
	lda	trk			; Get trk
	out	p$disk$track		; Save in track reg
	pop	psw			; Restore status
	ret

	page
;
; This routine actually executes the read or write command.  An initial
; read (or write) is sent out to the controller.  Since we are not 
; doing multiple sectors, an interrupt will be generated at the end of    
; the command.  This invokes the NMI set up at the beginning of the
; routine.  Either an INI or OUTI will be performed, depending on whether
; a read or write is invoked.  This lets us read in an entire sector 
; more efficiently.  
;

exec$command:				

	out p$disk$control		; send 1797 command

;
; Wait at least 24 usec after command before doing anything.
;

	mvi a,09
exec$delay
	dcr a
	jnz exec$delay			; (delays 31 usec)

;
; Now, wait for completion, but TIME OUT after 1.2 seconds.
;

	lxi d,60000+1
exec$0
	in p$disk$control		; get status
	rrc				; check not ready flag
	jnc exec$success		; if 0, successful completion

	inx d				; (waste time)
	dcx d				;
	inx d				;
	dcx d				;

	dcx d				; decrement count
	mov a,d				;
	ora e				;
	adi 0ffh			;
	jc exec$0			; 20 us*60000=1.2 seconds

;
; Time out.  Set A=0FFH and exit.
;

	mvi a,0d0h			; Reset FDC
	out p$disk$control		; send it out

	mvi a,0ffh			; Set time out flag
	jr exec$exit

;
; Successful completion.  Return w/status byte in A.


exec$success
	in p$disk$control		; Get status byte
exec$exit
	push	psw			; Save status
	call	start$motor$timer	; Start timer   
	pop	psw			;

	ret
	page
;
; Start up motor timer
;

Start$motor$timer:

	RET
;
; Exit from routine.
; Must set up interrupts appropriately.
;
fd$exit:
	push psw			; save status
	
	in p$disk$track			; read track
	out p$disk$data			; write out data

;
; Restore nmi locations
;

	lxi d,nmi			; Point at nmi
	lxi h,nmibuf			; and at save buffer
	lxi b,8				; load count
	ldir				; move saved data back


	mvi a,0d0h			;
	out p$disk$control		; Reset disk controller    

	pop	psw
	ora	a			; set flags
	ret				; and exit!!

;
; Set up NMI
; NMI (non-maskable interrupt) occurs at fixed location 0066h.
; During normal run time NMI does not occur, so these locations
; are normal RAM.  During diskette data transfers, NMI is
; triggered by the diskette Data Request signal, so the NMI
; locations are temporarily overlayed by intructions to process 
; the interrupt.
;
nmi	equ	0066h

nmi$setup:
	mvi	a,fdc$reset		; Reset FDC
	out	p$disk$control		;

	dcx	d			; Point to TYPE field of XDPH
	ldax	d			; Get value
	push	psw			; (save)
	ani	1			; Mask # sides
	sta	no$of$sides		; store

	pop	psw			; Get TYPE again
	push	psw			; Save
	db     07h			; Rotate 6&7into 0&1
	db	07h			;
	ani	0000$0011b		; Mask bits
	sta	step$rate		; store step rate

	pop	psw			; Get type
	ani	0000$0010b		; Mask TPI field
	rar				; Rotate into bit 0
	sta	TPI			; store

	lxi d,nmibuf			; point to storage area
	lxi h,nmi			; original values
	lxi b,8				; set up length
	ldir				; save them away

	lxi h,0d908h			; "EX AF,AF'"
	shld nmi			; beginning of nmi
	shld nmi+4			; also, end of nmi
	lxi h,045edh			; "RETN"
	shld nmi+6			; 

	mvi	a,3			; Enable FDC interrupt
	out	p$8255$control		;

	ret


	cseg

u$conin$echo:	; get console input, echo it, and shift to upper case
	call ?const ! ora a ! jrz u$c1	; see if any char already struck
	call ?conin ! jr  u$conin$echo	; yes, eat it and try again
u$c1:
	call ?conin ! push psw
	mov c,a ! call ?cono
	pop psw ! cpi 'a' ! rc
	sui 'a'-'A'		; make upper case
	ret

	cseg
	IF	REAL$1050
ivect2		equ	0fff8h	;
	ELSE
ivect2		equ	0ffe2h	; address of ivect+2
	ENDIF
nmibuf		ds	8	; buffer to hold prev contents of nmi
disk$command	ds	1	; current wd1797 command
select$mask	ds	1	; current drive select code
old$track	db	0ffh	; last track seeked to
dmaadr		ds	2
sect		ds	1
trk		ds	1	; track for current operation
disk$status	ds	1	; last error status code for messages

fd0$access
fd0$trk		db	0ffh	; last track accessed on A
fd1$trk		db	0ffh	; last track accessed on B

	; error message components

read$msg	db	', Read',0
write$msg	db	', Write',0

operation$name	dw	read$msg

	; table of pointers to error message strings
	;	first entry is for bit 7 of 1797 status byte

error$table	dw	b7$msg
		dw	b6$msg
		dw	b5$msg
		dw	b4$msg
		dw	b3$msg
		dw	b2$msg
		dw	b1$msg
		dw	b0$msg

b7$msg		db	' Not ready,',0
b6$msg		db	' Protect,',0
b5$msg		db	' Fault,',0
b4$msg		db	' Record not found,',0
b3$msg		db	' CRC,',0
b2$msg		db	' Lost data,',0
b1$msg		db	' DREQ,',0
b0$msg		db	' Busy,',0

time$out	db	' Time out,',0

error$msg	db	' Retry (Y/N) ? ',0
precomp$limit	db	43  
no$of$sides	db	0			; # sides
step$rate	db	0
tpi		db	0
motor$counter	db	0
	end
LDRKRNL.ASM
	title	'Root module of relocatable BIOS for CP/M 3.0'

	; version 1.0 15 Sept 82

true	equ -1
false	equ not true

banked	equ false
	

;		  Copyright (C), 1982
;		 Digital Research, Inc
;		     P.O. Box 579
;		Pacific Grove, CA  93950


;   This is the invariant portion of the modular BIOS and is
;	distributed as source for informational purposes only.
;	All desired modifications should be performed by
;	adding or changing externally defined modules.
;	This allows producing "standard" I/O modules that
;	can be combined to support a particular system 
;	configuration.

cr	equ 13
lf	equ 10
bell	equ 7
ctlQ	equ 'Q'-'@'
ctlS	equ 'S'-'@'

ccp	equ 0100h	; Console Command Processor gets loaded into the TPA

	cseg		; GENCPM puts CSEG stuff in common memory


    ; variables in system data page

	extrn @covec,@civec,@aovec,@aivec,@lovec ; I/O redirection vectors
	extrn @mxtpa				; addr of system entry point
	extrn @bnkbf				; 128 byte scratch buffer


    ; user defined character I/O routines

	extrn ?ci,?co,?cist,?cost	; each take device in <B>
	extrn ?cinit			; (re)initialize device in <C>
	extrn @ctbl			; physical character device table

    ; disk communication data items

	extrn @dtbl			; table of pointers to XDPHs
	public @adrv,@rdrv,@trk,@sect	; parameters for disk I/O
	public @dma,@dbnk,@cnt		;    ''       ''   ''  ''

    ; memory control

	public @cbnk			; current bank
	extrn ?xmove,?move		; select move bank, and block move
	extrn ?bank			; select CPU bank

    ; clock support

	extrn	?init
	extrn ?time			; signal time operation

    ; general utility routines

	public ?pmsg,?pdec	; print message, print number from 0 to 65535
	public ?pderr		; print BIOS disk error message header

	maclib modebaud		; define mode bits


    ; External names for BIOS entry points

	public ?boot,?wboot,?const,?conin,?cono,?list,?auxo,?auxi
	public ?home,?sldsk,?sttrk,?stsec,?stdma,?read,?write
	public ?lists,?sctrn
	public ?conos,?auxis,?auxos,?dvtbl,?devin,?drtbl
	public ?mltio,?flush,?mov,?tim,?bnksl,?stbnk,?xmov


    ; BIOS Jump vector.

		; All BIOS routines are invoked by calling these
		;	entry points.

?boot:	jmp boot	; initial entry on cold start
?wboot:	jmp wboot	; reentry on program exit, warm start

?const:	jmp const	; return console input status
?conin:	jmp conin	; return console input character
?cono:	jmp conout	; send console output character
?list:	jmp list	; send list output character
?auxo:	jmp auxout	; send auxilliary output character
?auxi:	jmp auxin	; return auxilliary input character

?home:	jmp home	; set disks to logical home
?sldsk:	jmp seldsk	; select disk drive, return disk parameter info
?sttrk:	jmp settrk	; set disk track
?stsec:	jmp setsec	; set disk sector
?stdma:	jmp setdma	; set disk I/O memory address
?read:	jmp read	; read physical block(s)
?write:	jmp write	; write physical block(s)

?lists:	jmp listst	; return list device status
?sctrn:	jmp sectrn	; translate logical to physical sector

?conos:	jmp conost	; return console output status
?auxis:	jmp auxist	; return aux input status
?auxos:	jmp auxost	; return aux output status
?dvtbl:	jmp devtbl	; return address of device def table
?devin:	jmp ?cinit	; change baud rate of device

?drtbl:	jmp getdrv	; return address of disk drive table
?mltio:	jmp multio	; set multiple record count for disk I/O
?flush:	jmp flush	; flush BIOS maintained disk caching

?mov:	jmp ?move	; block move memory to memory
?tim:	jmp ?time	; Signal Time and Date operation
?bnksl:	jmp bnksel	; select bank for code execution and default DMA
?stbnk:	jmp setbnk	; select different bank for disk I/O DMA operations.
?xmov:	jmp ?xmove	; set source and destination banks for one operation

	jmp 0		; reserved for future expansion
	jmp 0		; reserved for future expansion
	jmp 0		; reserved for future expansion


	; BOOT
	;	Initial entry point for system startup.

	dseg	; this part can be banked

boot:

	mvi c,15	; initialize all 16 character devices
c$init$loop:
	push b ! call ?cinit ! pop b
	dcr c ! jp c$init$loop

	call ?init

	lxi b,16*256+0 ! lxi h,@dtbl	; init all 16 logical disk drives
d$init$loop:
	push b		; save remaining count and abs drive
	mov e,m ! inx h ! mov d,m ! inx h	; grab @drv entry
	mov a,e ! ora d ! jz d$init$next	; if null, no drive
	push h					; save @drv pointer 
	xchg					; XDPH address in <HL>
	dcx h ! dcx h ! mov a,m ! sta @RDRV	; get relative drive code
	mov a,c ! sta @ADRV			; get absolute drive code
	dcx h					; point to init pointer
	mov d,m ! dcx h ! mov e,m		; get init pointer
	xchg ! call ipchl			; call init routine
	pop h					; recover @drv pointer
d$init$next:
	pop b					; recover counter and drive #
	inr c ! dcr b ! jnz d$init$loop		; and loop for each drive
	jmp boot$1

	cseg	; following in resident memory

boot$1:
	call set$jumps
;
;
;	call ?ldccp				; fetch CCP for first time
;	jmp ccp
	ret

	; WBOOT
	;	Entry for system restarts.

wboot:
	call set$jumps		; initialize page zero
;
;	call ?rlccp		; reload CCP
;	jmp ccp			; then reset jmp vectors and exit to ccp
	ret

set$jumps:

  if banked
	mvi a,1 ! call ?bnksl
  endif

	mvi a,JMP
	sta 0 ! sta 5		; set up jumps in page zero
	lxi h,?wboot ! shld 1	; BIOS warm start entry
	lhld @MXTPA ! shld 6	; BDOS system call entry
	ret


		ds 64
boot$stack	equ $


	; DEVTBL
	;	Return address of character device table

devtbl:
	lxi h,@ctbl ! ret


	; GETDRV
	;	Return address of drive table

getdrv:
	lxi h,@dtbl ! ret



	; CONOUT
	;	Console Output.  Send character in <C>
	;			to all selected devices

conout:	

	lhld @covec	; fetch console output bit vector
	jmp out$scan


	; AUXOUT
	;	Auxiliary Output. Send character in <C>
	;			to all selected devices

auxout:
	lhld @aovec	; fetch aux output bit vector
	jmp out$scan


	; LIST
	;	List Output.  Send character in <C>
	;			to all selected devices.

list:
	lhld @lovec	; fetch list output bit vector

out$scan:
	mvi b,0		; start with device 0
co$next:
	dad h		; shift out next bit
	jnc not$out$device
	push h		; save the vector
	push b		; save the count and character
not$out$ready:
	call coster ! ora a ! jz not$out$ready
	pop b ! push b	; restore and resave the character and device
	call ?co	; if device selected, print it
	pop b		; recover count and character
	pop h		; recover the rest of the vector
not$out$device:
	inr b		; next device number
	mov a,h ! ora l	; see if any devices left
	jnz co$next	; and go find them...
	ret


	; CONOST
	;	Console Output Status.  Return true if
	;		all selected console output devices
	;		are ready.

conost:
	lhld @covec	; get console output bit vector
	jmp ost$scan


	; AUXOST
	;	Auxiliary Output Status.  Return true if
	;		all selected auxiliary output devices
	;		are ready.

auxost:
	lhld @aovec	; get aux output bit vector
	jmp ost$scan


	; LISTST
	;	List Output Status.  Return true if
	;		all selected list output devices
	;		are ready.

listst:
	lhld @lovec	; get list output bit vector

ost$scan:
	mvi b,0		; start with device 0
cos$next:
	dad h		; check next bit
	push h		; save the vector
	push b		; save the count
	mvi a,0FFh	; assume device ready
	cc coster	; check status for this device
	pop b		; recover count
	pop h		; recover bit vector
	ora a		; see if device ready
	rz		; if any not ready, return false
	inr b		; drop device number
	mov a,h ! ora l	; see if any more selected devices
	jnz cos$next
	ori 0FFh	; all selected were ready, return true
	ret

coster:		; check for output device ready, including optional
		;	xon/xoff support
	mov l,b ! mvi h,0	; make device code 16 bits
	push h			; save it in stack
	dad h ! dad h ! dad h	; create offset into device characteristics tbl
	lxi d,@ctbl+6 ! dad d	; make address of mode byte
	mov a,m ! ani mb$xonxoff
	pop h			; recover console number in <HL>
	jz ?cost		; not a xon device, go get output status direct
	lxi d,xofflist ! dad d	; make pointer to proper xon/xoff flag
	call cist1		; see if this keyboard has character
	mov a,m ! cnz ci1	; get flag or read key if any
	cpi ctlq ! jnz not$q	; if its a ctl-Q,
	mvi a,0FFh 		;	set the flag ready
not$q:
	cpi ctls ! jnz not$s	; if its a ctl-S,
	mvi a,00h		;	clear the flag
not$s:
	mov m,a			; save the flag
	call cost1		; get the actual output status,
	ana m			; and mask with ctl-Q/ctl-S flag
	ret			; return this as the status

cist1:			; get input status with <BC> and <HL> saved
	push b ! push h 
	call ?cist
	pop h ! pop b
	ora a
	ret

cost1:			; get output status, saving <BC> & <HL>
	push b ! push h
	call ?cost
	pop h ! pop b
	ora a
	ret

ci1:			; get input, saving <BC> & <HL>
	push b ! push h
	call ?ci
	pop h ! pop b
	ret


	; CONST
	;	Console Input Status.  Return true if
	;		any selected console input device
	;		has an available character.

const:
	lhld @civec	; get console input bit vector
	jmp ist$scan


	; AUXIST
	;	Auxiliary Input Status.  Return true if
	;		any selected auxiliary input device
	;		has an available character.

auxist:
	lhld @aivec	; get aux input bit vector

ist$scan:
	mvi b,0		; start with device 0
cis$next:
	dad h		; check next bit
	mvi a,0		; assume device not ready
	cc cist1	; check status for this device
	ora a ! rnz	; if any ready, return true
	inr b		; drop device number
	mov a,h ! ora l	; see if any more selected devices
	jnz cis$next
	xra a		; all selected were not ready, return false
	ret


	; CONIN
	;	Console Input.  Return character from first
	;		ready console input device.

conin:
	lhld @civec
	jmp in$scan


	; AUXIN
	;	Auxiliary Input.  Return character from first
	;		ready auxiliary input device.

auxin:
	lhld @aivec

in$scan:
	push h		; save bit vector
	mvi b,0
ci$next:
	dad h		; shift out next bit
	mvi a,0		; insure zero a  (nonexistant device not ready).
	cc cist1	; see if the device has a character
	ora a
	jnz ci$rdy	; this device has a character
	inr b		; else, next device
	mov a,h ! ora l	; see if any more devices
	jnz ci$next	; go look at them
	pop h		; recover bit vector
	jmp in$scan	; loop til we find a character

ci$rdy:
	pop h		; discard extra stack
	jmp ?ci


;	Utility Subroutines


ipchl:		; vectored CALL point
	pchl


?pmsg:		; print message @<HL> up to a null
		; saves <BC> & <DE>
	push b
	push d
pmsg$loop:
	mov a,m ! ora a ! jz pmsg$exit
	mov c,a ! push h
	call ?cono ! pop h
	inx h ! jmp pmsg$loop
pmsg$exit:
	pop d
	pop b
	ret

?pdec:		; print binary number 0-65535 from <HL>
	lxi b,table10! lxi d,-10000
next:
	mvi a,'0'-1
pdecl:
	push h! inr a! dad d! jnc stoploop
	inx sp! inx sp! jmp pdecl
stoploop:
	push d! push b
	mov c,a! call ?cono
	pop b! pop d
nextdigit:
	pop h
	ldax b! mov e,a! inx b
	ldax b! mov d,a! inx b
	mov a,e! ora d! jnz next
	ret

table10:
	dw	-1000,-100,-10,-1,0

?pderr:
	lxi h,drive$msg ! call ?pmsg			; error header
	lda @adrv ! adi 'A' ! mov c,a ! call ?cono	; drive code
	lxi h,track$msg ! call ?pmsg			; track header
	lhld @trk ! call ?pdec				; track number
	lxi h,sector$msg ! call ?pmsg			; sector header
	lhld @sect ! call ?pdec				; sector number
	ret


	; BNKSEL
	;	Bank Select.  Select CPU bank for further execution.

bnksel:
	sta @cbnk 			; remember current bank
	jmp ?bank			; and go exit through users
					; physical bank select routine


xofflist	db	-1,-1,-1,-1,-1,-1,-1,-1		; ctl-s clears to zero
		db	-1,-1,-1,-1,-1,-1,-1,-1



	dseg	; following resides in banked memory



;	Disk I/O interface routines


	; SELDSK
	;	Select Disk Drive.  Drive code in <C>.
	;		Invoke login procedure for drive
	;		if this is first select.  Return
	;		address of disk parameter header
	;		in <HL>

seldsk:
	mov a,c ! sta @adrv			; save drive select code
	mov l,c ! mvi h,0 ! dad h		; create index from drive code
	lxi b,@dtbl ! dad b			; get pointer to dispatch table
	mov a,m ! inx h ! mov h,m ! mov l,a	; point at disk descriptor
	ora h ! rz 				; if no entry in table, no disk
	mov a,e ! ani 1 ! jnz not$first$select	; examine login bit
	push h ! xchg				; put pointer in stack & <DE>
	lxi h,-2 ! dad d ! mov a,m ! sta @RDRV	; get relative drive
	lxi h,-6 ! dad d			; find LOGIN addr
	mov a,m ! inx h ! mov h,m ! mov l,a	; get address of LOGIN routine
	call ipchl				; call LOGIN
	pop h					; recover DPH pointer
not$first$select:
	ret


	; HOME
	;	Home selected drive.  Treated as SETTRK(0).

home:
	lxi b,0		; same as set track zero


	; SETTRK
	;	Set Track. Saves track address from <BC> 
	;		in @TRK for further operations.

settrk:
	mov l,c ! mov h,b
	shld @trk
	ret


	; SETSEC
	;	Set Sector.  Saves sector number from <BC>
	;		in @sect for further operations.

setsec:
	mov l,c ! mov h,b
	shld @sect
	ret


	; SETDMA
	;	Set Disk Memory Address.  Saves DMA address
	;		from <BC> in @DMA and sets @DBNK to @CBNK
	;		so that further disk operations take place
	;		in current bank.

setdma:
	mov l,c ! mov h,b
	shld @dma

	lda @cbnk	; default DMA bank is current bank
			; fall through to set DMA bank

	; SETBNK
	;	Set Disk Memory Bank.  Saves bank number
	;		in @DBNK for future disk data
	;		transfers.

setbnk:
	sta @dbnk
	ret


	; SECTRN
	;	Sector Translate.  Indexes skew table in <DE>
	;		with sector in <BC>.  Returns physical sector
	;		in <HL>.  If no skew table (<DE>=0) then
	;		returns physical=logical.

sectrn:
	mov l,c ! mov h,b
	mov a,d ! ora e ! rz
	xchg ! dad b ! mov l,m ! mvi h,0
	ret


	; READ
	;	Read physical record from currently selected drive.
	;		Finds address of proper read routine from
	;		extended disk parameter header (XDPH).

read:
	lhld @adrv ! mvi h,0 ! dad h	; get drive code and double it
	lxi d,@dtbl ! dad d		; make address of table entry
	mov a,m ! inx h ! mov h,m ! mov l,a	; fetch table entry
	push h				; save address of table
	lxi d,-8 ! dad d		; point to read routine address
	jmp rw$common			; use common code


	; WRITE
	;	Write physical sector from currently selected drive.
	;		Finds address of proper write routine from
	;		extended disk parameter header (XDPH).

write:
	lhld @adrv ! mvi h,0 ! dad h	; get drive code and double it
	lxi d,@dtbl ! dad d		; make address of table entry
	mov a,m ! inx h ! mov h,m ! mov l,a	; fetch table entry
	push h				; save address of table
	lxi d,-10 ! dad d		; point to write routine address

rw$common:
	mov a,m ! inx h ! mov h,m ! mov l,a	; get address of routine
	pop d				; recover address of table
	dcx d ! dcx d			; point to relative drive
	ldax d ! sta @rdrv		; get relative drive code and post it
	inx d ! inx d			; point to DPH again
	pchl				; leap to driver


	; MULTIO
	;	Set multiple sector count. Saves passed count in
	;		@CNT

multio:
	sta @cnt ! ret


	; FLUSH
	;	BIOS deblocking buffer flush.  Not implemented.

flush:
	xra a ! ret		; return with no error



	; error message components
drive$msg	db	cr,lf,bell,'BIOS Error on ',0
track$msg	db	': T-',0
sector$msg	db	', S-',0


    ; disk communication data items

@adrv	ds	1		; currently selected disk drive
@rdrv	ds	1		; controller relative disk drive
@trk	ds	2		; current track number
@sect	ds	2		; current sector number
@dma	ds	2		; current DMA address
@cnt	db	0		; record count for multisector transfer
@dbnk	db	0		; bank for DMA operations


	cseg	; common memory

@cbnk	db	0		; bank for processor operations


	end
LDRMOVE.ASM
	title 'bank & move module for CP/M3 linked BIOS'

	cseg

	public ?move,?xmove,?bank
	extrn @cbnk
	extrn	?pmsg

	maclib z80
	maclib	vislib
	maclib ports

?bank:
?xmove:				; 1050 can't perform interbank moves
	ret

?move:
	xchg			; we are passed source in DE and dest in HL
	ldir			; use Z80 block move instruction
	xchg			; need next addresses in same regs
	ret
	end
LDRTBL.ASM
	public @dtbl
	extrn fddd0
	cseg

@dtbl	dw fddd0			; A drive = floppy
	dw 0     			; B drive = floppy
	dw 0,0,0,0			; C-F not available
	dw 0    			; G drive = winchester
	dw 0,0,0,0,0,0,0,0,0		; drives H-P non-existant

	end
MODEBAUD.LIB
	; equates for mode byte bit fields

mb$input		equ 0000$0001b	; device may do input
mb$output		equ 0000$0010b	; device may do output
mb$in$out		equ mb$input+mb$output

mb$soft$baud		equ 0000$0100b	; software selectable
					; baud rates

mb$serial		equ 0000$1000b	; device may use protocol
mb$xon$xoff		equ 0001$0000b	; XON/XOFF protocol
					; enabled

baud$none		equ 0		; no baud rate associated
					; with this device
baud$50			equ 1		; 50 baud
baud$75			equ 2		; 75 baud
baud$110		equ 3		; 110 baud
baud$134		equ 4		; 134.5 baud
baud$150		equ 5		; 150 baud
baud$300		equ 6		; 300 baud
baud$600		equ 7		; 600 baud
baud$1200		equ 8		; 1200 baud
baud$1800		equ 9		; 1800 baud
baud$2400		equ 10		; 2400 baud
baud$3600		equ 11		; 3600 baud
baud$4800		equ 12		; 4800 baud
baud$7200		equ 13		; 7200 baud
baud$9600		equ 14		; 9600 baud
baud$19200		equ 15		; 19.2k baud

; 8251 Modes
;

mode$s2	        equ 1000$0000b  ; stop bit high
mode$s1         equ 0100$0000b  ; stop bit low
mode$ep	        equ 0010$0000b  ; even parity
mode$pen        equ 0001$0000b  ; parity enable
mode$12         equ 0000$1000b  ; char length high
mode$11         equ 0000$0100b  ; char length low
mode$b2         equ 0000$0010b  ; baud rate factor high
mode$b1		equ 0000$0001b  ; baud rate factor low
com$eh    	equ 1000$0000b  ; enter hunt mode
com$ir		equ 0100$0000b  ; internal reset
com$rts		equ 0010$0000b  ; request to send
com$er		equ 0001$0000b  ; error reset
com$sbrk	equ 0000$1000b  ; send break
com$rxe		equ 0000$0100b  ; receive enable
com$dtr		equ 0000$0010b  ; data terminal ready
com$txe     	equ 0000$0001b  ; transmit enable

; some common values
;
mode$eight	equ 0000$1100b  ; eight data bits
mode$onestop	equ 0100$0000b  ; one stop bit
mode$div16	equ 0000$0010b  ; 16x baud rate factor
mode$div64	equ 0000$0011b  ; 64x baud rate factor
mode$baudmask	equ 0000$0011b  ; to get baud bits from port c
mode$default   	equ mode$onestop or mode$eight or mode$div16
                                ; one stop, eight data, no parity, 16x
com$default	equ com$rts or com$rxe 
			        ; request to send and receive enable

; port c base baud rate definitions
;
misc$base01200	equ 0000$0000b  ; port c 1200 baud
misc$base02400	equ 0000$0100b  ; port c 2400 baud
misc$base19200	equ 0000$1000b  ; port c 19200 baud
misc$base09600	equ 0000$1100b  ; port c 9600 baud
misc$baudmask	equ 0000$1100b  ; mask for port c base baud rate
;
; Display 8255 Modes
;
disp$model	equ    0B4H     ;mode: A=1&IN, CH=OT, b=1&OT, CL=XX
disp$set2c	equ    005H     ;set bit 2 of port c
disp$set4c	equ    009H     ;set bit 4 of port c
disp$set6c 	equ    00DH     ;set bit 6 of port c
disp$set7c	equ    00FH     ;set bit 7 of port c
;
; Keyboard 8251 mode bytes
;
kb$default	equ mode$onestop or mode$eight or mode$div16
                                ; one stop, eight data, no parity, 16x
kb$ir		equ 0100$0000b  ; internal reset
kb$sig		equ com$er or com$rxe or com$txe
		                ; err reset, RxE, TxE
kb$click	equ 0101$0101b  ; keyboard click
;
; Miscellaneous 8255
;
lpt$mode0	equ 088H        ; Mode:A=0&OT, CH=IN, B=0&OT, c=OT
lpt$baud	equ 0000$1100b  ; 1200 baud
motor$on	equ	0eh	; Motor on
motor$off	equ	0fh	; Motor off
;
; Floppy disk controller modes
;
fdc$reset	equ 1101$0000b	; Reset  		
MOVE.ASM
	title 'bank & move module for CP/M3 linked BIOS'

	cseg

	public ?move,?xmove,?bank
	extrn @cbnk
	extrn	?pmsg

	maclib z80
	maclib	vislib
	maclib ports

?xmove:
	ret

?move:
	xchg			; we are passed source in DE and dest in HL
	ldir			; use Z80 block move instruction
	xchg			; need next addresses in same regs
	ret


;
; Select memory bank.  Enter routine with desired bank in A
; register.  Preserve all registers except A.
;

?bank:

	if	banked		;
	ral			; rotate into 1&2
	ori	01h		; set bit 0 on
	out	p$bank$select	; Select bank
	endif
	ret			; return

	end
PORTS.LIB
;	PORTS.LIB
;	I/O Port addresses for Visual 1050          
;
;	Copyright (c) Visual Technology, 1983
;
; Revision history:
;	01 (IRN) Initial- based on cpm/3 for Ontel Amigo
;

real$1050	equ	true
keyboard$1050	equ	true
banked		equ	true 

; Boot Mode flip-flop
;
p$boot	equ 0D0h		; Boot prom enable/disable
p$bank$select	equ	0d0h	; Select bank
;
; Interrupt vectors
;
int$port	equ	0C0h
int$initial	equ	010h
int$mask	equ	1110$1111b	; All on except VERT
all$ints	equ	1111$1111b	; All interrupts enabled
vert$clear	equ	0A0h		; Clear vert interrupt
;
; Display section 8255 parallel interface
;
p$disp$in	equ 84h	; port a from display
p$disp$out	equ 85h	; port b to display
p$disp$c	equ 86h	; port c from/to display
p$disp$control	equ 87h	; control port for display
clear$6502	equ 0b0h
; Keyboard 8251 - keyboard input, loudspeaker output
;
p$kb$data	equ 88h	; in= kb data, out= loudspeaker data
p$kb$control	equ 89h	; kb control/status

; RS-232 8251
;
p$aux1$data	equ 8Ch	; rs-232 xmit/recv data
p$aux1$control	equ 8Dh	; rs-232 control/status

; Miscellaneous 8255
;
p$disk$bits	equ 90h	; diskette bits
p$printer	equ 91h	; printer bits
p$misc		equ 92h	; miscellaneous bits
p$8255$control	equ 93h	; 8255 control port

; MB8877 Floppy disk formatter/controller
;
p$disk$control	equ 94h	; mb8877 status/command
p$disk$track	equ 95h	; mb8877 track
p$disk$sector	equ 96h	; mb8877 sector
p$disk$data	equ 97h	; mb8877 data

; Winchester Interface to Xebec Controller
;
p$winch$data	equ 0E0h	; Winchester data
p$winch$control	equ 0E1h	; Winchester control

;
; Real time clock
;

p$clk$porta	equ 09Ch ; Port A
p$clk$portb	equ 09Dh ; Port B
p$clk$portc     equ 09Eh ; Port C
p$clk$control   equ 09Fh ; Control port

add$write$hi	equ	09h
add$write$lo	equ	08h

read$hi    	equ	0DH
read$lo		equ	0CH
write$hi	equ	0BH
write$lo	equ	0AH

rtc$select	equ	0fh
rtc$read	equ	91h
rtc$write	equ	81h

;  Display masks
;
disp$ready$rcv	equ	0000$0001b	; ready to receive
disp$ready$xmit	equ	0000$1000b	; ready to xmit
disp$req$rcv	equ	0100$0000b	; req rcv from display
disp$req$xmit	equ	1000$0000b	; req xmit to display
disp$portc$cons	equ	0001$0100b	; port c constants

;  Lpt masks
;
misc$lpt$strobe	equ	0000$0001b	; handshake strobe
misc$lpt$avail	equ	0010$0000b	; lpt available
misc$lpt$nobusy	equ	0001$0000b	; finished printing
PRIVATE.ASM
;
; Private BIOS call
;
; When called, A is a subfunction identifier.  (0 is illegal)
; Values in other registers depend upon particular subfunction.
;

	public	Priv$call
	maclib	Z80
	extrn	?pmsg

	dseg

PRIV$CALL:

	ora	a		; Check value in A
	jrz	bad$exit$2	; Jump if 0 (illegal)

	cpi	01		; Is it 1?
	jrnz	priv$80		; Jump if not

;
; A=1 is a private call which gives the user access to flags located
; in memory. Register values are as follows:
;
;	C = # of byte to be accessed
;	B =0FFH if setting a byte
;	  =0FEH if setting a word
;	  =000H if a GET operation
;	  (else, ignored)
;	DE =  word value to be set
;   or  D = byte value to be set
;
; Upon exit, A or HL will contain the byte or word on a GET operation.
;

	push	b
	mov	a,c		; Get OFFSET
	CPI	MAX		; > MAX?
	JP	BAD$EXIT	; Yes => error

	lxi	h,bytetbl	; Point to bytetbl
	mvi	b,0		; Clear B
	DAD	B		; Add to get address within tbl
 
	pop	Psw		; Move B into A
	ORA	A		; Check SET
	JRZ	GET$op		; 0 => Get operation

	inr	a		; Increment
	jrz	set$byte	; FF => Set Byte

	inr	a		; Increment
	jrnz	bad$exit2	; If not FE, error

;
; Set word in bytetbl to VALUE
;

Set$word:

	mov	m,e		; Move Move lo byte into table
	inx	h		; Increment
	mov	m,d		; Move hi byte into table
	jr	priv$exit	; Exit

;
; Set byte in Bytetbl to VALUE.
;
Set$byte:

	mov	m,d		; Store it
	jr	priv$exit	;

;
; Get operation.  Move low byte into A and L, move high byte into H.
;

GET$op:
	Mov	a,m		; Get low byte
	inx	h		; increment
	mov	h,m		; Move high byte to H
	mov	l,a		; Move low byte to L
	jr	priv$exit	; exit

;
; Other functions can be implemented here:
;
Priv$80:

	jr	priv$exit
;
; Error exit
;
Bad$exit:
	pop	b
bad$exit$2:



;
; Exit point
;

Priv$exit:
	ret


BYTETBL:
	DB	0
	DB	0
	DB	0
	DB	0   
	DB	0
	DB	0
	DB	0
	DB	0
	DB	0
	DB	0 
MAX	EQU	$-BYTETBL
	end
RANDOM.ASM
;***************************************************
;*                                                 *
;* sample random access program for cp/m 3         *
;*                                                 *
;***************************************************
        org     100h    ;base of tpa
;
reboot  equ     0000h   ;system reboot
bdos    equ     0005h   ;bdos entry point
;
coninp  equ     1       ;console input function
conout  equ     2       ;console output function
pstring equ     9       ;print string until '$'
rstring equ     10      ;read console buffer
version equ     12      ;return version number
openf   equ     15      ;file open function
closef  equ     16      ;close function
makef   equ     22      ;make file function
readr   equ     33      ;read random
writer  equ     34      ;write random
wrtrzf	equ	40	;write random zero fill
parsef  equ     152	;parse function
;
fcb     equ     005ch   ;default file control block
ranrec  equ     fcb+33  ;random record position
ranovf  equ     fcb+35  ;high order (overflow) byte
buff    equ     0080h   ;buffer address
;
cr      equ     0dh     ;carriage return
lf      equ     0ah     ;line feed
;
;***************************************************
;*                                                 *
;* load SP, set-up file for random access          *
;*                                                 *
;***************************************************
        lxi     sp,stack
;
;       version 3.1?
        mvi     c,version
        call    bdos
        cpi     31h     ;version 3.1 or better?
        jnc     versok
;       bad version, message and go back
        lxi     d,badver
        call    print
        jmp     reboot
;
versok:
;       correct version for random access
        mvi     c,openf ;open default fcb
rdname: lda     fcb+1
	cpi	' '
	jnz	opfile
	lxi	d,entmsg
	call 	print
	call 	parse
	jmp	versok
opfile:	lxi	d,fcb
	call    bdos
        inr     a       ;err 255 becomes zero
        jnz     ready
;
;       cannot open file, so create it
        mvi     c,makef
        lxi     d,fcb
        call    bdos
        inr     a       ;err 255 becomes zero
        jnz     ready
;
;       cannot create file, directory full
        lxi     d,nospace
        call    print
        jmp     reboot  ;back to ccp
;
;***************************************************
;*                                                 *
;*  loop back to "ready" after each command        *
;*                                                 *
;***************************************************
;
ready:
;       file is ready for processing
;
        call    readcom ;read next command
        shld    ranrec  ;store input record#
        lxi     h,ranovf
        mov     m,c     ;set ranrec high byte
        cpi     'Q'     ;quit?
        jnz     notq
;
;       quit processing, close file
        mvi     c,closef
        lxi     d,fcb
        call    bdos
        inr     a       ;err 255 becomes 0
        jz      error   ;error message, retry
        jmp     reboot  ;back to ccp
;
;***************************************************
;*                                                 *
;* end of quit command, process write              *
;*                                                 *
;***************************************************
notq:
;       not the quit command, random write?
        cpi     'W'
        jnz     notw
;
;       this is a random write, fill buffer until cr
        lxi     d,datmsg
        call    print   ;data prompt
        mvi     c,127   ;up to 127 characters
        lxi     h,buff  ;destination
rloop:  ;read next character to buff
        push    b       ;save counter
        push    h       ;next destination
        call    getchr  ;character to a
        pop     h       ;restore counter
        pop     b       ;restore next to fill
        cpi     cr      ;end of line?
        jz      erloop
;       not end, store character
        mov     m,a
        inx     h       ;next to fill
        dcr     c       ;counter goes down
        jnz     rloop   ;end of buffer?
erloop:
;       end of read loop, store 00
        mvi     m,0
;
;       write the record to selected record number
        mvi     c,writer
        lxi     d,fcb
        call    bdos
        ora     a       ;error code zero?
        jnz     error   ;message if not
        jmp     ready   ;for another record
;
;
;********************************************************
;*                                                      *
;* end of write command, process write random zero fill *
;*                                                      *
;********************************************************
notw:
;       not the quit command, random write zero fill?
        cpi     'F'
        jnz     notf
;
;       this is a random write, fill buffer until cr
        lxi     d,datmsg
        call    print   ;data prompt
        mvi     c,127   ;up to 127 characters
        lxi     h,buff  ;destination
rloop1: ;read next character to buff
        push    b       ;save counter
        push    h       ;next destination
        call    getchr  ;character to a
        pop     h       ;restore counter
        pop     b       ;restore next to fill
        cpi     cr      ;end of line?
        jz      erloop1
;       not end, store character
        mov     m,a
        inx     h       ;next to fill
        dcr     c       ;counter goes down
        jnz     rloop1  ;end of buffer?
erloop1:
;       end of read loop, store 00
        mvi     m,0
;
;       write the record to selected record number
        mvi     c,wrtrzf
        lxi     d,fcb
        call    bdos
        ora     a       ;error code zero?
        jnz     error   ;message if not
        jmp     ready   ;for another record
;
;***************************************************
;*                                                 *
;* end of write commands, process read             *
;*                                                 *
;***************************************************
notf:
;       not a write command, read record?
        cpi     'R'
        jnz     error   ;skip if not
;
;       read random record
        mvi     c,readr
        lxi     d,fcb
        call    bdos
        ora     a       ;return code 00?
        jnz     error
;
;       read was successful, write to console
        call    crlf    ;new line
        mvi     c,128   ;max 128 characters
        lxi     h,buff  ;next to get
wloop:
        mov     a,m     ;next character
        inx     h       ;next to get
        ani     7fh     ;mask parity
        jz      ready   ;for another command if 00
        push    b       ;save counter
        push    h       ;save next to get
        cpi     ' '     ;graphic?
        cnc     putchr  ;skip output if not
        pop     h
        pop     b
        dcr     c       ;count=count-1
        jnz     wloop
        jmp     ready
;
;***************************************************
;*                                                 *
;* end of read command, all errors end-up here     *
;*                                                 *
;***************************************************
;
error:
        lxi     d,errmsg
        call    print
        jmp     ready
;
;***************************************************
;*                                                 *
;* utility subroutines for console i/o             *
;*                                                 *
;***************************************************
getchr:
        ;read next console character to a
        mvi     c,coninp
        call    bdos
        ret
;
putchr:
        ;write character from a to console
        mvi     c,conout
        mov     e,a     ;character to send
        call    bdos    ;send character
        ret
;
crlf:
        ;send carriage return line feed
        mvi     a,cr    ;carriage return
        call    putchr
        mvi     a,lf    ;line feed
        call    putchr
        ret
;
parse:
	;read and parse filespec
	lxi	d,conbuf
	mvi	c,rstring
	call 	bdos
	lxi	d,pfncb
	mvi	c,parsef
	call 	bdos
	ret
;
print:
        ;print the buffer addressed by de until $
        push    d
        call    crlf
        pop     d       ;new line
        mvi     c,pstring
        call    bdos    ;print the string
        ret
;
readcom:
        ;read the next command line to the conbuf
        lxi     d,prompt
        call    print   ;command?
        mvi     c,rstring
        lxi     d,conbuf
        call    bdos    ;read command line
;       command line is present, scan it
	mvi	c,0	;start with 00
        lxi     h,0     ;           0000
        lxi     d,conlin;command line
readc:  ldax    d       ;next command character
        inx     d       ;to next command position
        ora     a       ;cannot be end of command
        rz
;       not zero, numeric?
        sui     '0'
        cpi     10      ;carry if numeric
        jnc     endrd
;       add-in next digit
	push 	psw
	mov	a,c	;value = ahl
	dad	h
	adc	a	;*2
	push	a	;save value * 2
	push	h
        dad     h       ;*4
	adc	a
	dad	h	;*8
	adc	a
	pop	b	;*2 + *8 = *10
	dad	b
	pop	b
	adc	b
	pop	b  	;+digit
	mov	c,b
	mvi	b,0
	dad	b
	aci	0
	mov	c,a
	jnc	readc
        jmp     readcom
endrd:
;       end of read, restore value in a
        adi     '0'     ;command
        cpi     'a'     ;translate case?
        rc
;       lower case, mask lower case bits
        ani     101$1111b
        ret		;return with value in chl
;
;***************************************************
;*                                                 *
;* string data area for console messages           *
;*                                                 *
;***************************************************
badver:
        db      'sorry, you need cp/m version 3$'
nospace:
        db      'no directory space$'
datmsg:
        db      'type data: $'
errmsg:
        db      'error, try again.$'
prompt:
        db      'next command? $'
entmsg:
	db	'enter filename: $' 
;
;***************************************************
;*                                                 *
;* fixed and variable data area                    *
;*                                                 *
;***************************************************
conbuf: db      conlen  ;length of console buffer
consiz: ds      1       ;resulting size after read
conlin: ds      32      ;length 32 buffer
conlen  equ     $-consiz
;
pfncb:
	dw	conlin
	dw	fcb
;
        ds      32      ;16 level stack
stack:
        end
SCB.ASM
	title 'System Control Block Definition for CP/M3 BIOS'

	public @civec, @covec, @aivec, @aovec, @lovec, @bnkbf
	public @crdma, @crdsk, @vinfo, @resel, @fx, @usrcd 
        public @mltio, @ermde, @erdsk, @media, @bflgs
	public @date, @hour, @min, @sec, ?erjmp, @mxtpa


scb$base equ    0FE00H          ; Base of the SCB

@CIVEC  equ     scb$base+22h    ; Console Input Redirection 
                                ; Vector (word, r/w)
@COVEC  equ     scb$base+24h    ; Console Output Redirection 
                                ; Vector (word, r/w)
@AIVEC  equ     scb$base+26h    ; Auxiliary Input Redirection 
                                ; Vector (word, r/w)
@AOVEC  equ     scb$base+28h    ; Auxiliary Output Redirection 
                                ; Vector (word, r/w)
@LOVEC  equ     scb$base+2Ah    ; List Output Redirection 
                                ; Vector (word, r/w)
@BNKBF  equ     scb$base+35h    ; Address of 128 Byte Buffer 
                                ; for Banked BIOS (word, r/o)
@CRDMA  equ     scb$base+3Ch    ; Current DMA Address 
                                ; (word, r/o)
@CRDSK  equ     scb$base+3Eh    ; Current Disk (byte, r/o)
@VINFO  equ     scb$base+3Fh    ; BDOS Variable "INFO" 
                                ; (word, r/o)
@RESEL  equ     scb$base+41h    ; FCB Flag (byte, r/o)
@FX     equ     scb$base+43h    ; BDOS Function for Error 
                                ; Messages (byte, r/o)
@USRCD  equ     scb$base+44h    ; Current User Code (byte, r/o)
@MLTIO	equ	scb$base+4Ah	; Current Multi-Sector Count
				; (byte,r/w)
@ERMDE  equ     scb$base+4Bh    ; BDOS Error Mode (byte, r/o)
@ERDSK	equ	scb$base+51h	; BDOS Error Disk (byte,r/o)
@MEDIA	equ	scb$base+54h	; Set by BIOS to indicate
				; open door (byte,r/w)
@BFLGS  equ     scb$base+57h    ; BDOS Message Size Flag (byte,r/o)  
@DATE   equ     scb$base+58h    ; Date in Days Since 1 Jan 78 
                                ; (word, r/w)
@HOUR   equ     scb$base+5Ah    ; Hour in BCD (byte, r/w)
@MIN    equ     scb$base+5Bh    ; Minute in BCD (byte, r/w)
@SEC    equ     scb$base+5Ch    ; Second in BCD (byte, r/w)
?ERJMP  equ     scb$base+5Fh    ; BDOS Error Message Jump
                                ; (word, r/w)
@MXTPA  equ     scb$base+62h    ; Top of User TPA 
                                ; (address at 6,7)(word, r/o)
	end
VISLIB.LIB
;solution.lib
;	Standard equates
;


true	equ	0ffh		; self explanatory
false	equ	0		; ditto
Z80.LIB
;	@CHK MACRO USED FOR CHECKING 8 BIT DISPLACMENTS
;
@CHK	MACRO	?DD	;; USED FOR CHECKING RANGE OF 8-BIT DISP.S
	IF (?DD GT 7FH) AND (?DD LT 0FF80H)
 'DISPLACEMENT RANGE ERROR - Z80 LIB'
	ENDIF
	ENDM
LDX	MACRO	?R,?D	
	@CHK	?D
	DB	0DDH,?R*8+46H,?D
	ENDM
LDY	MACRO	?R,?D	
	@CHK	?D
	DB	0FDH,?R*8+46H,?D
	ENDM
STX	MACRO	?R,?D	
	@CHK	?D
	DB	0DDH,70H+?R,?D
	ENDM
STY	MACRO	?R,?D	
	@CHK	?D
	DB	0FDH,70H+?R,?D
	ENDM
MVIX	MACRO	?N,?D	
	@CHK	?D
	DB	0DDH,36H,?D,?N
	ENDM
MVIY	MACRO	?N,?D	
	@CHK	?D
	DB	0FDH,36H,?D,?N
	ENDM
LDAI	MACRO		
	DB	0EDH,57H
	ENDM
LDAR	MACRO		
	DB	0EDH,5FH
	ENDM
STAI	MACRO		
	DB	0EDH,47H
	ENDM
STAR	MACRO		
	DB	0EDH,4FH
	ENDM

LXIX	MACRO	?NNNN	
	DB	0DDH,21H
	DW	?NNNN
	ENDM
LXIY	MACRO	?NNNN	
	DB	0FDH,21H
	DW	?NNNN
	ENDM
LDED	MACRO	?NNNN	
	DB	0EDH,5BH
	DW	?NNNN
	ENDM
LBCD	MACRO	?NNNN	
	DB	0EDH,4BH
	DW	?NNNN
	ENDM
LSPD	MACRO	?NNNN	
	DB	0EDH,07BH
	DW	?NNNN
	ENDM
LIXD	MACRO	?NNNN	
	DB	0DDH,2AH
	DW	?NNNN
	ENDM
LIYD	MACRO	?NNNN	
	DB	0FDH,2AH
	DW	?NNNN
	ENDM
SBCD	MACRO	?NNNN	
	DB	0EDH,43H
	DW	?NNNN
	ENDM
SDED	MACRO	?NNNN	
	DB	0EDH,53H
	DW	?NNNN
	ENDM
SSPD	MACRO	?NNNN	
	DB	0EDH,73H
	DW	?NNNN
	ENDM
SIXD	MACRO	?NNNN	
	DB	0DDH,22H
	DW	?NNNN
	ENDM
SIYD	MACRO	?NNNN	
	DB	0FDH,22H
	DW	?NNNN
	ENDM
SPIX	MACRO		
	DB	0DDH,0F9H
	ENDM
SPIY	MACRO		
	DB	0FDH,0F9H
	ENDM
PUSHIX	MACRO		
	DB	0DDH,0E5H
	ENDM
PUSHIY	MACRO		
	DB	0FDH,0E5H
	ENDM
POPIX	MACRO		
	DB	0DDH,0E1H
	ENDM
POPIY	MACRO		
	DB	0FDH,0E1H
	ENDM
EXAF	MACRO		
	DB	08H
	ENDM
EXX	MACRO		
	DB	0D9H
	ENDM
XTIX	MACRO		
	DB	0DDH,0E3H
	ENDM
XTIY	MACRO		
	DB	0FDH,0E3H
	ENDM

LDI	MACRO		
	DB	0EDH,0A0H
	ENDM
LDIR	MACRO		
	DB	0EDH,0B0H
	ENDM
LDD	MACRO		
	DB	0EDH,0A8H
	ENDM
LDDR	MACRO		
	DB	0EDH,0B8H
	ENDM
CCI	MACRO		
	DB	0EDH,0A1H
	ENDM
CCIR	MACRO		
	DB	0EDH,0B1H
	ENDM
CCD	MACRO		
	DB	0EDH,0A9H
	ENDM
CCDR	MACRO		
	DB	0EDH,0B9H
	ENDM

ADDX	MACRO	?D	
	@CHK	?D
	DB	0DDH,86H,?D
	ENDM
ADDY	MACRO	?D	
	@CHK	?D
	DB	0FDH,86H,?D
	ENDM
ADCX	MACRO	?D	
	@CHK	?D
	DB	0DDH,8EH,?D
	ENDM
ADCY	MACRO	?D	
	@CHK	?D
	DB	0FDH,8EH,?D
	ENDM
SUBX	MACRO	?D	
	@CHK	?D
	DB	0DDH,96H,?D
	ENDM
SUBY	MACRO	?D	
	@CHK	?D
	DB	0FDH,96H,?D
	ENDM
SBCX	MACRO	?D	
	@CHK	?D
	DB	0DDH,9EH,?D
	ENDM
SBCY	MACRO	?D	
	@CHK	?D
	DB	0FDH,9EH,?D
	ENDM
ANDX	MACRO	?D	
	@CHK	?D
	DB	0DDH,0A6H,?D
	ENDM
ANDY	MACRO	?D	
	@CHK	?D
	DB	0FDH,0A6H,?D
	ENDM
XORX	MACRO	?D	
	@CHK	?D
	DB	0DDH,0AEH,?D
	ENDM
XORY	MACRO	?D	
	@CHK	?D
	DB	0FDH,0AEH,?D
	ENDM
ORX	MACRO	?D	
	@CHK	?D
	DB	0DDH,0B6H,?D
	ENDM
ORY	MACRO	?D	
	@CHK	?D
	DB	0FDH,0B6H,?D
	ENDM
CMPX	MACRO	?D	
	@CHK	?D
	DB	0DDH,0BEH,?D
	ENDM
CMPY	MACRO	?D	
	@CHK	?D
	DB	0FDH,0BEH,?D
	ENDM
INRX	MACRO	?D	
	@CHK	?D
	DB	0DDH,34H,?D
	ENDM
INRY	MACRO	?D	
	@CHK	?D
	DB	0FDH,34H,?D
	ENDM
DCRX	MACRO	?D	
	@CHK	?D
	DB	0DDH,035H,?D
	ENDM
DCRY	MACRO	?D	
	@CHK	?D
	DB	0FDH,35H,?D
	ENDM

NEG	MACRO		
	DB	0EDH,44H
	ENDM
IM0	MACRO		
	DB	0EDH,46H
	ENDM
IM1	MACRO		
	DB	0EDH,56H
	ENDM
IM2	MACRO		
	DB	0EDH,5EH
	ENDM


BC	EQU	0
DE	EQU	2
HL	EQU	4
IX	EQU	4	
IY	EQU	4	
DADC	MACRO	?R	
	DB	0EDH,?R*8+4AH
	ENDM
DSBC	MACRO	?R	
	DB	0EDH,?R*8+42H
	ENDM
DADX	MACRO	?R	
	DB	0DDH,?R*8+09H
	ENDM
DADY	MACRO	?R	
	DB	0FDH,?R*8+09H
	ENDM
INXIX	MACRO		
	DB	0DDH,23H
	ENDM
INXIY	MACRO		
	DB	0FDH,23H
	ENDM
DCXIX	MACRO		
	DB	0DDH,2BH
	ENDM
DCXIY	MACRO		
	DB	0FDH,2BH
	ENDM

BIT	MACRO	?N,?R	
	DB	0CBH,?N*8+?R+40H
	ENDM
SETB	MACRO	?N,?R
	DB	0CBH,?N*8+?R+0C0H
	ENDM
RES	MACRO	?N,?R
	DB	0CBH,?N*8+?R+80H
	ENDM

BITX	MACRO	?N,?D	
	@CHK	?D
	DB	0DDH,0CBH,?D,?N*8+46H
	ENDM
BITY	MACRO	?N,?D	
	@CHK	?D
	DB	0FDH,0CBH,?D,?N*8+46H
	ENDM
SETX	MACRO	?N,?D	
	@CHK	?D
	DB	0DDH,0CBH,?D,?N*8+0C6H
	ENDM
SETY	MACRO	?N,?D	
	@CHK	?D
	DB	0FDH,0CBH,?D,?N*8+0C6H
	ENDM
RESX	MACRO	?N,?D	
	@CHK	?D
	DB	0DDH,0CBH,?D,?N*8+86H
	ENDM
RESY	MACRO	?N,?D	
	@CHK	?D
	DB	0FDH,0CBH,?D,?N*8+86H
	ENDM

JR	MACRO	?N
	DB	18H,?N-$-1
	ENDM
JRC	MACRO	?N
	DB	38H,?N-$-1
	ENDM
JRNC	MACRO	?N
	DB	30H,?N-$-1
	ENDM
JRZ	MACRO	?N
	DB	28H,?N-$-1
	ENDM
JRNZ	MACRO	?N
	DB	20H,?N-$-1
	ENDM
DJNZ	MACRO	?N
	DB	10H,?N-$-1
	ENDM

PCIX	MACRO		
	DB	0DDH,0E9H
	ENDM
PCIY	MACRO		
	DB	0FDH,0E9H
	ENDM

RETI	MACRO		
	DB	0EDH,4DH
	ENDM
RETN	MACRO		
	DB	0EDH,45H
	ENDM

INP	MACRO	?R	
	DB	0EDH,?R*8+40H
	ENDM
OUTP	MACRO	?R	
	DB	0EDH,?R*8+41H
	ENDM
INI	MACRO		
	DB	0EDH,0A2H
	ENDM
INIR	MACRO		
	DB	0EDH,0B2H
	ENDM
IND	MACRO		
	DB	0EDH,0AAH
	ENDM
INDR	MACRO		
	DB	0EDH,0BAH
	ENDM
OUTI	MACRO		
	DB	0EDH,0A3H
	ENDM
OUTIR	MACRO		
	DB	0EDH,0B3H
	ENDM
OUTD	MACRO		
	DB	0EDH,0ABH
	ENDM
OUTDR	MACRO		
	DB	0EDH,0BBH
	ENDM


RLCR	MACRO	?R	
	DB	0CBH, 00H + ?R
	ENDM
RLCX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 06H
	ENDM
RLCY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 06H
	ENDM
RALR	MACRO	?R	
	DB	0CBH, 10H+?R
	ENDM
RALX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 16H
	ENDM
RALY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 16H
	ENDM
RRCR	MACRO	?R	
	DB	0CBH, 08H + ?R
	ENDM
RRCX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 0EH
	ENDM
RRCY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 0EH
	ENDM
RARR	MACRO	?R	
	DB	0CBH, 18H + ?R
	ENDM
RARX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 1EH
	ENDM
RARY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 1EH
	ENDM
SLAR	MACRO	?R	
	DB	0CBH, 20H + ?R
	ENDM
SLAX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 26H
	ENDM
SLAY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 26H
	ENDM
SRAR	MACRO	?R	
	DB	0CBH, 28H+?R
	ENDM
SRAX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 2EH
	ENDM
SRAY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 2EH
	ENDM
SRLR	MACRO	?R	
	DB	0CBH, 38H + ?R
	ENDM
SRLX	MACRO	?D	
	@CHK	?D
	DB	0DDH, 0CBH, ?D, 3EH
	ENDM
SRLY	MACRO	?D	
	@CHK	?D
	DB	0FDH, 0CBH, ?D, 3EH
	ENDM
RLD	MACRO		
	DB	0EDH, 6FH
	ENDM
RRD	MACRO		
	DB	0EDH, 67H
	ENDM