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