bring up to revision 7 for tahoe release
[unix-history] / usr / src / sys / tahoe / vba / vdreg.h
CommitLineData
430f81c3
MK
1/*
2 * Copyright (c) 1988 Regents of the University of California.
3 * All rights reserved.
4 *
5 * Redistribution and use in source and binary forms are permitted
6 * provided that this notice is preserved and that due credit is given
7 * to the University of California at Berkeley. The name of the University
8 * may not be used to endorse or promote products derived from this
9 * software without specific prior written permission. This software
10 * is provided ``as is'' without express or implied warranty.
11 *
12 * @(#)vdreg.h 7.1 (Berkeley) %G%
13 */
ee18b8e6
SL
14
15/*
7bae1a62 16 * Versabus VDDC/SMDE disk controller definitions.
ee18b8e6 17 */
b39ce066
MK
18#define VDDC_SECSIZE 512 /* sector size for VDDC */
19#define VD_MAXSECSIZE 1024 /* max sector size for SMD/E */
ee18b8e6
SL
20
21/*
7bae1a62 22 * Controller communications block.
ee18b8e6 23 */
7bae1a62
SL
24struct vddevice {
25 u_long vdcdr; /* controller device register */
26 u_long vdreset; /* controller reset register */
27 u_long vdcsr; /* control-status register */
28 long vdrstclr; /* reset clear register */
29 u_short vdstatus[16]; /* per-drive status register */
30 u_short vdicf_status; /* status change interupt control format */
31 u_short vdicf_done; /* interrupt complete control format */
32 u_short vdicf_error; /* interrupt error control format */
33 u_short vdicf_success; /* interrupt success control format */
34 u_short vdtcf_mdcb; /* mdcb transfer control format */
35 u_short vdtcf_dcb; /* dcb transfer control format */
36 u_short vdtcf_trail; /* trail transfer control format */
37 u_short vdtcf_data; /* data transfer control format */
38 u_long vdccf; /* controller configuration flags */
39 u_long vdsecsize; /* sector size */
40 u_short vdfill0;
41 u_char vdcylskew; /* cylinder to cylinder skew factor */
42 u_char vdtrackskew; /* track to track skew factor */
43 u_long vdfill1;
44 u_long vddfr; /* diagnostic flag register */
45 u_long vddda; /* diagnostic dump address */
46};
ee18b8e6 47
7bae1a62
SL
48/* controller types */
49#define VDTYPE_VDDC 1 /* old vddc controller (smd only) */
50#define VDTYPE_SMDE 2 /* new smde controller (smd-e) */
ee18b8e6
SL
51
52/*
7bae1a62 53 * Controller status definitions.
82bc5dc5 54 */
7bae1a62
SL
55#define CS_SCS 0xf /* status change source (drive number) */
56#define CS_ELC 0x10 /* error on last command */
57#define CS_ICC 0x60 /* interupt cause code */
58#define ICC_NOI 0x00 /* no interupt */
59#define ICC_DUN 0x20 /* no interupt */
60#define ICC_ERR 0x40 /* no interupt */
61#define ICC_SUC 0x60 /* no interupt */
62#define CS_GO 0x80 /* go bit (controller busy) */
63#define CS_BE 0x100 /* buss error */
64#define CS_BOK 0x4000 /* board ok */
65#define CS_SFL 0x8000 /* system fail */
66#define CS_LEC 0xff000000 /* last error code */
ee18b8e6
SL
67
68/*
7bae1a62 69 * Drive status definitions.
ee18b8e6 70 */
7bae1a62
SL
71#define STA_UR 0x1 /* unit ready */
72#define STA_OC 0x2 /* on cylinder */
73#define STA_SE 0x4 /* seek error */
74#define STA_DF 0x8 /* drive fault */
75#define STA_WP 0x10 /* write protected */
76#define STA_US 0x20 /* unit selected */
ee18b8e6
SL
77
78/*
7bae1a62 79 * Interupt Control Field definitions.
ee18b8e6 80 */
7bae1a62
SL
81#define ICF_IPL 0x7 /* interupt priority level */
82#define ICF_IEN 0x8 /* interupt enable */
83#define ICF_IV 0xff00 /* interupt vector */
ee18b8e6
SL
84
85/*
7bae1a62 86 * Transfer Control Format definitions.
ee18b8e6 87 */
ee18b8e6
SL
88#define TCF_AM 0xff /* Address Modifier */
89#define AM_SNPDA 0x01 /* Standard Non-Privileged Data Access */
90#define AM_SASA 0x81 /* Standard Ascending Sequential Access */
91#define AM_ENPDA 0xf1 /* Extended Non-Privileged Data Access */
92#define AM_EASA 0xe1 /* Extended Ascending Sequential Access */
93#define TCF_BTE 0x800 /* Block Transfer Enable */
94
7bae1a62
SL
95/*
96 * Controller Configuration Flags.
97 */
98#define CCF_STS 0x1 /* sectors per track selectable */
99#define CCF_EAV 0x2 /* enable auto vector */
100#define CCF_ERR 0x4 /* enable reset register */
101#define CCF_DER 0x8 /* disable error recovery */
102#define CCF_XMD 0x60 /* xmd transfer mode (bus size) */
103#define XMD_8BIT 0x20 /* do only 8 bit transfers */
104#define XMD_16BIT 0x40 /* do only 16 bit transfers */
105#define XMD_32BIT 0x60 /* do only 32 bit transfers */
106#define CCF_BSZ 0x300 /* burst size */
ee18b8e6
SL
107#define BSZ_16WRD 0x000 /* 16 word transfer burst */
108#define BSZ_12WRD 0x100 /* 12 word transfer burst */
109#define BSZ_8WRD 0x200 /* 8 word transfer burst */
110#define BSZ_4WRD 0x300 /* 4 word transfer burst */
7bae1a62
SL
111#define CCF_SEN 0x400 /* cylinder/track skew enable (for format) */
112#define CCF_ENP 0x1000 /* enable parity */
113#define CCF_EPE 0x2000 /* enable parity errors */
114#define CCF_EDE 0x10000 /* error detection enable */
115#define CCF_ECE 0x20000 /* error correction enable */
ee18b8e6
SL
116
117/*
118 * Diagnostic register definitions.
119 */
7bae1a62
SL
120#define DIA_DC 0x7f /* dump count mask */
121#define DIA_DWR 0x80 /* dump write/read flag */
122#define DIA_ARE 0x100 /* auto rebuild enable */
123#define DIA_CEN 0x200 /* call enable flag */
124#define DIA_KEY 0xAA550000 /* reset enable key */
ee18b8e6 125
b39ce066
MK
126/*
127 * Hardware interface flags, in dcb.devselect and d_devflags
128 */
129#define VD_ESDI 0x10 /* drive is on ESDI interface */
130#define d_devflags d_drivedata[0] /* in disk label */
131
132/*
133 * Error recovery flags.
134 */
135#define VDRF_RTZ 0x0001 /* return to zero */
136#define VDRF_OCF 0x0002 /* on cylinder false */
137#define VDRF_OSP 0x0004 /* offset plus */
138#define VDRF_OSM 0x0008 /* offset minus */
139#define VDRF_DSE 0x0080 /* data strobe early */
140#define VDRF_DSL 0x0100 /* data strobe late */
141
142#define VDRF_NONE 0
143#define VDRF_NORMAL (VDRF_RTZ|VDRF_OCF|VDRF_OSP|VDRF_OSM|VDRF_DSE|VDRF_DSE)
144
ee18b8e6
SL
145/*
146 * Perform a reset on the controller.
147 */
7bae1a62
SL
148#define VDRESET(a,t) { \
149 if ((t) == VDTYPE_SMDE) { \
150 ((struct vddevice *)(a))->vddfr = DIA_KEY|DIA_CEN; \
151 ((struct vddevice *)(a))->vdcdr = (u_long)0xffffffff; \
ee18b8e6
SL
152 DELAY(5000000); \
153 } else { \
7bae1a62 154 ((struct vddevice *)(a))->vdreset = 0; \
ee18b8e6
SL
155 DELAY(1500000); \
156 } \
157}
158
159/*
160 * Abort a controller operation.
161 */
7bae1a62
SL
162#define VDABORT(a,t) { \
163 if ((t) == VDTYPE_VDDC) { \
164 movow((a), (VDOP_ABORT&0xffff0000)>>16) ; \
165 movow((int)(a)+2, VDOP_ABORT&0xffff); \
ee18b8e6 166 } else \
7bae1a62 167 ((struct vddevice *)(a))->vdcdr = (u_long)VDOP_ABORT; \
ee18b8e6
SL
168 DELAY(1000000); \
169}
170
171/*
7bae1a62 172 * Start a command.
ee18b8e6 173 */
7bae1a62
SL
174#define VDGO(a,mdcb,t) {\
175 if ((t) == VDTYPE_VDDC) { \
176 movow((a), ((int)(mdcb)&0xffff0000)>>16) ; \
177 movow((int)((a))+2, (int)(mdcb)&0xffff); \
ee18b8e6 178 } else \
7bae1a62 179 ((struct vddevice *)(a))->vdcdr = (mdcb); \
ee18b8e6
SL
180}
181
ee18b8e6 182/*
7bae1a62 183 * MDCB layout.
ee18b8e6 184 */
7bae1a62
SL
185struct mdcb {
186 struct dcb *mdcb_head; /* first dcb in list */
187 struct dcb *mdcb_busy; /* dcb being processed */
188 struct dcb *mdcb_intr; /* dcb causing interrupt */
189 long mdcb_status; /* status of dcb in mdcb_busy */
190};
ee18b8e6
SL
191
192/*
7bae1a62 193 * DCB definitions.
ee18b8e6 194 */
7bae1a62
SL
195
196/*
197 * A disk address.
198 */
199typedef struct {
200 u_char track; /* all 8 bits */
201 u_char sector; /* all 8 bits */
202 u_short cylinder; /* low order 12 bits */
203} dskadr;
ee18b8e6
SL
204
205/*
206 * DCB trailer formats.
207 */
208/* read/write trailer */
d99b7c9d 209struct trrw {
1f9a1539 210 u_long memadr; /* memory address */
ee18b8e6
SL
211 u_long wcount; /* 16 bit word count */
212 dskadr disk; /* disk address */
d99b7c9d 213};
ee18b8e6
SL
214
215/* scatter/gather trailer */
d99b7c9d
MK
216#define VDMAXPAGES (MAXPHYS / NBPG)
217struct trsg {
218 struct trrw start_addr;
219 struct addr_chain {
1f9a1539 220 u_long nxt_addr;
ee18b8e6 221 u_long nxt_len;
d99b7c9d
MK
222 } addr_chain[VDMAXPAGES + 1];
223};
ee18b8e6
SL
224
225/* seek trailer format */
d99b7c9d 226struct trseek {
ee18b8e6 227 dskadr skaddr;
d99b7c9d 228};
ee18b8e6
SL
229
230/* format trailer */
d99b7c9d 231struct trfmt {
ee18b8e6
SL
232 char *addr; /* data buffer to be filled on sector*/
233 long nsectors; /* # of sectors to be formatted */
234 dskadr disk; /* disk physical address info */
235 dskadr hdr; /* header address info */
d99b7c9d 236};
ee18b8e6
SL
237
238/* reset/configure trailer */
d99b7c9d 239struct treset {
ee18b8e6
SL
240 long ncyl; /* # cylinders */
241 long nsurfaces; /* # surfaces */
242 long nsectors; /* # sectors */
243 long slip_sec; /* # of slip sectors */
8d35fe51 244 long recovery; /* recovery flags */
d99b7c9d
MK
245};
246
247/* ident trailer */
248struct trid {
249 long name;
250 long id;
251 long date;
252};
ee18b8e6
SL
253
254/*
255 * DCB layout.
256 */
7bae1a62
SL
257struct dcb {
258 struct dcb *nxtdcb; /* next dcb */
ee18b8e6
SL
259 short intflg; /* interrupt settings and flags */
260 short opcode; /* DCB command code etc... */
261 long operrsta; /* error & status info */
262 short fill; /* not used */
263 char devselect; /* drive selection */
264 char trailcnt; /* trailer Word Count */
265 long err_memadr; /* error memory address */
266 char err_code; /* error codes for SMD/E */
267 char fill2; /* not used */
268 short err_wcount; /* error word count */
269 char err_trk; /* error track/sector */
270 char err_sec; /* error track/sector */
271 short err_cyl; /* error cylinder adr */
272 union {
d99b7c9d
MK
273 struct trid idtrail; /* ident command trailer */
274 struct trseek sktrail; /* seek command trailer */
275 struct trsg sgtrail; /* scatter/gather trailer */
276 struct trrw rwtrail; /* read/write trailer */
277 struct trfmt fmtrail; /* format trailer */
278 struct treset rstrail; /* reset/configure trailer */
279 } trail;
280};
281
282/*
283 * smaller DCB with seek trailer only (no scatter-gather).
284 */
285struct skdcb {
286 struct dcb *nxtdcb; /* next dcb */
287 short intflg; /* interrupt settings and flags */
288 short opcode; /* DCB command code etc... */
289 long operrsta; /* error & status info */
290 short fill; /* not used */
291 char devselect; /* drive selection */
292 char trailcnt; /* trailer Word Count */
293 long err_memadr; /* error memory address */
294 char err_code; /* error codes for SMD/E */
295 char fill2; /* not used */
296 short err_wcount; /* error word count */
297 char err_trk; /* error track/sector */
298 char err_sec; /* error track/sector */
299 short err_cyl; /* error cylinder adr */
300 union {
301 struct trseek sktrail; /* seek command trailer */
ee18b8e6 302 } trail;
7bae1a62 303};
ee18b8e6
SL
304
305/*
7bae1a62 306 * DCB command codes.
ee18b8e6 307 */
7bae1a62
SL
308#define VDOP_RD 0x80 /* read data */
309#define VDOP_FTR 0xc0 /* full track read */
310#define VDOP_RAS 0x90 /* read and scatter */
311#define VDOP_RDRAW 0x600 /* read unformatted disk sector */
312#define VDOP_CMP 0xa0 /* compare */
313#define VDOP_FTC 0xe0 /* full track compare */
314#define VDOP_RHDE 0x180 /* read header, data & ecc */
315#define VDOP_WD 0x00 /* write data */
316#define VDOP_FTW 0x40 /* full track write */
317#define VDOP_WTC 0x20 /* write then compare */
318#define VDOP_FTWTC 0x60 /* full track write then compare */
319#define VDOP_GAW 0x10 /* gather and write */
320#define VDOP_WDE 0x100 /* write data & ecc */
321#define VDOP_FSECT 0x900 /* format sector */
322#define VDOP_GWC 0x30 /* gather write & compare */
323#define VDOP_START 0x800 /* start drives */
324#define VDOP_RELEASE 0xa00 /* stop drives */
325#define VDOP_SEEK 0xb00 /* seek */
326#define VDOP_INIT 0xc00 /* initialize controller */
327#define VDOP_DIAG 0xd00 /* diagnose (self-test) controller */
328#define VDOP_CONFIG 0xe00 /* reset & configure drive */
329#define VDOP_STATUS 0xf00 /* get drive status */
d99b7c9d 330#define VDOP_IDENT 0x700 /* identify controller */
7bae1a62
SL
331
332#define VDOP_ABORT 0x80000000 /* abort current command */
ee18b8e6
SL
333
334/*
7bae1a62 335 * DCB status definitions.
ee18b8e6 336 */
7bae1a62
SL
337#define DCBS_HCRC 0x00000001 /* header crc error */
338#define DCBS_HCE 0x00000002 /* header compare error */
339#define DCBS_WPT 0x00000004 /* drive write protected */
340#define DCBS_CHE 0x00000008 /* controller hardware error */
341#define DCBS_SKI 0x00000010 /* seek incomplete */
342#define DCBS_UDE 0x00000020 /* uncorrectable data error */
343#define DCBS_OCYL 0x00000040 /* off cylinder */
344#define DCBS_NRDY 0x00000080 /* drive not ready */
345#define DCBS_ATA 0x00000100 /* alternate track accessed */
346#define DCBS_SKS 0x00000200 /* seek started */
347#define DCBS_IVA 0x00000400 /* invalid disk address error */
348#define DCBS_NEM 0x00000800 /* non-existant memory error */
349#define DCBS_DPE 0x00001000 /* memory data parity error */
350#define DCBS_DCE 0x00002000 /* data compare error */
351#define DCBS_DDI 0x00004000 /* ddi ready */
352#define DCBS_OAB 0x00008000 /* operation aborted */
353#define DCBS_DSE 0x00010000 /* data strobe early */
354#define DCBS_DSL 0x00020000 /* data strobe late */
355#define DCBS_TOP 0x00040000 /* track offset plus */
356#define DCBS_TOM 0x00080000 /* track offset minus */
357#define DCBS_CCD 0x00100000 /* controller corrected data */
358#define DCBS_HARD 0x00200000 /* hard error */
359#define DCBS_SOFT 0x00400000 /* soft error (retry succesful) */
360#define DCBS_ERR 0x00800000 /* composite error */
361#define DCBS_IVC 0x01000000 /* invalid command error */
362/* bits 24-27 unused */
363#define DCBS_BSY 0x10000000 /* controller busy */
364#define DCBS_ICC 0x60000000 /* interrupt cause code */
365#define DCBS_INT 0x80000000 /* interrupt generated for this dcb */
366
367#define VDERRBITS "\20\1HCRC\2HCE\3WPT\4CHE\5DSKI\6UDE\7OCYL\10NRDY\
368\11ATA\12SKS\13IVA\14NEM\15DPE\16DCE\17DDI\20OAB\21DSE\22DSL\23TOP\24TOM\
369\25CCD\26HARD\27SOFT\30ERR\31IVC\35ABORTED\36FAIL\37COMPLETE\40STARTED"
370
371/* drive related errors */
372#define VDERR_DRIVE (DCBS_SKI|DCBS_OCYL|DCBS_NRDY|DCBS_IVA)
373/* controller related errors */
374#define VDERR_CTLR (DCBS_CHE|DCBS_OAB|DCBS_IVC|DCBS_NEM)
375/* potentially recoverable errors */
1f9a1539 376#define VDERR_RETRY \
7bae1a62
SL
377 (VDERR_DRIVE|VDERR_CTLR|DCBS_DCE|DCBS_DPE|DCBS_HCRC|DCBS_HCE)
378/* uncorrected data errors */
1f9a1539 379#define VDERR_HARD (VDERR_RETRY|DCBS_WPT|DCBS_UDE)
ee18b8e6
SL
380
381/*
7bae1a62 382 * DCB status codes.
ee18b8e6 383 */
7bae1a62
SL
384#define DCBS_ABORT 0x10000000 /* dcb aborted */
385#define DCBS_FAIL 0x20000000 /* dcb unsuccesfully completed */
386#define DCBS_DONE 0x40000000 /* dcb complete */
387#define DCBS_START 0x80000000 /* dcb started */
ee18b8e6 388
7bae1a62
SL
389/*
390 * DCB interrupt control.
391 */
392#define DCBINT_NONE 0x0 /* don't interrupt */
393#define DCBINT_ERR 0x2 /* interrupt on error */
394#define DCBINT_SUC 0x1 /* interrupt on success */
395#define DCBINT_DONE (DCBINT_ERR|DCBINT_SUC)
396#define DCBINT_PBA 0x4 /* proceed before acknowledge */
ee18b8e6 397
7bae1a62
SL
398/*
399 * Sector formats.
400 */
401typedef union {
402 struct {
403 dskadr hdr_addr;
404 short smd_crc;
405 } smd;
406 struct {
407 dskadr physical;
408 dskadr logical;
409 long smd_e_crc;
410 } smd_e;
411} fmt_hdr;
ee18b8e6 412
7bae1a62
SL
413/* Sector Header bit assignments */
414#define VDMF 0x8000 /* Manufacturer Fault 1=good sector */
415#define VDUF 0x4000 /* User Fault 1=good sector */
416#define VDALT 0x2000 /* Alternate Sector 1=alternate */
417#define VDWPT 0x1000 /* Write Protect 1=Read Only Sector */
81304755
MK
418
419/* input register assignments for DIOCWFORMAT ioctl */
420#define dk_op df_reg[0] /* opcode */
421#define dk_althdr df_reg[1] /* alt. sect. header, in an int! */
422#define dk_fmtflags df_reg[2] /* header format flags */
423
424/* output register assignments for DIOCWFORMAT ioctl */
425#define dk_operrsta df_reg[0] /* dcb operrsta */
426#define dk_ecode df_reg[1] /* smd-e err_code */