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