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