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