bring up to revision 7 for tahoe release
[unix-history] / usr / src / sys / tahoe / vba / drreg.h
CommitLineData
430f81c3
MK
1/*
2 * @(#)drreg.h 7.1 (Berkeley) %G%
3 */
04cfaaaf
SL
4
5/*
6 ------------------------------------------
7 Must include <h/types.h> and <h/buf.h>
8 ------------------------------------------
9*/
10
11#define DRINTV 0x9c /* Has to match with ml/scb.s */
12#define DRADDMOD 0x01 /* Addr modifier used to access TAHOE memory */
13#define DR_ZERO 0
14#define DRPRI (PZERO+1)
15
16#define DR_TICK 600 /* Default # of clock ticks between call
17 to local timer watchdog routine */
18#define DR_TOCK 2 /* default # of calls to local watch dog
19 before an IO or wait is determined to
20 have timeout */
21
22
23struct rsdevice {
24 ushort dr_cstat; /* Control & status registers */
25 ushort dr_data; /* Input/Ouptut data registers */
26 char dr_addmod; /* Address modifier for DMA */
27 char dr_intvect; /* Interrupt vector */
28 ushort dr_pulse; /* Pulse command register */
29 ushort dr_xx08; /* Not used */
30 ushort dr_xx0A; /* Not used */
31 ushort dr_xx0C; /* Not used */
32 ushort dr_xx0E; /* Not used */
33 ushort dr_xx10; /* Not used */
34 ushort dr_walo; /* Low DMA address register --when written-- */
35 ushort dr_range; /* DMA range counter */
36 ushort dr_ralo; /* Low DMA address register --when read-- */
37 ushort dr_xx18; /* Not used */
38 ushort dr_wahi; /* High DMA address register --when written-- */
39 ushort dr_xx1C; /* Not used */
40 ushort dr_rahi; /* High DMA address register --when read-- */
41};
42
43
44struct dr_aux {
45 struct rsdevice *dr_addr; /* Physical addr of currently active DR11 */
46 struct buf *dr_actf; /* Pointers to DR11's active buffers list */
47 unsigned int dr_flags; /* State: Hold open, active,... */
48 ushort dr_cmd; /* Hold cmd placed here by ioctl
49 for later execution by rsstrategy() */
50 ushort dr_op; /* Current operation: DR_READ/DR_WRITE */
51 long dr_bycnt; /* Total byte cnt of current operation */
52 /* decremented by completion interrupt */
53 caddr_t dr_oba; /* original xfer addr, count */
54 long dr_obc;
55 unsigned long
56 rtimoticks, /* No of ticks before timing out on no stall
57 read */
58 wtimoticks, /* No of ticks before timing out on no stall
59 write */
60 currenttimo; /* the number of current timeout call to
61 omrwtimo() */
62 ushort dr_istat; /* Latest interrupt status */
63 struct buf dr_buf;
64
65 /*ushort dr_time; /* # of ticks until timeout */
66 /*ushort dr_tock; /* # of ticks accumulated */
67 /*ushort dr_cseq; /* Current sequence number */
68 /*ushort dr_lseq; /* Last sequence number */
69};
70
71/* Command used by drioctl()
72*/
73struct dr11io {
74 ushort arg[8];
75};
76
77#define RSADDR(unit) ((struct rsdevice *)drinfo[unit]->ui_addr)
78
79/* Control register bits */
80#define RDMA 0x8000 /* reset DMA end-of-range flag */
81#define RATN 0x4000 /* reset attention flag */
82#define RPER 0x2000 /* reset device parity error flag */
83#define MCLR 0x1000 /* master clear board and INT device */
84#define CYCL 0x0100 /* forces DMA cycle if DMA enabled */
85#define IENB 0x0040 /* enables interrupt */
86#define FCN3 0x0008 /* func. bit 3 to device (FNCT3 H) */
87#define FCN2 0x0004 /* func. bit 2 to device (FNCT2 H) */
88 /* also asserts ACLO FCNT2 H to device */
89#define FCN1 0x0002 /* func. bit 1 to device (FNCT1 H) */
90#define GO 0x0001 /* enable DMA and pulse GO to device */
91
92/* Status register bits */
93#define DMAF 0x8000 /* indicates DMA end-of-range */
94#define ATTF 0x4000 /* indicates attention false-to-true */
95#define ATTN 0x2000 /* current state of ATTENTION H input */
96#define PERR 0x1000 /* Set by external parity error */
97#define STTA 0x0800 /* STATUS A H input state */
98#define STTB 0x0400 /* STATUS B H input state */
99#define STTC 0x0200 /* STATUS C H input state */
100#define REDY 0x0080 /* board ready for cmd (dma not on) */
101#define IENF 0x0040 /* Interrupt enabled if on */
102#define BERR 0x0020 /* Set if bus error during DMA */
103#define TERR 0x0010 /* Set if bus timeout during DMA */
104#define FC3S 0x0008 /* State of FCN3 latch */
105#define FC2S 0x0004 /* State of FCN2 latch */
106#define FC1S 0x0002 /* State of FCN1 latch */
107#define DLFG 0x0001 /* 0 -> IKON-10083 *** 1 -> IKON-10077 */
108
109/* Pulse command register bits */
110#define SMSK 0x0040 /* pulse interrupt mask on: Set IENB */
111#define RMSK 0x0020 /* pulse interrupt mask off: Reset IENB */
112
113
114/*
115 * DR11 driver's internal flags -- to be stored in dr_flags
116*/
117#define DR_FMSK 0x0000E /* function bits mask */
118#define DR_OPEN 0x00001 /* This dr11 has been opened */
119#define DR_PRES 0x00002 /* This dr11 is present */
120#define DR_ACTV 0x00004 /* waiting for end-of-range */
121#define DR_ATWT 0x00008 /* waiting for attention interrupt */
122#define DR_ATRX 0x00010 /* attn received-resets when read */
123#define DR_TMDM 0x00020 /* timeout waiting for end-of-range */
124#define DR_TMAT 0x00040 /* timeout waiting for attention */
125#define DR_DMAX 0x00080 /* end-of-range interrupt received */
126#define DR_PCYL 0x00100 /* set cycle with next go */
127#define DR_DFCN 0x00200 /* donot update function bits until next go */
128#define DR_DACL 0x00400 /* defer alco pulse until go */
129#define DR_LOOPTST 0x02000 /* This dr11 is in loopback test mode */
130#define DR_LNKMODE 0x04000 /* This dr11 is in link mode */
131#define DR_NORSTALL 0x10000 /* Device is set to no stall mode for reads. */
132#define DR_NOWSTALL 0x20000 /* Device is set to no stall mode for writes. */
133#define DR_TIMEDOUT 0x40000 /* The device timed out on a stall mode R/W */
134
135/*
136 * DR11 driver's internal flags -- to be stored in dr_op
137*/
138#define DR_READ FCN1
139#define DR_WRITE 0
140
141/*
142 * Ioctl commands
143*/
11c1813d
KB
144#define DRWAIT _IOWR('d',1,long)
145#define DRPIOW _IOWR('d',2,long)
146#define DRPACL _IOWR('d',3,long)
147#define DRDACL _IOWR('d',4,long)
148#define DRPCYL _IOWR('d',5,long)
149#define DRDFCN _IOWR('d',6,long)
150#define DRRPER _IOWR('d',7,long)
151#define DRRATN _IOWR('d',8,long)
152#define DRRDMA _IOWR('d',9,long)
153#define DRSFCN _IOWR('d',10,long)
154
155#define DRSETRSTALL _IOWR('d',13,long)
156#define DRSETNORSTALL _IOWR('d',14,long)
157#define DRGETRSTALL _IOWR('d',15,long)
158#define DRSETRTIMEOUT _IOWR('d',16,long)
159#define DRGETRTIMEOUT _IOWR('d',17,long)
160#define DRSETWSTALL _IOWR('d',18,long)
161#define DRSETNOWSTALL _IOWR('d',19,long)
162#define DRGETWSTALL _IOWR('d',20,long)
163#define DRSETWTIMEOUT _IOWR('d',21,long)
164#define DRGETWTIMEOUT _IOWR('d',22,long)
165#define DRWRITEREADY _IOWR('d',23,long)
166#define DRREADREADY _IOWR('d',24,long)
167#define DRBUSY _IOWR('d',25,long)
168#define DRRESET _IOWR('d',26,long)
04cfaaaf
SL
169
170/* The block size for buffering and DMA transfers. */
171/* OM_BLOCKSIZE must be even and <= 32768. Multiples of 512 are prefered. */
172#define OM_BLOCKSIZE 32768
173
174
175/* --- Define ioctl call used by dr11 utility device -- */
176
11c1813d 177#define DR11STAT _IOWR('d',30,struct dr11io) /* Get status dr11, unit
04cfaaaf 178 number is dr11io.arg[0] */
11c1813d 179#define DR11LOOP _IOR('d',31,struct dr11io) /* Perform loopback test */
04cfaaaf
SL
180
181/* ---------------------------------------------------- */
182