xref: /csrg-svn/sys/tahoe/vba/mpreg.h (revision 35078)
1 /*
2  * Copyright (c) 1988 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  * Redistribution and use in source and binary forms are permitted
9  * provided that the above copyright notice and this paragraph are
10  * duplicated in all such forms and that any documentation,
11  * advertising materials, and other materials related to such
12  * distribution and use acknowledge that the software was developed
13  * by the University of California, Berkeley.  The name of the
14  * University may not be used to endorse or promote products derived
15  * from this software without specific prior written permission.
16  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
17  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19  *
20  *	@(#)mpreg.h	7.2 (Berkeley) 07/15/88
21  */
22 
23 /*
24  * MPCC Asynchronous Communications Interface.
25  */
26 #define MPINTRBASE	0xa0		/* base vector for interupts */
27 #define MPMAGIC		1969		/* magic number for mblok */
28 #define MPMAXPORT	32		/* maximum number of ports on an MPCC */
29 
30 /*
31  * MPCC's are capable of supporting one of a
32  * the protocols listed below.  This driver
33  * supports only the async terminal protocol.
34  */
35 #define MPPROTO_UNUSED	0	/* port not in use */
36 #define MPPROTO_ASYNC	1	/* async protocol */
37 #define MPPROTO_X25	2	/* x25 protocol (unsupported) */
38 #define MPPROTO_BISYNC	3	/* bisync protocol (unsupported) */
39 #define MPPROTO_SNA  	4	/* sna protocol (unsupported) */
40 
41 #define NMPPROTO	5	/* max protocols supported by MPCC */
42 
43 #define MPINSET        8
44 #define MPOUTSET       8
45 
46 /*
47  * Host Interface Structure
48  */
49 struct his {
50 	u_char	semaphore;
51 #define MPSEMA_AVAILABLE	1
52 #define MPSEMA_WORK		4
53 	u_char	imok;
54 #define MPIMOK_ALIVE	0x01
55 #define MPIMOK_DEAD	0x80
56 	u_char	brdnum;		/* Virtual brd number for protocol */
57 	u_char	unused;
58 	struct {
59 		u_char	inbdone[MPMAXPORT];	/* Ports w/ inbound completed */
60 		u_char	outbdone[MPMAXPORT];	/* Ports w/outbound available */
61 		u_int	fill[2];
62 	} proto[NMPPROTO];
63 };
64 
65 #define MPPORT_EOL	0xff		/* end of port list */
66 
67 /*
68  * Async host transmit list structure.
69  */
70 #define MPXMIT	4	/* # of transmit ptrs/MP_WRITE event */
71 
72 struct	hxmtl {
73 	caddr_t	dblock[MPXMIT];	/* ptrs to data blocks */
74 	u_short	size[MPXMIT];	/* size of each block */
75 };
76 
77 /*
78  * MPCC asynchronous protocol events.
79  */
80 struct mpevent {
81 	u_char	ev_status;	/* Go Status */
82 	u_char	ev_cmd;		/* Optional Op-code */
83 	u_short	ev_opts;	/* Optional flags */
84 	u_short	ev_error;	/* error status returned */
85 	u_short	ev_flags;	/* optional event flags field */
86 	caddr_t	ev_params;	/* pointer to event parameters */
87 	union {
88 		struct	hxmtl *hxl;	/* pointer to host xmit list */
89 		u_char	*rcvblk;	/* pointer to receive block */
90 	} ev_un;
91 	u_short	ev_count;	/* # ptrs in xmit list/# receive chars  */
92 	u_short	ev_unused;	/* round to longword */
93 	u_int	ev_unused2;	/* round to size of BSC struct. GROT!! */
94 };
95 
96 /* defines for ev_status */
97 #define EVSTATUS_FREE	0
98 #define EVSTATUS_GO	1
99 #define EVSTATUS_BUSY	2
100 #define EVSTATUS_DONE	4
101 
102 /* defines for ev_cmd */
103 #define EVCMD_OPEN	1
104 #define EVCMD_CLOSE	2
105 #define EVCMD_RESET	3
106 #define EVCMD_IOCTL	4
107 #define EVCMD_WRITE	5
108 #define EVCMD_READ	6
109 #define EVCMD_STATUS	7
110 #define EVCMD_EVENT	8
111 
112 /*
113  * Host-MPCC interface block.
114  */
115 struct	mblok {
116 	u_char	mb_status;		/* mpcc status */
117 	u_char	mb_ivec;		/* host interrupt vector */
118 	u_short	mb_magic;
119 	u_char	mb_diagswitch[2];	/* run diagnostics/application */
120 	u_char	mb_softerr;		/* soft error code */
121 	u_char	mb_harderr;		/* hard error code */
122 	struct mpdl {		/* download/config area */
123 		u_char	mpdl_status;	/* control/status */
124 		u_char	mpdl_cmd;	/* request type */
125 		u_short	mpdl_count;	/* size of parameter block */
126 		caddr_t	mpdl_data;	/* command parameters */
127 	} mb_dl;
128 	u_char	mb_hiport, mb_loport;	/* high-low mpcc port numbers */
129 	u_char	mb_unit;		/* mpcc unit number */
130 	u_char	mb_hndshk;		/* handshaking timer */
131 	caddr_t	mb_imokclk;		/* handshaking clock */
132 	u_char	mb_nointcnt;		/* no interrupt from handshake */
133 	u_char	mb_mpintcnt;		/* # outstanding interupts to MPCC */
134 	short	mb_unused;
135 	caddr_t	mb_mpintclk;		/* MPCC interrupt clock */
136 	struct	his mb_hostint;		/* To Talk with Host */
137 	u_char	mb_proto[MPMAXPORT];	/* per-port protocols */
138 	u_char	mb_intr[MPMAXPORT];	/* per-port host->mpcc int flags */
139 	struct	mpport {	/* per-port structure */
140 		u_short	mp_proto;	/* protocol of port */
141 		u_char	mp_on;		/* Next available entry on Host */
142 		u_char	mp_off;		/* Next expected 'DONE' entry on Host */
143 		struct	mpevent mp_recvq[MPINSET]; /* queue of events to host */
144 		struct	mpevent mp_sendq[MPOUTSET];/* queue of events to mpcc */
145 		u_char	mp_nextrcv;	/* next expected 'DONE' entry on Host */
146 		u_char	mp_flags;	/* host flags */
147 		short	mp_unused;
148 		caddr_t	mp_data;	/* pointer to data for port */
149 	} mb_port[MPMAXPORT];
150 };
151 
152 /* status defines for mblok.status */
153 #define MP_DLPEND	1
154 #define MP_DLOPEN	2
155 #define MP_DLDONE	3
156 #define MP_OPCLOSE	4
157 #define MP_OPOPEN	5
158 #define MP_DLTIME	6
159 #define MP_DLERROR	(-1)
160 
161 /* hard error status values loaded into mblock.herr */
162 #define NOHERR		0	/* no error */
163 #define MPBUSERR	1	/* bus error */
164 #define ADDRERR		2	/* address error */
165 #define UNDECC		3	/* undefined ecc interrupt */
166 #define UNDINT		4	/* undefined interrupt */
167 #define PWRFL		5	/* power fail occurred */
168 #define NOXENTRY	6	/* xdone was enterred w/o xmit entry on queue */
169 #define TWOFTMRS	7	/* tried to start two fast timers on one port */
170 #define INTQFULL	8	/* interupt queue full */
171 #define INTQERR		9	/* interupt queue ack error */
172 #define CBPERR		10	/* uncorrectable DMA parity error */
173 #define ACPDEAD		11	/* acap has died */
174 /* additional panic codes not listed */
175 
176 /* soft error status values loaded into mblock.serr */
177 #define NOSERR	0		/* no error */
178 #define DMAPERR	1		/* dma parity error */
179 #define ECCERR	2		/* local memory ecc error */
180 
181 /* Defines for flags */
182 #define MP_PROGRESS	1	/* Open or Close is in progress */
183 #define MP_PORTUP	2	/* link is up for port */
184 #define MP_REMBSY	4	/* remote station busy */
185 
186 /*
187  * Asynchronous Terminal Protocol Definitions.
188  */
189 #define A_RCVTIM	2	/* default max tix for receive event (~20ms) */
190 #define ACPTMR		300	/* approx. 5 secs to wait for acap     */
191 #define A_MAXEVTP	3	/* maximum # of L1 or Host Events to    */
192 				/* process per port at one time	 */
193 #define A_MAXRCV	128	/* max # of chars in rcv event - enough */
194 				/* to hold 20ms of chars at 19.2KB      */
195 #define A_NUMRCV	32	/* number of rcv buffers per port       */
196 #define A_NUMXMT	2	/* max number of concurrent xmits/port  */
197 #define A_NUMEVT	32	/* number of evt bufs for status evts   */
198 				/* and L2 to L1 transmit evts	   */
199 #define WR5	5		/* SCC Write Reg 5		      */
200 #define TXENBL	0x08		/* mask to enable transmitter in WR 5   */
201 #define RTSON	0x02		/* mask to turn on RTS in wreg 5	*/
202 #define CHR5MSK	0x1F		/* mask for 5-bit transmit data	 */
203 
204 /*
205  * macro to adjust a circular buffer ptr
206  *      x  = pointer or index
207  *      sz = size of circular buffer
208  */
209 #define adjptr(x,sz)	((x) = ((++(x) == (sz)) ? 0 : (x)))
210 #define adjptrbk(x,sz)	((x) = ((x) == 0) ? (sz) : --(x))
211 
212 /*
213  * Events from ASYNC Level 1 to Level 2
214  */
215 #define RCVDTA	10	/* normal receive data available */
216 #define PARERR	11	/* receive data with parity error */
217 #define OVRNERR	12	/* receive data with overrun error */
218 #define OVFERR	13	/* receive data with overflow error */
219 #define FRAMERR	14	/* receive data with framing error */
220 #define ACKXMT	15	/* successful completion of transmit */
221 #define NORBUF	16	/* No Receive Buffers available	 */
222 #define NOEBUF	17	/* No Event Buffers available */
223 #define BRKASRT	18	/* Break condition detected */
224 
225 /* defines for error conditions */
226 #define A_OK		0	/* No Errors */
227 #define A_INVEVT	1	/* Invalid Event Error */
228 #define A_IOCERR	2	/* Error while configuring port */
229 #define A_SIZERR	3	/* Error in count of data chars to xmt */
230 #define A_NXBERR	4	/* Transmit Incomplete due to lack of bufs */
231 
232 /*
233  * Modem control signal control structure.
234  */
235 struct mdmctl {
236         u_char	mc_rngdsr;	/* ring or dsr */
237         u_char	mc_rts;		/* request to send */
238         u_char	mc_rate;
239         u_char	mc_dcd;		/* data carrier detect */
240         u_char	mc_sectx;	/* secondary transmit */
241         u_char	mc_cts;		/* clear to send */
242         u_char	mc_secrx;	/* secondary receive */
243         u_char	mc_dtr;		/* data terminal ready */
244 };
245 
246 /* defines for modem control lines */
247 #define ASSERT	1		/* line asserted */
248 #define DROP	2		/* line dropped */
249 #define AUTO	3		/* auto mode enabled, rts only */
250 
251 /*
252  * Async parameter structure.
253  */
254 struct asyncparam {
255 	u_char	ap_xon, ap_xoff;	/* xon-xoff characters */
256 	u_char	ap_xena;		/* xon/xoff enabled */
257 	u_char	ap_xany;		/* any received char enables xmitter */
258 	struct	mdmctl ap_modem;	/* port modem control lines */
259 	struct	mdmctl ap_intena;	/* modem signals which generate */
260 					/* status change events */
261 	u_char	ap_data;		/* number of data bits */
262 	u_char	ap_stop;		/* number of stop bits */
263 	u_char	ap_baud;		/* baud rate */
264 	u_char	ap_parity;		/* even/odd/no parity */
265 	u_char	ap_loop;		/* enable for local loopback */
266 	u_char	ap_rtimer;		/* receive timer value (msec) */
267 	short	ap_fill;		/* round to longword */
268 };
269 
270 /* enable/disable signal codes */
271 #define MPA_ENA	1		/* condition enabled */
272 #define MPA_DIS	2		/* condition disabled */
273 
274 /* defines for ap_data */
275 #define MPCHAR_5	0	/* 5 bits per character */
276 #define MPCHAR_6	2	/* 6 bits per character */
277 #define MPCHAR_7	1	/* 7 bits per character */
278 #define MPCHAR_8 	3	/* 8 bits per character */
279 
280 /* defines for ap_stop */
281 #define MPSTOP_1	1	/* 1 stop bit per character */
282 #define MPSTOP_1_5	2	/* 1 1/2 stop bits per character */
283 #define MPSTOP_2	3	/* 2 stop bits per character */
284 
285 /* defines for ap_baud */
286 #define MODEM	0
287 #define M0	0		/* baud rate = 0 */
288 #define M50	1		/* baud rate = 50 */
289 #define M75	2		/* baud rate = 75 */
290 #define M110	3		/* baud rate = 110 */
291 #define M134_5	4		/* baud rate = 134.5 */
292 #define M150	5		/* baud rate = 150 */
293 #define M200	6		/* baud rate = 200 */
294 #define M300	7		/* baud rate = 300 */
295 #define M600	8		/* baud rate = 600 */
296 #define M1200	9		/* baud rate = 1200 */
297 #define M1800	10		/* baud rate = 1800 */
298 #define M2400	11		/* baud rate = 2400 */
299 #define M4800	12		/* baud rate = 4800 */
300 #define M9600	13		/* baud rate = 9600 */
301 #define MEXTA	14		/* baud rate = Ext A */
302 #define MEXTB	15		/* baud rate = Ext B */
303 #define M2000	16		/* baud rate = 2000 */
304 #define M3600	17		/* baud rate = 3600 */
305 #define M7200	18		/* baud rate = 7200 */
306 #define M19200	19		/* baud rate = 19,200 */
307 #define M24000	20		/* baud rate = 24,000 */
308 #define M28400	21		/* baud rate = 28,400 */
309 #define M37800	22		/* baud rate = 37,800 */
310 #define M40300	23		/* baud rate = 40,300 */
311 #define M48000	24		/* baud rate = 48,000 */
312 #define M52000	25		/* baud rate = 52,000 */
313 #define M56800	26		/* baud rate = 56,800 */
314 
315 /* defines for ap_parity */
316 #define MPPAR_NONE	0	/* no parity */
317 #define MPPAR_ODD	1	/* odd parity */
318 #define MPPAR_EVEN	3	/* even parity */
319 
320 /* possible flags for Host MP_IOCTL Events */
321 #define A_CHGX		1	/* IOCTL is only chging xonxoff params */
322 #define A_MDMCHG	2	/* change modem control lines */
323 #define A_MDMGET	3	/* get current state of modem ctl lines */
324 #define A_CHGL1P	4	/* IOCTL is changing changing L1 params */
325 #define A_BRKON		5	/* set port break bit */
326 #define A_BRKOFF	6	/* clear port break bit */
327 #define A_CHGALL	7	/* IOCTL is changing xonxoff params, */
328 				/* pcnfg struct, & modem ctl structs */
329 #define A_DISABX	8	/* disable port transmitter (ctl-s) */
330 #define A_ENABLX	9	/* enable port transmitter (ctl-q) */
331 
332 /* possible flags for Host MP_WRITE Events */
333 #define A_FLUSH		1	/* flush any queued transmit events */
334 #define A_SSTOP		2	/* transmit a port stop (xoff) char */
335 				/* before sending rest of event xmts */
336 #define A_SSTART	3	/* transmit a port start (xon) char */
337 				/* before sending rest of event xmts */
338 
339 /* possible flags for Outbound MP_READ Events */
340 #define A_XOFF		1	/* transmitter stopped from by xoff char */
341 
342 /* Perpos flags for modem control fields */
343 #define A_RNGDSR	00001
344 #define A_RTS		00002
345 #define A_RATE		00004
346 #define A_DCD		00010
347 #define A_SECTX		00020
348 #define A_CTS		00040
349 #define A_SECRX		00100
350 #define A_DTR		00200
351 
352 /* error messages printed at console , board & port # filled in later */
353 #define A_INVSTS	"\n#### Invalid Status Event "
354 #define A_INVCMD	"\n#### Invalid Event From the MPCC "
355 #define A_NORBUF	"\n#### No More Available Receive Buffers "
356 #define A_NOEBUF	"\n#### No More Available Event Buffers "
357 #define A_OVRN		"\n#### Overrun Error Detected "
358 #define A_OVRF		"\n#### Overflow Error Detected "
359 #define A_NOXBUF	"\n#### No More Available Transmit Event Buffers "
360 #define A_XSIZE		"\n#### Transmit Data Block Size Exceeds Event Data Buffer Size "
361 #define A_NOFREIN	"\n#### No Available Inbound Entries to Send Close Event "
362 
363 #define DCDASRT		100	/* data carrier detect asserted */
364 #define DTRASRT		101	/* data terminal ready asserted */
365 #define RNGASRT		102	/* ring indicator asserted */
366 #define DSRASRT		102	/* data set ready asserted */
367 #define CTSASRT		103	/* clear to send asserted */
368 #define RTSASRT		104	/* ready to send asserted */
369 #define STXASRT		105	/* secondary transmit asserted */
370 #define SRXASRT		106	/* secondary recieve asserted */
371 #define RATEASRT	107	/* rate signal asserted */
372 #define DCDDROP		108	/* data carrier detect dropped */
373 #define DTRDROP		109	/* data terminal ready dropped */
374 #define RNGDROP		110	/* ring indicator dropped */
375 #define MPDSRDROP	110	/* data set ready dropped */
376 #define CTSDROP		111	/* clear to send dropped */
377 #define RTSDROP		112	/* ready to send dropped */
378 #define STXDROP		113	/* secondary transmit dropped */
379 #define SRXDROP		114	/* secondary recieve dropped */
380 #define RATEDROP	115	/* rate signal dropped */
381 
382 /* Defines for filters and intena in portstat */
383 #define MDM_OFF	0
384 #define MDM_ON	1
385 
386 /* Modem on/off flags */
387 #define MMOD_OFF 0
388 #define MMOD_ON 1
389 
390 /* defintions for DL interface */
391 
392 #define MPDLBUFSIZE       1024
393 
394 
395 /*      mpdlioctl command defines       */
396 
397 struct protports {
398 	char protoport[MPMAXPORT];
399 } ;
400 
401 struct abdcf {
402         short   xmtbsz;         /* transmit buffer size - should */
403                                 /* equal # of chars in a cblock  */
404 };
405 
406 struct bdcf {
407 	char    loadname[NMPPROTO+1];
408 	char    protoports[MPMAXPORT];
409 	char    fccstimer;      /* powerfail timer */
410 	char    fccsports;      /* ports to affect */
411 	char    fccssoc;        /* ports which will 'switch on close' */
412 };
413 
414 
415 /* These ioctls are for the dlmpcc command */
416 #define MPIOPORTMAP         _IOW('m',1, struct protports)
417 #define MPIOHILO            _IOW('m',3, short)
418 #define MPIOENDCODE         _IO('m',4)
419 #define MPIOASYNCNF         _IOW('m',7, struct abdcf)
420 #define MPIOENDDL           _IO('m',10)
421 #define MPIOSTARTDL         _IO('m',11)
422 #define MPIORESETBOARD      _IO('m',12)
423 
424 /*      mpdlwrite opcode defines        */
425 
426 #define MPDLCMD_NORMAL          1
427 
428