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