xref: /csrg-svn/sys/tahoe/vba/mp.c (revision 34796)
134506Skarels /*
234506Skarels  * Copyright (c) 1988 Regents of the University of California.
334506Skarels  * All rights reserved.
434506Skarels  *
534506Skarels  * Redistribution and use in source and binary forms are permitted
634506Skarels  * provided that this notice is preserved and that due credit is given
734506Skarels  * to the University of California at Berkeley. The name of the University
834506Skarels  * may not be used to endorse or promote products derived from this
934506Skarels  * software without specific prior written permission. This software
1034506Skarels  * is provided ``as is'' without express or implied warranty.
1134506Skarels  *
12*34796Sbostic  *	@(#)mp.c	7.2 (Berkeley) 06/18/88
1334506Skarels  */
1432633Ssam 
1532633Ssam #include "mp.h"
1632633Ssam #if NMP > 0
1732633Ssam /*
1832633Ssam  * Multi Protocol Communications Controller (MPCC).
1932633Ssam  * Asynchronous Terminal Protocol Support.
2032633Ssam  */
2132633Ssam #include "param.h"
2232633Ssam #include "ioctl.h"
2332633Ssam #include "tty.h"
2432633Ssam #include "dir.h"
2532633Ssam #include "user.h"
2632633Ssam #include "map.h"
2732633Ssam #include "buf.h"
2832633Ssam #include "conf.h"
2932633Ssam #include "file.h"
3032633Ssam #include "uio.h"
3132633Ssam #include "errno.h"
3232633Ssam #include "syslog.h"
3332633Ssam #include "vmmac.h"
3432633Ssam #include "kernel.h"
3532633Ssam #include "clist.h"
3632633Ssam 
3734506Skarels #include "../machine/pte.h"
3834506Skarels #include "../machine/mtpr.h"
3934506Skarels 
4032633Ssam #include "../tahoevba/vbavar.h"
4132633Ssam #include "../tahoevba/mpreg.h"
4232633Ssam 
4332633Ssam #define	MPCHUNK	16
4432633Ssam #define	MPPORT(n)	((n) & 0xf)
4532633Ssam #define	MPUNIT(n)	((n) >> 4)
4632633Ssam 
4732633Ssam /*
4832633Ssam  * Driver information for auto-configuration stuff.
4932633Ssam  */
5032633Ssam int     mpprobe(), mpattach(), mpintr();
5132633Ssam struct  vba_device *mpinfo[NMP];
5232633Ssam long    mpstd[] = { 0 };
5332633Ssam struct  vba_driver mpdriver =
5432633Ssam     { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo };
5532633Ssam 
5632633Ssam int	mpstart();
5732633Ssam struct	mpevent *mpparam();
5832633Ssam struct	mpevent *mp_getevent();
5932633Ssam 
6032633Ssam /*
6132633Ssam  * The following structure is needed to deal with mpcc's convoluted
6232633Ssam  * method for locating it's mblok structures (hold your stomach).
6332633Ssam  * When an mpcc is reset at boot time it searches host memory
6432633Ssam  * looking for a string that says ``ThIs Is MpCc''.  The mpcc
6532633Ssam  * then reads the structure to locate the pointer to it's mblok
6632633Ssam  * structure (you can wretch now).
6732633Ssam  */
6832633Ssam struct mpbogus {
6932633Ssam 	char	s[12];			/* `ThIs Is MpCc'' */
7032633Ssam 	u_char	status;
7132633Ssam 	u_char	unused;
7232633Ssam 	u_short	magic;
7332633Ssam 	struct	mblok *mb;
7432633Ssam 	struct	mblok *mbloks[NMP];	/* can support at most 16 mpcc's */
7532633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' };
7632633Ssam 
7732633Ssam /*
7832633Ssam  * Software state per unit.
7932633Ssam  */
8032633Ssam struct	mpsoftc {
8132633Ssam 	u_int	ms_ivec;		/* interrupt vector */
8232633Ssam 	u_int	ms_softCAR;		/* software carrier for async */
8332633Ssam 	struct	mblok *ms_mb;		/* mpcc status area */
8432633Ssam 	struct	vb_buf ms_buf;		/* vba resources for ms_mb */
8532633Ssam 	struct	hxmtl ms_hxl[MPMAXPORT];/* host transmit list */
8632633Ssam 	struct	asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */
8732633Ssam 	char	ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */
8832633Ssam } mp_softc[NMP];
8932633Ssam 
9032633Ssam struct	tty mp_tty[NMP*MPCHUNK];
9132633Ssam #ifndef lint
9232633Ssam int	nmp = NMP*MPCHUNK;
9332633Ssam #endif
9432633Ssam 
9532633Ssam int	ttrstrt();
9632633Ssam 
9732633Ssam mpprobe(reg, vi)
9832633Ssam 	caddr_t reg;
9932633Ssam 	struct vba_device *vi;
10032633Ssam {
10132633Ssam 	register int br, cvec;
10232633Ssam 	register struct mpsoftc *ms;
10332633Ssam 
10432633Ssam #ifdef lint
10532633Ssam 	br = 0; cvec = br; br = cvec;
10632633Ssam 	mpintr(0);
10734506Skarels 	mpdlintr(0);
10832633Ssam #endif
10932633Ssam 	if (badaddr(reg, 2))
11032633Ssam 		return (0);
11132633Ssam 	ms = &mp_softc[vi->ui_unit];
11232633Ssam 	/*
11332633Ssam 	 * Allocate page tables and mblok
11432633Ssam 	 * structure (mblok in non-cached memory).
11532633Ssam 	 */
11632633Ssam 	if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) {
11732633Ssam 		printf("mp%d: vbainit failed\n", vi->ui_unit);
11832633Ssam 		return (0);
11932633Ssam 	}
12032633Ssam 	ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf;
12132633Ssam 	ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit;	/* XXX */
12232633Ssam 	br = 0x14, cvec = ms->ms_ivec;			/* XXX */
12334287Skarels 	return (sizeof (*reg));
12432633Ssam }
12532633Ssam 
12632633Ssam mpattach(vi)
12732633Ssam 	register struct vba_device *vi;
12832633Ssam {
12932633Ssam 	register struct mpsoftc *ms = &mp_softc[vi->ui_unit];
13032633Ssam 
13132633Ssam 	ms->ms_softCAR = vi->ui_flags;
13232633Ssam 	/*
13332633Ssam 	 * Setup pointer to mblok, initialize bogus
13432633Ssam 	 * status block used by mpcc to locate the pointer
13532633Ssam 	 * and then poke the mpcc to get it to search host
13632633Ssam 	 * memory to find mblok pointer.
13732633Ssam 	 */
13832633Ssam 	mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf;
13932633Ssam 	*(short *)vi->ui_addr = 0x100;		/* magic */
14032633Ssam }
14132633Ssam 
14232633Ssam /*
14332633Ssam  * Open an mpcc port.
14432633Ssam  */
14534506Skarels /* ARGSUSED */
14632633Ssam mpopen(dev, mode)
14732633Ssam 	dev_t dev;
14832633Ssam {
14932633Ssam 	register struct tty *tp;
15032633Ssam 	register struct mpsoftc *ms;
15132633Ssam 	int error, s, port, unit, mpu;
15232633Ssam 	struct vba_device *vi;
15332633Ssam 	struct mpport *mp;
15432633Ssam 	struct mpevent *ev;
15532633Ssam 
15632633Ssam 	unit = minor(dev);
15732633Ssam 	mpu = MPUNIT(unit);
15832633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
15932633Ssam 		return (ENXIO);
16032633Ssam 	tp = &mp_tty[unit];
16132633Ssam 	if (tp->t_state & TS_XCLUDE && u.u_uid != 0)
16232633Ssam 		return (EBUSY);
16332633Ssam 	ms = &mp_softc[mpu];
16432633Ssam 	port = MPPORT(unit);
16532633Ssam 	if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC ||
16632633Ssam 	    ms->ms_mb->mb_status != MP_OPOPEN)
16732633Ssam 		return (ENXIO);
16832633Ssam 	mp = &ms->ms_mb->mb_port[port];		/* host mpcc struct */
16932633Ssam 	s = spl8();
17032633Ssam 	while (mp->mp_flags & MP_PROGRESS)
17132633Ssam 		sleep((caddr_t)&tp->t_canq, TTIPRI);
17232633Ssam 	while (tp->t_state & TS_WOPEN)
17332633Ssam 		sleep((caddr_t)&tp->t_canq, TTIPRI);
17432633Ssam 	if (tp->t_state & TS_ISOPEN) {
17532633Ssam 		splx(s);
17632633Ssam 		return (0);
17732633Ssam 	}
17832633Ssam 	tp->t_state |= TS_WOPEN;
17932633Ssam 	tp->t_addr = (caddr_t)ms;
18032633Ssam 	tp->t_oproc = mpstart;
18132633Ssam 	tp->t_dev = dev;
18232633Ssam 	ttychars(tp);
18332633Ssam 	if (tp->t_ispeed == 0) {
18432633Ssam 		tp->t_ispeed = B9600;
18532633Ssam 		tp->t_ospeed = B9600;
18632633Ssam 		tp->t_flags |= ODDP|EVENP|ECHO;
18732633Ssam 	}
18832633Ssam 	/*
18932633Ssam 	 * Initialize port state: init MPCC interface
19032633Ssam 	 * structures for port and setup modem control.
19132633Ssam 	 */
19232633Ssam 	mp->mp_proto = MPPROTO_ASYNC;		/* XXX */
19332633Ssam 	error = mpportinit(ms, mp, port);
19432633Ssam 	if (error)
19532633Ssam 		goto bad;
19632633Ssam 	ev = mpparam(unit);
19732633Ssam 	if (ev == 0) {
19832633Ssam 		error = ENOBUFS;
19932633Ssam 		goto bad;
20032633Ssam 	}
20132633Ssam 	mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port);
20232633Ssam 	while ((tp->t_state & TS_CARR_ON) == 0)
20332633Ssam 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
20432633Ssam 	error = mpmodem(unit, MMOD_ON);
20532633Ssam 	if (error)
20632633Ssam 		goto bad;
20732633Ssam 	while ((tp->t_state & TS_CARR_ON) == 0)
20832633Ssam 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
20932633Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
21032633Ssam done:
21132633Ssam 	splx(s);
21232633Ssam 	/* wakeup anyone waiting for open to complete */
21332633Ssam 	wakeup((caddr_t)&tp->t_canq);
21432633Ssam 
21532633Ssam 	return (error);
21632633Ssam bad:
21732633Ssam 	tp->t_state &= ~TS_WOPEN;
21832633Ssam 	goto done;
21932633Ssam }
22032633Ssam 
22132633Ssam /*
22232633Ssam  * Close an mpcc port.
22332633Ssam  */
22434506Skarels /* ARGSUSED */
22534506Skarels mpclose(dev, flag)
22632633Ssam 	dev_t dev;
22732633Ssam {
22832633Ssam 	register struct tty *tp;
22932633Ssam 	register struct mpport *mp;
23032633Ssam 	register struct mpevent *ev;
23132633Ssam 	int s, port, unit, error;
23232633Ssam 	struct mblok *mb;
23332633Ssam 
23432633Ssam 	unit = minor(dev);
23532633Ssam 	tp = &mp_tty[unit];
23632633Ssam 	port = MPPORT(unit);
23732633Ssam 	mb = mp_softc[MPUNIT(unit)].ms_mb;
23832633Ssam 	mp = &mb->mb_port[port];
23932633Ssam 	s = spl8();
24032633Ssam 	if (mp->mp_flags & MP_PROGRESS) {		/* close in progress */
24132633Ssam 		if (mp->mp_flags & MP_REMBSY) {
24232633Ssam 			mp->mp_flags &= ~MP_REMBSY;
24332633Ssam 			splx(s);
24432633Ssam 			return (0);
24532633Ssam 		}
24632633Ssam 		while (mp->mp_flags & MP_PROGRESS)
24732633Ssam 			sleep((caddr_t)&tp->t_canq,TTIPRI);
24832633Ssam 	}
24932633Ssam 	error = 0;
25032633Ssam 	mp->mp_flags |= MP_PROGRESS;
25132633Ssam 	(*linesw[tp->t_line].l_close)(tp);
25232633Ssam 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
25332633Ssam 		if (error = mpmodem(unit, MMOD_OFF)) {
25432633Ssam 			mp->mp_flags &= ~MP_PROGRESS;
25532633Ssam 			goto out;
25632633Ssam 		}
25732633Ssam 	while (tp->t_state & TS_FLUSH)			/* ??? */
25832633Ssam 		sleep((caddr_t)&tp->t_state, TTOPRI);	/* ??? */
25932633Ssam 	ttyclose(tp);
26032633Ssam 	ev = mp_getevent(mp, unit);
26132633Ssam 	if (ev == 0) {
26232633Ssam 		 error = ENOBUFS;
26332633Ssam 		 goto out;
26432633Ssam 	}
26532633Ssam 	mpcmd(ev, EVCMD_CLOSE, 0, mb, port);
26632633Ssam out:
26732633Ssam 	if (mp->mp_flags & MP_REMBSY)
26832633Ssam 		mpclean(mb, port);
26932633Ssam 	splx(s);
27032633Ssam 	return (error);
27132633Ssam }
27232633Ssam 
27332633Ssam /*
27432633Ssam  * Read from an mpcc port.
27532633Ssam  */
27632633Ssam mpread(dev, uio)
27732633Ssam 	dev_t dev;
27832633Ssam 	struct uio *uio;
27932633Ssam {
28032633Ssam 	struct tty *tp;
28132633Ssam 
28232633Ssam 	tp = &mp_tty[minor(dev)];
28332633Ssam 	return ((*linesw[tp->t_line].l_read)(tp, uio));
28432633Ssam }
28532633Ssam 
28632633Ssam /*
28732633Ssam  * Write to an mpcc port.
28832633Ssam  */
28932633Ssam mpwrite(dev, uio)
29032633Ssam 	dev_t dev;
29132633Ssam 	struct uio *uio;
29232633Ssam {
29332633Ssam 	struct tty *tp;
29432633Ssam 
29532633Ssam 	tp = &mp_tty[minor(dev)];
29632633Ssam 	return ((*linesw[tp->t_line].l_write)(tp, uio));
29732633Ssam }
29832633Ssam 
29932633Ssam /*
30032633Ssam  * Ioctl for a mpcc port
30132633Ssam  */
30232633Ssam mpioctl(dev, cmd, data, flag)
30332633Ssam 	dev_t dev;
30432633Ssam 	caddr_t data;
30532633Ssam {
30632633Ssam 	register struct tty *tp;
30732633Ssam 	register struct mpsoftc *ms;
30832633Ssam 	register struct mpevent *ev;
30932633Ssam 	register struct mpport *mp;
31032633Ssam 	int s, port, error, unit;
31132633Ssam 	struct mblok *mb;
31232633Ssam 
31332633Ssam 	unit = minor(dev);
31432633Ssam 	tp = &mp_tty[unit];
31532633Ssam 	ms = &mp_softc[MPUNIT(unit)];
31632633Ssam 	mb = ms->ms_mb;
31732633Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
31832633Ssam 	if (error >= 0)
31932633Ssam 		return (error);
32032633Ssam 	error = ttioctl(tp, cmd, data, flag);
32132633Ssam 	if (error >= 0) {
32232633Ssam 		if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS ||
323*34796Sbostic 		    cmd == TIOCLBIC || cmd == TIOCLSET || cmd == TIOCSETC) {
32432633Ssam 			ev = mpparam(unit);
32532633Ssam 			if (ev == 0)
32632633Ssam 				error = ENOBUFS;
32732633Ssam 			else
32832633Ssam 				mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb,
32932633Ssam 				    MPPORT(unit));
33032633Ssam 		}
33132633Ssam 		return (error);
33232633Ssam 	}
33332633Ssam 	switch (cmd) {
33432633Ssam 	case TIOCSBRK:			/* send break */
33532633Ssam 	case TIOCCBRK:			/* clear break */
33632633Ssam 		port = MPPORT(unit);
33732633Ssam 		mp = &mb->mb_port[port];
33832633Ssam 		s = spl8();
33932633Ssam 		ev = mp_getevent(mp, unit);
34032633Ssam 		if (ev)
34132633Ssam 			mpcmd(ev, EVCMD_IOCTL,
34232633Ssam 			    (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF),
34332633Ssam 			    mb, port);
34432633Ssam 		else
34532633Ssam 			error = ENOBUFS;
34632633Ssam 		splx(s);
34732633Ssam 		break;
34832633Ssam 	case TIOCSDTR:			/* set dtr control line */
34932633Ssam 		break;
35032633Ssam 	case TIOCCDTR:			/* clear dtr control line */
35132633Ssam 		break;
35232633Ssam 	default:
35332633Ssam 		error = ENOTTY;
35432633Ssam 		break;
35532633Ssam 	}
35632633Ssam 	return (error);
35732633Ssam }
35832633Ssam 
35932633Ssam struct mpevent *
36032633Ssam mpparam(unit)
36132633Ssam 	int unit;
36232633Ssam {
36332633Ssam 	register struct mpevent *ev;
36432633Ssam 	register struct mpport *mp;
36532633Ssam 	register struct tty *tp;
36632633Ssam 	struct mblok *mb;
36732633Ssam 	struct mpsoftc *ms;
36832633Ssam 	register struct asyncparam *asp;
36932633Ssam 	int port;
37032633Ssam 
37132633Ssam 	ms = &mp_softc[MPUNIT(unit)];
37232633Ssam 	mb = ms->ms_mb;
37332633Ssam 	port = MPPORT(unit);
37432633Ssam 	mp = &mb->mb_port[port];
37532633Ssam 	ev = mp_getevent(mp, unit);	/* XXX */
37632633Ssam 	if (ev == 0)
37732633Ssam 		return (ev);
37832633Ssam 	tp = &mp_tty[unit];
37932633Ssam 	/* YUCK */
38032633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
381*34796Sbostic 	asp->ap_xon = (u_char)tp->t_startc;
382*34796Sbostic 	asp->ap_xoff = (u_char)tp->t_stopc;
383*34796Sbostic 	if ((tp->t_flags & RAW) || (tp->t_stopc == -1) || (tp->t_startc == -1))
384*34796Sbostic 		asp->ap_xena = MPA_DIS;
385*34796Sbostic 	else
386*34796Sbostic 		asp->ap_xena = MPA_ENA;
38733995Sbostic 	asp->ap_xany = ((tp->t_flags & DECCTQ) ? MPA_DIS : MPA_ENA);
38832633Ssam #ifdef notnow
38932633Ssam 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {
39032633Ssam #endif
39132633Ssam 		asp->ap_data = MPCHAR_8;
39232633Ssam 		asp->ap_parity = MPPAR_NONE;
39332633Ssam #ifdef notnow
39432633Ssam 	} else {
39532633Ssam 		asp->ap_data = MPCHAR_7;
39632633Ssam 		if ((tp->t_flags & (EVENP|ODDP)) == ODDP)
39732633Ssam 			asp->ap_parity = MPPAR_ODD;
39832633Ssam 		else
39932633Ssam 			asp->ap_parity = MPPAR_EVEN;
40032633Ssam 	}
40132633Ssam #endif
40232633Ssam 	if (tp->t_ospeed == B110)
40332633Ssam 		asp->ap_stop = MPSTOP_2;
40432633Ssam 	else
40532633Ssam 		asp->ap_stop = MPSTOP_1;
40632633Ssam 	if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB)
40732633Ssam 		asp->ap_baud = M19200;
40832633Ssam 	else
40932633Ssam 		asp->ap_baud = tp->t_ospeed;
41032633Ssam 	asp->ap_loop = MPA_DIS;		/* disable loopback */
41132633Ssam 	asp->ap_rtimer = A_RCVTIM;	/* default receive timer */
41232633Ssam 	if (ms->ms_softCAR & (1<<port))
41332633Ssam 		setm(&asp->ap_modem, A_DTR, ASSERT);
41432633Ssam 	else
41532633Ssam 		setm(&asp->ap_modem, A_DTR, AUTO);
41632633Ssam 	seti(&asp->ap_intena, A_DCD);
41732633Ssam 	return (ev);
41832633Ssam }
41932633Ssam 
42032633Ssam mpstart(tp)
42132633Ssam 	register struct tty *tp;
42232633Ssam {
42332633Ssam 	register struct mpevent *ev;
42432633Ssam 	register struct mpport *mp;
42532633Ssam 	struct mblok *mb;
42632633Ssam 	struct mpsoftc *ms;
42732633Ssam 	int port, unit, xcnt, n, s, i;
42832633Ssam 	struct	hxmtl *hxp;
42932633Ssam 	struct clist outq;
43032633Ssam 
43132633Ssam 	s = spl8();
43232633Ssam 	unit = minor(tp->t_dev);
43332633Ssam 	ms = &mp_softc[MPUNIT(unit)];
43432633Ssam 	mb = ms->ms_mb;
43532633Ssam 	port = MPPORT(unit);
43632633Ssam 	mp = &mb->mb_port[port];
43732633Ssam 	hxp = &ms->ms_hxl[port];
43832633Ssam 	xcnt = 0;
43932633Ssam 	outq = tp->t_outq;
44032633Ssam 	for (i = 0; i < MPXMIT; i++) {
44132633Ssam 		if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP))
44232633Ssam 			break;
44332633Ssam 		if (outq.c_cc <= TTLOWAT(tp)) {
44432633Ssam 			if (tp->t_state & TS_ASLEEP) {
44532633Ssam 				tp->t_state &= ~TS_ASLEEP;
44632633Ssam 				wakeup((caddr_t)&tp->t_outq);
44732633Ssam 			}
44832633Ssam 			if (tp->t_wsel) {
44932633Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
45032633Ssam 				tp->t_wsel = 0;
45132633Ssam 				tp->t_state &= ~TS_WCOLL;
45232633Ssam 			}
45332633Ssam 		}
45432633Ssam 		if (outq.c_cc == 0)
45532633Ssam 			break;
45632633Ssam 		/*
45732633Ssam 		 * If we're not currently busy outputting,
45832633Ssam 		 * and there is data to be output, set up
45932633Ssam 		 * port transmit structure to send to mpcc.
46032633Ssam 		 */
46132633Ssam 		if (tp->t_flags & (RAW|LITOUT))
46232633Ssam 			n = ndqb(&outq, 0);
46332633Ssam 		else {
46432633Ssam 			n = ndqb(&outq, 0200);
46532633Ssam 			if (n == 0) {
46632633Ssam 				n = getc(&outq);
46732633Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
46832633Ssam 				tp->t_state |= TS_TIMEOUT;
46932633Ssam 				break;
47032633Ssam 			}
47132633Ssam 		}
47234506Skarels 		hxp->dblock[i] = (caddr_t)kvtophys(outq.c_cf);
47332633Ssam 		hxp->size[i] = n;
47432633Ssam 		xcnt++;		/* count of xmts to send */
47532633Ssam 		ndadvance(&outq, n);
47632633Ssam 	}
47732633Ssam 	/*
47832633Ssam 	 * If data to send, poke mpcc.
47932633Ssam 	 */
48032633Ssam 	if (xcnt) {
48132633Ssam 		ev = mp_getevent(mp, unit);
48232633Ssam 		if (ev == 0) {
48332633Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
48432633Ssam 		} else {
48532633Ssam 			tp->t_state |= TS_BUSY;
48632633Ssam 			ev->ev_count = xcnt;
48732633Ssam 			mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit));
48832633Ssam 		}
48932633Ssam 	}
49032633Ssam 	splx(s);
49132633Ssam }
49232633Ssam 
49332633Ssam /*
49432633Ssam  * Advance cc bytes from q  but don't free memory.
49532633Ssam  */
49632633Ssam ndadvance(q, cc)
49732633Ssam 	register struct clist *q;
49832633Ssam 	register cc;
49932633Ssam {
50032633Ssam 	register struct cblock *bp;
50132633Ssam 	char *end;
50232633Ssam 	int rem, s;
50332633Ssam 
50432633Ssam 	s = spltty();
50532633Ssam 	if (q->c_cc <= 0)
50632633Ssam 		goto out;
50732633Ssam 	while (cc>0 && q->c_cc) {
50832633Ssam 		bp = (struct cblock *)((int)q->c_cf & ~CROUND);
50932633Ssam 		if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) {
51032633Ssam 			end = q->c_cl;
51132633Ssam 		} else {
51232633Ssam 			end = (char *)((int)bp + sizeof (struct cblock));
51332633Ssam 		}
51432633Ssam 		rem = end - q->c_cf;
51532633Ssam 		if (cc >= rem) {
51632633Ssam 			cc -= rem;
51732633Ssam 			q->c_cc -= rem;
51832633Ssam 			q->c_cf = bp->c_next->c_info;
51932633Ssam 		} else {
52032633Ssam 			q->c_cc -= cc;
52132633Ssam 			q->c_cf += cc;
52232633Ssam 			break;
52332633Ssam 		}
52432633Ssam 	}
52532633Ssam 	if (q->c_cc <= 0) {
52632633Ssam 		q->c_cf = q->c_cl = NULL;
52732633Ssam 		q->c_cc = 0;
52832633Ssam 	}
52932633Ssam out:
53032633Ssam 	splx(s);
53132633Ssam }
53232633Ssam 
53332633Ssam /*
53432633Ssam  * Stop output on a line, e.g. for ^S/^Q or output flush.
53532633Ssam  */
53634506Skarels /* ARGSUSED */
53732633Ssam mpstop(tp, rw)
53832633Ssam 	register struct tty *tp;
53932633Ssam 	int rw;
54032633Ssam {
54134506Skarels 	int s;
54232633Ssam 
54332633Ssam 	s = spl8();
54432633Ssam 	/* XXX: DISABLE TRANSMITTER */
54532633Ssam 	if (tp->t_state & TS_BUSY) {
54632633Ssam 		if ((tp->t_state & TS_TTSTOP) == 0)
54732633Ssam 			tp->t_state |= TS_FLUSH;
54832633Ssam 	}
54932633Ssam 	splx(s);
55032633Ssam }
55132633Ssam 
55232633Ssam /*
55332633Ssam  * Initialize an async port's MPCC state.
55432633Ssam  */
55532633Ssam mpportinit(ms, mp, port)
55632633Ssam 	register struct mpsoftc *ms;
55732633Ssam 	register struct mpport *mp;
55832633Ssam 	int port;
55932633Ssam {
56032633Ssam 	register struct mpevent *ev;
56132633Ssam 	register int i;
56232633Ssam 	caddr_t ptr;
56332633Ssam 
56432633Ssam 	mp->mp_on = mp->mp_off = 0;
56532633Ssam 	mp->mp_nextrcv = 0;
56632633Ssam 	mp->mp_flags = 0;
56732633Ssam 	ev = &mp->mp_recvq[0];
56832633Ssam 	for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) {
56932633Ssam 		ev->ev_status = EVSTATUS_FREE;
57032633Ssam 		ev->ev_cmd = 0;
57132633Ssam 		ev->ev_opts = 0;
57232633Ssam 		ev->ev_error = 0;
57332633Ssam 		ev->ev_flags = 0;
57432633Ssam 		ev->ev_count = 0;
57534506Skarels 		ev->ev_un.hxl = (struct hxmtl *) kvtophys(&ms->ms_hxl[port]);
57634506Skarels 		ev->ev_params = (caddr_t) kvtophys(&ms->ms_async[port][i]);
57732633Ssam 	}
57832633Ssam 	ev = &mp->mp_sendq[0];
57932633Ssam 	for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) {
58032633Ssam 		/* init so that L2 can't send any events */
58132633Ssam 		/* to host until open has completed      */
58232633Ssam 		ev->ev_status = EVSTATUS_FREE;
58332633Ssam 		ev->ev_cmd = 0;
58432633Ssam 		ev->ev_error = 0;
58532633Ssam 		ev->ev_flags = 0;
58632633Ssam 		ev->ev_count = 0;
58732633Ssam 		ptr = (caddr_t) &ms->ms_cbuf[port][i][0];
58834506Skarels 		ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
58934506Skarels 		ev->ev_params = (caddr_t) kvtophys(ptr);
59032633Ssam 	}
59132633Ssam 	return (0);
59232633Ssam }
59332633Ssam 
59432633Ssam /*
59532633Ssam  * Send an event to an mpcc.
59632633Ssam  */
59732633Ssam mpcmd(ev, cmd, flags, mb, port)
59832633Ssam 	register struct mpevent *ev;
59932633Ssam 	struct mblok *mb;
60032633Ssam {
60132633Ssam 	int s;
60232633Ssam 
60332633Ssam 	s = spl8();
60432633Ssam 	/* move host values to inbound entry */
60532633Ssam 	ev->ev_cmd = cmd;
60632633Ssam 	ev->ev_opts = flags;
60732633Ssam 	/* show event ready for mpcc */
60832633Ssam 	ev->ev_status = EVSTATUS_GO;
60932633Ssam 	mpintmpcc(mb, port);
61032633Ssam 	splx(s);
61132633Ssam }
61232633Ssam 
61332633Ssam /*
61432633Ssam  * Return the next available event entry for the indicated port.
61532633Ssam  */
61632633Ssam struct mpevent *
61732633Ssam mp_getevent(mp, unit)
61832633Ssam 	register struct mpport *mp;
61932633Ssam 	int unit;
62032633Ssam {
62132633Ssam 	register struct mpevent *ev;
62232633Ssam 	int i, s;
62332633Ssam 
62432633Ssam 	s = spl8();
62532633Ssam 	ev = &mp->mp_recvq[mp->mp_on];
62632633Ssam 	if (ev->ev_status != EVSTATUS_FREE)
62732633Ssam 		goto bad;
62832633Ssam 	/*
62932633Ssam 	 * If not a close request, verify one extra
63032633Ssam 	 * event is available for closing the port.
63132633Ssam 	 */
63234506Skarels 	if ((mp->mp_flags & MP_PROGRESS) == 0) {
63332633Ssam 		if ((i = mp->mp_on + 1) >= MPINSET)
63432633Ssam 			i = 0;
63532633Ssam 		if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE)
63632633Ssam 			goto bad;
63732633Ssam 	}
63832633Ssam 	/* init inbound fields marking this entry as busy */
63932633Ssam 	ev->ev_error = 0;
64032633Ssam 	ev->ev_flags = 0;
64132633Ssam 	ev->ev_count = 0;
64232633Ssam 	ev->ev_status = EVSTATUS_BUSY;
64332633Ssam 	/* adjust pointer to next available inbound entry */
64432633Ssam 	adjptr(mp->mp_on, MPINSET);
64532633Ssam 	splx(s);
64632633Ssam 	return (ev);
64732633Ssam bad:
64832633Ssam 	splx(s);
64932633Ssam 	log(LOG_ERR, "mp%d: port%d, out of events", MPUNIT(unit), MPPORT(unit));
65032633Ssam 	return ((struct mpevent *)0);
65132633Ssam }
65232633Ssam 
65332633Ssam mpmodem(unit, flag)
65432633Ssam 	int unit, flag;
65532633Ssam {
65632633Ssam 	struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
65732633Ssam 	int port = MPPORT(unit);
65832633Ssam 	register struct mpport *mp;
65932633Ssam 	register struct mpevent *ev;
66032633Ssam 	register struct asyncparam *asp;
66132633Ssam 
66232633Ssam 	mp = &ms->ms_mb->mb_port[port];
66332633Ssam 	ev = mp_getevent(mp, unit);
66432633Ssam 	if (ev == 0)
66532633Ssam 		return (ENOBUFS);
66632633Ssam 	/* YUCK */
66732633Ssam 	asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
66832633Ssam 	if (flag == MMOD_ON) {
66932633Ssam 		if (ms->ms_softCAR & (1 << port))
67032633Ssam 			setm(&asp->ap_modem, A_DTR, ASSERT);
67132633Ssam 		else
67232633Ssam 			setm(&asp->ap_modem, A_DTR, AUTO);
67332633Ssam 		seti(&asp->ap_intena, A_DCD);
67432633Ssam 	} else {
67532633Ssam 		setm(&asp->ap_modem, 0, DROP);
67632633Ssam 		seti(&asp->ap_intena, 0);
67732633Ssam 	}
67832633Ssam 	mpcmd(ev, EVCMD_IOCTL, A_MDMCHG, ms->ms_mb, port);
67932633Ssam 	return (0);
68032633Ssam }
68132633Ssam 
68232633Ssam /*
68332633Ssam  * Set up the modem control structure according to mask.
68432633Ssam  * Each set bit in the mask means assert the corresponding
68532633Ssam  * modem control line, otherwise, it will be dropped.
68632633Ssam  * RTS is special since it can either be asserted, dropped
68732633Ssam  * or put in auto mode for auto modem control.
68832633Ssam  */
68932633Ssam static
69032633Ssam setm(mc, mask, rts)
69132633Ssam 	register struct mdmctl *mc;
69232633Ssam 	register int mask;
69332633Ssam {
69432633Ssam 
69532633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP;
69632633Ssam 	mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP;
69732633Ssam 	mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP;
69832633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP;
69932633Ssam 	mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP;
70032633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP;
70132633Ssam 	mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP;
70232633Ssam 	mc->mc_rts = rts;
70332633Ssam }
70432633Ssam 
70532633Ssam /*
70632633Ssam  * Set up the status change enable field from mask.
70732633Ssam  * When a signal is enabled in this structure and
70832633Ssam  * and a change in state on a corresponding modem
70932633Ssam  * control line occurs, a status change event will
71032633Ssam  * be delivered to the host.
71132633Ssam  */
71232633Ssam static
71332633Ssam seti(mc, mask)
71432633Ssam 	register struct mdmctl *mc;
71532633Ssam 	register int mask;
71632633Ssam {
71732633Ssam 
71832633Ssam 	mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF;
71932633Ssam 	mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF;
72032633Ssam 	mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF;
72132633Ssam 	mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF;
72232633Ssam 	mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF;
72332633Ssam 	mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF;
72432633Ssam 	mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF;
72532633Ssam 	mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF;
72632633Ssam }
72732633Ssam 
72832633Ssam mpcleanport(mb, port)
72932633Ssam 	struct mblok *mb;
73032633Ssam 	int port;
73132633Ssam {
73232633Ssam 	register struct mpport *mp;
73332633Ssam 	register struct tty *tp;
73432633Ssam 
73532633Ssam 	mp = &mb->mb_port[port];
73632633Ssam 	if (mp->mp_proto == MPPROTO_ASYNC) {
73732633Ssam 		mp->mp_flags = MP_REMBSY;
73834506Skarels 		/* signal loss of carrier and close */
73932633Ssam 		tp = &mp_tty[mb->mb_unit*MPCHUNK+port];
74032633Ssam 		ttyflush(tp, FREAD|FWRITE);
74134506Skarels 		(void) (*linesw[tp->t_line].l_modem)(tp, 0);
74234506Skarels 		(void) mpclose(tp->t_dev, 0);
74332633Ssam 	}
74432633Ssam }
74532633Ssam 
74632633Ssam mpclean(mb, port)
74732633Ssam 	register struct mblok *mb;
74832633Ssam 	int port;
74932633Ssam {
75032633Ssam 	register struct mpport *mp;
75132633Ssam 	register struct mpevent *ev;
75232633Ssam 	register int i;
75334506Skarels 	u_char list[2];
75432633Ssam 	int unit;
75532633Ssam 
75632633Ssam 	mp = &mb->mb_port[port];
75732633Ssam 	unit = mb->mb_unit;
75832633Ssam 	for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) {
75932633Ssam 		ev = &mp->mp_recvq[i];
76032633Ssam 		ev->ev_error = ENXIO;
76132633Ssam 		ev->ev_status = EVSTATUS_DONE;
76232633Ssam 	}
76332633Ssam 	list[0] = port, list[1] = MPPORT_EOL;
76432633Ssam 	mpxintr(unit, list);
76532633Ssam 	mprintr(unit, list);
76632633Ssam 	/* Clear async for port */
76732633Ssam 	mp->mp_proto = MPPROTO_UNUSED;
76832633Ssam 	mp->mp_flags = 0;
76932633Ssam 	mp->mp_on = 0;
77032633Ssam 	mp->mp_off = 0;
77132633Ssam 	mp->mp_nextrcv = 0;
77232633Ssam 
77332633Ssam 	mp_tty[unit*MPCHUNK + port].t_state = 0;
77432633Ssam 	for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) {
77532633Ssam 		ev->ev_status = EVSTATUS_FREE;
77632633Ssam 		ev->ev_cmd = 0;
77732633Ssam 		ev->ev_error = 0;
77832633Ssam 		ev->ev_un.rcvblk = 0;
77932633Ssam 		ev->ev_params = 0;
78032633Ssam 	}
78132633Ssam 	for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) {
78232633Ssam 		ev->ev_status = EVSTATUS_FREE;
78332633Ssam 		ev->ev_cmd = 0;
78432633Ssam 		ev->ev_error = 0;
78532633Ssam 		ev->ev_params = 0;
78632633Ssam 	}
78732633Ssam }
78832633Ssam 
78932633Ssam /*
79032633Ssam  * MPCC interrupt handler.
79132633Ssam  */
79232633Ssam mpintr(mpcc)
79332633Ssam 	int mpcc;
79432633Ssam {
79532633Ssam 	register struct mblok *mb;
79632633Ssam 	register struct his *his;
79732633Ssam 
79832633Ssam 	mb = mp_softc[mpcc].ms_mb;
79932633Ssam 	if (mb == 0) {
80032633Ssam 		printf("mp%d: stray interrupt\n", mpcc);
80132633Ssam 		return;
80232633Ssam 	}
80332633Ssam 	his = &mb->mb_hostint;
80432633Ssam 	his->semaphore &= ~MPSEMA_AVAILABLE;
80532633Ssam 	/*
80632633Ssam 	 * Check for events to be processed.
80732633Ssam 	 */
80832633Ssam 	if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL)
80932633Ssam 		mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone);
81032633Ssam 	if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL)
81132633Ssam 		mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone);
81232633Ssam 	if (mb->mb_harderr || mb->mb_softerr)
81332633Ssam 		mperror(mb, mpcc);
81432633Ssam 	his->semaphore |= MPSEMA_AVAILABLE;
81532633Ssam }
81632633Ssam 
81732633Ssam /*
81832633Ssam  * Handler for processing completion of transmitted events.
81932633Ssam  */
82032633Ssam mpxintr(unit, list)
82134506Skarels 	register u_char *list;
82232633Ssam {
82332633Ssam 	register struct mpport *mp;
82432633Ssam 	register struct mpevent *ev;
82532633Ssam 	register struct mblok *mb;
82632633Ssam 	register struct tty *tp;
82732633Ssam 	register struct asyncparam *ap;
82832633Ssam 	struct mpsoftc *ms;
82932633Ssam 	int port, i, j;
83032633Ssam 
83132633Ssam 	ms = &mp_softc[unit];
83232633Ssam 	mb = mp_softc[unit].ms_mb;
83332633Ssam 	for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) {
83432633Ssam 		/*
83532633Ssam 		 * Process each completed entry in the inbound queue.
83632633Ssam 		 */
83732633Ssam 		mp = &mb->mb_port[port];
83832633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
83932633Ssam #define	nextevent(mp)	&mp->mp_recvq[mp->mp_off]
84032633Ssam 		ev = nextevent(mp);
84132633Ssam 		for(; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) {
84232633Ssam 			/* YUCK */
84332633Ssam 			ap = &ms->ms_async[port][mp->mp_off];
84434506Skarels 			mppurge((caddr_t)ap, (int)sizeof (*ap));
84532633Ssam 			switch (ev->ev_cmd) {
84632633Ssam 			case EVCMD_OPEN:
84732633Ssam 				/*
84832633Ssam 				 * Open completion, start all reads and
84932633Ssam 				 * assert modem status information.
85032633Ssam 				 */
85132633Ssam 				for (i = 0; i < MPOUTSET; i++)
85232633Ssam 					mp->mp_sendq[i].ev_status = EVSTATUS_GO;
85332633Ssam 				(*linesw[tp->t_line].l_modem)
85432633Ssam 				    (tp, ap->ap_modem.mc_dcd == ASSERT);
85532633Ssam 				break;
85632633Ssam 			case EVCMD_CLOSE:
85732633Ssam 				/*
85832633Ssam 				 * Close completion, flush all pending
85932633Ssam 				 * transmissions, free resources, and
86032633Ssam 				 * cleanup mpcc port state.
86132633Ssam 				 */
86232633Ssam 				for (i = 0; i < MPOUTSET; i++) {
86332633Ssam 					mp->mp_sendq[i].ev_status =
86432633Ssam 					    EVSTATUS_FREE;
86532633Ssam 					mp->mp_sendq[i].ev_un.rcvblk = 0;
86632633Ssam 					mp->mp_sendq[i].ev_params = 0;
86732633Ssam 				}
86832633Ssam 				tp->t_state &= ~TS_CARR_ON;
86932633Ssam 				mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0;
87032633Ssam 				mp->mp_flags &= ~MP_PROGRESS;
87132633Ssam 				mp->mp_proto = MPPROTO_UNUSED;
87232633Ssam 				wakeup((caddr_t)&tp->t_canq);	/* ??? */
87332633Ssam 				goto done;
87432633Ssam 			case EVCMD_IOCTL:
87532633Ssam 				/*
87632633Ssam 				 * Nothing to do, just pitch.
87732633Ssam 				 */
87832633Ssam 				break;
87932633Ssam 			case EVCMD_WRITE:
88032633Ssam 				/*
88132633Ssam 				 * Transmission completed, update tty
88232633Ssam 				 * state and restart output.
88332633Ssam 				 */
88432633Ssam 				tp->t_state &= ~TS_BUSY;
88532633Ssam 				if (tp->t_state & TS_FLUSH) {
88632633Ssam 					tp->t_state &= ~TS_FLUSH;
88732633Ssam 					wakeup((caddr_t)&tp->t_state);
88832633Ssam 				} else {
88934506Skarels 					register int cc = 0, n;
89032633Ssam 					struct hxmtl *hxp;
89132633Ssam 
89232633Ssam 					hxp = &ms->ms_hxl[port];
89334506Skarels 					for(n = 0; n < ev->ev_count; n++)
89434506Skarels 						cc += hxp->size[n];
89532633Ssam 					ndflush(&tp->t_outq, cc);
89632633Ssam 				}
89732633Ssam 				switch (ev->ev_error) {
89832633Ssam 				case A_SIZERR:  /*# error in xmt data size */
89932633Ssam 					mplog(unit, port, A_XSIZE, 0);
90032633Ssam 					break;
90132633Ssam 				case A_NXBERR:  /*# no more xmt evt buffers */
90232633Ssam 					mplog(unit, port, A_NOXBUF, 0);
90332633Ssam 					break;
90432633Ssam 				}
90532633Ssam 				mpstart(tp);
90632633Ssam 				break;
90732633Ssam 			default:
90834506Skarels 				mplog(unit, port, A_INVCMD, (int)ev->ev_cmd);
90932633Ssam 				break;
91032633Ssam 			}
91132633Ssam 			/* re-init all values in this entry */
91232633Ssam 			ev->ev_cmd = 0;
91332633Ssam 			ev->ev_opts = 0;
91432633Ssam 			ev->ev_error = 0;
91532633Ssam 			ev->ev_flags = 0;
91632633Ssam 			ev->ev_count = 0;
91732633Ssam 			/* show this entry is available for use */
91832633Ssam 			ev->ev_status = EVSTATUS_FREE;
91932633Ssam 			adjptr(mp->mp_off, MPINSET);
92032633Ssam #undef	nextevent
92132633Ssam 		}
92232633Ssam done:
92332633Ssam 		;
92432633Ssam 	}
92532633Ssam }
92632633Ssam 
92732633Ssam /*
92832633Ssam  * Handler for processing received events.
92932633Ssam  */
93032633Ssam mprintr(unit, list)
93134506Skarels 	u_char *list;
93232633Ssam {
93332633Ssam 	register struct tty *tp;
93432633Ssam 	register struct mpport *mp;
93532633Ssam 	register struct mpevent *ev;
93632633Ssam 	struct mblok *mb;
93732633Ssam 	register int cc;
93832633Ssam 	register char *cp;
93932633Ssam 	struct mpsoftc *ms;
94032633Ssam 	caddr_t ptr;
94132633Ssam 	char *rcverr;
94232633Ssam 	int port, i;
94332633Ssam 
94432633Ssam 	ms = &mp_softc[unit];
94532633Ssam 	mb = mp_softc[unit].ms_mb;
94632633Ssam 	for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) {
94732633Ssam 		tp = &mp_tty[unit*MPCHUNK + port];
94832633Ssam 		mp = &mb->mb_port[port];
94932633Ssam 		ev = &mp->mp_sendq[mp->mp_nextrcv];
95032633Ssam 		while (ev->ev_status & EVSTATUS_DONE) {
95132633Ssam 			if (ev->ev_cmd != EVCMD_READ &&
95232633Ssam 			    ev->ev_cmd != EVCMD_STATUS) {
95332633Ssam 				mplog(unit, port, "unexpected command",
95434506Skarels 				    (int)ev->ev_cmd);
95532633Ssam 				goto next;
95632633Ssam 			}
95732633Ssam 			if (ev->ev_cmd == EVCMD_STATUS) {
95832633Ssam 				/*
95932633Ssam 				 * Status change, look for carrier changes.
96032633Ssam 				 */
96132633Ssam 				if (ev->ev_opts == DCDASRT ||
96232633Ssam 				    ev->ev_opts == DCDDROP)
96332633Ssam 					(*linesw[tp->t_line].l_modem)
96432633Ssam 					    (tp, ev->ev_opts == DCDASRT);
96532633Ssam 				else
96632633Ssam 					mplog(unit, port,
96732633Ssam 					    "unexpect status command",
96834506Skarels 					    (int)ev->ev_opts);
96932633Ssam 				goto next;
97032633Ssam 			}
97132633Ssam 			/*
97232633Ssam 			 * Process received data.
97332633Ssam 			 */
97432633Ssam 			if ((tp->t_state & (TS_ISOPEN|TS_WOPEN)) == 0)
97532633Ssam 				goto next;
97632633Ssam 			cc = ev->ev_count;
97732633Ssam 			if (cc == 0)
97832633Ssam 				goto next;
97932633Ssam 			/* YUCK */
98032633Ssam 			cp = ms->ms_cbuf[port][mp->mp_nextrcv];
98132633Ssam 			mppurge(cp, CBSIZE);
98232633Ssam 			while (cc-- > 0) {
98332633Ssam 				/*
98432633Ssam 				 * A null character is inserted, potentially
98532633Ssam 				 * when a break or framing error occurs.  If
98632633Ssam 				 * we're not in raw mode, substitute the
98732633Ssam 				 * interrupt character.
98832633Ssam 				 */
98932633Ssam 				if (*cp == 0 &&
99032633Ssam 				    (ev->ev_error == BRKASRT ||
99132633Ssam 				     ev->ev_error == FRAMERR))
99232633Ssam 					if ((tp->t_flags&RAW) == 0)
99332633Ssam 						*cp = tp->t_intrc;
99432633Ssam 				(*linesw[tp->t_line].l_rint)(*cp++, tp);
99532633Ssam 			}
99632633Ssam 			/* setup for next read */
99732633Ssam 			ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0];
99834506Skarels 			ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
99934506Skarels 			ev->ev_params = (caddr_t) kvtophys(ptr);
100033673Sbostic 			switch(ev->ev_error) {
100133673Sbostic 			case RCVDTA:    /* Normal (good) rcv data */
100233673Sbostic 					/* do not report the following */
100333673Sbostic 					/* they are "normal" errors */
100433673Sbostic 			case FRAMERR:   /* frame error */
100533673Sbostic 			case BRKASRT:   /* Break condition */
100632633Ssam 			case PARERR:    /* parity error */
100733673Sbostic 				rcverr = (char *)0;
100832633Ssam 				break;
100932633Ssam 			case OVRNERR:   /* Overrun error */
101032633Ssam 				rcverr = "overrun error";
101132633Ssam 				break;
101232633Ssam 			case OVFERR:    /* Overflow error */
101332633Ssam 				rcverr = "overflow error";
101432633Ssam 				break;
101532633Ssam 			default:
101632633Ssam 				rcverr = "undefined rcv error";
101732633Ssam 			}
101832633Ssam 			if (rcverr != (char *)0)
101934506Skarels 				mplog(unit, port, rcverr, (int)ev->ev_error);
102032633Ssam 		next:
102132633Ssam 			ev->ev_cmd = 0;
102232633Ssam 			ev->ev_opts = 0;
102332633Ssam 			ev->ev_error = 0;
102432633Ssam 			ev->ev_flags = 0;
102532633Ssam 			ev->ev_status = EVSTATUS_GO;	/* start next read */
102632633Ssam 			adjptr(mp->mp_nextrcv, MPOUTSET);
102732633Ssam 			ev = &mp->mp_sendq[mp->mp_nextrcv];
102832633Ssam 		}
102932633Ssam 	}
103032633Ssam }
103132633Ssam 
103232633Ssam /*
103332633Ssam  * Log an mpcc diagnostic.
103432633Ssam  */
103532633Ssam mplog(unit, port, cp, flags)
103632633Ssam 	char *cp;
103732633Ssam {
103832633Ssam 
103932633Ssam 	if (flags)
104032633Ssam 		log(LOG_ERR, "mp%d: port%d, %s (%d)\n",
104132633Ssam 		    unit, port, cp, flags);
104232633Ssam 	else
104332633Ssam 		log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp);
104432633Ssam }
104532633Ssam 
104632633Ssam int	MPHOSTINT = 1;
104732633Ssam 
104832633Ssam mptimeint(mb)
104932633Ssam 	register struct mblok *mb;
105032633Ssam {
105132633Ssam 
105232633Ssam         mb->mb_mpintcnt = 0;
105332633Ssam         mb->mb_mpintclk = (caddr_t)0;
105432633Ssam 	*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
105532633Ssam }
105632633Ssam 
105732633Ssam /*
105832633Ssam  * Interupt mpcc
105932633Ssam  */
106032633Ssam mpintmpcc(mb, port)
106132633Ssam 	register struct mblok *mb;
106232633Ssam {
106332633Ssam 
106432633Ssam         mb->mb_intr[port] |= MPSEMA_WORK;
106532633Ssam         if (++mb->mb_mpintcnt == MPHOSTINT) {
106632633Ssam                 mb->mb_mpintcnt = 0;
106732633Ssam 		*(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
106832633Ssam                 if (mb->mb_mpintclk) {
106934506Skarels                         untimeout(mptimeint, (caddr_t)mb);
107032633Ssam                         mb->mb_mpintclk = 0;
107132633Ssam                 }
107232633Ssam         } else {
107332633Ssam                 if (mb->mb_mpintclk == 0) {
107434506Skarels                         timeout(mptimeint, (caddr_t)mb, 4);
107532633Ssam                         mb->mb_mpintclk = (caddr_t)1;
107632633Ssam                 }
107732633Ssam         }
107832633Ssam }
107932633Ssam 
108032633Ssam static char *mpherrmsg[] = {
108132633Ssam 	"",
108232633Ssam 	"Bus error",				/* MPBUSERR */
108332633Ssam 	"Address error",			/* ADDRERR */
108432633Ssam 	"Undefined ecc interrupt",		/* UNDECC */
108532633Ssam 	"Undefined interrupt",			/* UNDINT */
108632633Ssam 	"Power failure occurred",		/* PWRFL */
108732633Ssam 	"Stray transmit done interrupt",	/* NOXENTRY */
108832633Ssam 	"Two fast timers on one port",		/* TWOFTMRS */
108932633Ssam 	"Interrupt queue full",			/* INTQFULL */
109032633Ssam 	"Interrupt queue ack error",		/* INTQERR */
109132633Ssam 	"Uncorrectable dma parity error",	/* CBPERR */
109232633Ssam 	"32 port ACAP failed power up",		/* ACPDEAD */
109332633Ssam };
109432633Ssam #define	NHERRS	(sizeof (mpherrmsg) / sizeof (mpherrmsg[0]))
109532633Ssam 
109632633Ssam mperror(mb, unit)
109732633Ssam 	register struct mblok *mb;
109832633Ssam 	int unit;
109932633Ssam {
110032633Ssam 	register char *cp;
110132633Ssam 	register int i;
110232633Ssam 
110332633Ssam 	if (mb->mb_softerr) {
110432633Ssam 		switch (mb->mb_softerr) {
110532633Ssam 		case DMAPERR:   /* dma parity error */
110632633Ssam 			cp = "dma parity error";
110732633Ssam 			break;
110832633Ssam 		case ECCERR:
110932633Ssam 			cp = "local memory ecc error";
111032633Ssam 			break;
111132633Ssam 		default:
111232633Ssam 			cp = "unknown error";
111332633Ssam 			break;
111432633Ssam 		}
111532633Ssam 		log(LOG_ERR, "mp%d: soft error, %s", unit, cp);
111632633Ssam 		mb->mb_softerr = 0;
111732633Ssam 	}
111832633Ssam 	if (mb->mb_harderr) {
111932633Ssam 		if (mb->mb_harderr < NHERRS)
112032633Ssam 			cp = mpherrmsg[mb->mb_harderr];
112132633Ssam 		else
112232633Ssam 			cp = "unknown error";
112332633Ssam 		log(LOG_ERR, "mp%d: hard error, %s", unit, cp);
112432633Ssam 		if (mb->mb_status == MP_OPOPEN) {
112532633Ssam 			for (i = 0; i < MPMAXPORT; i++) {
112632633Ssam 				mpcleanport(mb, i);
112732633Ssam 				mb->mb_proto[i] = MPPROTO_UNUSED;
112832633Ssam 			}
112932633Ssam 		}
113032633Ssam 		mb->mb_harderr = 0;
113132633Ssam 		mb->mb_status = 0;
113232633Ssam 	}
113332633Ssam }
113432633Ssam 
113532633Ssam mppurge(addr, cc)
113632633Ssam 	register caddr_t addr;
113732633Ssam 	register int cc;
113832633Ssam {
113932633Ssam 
114032633Ssam 	for (; cc >= 0; addr += NBPG, cc -= NBPG)
114132633Ssam 		mtpr(P1DC, addr);
114232633Ssam }
114332633Ssam 
114432633Ssam /*
114532633Ssam  * MPCC Download Pseudo-device.
114632633Ssam  */
114732633Ssam char	mpdlbuf[MPDLBUFSIZE];
114832633Ssam int	mpdlbusy;		/* interlock on download buffer */
114932633Ssam int	mpdlerr;
115032633Ssam 
115132633Ssam mpdlopen(dev)
115232633Ssam 	dev_t dev;
115332633Ssam {
115432633Ssam 	int unit, mpu;
115532633Ssam 	struct vba_device *vi;
115632633Ssam 
115732633Ssam 	unit = minor(dev);
115832633Ssam 	mpu = MPUNIT(unit);
115932633Ssam 	if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
116032633Ssam 		return (ENODEV);
116132633Ssam 	return (0);
116232633Ssam }
116332633Ssam 
116432633Ssam mpdlwrite(dev, uio)
116532633Ssam 	dev_t dev;
116632633Ssam 	struct uio *uio;
116732633Ssam {
116832633Ssam 	register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))];
116932633Ssam 	register struct mpdl *dl;
117032633Ssam 	int error;
117132633Ssam 
117232633Ssam 	if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN)
117332633Ssam 		return (EFAULT);
117432633Ssam 	dl = &ms->ms_mb->mb_dl;
117532633Ssam 	dl->mpdl_count = uio->uio_iov->iov_len;
117634506Skarels 	dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
117734506Skarels 	if (error = uiomove(mpdlbuf, (int)dl->mpdl_count, UIO_WRITE, uio))
117832633Ssam 		return (error);
117932633Ssam 	uio->uio_resid -= dl->mpdl_count;    /* set up return from write */
118032633Ssam 	dl->mpdl_cmd = MPDLCMD_NORMAL;
118132633Ssam 	error = mpdlwait(dl);
118232633Ssam 	return (error);
118332633Ssam }
118432633Ssam 
118532633Ssam mpdlclose(dev)
118632633Ssam 	dev_t dev;
118732633Ssam {
118832633Ssam 	register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb;
118932633Ssam 
119032633Ssam 	if (mb == 0 || mb->mb_status != MP_DLDONE) {
119132633Ssam 		mpbogus.status = 0;
119232633Ssam 		if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))])
119332633Ssam 			mpdlbusy--;
119432633Ssam 		return (EEXIST);
119532633Ssam 	}
119632633Ssam 	mb->mb_status = MP_OPOPEN;
119732633Ssam 	mpbogus.status = 0;
119832633Ssam 	/* set to dead, for board handshake */
119932633Ssam 	mb->mb_hostint.imok = MPIMOK_DEAD;
120032633Ssam 	return (0);
120132633Ssam }
120232633Ssam 
120332633Ssam int	mpdltimeout();
120432633Ssam 
120534506Skarels /* ARGSUSED */
120632633Ssam mpdlioctl(dev, cmd, data, flag)
120732633Ssam 	dev_t dev;
120832633Ssam 	caddr_t data;
120932633Ssam {
121032633Ssam 	register struct mblok *mb;
121132633Ssam 	register struct mpdl *dl;
121234506Skarels 	int unit, error, s, i;
121332633Ssam 
121432633Ssam 	mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb;
121532633Ssam 	if (mb == 0)
121632633Ssam 		return (EEXIST);
121732633Ssam 	dl = &mb->mb_dl;
121832633Ssam 	error = 0;
121932633Ssam 	switch (cmd) {
122032633Ssam 	case MPIOPORTMAP:
122132633Ssam 		bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto));
122232633Ssam 		break;
122332633Ssam 	case MPIOHILO:
122432633Ssam 		bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport)));
122532633Ssam 		break;
122632633Ssam 	case MPIOENDDL:
122732633Ssam 		dl->mpdl_count = 0;
122832633Ssam 		dl->mpdl_data = 0;
122932633Ssam 		dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK;
123032633Ssam 		error = mpdlwait(dl);
123132633Ssam 		mpccinit(unit);
123232633Ssam 		mb->mb_status = MP_DLDONE;
123332633Ssam 		mpdlbusy--;
123432633Ssam 		break;
123532633Ssam 	case MPIOENDCODE:
123632633Ssam 		dl->mpdl_count = 0;
123732633Ssam 		dl->mpdl_data = 0;
123832633Ssam 		dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK;
123932633Ssam 		error = mpdlwait(dl);
124032633Ssam 		break;
124132633Ssam 	case MPIOASYNCNF:
124232633Ssam 		bcopy(data, mpdlbuf, sizeof (struct abdcf));
124334506Skarels 		dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
124432633Ssam 		dl->mpdl_count = sizeof (struct abdcf);
124532633Ssam 		dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK;
124632633Ssam 		error = mpdlwait(dl);
124732633Ssam 		break;
124832633Ssam 	case MPIOSTARTDL:
124932633Ssam 		while (mpdlbusy)
125032633Ssam 			sleep((caddr_t)&mpdlbusy, PZERO+1);
125132633Ssam 		mpdlbusy++;
125232633Ssam 		/* initialize the downloading interface */
125332633Ssam 		mpbogus.magic = MPMAGIC;
125432633Ssam 		mpbogus.mb = mpbogus.mbloks[unit];
125532633Ssam 		mpbogus.status = 1;
125632633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
125732633Ssam 		dl->mpdl_count = 0;
125832633Ssam 		dl->mpdl_cmd = 0;
125932633Ssam 		dl->mpdl_data = (char *) 0;
126032633Ssam 		mpdlerr = 0;
126132633Ssam 		mb->mb_magic = MPMAGIC;
126232633Ssam         	mb->mb_ivec = mp_softc[unit].ms_ivec+1;	/* download vector */
126332633Ssam 		mb->mb_status = MP_DLPEND;
126432633Ssam 		mb->mb_diagswitch[0] = 'A';
126532633Ssam 		mb->mb_diagswitch[1] = 'P';
126632633Ssam 		s = spl8();
126732633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 2;
126834506Skarels 		timeout(mpdltimeout, (caddr_t)mb, 30*hz);
126932633Ssam 		sleep((caddr_t)&mb->mb_status, PZERO+1);
127032633Ssam 		splx(s);
127132633Ssam 		if (mb->mb_status == MP_DLOPEN) {
127234506Skarels 			untimeout(mpdltimeout, (caddr_t)mb);
127332633Ssam 		} else if (mb->mb_status == MP_DLTIME) {
127432633Ssam 			mpbogus.status = 0;
127532633Ssam 			error = ETIMEDOUT;
127632633Ssam 		} else {
127732633Ssam 			mpbogus.status = 0;
127832633Ssam 			error = ENXIO;
127932633Ssam 			log(LOG_ERR, "mp%d: start download: unknown status %x",
128032633Ssam 			    unit, mb->mb_status);
128132633Ssam 		}
128234506Skarels 		bzero((caddr_t)mb->mb_port, sizeof (mb->mb_port));
128332633Ssam 		break;
128432633Ssam 	case MPIORESETBOARD:
128532633Ssam 		s = spl8();
128632633Ssam 		if (mb->mb_imokclk)
128732633Ssam 			mb->mb_imokclk = 0;
128832633Ssam 		*(u_short *)mpinfo[unit]->ui_addr = 0x100;
128932633Ssam 		if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) {
129032633Ssam 			mpdlerr = MP_DLERROR;
129132633Ssam 			dl->mpdl_status = EVSTATUS_FREE;
129232633Ssam 			wakeup((caddr_t)&dl->mpdl_status);
129332633Ssam 			mpbogus.status = 0;
129432633Ssam 		}
129532633Ssam 		for (i = 0; i < MPMAXPORT; i++) {
129632633Ssam 			if (mb->mb_harderr || mb->mb_softerr)
129732633Ssam 				mperror(mb, i);
129832633Ssam 			mpcleanport(mb, i);
129932633Ssam 			mb->mb_proto[i] = MPPROTO_UNUSED;
130032633Ssam 		}
130132633Ssam 		mb->mb_status = 0;
130232633Ssam 		splx(s);
130332633Ssam 		break;
130432633Ssam 	default:
130532633Ssam 		error = EINVAL;
130632633Ssam 		break;
130732633Ssam 	}
130832633Ssam 	return (error);
130932633Ssam }
131032633Ssam 
131132633Ssam mpccinit(unit)
131232633Ssam 	int unit;
131332633Ssam {
131432633Ssam         register struct mblok *mb = mp_softc[unit].ms_mb;
131532633Ssam         register struct his *his;
131632633Ssam         register int i, j;
131732633Ssam 
131832633Ssam         mb->mb_status = MP_DLDONE;
131932633Ssam         mb->mb_ivec = mp_softc[unit].ms_ivec;
132032633Ssam         mb->mb_magic = MPMAGIC;
132132633Ssam         /* Init host interface structure */
132232633Ssam         his = &mb->mb_hostint;
132332633Ssam         his->semaphore = MPSEMA_AVAILABLE;
132432633Ssam         for (i = 0; i < NMPPROTO; i++)
132532633Ssam                 for (j = 0; j < MPMAXPORT; j++) {
132632633Ssam                         his->proto[i].inbdone[j] = MPPORT_EOL;
132732633Ssam                         his->proto[i].outbdone[j] = MPPORT_EOL;
132832633Ssam                 }
132932633Ssam         mb->mb_unit = unit;
133032633Ssam }
133132633Ssam 
133232633Ssam mpdlintr(mpcc)
133332633Ssam 	int mpcc;
133432633Ssam {
133532633Ssam 	register struct mblok *mb;
133632633Ssam 	register struct mpdl *dl;
133732633Ssam 
133832633Ssam 	mb = mp_softc[mpcc].ms_mb;
133932633Ssam 	if (mb == 0) {
134032633Ssam 		printf("mp%d: stray download interrupt\n", mpcc);
134132633Ssam 		return;
134232633Ssam 	}
134332633Ssam 	dl = &mb->mb_dl;
134432633Ssam 	switch (mb->mb_status) {
134532633Ssam 	case MP_DLOPEN:
134632633Ssam 		if (dl->mpdl_status != EVSTATUS_DONE)
134732633Ssam 			mpdlerr = MP_DLERROR;
134832633Ssam 		dl->mpdl_status = EVSTATUS_FREE;
134932633Ssam 		wakeup((caddr_t)&dl->mpdl_status);
135032633Ssam 		return;
135132633Ssam 	case MP_DLPEND:
135232633Ssam 		mb->mb_status = MP_DLOPEN;
135334506Skarels 		wakeup((caddr_t)&mb->mb_status);
135432633Ssam 		/* fall thru... */
135532633Ssam 	case MP_DLTIME:
135632633Ssam 		return;
135732633Ssam 	case MP_OPOPEN:
135832633Ssam 		if (mb->mb_imokclk)
135932633Ssam 			mb->mb_imokclk = 0;
136032633Ssam 		mb->mb_nointcnt = 0;		/* reset no interrupt count */
136132633Ssam 		mb->mb_hostint.imok = MPIMOK_DEAD;
136232633Ssam 		mb->mb_imokclk = (caddr_t)1;
136332633Ssam 		break;
136432633Ssam 	default:
136532633Ssam 		log(LOG_ERR, "mp%d: mpdlintr, status %x\n",
136632633Ssam 		    mpcc, mb->mb_status);
136732633Ssam 		break;
136832633Ssam 	}
136932633Ssam }
137032633Ssam 
137132633Ssam mpdltimeout(mp)
137232633Ssam 	struct mblok *mp;
137332633Ssam {
137432633Ssam 
137532633Ssam 	mp->mb_status = MP_DLTIME;
137632633Ssam 	wakeup((caddr_t)&mp->mb_status);
137732633Ssam }
137832633Ssam 
137932633Ssam /*
138032633Ssam  * Wait for a transfer to complete or a timeout to occur.
138132633Ssam  */
138232633Ssam mpdlwait(dl)
138332633Ssam 	register struct mpdl *dl;
138432633Ssam {
138532633Ssam 	int s, error = 0;
138632633Ssam 
138732633Ssam 	s = spl8();
138832633Ssam 	dl->mpdl_status = EVSTATUS_GO;
138932633Ssam 	while (dl->mpdl_status != EVSTATUS_FREE) {
139032633Ssam 		sleep((caddr_t)&dl->mpdl_status, PZERO+1);
139132633Ssam 		if (mpdlerr == MP_DLERROR)
139232633Ssam 			error = EIO;
139332633Ssam 	}
139432633Ssam 	splx(s);
139532633Ssam 	return (error);
139632633Ssam }
139732633Ssam #endif
1398