xref: /original-bsd/sys/tahoe/vba/vddc.h (revision 8af5b582)
1 /*	vddc.h	1.1	85/07/21	*/
2 
3 /*
4 **	Header file for the VDDC (Versabus Direct Disk Controller) Driver
5 */
6 
7 #define	NSECPTRK 32		/* #sectors/track - fixed by VDDC */
8 #define SECTSIZ 512		/* sector size fixed by VDDC */
9 #define L2SIZ	9		/* log2 of sector size */
10 #define L2BSIZ	10		/* log2 of block size */
11 #define NVDDRV	3		/* number of drive types supported */
12 
13 /*
14 **	DCB Command Codes
15 */
16 
17 #define	RD	0x80		/* Read Data */
18 #define	FTR	0xc0		/* Full Track Read */
19 #define	RAS	0x90		/* Read and Scatter */
20 #define	C	0xa0		/* Compare */
21 #define	FTC	0xe0		/* Full Track Compare */
22 #define	RHDE	0x180		/* Read Header, Data & ECC (not used) */
23 #define	WD	0x00		/* Write Data */
24 #define	FTW	0x40		/* Full Track Write */
25 #define	WTC	0x20		/* Write Then Compare */
26 #define	FTWTC	0x60		/* Full Track Write Then Compare */
27 #define	GAW	0x10		/* Gather and Write */
28 #define	WDE	0x100		/* Write Data & ECC (not used) */
29 #define	FSECT	0x900		/* Format Sector */
30 #define	GWC	0x30		/* Gather Write & Compare */
31 #define	VDSTART 0x800		/* Start drives */
32 #define	VDRELEASE 0xa00		/* Stop drives */
33 #define	SEEK	0xb00		/* Seek */
34 #define	INIT	0xc00		/* Initialize VDDC */
35 #define	DIAG	0xd00		/* Diagnose (self-test) VDDC */
36 #define	RSTCFG	0xe00		/* Reset/Configure VDDC/DDI/Drive(s) */
37 #define	VDSTATUS   0xf00		/* VDDC Status */
38 #define	ABORT	0x80000000	/* To be written to VDDC Cntrl Register */
39 
40 /*
41  * Error/Status Symbolic Constants
42  */
43 #define	HCRCERR		0x1		/* Header CRC Error */
44 #define	HCMPERR		0x2		/* Header Compare Error */
45 #define	WPTERR		0x4		/* Write Protect Error/Status */
46 #define	SZTIMEOUT	0x8		/* Seize timeout Error */
47 #define	DSEEKERR	0x10		/* Disk Seek Error */
48 #define	UCDATERR	0x20		/* Uncorrectable Data Error */
49 #define	NOTCYLERR	0x40		/* Not on Cylinder Error */
50 #define	DRVNRDY		0x80		/* Drive Not Ready Error/Status */
51 #define	ALTACC		0x100		/* Alternate (track) accessed Status */
52 #define	SEEKSTRT	0x200		/* Seek Started Status */
53 #define	INVDADR		0x400		/* Invalid Disk Address Error */
54 #define	DNEMEM		0x800		/* Non-Existant Memory Error */
55 #define	PARERR		0x1000		/* Memory Parity Error */
56 #define	DCOMPERR	0x2000		/* Data Compare Error */
57 #define	DDIRDY		0x4000		/* DDI Ready Error/Status */
58 #define	OPABRT		0x8000		/* Operator Abort (Host) Error/Status */
59 #define	DSERLY		0x10000		/* Data Strobe Early */
60 #define	DSLATE		0x20000		/* Data Strobe Late */
61 #define	TOPLUS		0x40000		/* Track Offset Plus */
62 #define	TOMNUS		0x80000		/* Track Offset Minus */
63 #define	CPDCRT		0x100000	/* Cntlr Performed Data Correction */
64 #define	HRDERR		0x200000	/* Hard Error */
65 #define	SFTERR		0x400000	/* Soft Error (retry succesful) */
66 #define	ANYERR		0x800000	/* Any Error */
67 
68 #define	ERRBITS	"\20\30\27SOFT\26HARD\25CPDCRT\24TOMNUS\23TOPLUS\22DSLATE\
69 \21DSERLY\20OPABRT\17DDIRDY\16DCOMPERR\15PARERR\14DNEMEM\13INVADR\12SEEKSTRT\
70 \11ALTACC\10\DRVNRDY\7NOTCYLERR\6UCDATERR\5DSEEKERR\4SZTIMEOUT\3WPTERR\2HCMPERR\
71 \1HCRCERR"
72 
73 /*
74  * DCB Status Symbolic Constants
75  */
76 #define	DCBABT		0x10000000	/* DCB Aborted */
77 #define	DCBUSC		0x20000000	/* DCB Unsuccesfully Completed */
78 #define	DCBCMP		0x40000000	/* DCB Complete */
79 #define	DCBSTR		0x80000000	/* DCB Started */
80 
81 #define	DCBBITS	"\20\40DCBSTR\37DCBCMP\36DCBUSC\35DCBABT"
82 
83 /*
84  * MDCB Status Symbolic Constants
85  */
86 #define	CTLRBSY		0x10000000	/* Cntlr Busy */
87 #define	INTCCDE		0x60000000	/* Interrupt Cause Code */
88 #define	DCBINT		0x80000000	/* DCB Interrupt Flag */
89 
90 #define	MDCBBITS "\20\40DCBINT\37INTCCDE\36CTRLBSY"
91 
92 /*
93 **	Hard Error Types
94 */
95 
96 #define	HTYPES	(HCRCERR|HCMPERR|WPTERR|SZTIMEOUT|DSEEKERR|UCDATERR|NOTCYLERR| \
97 		 DRVNRDY|INVDADR|DNEMEM|PARERR|DCOMPERR)
98 
99 
100 /*
101 **	Errors
102 */
103 
104 #define	ERRS	0x3FFF
105 #define	CANRETRY	(SZTIMEOUT|DSEEKERR|NOTCYLERR|DCOMPERR|UCDATERR| \
106 			 PARERR|DNEMEM|HCRCERR|HCMPERR)
107 /*
108 **	VDDC Interrupt Modes
109 */
110 
111 #define	NOINT	0x0		/* No Interrupt */
112 #define	INTERR	0x2		/* Interrupt on Error */
113 #define	INTSUC	0x1		/* Interrupt on Success */
114 #define	INTDUN	0x3		/* Interrupt on Error or Success */
115 
116 #define	CMD_MASK 0xFF0		/* Command code mask */
117 				/* When a tabular approach can be used */
118 				/* again change this back to 0x1F0 */
119 
120 #define vdaddr ( (char *)(0xff0000+IOBASE) )
121 
122 struct	size
123 {
124 	daddr_t	nblocks;
125 	int	block0;
126 };
127 
128 
129 
130 #define	VDMF	0x8000		/* Manufacturer Fault 1=good sector */
131 #define	VDUF	0x4000		/* User Fault 1=good sector */
132 #define	VDALT	0x2000		/* Alternate Sector 1=alternate */
133 #define	VDWPT	0x1000		/* Write Protect 1=Read Only Sector */
134 
135 /*
136 **	Addr of Memory-Mapped I/O port for VDDC Control Register
137 */
138 
139 #define	VDDC_ADR (char *)(0xFF2000 + IOBASE)	/* device address register */
140 						/* this is the logical value */
141 						/* physically @ 0xFF2000 */
142 						/* location was extracted */
143 						/* from the VDDC diagnostic */
144 						/* package */
145 
146 /*
147 **	Address of Memory-Mapped I/O Port for VDDC H/W Reset
148 */
149 
150 #define	VDDC_RESET(addr)	*(addr + 4) = 0;	/* reset controller */
151 
152 /*
153 **	Start i/o to/from controller.
154 */
155 
156 #define VDDC_ATTENTION(ctrl,mdcbadr)  \
157 			{ movow(((int)mdcbadr & 0xffff0000)>>16,ctrl) ;\
158 			  movow( (int)mdcbadr & 0xffff, ctrl+2);\
159 			}
160