xref: /csrg-svn/sys/tahoe/vba/vdreg.h (revision 25857)
1 /*	vdreg.h	1.2	86/01/12	*/
2 
3 /*
4  * VDDC (Versabus Direct Disk Controller) definitions.
5  */
6 
7 /*
8  * DCB Command Codes
9  */
10 #define	RD		0x80		/* Read Data */
11 #define	FTR		0xc0		/* Full Track Read */
12 #define	RAS		0x90		/* Read and Scatter */
13 #define	C		0xa0		/* Compare */
14 #define	FTC		0xe0		/* Full Track Compare */
15 #define	RHDE		0x180		/* Read Header, Data & ECC (not used) */
16 #define	WD		0x00		/* Write Data */
17 #define	FTW		0x40		/* Full Track Write */
18 #define	WTC		0x20		/* Write Then Compare */
19 #define	FTWTC		0x60		/* Full Track Write Then Compare */
20 #define	GAW		0x10		/* Gather and Write */
21 #define	WDE		0x100		/* Write Data & ECC (not used) */
22 #define	FSECT		0x900		/* Format Sector */
23 #define	GWC		0x30		/* Gather Write & Compare */
24 #define	VDSTART		0x800		/* Start drives */
25 #define	VDRELEASE	0xa00		/* Stop drives */
26 #define	SEEK		0xb00		/* Seek */
27 #define	INIT		0xc00		/* Initialize VDDC */
28 #define	DIAG		0xd00		/* Diagnose (self-test) VDDC */
29 #define	RSTCFG		0xe00		/* Reset/Configure VDDC/DDI/Drive(s) */
30 #define	VDSTATUS	0xf00		/* VDDC Status */
31 
32 #define	ABORT		0x80000000	/* ABORT active i/o */
33 
34 /*
35  * Error/status codes.
36  */
37 #define	HCRCERR		0x1		/* Header CRC Error */
38 #define	HCMPERR		0x2		/* Header Compare Error */
39 #define	WPTERR		0x4		/* Write Protect Error/Status */
40 #define	CTLRERR		0x8		/* Controller Error */
41 #define	DSEEKERR	0x10		/* Disk Seek Error */
42 #define	UCDATERR	0x20		/* Uncorrectable Data Error */
43 #define	NOTCYLERR	0x40		/* Not on Cylinder Error */
44 #define	DRVNRDY		0x80		/* Drive Not Ready Error/Status */
45 #define	ALTACC		0x100		/* Alternate (track) accessed Status */
46 #define	SEEKSTRT	0x200		/* Seek Started Status */
47 #define	INVDADR		0x400		/* Invalid Disk Address Error */
48 #define	DNEMEM		0x800		/* Non-Existant Memory Error */
49 #define	PARERR		0x1000		/* Memory Parity Error */
50 #define	DCOMPERR	0x2000		/* Data Compare Error */
51 #define	DDIRDY		0x4000		/* DDI Ready Error/Status */
52 #define	OPABRT		0x8000		/* Operator Abort (Host) Error/Status */
53 #define	DSERLY		0x10000		/* Data Strobe Early */
54 #define	DSLATE		0x20000		/* Data Strobe Late */
55 #define	TOPLUS		0x40000		/* Track Offset Plus */
56 #define	TOMNUS		0x80000		/* Track Offset Minus */
57 #define	CPDCRT		0x100000	/* Cntlr Performed Data Correction */
58 #define	HRDERR		0x200000	/* Hard Error */
59 #define	SFTERR		0x400000	/* Soft Error (retry succesful) */
60 #define	ANYERR		0x800000	/* Any Error */
61 #define INVCMD		0x1000000	/* Programmer error */
62 
63 /* hard error */
64 #define	HTYPES \
65     (HCRCERR|HCMPERR|WPTERR|CTLRERR|DSEEKERR|UCDATERR|NOTCYLERR|DRVNRDY|\
66      INVDADR|DNEMEM|PARERR|DCOMPERR)
67 
68 #define	ERRS	0x3FFF
69 /* retryable errors */
70 #define	CANRETRY \
71     (CTLRERR|DSEEKERR|NOTCYLERR|DCOMPERR|UCDATERR|PARERR|DNEMEM|HCRCERR|HCMPERR)
72 
73 #define	ERRBITS	"\20\1HCRC\2HCMP\3WPT\4CTLR\5DSEEK\6UCDATA\7NOTCYL\10DRVNRDY\
74 \11ALTACC\12SEEKSTRT\13INVDADR\14DNEMEM\15PAR\16DCOMP\17DDIRDY\20OPABRT\
75 \21DSERLY\22DSLATE\23TOPLUS\24TOPMNUS\25CPDCRT\26HRDERR\27SFTERR\30ANYERR\
76 \31INVCMD"
77 
78 /*
79  * DCB status codes.
80  */
81 #define	DCBABT		0x10000000	/* DCB Aborted */
82 #define	DCBUSC		0x20000000	/* DCB Unsuccesfully Completed */
83 #define	DCBCMP		0x40000000	/* DCB Complete */
84 #define	DCBSTR		0x80000000	/* DCB Started */
85 
86 /*
87  * MDCB status codes.
88  */
89 #define	CTLRBSY		0x10000000	/* Cntlr Busy */
90 #define	INTCCDE		0x60000000	/* Interrupt Cause Code */
91 #define	DCBINT		0x80000000	/* DCB Interrupt Flag */
92 
93 /*
94  * VDDC interrupt modes.
95  */
96 #define	NOINT	0x0		/* No Interrupt */
97 #define	INTERR	0x2		/* Interrupt on Error */
98 #define	INTSUC	0x1		/* Interrupt on Success */
99 #define	INTDONE	0x3		/* Interrupt on Error or Success */
100 
101 
102 /*
103  * Constrol status definitions.
104  */
105 #define	CS_SCS	0xf		/* Status Change Source (drive number) */
106 #define	CS_ELC	0x10		/* Error on Last Command */
107 #define	CS_ICC	0x60		/* Interupt Cause Code */
108 #define   ICC_NOI  0x00		/* No interupt */
109 #define   ICC_DUN  0x20		/* No interupt */
110 #define   ICC_ERR  0x40		/* No interupt */
111 #define   ICC_SUC  0x60		/* No interupt */
112 #define	CS_GO	0x80		/* Go bit (controller working) */
113 #define	CS_BE	0x100		/* Buss Error */
114 #define	CS_BOK	0x4000		/* Board O.K. */
115 #define	CS_SFL	0x8000		/* System fail */
116 #define	CS_LEC	0xff000000	/* Last Error Code */
117 
118 /* Status word bit assignments */
119 #define	STA_UR	0x1		/* Unit Ready */
120 #define	STA_OC	0x2		/* On Cylinder */
121 #define	STA_SE	0x4		/* Seek Error */
122 #define	STA_DF	0x8		/* Drive Fault */
123 #define	STA_WP	0x10		/* Write Protected */
124 #define	STA_US	0x20		/* Unit Selected */
125 
126 /* Interupt Control Field bit assignments */
127 #define	ICF_IPL	0x7		/* Interupt Priority Level */
128 #define	ICF_IEN	0x8		/* Interupt ENable */
129 #define	ICF_IV	0xff00		/* Interupt Vector */
130 
131 /* Transfer Control Format bit assignments */
132 #define	TCF_AM	0xff		/* Address Modifier */
133 #define	  AM_SNPDA   0x01	/* Standard Non-Privileged Data Access */
134 #define	  AM_SASA    0x81	/* Standard Ascending Sequential Access */
135 #define	  AM_ENPDA   0xf1	/* Extended Non-Privileged Data Access */
136 #define	  AM_EASA    0xe1	/* Extended Ascending Sequential Access */
137 #define	TCF_BTE	0x800		/* Block Transfer Enable */
138 
139 /* Controller Configuration Flags bit assignments */
140 #define	CCF_STS	0x1		/* Sectors per Track Selectable */
141 #define	CCF_EAV	0x2		/* Enable Auto Vector */
142 #define	CCF_ERR	0x4		/* Enable Reset Register */
143 #define	CCF_XMD	0x60		/* XMD transfer mode (buss size) */
144 #define	  XMD_8BIT  0x20	/*   Do only 8 bit transfers */
145 #define	  XMD_16BIT 0x40	/*   Do only 16 bit transfers */
146 #define	  XMD_32BIT 0x60	/*   Do only 32 bit transfers */
147 #define	CCF_BSZ	0x300		/* Burst SiZe */
148 #define	  BSZ_16WRD 0x000	/*   16 word transfer burst */
149 #define	  BSZ_12WRD 0x100	/*   12 word transfer burst */
150 #define	  BSZ_8WRD  0x200	/*   8 word transfer burst */
151 #define	  BSZ_4WRD  0x300	/*   4 word transfer burst */
152 #define	CCF_ENP	0x1000		/* ENable Parity */
153 #define	CCF_EPE	0x2000		/* Enable Parity Errors */
154 #define	CCF_EDE	0x10000		/* Error Detection Enable */
155 #define	CCF_ECE	0x20000		/* Error Correction Enable */
156 
157 /*
158  * Diagnostic register definitions.
159  */
160 #define	DIA_DC	0x7f		/* Dump count mask */
161 #define	DIA_DWR	0x80		/* Dump Write / Read flag */
162 #define	DIA_ARE	0x100		/* Auto Rebuild Enable */
163 #define	DIA_CEN	0x200		/* Call ENable flag */
164 #define	DIA_KEY	0xAA550000	/* Reset KEY */
165 
166 /* Sector Header bit assignments */
167 #define	VDMF	0x8000		/* Manufacturer Fault 1=good sector */
168 #define	VDUF	0x4000		/* User Fault 1=good sector */
169 #define	VDALT	0x2000		/* Alternate Sector 1=alternate */
170 #define	VDWPT	0x1000		/* Write Protect 1=Read Only Sector */
171 
172 /* DCB Bit assignments */
173 #define	INT_IC	0x3		/* Interupt Control */
174 #define	  IC_NOI  0x0		/*   NO Interupt */
175 #define	  IC_IOD  0x1		/*   Interupt On Done */
176 #define	  IC_IOE  0x2		/*   Interupt On Error */
177 #define	  IC_IOS  0x3		/*   Interupt On Success */
178 #define	INT_PBA	0x4		/* Proceed before ACK */
179 
180 /*
181  * Perform a reset on the controller.
182  */
183 #define	VDDC_RESET(addr, type) { \
184 	if (type == SMD_ECTLR) { \
185 		(addr)->diag_flags = DIA_KEY|DIA_CEN; \
186 		(addr)->cdr_mdcb_ptr = (fmt_mdcb *)0xffffffff; \
187 		DELAY(5000000); \
188 	} else { \
189 		(addr)->cdr_reset = 0x0; \
190 		DELAY(1500000); \
191 	} \
192 }
193 
194 /*
195  * Abort a controller operation.
196  */
197 #define	VDDC_ABORT(a, type) { \
198 	if ((type) == SMDCTLR) { \
199 		movow(a, (ABORT & 0xffff0000) >> 16) ; \
200 		movow((int)(a)+2, ABORT & 0xffff); \
201 	} else \
202 		(a)->cdr_mdcb_ptr = (fmt_mdcb *)ABORT; \
203 	DELAY(1000000); \
204 }
205 
206 /*
207  * Start i/o on controller.
208  */
209 #define VDDC_ATTENTION(ctlr, mdcbadr, type) {\
210 	if (type == SMDCTLR) { \
211 		movow(ctlr, ((int)mdcbadr & 0xffff0000) >> 16) ; \
212 		movow((int)(ctlr)+2, (int)mdcbadr & 0xffff); \
213 	} else \
214 		(ctlr)->cdr_mdcb_ptr = mdcbadr; \
215 }
216 
217 /*
218  * Poll controller until operation completes
219  * or timeout expires.
220  * YECH!!!! THIS SHOULD BE A SUBROUTINE!!!
221  */
222 #define	POLLTILLDONE(c, a, x, t) { \
223 	vdtimeout = 1000 * (x); \
224 	uncache(&(a)->operrsta); \
225 	while ((((a)->operrsta) & (DCBCMP|DCBABT)) == 0) { \
226 		DELAY(1000); \
227 		vdtimeout--; \
228 		uncache(&(a)->operrsta); \
229 		if (vdtimeout <= 0) { \
230 			printf("vd%d: controller timeout", c); \
231 			VDDC_ABORT(c, t); \
232 			DELAY(30000); \
233 			break; \
234 		} \
235 	} \
236 	if (vdtimeout > 0) \
237 		if ((t) == SMD_ECTLR && vdtimeout > 0) { \
238 			uncache(&(c)->cdr_csr); \
239 			while((c)->cdr_csr&CS_GO) { \
240 				DELAY(50); \
241 				uncache(&(c)->cdr_csr); \
242 			} \
243 			DELAY(500); \
244 		} else \
245 			DELAY(200); \
246 	uncache(&(a)->operrsta); \
247 }
248 
249 /*
250  * A disk address.
251  */
252 typedef struct {
253 	char	track;			/* all 8 bits */
254 	char	sector;			/* all 8  bits */
255 	short	cylinder;		/* low order 12 bits */
256 } dskadr;
257 
258 /*
259  * Sector formats.
260  */
261 typedef union {
262 	struct {
263 		dskadr	hdr_addr;
264 		short	smd_crc;
265 	} smd;
266 	struct {
267 		dskadr	physical;
268 		dskadr	logical;
269 		long	smd_e_crc;
270 	} smd_e;
271 } fmt_hdr;
272 
273 /*
274  * DCB trailer formats.
275  */
276 /* read/write trailer */
277 typedef struct {
278 	char	*memadr;	/* memory address */
279 	u_long	wcount;		/* 16 bit word count */
280 	dskadr	disk;		/* disk address */
281 } trrw;
282 
283 /* scatter/gather trailer */
284 typedef struct {
285 	trrw	start_addr;
286 	struct {
287 		char	*nxt_addr;
288 		u_long	nxt_len;
289 	} addr_chain[126];
290 } trsg;
291 
292 /* seek trailer format */
293 typedef struct {
294 	dskadr	skaddr;
295 } trseek;
296 
297 /* format trailer */
298 typedef struct {
299 	char	*addr;		/* data buffer to be filled on sector*/
300 	long	nsectors;	/* # of sectors to be formatted */
301 	dskadr	disk;		/* disk physical address info */
302 	dskadr  hdr;		/* header address info */
303 } trfmt;
304 
305 /* reset/configure trailer */
306 typedef struct {
307 	long	ncyl;		/* # cylinders */
308 	long	nsurfaces;	/* # surfaces */
309 	long	nsectors;	/* # sectors */
310 	long	slip_sec;	/* # of slip sectors */
311 } treset;
312 
313 /*
314  * DCB layout.
315  */
316 typedef struct fmtdcb {
317 	struct	fmtdcb *nxtdcb;	/* next dcb */
318 	short	intflg;		/* interrupt settings and flags */
319 	short	opcode;		/* DCB command code etc... */
320 	long	operrsta;	/* error & status info */
321 	short	fill;		/* not used */
322 	char	devselect;	/* drive selection */
323 	char	trailcnt;	/* trailer Word Count */
324 	long	err_memadr;	/* error memory address */
325 	char	err_code;	/* error codes for SMD/E */
326 	char	fill2;		/* not used */
327 	short	err_wcount;	/* error word count */
328 	char	err_trk;	/* error track/sector */
329 	char	err_sec;	/* error track/sector */
330 	short	err_cyl;	/* error cylinder adr */
331 	union {
332 		trseek	sktrail;	/* seek command trailer */
333 #ifdef notdef
334 		trsg	sgtrail;	/* scatter/gather trailer */
335 #endif
336 		trrw	rwtrail;	/* read/write trailer */
337 		trfmt	fmtrail;	/* format trailer */
338 		treset	rstrail;	/* reset/configure trailer */
339 	} trail;
340 } fmt_dcb;
341 
342 /*
343  * MDCB layout.
344  */
345 typedef struct {
346 	fmt_dcb	*firstdcb;	/* first dcb in chain */
347 	fmt_dcb	*procdcb;	/* dcb being processed */
348 	fmt_dcb	*intdcb;	/* dcb causing interrupt */
349 	long	vddcstat;	/* VDDC status */
350 } fmt_mdcb;
351 
352 /*
353  * Control-status communications block.
354  */
355 typedef struct {
356 	fmt_mdcb *cdr_mdcb_ptr;	/* controller's mdcb */
357 	u_long	cdr_reset;	/* controller reset register */
358 	u_long	cdr_csr;	/* control/status register */
359 	long	cdr_reserved;	/* reserved */
360 	u_short	cdr_status[16];	/* per-drive status register */
361 	u_short	stat_chng;	/* status change interupt register */
362 	u_short	done_icf;	/* interupt-complete register */
363 	u_short	error_icf;	/* error-interupt register */
364 	u_short	success_icf;	/* success-interupt register */
365 	u_short	mdcb_tcf;	/* mdcb transfer control register */
366 	u_short	dcb_tcf;	/* dcb transfer control register */
367 	u_short	trail_tcf;	/* trail transfer control register */
368 	u_short	data_tcf;	/* data transfer control register */
369 	u_long	cdr_ccf;	/* controller configuration flags */
370 	u_long	sec_size;	/* drive sector size */
371 	u_long	diag_flags;	/* diagnostic flag register */
372 	u_long	diag_dump;	/* pointer for diagnostic addresses */
373 } cdr;
374 
375 /* controller types */
376 #define	UNKNOWN		-1
377 #define	SMDCTLR		1	/* smd interface */
378 #define	SMD_ECTLR	2	/* extended-smd interface */
379 
380 /* drive types */
381 #define	XSD	0
382 #define	FUJ	1 		/* fujitsu */
383 #define	XFD	2		/* CDC 340Mb Winchester */
384 #define	SMD	3		/* CDC 9766 or equivalent */
385 #define	FSD	4
386 
387 /*
388  * Drive logical partitions.
389  */
390 typedef struct {
391 	long	par_start;	/* starting sector # */
392 	long	par_len;	/* size in sectors */
393 } par_tab;
394 
395 typedef struct {
396 	int	secsize;		/* bytes/sector */
397 	int	nsec;			/* sectors/track */
398 	int	ntrak;			/* tracks/cylinder */
399 	int	ncyl;			/* # cylinders */
400 	int	nslip;			/* # slip sectors */
401 	int	rpm;			/* revolutions/minute */
402 	int	nbits;			/* bits/track */
403 	char	*type_name;		/* drive name */
404 	long	fmt_pat[16];		/* patterns to be used for formatting */
405 	par_tab	partition[8];		/* partition tables */
406 } fs_tab;
407 
408 /* physical information for known disk drives.  */
409 #ifdef VDGENDATA
410 long	vddcaddr[] = { 0xf2000, 0xf2100, 0xf2200, 0xf2300, 0 };
411 long	vdtimeout = 0;
412 
413 fs_tab	vdst[] = {
414 	{512, 48, 24, 711, 0, 3600, 0,	"xsd",	/* 515 Mb FSD */
415 		{ 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98,
416 		  0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980,
417 		  0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800,
418 		  0x4c993000, 0x99326000, 0x3264c000, 0x54c98000},
419 		{{0,	 30528},	/* xsd0a cyl   0 - 52 */
420 		{30528,	 30528},	/* xsd0b cyl  53 - 105 */
421 		{61056,	 345600}, 	/* xsd0c cyl 106 - 705 */
422 		{0,	 61056}, 	/* xsd0d cyl 709 - 710 (a & b) */
423 		{0,	 406656},	/* xsd0e cyl   0 - 705 */
424 		{30528,	 376128}, 	/* xsd0f cyl  53 - 705 (b & c) */
425 		{61056,	 172800},	/* xsd0g cyl 106 - 405 (1/2 of c) */
426 		{233856, 172800}}	/* xsd0h cyl 406 - 705 (1/2 of c) */
427 	},
428 	{512, 64, 10, 823, 0, 3600, 0,	"fuj",	/* 360 Mb Fujitsu */
429 		{ 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98,
430 		  0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980,
431 		  0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800,
432 		  0x4c993000, 0x99326000, 0x3264c000, 0x54c98000},
433 		{{0,	 19200},	/* fuj0a cyl   0 - 59 */
434 		{19200,	 24000},	/* fuj0b cyl  60 - 134 */
435 		{43200,	 218560}, 	/* fuj0c cyl 135 - 817 */
436 		{0,	 43200}, 	/* fuj0d cyl 821 - 822 (a & b) */
437 		{0,	 261760},	/* fuj0e cyl   0 - 817 */
438 		{19200,	 242560}, 	/* fuj0f cyl   0 - 134 (b & c) */
439 		{43200,  109440},	/* fuj0g cyl 135 - 476 (1/2 of c) */
440 		{152640, 109120}}	/* fug0h cyl 477 - 817 (1/2 of c) */
441 	},
442 	{512, 32, 24, 711, 0, 3600, 0,	"xfd",	/* 340 Mb FSD */
443 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
444 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
445 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
446 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
447 #ifdef MICKEY
448 		{{ 0,	 20352 },	/* xfd0a cyl   0-52 */
449 		{ 20352, 20352 },	/* xfd0b cyl  53-105 */
450 		{ 40704, 230400 },	/* xfd0c cyl 106-705 */
451 		{ 271104,1920 },	/* xfd0d cyl 706-710 */
452 		{ 0,	 271104 },	/* xfd0e cyl   0-705 */
453 		{ 0,	 273024 }},	/* xfd0f cyl   0-710 */
454 #else
455 		{{ 0,	 20352 },	/* xfd0a cyl   0 - 52 */
456 		{ 20352, 20352 },	/* xfd0b cyl  53 - 105 */
457 		{ 40704, 230400 },	/* xfd0c cyl 106 - 705 */
458 		{ 0,	 40704 },	/* xfd0d cyl 709 - 710 (a & b) */
459 		{ 0,	 271104 },	/* xfd0e cyl   0 - 705 */
460 		{ 20352, 250752 },	/* xfd0f cyl  53 - 705 (b & c) */
461 		{ 40704, 115200 },	/* xfd0g cyl 106 - 405 (1/2 of c) */
462 		{ 155904,115200 }}	/* xfd0h cyl 406 - 705 (1/2 of c) */
463 #endif
464 	},
465 	{512, 32, 19, 823, 0, 3600, 0,	"smd",	/* 300 Mb SMD */
466 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
467 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
468 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
469 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
470 		{{ 0,	 20064},	/* smd0a cyl   0-65 */
471 		{ 20064, 13680},	/* smd0b cyl  66-110 */
472 		{ 33744, 214928},	/* smd0c cyl 111-817 */
473 		{ 248672,1520 },	/* smd0d cyl 818-822 */
474 		{ 0,	 248672 },	/* smd0e cyl   0-817 */
475 		{ 0,	 250192 }},	/* smd0f cyl   0-822 */
476 	},
477 	{512, 32, 10, 823, 0, 3600, 0,	"fsd",	/* 160 Mb FSD */
478 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
479 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
480 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
481 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
482 		{{0,	 9600},		/* fsd0a cyl   0 -  59 */
483 		{9600,	 12000},	/* fsd0b cyl  60 - 134 */
484 		{21600,	 109280},	/* fsd0c cyl 135 - 817 */
485 		{0,	 21600},	/* fsd0d cyl   0 - 134 (a & b) */
486 		{0,	 130880},	/* fsd0e cyl   0 - 817 */
487 		{9600,	 121280},	/* fsd0f cyl  60 - 817 (b & c) */
488 		{21600,  54240},	/* fsd0g cyl 135 - 473 (1/2 of c) */
489 		{75840,  55040}}	/* fsd0h cyl 474 - 817 (1/2 of c) */
490 	}
491 };
492 
493 int	nvddrv = (sizeof (vdst) / sizeof (fs_tab));
494 
495 #else
496 #ifdef STANDALONE
497 extern long	vddcaddr[];
498 extern long	vdtimeout;
499 extern fs_tab	vdst[];
500 extern int	nvddrv;
501 #endif
502 #endif
503