xref: /csrg-svn/sys/tahoe/vba/mp.c (revision 32633)
1*32633Ssam /*	mp.c	1.1	87/11/17	*/
2*32633Ssam 
3*32633Ssam #include "mp.h"
4*32633Ssam #if NMP > 0
5*32633Ssam /*
6*32633Ssam  * Multi Protocol Communications Controller (MPCC).
7*32633Ssam  * Asynchronous Terminal Protocol Support.
8*32633Ssam  */
9*32633Ssam #include "../machine/pte.h"
10*32633Ssam #include "../machine/mtpr.h"
11*32633Ssam 
12*32633Ssam #include "param.h"
13*32633Ssam #include "ioctl.h"
14*32633Ssam #include "tty.h"
15*32633Ssam #include "dir.h"
16*32633Ssam #include "user.h"
17*32633Ssam #include "map.h"
18*32633Ssam #include "buf.h"
19*32633Ssam #include "conf.h"
20*32633Ssam #include "file.h"
21*32633Ssam #include "uio.h"
22*32633Ssam #include "errno.h"
23*32633Ssam #include "syslog.h"
24*32633Ssam #include "vmmac.h"
25*32633Ssam #include "kernel.h"
26*32633Ssam #include "clist.h"
27*32633Ssam 
28*32633Ssam #include "../tahoevba/vbavar.h"
29*32633Ssam #include "../tahoevba/mpreg.h"
30*32633Ssam 
31*32633Ssam #define	MPCHUNK	16
32*32633Ssam #define	MPPORT(n)	((n) & 0xf)
33*32633Ssam #define	MPUNIT(n)	((n) >> 4)
34*32633Ssam 
35*32633Ssam /*
36*32633Ssam  * Driver information for auto-configuration stuff.
37*32633Ssam  */
38*32633Ssam int     mpprobe(), mpattach(), mpintr();
39*32633Ssam struct  vba_device *mpinfo[NMP];
40*32633Ssam long    mpstd[] = { 0 };
41*32633Ssam struct  vba_driver mpdriver =
42*32633Ssam     { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo };
43*32633Ssam 
44*32633Ssam int	mpstart();
45*32633Ssam struct	mpevent *mpparam();
46*32633Ssam struct	mpevent *mp_getevent();
47*32633Ssam 
48*32633Ssam /*
49*32633Ssam  * The following structure is needed to deal with mpcc's convoluted
50*32633Ssam  * method for locating it's mblok structures (hold your stomach).
51*32633Ssam  * When an mpcc is reset at boot time it searches host memory
52*32633Ssam  * looking for a string that says ``ThIs Is MpCc''.  The mpcc
53*32633Ssam  * then reads the structure to locate the pointer to it's mblok
54*32633Ssam  * structure (you can wretch now).
55*32633Ssam  */
56*32633Ssam struct mpbogus {
57*32633Ssam 	char	s[12];			/* `ThIs Is MpCc'' */
58*32633Ssam 	u_char	status;
59*32633Ssam 	u_char	unused;
60*32633Ssam 	u_short	magic;
61*32633Ssam 	struct	mblok *mb;
62*32633Ssam 	struct	mblok *mbloks[NMP];	/* can support at most 16 mpcc's */
63*32633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' };
64*32633Ssam 
65*32633Ssam /*
66*32633Ssam  * Software state per unit.
67*32633Ssam  */
68*32633Ssam struct	mpsoftc {
69*32633Ssam 	u_int	ms_ivec;		/* interrupt vector */
70*32633Ssam 	u_int	ms_softCAR;		/* software carrier for async */
71*32633Ssam 	struct	mblok *ms_mb;		/* mpcc status area */
72*32633Ssam 	struct	vb_buf ms_buf;		/* vba resources for ms_mb */
73*32633Ssam 	struct	hxmtl ms_hxl[MPMAXPORT];/* host transmit list */
74*32633Ssam 	struct	asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */
75*32633Ssam 	char	ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */
76*32633Ssam } mp_softc[NMP];
77*32633Ssam 
78*32633Ssam struct	tty mp_tty[NMP*MPCHUNK];
79*32633Ssam #ifndef lint
80*32633Ssam int	nmp = NMP*MPCHUNK;
81*32633Ssam #endif
82*32633Ssam 
83*32633Ssam int	ttrstrt();
84*32633Ssam 
85*32633Ssam mpprobe(reg, vi)
86*32633Ssam 	caddr_t reg;
87*32633Ssam 	struct vba_device *vi;
88*32633Ssam {
89*32633Ssam 	register int br, cvec;
90*32633Ssam 	register struct mpsoftc *ms;
91*32633Ssam 
92*32633Ssam #ifdef lint
93*32633Ssam 	br = 0; cvec = br; br = cvec;
94*32633Ssam 	mpintr(0);
95*32633Ssam #endif
96*32633Ssam 	if (badaddr(reg, 2))
97*32633Ssam 		return (0);
98*32633Ssam 	ms = &mp_softc[vi->ui_unit];
99*32633Ssam 	/*
100*32633Ssam 	 * Allocate page tables and mblok
101*32633Ssam 	 * structure (mblok in non-cached memory).
102*32633Ssam 	 */
103*32633Ssam 	if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) {
104*32633Ssam 		printf("mp%d: vbainit failed\n", vi->ui_unit);
105*32633Ssam 		return (0);
106*32633Ssam 	}
107*32633Ssam 	ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf;
108*32633Ssam 	ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit;	/* XXX */
109*32633Ssam 	br = 0x14, cvec = ms->ms_ivec;			/* XXX */
110*32633Ssam 	return (sizeof (struct mblok));
111*32633Ssam }
112*32633Ssam 
113*32633Ssam mpattach(vi)
114*32633Ssam 	register struct vba_device *vi;
115*32633Ssam {
116*32633Ssam 	register struct mpsoftc *ms = &mp_softc[vi->ui_unit];
117*32633Ssam 
118*32633Ssam 	ms->ms_softCAR = vi->ui_flags;
119*32633Ssam 	/*
120*32633Ssam 	 * Setup pointer to mblok, initialize bogus
121*32633Ssam 	 * status block used by mpcc to locate the pointer
122*32633Ssam 	 * and then poke the mpcc to get it to search host
123*32633Ssam 	 * memory to find mblok pointer.
124*32633Ssam 	 */
125*32633Ssam 	mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf;
126*32633Ssam 	*(short *)vi->ui_addr = 0x100;		/* magic */
127*32633Ssam }
128*32633Ssam 
129*32633Ssam /*
130*32633Ssam  * Open an mpcc port.
131*32633Ssam  */
132*32633Ssam mpopen(dev, mode)
133*32633Ssam 	dev_t dev;
134*32633Ssam {
135*32633Ssam 	register struct tty *tp;
136*32633Ssam 	register struct mpsoftc *ms;
137*32633Ssam 	int error, s, port, unit, mpu;
138*32633Ssam 	struct vba_device *vi;
139*32633Ssam 	struct mpport *mp;
140*32633Ssam 	struct mpevent *ev;
141*32633Ssam 
142*32633Ssam 	unit = minor(dev);
143*32633Ssam 	mpu = MPUNIT(unit);
144*32633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
145*32633Ssam 		return (ENXIO);
146*32633Ssam 	tp = &mp_tty[unit];
147*32633Ssam 	if (tp->t_state & TS_XCLUDE && u.u_uid != 0)
148*32633Ssam 		return (EBUSY);
149*32633Ssam 	ms = &mp_softc[mpu];
150*32633Ssam 	port = MPPORT(unit);
151*32633Ssam 	if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC ||
152*32633Ssam 	    ms->ms_mb->mb_status != MP_OPOPEN)
153*32633Ssam 		return (ENXIO);
154*32633Ssam 	mp = &ms->ms_mb->mb_port[port];		/* host mpcc struct */
155*32633Ssam 	s = spl8();
156*32633Ssam 	while (mp->mp_flags & MP_PROGRESS)
157*32633Ssam 		sleep((caddr_t)&tp->t_canq, TTIPRI);
158*32633Ssam 	while (tp->t_state & TS_WOPEN)
159*32633Ssam 		sleep((caddr_t)&tp->t_canq, TTIPRI);
160*32633Ssam 	if (tp->t_state & TS_ISOPEN) {
161*32633Ssam 		splx(s);
162*32633Ssam 		return (0);
163*32633Ssam 	}
164*32633Ssam 	tp->t_state |= TS_WOPEN;
165*32633Ssam 	tp->t_addr = (caddr_t)ms;
166*32633Ssam 	tp->t_oproc = mpstart;
167*32633Ssam 	tp->t_dev = dev;
168*32633Ssam 	ttychars(tp);
169*32633Ssam 	if (tp->t_ispeed == 0) {
170*32633Ssam 		tp->t_ispeed = B9600;
171*32633Ssam 		tp->t_ospeed = B9600;
172*32633Ssam 		tp->t_flags |= ODDP|EVENP|ECHO;
173*32633Ssam 	}
174*32633Ssam 	/*
175*32633Ssam 	 * Initialize port state: init MPCC interface
176*32633Ssam 	 * structures for port and setup modem control.
177*32633Ssam 	 */
178*32633Ssam 	mp->mp_proto = MPPROTO_ASYNC;		/* XXX */
179*32633Ssam 	error = mpportinit(ms, mp, port);
180*32633Ssam 	if (error)
181*32633Ssam 		goto bad;
182*32633Ssam 	ev = mpparam(unit);
183*32633Ssam 	if (ev == 0) {
184*32633Ssam 		error = ENOBUFS;
185*32633Ssam 		goto bad;
186*32633Ssam 	}
187*32633Ssam 	mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port);
188*32633Ssam 	while ((tp->t_state & TS_CARR_ON) == 0)
189*32633Ssam 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
190*32633Ssam 	error = mpmodem(unit, MMOD_ON);
191*32633Ssam 	if (error)
192*32633Ssam 		goto bad;
193*32633Ssam 	while ((tp->t_state & TS_CARR_ON) == 0)
194*32633Ssam 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
195*32633Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
196*32633Ssam done:
197*32633Ssam 	splx(s);
198*32633Ssam 	/* wakeup anyone waiting for open to complete */
199*32633Ssam 	wakeup((caddr_t)&tp->t_canq);
200*32633Ssam 
201*32633Ssam 	return (error);
202*32633Ssam bad:
203*32633Ssam 	tp->t_state &= ~TS_WOPEN;
204*32633Ssam 	goto done;
205*32633Ssam }
206*32633Ssam 
207*32633Ssam /*
208*32633Ssam  * Close an mpcc port.
209*32633Ssam  */
210*32633Ssam mpclose(dev)
211*32633Ssam 	dev_t dev;
212*32633Ssam {
213*32633Ssam 	register struct tty *tp;
214*32633Ssam 	register struct mpport *mp;
215*32633Ssam 	register struct mpevent *ev;
216*32633Ssam 	int s, port, unit, error;
217*32633Ssam 	struct mblok *mb;
218*32633Ssam 
219*32633Ssam 	unit = minor(dev);
220*32633Ssam 	tp = &mp_tty[unit];
221*32633Ssam 	port = MPPORT(unit);
222*32633Ssam 	mb = mp_softc[MPUNIT(unit)].ms_mb;
223*32633Ssam 	mp = &mb->mb_port[port];
224*32633Ssam 	s = spl8();
225*32633Ssam 	if (mp->mp_flags & MP_PROGRESS) {		/* close in progress */
226*32633Ssam 		if (mp->mp_flags & MP_REMBSY) {
227*32633Ssam 			mp->mp_flags &= ~MP_REMBSY;
228*32633Ssam 			splx(s);
229*32633Ssam 			return (0);
230*32633Ssam 		}
231*32633Ssam 		while (mp->mp_flags & MP_PROGRESS)
232*32633Ssam 			sleep((caddr_t)&tp->t_canq,TTIPRI);
233*32633Ssam 	}
234*32633Ssam 	error = 0;
235*32633Ssam 	mp->mp_flags |= MP_PROGRESS;
236*32633Ssam 	(*linesw[tp->t_line].l_close)(tp);
237*32633Ssam 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
238*32633Ssam 		if (error = mpmodem(unit, MMOD_OFF)) {
239*32633Ssam 			mp->mp_flags &= ~MP_PROGRESS;
240*32633Ssam 			goto out;
241*32633Ssam 		}
242*32633Ssam 	while (tp->t_state & TS_FLUSH)			/* ??? */
243*32633Ssam 		sleep((caddr_t)&tp->t_state, TTOPRI);	/* ??? */
244*32633Ssam 	ttyclose(tp);
245*32633Ssam 	ev = mp_getevent(mp, unit);
246*32633Ssam 	if (ev == 0) {
247*32633Ssam 		 error = ENOBUFS;
248*32633Ssam 		 goto out;
249*32633Ssam 	}
250*32633Ssam 	mpcmd(ev, EVCMD_CLOSE, 0, mb, port);
251*32633Ssam out:
252*32633Ssam 	if (mp->mp_flags & MP_REMBSY)
253*32633Ssam 		mpclean(mb, port);
254*32633Ssam 	splx(s);
255*32633Ssam 	return (error);
256*32633Ssam }
257*32633Ssam 
258*32633Ssam /*
259*32633Ssam  * Read from an mpcc port.
260*32633Ssam  */
261*32633Ssam mpread(dev, uio)
262*32633Ssam 	dev_t dev;
263*32633Ssam 	struct uio *uio;
264*32633Ssam {
265*32633Ssam 	struct tty *tp;
266*32633Ssam 
267*32633Ssam 	tp = &mp_tty[minor(dev)];
268*32633Ssam 	return ((*linesw[tp->t_line].l_read)(tp, uio));
269*32633Ssam }
270*32633Ssam 
271*32633Ssam /*
272*32633Ssam  * Write to an mpcc port.
273*32633Ssam  */
274*32633Ssam mpwrite(dev, uio)
275*32633Ssam 	dev_t dev;
276*32633Ssam 	struct uio *uio;
277*32633Ssam {
278*32633Ssam 	struct tty *tp;
279*32633Ssam 
280*32633Ssam 	tp = &mp_tty[minor(dev)];
281*32633Ssam 	return ((*linesw[tp->t_line].l_write)(tp, uio));
282*32633Ssam }
283*32633Ssam 
284*32633Ssam /*
285*32633Ssam  * Ioctl for a mpcc port
286*32633Ssam  */
287*32633Ssam mpioctl(dev, cmd, data, flag)
288*32633Ssam 	dev_t dev;
289*32633Ssam 	caddr_t data;
290*32633Ssam {
291*32633Ssam 	register struct tty *tp;
292*32633Ssam 	register struct mpsoftc *ms;
293*32633Ssam 	register struct mpevent *ev;
294*32633Ssam 	register struct mpport *mp;
295*32633Ssam 	int s, port, error, unit;
296*32633Ssam 	struct mblok *mb;
297*32633Ssam 
298*32633Ssam 	unit = minor(dev);
299*32633Ssam 	tp = &mp_tty[unit];
300*32633Ssam 	ms = &mp_softc[MPUNIT(unit)];
301*32633Ssam 	mb = ms->ms_mb;
302*32633Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
303*32633Ssam 	if (error >= 0)
304*32633Ssam 		return (error);
305*32633Ssam 	error = ttioctl(tp, cmd, data, flag);
306*32633Ssam 	if (error >= 0) {
307*32633Ssam 		if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS ||
308*32633Ssam 		    cmd == TIOCLBIC || cmd == TIOCLSET) {
309*32633Ssam 			ev = mpparam(unit);
310*32633Ssam 			if (ev == 0)
311*32633Ssam 				error = ENOBUFS;
312*32633Ssam 			else
313*32633Ssam 				mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb,
314*32633Ssam 				    MPPORT(unit));
315*32633Ssam 		}
316*32633Ssam 		return (error);
317*32633Ssam 	}
318*32633Ssam 	switch (cmd) {
319*32633Ssam 	case TIOCSBRK:			/* send break */
320*32633Ssam 	case TIOCCBRK:			/* clear break */
321*32633Ssam 		port = MPPORT(unit);
322*32633Ssam 		mp = &mb->mb_port[port];
323*32633Ssam 		s = spl8();
324*32633Ssam 		ev = mp_getevent(mp, unit);
325*32633Ssam 		if (ev)
326*32633Ssam 			mpcmd(ev, EVCMD_IOCTL,
327*32633Ssam 			    (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF),
328*32633Ssam 			    mb, port);
329*32633Ssam 		else
330*32633Ssam 			error = ENOBUFS;
331*32633Ssam 		splx(s);
332*32633Ssam 		break;
333*32633Ssam 	case TIOCSDTR:			/* set dtr control line */
334*32633Ssam 		break;
335*32633Ssam 	case TIOCCDTR:			/* clear dtr control line */
336*32633Ssam 		break;
337*32633Ssam 	default:
338*32633Ssam 		error = ENOTTY;
339*32633Ssam 		break;
340*32633Ssam 	}
341*32633Ssam 	return (error);
342*32633Ssam }
343*32633Ssam 
344*32633Ssam struct mpevent *
345*32633Ssam mpparam(unit)
346*32633Ssam 	int unit;
347*32633Ssam {
348*32633Ssam 	register struct mpevent *ev;
349*32633Ssam 	register struct mpport *mp;
350*32633Ssam 	register struct tty *tp;
351*32633Ssam 	struct mblok *mb;
352*32633Ssam 	struct mpsoftc *ms;
353*32633Ssam 	register struct asyncparam *asp;
354*32633Ssam 	int port;
355*32633Ssam 
356*32633Ssam 	ms = &mp_softc[MPUNIT(unit)];
357*32633Ssam 	mb = ms->ms_mb;
358*32633Ssam 	port = MPPORT(unit);
359*32633Ssam 	mp = &mb->mb_port[port];
360*32633Ssam 	ev = mp_getevent(mp, unit);	/* XXX */
361*32633Ssam 	if (ev == 0)
362*32633Ssam 		return (ev);
363*32633Ssam 	tp = &mp_tty[unit];
364*32633Ssam 	/* YUCK */
365*32633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
366*32633Ssam 	asp->ap_xon = tp->t_startc;
367*32633Ssam 	asp->ap_xoff = tp->t_stopc;
368*32633Ssam 	asp->ap_xena =
369*32633Ssam 	    (tp->t_flags & (RAW|TANDEM)) == TANDEM ? MPA_ENA : MPA_DIS;
370*32633Ssam 	asp->ap_xany = (tp->t_flags & DECCTQ ? MPA_DIS : MPA_ENA);
371*32633Ssam #ifdef notnow
372*32633Ssam 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {
373*32633Ssam #endif
374*32633Ssam 		asp->ap_data = MPCHAR_8;
375*32633Ssam 		asp->ap_parity = MPPAR_NONE;
376*32633Ssam #ifdef notnow
377*32633Ssam 	} else {
378*32633Ssam 		asp->ap_data = MPCHAR_7;
379*32633Ssam 		if ((tp->t_flags & (EVENP|ODDP)) == ODDP)
380*32633Ssam 			asp->ap_parity = MPPAR_ODD;
381*32633Ssam 		else
382*32633Ssam 			asp->ap_parity = MPPAR_EVEN;
383*32633Ssam 	}
384*32633Ssam #endif
385*32633Ssam 	if (tp->t_ospeed == B110)
386*32633Ssam 		asp->ap_stop = MPSTOP_2;
387*32633Ssam 	else
388*32633Ssam 		asp->ap_stop = MPSTOP_1;
389*32633Ssam 	if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB)
390*32633Ssam 		asp->ap_baud = M19200;
391*32633Ssam 	else
392*32633Ssam 		asp->ap_baud = tp->t_ospeed;
393*32633Ssam 	asp->ap_loop = MPA_DIS;		/* disable loopback */
394*32633Ssam 	asp->ap_rtimer = A_RCVTIM;	/* default receive timer */
395*32633Ssam 	if (ms->ms_softCAR & (1<<port))
396*32633Ssam 		setm(&asp->ap_modem, A_DTR, ASSERT);
397*32633Ssam 	else
398*32633Ssam 		setm(&asp->ap_modem, A_DTR, AUTO);
399*32633Ssam 	seti(&asp->ap_intena, A_DCD);
400*32633Ssam 	return (ev);
401*32633Ssam }
402*32633Ssam 
403*32633Ssam mpstart(tp)
404*32633Ssam 	register struct tty *tp;
405*32633Ssam {
406*32633Ssam 	register struct mpevent *ev;
407*32633Ssam 	register struct mpport *mp;
408*32633Ssam 	struct mblok *mb;
409*32633Ssam 	struct mpsoftc *ms;
410*32633Ssam 	int port, unit, xcnt, n, s, i;
411*32633Ssam 	struct	hxmtl *hxp;
412*32633Ssam 	struct clist outq;
413*32633Ssam 
414*32633Ssam 	s = spl8();
415*32633Ssam 	unit = minor(tp->t_dev);
416*32633Ssam 	ms = &mp_softc[MPUNIT(unit)];
417*32633Ssam 	mb = ms->ms_mb;
418*32633Ssam 	port = MPPORT(unit);
419*32633Ssam 	mp = &mb->mb_port[port];
420*32633Ssam 	hxp = &ms->ms_hxl[port];
421*32633Ssam 	xcnt = 0;
422*32633Ssam 	outq = tp->t_outq;
423*32633Ssam 	for (i = 0; i < MPXMIT; i++) {
424*32633Ssam 		if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP))
425*32633Ssam 			break;
426*32633Ssam 		if (outq.c_cc <= TTLOWAT(tp)) {
427*32633Ssam 			if (tp->t_state & TS_ASLEEP) {
428*32633Ssam 				tp->t_state &= ~TS_ASLEEP;
429*32633Ssam 				wakeup((caddr_t)&tp->t_outq);
430*32633Ssam 			}
431*32633Ssam 			if (tp->t_wsel) {
432*32633Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
433*32633Ssam 				tp->t_wsel = 0;
434*32633Ssam 				tp->t_state &= ~TS_WCOLL;
435*32633Ssam 			}
436*32633Ssam 		}
437*32633Ssam 		if (outq.c_cc == 0)
438*32633Ssam 			break;
439*32633Ssam 		/*
440*32633Ssam 		 * If we're not currently busy outputting,
441*32633Ssam 		 * and there is data to be output, set up
442*32633Ssam 		 * port transmit structure to send to mpcc.
443*32633Ssam 		 */
444*32633Ssam 		if (tp->t_flags & (RAW|LITOUT))
445*32633Ssam 			n = ndqb(&outq, 0);
446*32633Ssam 		else {
447*32633Ssam 			n = ndqb(&outq, 0200);
448*32633Ssam 			if (n == 0) {
449*32633Ssam 				n = getc(&outq);
450*32633Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
451*32633Ssam 				tp->t_state |= TS_TIMEOUT;
452*32633Ssam 				break;
453*32633Ssam 			}
454*32633Ssam 		}
455*32633Ssam 		hxp->dblock[i] = (caddr_t)vtoph(0, (int)outq.c_cf);
456*32633Ssam 		hxp->size[i] = n;
457*32633Ssam 		xcnt++;		/* count of xmts to send */
458*32633Ssam 		ndadvance(&outq, n);
459*32633Ssam 	}
460*32633Ssam 	/*
461*32633Ssam 	 * If data to send, poke mpcc.
462*32633Ssam 	 */
463*32633Ssam 	if (xcnt) {
464*32633Ssam 		ev = mp_getevent(mp, unit);
465*32633Ssam 		if (ev == 0) {
466*32633Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
467*32633Ssam 		} else {
468*32633Ssam 			tp->t_state |= TS_BUSY;
469*32633Ssam 			ev->ev_count = xcnt;
470*32633Ssam 			mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit));
471*32633Ssam 		}
472*32633Ssam 	}
473*32633Ssam 	splx(s);
474*32633Ssam }
475*32633Ssam 
476*32633Ssam /*
477*32633Ssam  * Advance cc bytes from q  but don't free memory.
478*32633Ssam  */
479*32633Ssam ndadvance(q, cc)
480*32633Ssam 	register struct clist *q;
481*32633Ssam 	register cc;
482*32633Ssam {
483*32633Ssam 	register struct cblock *bp;
484*32633Ssam 	char *end;
485*32633Ssam 	int rem, s;
486*32633Ssam 
487*32633Ssam 	s = spltty();
488*32633Ssam 	if (q->c_cc <= 0)
489*32633Ssam 		goto out;
490*32633Ssam 	while (cc>0 && q->c_cc) {
491*32633Ssam 		bp = (struct cblock *)((int)q->c_cf & ~CROUND);
492*32633Ssam 		if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) {
493*32633Ssam 			end = q->c_cl;
494*32633Ssam 		} else {
495*32633Ssam 			end = (char *)((int)bp + sizeof (struct cblock));
496*32633Ssam 		}
497*32633Ssam 		rem = end - q->c_cf;
498*32633Ssam 		if (cc >= rem) {
499*32633Ssam 			cc -= rem;
500*32633Ssam 			q->c_cc -= rem;
501*32633Ssam 			q->c_cf = bp->c_next->c_info;
502*32633Ssam 		} else {
503*32633Ssam 			q->c_cc -= cc;
504*32633Ssam 			q->c_cf += cc;
505*32633Ssam 			break;
506*32633Ssam 		}
507*32633Ssam 	}
508*32633Ssam 	if (q->c_cc <= 0) {
509*32633Ssam 		q->c_cf = q->c_cl = NULL;
510*32633Ssam 		q->c_cc = 0;
511*32633Ssam 	}
512*32633Ssam out:
513*32633Ssam 	splx(s);
514*32633Ssam }
515*32633Ssam 
516*32633Ssam /*
517*32633Ssam  * Stop output on a line, e.g. for ^S/^Q or output flush.
518*32633Ssam  */
519*32633Ssam mpstop(tp, rw)
520*32633Ssam 	register struct tty *tp;
521*32633Ssam 	int rw;
522*32633Ssam {
523*32633Ssam 	int s, port;
524*32633Ssam 	struct mpevent *ev;
525*32633Ssam 	struct mblok *mb;
526*32633Ssam 
527*32633Ssam 	s = spl8();
528*32633Ssam 	/* XXX: DISABLE TRANSMITTER */
529*32633Ssam 	if (tp->t_state & TS_BUSY) {
530*32633Ssam 		if ((tp->t_state & TS_TTSTOP) == 0)
531*32633Ssam 			tp->t_state |= TS_FLUSH;
532*32633Ssam 	}
533*32633Ssam 	splx(s);
534*32633Ssam }
535*32633Ssam 
536*32633Ssam /*
537*32633Ssam  * Initialize an async port's MPCC state.
538*32633Ssam  */
539*32633Ssam mpportinit(ms, mp, port)
540*32633Ssam 	register struct mpsoftc *ms;
541*32633Ssam 	register struct mpport *mp;
542*32633Ssam 	int port;
543*32633Ssam {
544*32633Ssam 	register struct mpevent *ev;
545*32633Ssam 	register int i;
546*32633Ssam 	caddr_t ptr;
547*32633Ssam 
548*32633Ssam 	mp->mp_on = mp->mp_off = 0;
549*32633Ssam 	mp->mp_nextrcv = 0;
550*32633Ssam 	mp->mp_flags = 0;
551*32633Ssam 	ev = &mp->mp_recvq[0];
552*32633Ssam 	for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) {
553*32633Ssam 		ev->ev_status = EVSTATUS_FREE;
554*32633Ssam 		ev->ev_cmd = 0;
555*32633Ssam 		ev->ev_opts = 0;
556*32633Ssam 		ev->ev_error = 0;
557*32633Ssam 		ev->ev_flags = 0;
558*32633Ssam 		ev->ev_count = 0;
559*32633Ssam 		ev->ev_un.hxl = (struct hxmtl *) vtoph(0, &ms->ms_hxl[port]);
560*32633Ssam 		ev->ev_params = (caddr_t) vtoph(0, &ms->ms_async[port][i]);
561*32633Ssam 	}
562*32633Ssam 	ev = &mp->mp_sendq[0];
563*32633Ssam 	for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) {
564*32633Ssam 		/* init so that L2 can't send any events */
565*32633Ssam 		/* to host until open has completed      */
566*32633Ssam 		ev->ev_status = EVSTATUS_FREE;
567*32633Ssam 		ev->ev_cmd = 0;
568*32633Ssam 		ev->ev_error = 0;
569*32633Ssam 		ev->ev_flags = 0;
570*32633Ssam 		ev->ev_count = 0;
571*32633Ssam 		ptr = (caddr_t) &ms->ms_cbuf[port][i][0];
572*32633Ssam 		ev->ev_un.rcvblk = (u_char *)vtoph(0, ptr);
573*32633Ssam 		ev->ev_params = (caddr_t) vtoph(0, ptr);
574*32633Ssam 	}
575*32633Ssam 	return (0);
576*32633Ssam }
577*32633Ssam 
578*32633Ssam /*
579*32633Ssam  * Send an event to an mpcc.
580*32633Ssam  */
581*32633Ssam mpcmd(ev, cmd, flags, mb, port)
582*32633Ssam 	register struct mpevent *ev;
583*32633Ssam 	struct mblok *mb;
584*32633Ssam {
585*32633Ssam 	int s;
586*32633Ssam 
587*32633Ssam 	s = spl8();
588*32633Ssam 	/* move host values to inbound entry */
589*32633Ssam 	ev->ev_cmd = cmd;
590*32633Ssam 	ev->ev_opts = flags;
591*32633Ssam 	/* show event ready for mpcc */
592*32633Ssam 	ev->ev_status = EVSTATUS_GO;
593*32633Ssam 	mpintmpcc(mb, port);
594*32633Ssam 	splx(s);
595*32633Ssam }
596*32633Ssam 
597*32633Ssam /*
598*32633Ssam  * Return the next available event entry for the indicated port.
599*32633Ssam  */
600*32633Ssam struct mpevent *
601*32633Ssam mp_getevent(mp, unit)
602*32633Ssam 	register struct mpport *mp;
603*32633Ssam 	int unit;
604*32633Ssam {
605*32633Ssam 	register struct mpevent *ev;
606*32633Ssam 	int i, s;
607*32633Ssam 
608*32633Ssam 	s = spl8();
609*32633Ssam 	ev = &mp->mp_recvq[mp->mp_on];
610*32633Ssam 	if (ev->ev_status != EVSTATUS_FREE)
611*32633Ssam 		goto bad;
612*32633Ssam 	/*
613*32633Ssam 	 * If not a close request, verify one extra
614*32633Ssam 	 * event is available for closing the port.
615*32633Ssam 	 */
616*32633Ssam 	if ((mp->mp_flags && MP_PROGRESS) == 0) {
617*32633Ssam 		if ((i = mp->mp_on + 1) >= MPINSET)
618*32633Ssam 			i = 0;
619*32633Ssam 		if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE)
620*32633Ssam 			goto bad;
621*32633Ssam 	}
622*32633Ssam 	/* init inbound fields marking this entry as busy */
623*32633Ssam 	ev->ev_error = 0;
624*32633Ssam 	ev->ev_flags = 0;
625*32633Ssam 	ev->ev_count = 0;
626*32633Ssam 	ev->ev_status = EVSTATUS_BUSY;
627*32633Ssam 	/* adjust pointer to next available inbound entry */
628*32633Ssam 	adjptr(mp->mp_on, MPINSET);
629*32633Ssam 	splx(s);
630*32633Ssam 	return (ev);
631*32633Ssam bad:
632*32633Ssam 	splx(s);
633*32633Ssam 	log(LOG_ERR, "mp%d: port%d, out of events", MPUNIT(unit), MPPORT(unit));
634*32633Ssam 	return ((struct mpevent *)0);
635*32633Ssam }
636*32633Ssam 
637*32633Ssam mpmodem(unit, flag)
638*32633Ssam 	int unit, flag;
639*32633Ssam {
640*32633Ssam 	struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
641*32633Ssam 	int port = MPPORT(unit);
642*32633Ssam 	register struct mpport *mp;
643*32633Ssam 	register struct mpevent *ev;
644*32633Ssam 	register struct asyncparam *asp;
645*32633Ssam 
646*32633Ssam 	mp = &ms->ms_mb->mb_port[port];
647*32633Ssam 	ev = mp_getevent(mp, unit);
648*32633Ssam 	if (ev == 0)
649*32633Ssam 		return (ENOBUFS);
650*32633Ssam 	/* YUCK */
651*32633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
652*32633Ssam 	if (flag == MMOD_ON) {
653*32633Ssam 		if (ms->ms_softCAR & (1 << port))
654*32633Ssam 			setm(&asp->ap_modem, A_DTR, ASSERT);
655*32633Ssam 		else
656*32633Ssam 			setm(&asp->ap_modem, A_DTR, AUTO);
657*32633Ssam 		seti(&asp->ap_intena, A_DCD);
658*32633Ssam 	} else {
659*32633Ssam 		setm(&asp->ap_modem, 0, DROP);
660*32633Ssam 		seti(&asp->ap_intena, 0);
661*32633Ssam 	}
662*32633Ssam 	mpcmd(ev, EVCMD_IOCTL, A_MDMCHG, ms->ms_mb, port);
663*32633Ssam 	return (0);
664*32633Ssam }
665*32633Ssam 
666*32633Ssam /*
667*32633Ssam  * Set up the modem control structure according to mask.
668*32633Ssam  * Each set bit in the mask means assert the corresponding
669*32633Ssam  * modem control line, otherwise, it will be dropped.
670*32633Ssam  * RTS is special since it can either be asserted, dropped
671*32633Ssam  * or put in auto mode for auto modem control.
672*32633Ssam  */
673*32633Ssam static
674*32633Ssam setm(mc, mask, rts)
675*32633Ssam 	register struct mdmctl *mc;
676*32633Ssam 	register int mask;
677*32633Ssam {
678*32633Ssam 
679*32633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP;
680*32633Ssam 	mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP;
681*32633Ssam 	mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP;
682*32633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP;
683*32633Ssam 	mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP;
684*32633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP;
685*32633Ssam 	mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP;
686*32633Ssam 	mc->mc_rts = rts;
687*32633Ssam }
688*32633Ssam 
689*32633Ssam /*
690*32633Ssam  * Set up the status change enable field from mask.
691*32633Ssam  * When a signal is enabled in this structure and
692*32633Ssam  * and a change in state on a corresponding modem
693*32633Ssam  * control line occurs, a status change event will
694*32633Ssam  * be delivered to the host.
695*32633Ssam  */
696*32633Ssam static
697*32633Ssam seti(mc, mask)
698*32633Ssam 	register struct mdmctl *mc;
699*32633Ssam 	register int mask;
700*32633Ssam {
701*32633Ssam 
702*32633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF;
703*32633Ssam 	mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF;
704*32633Ssam 	mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF;
705*32633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF;
706*32633Ssam 	mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF;
707*32633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF;
708*32633Ssam 	mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF;
709*32633Ssam 	mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF;
710*32633Ssam }
711*32633Ssam 
712*32633Ssam mpcleanport(mb, port)
713*32633Ssam 	struct mblok *mb;
714*32633Ssam 	int port;
715*32633Ssam {
716*32633Ssam 	register struct mpport *mp;
717*32633Ssam 	register struct tty *tp;
718*32633Ssam 
719*32633Ssam 	mp = &mb->mb_port[port];
720*32633Ssam 	if (mp->mp_proto == MPPROTO_ASYNC) {
721*32633Ssam 		mp->mp_flags = MP_REMBSY;
722*32633Ssam 		/* flush I/O queues and send hangup signals */
723*32633Ssam 		tp = &mp_tty[mb->mb_unit*MPCHUNK+port];
724*32633Ssam 		tp->t_state &= ~TS_CARR_ON;
725*32633Ssam 		ttyflush(tp, FREAD|FWRITE);
726*32633Ssam 		gsignal(tp->t_pgrp, SIGHUP);
727*32633Ssam 		gsignal(tp->t_pgrp, SIGKILL);
728*32633Ssam 		mpclose(tp->t_dev, 0);
729*32633Ssam 	}
730*32633Ssam }
731*32633Ssam 
732*32633Ssam mpclean(mb, port)
733*32633Ssam 	register struct mblok *mb;
734*32633Ssam 	int port;
735*32633Ssam {
736*32633Ssam 	register struct mpport *mp;
737*32633Ssam 	register struct mpevent *ev;
738*32633Ssam 	register int i;
739*32633Ssam 	char list[2], *cp;
740*32633Ssam 	int unit;
741*32633Ssam 
742*32633Ssam 	mp = &mb->mb_port[port];
743*32633Ssam 	unit = mb->mb_unit;
744*32633Ssam 	for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) {
745*32633Ssam 		ev = &mp->mp_recvq[i];
746*32633Ssam 		ev->ev_error = ENXIO;
747*32633Ssam 		ev->ev_status = EVSTATUS_DONE;
748*32633Ssam 	}
749*32633Ssam 	list[0] = port, list[1] = MPPORT_EOL;
750*32633Ssam 	mpxintr(unit, list);
751*32633Ssam 	mprintr(unit, list);
752*32633Ssam 	/* Clear async for port */
753*32633Ssam 	mp->mp_proto = MPPROTO_UNUSED;
754*32633Ssam 	mp->mp_flags = 0;
755*32633Ssam 	mp->mp_on = 0;
756*32633Ssam 	mp->mp_off = 0;
757*32633Ssam 	mp->mp_nextrcv = 0;
758*32633Ssam 
759*32633Ssam 	mp_tty[unit*MPCHUNK + port].t_state = 0;
760*32633Ssam 	for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) {
761*32633Ssam 		ev->ev_status = EVSTATUS_FREE;
762*32633Ssam 		ev->ev_cmd = 0;
763*32633Ssam 		ev->ev_error = 0;
764*32633Ssam 		ev->ev_un.rcvblk = 0;
765*32633Ssam 		ev->ev_params = 0;
766*32633Ssam 	}
767*32633Ssam 	for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) {
768*32633Ssam 		ev->ev_status = EVSTATUS_FREE;
769*32633Ssam 		ev->ev_cmd = 0;
770*32633Ssam 		ev->ev_error = 0;
771*32633Ssam 		ev->ev_params = 0;
772*32633Ssam 	}
773*32633Ssam }
774*32633Ssam 
775*32633Ssam /*
776*32633Ssam  * MPCC interrupt handler.
777*32633Ssam  */
778*32633Ssam mpintr(mpcc)
779*32633Ssam 	int mpcc;
780*32633Ssam {
781*32633Ssam 	register struct mblok *mb;
782*32633Ssam 	register struct his *his;
783*32633Ssam 	register int i;
784*32633Ssam 
785*32633Ssam 	mb = mp_softc[mpcc].ms_mb;
786*32633Ssam 	if (mb == 0) {
787*32633Ssam 		printf("mp%d: stray interrupt\n", mpcc);
788*32633Ssam 		return;
789*32633Ssam 	}
790*32633Ssam 	his = &mb->mb_hostint;
791*32633Ssam 	his->semaphore &= ~MPSEMA_AVAILABLE;
792*32633Ssam 	/*
793*32633Ssam 	 * Check for events to be processed.
794*32633Ssam 	 */
795*32633Ssam 	if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL)
796*32633Ssam 		mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone);
797*32633Ssam 	if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL)
798*32633Ssam 		mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone);
799*32633Ssam 	if (mb->mb_harderr || mb->mb_softerr)
800*32633Ssam 		mperror(mb, mpcc);
801*32633Ssam 	his->semaphore |= MPSEMA_AVAILABLE;
802*32633Ssam }
803*32633Ssam 
804*32633Ssam /*
805*32633Ssam  * Handler for processing completion of transmitted events.
806*32633Ssam  */
807*32633Ssam mpxintr(unit, list)
808*32633Ssam 	register char *list;
809*32633Ssam {
810*32633Ssam 	register struct mpport *mp;
811*32633Ssam 	register struct mpevent *ev;
812*32633Ssam 	register struct mblok *mb;
813*32633Ssam 	register struct tty *tp;
814*32633Ssam 	register struct asyncparam *ap;
815*32633Ssam 	struct mpsoftc *ms;
816*32633Ssam 	int port, i, j;
817*32633Ssam 
818*32633Ssam 	ms = &mp_softc[unit];
819*32633Ssam 	mb = mp_softc[unit].ms_mb;
820*32633Ssam 	for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) {
821*32633Ssam 		/*
822*32633Ssam 		 * Process each completed entry in the inbound queue.
823*32633Ssam 		 */
824*32633Ssam 		mp = &mb->mb_port[port];
825*32633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
826*32633Ssam #define	nextevent(mp)	&mp->mp_recvq[mp->mp_off]
827*32633Ssam 		ev = nextevent(mp);
828*32633Ssam 		for(; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) {
829*32633Ssam 			/* YUCK */
830*32633Ssam 			ap = &ms->ms_async[port][mp->mp_off];
831*32633Ssam 			mppurge(ap, sizeof (*ap));
832*32633Ssam 			switch (ev->ev_cmd) {
833*32633Ssam 			case EVCMD_OPEN:
834*32633Ssam 				/*
835*32633Ssam 				 * Open completion, start all reads and
836*32633Ssam 				 * assert modem status information.
837*32633Ssam 				 */
838*32633Ssam 				for (i = 0; i < MPOUTSET; i++)
839*32633Ssam 					mp->mp_sendq[i].ev_status = EVSTATUS_GO;
840*32633Ssam 				(*linesw[tp->t_line].l_modem)
841*32633Ssam 				    (tp, ap->ap_modem.mc_dcd == ASSERT);
842*32633Ssam 				break;
843*32633Ssam 			case EVCMD_CLOSE:
844*32633Ssam 				/*
845*32633Ssam 				 * Close completion, flush all pending
846*32633Ssam 				 * transmissions, free resources, and
847*32633Ssam 				 * cleanup mpcc port state.
848*32633Ssam 				 */
849*32633Ssam 				for (i = 0; i < MPOUTSET; i++) {
850*32633Ssam 					mp->mp_sendq[i].ev_status =
851*32633Ssam 					    EVSTATUS_FREE;
852*32633Ssam 					mp->mp_sendq[i].ev_un.rcvblk = 0;
853*32633Ssam 					mp->mp_sendq[i].ev_params = 0;
854*32633Ssam 				}
855*32633Ssam 				tp->t_state &= ~TS_CARR_ON;
856*32633Ssam 				mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0;
857*32633Ssam 				mp->mp_flags &= ~MP_PROGRESS;
858*32633Ssam 				mp->mp_proto = MPPROTO_UNUSED;
859*32633Ssam 				wakeup((caddr_t)&tp->t_canq);	/* ??? */
860*32633Ssam 				goto done;
861*32633Ssam 			case EVCMD_IOCTL:
862*32633Ssam 				/*
863*32633Ssam 				 * Nothing to do, just pitch.
864*32633Ssam 				 */
865*32633Ssam 				break;
866*32633Ssam 			case EVCMD_WRITE:
867*32633Ssam 				/*
868*32633Ssam 				 * Transmission completed, update tty
869*32633Ssam 				 * state and restart output.
870*32633Ssam 				 */
871*32633Ssam 				tp->t_state &= ~TS_BUSY;
872*32633Ssam 				if (tp->t_state & TS_FLUSH) {
873*32633Ssam 					tp->t_state &= ~TS_FLUSH;
874*32633Ssam 					wakeup((caddr_t)&tp->t_state);
875*32633Ssam 				} else {
876*32633Ssam 					register int cc = 0, i;
877*32633Ssam 					struct hxmtl *hxp;
878*32633Ssam 
879*32633Ssam 					hxp = &ms->ms_hxl[port];
880*32633Ssam 					for(i = 0; i < ev->ev_count; i++)
881*32633Ssam 						cc += hxp->size[i];
882*32633Ssam 					ndflush(&tp->t_outq, cc);
883*32633Ssam 				}
884*32633Ssam 				switch (ev->ev_error) {
885*32633Ssam 				case A_SIZERR:  /*# error in xmt data size */
886*32633Ssam 					mplog(unit, port, A_XSIZE, 0);
887*32633Ssam 					break;
888*32633Ssam 				case A_NXBERR:  /*# no more xmt evt buffers */
889*32633Ssam 					mplog(unit, port, A_NOXBUF, 0);
890*32633Ssam 					break;
891*32633Ssam 				}
892*32633Ssam 				mpstart(tp);
893*32633Ssam 				break;
894*32633Ssam 			default:
895*32633Ssam 				mplog(unit, port, A_INVCMD, ev->ev_cmd);
896*32633Ssam 				break;
897*32633Ssam 			}
898*32633Ssam 			/* re-init all values in this entry */
899*32633Ssam 			ev->ev_cmd = 0;
900*32633Ssam 			ev->ev_opts = 0;
901*32633Ssam 			ev->ev_error = 0;
902*32633Ssam 			ev->ev_flags = 0;
903*32633Ssam 			ev->ev_count = 0;
904*32633Ssam 			/* show this entry is available for use */
905*32633Ssam 			ev->ev_status = EVSTATUS_FREE;
906*32633Ssam 			adjptr(mp->mp_off, MPINSET);
907*32633Ssam #undef	nextevent
908*32633Ssam 		}
909*32633Ssam done:
910*32633Ssam 		;
911*32633Ssam 	}
912*32633Ssam }
913*32633Ssam 
914*32633Ssam /*
915*32633Ssam  * Handler for processing received events.
916*32633Ssam  */
917*32633Ssam mprintr(unit, list)
918*32633Ssam 	char *list;
919*32633Ssam {
920*32633Ssam 	register struct tty *tp;
921*32633Ssam 	register struct mpport *mp;
922*32633Ssam 	register struct mpevent *ev;
923*32633Ssam 	struct mblok *mb;
924*32633Ssam 	register int cc;
925*32633Ssam 	register char *cp;
926*32633Ssam 	struct mpsoftc *ms;
927*32633Ssam 	caddr_t ptr;
928*32633Ssam 	char *rcverr;
929*32633Ssam 	int port, i;
930*32633Ssam 
931*32633Ssam 	ms = &mp_softc[unit];
932*32633Ssam 	mb = mp_softc[unit].ms_mb;
933*32633Ssam 	for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) {
934*32633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
935*32633Ssam 		mp = &mb->mb_port[port];
936*32633Ssam 		ev = &mp->mp_sendq[mp->mp_nextrcv];
937*32633Ssam 		while (ev->ev_status & EVSTATUS_DONE) {
938*32633Ssam 			if (ev->ev_cmd != EVCMD_READ &&
939*32633Ssam 			    ev->ev_cmd != EVCMD_STATUS) {
940*32633Ssam 				mplog(unit, port, "unexpected command",
941*32633Ssam 				    ev->ev_cmd);
942*32633Ssam 				goto next;
943*32633Ssam 			}
944*32633Ssam 			if (ev->ev_cmd == EVCMD_STATUS) {
945*32633Ssam 				/*
946*32633Ssam 				 * Status change, look for carrier changes.
947*32633Ssam 				 */
948*32633Ssam 				if (ev->ev_opts == DCDASRT ||
949*32633Ssam 				    ev->ev_opts == DCDDROP)
950*32633Ssam 					(*linesw[tp->t_line].l_modem)
951*32633Ssam 					    (tp, ev->ev_opts == DCDASRT);
952*32633Ssam 				else
953*32633Ssam 					mplog(unit, port,
954*32633Ssam 					    "unexpect status command",
955*32633Ssam 					    ev->ev_opts);
956*32633Ssam 				goto next;
957*32633Ssam 			}
958*32633Ssam 			/*
959*32633Ssam 			 * Process received data.
960*32633Ssam 			 */
961*32633Ssam 			if ((tp->t_state & (TS_ISOPEN|TS_WOPEN)) == 0)
962*32633Ssam 				goto next;
963*32633Ssam 			cc = ev->ev_count;
964*32633Ssam 			if (cc == 0)
965*32633Ssam 				goto next;
966*32633Ssam 			/* YUCK */
967*32633Ssam 			cp = ms->ms_cbuf[port][mp->mp_nextrcv];
968*32633Ssam 			mppurge(cp, CBSIZE);
969*32633Ssam 			while (cc-- > 0) {
970*32633Ssam 				/*
971*32633Ssam 				 * A null character is inserted, potentially
972*32633Ssam 				 * when a break or framing error occurs.  If
973*32633Ssam 				 * we're not in raw mode, substitute the
974*32633Ssam 				 * interrupt character.
975*32633Ssam 				 */
976*32633Ssam 				if (*cp == 0 &&
977*32633Ssam 				    (ev->ev_error == BRKASRT ||
978*32633Ssam 				     ev->ev_error == FRAMERR))
979*32633Ssam 					if ((tp->t_flags&RAW) == 0)
980*32633Ssam 						*cp = tp->t_intrc;
981*32633Ssam 				(*linesw[tp->t_line].l_rint)(*cp++, tp);
982*32633Ssam 			}
983*32633Ssam 			/* setup for next read */
984*32633Ssam 			ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0];
985*32633Ssam 			ev->ev_un.rcvblk = (u_char *)vtoph(0, ptr);
986*32633Ssam 			ev->ev_params = (caddr_t) vtoph(0, ptr);
987*32633Ssam                         switch(ev->ev_error) {
988*32633Ssam                         case RCVDTA:    /* Normal (good) rcv data */
989*32633Ssam                                 rcverr = (char *)0;
990*32633Ssam 				break;
991*32633Ssam 			case PARERR:    /* parity error */
992*32633Ssam 				rcverr = "parity error";
993*32633Ssam 				break;
994*32633Ssam 			case FRAMERR:   /* frame error */
995*32633Ssam 				rcverr = "frame error";
996*32633Ssam 				break;
997*32633Ssam 			case OVRNERR:   /* Overrun error */
998*32633Ssam 				rcverr = "overrun error";
999*32633Ssam 				break;
1000*32633Ssam 			case OVFERR:    /* Overflow error */
1001*32633Ssam 				rcverr = "overflow error";
1002*32633Ssam 				break;
1003*32633Ssam 			default:
1004*32633Ssam 				rcverr = "undefined rcv error";
1005*32633Ssam 			}
1006*32633Ssam 			if (rcverr != (char *)0)
1007*32633Ssam 				mplog(unit, port, rcverr, ev->ev_error);
1008*32633Ssam 		next:
1009*32633Ssam 			ev->ev_cmd = 0;
1010*32633Ssam 			ev->ev_opts = 0;
1011*32633Ssam 			ev->ev_error = 0;
1012*32633Ssam 			ev->ev_flags = 0;
1013*32633Ssam 			ev->ev_status = EVSTATUS_GO;	/* start next read */
1014*32633Ssam 			adjptr(mp->mp_nextrcv, MPOUTSET);
1015*32633Ssam 			ev = &mp->mp_sendq[mp->mp_nextrcv];
1016*32633Ssam 		}
1017*32633Ssam 	}
1018*32633Ssam }
1019*32633Ssam 
1020*32633Ssam /*
1021*32633Ssam  * Log an mpcc diagnostic.
1022*32633Ssam  */
1023*32633Ssam mplog(unit, port, cp, flags)
1024*32633Ssam 	char *cp;
1025*32633Ssam {
1026*32633Ssam 
1027*32633Ssam 	if (flags)
1028*32633Ssam 		log(LOG_ERR, "mp%d: port%d, %s (%d)\n",
1029*32633Ssam 		    unit, port, cp, flags);
1030*32633Ssam 	else
1031*32633Ssam 		log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp);
1032*32633Ssam }
1033*32633Ssam 
1034*32633Ssam int	MPHOSTINT = 1;
1035*32633Ssam 
1036*32633Ssam mptimeint(mb)
1037*32633Ssam 	register struct mblok *mb;
1038*32633Ssam {
1039*32633Ssam 
1040*32633Ssam         mb->mb_mpintcnt = 0;
1041*32633Ssam         mb->mb_mpintclk = (caddr_t)0;
1042*32633Ssam 	*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
1043*32633Ssam }
1044*32633Ssam 
1045*32633Ssam /*
1046*32633Ssam  * Interupt mpcc
1047*32633Ssam  */
1048*32633Ssam mpintmpcc(mb, port)
1049*32633Ssam 	register struct mblok *mb;
1050*32633Ssam 	u_short port;
1051*32633Ssam {
1052*32633Ssam 
1053*32633Ssam         mb->mb_intr[port] |= MPSEMA_WORK;
1054*32633Ssam         if (++mb->mb_mpintcnt == MPHOSTINT) {
1055*32633Ssam                 mb->mb_mpintcnt = 0;
1056*32633Ssam 		*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
1057*32633Ssam                 if (mb->mb_mpintclk) {
1058*32633Ssam                         untimeout(mptimeint, mb);
1059*32633Ssam                         mb->mb_mpintclk = 0;
1060*32633Ssam                 }
1061*32633Ssam         } else {
1062*32633Ssam                 if (mb->mb_mpintclk == 0) {
1063*32633Ssam                         timeout(mptimeint, mb, 4);
1064*32633Ssam                         mb->mb_mpintclk = (caddr_t)1;
1065*32633Ssam                 }
1066*32633Ssam         }
1067*32633Ssam }
1068*32633Ssam 
1069*32633Ssam static char *mpherrmsg[] = {
1070*32633Ssam 	"",
1071*32633Ssam 	"Bus error",				/* MPBUSERR */
1072*32633Ssam 	"Address error",			/* ADDRERR */
1073*32633Ssam 	"Undefined ecc interrupt",		/* UNDECC */
1074*32633Ssam 	"Undefined interrupt",			/* UNDINT */
1075*32633Ssam 	"Power failure occurred",		/* PWRFL */
1076*32633Ssam 	"Stray transmit done interrupt",	/* NOXENTRY */
1077*32633Ssam 	"Two fast timers on one port",		/* TWOFTMRS */
1078*32633Ssam 	"Interrupt queue full",			/* INTQFULL */
1079*32633Ssam 	"Interrupt queue ack error",		/* INTQERR */
1080*32633Ssam 	"Uncorrectable dma parity error",	/* CBPERR */
1081*32633Ssam 	"32 port ACAP failed power up",		/* ACPDEAD */
1082*32633Ssam };
1083*32633Ssam #define	NHERRS	(sizeof (mpherrmsg) / sizeof (mpherrmsg[0]))
1084*32633Ssam 
1085*32633Ssam mperror(mb, unit)
1086*32633Ssam 	register struct mblok *mb;
1087*32633Ssam 	int unit;
1088*32633Ssam {
1089*32633Ssam 	register char *cp;
1090*32633Ssam 	register int i;
1091*32633Ssam 
1092*32633Ssam 	if (mb->mb_softerr) {
1093*32633Ssam 		switch (mb->mb_softerr) {
1094*32633Ssam 		case DMAPERR:   /* dma parity error */
1095*32633Ssam 			cp = "dma parity error";
1096*32633Ssam 			break;
1097*32633Ssam 		case ECCERR:
1098*32633Ssam 			cp = "local memory ecc error";
1099*32633Ssam 			break;
1100*32633Ssam 		default:
1101*32633Ssam 			cp = "unknown error";
1102*32633Ssam 			break;
1103*32633Ssam 		}
1104*32633Ssam 		log(LOG_ERR, "mp%d: soft error, %s", unit, cp);
1105*32633Ssam 		mb->mb_softerr = 0;
1106*32633Ssam 	}
1107*32633Ssam 	if (mb->mb_harderr) {
1108*32633Ssam 		if (mb->mb_harderr < NHERRS)
1109*32633Ssam 			cp = mpherrmsg[mb->mb_harderr];
1110*32633Ssam 		else
1111*32633Ssam 			cp = "unknown error";
1112*32633Ssam 		log(LOG_ERR, "mp%d: hard error, %s", unit, cp);
1113*32633Ssam 		if (mb->mb_status == MP_OPOPEN) {
1114*32633Ssam 			for (i = 0; i < MPMAXPORT; i++) {
1115*32633Ssam 				mpcleanport(mb, i);
1116*32633Ssam 				mb->mb_proto[i] = MPPROTO_UNUSED;
1117*32633Ssam 			}
1118*32633Ssam 		}
1119*32633Ssam 		mb->mb_harderr = 0;
1120*32633Ssam 		mb->mb_status = 0;
1121*32633Ssam 	}
1122*32633Ssam }
1123*32633Ssam 
1124*32633Ssam mppurge(addr, cc)
1125*32633Ssam 	register caddr_t addr;
1126*32633Ssam 	register int cc;
1127*32633Ssam {
1128*32633Ssam 
1129*32633Ssam 	for (; cc >= 0; addr += NBPG, cc -= NBPG)
1130*32633Ssam 		mtpr(P1DC, addr);
1131*32633Ssam }
1132*32633Ssam 
1133*32633Ssam /*
1134*32633Ssam  * MPCC Download Pseudo-device.
1135*32633Ssam  */
1136*32633Ssam char	mpdlbuf[MPDLBUFSIZE];
1137*32633Ssam int	mpdlbusy;		/* interlock on download buffer */
1138*32633Ssam int	mpdlerr;
1139*32633Ssam 
1140*32633Ssam mpdlopen(dev)
1141*32633Ssam 	dev_t dev;
1142*32633Ssam {
1143*32633Ssam 	int unit, mpu;
1144*32633Ssam 	struct vba_device *vi;
1145*32633Ssam 
1146*32633Ssam 	unit = minor(dev);
1147*32633Ssam 	mpu = MPUNIT(unit);
1148*32633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
1149*32633Ssam 		return (ENODEV);
1150*32633Ssam 	return (0);
1151*32633Ssam }
1152*32633Ssam 
1153*32633Ssam mpdlwrite(dev, uio)
1154*32633Ssam 	dev_t dev;
1155*32633Ssam 	struct uio *uio;
1156*32633Ssam {
1157*32633Ssam 	register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))];
1158*32633Ssam 	register struct mpdl *dl;
1159*32633Ssam 	int error;
1160*32633Ssam 
1161*32633Ssam 	if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN)
1162*32633Ssam 		return (EFAULT);
1163*32633Ssam 	dl = &ms->ms_mb->mb_dl;
1164*32633Ssam 	dl->mpdl_count = uio->uio_iov->iov_len;
1165*32633Ssam 	dl->mpdl_data = (caddr_t) vtoph((struct proc *)0, mpdlbuf);
1166*32633Ssam 	if (error = uiomove(mpdlbuf, dl->mpdl_count, UIO_WRITE, uio))
1167*32633Ssam 		return (error);
1168*32633Ssam 	uio->uio_resid -= dl->mpdl_count;    /* set up return from write */
1169*32633Ssam 	dl->mpdl_cmd = MPDLCMD_NORMAL;
1170*32633Ssam 	error = mpdlwait(dl);
1171*32633Ssam 	return (error);
1172*32633Ssam }
1173*32633Ssam 
1174*32633Ssam mpdlclose(dev)
1175*32633Ssam 	dev_t dev;
1176*32633Ssam {
1177*32633Ssam 	register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb;
1178*32633Ssam 	int ret = 0;
1179*32633Ssam 
1180*32633Ssam 	if (mb == 0 || mb->mb_status != MP_DLDONE) {
1181*32633Ssam 		mpbogus.status = 0;
1182*32633Ssam 		if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))])
1183*32633Ssam 			mpdlbusy--;
1184*32633Ssam 		return (EEXIST);
1185*32633Ssam 	}
1186*32633Ssam 	mb->mb_status = MP_OPOPEN;
1187*32633Ssam 	mpbogus.status = 0;
1188*32633Ssam 	/* set to dead, for board handshake */
1189*32633Ssam 	mb->mb_hostint.imok = MPIMOK_DEAD;
1190*32633Ssam 	return (0);
1191*32633Ssam }
1192*32633Ssam 
1193*32633Ssam int	mpdltimeout();
1194*32633Ssam 
1195*32633Ssam mpdlioctl(dev, cmd, data, flag)
1196*32633Ssam 	dev_t dev;
1197*32633Ssam 	caddr_t data;
1198*32633Ssam {
1199*32633Ssam 	register struct mblok *mb;
1200*32633Ssam 	register struct mpdl *dl;
1201*32633Ssam 	int unit, error, s, i, j;
1202*32633Ssam 
1203*32633Ssam 	mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb;
1204*32633Ssam 	if (mb == 0)
1205*32633Ssam 		return (EEXIST);
1206*32633Ssam 	dl = &mb->mb_dl;
1207*32633Ssam 	error = 0;
1208*32633Ssam 	switch (cmd) {
1209*32633Ssam 	case MPIOPORTMAP:
1210*32633Ssam 		bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto));
1211*32633Ssam 		break;
1212*32633Ssam 	case MPIOHILO:
1213*32633Ssam 		bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport)));
1214*32633Ssam 		break;
1215*32633Ssam 	case MPIOENDDL:
1216*32633Ssam 		dl->mpdl_count = 0;
1217*32633Ssam 		dl->mpdl_data = 0;
1218*32633Ssam 		dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK;
1219*32633Ssam 		error = mpdlwait(dl);
1220*32633Ssam 		mpccinit(unit);
1221*32633Ssam 		mb->mb_status = MP_DLDONE;
1222*32633Ssam 		mpdlbusy--;
1223*32633Ssam 		break;
1224*32633Ssam 	case MPIOENDCODE:
1225*32633Ssam 		dl->mpdl_count = 0;
1226*32633Ssam 		dl->mpdl_data = 0;
1227*32633Ssam 		dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK;
1228*32633Ssam 		error = mpdlwait(dl);
1229*32633Ssam 		break;
1230*32633Ssam 	case MPIOASYNCNF:
1231*32633Ssam 		bcopy(data, mpdlbuf, sizeof (struct abdcf));
1232*32633Ssam 		dl->mpdl_data = (caddr_t) vtoph((struct proc *)0, mpdlbuf);
1233*32633Ssam 		dl->mpdl_count = sizeof (struct abdcf);
1234*32633Ssam 		dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK;
1235*32633Ssam 		error = mpdlwait(dl);
1236*32633Ssam 		break;
1237*32633Ssam 	case MPIOSTARTDL:
1238*32633Ssam 		while (mpdlbusy)
1239*32633Ssam 			sleep((caddr_t)&mpdlbusy, PZERO+1);
1240*32633Ssam 		mpdlbusy++;
1241*32633Ssam 		/* initialize the downloading interface */
1242*32633Ssam 		mpbogus.magic = MPMAGIC;
1243*32633Ssam 		mpbogus.mb = mpbogus.mbloks[unit];
1244*32633Ssam 		mpbogus.status = 1;
1245*32633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
1246*32633Ssam 		dl->mpdl_count = 0;
1247*32633Ssam 		dl->mpdl_cmd = 0;
1248*32633Ssam 		dl->mpdl_data = (char *) 0;
1249*32633Ssam 		mpdlerr = 0;
1250*32633Ssam 		mb->mb_magic = MPMAGIC;
1251*32633Ssam         	mb->mb_ivec = mp_softc[unit].ms_ivec+1;	/* download vector */
1252*32633Ssam 		mb->mb_status = MP_DLPEND;
1253*32633Ssam 		mb->mb_diagswitch[0] = 'A';
1254*32633Ssam 		mb->mb_diagswitch[1] = 'P';
1255*32633Ssam 		s = spl8();
1256*32633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 2;
1257*32633Ssam 		timeout(mpdltimeout, mb, 30*hz);	/* approx 15 seconds */
1258*32633Ssam 		sleep((caddr_t)&mb->mb_status, PZERO+1);
1259*32633Ssam 		splx(s);
1260*32633Ssam 		if (mb->mb_status == MP_DLOPEN) {
1261*32633Ssam 			untimeout(mpdltimeout, mb);
1262*32633Ssam 		} else if (mb->mb_status == MP_DLTIME) {
1263*32633Ssam 			mpbogus.status = 0;
1264*32633Ssam 			error = ETIMEDOUT;
1265*32633Ssam 		} else {
1266*32633Ssam 			mpbogus.status = 0;
1267*32633Ssam 			error = ENXIO;
1268*32633Ssam 			log(LOG_ERR, "mp%d: start download: unknown status %x",
1269*32633Ssam 			    unit, mb->mb_status);
1270*32633Ssam 		}
1271*32633Ssam 		bzero(mb->mb_port, sizeof (mb->mb_port));
1272*32633Ssam 		break;
1273*32633Ssam 	case MPIORESETBOARD:
1274*32633Ssam 		s = spl8();
1275*32633Ssam 		if (mb->mb_imokclk)
1276*32633Ssam 			mb->mb_imokclk = 0;
1277*32633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 0x100;
1278*32633Ssam 		if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) {
1279*32633Ssam 			mpdlerr = MP_DLERROR;
1280*32633Ssam 			dl->mpdl_status = EVSTATUS_FREE;
1281*32633Ssam 			wakeup((caddr_t)&dl->mpdl_status);
1282*32633Ssam 			mpbogus.status = 0;
1283*32633Ssam 		}
1284*32633Ssam 		for (i = 0; i < MPMAXPORT; i++) {
1285*32633Ssam 			if (mb->mb_harderr || mb->mb_softerr)
1286*32633Ssam 				mperror(mb, i);
1287*32633Ssam 			mpcleanport(mb, i);
1288*32633Ssam 			mb->mb_proto[i] = MPPROTO_UNUSED;
1289*32633Ssam 		}
1290*32633Ssam 		mb->mb_status = 0;
1291*32633Ssam 		splx(s);
1292*32633Ssam 		break;
1293*32633Ssam 	default:
1294*32633Ssam 		error = EINVAL;
1295*32633Ssam 		break;
1296*32633Ssam 	}
1297*32633Ssam 	return (error);
1298*32633Ssam }
1299*32633Ssam 
1300*32633Ssam mpccinit(unit)
1301*32633Ssam 	int unit;
1302*32633Ssam {
1303*32633Ssam         register struct mblok *mb = mp_softc[unit].ms_mb;
1304*32633Ssam         register struct his *his;
1305*32633Ssam         register int i, j;
1306*32633Ssam 
1307*32633Ssam         mb->mb_status = MP_DLDONE;
1308*32633Ssam         mb->mb_ivec = mp_softc[unit].ms_ivec;
1309*32633Ssam         mb->mb_magic = MPMAGIC;
1310*32633Ssam         /* Init host interface structure */
1311*32633Ssam         his = &mb->mb_hostint;
1312*32633Ssam         his->semaphore = MPSEMA_AVAILABLE;
1313*32633Ssam         for (i = 0; i < NMPPROTO; i++)
1314*32633Ssam                 for (j = 0; j < MPMAXPORT; j++) {
1315*32633Ssam                         his->proto[i].inbdone[j] = MPPORT_EOL;
1316*32633Ssam                         his->proto[i].outbdone[j] = MPPORT_EOL;
1317*32633Ssam                 }
1318*32633Ssam         mb->mb_unit = unit;
1319*32633Ssam }
1320*32633Ssam 
1321*32633Ssam mpdlintr(mpcc)
1322*32633Ssam 	int mpcc;
1323*32633Ssam {
1324*32633Ssam 	register struct mblok *mb;
1325*32633Ssam 	register struct mpdl *dl;
1326*32633Ssam 
1327*32633Ssam 	mb = mp_softc[mpcc].ms_mb;
1328*32633Ssam 	if (mb == 0) {
1329*32633Ssam 		printf("mp%d: stray download interrupt\n", mpcc);
1330*32633Ssam 		return;
1331*32633Ssam 	}
1332*32633Ssam 	dl = &mb->mb_dl;
1333*32633Ssam 	switch (mb->mb_status) {
1334*32633Ssam 	case MP_DLOPEN:
1335*32633Ssam 		if (dl->mpdl_status != EVSTATUS_DONE)
1336*32633Ssam 			mpdlerr = MP_DLERROR;
1337*32633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
1338*32633Ssam 		wakeup((caddr_t)&dl->mpdl_status);
1339*32633Ssam 		return;
1340*32633Ssam 	case MP_DLPEND:
1341*32633Ssam 		mb->mb_status = MP_DLOPEN;
1342*32633Ssam 		wakeup(&mb->mb_status);
1343*32633Ssam 		/* fall thru... */
1344*32633Ssam 	case MP_DLTIME:
1345*32633Ssam 		return;
1346*32633Ssam 	case MP_OPOPEN:
1347*32633Ssam 		if (mb->mb_imokclk)
1348*32633Ssam 			mb->mb_imokclk = 0;
1349*32633Ssam 		mb->mb_nointcnt = 0;		/* reset no interrupt count */
1350*32633Ssam 		mb->mb_hostint.imok = MPIMOK_DEAD;
1351*32633Ssam 		mb->mb_imokclk = (caddr_t)1;
1352*32633Ssam 		break;
1353*32633Ssam 	default:
1354*32633Ssam 		log(LOG_ERR, "mp%d: mpdlintr, status %x\n",
1355*32633Ssam 		    mpcc, mb->mb_status);
1356*32633Ssam 		break;
1357*32633Ssam 	}
1358*32633Ssam }
1359*32633Ssam 
1360*32633Ssam mpdltimeout(mp)
1361*32633Ssam 	struct mblok *mp;
1362*32633Ssam {
1363*32633Ssam 
1364*32633Ssam 	mp->mb_status = MP_DLTIME;
1365*32633Ssam 	wakeup((caddr_t)&mp->mb_status);
1366*32633Ssam }
1367*32633Ssam 
1368*32633Ssam /*
1369*32633Ssam  * Wait for a transfer to complete or a timeout to occur.
1370*32633Ssam  */
1371*32633Ssam mpdlwait(dl)
1372*32633Ssam 	register struct mpdl *dl;
1373*32633Ssam {
1374*32633Ssam 	int s, error = 0;
1375*32633Ssam 
1376*32633Ssam 	s = spl8();
1377*32633Ssam 	dl->mpdl_status = EVSTATUS_GO;
1378*32633Ssam 	while (dl->mpdl_status != EVSTATUS_FREE) {
1379*32633Ssam 		sleep((caddr_t)&dl->mpdl_status, PZERO+1);
1380*32633Ssam 		if (mpdlerr == MP_DLERROR)
1381*32633Ssam 			error = EIO;
1382*32633Ssam 	}
1383*32633Ssam 	splx(s);
1384*32633Ssam 	return (error);
1385*32633Ssam }
1386*32633Ssam #endif
1387