xref: /csrg-svn/sys/tahoe/vba/vdreg.h (revision 30372)
1 /*	vdreg.h	1.7	87/01/11	*/
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	RD_RAW		0x600		/* Read unformatted disk sector */
14 #define	CMP		0xa0		/* Compare */
15 #define	FTC		0xe0		/* Full Track Compare */
16 #define	RHDE		0x180		/* Read Header, Data & ECC (not used) */
17 #define	WD		0x00		/* Write Data */
18 #define	FTW		0x40		/* Full Track Write */
19 #define	WTC		0x20		/* Write Then Compare */
20 #define	FTWTC		0x60		/* Full Track Write Then Compare */
21 #define	GAW		0x10		/* Gather and Write */
22 #define	WDE		0x100		/* Write Data & ECC (not used) */
23 #define	FSECT		0x900		/* Format Sector */
24 #define	GWC		0x30		/* Gather Write & Compare */
25 #define	VDSTART		0x800		/* Start drives */
26 #define	VDRELEASE	0xa00		/* Stop drives */
27 #define	SEEK		0xb00		/* Seek */
28 #define	INIT		0xc00		/* Initialize VDDC */
29 #define	DIAG		0xd00		/* Diagnose (self-test) VDDC */
30 #define	RSTCFG		0xe00		/* Reset/Configure VDDC/DDI/Drive(s) */
31 #define	VDSTATUS	0xf00		/* VDDC Status */
32 
33 #define	ABORT		0x80000000	/* ABORT active i/o */
34 
35 /*
36  * Error/status codes.
37  */
38 #define	HCRCERR		0x1		/* Header CRC Error */
39 #define	HCMPERR		0x2		/* Header Compare Error */
40 #define	WPTERR		0x4		/* Write Protect Error/Status */
41 #define	CTLRERR		0x8		/* Controller Error */
42 #define	DSEEKERR	0x10		/* Disk Seek Error */
43 #define	UCDATERR	0x20		/* Uncorrectable Data Error */
44 #define	NOTCYLERR	0x40		/* Not on Cylinder Error */
45 #define	DRVNRDY		0x80		/* Drive Not Ready Error/Status */
46 #define	ALTACC		0x100		/* Alternate (track) accessed Status */
47 #define	SEEKSTRT	0x200		/* Seek Started Status */
48 #define	INVDADR		0x400		/* Invalid Disk Address Error */
49 #define	DNEMEM		0x800		/* Non-Existant Memory Error */
50 #define	PARERR		0x1000		/* Memory Parity Error */
51 #define	DCOMPERR	0x2000		/* Data Compare Error */
52 #define	DDIRDY		0x4000		/* DDI Ready Error/Status */
53 #define	OPABRT		0x8000		/* Operator Abort (Host) Error/Status */
54 #define	DSERLY		0x10000		/* Data Strobe Early */
55 #define	DSLATE		0x20000		/* Data Strobe Late */
56 #define	TOPLUS		0x40000		/* Track Offset Plus */
57 #define	TOMNUS		0x80000		/* Track Offset Minus */
58 #define	CPDCRT		0x100000	/* Cntlr Performed Data Correction */
59 #define	HRDERR		0x200000	/* Hard Error */
60 #define	SFTERR		0x400000	/* Soft Error (retry succesful) */
61 #define	ANYERR		0x800000	/* Any Error */
62 #define INVCMD		0x1000000	/* Programmer error */
63 /*
64  * DCB status codes.
65  */
66 #define	DCBABT		0x10000000	/* DCB Aborted */
67 #define	DCBUSC		0x20000000	/* DCB Unsuccesfully Completed */
68 #define	DCBCMP		0x40000000	/* DCB Complete */
69 #define	DCBSTR		0x80000000	/* DCB Started */
70 
71 /* hard error */
72 #define	HTYPES \
73     (HCRCERR|HCMPERR|WPTERR|CTLRERR|DSEEKERR|UCDATERR|NOTCYLERR|DRVNRDY|\
74      INVDADR|DNEMEM|PARERR|DCOMPERR)
75 
76 #define	ERRS	0x3FFF
77 /* retryable errors */
78 #define	CANRETRY \
79     (CTLRERR|DSEEKERR|NOTCYLERR|DCOMPERR|UCDATERR|PARERR|DNEMEM|HCRCERR|HCMPERR)
80 
81 #define	ERRBITS	"\20\1HCRC\2HCMP\3WPT\4CTLR\5DSEEK\6UCDATA\7NOTCYL\10DRVNRDY\
82 \11ALTACC\12SEEKSTRT\13INVDADR\14DNEMEM\15PAR\16DCOMP\17DDIRDY\20OPABRT\
83 \21DSERLY\22DSLATE\23TOPLUS\24TOPMNUS\25CPDCRT\26HRDERR\27SFTERR\30ANYERR\
84 \31INVCMD\35ABORTED\36FAIL\37COMPLETE\40STARTED"
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_DER 0x8		/* Disable Error Recovery */
144 #define	CCF_XMD	0x60		/* XMD transfer mode (buss size) */
145 #define	  XMD_8BIT  0x20	/*   Do only 8 bit transfers */
146 #define	  XMD_16BIT 0x40	/*   Do only 16 bit transfers */
147 #define	  XMD_32BIT 0x60	/*   Do only 32 bit transfers */
148 #define	CCF_BSZ	0x300		/* Burst SiZe */
149 #define	  BSZ_16WRD 0x000	/*   16 word transfer burst */
150 #define	  BSZ_12WRD 0x100	/*   12 word transfer burst */
151 #define	  BSZ_8WRD  0x200	/*   8 word transfer burst */
152 #define	  BSZ_4WRD  0x300	/*   4 word transfer burst */
153 #define CCF_SEN	0x400		/* Cylinder / track Skew ENable (for format) */
154 #define	CCF_ENP	0x1000		/* ENable Parity */
155 #define	CCF_EPE	0x2000		/* Enable Parity Errors */
156 #define	CCF_EDE	0x10000		/* Error Detection Enable */
157 #define	CCF_ECE	0x20000		/* Error Correction Enable */
158 
159 /*
160  * Diagnostic register definitions.
161  */
162 #define	DIA_DC	0x7f		/* Dump count mask */
163 #define	DIA_DWR	0x80		/* Dump Write / Read flag */
164 #define	DIA_ARE	0x100		/* Auto Rebuild Enable */
165 #define	DIA_CEN	0x200		/* Call ENable flag */
166 #define	DIA_KEY	0xAA550000	/* Reset KEY */
167 
168 /* Sector Header bit assignments */
169 #define	VDMF	0x8000		/* Manufacturer Fault 1=good sector */
170 #define	VDUF	0x4000		/* User Fault 1=good sector */
171 #define	VDALT	0x2000		/* Alternate Sector 1=alternate */
172 #define	VDWPT	0x1000		/* Write Protect 1=Read Only Sector */
173 
174 /* DCB Bit assignments */
175 #define	INT_IC	0x3		/* Interupt Control */
176 #define	  IC_NOI  0x0		/*   NO Interupt */
177 #define	  IC_IOD  0x1		/*   Interupt On Done */
178 #define	  IC_IOE  0x2		/*   Interupt On Error */
179 #define	  IC_IOS  0x3		/*   Interupt On Success */
180 #define	INT_PBA	0x4		/* Proceed before ACK */
181 
182 /*
183  * Perform a reset on the controller.
184  */
185 #define	VDDC_RESET(addr, type) { \
186 	if (type == SMD_ECTLR) { \
187 		(addr)->diag_flags = DIA_KEY|DIA_CEN; \
188 		(addr)->cdr_mdcb_ptr = (fmt_mdcb *)0xffffffff; \
189 		DELAY(5000000); \
190 	} else { \
191 		(addr)->cdr_reset = 0x0; \
192 		DELAY(1500000); \
193 	} \
194 }
195 
196 /*
197  * Abort a controller operation.
198  */
199 #define	VDDC_ABORT(a, type) { \
200 	if ((type) == SMDCTLR) { \
201 		movow(a, (ABORT & 0xffff0000) >> 16) ; \
202 		movow((int)(a)+2, ABORT & 0xffff); \
203 	} else \
204 		(a)->cdr_mdcb_ptr = (fmt_mdcb *)ABORT; \
205 	DELAY(1000000); \
206 }
207 
208 /*
209  * Start i/o on controller.
210  */
211 #define VDDC_ATTENTION(ctlr, mdcbadr, type) {\
212 	if (type == SMDCTLR) { \
213 		movow(ctlr, ((int)mdcbadr & 0xffff0000) >> 16) ; \
214 		movow((int)(ctlr)+2, (int)mdcbadr & 0xffff); \
215 	} else \
216 		(ctlr)->cdr_mdcb_ptr = mdcbadr; \
217 }
218 
219 /*
220  * A disk address.
221  */
222 typedef struct {
223 	char	track;			/* all 8 bits */
224 	char	sector;			/* all 8  bits */
225 	short	cylinder;		/* low order 12 bits */
226 } dskadr;
227 
228 /*
229  * Sector formats.
230  */
231 typedef union {
232 	struct {
233 		dskadr	hdr_addr;
234 		short	smd_crc;
235 	} smd;
236 	struct {
237 		dskadr	physical;
238 		dskadr	logical;
239 		long	smd_e_crc;
240 	} smd_e;
241 } fmt_hdr;
242 
243 /*
244  * DCB trailer formats.
245  */
246 /* read/write trailer */
247 typedef struct {
248 	char	*memadr;	/* memory address */
249 	u_long	wcount;		/* 16 bit word count */
250 	dskadr	disk;		/* disk address */
251 } trrw;
252 
253 /* scatter/gather trailer */
254 typedef struct {
255 	trrw	start_addr;
256 	struct {
257 		char	*nxt_addr;
258 		u_long	nxt_len;
259 	} addr_chain[126];
260 } trsg;
261 
262 /* seek trailer format */
263 typedef struct {
264 	dskadr	skaddr;
265 } trseek;
266 
267 /* format trailer */
268 typedef struct {
269 	char	*addr;		/* data buffer to be filled on sector*/
270 	long	nsectors;	/* # of sectors to be formatted */
271 	dskadr	disk;		/* disk physical address info */
272 	dskadr  hdr;		/* header address info */
273 } trfmt;
274 
275 /* reset/configure trailer */
276 typedef struct {
277 	long	ncyl;		/* # cylinders */
278 	long	nsurfaces;	/* # surfaces */
279 	long	nsectors;	/* # sectors */
280 	long	slip_sec;	/* # of slip sectors */
281 	long	recovery;	/* recovery flags */
282 } treset;
283 
284 /*
285  * DCB layout.
286  */
287 typedef struct fmtdcb {
288 	struct	fmtdcb *nxtdcb;	/* next dcb */
289 	short	intflg;		/* interrupt settings and flags */
290 	short	opcode;		/* DCB command code etc... */
291 	long	operrsta;	/* error & status info */
292 	short	fill;		/* not used */
293 	char	devselect;	/* drive selection */
294 	char	trailcnt;	/* trailer Word Count */
295 	long	err_memadr;	/* error memory address */
296 	char	err_code;	/* error codes for SMD/E */
297 	char	fill2;		/* not used */
298 	short	err_wcount;	/* error word count */
299 	char	err_trk;	/* error track/sector */
300 	char	err_sec;	/* error track/sector */
301 	short	err_cyl;	/* error cylinder adr */
302 	union {
303 		trseek	sktrail;	/* seek command trailer */
304 #ifdef notdef
305 		trsg	sgtrail;	/* scatter/gather trailer */
306 #endif
307 		trrw	rwtrail;	/* read/write trailer */
308 		trfmt	fmtrail;	/* format trailer */
309 		treset	rstrail;	/* reset/configure trailer */
310 	} trail;
311 } fmt_dcb;
312 
313 /*
314  * MDCB layout.
315  */
316 typedef struct {
317 	fmt_dcb	*firstdcb;	/* first dcb in chain */
318 	fmt_dcb	*procdcb;	/* dcb being processed */
319 	fmt_dcb	*intdcb;	/* dcb causing interrupt */
320 	long	vddcstat;	/* VDDC status */
321 } fmt_mdcb;
322 
323 /*
324  * Control-status communications block.
325  */
326 typedef struct {
327 	fmt_mdcb *cdr_mdcb_ptr;	/* controller's mdcb */
328 	u_long	cdr_reset;	/* controller reset register */
329 	u_long	cdr_csr;	/* control/status register */
330 	long	cdr_reserved;	/* reserved */
331 	u_short	cdr_status[16];	/* per-drive status register */
332 	u_short	stat_chng;	/* status change interupt register */
333 	u_short	done_icf;	/* interupt-complete register */
334 	u_short	error_icf;	/* error-interupt register */
335 	u_short	success_icf;	/* success-interupt register */
336 	u_short	mdcb_tcf;	/* mdcb transfer control register */
337 	u_short	dcb_tcf;	/* dcb transfer control register */
338 	u_short	trail_tcf;	/* trail transfer control register */
339 	u_short	data_tcf;	/* data transfer control register */
340 	u_long	cdr_ccf;	/* controller configuration flags */
341 	u_long	sec_size;	/* drive sector size */
342 	u_short	cdr_unused0;
343 	u_char	cyl_skew;	/* cylinder to cylinder skew factor */
344 	u_char	trk_skew;	/* track to track skew factor */
345 	u_long	cdr_unused1;
346 	u_long	diag_flags;	/* diagnostic flag register */
347 	u_long	diag_dump;	/* pointer for diagnostic addresses */
348 } cdr;
349 
350 /* controller types */
351 #define	UNKNOWN		-1
352 #define	SMDCTLR		1	/* smd interface */
353 #define	SMD_ECTLR	2	/* extended-smd interface */
354 
355 /* drive types */
356 #define	XSD	0
357 #define	FUJ	1 		/* Fujitsu 160 */
358 #define	XFD	2		/* CDC 340Mb Winchester */
359 #define	SMD	3		/* CDC 9766 or equivalent */
360 #define	FSD	4
361 #define	EGL	5		/* Fujitsu Eagle */
362 
363 /*
364  * Drive logical partitions.
365  */
366 typedef struct {
367 	long	par_start;	/* starting sector # */
368 	long	par_len;	/* size in sectors */
369 } par_tab;
370 
371 typedef struct {
372 	int	secsize;		/* bytes/sector */
373 	int	nsec;			/* sectors/track */
374 	int	ntrak;			/* tracks/cylinder */
375 	int	ncyl;			/* # cylinders */
376 	int	nslip;			/* # slip sectors */
377 	int	rpm;			/* revolutions/minute */
378 	int	nbits;			/* bits/track */
379 	char	*type_name;		/* drive name */
380 	char	*type_descrip;		/* drive description */
381 	long	fmt_pat[16];		/* patterns to be used for formatting */
382 	par_tab	partition[8];		/* partition tables */
383 } fs_tab;
384 
385 /* physical information for known disk drives.  */
386 #ifdef VDGENDATA
387 long	vddcaddr[] =
388   { 0xffff2000, 0xffff2100, 0xffff2200, 0xffff2300, 0xffff2400, 0xffff2500,
389     0xffff2600, 0xffff2700, 0 };
390 
391 fs_tab	vdst[] = {
392 	{512, 48, 24, 711, 0, 3600, 30240,	"CDC xsd",
393 	    "515 Mb Control Data Winchester drive",
394 		{ 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98,
395 		  0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980,
396 		  0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800,
397 		  0x4c993000, 0x99326000, 0x3264c000, 0x54c98000},
398 		{{0,	 30528},	/* a cyl   0 - 52 */
399 		{30528,	 30528},	/* b cyl  53 - 105 */
400 		{61056,	 345600}, 	/* c cyl 106 - 705 */
401 		{118656, 288000}, 	/* d cyl 206 - 705 */
402 		{176256, 230400},	/* e cyl 306 - 705 */
403 		{233856, 172800}, 	/* f cyl 406 - 705 */
404 		{291456, 115200},	/* g cyl 506 - 705 */
405 		{349056, 57600}}	/* h cyl 606 - 705 */
406 	},
407 	{512, 44, 20, 842, 0, 3961, 27720,	  "eagle",
408 	     "474 Mb Fujitsu Eagle drive",
409 		{ 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98,
410 		  0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980,
411 		  0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800,
412 		  0x4c993000, 0x99326000, 0x3264c000, 0x54c98000},
413 		{{0,	 26400},	/* egl0a cyl   0 - 59 */
414 		{26400,	 33000},	/* egl0b cyl  60 - 134 */
415 		{59400,	 308880}, 	/* egl0c cyl 135 - 836 */
416 		{368280, 2640}, 	/* egl0d cyl 837 - 842 */
417 		{0, 368280},		/* egl0e cyl 0 - 836 */
418 		{0, 370920}, 		/* egl0f cyl 0 - 842 */
419 		{59400, 155320},	/* egl0g cyl 135 - 487 */
420 		{214720, 153560}}	/* egl0h cyl 488 - 836 */
421 	},
422 	{512, 64, 10, 823, 0, 3600, 40960, "fuji 360",	/* 360 Mb Fujitsu */
423 	    "360 Mb Fujitsu Winchester drive",
424 		{ 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98,
425 		  0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980,
426 		  0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800,
427 		  0x4c993000, 0x99326000, 0x3264c000, 0x54c98000},
428 		{{0,	 19200},	/* fuj0a cyl   0 - 59 */
429 		{19200,	 24000},	/* fuj0b cyl  60 - 134 */
430 		{43200,	 218560}, 	/* fuj0c cyl 135 - 817 */
431 		{79680,	 182080}, 	/* fuj0d cyl 249 - 817 */
432 		{116160, 145600},	/* fuj0e cyl 363 - 817 */
433 		{152640, 109120}, 	/* fuj0f cyl 477 - 817 */
434 		{189120, 72640},	/* fuj0g cyl 591 - 817 */
435 		{225600, 36160}}	/* fug0h cyl 705 - 817 */
436 	},
437 	{512, 32, 24, 711, 0, 3600, 20160, "CDC xfd",	/* 340 Mb FSD */
438 	    "340 Mb Control Data Winchester drive",
439 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
440 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
441 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
442 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
443 #ifdef cci1.21
444 		{{ 0,	 20352 },	/* a cyl   0 - 52 */
445 		{ 20352, 20352 },	/* b cyl  53 - 105 */
446 		{ 40704, 230400 },	/* c cyl 106 - 705 */
447 		{79104,	 192000},	/* d cyl 206 - 705 */
448 		{117504, 153600},	/* e cyl 306 - 705 */
449 		{155904, 115200},	/* f cyl 406 - 705 */
450 		{194304, 76800},	/* g cyl 506 - 705 */
451 		{232704, 38400}}	/* h cyl 606 - 705 */
452 #else
453 		{{ 0,	 20352 },	/* a cyl   0 - 52 */
454 		{ 20352, 20352 },	/* b cyl  53 - 105 */
455 		{ 40704, 230400 },	/* c cyl 106 - 705 */
456 		{ 0,	 40704 },	/* d cyl 709 - 710 (a & b) */
457 		{ 0,	 271104 },	/* e cyl   0 - 705 */
458 		{ 20352, 250752 },	/* f cyl  53 - 705 (b & c) */
459 		{ 40704, 115200 },	/* g cyl 106 - 405 (1/2 of c) */
460 		{ 155904,115200 }}	/* h cyl 406 - 705 (1/2 of c) */
461 #endif
462 	},
463 	{512, 32, 19, 823, 0, 3600, 20160,	"9766",	/* 300 Mb SMD */
464 	    "300 Mb Control Data 9766 removable media drive",
465 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
466 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
467 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
468 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
469 		{{0,	 20064},	/* a cyl   0-65 */
470 		{20064, 13680},		/* b cyl  66-110 */
471 		{33744, 214928},	/* c cyl 111-817 */
472 		{69616,	 179056},	/* d cyl 229 - 817 */
473 		{105488, 143184},	/* e cyl 347 - 817 */
474 		{141360, 107312},	/* f cyl 465 - 817 */
475 		{177232, 71440},	/* g cyl 583 - 817 */
476 		{213104, 35568}}	/* h cyl 701 - 817 */
477 	},
478 	{512, 32, 10, 823, 0, 3600, 20160, "fsd",	/* 160 Mb FSD */
479 	    "160 Mb Winchester drive",
480 		{ 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360,
481 		  0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600,
482 		  0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000,
483 		  0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000},
484 		{{0,	 9600},		/* a cyl   0 -  59 */
485 		{9600,	 12000},	/* b cyl  60 - 134 */
486 		{21600,	 109280},	/* c cyl 135 - 817 */
487 		{39840,	 91040},	/* d cyl 249 - 817 */
488 		{58080,	 72800},	/* e cyl 363 - 817 */
489 		{76320,	 54560},	/* f cyl 477 - 817 */
490 		{94560,  36320},	/* g cyl 591 - 817 */
491 		{112800, 18080}}	/* h cyl 705 - 817 */
492 	}
493 };
494 
495 int	nvddrv = (sizeof (vdst) / sizeof (fs_tab));
496 
497 #else
498 #ifdef STANDALONE
499 extern long	vddcaddr[];
500 extern fs_tab	vdst[];
501 extern int	nvddrv;
502 #endif
503 #endif
504