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