xref: /csrg-svn/sys/tahoe/vba/mp.c (revision 40734)
134506Skarels /*
234506Skarels  * Copyright (c) 1988 Regents of the University of California.
334506Skarels  * All rights reserved.
434506Skarels  *
535055Skarels  * This code is derived from software contributed to Berkeley by
635055Skarels  * Computer Consoles Inc.
735055Skarels  *
834506Skarels  * Redistribution and use in source and binary forms are permitted
934866Sbostic  * provided that the above copyright notice and this paragraph are
1034866Sbostic  * duplicated in all such forms and that any documentation,
1134866Sbostic  * advertising materials, and other materials related to such
1234866Sbostic  * distribution and use acknowledge that the software was developed
1334866Sbostic  * by the University of California, Berkeley.  The name of the
1434866Sbostic  * University may not be used to endorse or promote products derived
1534866Sbostic  * from this software without specific prior written permission.
1634866Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
1734866Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
1834866Sbostic  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
1934506Skarels  *
20*40734Skarels  *	@(#)mp.c	7.11 (Berkeley) 04/03/90
2134506Skarels  */
2232633Ssam 
2332633Ssam #include "mp.h"
2432633Ssam #if NMP > 0
2532633Ssam /*
2632633Ssam  * Multi Protocol Communications Controller (MPCC).
2732633Ssam  * Asynchronous Terminal Protocol Support.
2832633Ssam  */
2932633Ssam #include "param.h"
3032633Ssam #include "ioctl.h"
3132633Ssam #include "tty.h"
3232633Ssam #include "user.h"
3332633Ssam #include "map.h"
3432633Ssam #include "buf.h"
3532633Ssam #include "conf.h"
3632633Ssam #include "file.h"
3732633Ssam #include "errno.h"
3832633Ssam #include "syslog.h"
3932633Ssam #include "vmmac.h"
4032633Ssam #include "kernel.h"
4132633Ssam #include "clist.h"
4232633Ssam 
4337507Smckusick #include "machine/pte.h"
4437507Smckusick #include "machine/mtpr.h"
4534506Skarels 
4632633Ssam #include "../tahoevba/vbavar.h"
4732633Ssam #include "../tahoevba/mpreg.h"
4832633Ssam 
4932633Ssam #define	MPCHUNK	16
5032633Ssam #define	MPPORT(n)	((n) & 0xf)
5132633Ssam #define	MPUNIT(n)	((n) >> 4)
5232633Ssam 
5332633Ssam /*
5432633Ssam  * Driver information for auto-configuration stuff.
5532633Ssam  */
5632633Ssam int     mpprobe(), mpattach(), mpintr();
5732633Ssam struct  vba_device *mpinfo[NMP];
5832633Ssam long    mpstd[] = { 0 };
5932633Ssam struct  vba_driver mpdriver =
6032633Ssam     { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo };
6132633Ssam 
6232633Ssam int	mpstart();
6337607Smarc int	mpparam();
6437607Smarc struct	mpevent *mpparam2();
6532633Ssam struct	mpevent *mp_getevent();
6632633Ssam 
6732633Ssam /*
6832633Ssam  * The following structure is needed to deal with mpcc's convoluted
6932633Ssam  * method for locating it's mblok structures (hold your stomach).
7032633Ssam  * When an mpcc is reset at boot time it searches host memory
7132633Ssam  * looking for a string that says ``ThIs Is MpCc''.  The mpcc
7232633Ssam  * then reads the structure to locate the pointer to it's mblok
7332633Ssam  * structure (you can wretch now).
7432633Ssam  */
7532633Ssam struct mpbogus {
7632633Ssam 	char	s[12];			/* `ThIs Is MpCc'' */
7732633Ssam 	u_char	status;
7832633Ssam 	u_char	unused;
7932633Ssam 	u_short	magic;
8032633Ssam 	struct	mblok *mb;
8132633Ssam 	struct	mblok *mbloks[NMP];	/* can support at most 16 mpcc's */
8232633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' };
8332633Ssam 
8432633Ssam /*
8532633Ssam  * Software state per unit.
8632633Ssam  */
8732633Ssam struct	mpsoftc {
8832633Ssam 	u_int	ms_ivec;		/* interrupt vector */
8932633Ssam 	u_int	ms_softCAR;		/* software carrier for async */
9032633Ssam 	struct	mblok *ms_mb;		/* mpcc status area */
9132633Ssam 	struct	vb_buf ms_buf;		/* vba resources for ms_mb */
9232633Ssam 	struct	hxmtl ms_hxl[MPMAXPORT];/* host transmit list */
9332633Ssam 	struct	asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */
9432633Ssam 	char	ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */
9532633Ssam } mp_softc[NMP];
9632633Ssam 
9737607Smarc struct	speedtab
9837607Smarc mpspeedtab[] = {
9937607Smarc 	9600,	M9600,	  /* baud rate = 9600 */
10037607Smarc 	4800,	M4800,	  /* baud rate = 4800 */
10137607Smarc 	2400,	M2400,	  /* baud rate = 2400 */
10237607Smarc 	1800,	M1800,	  /* baud rate = 1800 */
10337607Smarc 	1200,	M1200,	  /* baud rate = 1200 */
10437607Smarc 	600,	M600,	  /* baud rate = 600 */
10537607Smarc 	300,	M300,	  /* baud rate = 300 */
10637607Smarc 	200,	M200,	  /* baud rate = 200 */
10737607Smarc 	150,	M150,	  /* baud rate = 150 */
10837607Smarc 	134,	M134_5,	  /* baud rate = 134.5 */
10937607Smarc 	110,	M110,	  /* baud rate = 110 */
11037607Smarc 	75,	M75,	  /* baud rate = 75 */
11137607Smarc 	50,	M50,	  /* baud rate = 50 */
11237607Smarc 	0,	M0,	  /* baud rate = 0 */
11337607Smarc 	2000,	M2000,	  /* baud rate = 2000 */
11437607Smarc 	3600,	M3600,	  /* baud rate = 3600 */
11537607Smarc 	7200,	M7200,	  /* baud rate = 7200 */
11637607Smarc 	19200,	M19200,	  /* baud rate = 19,200 */
11737607Smarc 	24000,	M24000,	  /* baud rate = 24,000 */
11837607Smarc 	28400,	M28400,	  /* baud rate = 28,400 */
11937607Smarc 	37800,	M37800,	  /* baud rate = 37,800 */
12037607Smarc 	40300,	M40300,	  /* baud rate = 40,300 */
12137607Smarc 	48000,	M48000,	  /* baud rate = 48,000 */
12237607Smarc 	52000,	M52000,	  /* baud rate = 52,000 */
12337607Smarc 	56800,	M56800,	  /* baud rate = 56,800 */
12437607Smarc 	EXTA,	MEXTA,	  /* baud rate = Ext A */
12537607Smarc 	EXTB,	MEXTB,	  /* baud rate = Ext B */
12637607Smarc 	-1,	-1,
12737607Smarc };
12837607Smarc 
12932633Ssam struct	tty mp_tty[NMP*MPCHUNK];
13032633Ssam #ifndef lint
13132633Ssam int	nmp = NMP*MPCHUNK;
13232633Ssam #endif
13332633Ssam 
13432633Ssam int	ttrstrt();
13532633Ssam 
13632633Ssam mpprobe(reg, vi)
13732633Ssam 	caddr_t reg;
13832633Ssam 	struct vba_device *vi;
13932633Ssam {
14032633Ssam 	register int br, cvec;
14132633Ssam 	register struct mpsoftc *ms;
14232633Ssam 
14332633Ssam #ifdef lint
14432633Ssam 	br = 0; cvec = br; br = cvec;
14532633Ssam 	mpintr(0);
14634506Skarels 	mpdlintr(0);
14732633Ssam #endif
14832633Ssam 	if (badaddr(reg, 2))
14932633Ssam 		return (0);
15032633Ssam 	ms = &mp_softc[vi->ui_unit];
15132633Ssam 	/*
15232633Ssam 	 * Allocate page tables and mblok
15332633Ssam 	 * structure (mblok in non-cached memory).
15432633Ssam 	 */
15532633Ssam 	if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) {
15632633Ssam 		printf("mp%d: vbainit failed\n", vi->ui_unit);
15732633Ssam 		return (0);
15832633Ssam 	}
15932633Ssam 	ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf;
16032633Ssam 	ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit;	/* XXX */
16132633Ssam 	br = 0x14, cvec = ms->ms_ivec;			/* XXX */
16234287Skarels 	return (sizeof (*reg));
16332633Ssam }
16432633Ssam 
16532633Ssam mpattach(vi)
16632633Ssam 	register struct vba_device *vi;
16732633Ssam {
16832633Ssam 	register struct mpsoftc *ms = &mp_softc[vi->ui_unit];
16932633Ssam 
17032633Ssam 	ms->ms_softCAR = vi->ui_flags;
17132633Ssam 	/*
17232633Ssam 	 * Setup pointer to mblok, initialize bogus
17332633Ssam 	 * status block used by mpcc to locate the pointer
17432633Ssam 	 * and then poke the mpcc to get it to search host
17532633Ssam 	 * memory to find mblok pointer.
17632633Ssam 	 */
17732633Ssam 	mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf;
17832633Ssam 	*(short *)vi->ui_addr = 0x100;		/* magic */
17932633Ssam }
18032633Ssam 
18132633Ssam /*
18232633Ssam  * Open an mpcc port.
18332633Ssam  */
18434506Skarels /* ARGSUSED */
18532633Ssam mpopen(dev, mode)
18632633Ssam 	dev_t dev;
18732633Ssam {
18832633Ssam 	register struct tty *tp;
18932633Ssam 	register struct mpsoftc *ms;
19032633Ssam 	int error, s, port, unit, mpu;
19132633Ssam 	struct vba_device *vi;
19232633Ssam 	struct mpport *mp;
19332633Ssam 	struct mpevent *ev;
19432633Ssam 
19532633Ssam 	unit = minor(dev);
19632633Ssam 	mpu = MPUNIT(unit);
19732633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
19832633Ssam 		return (ENXIO);
19932633Ssam 	tp = &mp_tty[unit];
20032633Ssam 	if (tp->t_state & TS_XCLUDE && u.u_uid != 0)
20132633Ssam 		return (EBUSY);
20232633Ssam 	ms = &mp_softc[mpu];
20332633Ssam 	port = MPPORT(unit);
20432633Ssam 	if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC ||
20532633Ssam 	    ms->ms_mb->mb_status != MP_OPOPEN)
20632633Ssam 		return (ENXIO);
20732633Ssam 	mp = &ms->ms_mb->mb_port[port];		/* host mpcc struct */
20832633Ssam 	s = spl8();
20935935Sbostic 	/*
21035935Sbostic 	 * serialize open and close events
21135935Sbostic 	 */
21237607Smarc 	while ((mp->mp_flags & MP_PROGRESS) || ((tp->t_state & TS_WOPEN) &&
213*40734Skarels 	    !(mode&O_NONBLOCK) && !(tp->t_cflag&CLOCAL)))
214*40734Skarels 		if (error = tsleep((caddr_t)&tp->t_canq, TTIPRI | PCATCH,
215*40734Skarels 		    ttopen, 0)) {
216*40734Skarels 			splx(s);
217*40734Skarels 			return (error);
218*40734Skarels 		}
21935935Sbostic restart:
22032633Ssam 	tp->t_state |= TS_WOPEN;
22132633Ssam 	tp->t_addr = (caddr_t)ms;
22232633Ssam 	tp->t_oproc = mpstart;
22337607Smarc 	tp->t_param = mpparam;
22432633Ssam 	tp->t_dev = dev;
22534978Sbostic 	if ((tp->t_state & TS_ISOPEN) == 0) {
22634978Sbostic 		ttychars(tp);
22734978Sbostic 		if (tp->t_ispeed == 0) {
228*40734Skarels 			tp->t_ispeed = TTYDEF_SPEED;
229*40734Skarels 			tp->t_ospeed = TTYDEF_SPEED;
230*40734Skarels 			tp->t_iflag = TTYDEF_IFLAG;
231*40734Skarels 			tp->t_oflag = TTYDEF_OFLAG;
232*40734Skarels 			tp->t_lflag = TTYDEF_LFLAG;
233*40734Skarels 			tp->t_cflag = TTYDEF_CFLAG;
23434978Sbostic 		}
23534978Sbostic 		/*
23634978Sbostic 		 * Initialize port state: init MPCC interface
23734978Sbostic 		 * structures for port and setup modem control.
23834978Sbostic 		 */
23934978Sbostic 		error = mpportinit(ms, mp, port);
24034978Sbostic 		if (error)
24134978Sbostic 			goto bad;
24237607Smarc 		ev = mpparam2(tp, &tp->t_termios);
24334978Sbostic 		if (ev == 0) {
24434978Sbostic 			error = ENOBUFS;
24534978Sbostic 			goto bad;
24634978Sbostic 		}
24735935Sbostic 		mp->mp_flags |= MP_PROGRESS;
24834978Sbostic 		mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port);
24935935Sbostic 		/*
25035935Sbostic 		 * wait for port to start
25135935Sbostic 		 */
25235935Sbostic 		while (mp->mp_proto != MPPROTO_ASYNC)
253*40734Skarels 			if (error = tsleep((caddr_t)&tp->t_canq,
254*40734Skarels 			    TTIPRI | PCATCH, ttopen, 0))
255*40734Skarels 				goto bad;
25637607Smarc 		ttsetwater(tp);
25735935Sbostic 		mp->mp_flags &= ~MP_PROGRESS;
25832633Ssam 	}
259*40734Skarels 	while ((mode&O_NONBLOCK) == 0 && (tp->t_cflag&CLOCAL) == 0 &&
260*40734Skarels 	    (tp->t_state & TS_CARR_ON) == 0) {
261*40734Skarels 		if (error = tsleep((caddr_t)&tp->t_rawq, TTIPRI | PCATCH,
262*40734Skarels 		    ttopen, 0))
263*40734Skarels 			goto bad;
26435935Sbostic 		/*
26535935Sbostic 		 * a mpclose() might have disabled port. if so restart
26635935Sbostic 		 */
26735935Sbostic 		if (mp->mp_proto != MPPROTO_ASYNC)
26835935Sbostic 			goto restart;
26935935Sbostic 		tp->t_state |= TS_WOPEN;
27035935Sbostic 	}
27132633Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
27232633Ssam done:
27332633Ssam 	splx(s);
27435935Sbostic 	/*
27535935Sbostic 	 * wakeup those processes waiting for the open to complete
27635935Sbostic 	 */
27732633Ssam 	wakeup((caddr_t)&tp->t_canq);
27832633Ssam 	return (error);
27932633Ssam bad:
28032633Ssam 	tp->t_state &= ~TS_WOPEN;
28132633Ssam 	goto done;
28232633Ssam }
28332633Ssam 
28432633Ssam /*
28532633Ssam  * Close an mpcc port.
28632633Ssam  */
28734506Skarels /* ARGSUSED */
28834506Skarels mpclose(dev, flag)
28932633Ssam 	dev_t dev;
29032633Ssam {
29132633Ssam 	register struct tty *tp;
29232633Ssam 	register struct mpport *mp;
29332633Ssam 	register struct mpevent *ev;
294*40734Skarels 	int s, port, unit, error = 0;
29532633Ssam 	struct mblok *mb;
29632633Ssam 
29732633Ssam 	unit = minor(dev);
29832633Ssam 	tp = &mp_tty[unit];
29932633Ssam 	port = MPPORT(unit);
30032633Ssam 	mb = mp_softc[MPUNIT(unit)].ms_mb;
30132633Ssam 	mp = &mb->mb_port[port];
30232633Ssam 	s = spl8();
30335935Sbostic 	if (mp->mp_flags & MP_PROGRESS) {
30432633Ssam 		if (mp->mp_flags & MP_REMBSY) {
30532633Ssam 			mp->mp_flags &= ~MP_REMBSY;
30632633Ssam 			splx(s);
30732633Ssam 			return (0);
30832633Ssam 		}
30932633Ssam 		while (mp->mp_flags & MP_PROGRESS)
310*40734Skarels 			if (error = tsleep((caddr_t)&tp->t_canq,
311*40734Skarels 			    TTIPRI | PCATCH, ttclos, 0)) {
312*40734Skarels 				splx(s);
313*40734Skarels 				return (error);
314*40734Skarels 			}
31532633Ssam 	}
31632633Ssam 	mp->mp_flags |= MP_PROGRESS;
31732633Ssam 	(*linesw[tp->t_line].l_close)(tp);
31835935Sbostic 	ev = mp_getevent(mp, unit, 1);
31932633Ssam 	if (ev == 0) {
32034977Sbostic 		error = ENOBUFS;
32134977Sbostic 		mp->mp_flags &= ~MP_PROGRESS;
32234977Sbostic 		goto out;
32332633Ssam 	}
32434977Sbostic 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
32534977Sbostic 		mpmodem(unit, MMOD_OFF);
32634977Sbostic 	else
32734977Sbostic 		mpmodem(unit, MMOD_ON);
32832633Ssam 	mpcmd(ev, EVCMD_CLOSE, 0, mb, port);
329*40734Skarels 	error = ttyclose(tp);
33032633Ssam out:
33132633Ssam 	if (mp->mp_flags & MP_REMBSY)
33232633Ssam 		mpclean(mb, port);
33335935Sbostic 	else
334*40734Skarels 		while (mp->mp_flags & MP_PROGRESS && error == 0)
335*40734Skarels 			error = tsleep((caddr_t)&tp->t_canq, TTIPRI | PCATCH,
336*40734Skarels 			    ttclos, 0);
33732633Ssam 	splx(s);
33832633Ssam 	return (error);
33932633Ssam }
34032633Ssam 
34132633Ssam /*
34232633Ssam  * Read from an mpcc port.
34332633Ssam  */
34437607Smarc mpread(dev, uio, flag)
34532633Ssam 	dev_t dev;
34632633Ssam 	struct uio *uio;
34732633Ssam {
34832633Ssam 	struct tty *tp;
34932633Ssam 
35032633Ssam 	tp = &mp_tty[minor(dev)];
35137607Smarc 	return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
35232633Ssam }
35332633Ssam 
35432633Ssam /*
35532633Ssam  * Write to an mpcc port.
35632633Ssam  */
35737607Smarc mpwrite(dev, uio, flag)
35832633Ssam 	dev_t dev;
35932633Ssam 	struct uio *uio;
36032633Ssam {
36132633Ssam 	struct tty *tp;
36232633Ssam 
36332633Ssam 	tp = &mp_tty[minor(dev)];
36437607Smarc 	return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
36532633Ssam }
36632633Ssam 
36732633Ssam /*
36832633Ssam  * Ioctl for a mpcc port
36932633Ssam  */
37032633Ssam mpioctl(dev, cmd, data, flag)
37132633Ssam 	dev_t dev;
37232633Ssam 	caddr_t data;
37332633Ssam {
37432633Ssam 	register struct tty *tp;
37532633Ssam 	register struct mpsoftc *ms;
37637607Smarc 	register struct mpport *mp;
37732633Ssam 	register struct mpevent *ev;
37832633Ssam 	int s, port, error, unit;
37932633Ssam 	struct mblok *mb;
38032633Ssam 
38132633Ssam 	unit = minor(dev);
38232633Ssam 	tp = &mp_tty[unit];
38332633Ssam 	ms = &mp_softc[MPUNIT(unit)];
38432633Ssam 	mb = ms->ms_mb;
38535935Sbostic 	port = MPPORT(unit);
38635935Sbostic 	mp = &mb->mb_port[port];
38735935Sbostic 	if (mp->mp_proto != MPPROTO_ASYNC)
38835935Sbostic 		return(ENXIO);
38932633Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
39032633Ssam 	if (error >= 0)
39132633Ssam 		return (error);
39232633Ssam 	error = ttioctl(tp, cmd, data, flag);
39337607Smarc 	if (error >= 0)
39432633Ssam 		return (error);
39532633Ssam 	switch (cmd) {
39632633Ssam 	case TIOCSBRK:			/* send break */
39732633Ssam 	case TIOCCBRK:			/* clear break */
39832633Ssam 		s = spl8();
39935935Sbostic 		while (mp->mp_flags & MP_IOCTL) {
400*40734Skarels 			if (error = tsleep((caddr_t)&tp->t_canq,
401*40734Skarels 			    TTIPRI | PCATCH, ttyout, 0)) {
402*40734Skarels 				splx(s);
403*40734Skarels 				return (error);
404*40734Skarels 			}
40535935Sbostic 			if (mp->mp_proto != MPPROTO_ASYNC) {
40635935Sbostic 				splx(s);
407*40734Skarels 				return (ENXIO);
40835935Sbostic 			}
40935935Sbostic 		}
41035935Sbostic 		ev = mp_getevent(mp, unit, 0);
41135935Sbostic 		if (ev) {
41235935Sbostic 			mp->mp_flags |= MP_IOCTL;
41332633Ssam 			mpcmd(ev, EVCMD_IOCTL,
41435935Sbostic 			    (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF), mb, port);
41535935Sbostic 		} else
41632633Ssam 			error = ENOBUFS;
41732633Ssam 		splx(s);
41832633Ssam 		break;
41932633Ssam 	case TIOCSDTR:			/* set dtr control line */
42032633Ssam 		break;
42132633Ssam 	case TIOCCDTR:			/* clear dtr control line */
42232633Ssam 		break;
42332633Ssam 	default:
42432633Ssam 		error = ENOTTY;
42532633Ssam 		break;
42632633Ssam 	}
42732633Ssam 	return (error);
42832633Ssam }
42932633Ssam 
43037607Smarc mpparam(tp, t)
43137607Smarc 	struct tty *tp;
43237607Smarc 	struct termios *t;
43337607Smarc {
43437607Smarc 	register struct mpevent *ev;
43537607Smarc 	int unit = minor(tp->t_dev);
43637607Smarc 	struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
43737607Smarc 	struct mblok *mb = ms->ms_mb;
43837607Smarc 
43937607Smarc 	ev = mpparam2(tp, t);
44037607Smarc 	if (ev == 0)
44137607Smarc 		return (ENOBUFS);
44237607Smarc 	mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb, MPPORT(unit));
44337607Smarc 	return (0);
44437607Smarc }
44537607Smarc 
44632633Ssam struct mpevent *
44737607Smarc mpparam2(tp, t)
44837607Smarc 	register struct tty *tp;
44937607Smarc 	struct termios *t;
45032633Ssam {
45132633Ssam 	register struct mpevent *ev;
45232633Ssam 	register struct mpport *mp;
45337607Smarc 	int unit = minor(tp->t_dev);
45432633Ssam 	struct mblok *mb;
45532633Ssam 	struct mpsoftc *ms;
45632633Ssam 	register struct asyncparam *asp;
45737607Smarc 	int port, speedcode;
45832633Ssam 
45932633Ssam 	ms = &mp_softc[MPUNIT(unit)];
46032633Ssam 	mb = ms->ms_mb;
46132633Ssam 	port = MPPORT(unit);
46232633Ssam 	mp = &mb->mb_port[port];
46335935Sbostic 	ev = mp_getevent(mp, unit, 0);	/* XXX */
46437607Smarc 	speedcode = ttspeedtab(t->c_ospeed, mpspeedtab);
46537607Smarc 	if (ev == 0 || speedcode < 0) {
46637607Smarc printf("mp mpunit %d port %d param2 failed ev: %x speed %d, wanted %d\n",
46737607Smarc 			MPUNIT(unit), port, ev, speedcode, t->c_ospeed);
46837607Smarc 		return (0);	/* XXX */
46937607Smarc 	}
47032633Ssam 	/* YUCK */
47132633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
47237607Smarc 	asp->ap_xon = t->c_cc[VSTART];
47337607Smarc 	asp->ap_xoff = t->c_cc[VSTOP];
47437607Smarc 	if (!(t->c_iflag&IXON) || (asp->ap_xon == _POSIX_VDISABLE) ||
47537607Smarc 	    (asp->ap_xoff == _POSIX_VDISABLE))
47634796Sbostic 		asp->ap_xena = MPA_DIS;
47734796Sbostic 	else
47834796Sbostic 		asp->ap_xena = MPA_ENA;
47937607Smarc 	asp->ap_xany = ((t->c_iflag & IXANY) ? MPA_ENA : MPA_DIS);
48032633Ssam #ifdef notnow
48137607Smarc 	if (t->t_cflag&CSIZE) == CS8) {
48232633Ssam #endif
48332633Ssam 		asp->ap_data = MPCHAR_8;
48432633Ssam 		asp->ap_parity = MPPAR_NONE;
48532633Ssam #ifdef notnow
48632633Ssam 	} else {
48732633Ssam 		asp->ap_data = MPCHAR_7;
48837607Smarc 		if ((t->c_flags & (EVENP|ODDP)) == ODDP) /* XXX */
48932633Ssam 			asp->ap_parity = MPPAR_ODD;
49032633Ssam 		else
49132633Ssam 			asp->ap_parity = MPPAR_EVEN;
49232633Ssam 	}
49332633Ssam #endif
49435935Sbostic 	asp->ap_loop = MPA_DIS;		/* disable loopback */
49535935Sbostic 	asp->ap_rtimer = A_RCVTIM;	/* default receive timer */
49637607Smarc 	if (t->c_ospeed == B110)
49732633Ssam 		asp->ap_stop = MPSTOP_2;
49832633Ssam 	else
49932633Ssam 		asp->ap_stop = MPSTOP_1;
50037607Smarc 	if (t->c_ospeed == 0) {
50135935Sbostic 		tp->t_state |= TS_HUPCLS;
50235935Sbostic 		setm(&asp->ap_modem, 0, DROP);
50335935Sbostic 		seti(&asp->ap_intena, A_DCD);
50435935Sbostic 		return (ev);
50535935Sbostic 	}
50637607Smarc 	if (t->c_ospeed == EXTA || t->c_ospeed == EXTB)
50732633Ssam 		asp->ap_baud = M19200;
50832633Ssam 	else
50937607Smarc 		asp->ap_baud = speedcode;
51037607Smarc 	if (1 || ms->ms_softCAR & (1<<port)) /* XXX HARDWIRE FOR NOW */
51132633Ssam 		setm(&asp->ap_modem, A_DTR, ASSERT);
51232633Ssam 	else
51332633Ssam 		setm(&asp->ap_modem, A_DTR, AUTO);
51432633Ssam 	seti(&asp->ap_intena, A_DCD);
51537607Smarc 	return(ev);
51632633Ssam }
51732633Ssam 
51832633Ssam mpstart(tp)
51932633Ssam 	register struct tty *tp;
52032633Ssam {
52132633Ssam 	register struct mpevent *ev;
52232633Ssam 	register struct mpport *mp;
52332633Ssam 	struct mblok *mb;
52432633Ssam 	struct mpsoftc *ms;
52532633Ssam 	int port, unit, xcnt, n, s, i;
52632633Ssam 	struct	hxmtl *hxp;
52732633Ssam 	struct clist outq;
52832633Ssam 
52932633Ssam 	s = spl8();
53032633Ssam 	unit = minor(tp->t_dev);
53132633Ssam 	ms = &mp_softc[MPUNIT(unit)];
53232633Ssam 	mb = ms->ms_mb;
53332633Ssam 	port = MPPORT(unit);
53432633Ssam 	mp = &mb->mb_port[port];
53532633Ssam 	hxp = &ms->ms_hxl[port];
53632633Ssam 	xcnt = 0;
53732633Ssam 	outq = tp->t_outq;
53832633Ssam 	for (i = 0; i < MPXMIT; i++) {
53932633Ssam 		if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP))
54032633Ssam 			break;
54137607Smarc 		if (outq.c_cc <= tp->t_lowat) {
54232633Ssam 			if (tp->t_state & TS_ASLEEP) {
54332633Ssam 				tp->t_state &= ~TS_ASLEEP;
54432633Ssam 				wakeup((caddr_t)&tp->t_outq);
54532633Ssam 			}
54632633Ssam 			if (tp->t_wsel) {
54732633Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
54832633Ssam 				tp->t_wsel = 0;
54932633Ssam 				tp->t_state &= ~TS_WCOLL;
55032633Ssam 			}
55132633Ssam 		}
55232633Ssam 		if (outq.c_cc == 0)
55332633Ssam 			break;
55432633Ssam 		/*
55532633Ssam 		 * If we're not currently busy outputting,
55632633Ssam 		 * and there is data to be output, set up
55732633Ssam 		 * port transmit structure to send to mpcc.
55832633Ssam 		 */
55937607Smarc 		if (1) /* || tp->t_flags & (RAW|LITOUT))  XXX FIX */
56032633Ssam 			n = ndqb(&outq, 0);
56132633Ssam 		else {
56232633Ssam 			n = ndqb(&outq, 0200);
56332633Ssam 			if (n == 0) {
56435935Sbostic 				if (xcnt > 0)
56535935Sbostic 					break;
56632633Ssam 				n = getc(&outq);
56732633Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
56832633Ssam 				tp->t_state |= TS_TIMEOUT;
56932633Ssam 				break;
57032633Ssam 			}
57132633Ssam 		}
57234506Skarels 		hxp->dblock[i] = (caddr_t)kvtophys(outq.c_cf);
57332633Ssam 		hxp->size[i] = n;
57432633Ssam 		xcnt++;		/* count of xmts to send */
57532633Ssam 		ndadvance(&outq, n);
57632633Ssam 	}
57732633Ssam 	/*
57832633Ssam 	 * If data to send, poke mpcc.
57932633Ssam 	 */
58032633Ssam 	if (xcnt) {
58135935Sbostic 		ev = mp_getevent(mp, unit, 0);
58232633Ssam 		if (ev == 0) {
58332633Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
58432633Ssam 		} else {
58532633Ssam 			tp->t_state |= TS_BUSY;
58632633Ssam 			ev->ev_count = xcnt;
58732633Ssam 			mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit));
58832633Ssam 		}
58932633Ssam 	}
59032633Ssam 	splx(s);
59132633Ssam }
59232633Ssam 
59332633Ssam /*
59432633Ssam  * Advance cc bytes from q  but don't free memory.
59532633Ssam  */
59632633Ssam ndadvance(q, cc)
59732633Ssam 	register struct clist *q;
59832633Ssam 	register cc;
59932633Ssam {
60032633Ssam 	register struct cblock *bp;
60132633Ssam 	char *end;
60232633Ssam 	int rem, s;
60332633Ssam 
60432633Ssam 	s = spltty();
60532633Ssam 	if (q->c_cc <= 0)
60632633Ssam 		goto out;
60732633Ssam 	while (cc>0 && q->c_cc) {
60832633Ssam 		bp = (struct cblock *)((int)q->c_cf & ~CROUND);
60932633Ssam 		if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) {
61032633Ssam 			end = q->c_cl;
61132633Ssam 		} else {
61232633Ssam 			end = (char *)((int)bp + sizeof (struct cblock));
61332633Ssam 		}
61432633Ssam 		rem = end - q->c_cf;
61532633Ssam 		if (cc >= rem) {
61632633Ssam 			cc -= rem;
61732633Ssam 			q->c_cc -= rem;
61832633Ssam 			q->c_cf = bp->c_next->c_info;
61932633Ssam 		} else {
62032633Ssam 			q->c_cc -= cc;
62132633Ssam 			q->c_cf += cc;
62232633Ssam 			break;
62332633Ssam 		}
62432633Ssam 	}
62532633Ssam 	if (q->c_cc <= 0) {
62632633Ssam 		q->c_cf = q->c_cl = NULL;
62732633Ssam 		q->c_cc = 0;
62832633Ssam 	}
62932633Ssam out:
63032633Ssam 	splx(s);
63132633Ssam }
63232633Ssam 
63332633Ssam /*
63432633Ssam  * Stop output on a line, e.g. for ^S/^Q or output flush.
63532633Ssam  */
63634506Skarels /* ARGSUSED */
63732633Ssam mpstop(tp, rw)
63832633Ssam 	register struct tty *tp;
63932633Ssam 	int rw;
64032633Ssam {
64135935Sbostic 	register struct mpport *mp;
64235935Sbostic 	register struct mpevent *ev;
64335935Sbostic 	int unit = minor(tp->t_dev);
64435935Sbostic 	int port;
64535935Sbostic 	struct mblok *mb;
64634506Skarels 	int s;
64732633Ssam 
64832633Ssam 	s = spl8();
64932633Ssam 	if (tp->t_state & TS_BUSY) {
65035935Sbostic 		if ((tp->t_state & TS_TTSTOP) == 0) {
65132633Ssam 			tp->t_state |= TS_FLUSH;
65235935Sbostic 			port = MPPORT(unit);
65335935Sbostic 			mb = mp_softc[MPUNIT(unit)].ms_mb;
65435935Sbostic 			mp = &mb->mb_port[port];
65535935Sbostic 			ev = mp_getevent(mp, unit, 0);
65635935Sbostic 			if (ev == 0) {
65735935Sbostic 				splx(s);
65835935Sbostic 				return;
65935935Sbostic 			}
66035935Sbostic 			mpcmd(ev, EVCMD_WRITE, A_FLUSH, mb, port);
66135935Sbostic 		}
66232633Ssam 	}
66332633Ssam 	splx(s);
66432633Ssam }
66532633Ssam 
66632633Ssam /*
66732633Ssam  * Initialize an async port's MPCC state.
66832633Ssam  */
66932633Ssam mpportinit(ms, mp, port)
67032633Ssam 	register struct mpsoftc *ms;
67132633Ssam 	register struct mpport *mp;
67232633Ssam 	int port;
67332633Ssam {
67432633Ssam 	register struct mpevent *ev;
67532633Ssam 	register int i;
67632633Ssam 	caddr_t ptr;
67732633Ssam 
67832633Ssam 	mp->mp_on = mp->mp_off = 0;
67932633Ssam 	mp->mp_nextrcv = 0;
68032633Ssam 	mp->mp_flags = 0;
68132633Ssam 	ev = &mp->mp_recvq[0];
68232633Ssam 	for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) {
68332633Ssam 		ev->ev_status = EVSTATUS_FREE;
68432633Ssam 		ev->ev_cmd = 0;
68532633Ssam 		ev->ev_opts = 0;
68632633Ssam 		ev->ev_error = 0;
68732633Ssam 		ev->ev_flags = 0;
68832633Ssam 		ev->ev_count = 0;
68934506Skarels 		ev->ev_un.hxl = (struct hxmtl *) kvtophys(&ms->ms_hxl[port]);
69034506Skarels 		ev->ev_params = (caddr_t) kvtophys(&ms->ms_async[port][i]);
69132633Ssam 	}
69232633Ssam 	ev = &mp->mp_sendq[0];
69332633Ssam 	for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) {
69432633Ssam 		/* init so that L2 can't send any events */
69532633Ssam 		/* to host until open has completed      */
69632633Ssam 		ev->ev_status = EVSTATUS_FREE;
69732633Ssam 		ev->ev_cmd = 0;
69835935Sbostic 		ev->ev_opts = 0;
69932633Ssam 		ev->ev_error = 0;
70032633Ssam 		ev->ev_flags = 0;
70132633Ssam 		ev->ev_count = 0;
70232633Ssam 		ptr = (caddr_t) &ms->ms_cbuf[port][i][0];
70334506Skarels 		ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
70434506Skarels 		ev->ev_params = (caddr_t) kvtophys(ptr);
70532633Ssam 	}
70632633Ssam 	return (0);
70732633Ssam }
70832633Ssam 
70932633Ssam /*
71032633Ssam  * Send an event to an mpcc.
71132633Ssam  */
71232633Ssam mpcmd(ev, cmd, flags, mb, port)
71332633Ssam 	register struct mpevent *ev;
71432633Ssam 	struct mblok *mb;
71532633Ssam {
71632633Ssam 	int s;
71732633Ssam 
71832633Ssam 	s = spl8();
71932633Ssam 	/* move host values to inbound entry */
72032633Ssam 	ev->ev_cmd = cmd;
72132633Ssam 	ev->ev_opts = flags;
72232633Ssam 	/* show event ready for mpcc */
72332633Ssam 	ev->ev_status = EVSTATUS_GO;
72432633Ssam 	mpintmpcc(mb, port);
72532633Ssam 	splx(s);
72632633Ssam }
72732633Ssam 
72832633Ssam /*
72932633Ssam  * Return the next available event entry for the indicated port.
73032633Ssam  */
73132633Ssam struct mpevent *
73235935Sbostic mp_getevent(mp, unit, cls_req)
73332633Ssam 	register struct mpport *mp;
73432633Ssam 	int unit;
73535935Sbostic 	int cls_req;
73632633Ssam {
73732633Ssam 	register struct mpevent *ev;
73832633Ssam 	int i, s;
73932633Ssam 
74032633Ssam 	s = spl8();
74132633Ssam 	ev = &mp->mp_recvq[mp->mp_on];
74232633Ssam 	if (ev->ev_status != EVSTATUS_FREE)
74332633Ssam 		goto bad;
74432633Ssam 	/*
74532633Ssam 	 * If not a close request, verify one extra
74632633Ssam 	 * event is available for closing the port.
74732633Ssam 	 */
74835935Sbostic 	if (!cls_req) {
74932633Ssam 		if ((i = mp->mp_on + 1) >= MPINSET)
75032633Ssam 			i = 0;
75132633Ssam 		if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE)
75232633Ssam 			goto bad;
75332633Ssam 	}
75432633Ssam 	/* init inbound fields marking this entry as busy */
75535935Sbostic 	ev->ev_cmd = 0;
75635935Sbostic 	ev->ev_opts = 0;
75732633Ssam 	ev->ev_error = 0;
75832633Ssam 	ev->ev_flags = 0;
75932633Ssam 	ev->ev_count = 0;
76032633Ssam 	ev->ev_status = EVSTATUS_BUSY;
76132633Ssam 	/* adjust pointer to next available inbound entry */
76232633Ssam 	adjptr(mp->mp_on, MPINSET);
76332633Ssam 	splx(s);
76432633Ssam 	return (ev);
76532633Ssam bad:
76632633Ssam 	splx(s);
76735935Sbostic 	log(LOG_ERR, "mp%d: port%d, out of events\n",
76835935Sbostic 	    MPUNIT(unit), MPPORT(unit));
76932633Ssam 	return ((struct mpevent *)0);
77032633Ssam }
77132633Ssam 
77232633Ssam mpmodem(unit, flag)
77332633Ssam 	int unit, flag;
77432633Ssam {
77532633Ssam 	struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
77632633Ssam 	int port = MPPORT(unit);
77732633Ssam 	register struct mpport *mp;
77832633Ssam 	register struct asyncparam *asp;
77932633Ssam 
78032633Ssam 	mp = &ms->ms_mb->mb_port[port];
78132633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
78232633Ssam 	if (flag == MMOD_ON) {
78337607Smarc 		if (1 || ms->ms_softCAR & (1 << port))/* XXX HARDWIRE FOR NOW */
78432633Ssam 			setm(&asp->ap_modem, A_DTR, ASSERT);
78532633Ssam 		else
78632633Ssam 			setm(&asp->ap_modem, A_DTR, AUTO);
78732633Ssam 		seti(&asp->ap_intena, A_DCD);
78832633Ssam 	} else {
78932633Ssam 		setm(&asp->ap_modem, 0, DROP);
79032633Ssam 		seti(&asp->ap_intena, 0);
79132633Ssam 	}
79232633Ssam }
79332633Ssam 
79432633Ssam /*
79532633Ssam  * Set up the modem control structure according to mask.
79632633Ssam  * Each set bit in the mask means assert the corresponding
79732633Ssam  * modem control line, otherwise, it will be dropped.
79832633Ssam  * RTS is special since it can either be asserted, dropped
79932633Ssam  * or put in auto mode for auto modem control.
80032633Ssam  */
80132633Ssam static
80232633Ssam setm(mc, mask, rts)
80332633Ssam 	register struct mdmctl *mc;
80432633Ssam 	register int mask;
80532633Ssam {
80632633Ssam 
80732633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP;
80832633Ssam 	mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP;
80932633Ssam 	mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP;
81032633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP;
81132633Ssam 	mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP;
81232633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP;
81332633Ssam 	mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP;
81432633Ssam 	mc->mc_rts = rts;
81532633Ssam }
81632633Ssam 
81732633Ssam /*
81832633Ssam  * Set up the status change enable field from mask.
81932633Ssam  * When a signal is enabled in this structure and
82032633Ssam  * and a change in state on a corresponding modem
82132633Ssam  * control line occurs, a status change event will
82232633Ssam  * be delivered to the host.
82332633Ssam  */
82432633Ssam static
82532633Ssam seti(mc, mask)
82632633Ssam 	register struct mdmctl *mc;
82732633Ssam 	register int mask;
82832633Ssam {
82932633Ssam 
83032633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF;
83132633Ssam 	mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF;
83232633Ssam 	mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF;
83332633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF;
83432633Ssam 	mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF;
83532633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF;
83632633Ssam 	mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF;
83732633Ssam 	mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF;
83832633Ssam }
83932633Ssam 
84032633Ssam mpcleanport(mb, port)
84132633Ssam 	struct mblok *mb;
84232633Ssam 	int port;
84332633Ssam {
84432633Ssam 	register struct mpport *mp;
84532633Ssam 	register struct tty *tp;
84632633Ssam 
84732633Ssam 	mp = &mb->mb_port[port];
84832633Ssam 	if (mp->mp_proto == MPPROTO_ASYNC) {
84932633Ssam 		mp->mp_flags = MP_REMBSY;
85034506Skarels 		/* signal loss of carrier and close */
85132633Ssam 		tp = &mp_tty[mb->mb_unit*MPCHUNK+port];
85232633Ssam 		ttyflush(tp, FREAD|FWRITE);
85334506Skarels 		(void) (*linesw[tp->t_line].l_modem)(tp, 0);
85432633Ssam 	}
85532633Ssam }
85632633Ssam 
85732633Ssam mpclean(mb, port)
85832633Ssam 	register struct mblok *mb;
85932633Ssam 	int port;
86032633Ssam {
86132633Ssam 	register struct mpport *mp;
86232633Ssam 	register struct mpevent *ev;
86332633Ssam 	register int i;
86434506Skarels 	u_char list[2];
86532633Ssam 	int unit;
86632633Ssam 
86732633Ssam 	mp = &mb->mb_port[port];
86832633Ssam 	unit = mb->mb_unit;
86932633Ssam 	for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) {
87032633Ssam 		ev = &mp->mp_recvq[i];
87132633Ssam 		ev->ev_error = ENXIO;
87232633Ssam 		ev->ev_status = EVSTATUS_DONE;
87332633Ssam 	}
87432633Ssam 	list[0] = port, list[1] = MPPORT_EOL;
87532633Ssam 	mpxintr(unit, list);
87632633Ssam 	mprintr(unit, list);
87732633Ssam 	/* Clear async for port */
87832633Ssam 	mp->mp_proto = MPPROTO_UNUSED;
87932633Ssam 	mp->mp_flags = 0;
88032633Ssam 	mp->mp_on = 0;
88132633Ssam 	mp->mp_off = 0;
88232633Ssam 	mp->mp_nextrcv = 0;
88332633Ssam 
88432633Ssam 	mp_tty[unit*MPCHUNK + port].t_state = 0;
88532633Ssam 	for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) {
88632633Ssam 		ev->ev_status = EVSTATUS_FREE;
88732633Ssam 		ev->ev_cmd = 0;
88832633Ssam 		ev->ev_error = 0;
88932633Ssam 		ev->ev_un.rcvblk = 0;
89032633Ssam 		ev->ev_params = 0;
89132633Ssam 	}
89232633Ssam 	for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) {
89332633Ssam 		ev->ev_status = EVSTATUS_FREE;
89432633Ssam 		ev->ev_cmd = 0;
89532633Ssam 		ev->ev_error = 0;
89632633Ssam 		ev->ev_params = 0;
89732633Ssam 	}
89832633Ssam }
89932633Ssam 
90032633Ssam /*
90132633Ssam  * MPCC interrupt handler.
90232633Ssam  */
90332633Ssam mpintr(mpcc)
90432633Ssam 	int mpcc;
90532633Ssam {
90632633Ssam 	register struct mblok *mb;
90732633Ssam 	register struct his *his;
90832633Ssam 
90932633Ssam 	mb = mp_softc[mpcc].ms_mb;
91032633Ssam 	if (mb == 0) {
91132633Ssam 		printf("mp%d: stray interrupt\n", mpcc);
91232633Ssam 		return;
91332633Ssam 	}
91432633Ssam 	his = &mb->mb_hostint;
91532633Ssam 	his->semaphore &= ~MPSEMA_AVAILABLE;
91632633Ssam 	/*
91732633Ssam 	 * Check for events to be processed.
91832633Ssam 	 */
91932633Ssam 	if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL)
92032633Ssam 		mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone);
92132633Ssam 	if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL)
92232633Ssam 		mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone);
92332633Ssam 	if (mb->mb_harderr || mb->mb_softerr)
92432633Ssam 		mperror(mb, mpcc);
92532633Ssam 	his->semaphore |= MPSEMA_AVAILABLE;
92632633Ssam }
92732633Ssam 
92832633Ssam /*
92932633Ssam  * Handler for processing completion of transmitted events.
93032633Ssam  */
93132633Ssam mpxintr(unit, list)
93234506Skarels 	register u_char *list;
93332633Ssam {
93432633Ssam 	register struct mpport *mp;
93532633Ssam 	register struct mpevent *ev;
93632633Ssam 	register struct mblok *mb;
93732633Ssam 	register struct tty *tp;
93832633Ssam 	register struct asyncparam *ap;
93932633Ssam 	struct mpsoftc *ms;
94032633Ssam 	int port, i, j;
94135935Sbostic #	define nextevent(mp) &mp->mp_recvq[mp->mp_off]
94232633Ssam 
94332633Ssam 	ms = &mp_softc[unit];
94432633Ssam 	mb = mp_softc[unit].ms_mb;
94532633Ssam 	for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) {
94632633Ssam 		/*
94732633Ssam 		 * Process each completed entry in the inbound queue.
94832633Ssam 		 */
94932633Ssam 		mp = &mb->mb_port[port];
95032633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
95132633Ssam 		ev = nextevent(mp);
95235935Sbostic 		for (; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) {
95332633Ssam 			/* YUCK */
95432633Ssam 			ap = &ms->ms_async[port][mp->mp_off];
95534506Skarels 			mppurge((caddr_t)ap, (int)sizeof (*ap));
95632633Ssam 			switch (ev->ev_cmd) {
95732633Ssam 			case EVCMD_OPEN:
95832633Ssam 				/*
95932633Ssam 				 * Open completion, start all reads and
96032633Ssam 				 * assert modem status information.
96132633Ssam 				 */
96232633Ssam 				for (i = 0; i < MPOUTSET; i++)
96332633Ssam 					mp->mp_sendq[i].ev_status = EVSTATUS_GO;
96432633Ssam 				(*linesw[tp->t_line].l_modem)
96532633Ssam 				    (tp, ap->ap_modem.mc_dcd == ASSERT);
96635935Sbostic 				mp_freein(ev);
96735935Sbostic 				adjptr(mp->mp_off, MPINSET);
96835935Sbostic 				mp->mp_proto = MPPROTO_ASYNC;	/* XXX */
96935935Sbostic 				wakeup((caddr_t)&tp->t_canq);
97032633Ssam 				break;
97132633Ssam 			case EVCMD_CLOSE:
97232633Ssam 				/*
97332633Ssam 				 * Close completion, flush all pending
97432633Ssam 				 * transmissions, free resources, and
97532633Ssam 				 * cleanup mpcc port state.
97632633Ssam 				 */
97732633Ssam 				for (i = 0; i < MPOUTSET; i++) {
97832633Ssam 					mp->mp_sendq[i].ev_status =
97932633Ssam 					    EVSTATUS_FREE;
98032633Ssam 					mp->mp_sendq[i].ev_un.rcvblk = 0;
98132633Ssam 					mp->mp_sendq[i].ev_params = 0;
98232633Ssam 				}
98335935Sbostic 				mp_freein(ev);
98435935Sbostic 				adjptr(mp->mp_off, MPINSET);
98535935Sbostic 				tp->t_state &= ~(TS_CARR_ON|TS_BUSY|TS_FLUSH);
98632633Ssam 				mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0;
98732633Ssam 				mp->mp_flags &= ~MP_PROGRESS;
98832633Ssam 				mp->mp_proto = MPPROTO_UNUSED;
98935055Skarels 				wakeup((caddr_t)&tp->t_canq);
99035935Sbostic 				break;
99132633Ssam 			case EVCMD_IOCTL:
99235935Sbostic 				mp_freein(ev);
99335935Sbostic 				adjptr(mp->mp_off, MPINSET);
99435935Sbostic 				mp->mp_flags &= ~MP_IOCTL;
99535935Sbostic 				wakeup((caddr_t)&tp->t_canq);
99632633Ssam 				break;
99732633Ssam 			case EVCMD_WRITE:
99832633Ssam 				/*
99932633Ssam 				 * Transmission completed, update tty
100032633Ssam 				 * state and restart output.
100132633Ssam 				 */
100235935Sbostic 				if (ev->ev_opts != A_FLUSH) {
100335935Sbostic 					tp->t_state &= ~TS_BUSY;
100435935Sbostic 					if (tp->t_state & TS_FLUSH)
100535935Sbostic 						tp->t_state &= ~TS_FLUSH;
100635935Sbostic 					else {
100735935Sbostic 						register int cc = 0, n;
100835935Sbostic 						struct hxmtl *hxp;
100932633Ssam 
101035935Sbostic 						hxp = &ms->ms_hxl[port];
101135935Sbostic 						for (n=0;n < ev->ev_count; n++)
101235935Sbostic 							cc += hxp->size[n];
101335935Sbostic 						ndflush(&tp->t_outq, cc);
101435935Sbostic 					}
101532633Ssam 				}
101632633Ssam 				switch (ev->ev_error) {
101732633Ssam 				case A_SIZERR:  /*# error in xmt data size */
101832633Ssam 					mplog(unit, port, A_XSIZE, 0);
101932633Ssam 					break;
102032633Ssam 				case A_NXBERR:  /*# no more xmt evt buffers */
102132633Ssam 					mplog(unit, port, A_NOXBUF, 0);
102232633Ssam 					break;
102332633Ssam 				}
102435935Sbostic 				mp_freein(ev);
102535935Sbostic 				adjptr(mp->mp_off, MPINSET);
102632633Ssam 				mpstart(tp);
102732633Ssam 				break;
102832633Ssam 			default:
102934506Skarels 				mplog(unit, port, A_INVCMD, (int)ev->ev_cmd);
103035935Sbostic 				mp_freein(ev);
103135935Sbostic 				adjptr(mp->mp_off, MPINSET);
103232633Ssam 				break;
103332633Ssam 			}
103432633Ssam 		}
103532633Ssam 	}
103635935Sbostic #undef	nextevent
103732633Ssam }
103832633Ssam 
103935935Sbostic mp_freein(ev)
104035935Sbostic 	register struct mpevent *ev;
104135935Sbostic {
104235935Sbostic 	/* re-init all values in this entry */
104335935Sbostic 	ev->ev_cmd = 0;
104435935Sbostic 	ev->ev_opts = 0;
104535935Sbostic 	ev->ev_error = 0;
104635935Sbostic 	ev->ev_flags = 0;
104735935Sbostic 	ev->ev_count = 0;
104835935Sbostic 	/* show this entry is available for use */
104935935Sbostic 	ev->ev_status = EVSTATUS_FREE;
105035935Sbostic }
105135935Sbostic 
105232633Ssam /*
105332633Ssam  * Handler for processing received events.
105432633Ssam  */
105532633Ssam mprintr(unit, list)
105634506Skarels 	u_char *list;
105732633Ssam {
105832633Ssam 	register struct tty *tp;
105932633Ssam 	register struct mpport *mp;
106032633Ssam 	register struct mpevent *ev;
106132633Ssam 	struct mblok *mb;
106232633Ssam 	register int cc;
106332633Ssam 	register char *cp;
106432633Ssam 	struct mpsoftc *ms;
106532633Ssam 	caddr_t ptr;
106632633Ssam 	char *rcverr;
106732633Ssam 	int port, i;
106832633Ssam 
106932633Ssam 	ms = &mp_softc[unit];
107032633Ssam 	mb = mp_softc[unit].ms_mb;
107132633Ssam 	for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) {
107232633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
107332633Ssam 		mp = &mb->mb_port[port];
107432633Ssam 		ev = &mp->mp_sendq[mp->mp_nextrcv];
107532633Ssam 		while (ev->ev_status & EVSTATUS_DONE) {
107635935Sbostic 			switch(ev->ev_cmd) {
107735935Sbostic 			case EVCMD_STATUS:
107832633Ssam 				/*
107932633Ssam 				 * Status change, look for carrier changes.
108032633Ssam 				 */
108135935Sbostic 				switch(ev->ev_opts) {
108235935Sbostic 				case DCDASRT:
108335935Sbostic 					(*linesw[tp->t_line].l_modem)(tp, 1);
108435935Sbostic 					wakeup((caddr_t)&tp->t_canq);
108535935Sbostic 					break;
108635935Sbostic 				case DCDDROP:
108735935Sbostic 					(*linesw[tp->t_line].l_modem)(tp, 0);
108835935Sbostic 					wakeup((caddr_t)&tp->t_canq);
108935935Sbostic 					break;
109035935Sbostic 				case NORBUF:
109135935Sbostic 				case NOEBUF:
109232633Ssam 					mplog(unit, port,
109335935Sbostic 					    "out of receive events", 0);
109435935Sbostic 					break;
109535935Sbostic 				default:
109635935Sbostic 					mplog(unit, port,
109732633Ssam 					    "unexpect status command",
109834506Skarels 					    (int)ev->ev_opts);
109935935Sbostic 					break;
110035935Sbostic 				}
110135935Sbostic 				break;
110235935Sbostic 			case EVCMD_READ:
110332633Ssam 				/*
110435935Sbostic 			 	 * Process received data.
110535935Sbostic 			 	 */
110635935Sbostic 				if ((tp->t_state & TS_ISOPEN) == 0) {
110735935Sbostic 					wakeup((caddr_t)&tp->t_rawq);
110835935Sbostic 					break;
110935935Sbostic 				}
111035935Sbostic 				if ((cc = ev->ev_count) == 0)
111135935Sbostic 					break;
111235935Sbostic 				cp = ms->ms_cbuf[port][mp->mp_nextrcv];
111335935Sbostic 				mppurge(cp, CBSIZE);
111435935Sbostic 				while (cc-- > 0) {
111535935Sbostic 					/*
111635935Sbostic 				 	 * A null character is inserted,
111735935Sbostic 					 * potentially when a break or framing
111835935Sbostic 					 * error occurs. If we're not in raw
111935935Sbostic 					 * mode, substitute the interrupt
112035935Sbostic 					 * character.
112135935Sbostic 				 	 */
112237607Smarc 					/*** XXX - FIXUP ***/
112335935Sbostic 					if (*cp == 0 &&
112435935Sbostic 				            (ev->ev_error == BRKASRT ||
112535935Sbostic 				             ev->ev_error == FRAMERR))
112635935Sbostic 						if ((tp->t_flags&RAW) == 0)
112737607Smarc 							;
112837607Smarc 							/* XXX was break */
112935935Sbostic 					(*linesw[tp->t_line].l_rint)(*cp++, tp);
113035935Sbostic 				}
113135935Sbostic 				/* setup for next read */
113235935Sbostic 				ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0];
113335935Sbostic 				ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
113435935Sbostic 				ev->ev_params = (caddr_t) kvtophys(ptr);
113535935Sbostic 				switch(ev->ev_error) {
113635935Sbostic 				case RCVDTA:
113735935Sbostic 					/* Normal (good) rcv data do not
113835935Sbostic 					 * report the following they are
113935935Sbostic 					 * "normal" errors
114035935Sbostic 					 */
114135935Sbostic 				case FRAMERR:
114235935Sbostic 					/* frame error */
114335935Sbostic 				case BRKASRT:
114435935Sbostic 					/* Break condition */
114535935Sbostic 				case PARERR:
114635935Sbostic 					/* parity error */
114735935Sbostic 					rcverr = (char *)0;
114835935Sbostic 					break;
114935935Sbostic 				case OVRNERR:
115035935Sbostic 					/* Overrun error */
115135935Sbostic 					rcverr = "overrun error";
115235935Sbostic 					break;
115335935Sbostic 				case OVFERR:
115435935Sbostic 					/* Overflow error */
115535935Sbostic 					rcverr = "overflow error";
115635935Sbostic 					break;
115735935Sbostic 				default:
115835935Sbostic 					rcverr = "undefined rcv error";
115935935Sbostic 					break;
116035935Sbostic 				}
116135935Sbostic 				if (rcverr != (char *)0)
116235935Sbostic 					mplog(unit, port, rcverr,
116335935Sbostic 					      (int)ev->ev_error);
116432633Ssam 				break;
116535935Sbostic 			default:
116635935Sbostic 				mplog(unit, port, "unexpected command",
116735935Sbostic 					(int)ev->ev_cmd);
116832633Ssam 				break;
116932633Ssam 			}
117032633Ssam 			ev->ev_cmd = 0;
117132633Ssam 			ev->ev_opts = 0;
117232633Ssam 			ev->ev_error = 0;
117332633Ssam 			ev->ev_flags = 0;
117435935Sbostic 			ev->ev_count = 0;
117532633Ssam 			ev->ev_status = EVSTATUS_GO;	/* start next read */
117632633Ssam 			adjptr(mp->mp_nextrcv, MPOUTSET);
117732633Ssam 			ev = &mp->mp_sendq[mp->mp_nextrcv];
117832633Ssam 		}
117932633Ssam 	}
118032633Ssam }
118132633Ssam 
118232633Ssam /*
118332633Ssam  * Log an mpcc diagnostic.
118432633Ssam  */
118532633Ssam mplog(unit, port, cp, flags)
118632633Ssam 	char *cp;
118732633Ssam {
118832633Ssam 
118932633Ssam 	if (flags)
119032633Ssam 		log(LOG_ERR, "mp%d: port%d, %s (%d)\n",
119132633Ssam 		    unit, port, cp, flags);
119232633Ssam 	else
119332633Ssam 		log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp);
119432633Ssam }
119532633Ssam 
119632633Ssam int	MPHOSTINT = 1;
119732633Ssam 
119832633Ssam mptimeint(mb)
119932633Ssam 	register struct mblok *mb;
120032633Ssam {
120132633Ssam 
120232633Ssam         mb->mb_mpintcnt = 0;
120332633Ssam         mb->mb_mpintclk = (caddr_t)0;
120432633Ssam 	*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
120532633Ssam }
120632633Ssam 
120732633Ssam /*
120832633Ssam  * Interupt mpcc
120932633Ssam  */
121032633Ssam mpintmpcc(mb, port)
121132633Ssam 	register struct mblok *mb;
121232633Ssam {
121332633Ssam 
121432633Ssam         mb->mb_intr[port] |= MPSEMA_WORK;
121532633Ssam         if (++mb->mb_mpintcnt == MPHOSTINT) {
121632633Ssam                 mb->mb_mpintcnt = 0;
121732633Ssam 		*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
121832633Ssam                 if (mb->mb_mpintclk) {
121934506Skarels                         untimeout(mptimeint, (caddr_t)mb);
122032633Ssam                         mb->mb_mpintclk = 0;
122132633Ssam                 }
122232633Ssam         } else {
122332633Ssam                 if (mb->mb_mpintclk == 0) {
122434506Skarels                         timeout(mptimeint, (caddr_t)mb, 4);
122532633Ssam                         mb->mb_mpintclk = (caddr_t)1;
122632633Ssam                 }
122732633Ssam         }
122832633Ssam }
122932633Ssam 
123032633Ssam static char *mpherrmsg[] = {
123132633Ssam 	"",
123232633Ssam 	"Bus error",				/* MPBUSERR */
123332633Ssam 	"Address error",			/* ADDRERR */
123432633Ssam 	"Undefined ecc interrupt",		/* UNDECC */
123532633Ssam 	"Undefined interrupt",			/* UNDINT */
123632633Ssam 	"Power failure occurred",		/* PWRFL */
123732633Ssam 	"Stray transmit done interrupt",	/* NOXENTRY */
123832633Ssam 	"Two fast timers on one port",		/* TWOFTMRS */
123932633Ssam 	"Interrupt queue full",			/* INTQFULL */
124032633Ssam 	"Interrupt queue ack error",		/* INTQERR */
124132633Ssam 	"Uncorrectable dma parity error",	/* CBPERR */
124232633Ssam 	"32 port ACAP failed power up",		/* ACPDEAD */
124332633Ssam };
124432633Ssam #define	NHERRS	(sizeof (mpherrmsg) / sizeof (mpherrmsg[0]))
124532633Ssam 
124632633Ssam mperror(mb, unit)
124732633Ssam 	register struct mblok *mb;
124832633Ssam 	int unit;
124932633Ssam {
125032633Ssam 	register char *cp;
125132633Ssam 	register int i;
125232633Ssam 
125332633Ssam 	if (mb->mb_softerr) {
125432633Ssam 		switch (mb->mb_softerr) {
125532633Ssam 		case DMAPERR:   /* dma parity error */
125632633Ssam 			cp = "dma parity error";
125732633Ssam 			break;
125832633Ssam 		case ECCERR:
125932633Ssam 			cp = "local memory ecc error";
126032633Ssam 			break;
126132633Ssam 		default:
126232633Ssam 			cp = "unknown error";
126332633Ssam 			break;
126432633Ssam 		}
126532633Ssam 		log(LOG_ERR, "mp%d: soft error, %s", unit, cp);
126632633Ssam 		mb->mb_softerr = 0;
126732633Ssam 	}
126832633Ssam 	if (mb->mb_harderr) {
126932633Ssam 		if (mb->mb_harderr < NHERRS)
127032633Ssam 			cp = mpherrmsg[mb->mb_harderr];
127132633Ssam 		else
127232633Ssam 			cp = "unknown error";
127332633Ssam 		log(LOG_ERR, "mp%d: hard error, %s", unit, cp);
127432633Ssam 		if (mb->mb_status == MP_OPOPEN) {
127532633Ssam 			for (i = 0; i < MPMAXPORT; i++) {
127632633Ssam 				mpcleanport(mb, i);
127732633Ssam 				mb->mb_proto[i] = MPPROTO_UNUSED;
127832633Ssam 			}
127932633Ssam 		}
128032633Ssam 		mb->mb_harderr = 0;
128132633Ssam 		mb->mb_status = 0;
128232633Ssam 	}
128332633Ssam }
128432633Ssam 
128532633Ssam mppurge(addr, cc)
128632633Ssam 	register caddr_t addr;
128732633Ssam 	register int cc;
128832633Ssam {
128932633Ssam 
129032633Ssam 	for (; cc >= 0; addr += NBPG, cc -= NBPG)
129132633Ssam 		mtpr(P1DC, addr);
129232633Ssam }
129332633Ssam 
129432633Ssam /*
129532633Ssam  * MPCC Download Pseudo-device.
129632633Ssam  */
129732633Ssam char	mpdlbuf[MPDLBUFSIZE];
129832633Ssam int	mpdlbusy;		/* interlock on download buffer */
129932633Ssam int	mpdlerr;
130032633Ssam 
130132633Ssam mpdlopen(dev)
130232633Ssam 	dev_t dev;
130332633Ssam {
130432633Ssam 	int unit, mpu;
130532633Ssam 	struct vba_device *vi;
130632633Ssam 
130732633Ssam 	unit = minor(dev);
130832633Ssam 	mpu = MPUNIT(unit);
130932633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
131032633Ssam 		return (ENODEV);
131132633Ssam 	return (0);
131232633Ssam }
131332633Ssam 
131432633Ssam mpdlwrite(dev, uio)
131532633Ssam 	dev_t dev;
131632633Ssam 	struct uio *uio;
131732633Ssam {
131832633Ssam 	register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))];
131932633Ssam 	register struct mpdl *dl;
132032633Ssam 	int error;
132132633Ssam 
132232633Ssam 	if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN)
132332633Ssam 		return (EFAULT);
132432633Ssam 	dl = &ms->ms_mb->mb_dl;
132532633Ssam 	dl->mpdl_count = uio->uio_iov->iov_len;
132634506Skarels 	dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
132737751Smckusick 	if (error = uiomove(mpdlbuf, (int)dl->mpdl_count, uio))
132832633Ssam 		return (error);
132932633Ssam 	uio->uio_resid -= dl->mpdl_count;    /* set up return from write */
133032633Ssam 	dl->mpdl_cmd = MPDLCMD_NORMAL;
133132633Ssam 	error = mpdlwait(dl);
133232633Ssam 	return (error);
133332633Ssam }
133432633Ssam 
133532633Ssam mpdlclose(dev)
133632633Ssam 	dev_t dev;
133732633Ssam {
133832633Ssam 	register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb;
133932633Ssam 
134032633Ssam 	if (mb == 0 || mb->mb_status != MP_DLDONE) {
134132633Ssam 		mpbogus.status = 0;
134232633Ssam 		if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))])
134332633Ssam 			mpdlbusy--;
134432633Ssam 		return (EEXIST);
134532633Ssam 	}
134632633Ssam 	mb->mb_status = MP_OPOPEN;
134732633Ssam 	mpbogus.status = 0;
134832633Ssam 	/* set to dead, for board handshake */
134932633Ssam 	mb->mb_hostint.imok = MPIMOK_DEAD;
135032633Ssam 	return (0);
135132633Ssam }
135232633Ssam 
135334506Skarels /* ARGSUSED */
135432633Ssam mpdlioctl(dev, cmd, data, flag)
135532633Ssam 	dev_t dev;
135632633Ssam 	caddr_t data;
135732633Ssam {
135832633Ssam 	register struct mblok *mb;
135932633Ssam 	register struct mpdl *dl;
1360*40734Skarels 	int unit, error = 0, s, i;
136132633Ssam 
136232633Ssam 	mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb;
136332633Ssam 	if (mb == 0)
1364*40734Skarels 		 return (EEXIST);
136532633Ssam 	dl = &mb->mb_dl;
136632633Ssam 	error = 0;
136732633Ssam 	switch (cmd) {
136832633Ssam 	case MPIOPORTMAP:
136932633Ssam 		bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto));
137032633Ssam 		break;
137132633Ssam 	case MPIOHILO:
137232633Ssam 		bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport)));
137332633Ssam 		break;
137432633Ssam 	case MPIOENDDL:
137532633Ssam 		dl->mpdl_count = 0;
137632633Ssam 		dl->mpdl_data = 0;
137732633Ssam 		dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK;
137832633Ssam 		error = mpdlwait(dl);
137932633Ssam 		mpccinit(unit);
138032633Ssam 		mb->mb_status = MP_DLDONE;
138132633Ssam 		mpdlbusy--;
138232633Ssam 		break;
138332633Ssam 	case MPIOENDCODE:
138432633Ssam 		dl->mpdl_count = 0;
138532633Ssam 		dl->mpdl_data = 0;
138632633Ssam 		dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK;
138732633Ssam 		error = mpdlwait(dl);
138832633Ssam 		break;
138932633Ssam 	case MPIOASYNCNF:
139032633Ssam 		bcopy(data, mpdlbuf, sizeof (struct abdcf));
139134506Skarels 		dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
139232633Ssam 		dl->mpdl_count = sizeof (struct abdcf);
139332633Ssam 		dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK;
139432633Ssam 		error = mpdlwait(dl);
139532633Ssam 		break;
139632633Ssam 	case MPIOSTARTDL:
1397*40734Skarels 		s = spl8();
139832633Ssam 		while (mpdlbusy)
1399*40734Skarels 			if (error = tsleep((caddr_t)&mpdlbusy,
1400*40734Skarels 			    (PZERO+1) | PCATCH, devioc, 0))
1401*40734Skarels 				break;
1402*40734Skarels 		splx(s);
1403*40734Skarels 		if (error)
1404*40734Skarels 			break;
140532633Ssam 		mpdlbusy++;
140632633Ssam 		/* initialize the downloading interface */
140732633Ssam 		mpbogus.magic = MPMAGIC;
140832633Ssam 		mpbogus.mb = mpbogus.mbloks[unit];
140932633Ssam 		mpbogus.status = 1;
141032633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
141132633Ssam 		dl->mpdl_count = 0;
141232633Ssam 		dl->mpdl_cmd = 0;
141332633Ssam 		dl->mpdl_data = (char *) 0;
141432633Ssam 		mpdlerr = 0;
141532633Ssam 		mb->mb_magic = MPMAGIC;
141632633Ssam         	mb->mb_ivec = mp_softc[unit].ms_ivec+1;	/* download vector */
141732633Ssam 		mb->mb_status = MP_DLPEND;
141832633Ssam 		mb->mb_diagswitch[0] = 'A';
141932633Ssam 		mb->mb_diagswitch[1] = 'P';
142032633Ssam 		s = spl8();
142132633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 2;
1422*40734Skarels 		error = tsleep((caddr_t)&mb->mb_status, (PZERO+1) | PCATCH,
1423*40734Skarels 		    devio, 30*hz);
142432633Ssam 		splx(s);
1425*40734Skarels 		if (error == EWOULDBLOCK)
142632633Ssam 			error = ETIMEDOUT;
1427*40734Skarels 		if (error)
142832633Ssam 			mpbogus.status = 0;
142934506Skarels 		bzero((caddr_t)mb->mb_port, sizeof (mb->mb_port));
143032633Ssam 		break;
143132633Ssam 	case MPIORESETBOARD:
143232633Ssam 		s = spl8();
143332633Ssam 		if (mb->mb_imokclk)
143432633Ssam 			mb->mb_imokclk = 0;
143532633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 0x100;
143632633Ssam 		if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) {
143732633Ssam 			mpdlerr = MP_DLERROR;
143832633Ssam 			dl->mpdl_status = EVSTATUS_FREE;
143932633Ssam 			wakeup((caddr_t)&dl->mpdl_status);
144032633Ssam 			mpbogus.status = 0;
144132633Ssam 		}
144232633Ssam 		for (i = 0; i < MPMAXPORT; i++) {
144332633Ssam 			if (mb->mb_harderr || mb->mb_softerr)
144432633Ssam 				mperror(mb, i);
144532633Ssam 			mpcleanport(mb, i);
144632633Ssam 			mb->mb_proto[i] = MPPROTO_UNUSED;
144732633Ssam 		}
144832633Ssam 		mb->mb_status = 0;
144932633Ssam 		splx(s);
145032633Ssam 		break;
145132633Ssam 	default:
145232633Ssam 		error = EINVAL;
145332633Ssam 		break;
145432633Ssam 	}
145532633Ssam 	return (error);
145632633Ssam }
145732633Ssam 
145832633Ssam mpccinit(unit)
145932633Ssam 	int unit;
146032633Ssam {
146132633Ssam         register struct mblok *mb = mp_softc[unit].ms_mb;
146232633Ssam         register struct his *his;
146332633Ssam         register int i, j;
146432633Ssam 
146532633Ssam         mb->mb_status = MP_DLDONE;
146632633Ssam         mb->mb_ivec = mp_softc[unit].ms_ivec;
146732633Ssam         mb->mb_magic = MPMAGIC;
146832633Ssam         /* Init host interface structure */
146932633Ssam         his = &mb->mb_hostint;
147032633Ssam         his->semaphore = MPSEMA_AVAILABLE;
147132633Ssam         for (i = 0; i < NMPPROTO; i++)
147232633Ssam                 for (j = 0; j < MPMAXPORT; j++) {
147332633Ssam                         his->proto[i].inbdone[j] = MPPORT_EOL;
147432633Ssam                         his->proto[i].outbdone[j] = MPPORT_EOL;
147532633Ssam                 }
147632633Ssam         mb->mb_unit = unit;
147732633Ssam }
147832633Ssam 
147932633Ssam mpdlintr(mpcc)
148032633Ssam 	int mpcc;
148132633Ssam {
148232633Ssam 	register struct mblok *mb;
148332633Ssam 	register struct mpdl *dl;
148432633Ssam 
148532633Ssam 	mb = mp_softc[mpcc].ms_mb;
148632633Ssam 	if (mb == 0) {
148732633Ssam 		printf("mp%d: stray download interrupt\n", mpcc);
148832633Ssam 		return;
148932633Ssam 	}
149032633Ssam 	dl = &mb->mb_dl;
149132633Ssam 	switch (mb->mb_status) {
149232633Ssam 	case MP_DLOPEN:
149332633Ssam 		if (dl->mpdl_status != EVSTATUS_DONE)
149432633Ssam 			mpdlerr = MP_DLERROR;
149532633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
149632633Ssam 		wakeup((caddr_t)&dl->mpdl_status);
149732633Ssam 		return;
149832633Ssam 	case MP_DLPEND:
149932633Ssam 		mb->mb_status = MP_DLOPEN;
150034506Skarels 		wakeup((caddr_t)&mb->mb_status);
150132633Ssam 		/* fall thru... */
150232633Ssam 	case MP_DLTIME:
150332633Ssam 		return;
150432633Ssam 	case MP_OPOPEN:
150532633Ssam 		if (mb->mb_imokclk)
150632633Ssam 			mb->mb_imokclk = 0;
150732633Ssam 		mb->mb_nointcnt = 0;		/* reset no interrupt count */
150832633Ssam 		mb->mb_hostint.imok = MPIMOK_DEAD;
150932633Ssam 		mb->mb_imokclk = (caddr_t)1;
151032633Ssam 		break;
151132633Ssam 	default:
151232633Ssam 		log(LOG_ERR, "mp%d: mpdlintr, status %x\n",
151332633Ssam 		    mpcc, mb->mb_status);
151432633Ssam 		break;
151532633Ssam 	}
151632633Ssam }
151732633Ssam 
151832633Ssam /*
151932633Ssam  * Wait for a transfer to complete or a timeout to occur.
152032633Ssam  */
152132633Ssam mpdlwait(dl)
152232633Ssam 	register struct mpdl *dl;
152332633Ssam {
152432633Ssam 	int s, error = 0;
152532633Ssam 
152632633Ssam 	s = spl8();
152732633Ssam 	dl->mpdl_status = EVSTATUS_GO;
152832633Ssam 	while (dl->mpdl_status != EVSTATUS_FREE) {
1529*40734Skarels 		error = tsleep((caddr_t)&dl->mpdl_status, (PZERO+1) | PCATCH,
1530*40734Skarels 		    devout, 0);
153132633Ssam 		if (mpdlerr == MP_DLERROR)
153232633Ssam 			error = EIO;
1533*40734Skarels 		if (error)
1534*40734Skarels 			break;
153532633Ssam 	}
153632633Ssam 	splx(s);
153732633Ssam 	return (error);
153832633Ssam }
153932633Ssam #endif
1540