DataMuseum.dk

Presents historical artifacts from the history of:

RegneCentralen RC850

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about RegneCentralen RC850

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - metrics - download

⟦5e8b3a704⟧ TextFile

    Length: 20608 (0x5080)
    Types: TextFile
    Names: »FDSKDRV.MAC«

Derivation

└─⟦9f46c4107⟧ Bits:30005988 Sources for TurboDOS ver. 1.30 device drivers
    └─⟦this⟧ »FDSKDRV.MAC« 

TextFile

.Z80
TITLE	DISK DRIVER FOR WD1793 FLOPPY DISK CONTROLLER
SUBTTL	Copyright (c) by ASE GmbH, Altenstadt, vers.: 16.12.83
;
	NAME	('WDFDDR')
;
;******************************************************************************
;
;	This Driver supports any intermix of 4 Floppy Drives connected
;	to the ASE 839-A1-16/SF Controller.
;
;******************************************************************************
;
MAXTRY  EQU	5		;Maximum number of retrys
CBADDR	EQU	90H		;Controller base address
MDRNO	EQU	4		;Maximum number of drives
SIDES	EQU	3		;side select bit
READY	EQU	7		;ready bit
BUSY	EQU	0		;busy bit
WRTPR	EQU	6		;write protect bit
BELL	EQU	7		;bell character
DDENS	EQU	5		;density select bit
MOTON	EQU	4		;motor on bit (5 1/4")
;
CTC4	EQU	10H
;
;	DMA Controller equates (DMA channel 3 is used)
;
CH3DMA	EQU	0F6H		;DMA channel 3
CH3TC	EQU	0F7H		;terminal count register
DMACTL	EQU	0F8H		;status and command register
MASKR	EQU	0FAH		;mask register
MODER	EQU	0FBH		;mode register
CLIFF	EQU	0FCH		;8/16 bit flip flop
;
DMARD	EQU	47H		;read command
DMAWR	EQU	4BH		;write command
ENADMA	EQU	3		;enable DMA channel 3 command
DISDMA	EQU	7		;dissable DMA channel 3 command
;
;       controller equates
;
FCCONT  EQU   	CBADDR+0AH	;control word register
FCSTAT  EQU	CBADDR+0AH	;status register
FCTRCK  EQU   	CBADDR+0BH	;track register
FCSECT  EQU   	CBADDR+0CH	;sector register
FCDATA  EQU   	CBADDR+0DH	;data register
;
DRVSEL	EQU	CBADDR+08H	;drive select port
DENSEL	EQU	CBADDR+06H	;density select port
;
;       controller commands
;
RESTOR  EQU   	00000000B  	;restore (without verify)
SEEKC   EQU   	00011100B  	;seek 
READS   EQU   	10000000B  	;read sector
WRITES  EQU   	10100000B  	;write sector
READAD	EQU	0C4H		;read address with 15ms delay
WRTTRK	EQU	11110100B	;write track command with 15ms delay
STPIN	EQU	01001000B	;step in command
;
;	INCLUDE	RCEQUATE.MAC
;
;	HARDWARE INITIALIZATION
;
	COMMON	/?INIT?/
;;
DSKIN@::LD	HL,FCISR	;set Floppy Controller interupt vector
	LD	(CTC4V##),HL	;
	IN	A,(FCSTAT)	;reset the INTRQ from floppy controller
	LD	A,20H		;set precomp to zero, select single density
	OUT	(DENSEL),A	;
	LD	A,18H		;select drive 1, side 0, motor on
	OUT	(DRVSEL),A	;
;
	RET			;initialization done
;
	CSEG			;LOCATED IN PROGRAM AREA
;
DSKDR@::LD	HL,MUXSPH	;lock driver
	CALL	WAIT##		;
	XOR	A		;set driver busy bit
	OUT	(2),A		;
	CALL	DSKFD		;do function call
	PUSH	AF		;save return code
	LD	HL,MUXSPH	;unlock driver
	CALL	SIGNAL##	;
	LD	A,1		;clear driver busy bit
	OUT	(2),A		;
	POP	AF		;restore return code
	RET			;done
;
DSKFD:	LD	A,(IX)		;GET FUNCTION CODE
	CP	0		;READ SECTOR(S)
	JP	Z,DREAD		;
	CP	1		;WRITE SECTOR(S)
	JP	Z,DWRITE	;
	CP	2		;DETERMINE DISK TYPE
	JP	Z,DTYPE		;
	CP	3		;SPECIFIC DISK READY
	JP	Z,DREADY	;
	CP	4		;FORMAT TRACK
	JP	Z,DFORMA	;
	LD	A,0FFH		;SET ERROR
	RET			;DONE
;
DREAD:	LD	A,READS		;set read sector
	JR	DREWR		;and go to common read/write code
;
DWRITE:	LD	A,(IX+1)	;get requested drive
	SET	SIDES,A		;select side 0
	OUT	(DRVSEL),A	;select the drive
	IN	A,(FCSTAT)	;get drive status
	BIT	WRTPR,A		;test write protect bit
	LD	A,0FFH		;set error code
	RET	NZ		;signal the error if the bit is set
	LD	A,WRITES	;set write sector
;
DREWR:	LD	(SREWRC),A	;save the command
	LD	A,MAXTRY	;set retry counter
	LD	(RTRYC),A	;
	LD	A,(IX+1)	;set current disk number
	LD	(CURDSK),A	;
DRTRY:	CALL	SETTRK		;set track number
	OR	A		;test for error
	JR	Z,DRWRS		;on error, restore heads
	LD	A,(IX+4)	;get sector number
	LD	(SECTOR),A	;save it
	LD	A,(IX+6)	;get sector count
	LD	(SECCNT),A	;save it
	CALL	SETDMA		;
DREWRL:	CALL	SETSEC		;set sector
	LD	A,ENADMA	;enable DMA service
	OUT	(MASKR),A	;
	LD	A,(SREWRC)	;get requested function
	LD	C,A		;save command
	CALL	SETCMD		;
;
DREWR0:	LD	A,(STAT1)	;get command 2/3 status
	LD	HL,SREWRC	;get requested command
	BIT	5,(HL)		;WRITE BIT SET ?
	JR	NZ,DREWR1	;IF SET NO UPDATE
	RES	5,A		;ON READ IGNORE DELETED MARK
DREWR1:	OR	A		;on zero, no error
	JR	Z,DREWR2	;
DRWRS:	LD	A,(RTRYC)	;get retry counter
	SUB	1		;decrement it
	JR	C,DREWRF	;on carry, error still occurs
	LD	(RTRYC),A	;else restore the counter
	CALL	HOME		;recalibrate the heads
	JP	DRTRY		;and try again
DREWRF:	LD	A,0FFH		;unrecoverable error, so
	RET			;leave the driver
;
DREWR2:	LD	A,(SECCNT)	;test for multiple sector request
	CP	0		;
	RET	Z		;on match, all done
	LD	A,(SECTOR)	;else update the sector pointer
	INC	A		;
	LD	(SECTOR),A	;
	JR	DREWRL		;and process the next sector
;
;
;
DTYPE:	CALL	DREADY		;get ready status
	OR	A		;drive ready ?
	RET	Z		;if not, return
	CALL	HOME		;recalibrate heads on first access
	OR	A		;
	RET	Z		;on error, return
	LD	A,SEEKC		;get seek command
	RES	2,A		;dissable track verify
	LD	(RQCMD),A	;set command
	LD	A,1		;get track number
	CALL	SEEK		;and position head
	CALL	SELDSK		;read sector ID
	OR	A		;
	JR	NZ,DTYPE0	;successfull read
				;on error try other density
	LD	HL,(DSTYPT)	;get disk specification table
	BIT	DDENS,(HL)	;test density bit
	JR	NZ,DTYDD	;if set, try double density
	SET	DDENS,(HL)	;else, set single density bit
	RES	7,(HL)		;set single side
	JR	DTYPES		;use common part
DTYDD:	RES	DDENS,(HL)	;set double density bit
	LD	A,(HL)		;get updated density / precomp.
	SET	7,(HL)		;set double side
DTYPES:	LD	A,(HL)		;get updated density / precomp.
	OUT	(DENSEL),A	;set controller
	CALL	SELDSK		;try with other density
	OR	A		;
	RET	Z		;if error still occurs -> done
;
DTYPE0:	LD	A,(CURTRK)	;get current track from read ID table
	OUT	(FCTRCK),A	;set it into controller track register
	LD	HL,(DSTYPT)	;test for single/double density
	LD	A,(HL)		;definition byte to A
	BIT	DDENS,A		;test density 
	JR	Z,SETDDT	;bit not set, get double density link table
	BIT	3,A		;test now for 8" / 5 1/4"
	LD	HL,SDLTA5	;get 5 1/4 zoll link table
	JR	NZ,DTYPE1	;
	LD	HL,SDLTAB	;get linktable top for 8" single density
	JR	DTYPE1		;
;
SETDDT:	BIT	3,A		;test now for 8" / 5 1/4"
	LD	HL,DDLTA5	;get 5 1/4 zoll link table
	JR	NZ,DTYPE1	;
	LD	HL,DDLTAB	;get double density linke table
DTYPE1:	BIT	7,A		;double side bit set ?
	JR	NZ,DTYPE2	;if not, continue
	LD	BC,8		;add offset for single side table part
	ADD	HL,BC		;
DTYPE2:	LD	D,0		;compute sector size
	LD	A,(CURSLE)	;get sector length from read status
	ADD	A,A		;multiply by two
	LD	E,A		;
	ADD	HL,DE		;HL now holds pointer to spec. dsk tab.
	LD	E,(HL)		;load specification table address
	INC	HL		;
	LD	D,(HL)		;
	LD	A,D		;upper addres to A
	OR	A		;table entry zero ?
	RET	Z		;if, disk format not specified
	LD	(IX+12),E	;SET DISK SPECIFICATIO TABLE ADDR.
	LD	(IX+13),D	;for OS
	LD	HL,(DSTYPT)	;set spec. dsk tab pointer also
	INC	HL		;to to drive table
	INC	HL		;
	LD	(HL),E		;
	INC	HL		;
	LD	(HL),D		;
	INC	HL		;HL points to track address
	LD	A,(CURTRK)	;set current track into table
	LD	(HL),A		;
	LD	A,0FFH		;MEANS DRIVE READY
	RET			;DONE
;
;
;
DREADY:	LD	A,(IX+1)	;get requested disk number
	SUB	MDRNO		;subtract max. drive number
	LD	A,0		;set error code
	RET	NC		;
	LD	A,(IX+1)	;get requested drive number again
	SET	SIDES,A		;select side 0
	RES	MOTON,A		;set motor on
	OUT	(DRVSEL),A	;select drive
DREAD1:	IN	A,(FCSTAT)	;ready status test
	BIT	BUSY,A		;busy test
	JR	NZ,DREAD1	;on busy set, loop
	LD	(STAT1),A	;save the type 1 status
	BIT 	READY,A		;drive ready ?
	LD	A,0		;
	RET	NZ		;bit set, means not ready
	LD	A,0FFH		;else set ready condition
	RET			;done
;
;
;
DFORMA:	CALL	DREADY		;get disk status
	OR	A		;
	LD	A,0FFH		;
	RET	Z		;return, if drive is not ready
	CALL	SETDSK		;get table address
	LD	A,(IX+5)	;test head 1 select flag
	BIT	7,A		;
	LD	A,(IX+1)	;get requested drive
	SET	SIDES,A		;select side 0
	JR	Z,$+4		;if bit set side 1 request
	RES	SIDES,A		;select side 1 
	OUT	(DRVSEL),A	;select drive and side
	LD	A,(IX+4)	;test density flag
	BIT	7,A		;if set double density
	SET	DDENS,(HL)	;set single density
	RES	7,(HL)		;reset double side bit
	JR	Z,$+6		;
	RES	DDENS,(HL)	;select double density
	SET	7,(HL)		;set also double side bit
	LD	A,(HL)		;get drive definition byte
	OUT	(DENSEL),A	;issue density, precomp. values
	LD	A,(IX+2)	;get requested track number
	CP	0		;on first track recalibrate disk
	CALL	Z,HOME		;
	LD	A,SEEKC		;get seek command
	RES	2,A		;dissable track verify
	LD	(RQCMD),A	;set command
	LD	A,(IX+2)	;get track number
	CALL	SEEK		;and position head
	LD	A,WRTTRK	;set command type
	LD	(SREWRC),A	;
	LD	A,0FFH		;set sector count to format
	LD	(SECCNT),A	;
	CALL	SETDMA		;setup DMA for track write
	LD	A,ENADMA	;START DMA
	OUT	(MASKR),A	;
	LD	C,WRTTRK	;get command
	CALL	SETCMD		;issue command
	LD	A,(STAT1)	;
	OR	A		;
	RET	Z		;
	LD	A,0FFH		;
	RET			;done
;
	PAGE
;
;	SUBROUTINES AREA
;
FCISR::	DI			;FDCONTROLER INTERUPT ON RAEDY
	LD	(INTSP##),SP	;save stack pointer
	LD	SP,INTSTK##	;get auxilary stack
	PUSH	AF		;
	PUSH	BC		;
	PUSH	DE		;
	PUSH	HL		;
	LD	HL,EVENTC	;SIGNAL INT. OCURRED
	CALL	SIGNAL##	;
	LD	A,DISDMA	;DISABLE DMA TRANSFER
	OUT	(MASKR),A	;
	LD	A,3		;dissable interupt
	OUT	(CTC4),A	;
	POP	HL		;
	POP	DE		;
	POP	BC		;
	POP	AF		;
	LD	SP,(INTSP##)	;restore stack pointer
	EI
	RETI
	JP	ISRXIT##	;exit thru disspatcher
;
;
;
SELDSK:	CALL	DREADY		;test ready status
	OR	A		;on error ret
	RET	Z		;
	LD	A,MAXTRY	;set retry counter to start value
	LD	(RTRYC),A	;
	LD	A,(IX+1)	;get requested drive number again
	SET	SIDES,A		;select side 0
	OUT	(DRVSEL),A	;
SELDS1:	LD	A,READS		;set read command for DMA initialization
	LD	(SREWRC),A	;
	LD	HL,RECID	;GET DMA ADDRESS
	LD	(DMAADR),HL	;SET IT TO DMA COMMAND
	LD	HL,5		;SET BYTES TO MOVE (-1)
	LD	(DMACNT),HL	;STORE IT
	CALL	SETDM3		;initialize DMA
	LD	C,READAD	;load read address comand
	LD	A,ENADMA	;enable the DMA
	OUT	(MASKR),A	;
	CALL	SETCMD		;
SELDS2:	LD	A,(STAT1)	;
	OR	A		;on zero no error at all
	LD	A,0FFH		;set succesfull ID read
	RET	Z		;good return
	XOR	A		;set error
	RET			;done, with error
;
;
;
SETDMA:	LD	H,(IX+11)	;GET DMA ADDRESS
	LD	L,(IX+10)	;
	LD	(DMAADR),HL	;SET IT TO DMA COMMAND
	LD	A,(SECCNT)	;
	CP	0FFH		;on FF no count update
	JR	Z,SETDM1	;
	LD	A,(IX+18)	;get sector size
	AND	3		;
	LD	HL,128		;set minimum sector size
	CALL	MULLOP		;multiply sector size
	LD	A,(SECCNT)	;multiply sector size by sector count
	CALL	MULLOP		;
	JR	SETDM2		;
SETDM1:	LD	H,(IX+9)	;get number of bytes to move
	LD	L,(IX+8)	;
SETDM2:	DEC	HL		;minus 1
	LD	(DMACNT),HL	;save move count
SETDM3:	LD	A,DISDMA	;dissable DMA
	OUT	(MASKR),A	;
	DI			;
	LD	A,(SREWRC)	;get command type
	LD	HL,DMACMD	;
	BIT	5,A		;test direction (read or write)
	LD	A,DMAWR		;
	JR	NZ,SETDM4	;
	LD	A,DMARD		;no write, set read command
SETDM4:	OUT	(MODER),A	;
	OUT	(CLIFF),A	;reset flipp/flopp
	LD	HL,(DMAADR)	;output dma address to controller
	LD	A,L		;
	OUT	(CH3DMA),A	;
	LD	A,H		;
	OUT	(CH3DMA),A	;
	LD	HL,(DMACNT)	;output move count to controller
	LD	A,L		;
	OUT	(CH3TC),A	;
	LD	A,H		;
	OUT	(CH3TC),A	;
	EI			;
	RET			;
;
;
;
MULLOP:	SUB	1		;multiply HL by A
	RET	C		;on carry done
	ADD	HL,HL		;
	JR	MULLOP		;loop
;
;
;
HOME:	CALL	SETDSK		;get drive table
	INC	HL		;update current track number
	INC	HL		;
	INC	HL		;
	INC	HL		;
	LD	(HL),0		;
        LD    	C,RESTOR   	;get restore comand
	CALL	SETCMD		;WAIT FOR INT.
	OR	A		;error occured during restore ?
	RET	Z		;if so, done
	LD	A,(STAT1)	;get the status again
	BIT	2,A		;track 0 detected ?
	LD	A,0		;
	RET	Z		;if not set, track 0 not reached !
HOME1:	LD	(FCTRCK),A	;set track register to 0
	LD	A,0FFH		;track 0 set
	RET			;done
;
;
;
SETTRK:	LD	A,SEEKC		;set requested command
	LD	(RQCMD),A	;
	CALL	DREADY		;get disk ready status
	OR	A		;
	RET	Z		;if not ready, done
	CALL	SETDSK		;get drive table address
	LD	A,(HL)		;get density and precomp value
	OUT	(DENSEL),A	;issue it to the controllerr
	INC	HL		;get current track address from table
	INC	HL		;
	INC	HL		;
	INC	HL		;
	LD	A,(HL)		;
	EX	DE,HL		;save track address
	OUT	(FCTRCK),A	;set current track to controler
	LD	C,A		;save current track
	LD	A,(IX+2)	;GET REQUESTED TRACK NUMBER
	CP	C		;REQUESTED = CURRENT ?
	JP	Z,DREADY	;IF SO,DONE
	EX	DE,HL		;get track address back
	LD	(HL),A		;and set new track number
;
;
;
SEEK:	OUT   	(FCDATA),A	;set new track
        LD    	A,(RQCMD)	;get command type
	LD	HL,(DSTYPT)	;set step rate
	INC	HL		;
	OR	(HL)		;
	LD	C,A		;save updated command
	CALL	SETCMD		;issue command
	AND	00011000B	;test seek err., crc err.
	LD	A,0FFH		;set no error
	RET	Z		;
	XOR	A		;set error
	RET			;done
;
;
;
SETSEC: LD	HL,(DSTYPT)	;get current disk spec. pointer
	INC	HL		;
	INC	HL		;points to disk specification table
	LD	E,(HL)		;
	INC	HL		;
	LD	D,(HL)		;DE now holds spec. tab address
	LD	HL,12		;
	ADD	HL,DE		;HL points to translation table address
	XOR	A		;(upper byte)
	CP	(HL)		;if zero no tab entry
	LD	A,(SECTOR)	;get requested sector
	LD	C,A		;save sector
	JR	Z,SETSE1	;
;
	LD	B,0		;
	LD	D,(HL)		;GET TABLE ADDRESS
	DEC	HL		;HL points to lower byte
	LD	E,(HL)		;
	EX	DE,HL		;
	ADD	HL,BC		;OFFSET ADD
	LD	C,(HL)		;GET PHYSICAL SECTOR
;
SETSE1:	LD	HL,(DSTYPT)	;get two sided bit from drive table
	INC	C		;set physical sector base to 1
	BIT	7,(HL)		;test it
	JR	Z,SETSE3	;if not set, single side
	LD	A,(IX+19)	;get number of sectors per track
	SRL	A		;devide sectors/track by 2
	LD	B,A		;save sectors/side
	SUB	C		;subtract requested sector
	LD	A,(IX+1)	;get drive address
	SET	SIDES,A		;select side 0
	JR	NC,SETSE2	;on carry req. sector is on side 1
	RES	SIDES,A		;select side 1
	OUT	(DRVSEL),A	;
	LD	A,C		;get requested physical sector
	SUB	B		;subtract sectors/side
	JR	SETSE4		;
SETSE2:	OUT	(DRVSEL),A	;
SETSE3:	LD	A,C		;get requested sector
SETSE4:	OUT   	(FCSECT),A	;SET SECTOR REGISTER
	LD	A,(SECCNT)	;DECREMENT SECTOR COUNT
	DEC	A		;
	LD	(SECCNT),A	;
        RET
;
;
;
SETDSK:	LD	HL,DRVTAB	;SET DISK ACCES TABLE
	LD	A,(IX+1)	;FOR SELECTED DISK
	LD	B,0		;
	LD	C,8		;TABLE STEP RATE
SETDS1:	CP	0		;IF DRIVE =0 NO ADD
	JR	Z,SETDS2	;
	DEC	A		;
	ADD	HL,BC		;
	JR	SETDS1		;LOOP TILL A=0
SETDS2:	LD	(DSTYPT),HL	;save specification table address
	RET			;DONE
;
SETCMD:	LD	A,0D7H		;enable floppy interupt
	OUT	(CTC4),A	;
	LD	A,1		;
	OUT	(CTC4),A	;
	LD	HL,EVENTC	;
	LD	A,C		;get saved command back
	OUT   	(FCCONT),A	;
	CALL	WAIT##		;WAIT FOR INT.
;
;
;
STATUS:	IN	A,(FCSTAT)	;status test for type I commands
	BIT	BUSY,A		;controller busy ?
	JR	NZ,STATUS	;if so, wait for change
	LD	(STAT1),A	;else save staus for further access
	RET			;no error return
;
;	DISKS SPECIFICATION TABLES
;
	DSEG			;LOCATED IN DATA SEGMENT AREA
;
DDLTAB:	DW	0		;double side, double density 128 bytes
	DW	DSDDT1		;double side, double density 256 bytes
	DW	DSDDT2		;double side, double density 512 bytes
	DW	DSDDT3		;double side, double density 1024 bytes
	DW	0		;single side, double density 128 bytes
	DW	0		;single side, double density 256 bytes
	DW	0		;single side, double density 512 bytes
	DW	0		;single side, double density 1024 bytes
;       
SDLTAB:	DW	0		;double side single density 128 bytes
	DW	0		;double side single density 256 bytes
	DW	0		;double side single density 512 bytes
	DW	0		;double side single density 1024 bytes
	DW	SSSDT1		;single side single density 128 bytes
	DW	SSSDT2		;single side single density 256 bytes
	DW	SSSDT3		;single side single density 512 bytes
	DW	0		;single side single density 1024 bytes
;
DDLTA5:	DW	0		;double side, double density 128 bytes
	DW	DSDT51		;double side, double density 256 bytes
	DW	0		;double side, double density 512 bytes
	DW	0		;double side, double density 1024 bytes
	DW	0		;single side, double density 128 bytes
	DW	0		;single side, double density 256 bytes
	DW	0		;single side, double density 512 bytes
	DW	0		;single side, double density 1024 bytes
;       
SDLTA5:	DW	0		;double side single density 128 bytes
	DW	0		;double side single density 256 bytes
	DW	0		;double side single density 512 bytes
	DW	0		;double side single density 1024 bytes
	DW	SSDT51		;single side single density 128 bytes
	DW	0		;single side single density 256 bytes
	DW	0		;single side single density 512 bytes
	DW	0		;single side single density 1024 bytes
;       
DSDDT1:	DB	4	;BLOCK SIZE = 2K
	DW	500D	;NUMBER OF BLOCKS
	DB	4	;NUMBER OF DIRECTORY BLOKS
	DB	1	;SECTOR SIZE = 256
	DW	52	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	0	;RESERVED TRACKS
	DW	0
;       
DSDDT2:	DB	4	;BLOCK SIZE = 2K
	DW	577	;NUMBER OF BLOCKS
	DB	4	;NUMBER OF DIRECTORY BLOKS
	DB	2	;SECTOR SIZE = 512
	DW	30	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	2	;RESERVED TRACKS
	DW	RCTAB	;
;       
DSDDT3:	DB	4	;BLOCK SIZE = 2K
	DW	616	;NUMBER OF BLOCKS
	DB	4	;NUMBER OF DIRECTORY BLOKS
	DB	3	;SECTOR SIZE = 1K
	DW	16	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	0	;RESERVED TRACKS
	DW	0
;
;	CPM COMPATIBLE SPECIFICATION TABLE
;
SSSDT1:	DB	3	;BLOCK SIZE = 1K
	DW	243	;NUMBER OF BLOCKS
	DB	2	;NUMBER OF DIRECTORY BLOKS
	DB	0	;SECTOR SIZE = 128
	DW	26	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	2	;RESERVED TRACKS
	DW	STRTA2	;ADDRES OF SECTOR TRANSLATION TABLE
;       
SSSDT2:	DB	4	;BLOCK SIZE = 2K
	DW	144	;NUMBER OF BLOCKS
	DB	2	;NUMBER OF DIRECTORY BLOKS
	DB	1	;SECTOR SIZE = 256
	DW	15	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	0	;RESERVED TRACKS
	DW	0	;
;       
SSSDT3:	DB	4	;BLOCK SIZE = 2K
	DW	154	;NUMBER OF BLOCKS
	DB	2	;NUMBER OF DIRECTORY BLOKS
	DB	2	;SECTOR SIZE = 512
	DW	8	;SECTORS PER TRACK
	DW	77	;TRACKS PER DISK
	DW	0	;RESERVED TRACKS
	DW	0
;       
SSDT51:	DB	3	;BLOCK SIZE = 1K
	DW	80	;NUMBER OF BLOCKS
	DB	1	;NUMBER OF DIRECTORY BLOKS
	DB	0	;SECTOR SIZE = 128 MINI
	DW	16	;SECTORS PER TRACK
	DW	40	;TRACKS PER DISK
	DW	0	;RESERVED TRACKS
	DW	0	;
;
DSDT51:	DB	4	;BLOCK SIZE = 1K
	DW	320	;NUMBER OF BLOCKS
	DB	1	;NUMBER OF DIRECTORY BLOKS
	DB	1	;SECTOR SIZE = 256 MINI
	DW	32	;SECTORS PER TRACK
	DW	80	;TRACKS PER DISK
	DW	2	;RESERVED TRACKS
	DW	OLYTAB	;
;       
;	PHYSICAL TO LOGICAL SECTOR TRANSLATION TABLE
;
STRTA2:	DB	0,6,12,18,24,4,10,16,22,2,8,14,20
	DB	1,7,13,19,25,5,11,17,23,3,9,15,21
;
RCTAB:	DB	0,4,8,12,1,5,9,13,2,6,10,14,3,7,11,15,19
	DB	23,27,16,20,24,28,17,21,25,29,18,22,26
;
OLYTAB:	DB	0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30
	DB	1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31
;
DMACMD:	DB	0		;DMA command (read or write)
DMAADR:	DW	0		;DMA address
DMACNT:	DW	0		;DMA count
;	
EVENTC:	DW	0		;EVENT COUNTER
	DW	$		;
	DW	$-2		;
;
MUXSPH:	DW	1		;SIGNAL DISPATCHER DRIVER IN USE
	DW	$		;
	DW	$-2		;
;
SREWRC:	DB	0		;SAVE BYTE FOR READ/WRITE COMMAND
SECCNT:	DB	0		;NUMBEROF SECTORS TO READ
CURDSK:	DB	0FFH		;CURRENT LOGGED IN DISK
SECTOR:	DB	0		;CURRENT SECTOR ADDRESS
STAT1:	DB	0		;type 1 command status
STAT2:	DB	0		;type 2/3 commands status
RQCMD:	DB	0		;command save area
;
DRVTAB:	DB	00100100B	;bit meaning as follows
				; 7 = 0 - single side
				;     1 - double side
				; 6 = not used
				; 5 = 0 - double density
				;     1 - single density
				; 4 = not used
				; 3 = 0 - 8" Floppy
				;     1 - 5 1/4" Floppy
				; 2-0 precompesition times,
				; as specfied in 9229 product description
	DB	0		;step rate value
				; byte meaning for 8" as follows
				; 0 = 3ms step rate
				; 1 = 6ms
				; 2 = 10ms
				; 3 = 15ms
				; byte meaning for 5 1/4" as follows
				; 0 = 6ms step rate
				; 1 = 12ms
				; 2 = 20ms
				; 3 = 30ms
	DW	0		;drive specification table linke pointer
	DB	0		;current track
	DS	3		;space
;
	DB	0		;precomp, density, disk type
	DB	0		;step rate value
	DW	0		;drive specification table linke pointer
	DB	0		;current track
	DS	3		;space
;
	DB	88H		;precomp, density, disk type
	DB	0		;step rate value
	DW	0		;drive specification table linke pointer
	DB	0		;current track
	DS	3		;space
;
	DB	0		;precomp, density, disk type
	DB	0		;step rate value
	DW	0		;drive specification table linke pointer
	DB	0		;current track
	DS	3		;space
;
RECID:				;record id field, set by read address
CURTRK:	DB	0		;cuurrent track position
CURSID:	DB	0		;selected side
CURSEC:	DB	0		;sector number read
CURSLE:	DB	0		;sector length decoded by controler
				;0 = 128, 1 = 256, 2=512, 3 = 1024
CURCRC:	DW	0		;crc for id field
RTRYC:	DB	0		;retry counter
DSTYPT:	DW	0		;disktype table address
;
	END
«eof»