xref: /csrg-svn/sys/tahoe/vba/vdreg.h (revision 30519)
1*30519Ssam /*	vdreg.h	1.8	87/02/18	*/
225677Ssam 
325677Ssam /*
4*30519Ssam  * Versabus VDDC/SMDE disk controller definitions.
525677Ssam  */
625677Ssam 
725677Ssam /*
8*30519Ssam  * Controller communications block.
925677Ssam  */
10*30519Ssam struct vddevice {
11*30519Ssam 	u_long	vdcdr;		/* controller device register */
12*30519Ssam 	u_long	vdreset;	/* controller reset register */
13*30519Ssam 	u_long	vdcsr;		/* control-status register */
14*30519Ssam 	long	vdrstclr;	/* reset clear register */
15*30519Ssam 	u_short	vdstatus[16];	/* per-drive status register */
16*30519Ssam 	u_short	vdicf_status;	/* status change interupt control format */
17*30519Ssam 	u_short	vdicf_done;	/* interrupt complete control format */
18*30519Ssam 	u_short	vdicf_error;	/* interrupt error control format */
19*30519Ssam 	u_short	vdicf_success;	/* interrupt success control format */
20*30519Ssam 	u_short	vdtcf_mdcb;	/* mdcb transfer control format */
21*30519Ssam 	u_short	vdtcf_dcb;	/* dcb transfer control format */
22*30519Ssam 	u_short	vdtcf_trail;	/* trail transfer control format */
23*30519Ssam 	u_short	vdtcf_data;	/* data transfer control format */
24*30519Ssam 	u_long	vdccf;		/* controller configuration flags */
25*30519Ssam 	u_long	vdsecsize;	/* sector size */
26*30519Ssam 	u_short	vdfill0;
27*30519Ssam 	u_char	vdcylskew;	/* cylinder to cylinder skew factor */
28*30519Ssam 	u_char	vdtrackskew;	/* track to track skew factor */
29*30519Ssam 	u_long	vdfill1;
30*30519Ssam 	u_long	vddfr;		/* diagnostic flag register */
31*30519Ssam 	u_long	vddda;		/* diagnostic dump address */
32*30519Ssam };
3325677Ssam 
34*30519Ssam /* controller types */
35*30519Ssam #define	VDTYPE_VDDC	1	/* old vddc controller (smd only) */
36*30519Ssam #define	VDTYPE_SMDE	2	/* new smde controller (smd-e) */
3725677Ssam 
3825677Ssam /*
39*30519Ssam  * Controller status definitions.
4025677Ssam  */
41*30519Ssam #define	CS_SCS	0xf		/* status change source (drive number) */
42*30519Ssam #define	CS_ELC	0x10		/* error on last command */
43*30519Ssam #define	CS_ICC	0x60		/* interupt cause code */
44*30519Ssam #define   ICC_NOI  0x00		/* no interupt */
45*30519Ssam #define   ICC_DUN  0x20		/* no interupt */
46*30519Ssam #define   ICC_ERR  0x40		/* no interupt */
47*30519Ssam #define   ICC_SUC  0x60		/* no interupt */
48*30519Ssam #define	CS_GO	0x80		/* go bit (controller busy) */
49*30519Ssam #define	CS_BE	0x100		/* buss error */
50*30519Ssam #define	CS_BOK	0x4000		/* board ok */
51*30519Ssam #define	CS_SFL	0x8000		/* system fail */
52*30519Ssam #define	CS_LEC	0xff000000	/* last error code */
5325677Ssam 
5425677Ssam /*
55*30519Ssam  * Drive status definitions.
5625677Ssam  */
57*30519Ssam #define	STA_UR	0x1		/* unit ready */
58*30519Ssam #define	STA_OC	0x2		/* on cylinder */
59*30519Ssam #define	STA_SE	0x4		/* seek error */
60*30519Ssam #define	STA_DF	0x8		/* drive fault */
61*30519Ssam #define	STA_WP	0x10		/* write protected */
62*30519Ssam #define	STA_US	0x20		/* unit selected */
6325677Ssam 
6425677Ssam /*
65*30519Ssam  * Interupt Control Field definitions.
6625677Ssam  */
67*30519Ssam #define	ICF_IPL	0x7		/* interupt priority level */
68*30519Ssam #define	ICF_IEN	0x8		/* interupt enable */
69*30519Ssam #define	ICF_IV	0xff00		/* interupt vector */
7025677Ssam 
7125677Ssam /*
72*30519Ssam  * Transfer Control Format definitions.
7325677Ssam  */
7425677Ssam #define	TCF_AM	0xff		/* Address Modifier */
7525677Ssam #define	  AM_SNPDA   0x01	/* Standard Non-Privileged Data Access */
7625677Ssam #define	  AM_SASA    0x81	/* Standard Ascending Sequential Access */
7725677Ssam #define	  AM_ENPDA   0xf1	/* Extended Non-Privileged Data Access */
7825677Ssam #define	  AM_EASA    0xe1	/* Extended Ascending Sequential Access */
7925677Ssam #define	TCF_BTE	0x800		/* Block Transfer Enable */
8025677Ssam 
81*30519Ssam /*
82*30519Ssam  * Controller Configuration Flags.
83*30519Ssam  */
84*30519Ssam #define	CCF_STS	0x1		/* sectors per track selectable */
85*30519Ssam #define	CCF_EAV	0x2		/* enable auto vector */
86*30519Ssam #define	CCF_ERR	0x4		/* enable reset register */
87*30519Ssam #define CCF_DER 0x8		/* disable error recovery */
88*30519Ssam #define	CCF_XMD	0x60		/* xmd transfer mode (bus size) */
89*30519Ssam #define	  XMD_8BIT  0x20	/*   do only 8 bit transfers */
90*30519Ssam #define	  XMD_16BIT 0x40	/*   do only 16 bit transfers */
91*30519Ssam #define	  XMD_32BIT 0x60	/*   do only 32 bit transfers */
92*30519Ssam #define	CCF_BSZ	0x300		/* burst size */
9325677Ssam #define	  BSZ_16WRD 0x000	/*   16 word transfer burst */
9425677Ssam #define	  BSZ_12WRD 0x100	/*   12 word transfer burst */
9525677Ssam #define	  BSZ_8WRD  0x200	/*   8 word transfer burst */
9625677Ssam #define	  BSZ_4WRD  0x300	/*   4 word transfer burst */
97*30519Ssam #define CCF_SEN	0x400		/* cylinder/track skew enable (for format) */
98*30519Ssam #define	CCF_ENP	0x1000		/* enable parity */
99*30519Ssam #define	CCF_EPE	0x2000		/* enable parity errors */
100*30519Ssam #define	CCF_EDE	0x10000		/* error detection enable */
101*30519Ssam #define	CCF_ECE	0x20000		/* error correction enable */
10225677Ssam 
10325677Ssam /*
10425677Ssam  * Diagnostic register definitions.
10525677Ssam  */
106*30519Ssam #define	DIA_DC	0x7f		/* dump count mask */
107*30519Ssam #define	DIA_DWR	0x80		/* dump write/read flag */
108*30519Ssam #define	DIA_ARE	0x100		/* auto rebuild enable */
109*30519Ssam #define	DIA_CEN	0x200		/* call enable flag */
110*30519Ssam #define	DIA_KEY	0xAA550000	/* reset enable key */
11125677Ssam 
11225677Ssam /*
11325677Ssam  * Perform a reset on the controller.
11425677Ssam  */
115*30519Ssam #define	VDRESET(a,t) { \
116*30519Ssam 	if ((t) == VDTYPE_SMDE) { \
117*30519Ssam 		((struct vddevice *)(a))->vddfr = DIA_KEY|DIA_CEN; \
118*30519Ssam 		((struct vddevice *)(a))->vdcdr = (u_long)0xffffffff; \
11925677Ssam 		DELAY(5000000); \
12025677Ssam 	} else { \
121*30519Ssam 		((struct vddevice *)(a))->vdreset = 0; \
12225677Ssam 		DELAY(1500000); \
12325677Ssam 	} \
12425677Ssam }
12525677Ssam 
12625677Ssam /*
12725677Ssam  * Abort a controller operation.
12825677Ssam  */
129*30519Ssam #define	VDABORT(a,t) { \
130*30519Ssam 	if ((t) == VDTYPE_VDDC) { \
131*30519Ssam 		movow((a), (VDOP_ABORT&0xffff0000)>>16) ; \
132*30519Ssam 		movow((int)(a)+2, VDOP_ABORT&0xffff); \
13325677Ssam 	} else \
134*30519Ssam 		((struct vddevice *)(a))->vdcdr = (u_long)VDOP_ABORT; \
13525677Ssam 	DELAY(1000000); \
13625677Ssam }
13725677Ssam 
13825677Ssam /*
139*30519Ssam  * Start a command.
14025677Ssam  */
141*30519Ssam #define VDGO(a,mdcb,t) {\
142*30519Ssam 	if ((t) == VDTYPE_VDDC) { \
143*30519Ssam 		movow((a), ((int)(mdcb)&0xffff0000)>>16) ; \
144*30519Ssam 		movow((int)((a))+2, (int)(mdcb)&0xffff); \
14525677Ssam 	} else \
146*30519Ssam 		((struct vddevice *)(a))->vdcdr = (mdcb); \
14725677Ssam }
14825677Ssam 
14925677Ssam /*
150*30519Ssam  * MDCB layout.
151*30519Ssam  */
152*30519Ssam struct mdcb {
153*30519Ssam 	struct	dcb *mdcb_head;		/* first dcb in list */
154*30519Ssam 	struct	dcb *mdcb_busy;		/* dcb being processed */
155*30519Ssam 	struct	dcb *mdcb_intr;		/* dcb causing interrupt */
156*30519Ssam 	long	mdcb_status;		/* status of dcb in mdcb_busy */
157*30519Ssam };
158*30519Ssam 
159*30519Ssam /*
160*30519Ssam  * DCB definitions.
161*30519Ssam  */
162*30519Ssam 
163*30519Ssam /*
16425677Ssam  * A disk address.
16525677Ssam  */
16625677Ssam typedef struct {
167*30519Ssam 	u_char	track;			/* all 8 bits */
168*30519Ssam 	u_char	sector;			/* all 8  bits */
169*30519Ssam 	u_short	cylinder;		/* low order 12 bits */
17025677Ssam } dskadr;
17125677Ssam 
17225677Ssam /*
17325677Ssam  * DCB trailer formats.
17425677Ssam  */
17525677Ssam /* read/write trailer */
17625677Ssam typedef struct {
17725677Ssam 	char	*memadr;	/* memory address */
17825677Ssam 	u_long	wcount;		/* 16 bit word count */
17925677Ssam 	dskadr	disk;		/* disk address */
18025677Ssam } trrw;
18125677Ssam 
18225677Ssam /* scatter/gather trailer */
18325677Ssam typedef struct {
18425677Ssam 	trrw	start_addr;
18525677Ssam 	struct {
18625677Ssam 		char	*nxt_addr;
18725677Ssam 		u_long	nxt_len;
18825677Ssam 	} addr_chain[126];
18925677Ssam } trsg;
19025677Ssam 
19125677Ssam /* seek trailer format */
19225677Ssam typedef struct {
19325677Ssam 	dskadr	skaddr;
19425677Ssam } trseek;
19525677Ssam 
19625677Ssam /* format trailer */
19725677Ssam typedef struct {
19825677Ssam 	char	*addr;		/* data buffer to be filled on sector*/
19925677Ssam 	long	nsectors;	/* # of sectors to be formatted */
20025677Ssam 	dskadr	disk;		/* disk physical address info */
20125677Ssam 	dskadr  hdr;		/* header address info */
20225677Ssam } trfmt;
20325677Ssam 
20425677Ssam /* reset/configure trailer */
20525677Ssam typedef struct {
20625677Ssam 	long	ncyl;		/* # cylinders */
20725677Ssam 	long	nsurfaces;	/* # surfaces */
20825677Ssam 	long	nsectors;	/* # sectors */
20925677Ssam 	long	slip_sec;	/* # of slip sectors */
21029683Ssam 	long	recovery;	/* recovery flags */
21125677Ssam } treset;
21225677Ssam 
21325677Ssam /*
21425677Ssam  * DCB layout.
21525677Ssam  */
216*30519Ssam struct dcb {
217*30519Ssam 	struct	dcb *nxtdcb;	/* next dcb */
21825677Ssam 	short	intflg;		/* interrupt settings and flags */
21925677Ssam 	short	opcode;		/* DCB command code etc... */
22025677Ssam 	long	operrsta;	/* error & status info */
22125677Ssam 	short	fill;		/* not used */
22225677Ssam 	char	devselect;	/* drive selection */
22325677Ssam 	char	trailcnt;	/* trailer Word Count */
22425677Ssam 	long	err_memadr;	/* error memory address */
22525677Ssam 	char	err_code;	/* error codes for SMD/E */
22625677Ssam 	char	fill2;		/* not used */
22725677Ssam 	short	err_wcount;	/* error word count */
22825677Ssam 	char	err_trk;	/* error track/sector */
22925677Ssam 	char	err_sec;	/* error track/sector */
23025677Ssam 	short	err_cyl;	/* error cylinder adr */
23125677Ssam 	union {
23225677Ssam 		trseek	sktrail;	/* seek command trailer */
23325677Ssam #ifdef notdef
23425677Ssam 		trsg	sgtrail;	/* scatter/gather trailer */
23525677Ssam #endif
23625677Ssam 		trrw	rwtrail;	/* read/write trailer */
23725677Ssam 		trfmt	fmtrail;	/* format trailer */
23825677Ssam 		treset	rstrail;	/* reset/configure trailer */
23925677Ssam 	} trail;
240*30519Ssam };
24125677Ssam 
24225677Ssam /*
243*30519Ssam  * DCB command codes.
24425677Ssam  */
245*30519Ssam #define	VDOP_RD		0x80		/* read data */
246*30519Ssam #define	VDOP_FTR	0xc0		/* full track read */
247*30519Ssam #define	VDOP_RAS	0x90		/* read and scatter */
248*30519Ssam #define	VDOP_RDRAW	0x600		/* read unformatted disk sector */
249*30519Ssam #define	VDOP_CMP	0xa0		/* compare */
250*30519Ssam #define	VDOP_FTC	0xe0		/* full track compare */
251*30519Ssam #define	VDOP_RHDE	0x180		/* read header, data & ecc */
252*30519Ssam #define	VDOP_WD		0x00		/* write data */
253*30519Ssam #define	VDOP_FTW	0x40		/* full track write */
254*30519Ssam #define	VDOP_WTC	0x20		/* write then compare */
255*30519Ssam #define	VDOP_FTWTC	0x60		/* full track write then compare */
256*30519Ssam #define	VDOP_GAW	0x10		/* gather and write */
257*30519Ssam #define	VDOP_WDE	0x100		/* write data & ecc */
258*30519Ssam #define	VDOP_FSECT	0x900		/* format sector */
259*30519Ssam #define	VDOP_GWC	0x30		/* gather write & compare */
260*30519Ssam #define	VDOP_START	0x800		/* start drives */
261*30519Ssam #define	VDOP_RELEASE	0xa00		/* stop drives */
262*30519Ssam #define	VDOP_SEEK	0xb00		/* seek */
263*30519Ssam #define	VDOP_INIT	0xc00		/* initialize controller */
264*30519Ssam #define	VDOP_DIAG	0xd00		/* diagnose (self-test) controller */
265*30519Ssam #define	VDOP_CONFIG	0xe00		/* reset & configure drive */
266*30519Ssam #define	VDOP_STATUS	0xf00		/* get drive status */
26725677Ssam 
268*30519Ssam #define	VDOP_ABORT	0x80000000	/* abort current command */
269*30519Ssam 
27025677Ssam /*
271*30519Ssam  * DCB status definitions.
27225677Ssam  */
273*30519Ssam #define	DCBS_HCRC	0x00000001	/* header crc error */
274*30519Ssam #define	DCBS_HCE	0x00000002	/* header compare error */
275*30519Ssam #define	DCBS_WPT	0x00000004	/* drive write protected */
276*30519Ssam #define	DCBS_CHE	0x00000008	/* controller hardware error */
277*30519Ssam #define	DCBS_SKI	0x00000010	/* seek incomplete */
278*30519Ssam #define	DCBS_UDE	0x00000020	/* uncorrectable data error */
279*30519Ssam #define	DCBS_OCYL	0x00000040	/* off cylinder */
280*30519Ssam #define	DCBS_NRDY	0x00000080	/* drive not ready */
281*30519Ssam #define	DCBS_ATA	0x00000100	/* alternate track accessed */
282*30519Ssam #define	DCBS_SKS	0x00000200	/* seek started */
283*30519Ssam #define	DCBS_IVA	0x00000400	/* invalid disk address error */
284*30519Ssam #define	DCBS_NEM	0x00000800	/* non-existant memory error */
285*30519Ssam #define	DCBS_DPE	0x00001000	/* memory data parity error */
286*30519Ssam #define	DCBS_DCE	0x00002000	/* data compare error */
287*30519Ssam #define	DCBS_DDI	0x00004000	/* ddi ready */
288*30519Ssam #define	DCBS_OAB	0x00008000	/* operation aborted */
289*30519Ssam #define	DCBS_DSE	0x00010000	/* data strobe early */
290*30519Ssam #define	DCBS_DSL	0x00020000	/* data strobe late */
291*30519Ssam #define	DCBS_TOP	0x00040000	/* track offset plus */
292*30519Ssam #define	DCBS_TOM	0x00080000	/* track offset minus */
293*30519Ssam #define	DCBS_CCD	0x00100000	/* controller corrected data */
294*30519Ssam #define	DCBS_HARD	0x00200000	/* hard error */
295*30519Ssam #define	DCBS_SOFT	0x00400000	/* soft error (retry succesful) */
296*30519Ssam #define	DCBS_ERR	0x00800000	/* composite error */
297*30519Ssam #define DCBS_IVC	0x01000000	/* invalid command error */
298*30519Ssam /* bits 24-27 unused */
299*30519Ssam #define	DCBS_BSY	0x10000000	/* controller busy */
300*30519Ssam #define	DCBS_ICC	0x60000000	/* interrupt cause code */
301*30519Ssam #define	DCBS_INT	0x80000000	/* interrupt generated for this dcb */
30225677Ssam 
303*30519Ssam #define	VDERRBITS	"\20\1HCRC\2HCE\3WPT\4CHE\5DSKI\6UDE\7OCYL\10NRDY\
304*30519Ssam \11ATA\12SKS\13IVA\14NEM\15DPE\16DCE\17DDI\20OAB\21DSE\22DSL\23TOP\24TOM\
305*30519Ssam \25CCD\26HARD\27SOFT\30ERR\31IVC\35ABORTED\36FAIL\37COMPLETE\40STARTED"
30625677Ssam 
307*30519Ssam /* drive related errors */
308*30519Ssam #define	VDERR_DRIVE	(DCBS_SKI|DCBS_OCYL|DCBS_NRDY|DCBS_IVA)
309*30519Ssam /* controller related errors */
310*30519Ssam #define	VDERR_CTLR	(DCBS_CHE|DCBS_OAB|DCBS_IVC|DCBS_NEM)
311*30519Ssam /* potentially recoverable errors */
312*30519Ssam #define	VDERR_SOFT \
313*30519Ssam     (VDERR_DRIVE|VDERR_CTLR|DCBS_DCE|DCBS_DPE|DCBS_HCRC|DCBS_HCE)
314*30519Ssam /* uncorrected data errors */
315*30519Ssam #define	VDERR_HARD	(VDERR_SOFT|DCBS_WPT|DCBS_UDE)
31625677Ssam 
31725677Ssam /*
318*30519Ssam  * DCB status codes.
31925677Ssam  */
320*30519Ssam #define	DCBS_ABORT	0x10000000	/* dcb aborted */
321*30519Ssam #define	DCBS_FAIL	0x20000000	/* dcb unsuccesfully completed */
322*30519Ssam #define	DCBS_DONE	0x40000000	/* dcb complete */
323*30519Ssam #define	DCBS_START	0x80000000	/* dcb started */
32425677Ssam 
325*30519Ssam /*
326*30519Ssam  * DCB interrupt control.
327*30519Ssam  */
328*30519Ssam #define	DCBINT_NONE	0x0		/* don't interrupt */
329*30519Ssam #define	DCBINT_ERR	0x2		/* interrupt on error */
330*30519Ssam #define	DCBINT_SUC	0x1		/* interrupt on success */
331*30519Ssam #define	DCBINT_DONE	(DCBINT_ERR|DCBINT_SUC)
332*30519Ssam #define	DCBINT_PBA	0x4		/* proceed before acknowledge */
33325677Ssam 
334*30519Ssam /*
335*30519Ssam  * Sector formats.
336*30519Ssam  */
337*30519Ssam typedef union {
338*30519Ssam 	struct {
339*30519Ssam 		dskadr	hdr_addr;
340*30519Ssam 		short	smd_crc;
341*30519Ssam 	} smd;
342*30519Ssam 	struct {
343*30519Ssam 		dskadr	physical;
344*30519Ssam 		dskadr	logical;
345*30519Ssam 		long	smd_e_crc;
346*30519Ssam 	} smd_e;
347*30519Ssam } fmt_hdr;
34825677Ssam 
349*30519Ssam /* Sector Header bit assignments */
350*30519Ssam #define	VDMF	0x8000		/* Manufacturer Fault 1=good sector */
351*30519Ssam #define	VDUF	0x4000		/* User Fault 1=good sector */
352*30519Ssam #define	VDALT	0x2000		/* Alternate Sector 1=alternate */
353*30519Ssam #define	VDWPT	0x1000		/* Write Protect 1=Read Only Sector */
354