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