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