xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 34406)
1*34406Skarels /*
2*34406Skarels  * Copyright (c) 1988 Regents of the University of California.
3*34406Skarels  * All rights reserved.  The Berkeley software License Agreement
4*34406Skarels  * specifies the terms and conditions for redistribution.
5*34406Skarels  *
6*34406Skarels  *	@(#)vx.c	7.1 (Berkeley) 05/21/88
7*34406Skarels  */
824003Ssam 
924003Ssam #include "vx.h"
1024003Ssam #if NVX > 0
1124003Ssam /*
1225857Ssam  * VIOC-X driver
1324003Ssam  */
1425877Ssam #ifdef VXPERF
1525948Ssam #define	DOSCOPE
1625877Ssam #endif
1725877Ssam 
1825877Ssam #include "param.h"
1925877Ssam #include "ioctl.h"
2025877Ssam #include "tty.h"
2125877Ssam #include "dir.h"
2225877Ssam #include "user.h"
2325877Ssam #include "map.h"
2425877Ssam #include "buf.h"
2525877Ssam #include "conf.h"
2625877Ssam #include "file.h"
2725877Ssam #include "uio.h"
2825877Ssam #include "proc.h"
2925877Ssam #include "vm.h"
3025881Ssam #include "kernel.h"
3129954Skarels #include "syslog.h"
3225675Ssam 
33*34406Skarels #include "../tahoe/pte.h"
34*34406Skarels 
3525675Ssam #include "../tahoevba/vbavar.h"
3625881Ssam #include "../tahoevba/vxreg.h"
3725675Ssam #include "../tahoevba/scope.h"
3824003Ssam 
3925881Ssam #ifdef VX_DEBUG
4025881Ssam long	vxintr4 = 0;
4125948Ssam #define	VXERR4	1
4225948Ssam #define	VXNOBUF	2
4325881Ssam long	vxdebug = 0;
4425948Ssam #define	VXVCM	1
4525948Ssam #define	VXVCC	2
4625948Ssam #define	VXVCX	4
4725881Ssam #endif
4824003Ssam 
4925881Ssam /*
5025881Ssam  * Interrupt type bits passed to vinthandl().
5125881Ssam  */
5225948Ssam #define	CMDquals 0		/* command completed interrupt */
5325948Ssam #define	RSPquals 1		/* command response interrupt */
5425948Ssam #define	UNSquals 2		/* unsolicited interrupt */
5524003Ssam 
5630372Skarels #define	VXUNIT(n)	((n) >> 4)
5730372Skarels #define	VXPORT(n)	((n) & 0xf)
5830372Skarels 
5925881Ssam struct	tty vx_tty[NVX*16];
6029954Skarels #ifndef lint
6129954Skarels int	nvx = NVX*16;
6229954Skarels #endif
6325881Ssam int	vxstart(), ttrstrt();
6425881Ssam struct	vxcmd *vobtain(), *nextcmd();
6524003Ssam 
6624003Ssam /*
6724003Ssam  * Driver information for auto-configuration stuff.
6824003Ssam  */
6924003Ssam int	vxprobe(), vxattach(), vxrint();
7025881Ssam struct	vba_device *vxinfo[NVX];
7124003Ssam long	vxstd[] = { 0 };
7224003Ssam struct	vba_driver vxdriver =
7325857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
7424003Ssam 
7525881Ssam struct	vx_softc {
7625881Ssam 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
7725881Ssam 	u_char	vs_bop;		/* bop board # for vioc-bop's */
7825881Ssam 	u_char	vs_loport;	/* low port nbr */
7925881Ssam 	u_char	vs_hiport;	/* high port nbr */
8025881Ssam 	u_short	vs_nbr;		/* viocx number */
8125881Ssam 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
8225881Ssam 	u_short	vs_silosiz;	/* silo size */
8325881Ssam 	short	vs_vers;	/* vioc/pvioc version */
8425948Ssam #define	VXV_OLD	0		/* PVIOCX | VIOCX */
8525948Ssam #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
8625881Ssam 	short	vs_xmtcnt;	/* xmit commands pending */
8725881Ssam 	short	vs_brkreq;	/* send break requests pending */
8825881Ssam 	short 	vs_state;	/* controller state */
8925948Ssam #define	VXS_READY	0	/* ready for commands */
9025948Ssam #define	VXS_RESET	1	/* in process of reseting */
9130372Skarels 	u_short	vs_softCAR;	/* soft carrier */
9225881Ssam 	caddr_t vs_mricmd;	/* most recent issued cmd */
9325881Ssam 	u_int	vs_ivec;	/* interrupt vector base */
9425881Ssam 	struct	vxcmd *vs_avail;/* next available command buffer */
9525881Ssam 	struct	vxcmd *vs_build;
9625881Ssam 	struct	vxcmd vs_lst[NVCXBUFS];
9725881Ssam 	struct	vcmds vs_cmds;
9825881Ssam } vx_softc[NVX];
9924003Ssam 
10025857Ssam vxprobe(reg, vi)
10124003Ssam 	caddr_t reg;
10225857Ssam 	struct vba_device *vi;
10324003Ssam {
10425857Ssam 	register int br, cvec;			/* must be r12, r11 */
10525881Ssam 	register struct vxdevice *vp = (struct vxdevice *)reg;
10625881Ssam 	register struct vx_softc *vs;
10724003Ssam 
10824003Ssam #ifdef lint
10924003Ssam 	br = 0; cvec = br; br = cvec;
11025675Ssam 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
11124003Ssam #endif
11225675Ssam 	if (badaddr((caddr_t)vp, 1))
11325675Ssam 		return (0);
11425675Ssam 	vp->v_fault = 0;
11525675Ssam 	vp->v_vioc = V_BSY;
11625675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
11724003Ssam 	DELAY(4000000);
11825881Ssam 	if (vp->v_fault != VXF_READY)
11925675Ssam 		return (0);
12025881Ssam 	vs = &vx_softc[vi->ui_unit];
12125857Ssam #ifdef notdef
12225857Ssam 	/*
12325857Ssam 	 * Align vioc interrupt vector base to 4 vector
12425857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
12525857Ssam 	 * wish we had documentation).
12625857Ssam 	 */
12725857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
12825857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
12925881Ssam 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
13025857Ssam #else
13125881Ssam 	vs->vs_ivec = 0x40+vi->ui_unit*4;
13225857Ssam #endif
13325881Ssam 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
13425881Ssam 	return (sizeof (struct vxdevice));
13524003Ssam }
13624003Ssam 
13725857Ssam vxattach(vi)
13825857Ssam 	register struct vba_device *vi;
13924003Ssam {
14025675Ssam 
14130372Skarels 	vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags;
14229954Skarels 	vxinit(vi->ui_unit, 1);
14324003Ssam }
14424003Ssam 
14524003Ssam /*
14624003Ssam  * Open a VX line.
14724003Ssam  */
14825675Ssam /*ARGSUSED*/
14924003Ssam vxopen(dev, flag)
15025881Ssam 	dev_t dev;
15125881Ssam 	int flag;
15224003Ssam {
15324003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
15425881Ssam 	register struct vx_softc *vs;
15525881Ssam 	register struct vba_device *vi;
15625881Ssam 	int unit, vx, s, error;
15724003Ssam 
15825881Ssam 	unit = minor(dev);
15930372Skarels 	vx = VXUNIT(unit);
16030372Skarels 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
16125881Ssam 		return (ENXIO);
16230372Skarels 	vs = &vx_softc[vx];
16325881Ssam 	tp = &vx_tty[unit];
16430372Skarels 	unit = VXPORT(unit);
16525881Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
16625881Ssam 		return (EBUSY);
16730372Skarels 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
16825881Ssam 		return (ENXIO);
16925881Ssam 	tp->t_addr = (caddr_t)vs;
17025881Ssam 	tp->t_oproc = vxstart;
17125881Ssam 	tp->t_dev = dev;
17225881Ssam 	s = spl8();
17325881Ssam 	tp->t_state |= TS_WOPEN;
17425881Ssam 	if ((tp->t_state&TS_ISOPEN) == 0) {
17525881Ssam 		ttychars(tp);
17625881Ssam 		if (tp->t_ispeed == 0) {
17725881Ssam 			tp->t_ispeed = SSPEED;
17825881Ssam 			tp->t_ospeed = SSPEED;
17925881Ssam 			tp->t_flags |= ODDP|EVENP|ECHO;
18024003Ssam 		}
18125881Ssam 		vxparam(dev);
18224003Ssam 	}
18330372Skarels 	vcmodem(dev, VMOD_ON);
18430372Skarels 	while ((tp->t_state&TS_CARR_ON) == 0)
18530372Skarels 		sleep((caddr_t)&tp->t_rawq, TTIPRI);
18625881Ssam 	error = (*linesw[tp->t_line].l_open)(dev,tp);
18725881Ssam 	splx(s);
18825881Ssam 	return (error);
18924003Ssam }
19024003Ssam 
19124003Ssam /*
19224003Ssam  * Close a VX line.
19324003Ssam  */
19425675Ssam /*ARGSUSED*/
19524003Ssam vxclose(dev, flag)
19625881Ssam 	dev_t dev;
19725881Ssam 	int flag;
19824003Ssam {
19924003Ssam 	register struct tty *tp;
20025881Ssam 	int unit, s;
20124003Ssam 
20225881Ssam 	unit = minor(dev);
20325881Ssam 	tp = &vx_tty[unit];
20425881Ssam 	s = spl8();
20524003Ssam 	(*linesw[tp->t_line].l_close)(tp);
20630372Skarels 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
20730372Skarels 		vcmodem(dev, VMOD_OFF);
20824003Ssam 	/* wait for the last response */
20925881Ssam 	while (tp->t_state&TS_FLUSH)
21025881Ssam 		sleep((caddr_t)&tp->t_state, TTOPRI);
21125881Ssam 	ttyclose(tp);
21225881Ssam 	splx(s);
21324003Ssam }
21424003Ssam 
21524003Ssam /*
21624003Ssam  * Read from a VX line.
21724003Ssam  */
21824003Ssam vxread(dev, uio)
21924003Ssam 	dev_t dev;
22024003Ssam 	struct uio *uio;
22124003Ssam {
22225881Ssam 	struct tty *tp = &vx_tty[minor(dev)];
22325881Ssam 
22425881Ssam 	return ((*linesw[tp->t_line].l_read)(tp, uio));
22524003Ssam }
22624003Ssam 
22724003Ssam /*
22824003Ssam  * write on a VX line
22924003Ssam  */
23024003Ssam vxwrite(dev, uio)
23124003Ssam 	dev_t dev;
23224003Ssam 	struct uio *uio;
23324003Ssam {
23425881Ssam 	register struct tty *tp = &vx_tty[minor(dev)];
23525881Ssam 
23625881Ssam 	return ((*linesw[tp->t_line].l_write)(tp, uio));
23724003Ssam }
23824003Ssam 
23924003Ssam /*
24024003Ssam  * VIOCX unsolicited interrupt.
24124003Ssam  */
24225881Ssam vxrint(vx)
24325881Ssam 	register vx;
24424003Ssam {
24525881Ssam 	register struct tty *tp, *tp0;
24625881Ssam 	register struct vxdevice *addr;
24725881Ssam 	register struct vx_softc *vs;
24825881Ssam 	struct vba_device *vi;
24925881Ssam 	register int nc, c;
25025881Ssam 	register struct silo {
25125881Ssam 		char	data, port;
25225881Ssam 	} *sp;
25325881Ssam 	short *osp;
25425881Ssam 	int overrun = 0;
25524003Ssam 
25625881Ssam 	vi = vxinfo[vx];
25725881Ssam 	if (vi == 0 || vi->ui_alive == 0)
25825881Ssam 		return;
25925881Ssam 	addr = (struct vxdevice *)vi->ui_addr;
26025881Ssam 	switch (addr->v_uqual&037) {
26124003Ssam 	case 0:
26224003Ssam 		break;
26324003Ssam 	case 2:
26430372Skarels 		printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat);
26525881Ssam 		vxstreset(vx);
26630372Skarels 		return;
26724003Ssam 	case 3:
26825881Ssam 		vcmintr(vx);
26930372Skarels 		return;
27024003Ssam 	case 4:
27130372Skarels 		return;
27224003Ssam 	default:
27330372Skarels 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
27425881Ssam 		vxstreset(vx);
27530372Skarels 		return;
27624003Ssam 	}
27725881Ssam 	vs = &vx_softc[vx];
27825881Ssam 	if (vs->vs_vers == VXV_NEW)
27925881Ssam 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
28025881Ssam 	else
28125881Ssam 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
28225881Ssam 	nc = *(osp = (short *)sp);
28325881Ssam 	if (nc == 0)
28430372Skarels 		return;
28525881Ssam 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
28625881Ssam 		printf("vx%d: %d exceeds silo size\n", nc);
28725881Ssam 		nc = vs->vs_silosiz;
28824003Ssam 	}
28925881Ssam 	tp0 = &vx_tty[vx*16];
29025881Ssam 	sp = (struct silo *)(((short *)sp)+1);
29125881Ssam 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
29225881Ssam 		c = sp->port & 017;
29325881Ssam 		if (vs->vs_loport > c || c > vs->vs_hiport)
29425881Ssam 			continue;
29525881Ssam 		tp = tp0 + c;
29625881Ssam 		if( (tp->t_state&TS_ISOPEN) == 0) {
29724003Ssam 			wakeup((caddr_t)&tp->t_rawq);
29824003Ssam 			continue;
29924003Ssam 		}
30025881Ssam 		c = sp->data;
30125881Ssam 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
30229954Skarels 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
30325881Ssam 			overrun = 1;
30425881Ssam 			continue;
30525881Ssam 		}
30625881Ssam 		if (sp->port&VX_PE)
30725881Ssam 			if ((tp->t_flags&(EVENP|ODDP)) == EVENP ||
30825881Ssam 			    (tp->t_flags&(EVENP|ODDP)) == ODDP)
30924003Ssam 				continue;
31030372Skarels 		if ((tp->t_flags & (RAW | PASS8)) == 0)
31130372Skarels 			c &= 0177;
31225881Ssam 		if (sp->port&VX_FE) {
31325881Ssam 			/*
31425881Ssam 			 * At framing error (break) generate
31525881Ssam 			 * a null (in raw mode, for getty), or a
31625881Ssam 			 * interrupt (in cooked/cbreak mode).
31725881Ssam 			 */
31825881Ssam 			if (tp->t_flags&RAW)
31925881Ssam 				c = 0;
32025881Ssam 			else
32125881Ssam 				c = tp->t_intrc;
32224003Ssam 		}
32324003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
32424003Ssam 	}
32525881Ssam 	*osp = 0;
32624003Ssam }
32724003Ssam 
32824003Ssam /*
32925881Ssam  * Ioctl for VX.
33024003Ssam  */
33124003Ssam vxioctl(dev, cmd, data, flag)
33225881Ssam 	dev_t dev;
33325881Ssam 	caddr_t	data;
33424003Ssam {
33525881Ssam 	register struct tty *tp;
33625881Ssam 	int error;
33724003Ssam 
33825881Ssam 	tp = &vx_tty[minor(dev)];
33924003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
34024003Ssam 	if (error == 0)
34125881Ssam 		return (error);
34225881Ssam 	error = ttioctl(tp, cmd, data, flag);
34325881Ssam 	if (error >= 0) {
34429954Skarels 		if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS ||
34529954Skarels 		    cmd == TIOCLBIC || cmd == TIOCLSET)
34624003Ssam 			vxparam(dev);
34725881Ssam 		return (error);
34825881Ssam 	}
34925881Ssam 	return (ENOTTY);
35024003Ssam }
35124003Ssam 
35224003Ssam vxparam(dev)
35325881Ssam 	dev_t dev;
35424003Ssam {
35525881Ssam 
35624003Ssam 	vxcparam(dev, 1);
35724003Ssam }
35824003Ssam 
35924003Ssam /*
36024003Ssam  * Set parameters from open or stty into the VX hardware
36124003Ssam  * registers.
36224003Ssam  */
36324003Ssam vxcparam(dev, wait)
36425881Ssam 	dev_t dev;
36525881Ssam 	int wait;
36624003Ssam {
36725881Ssam 	register struct tty *tp;
36825881Ssam 	register struct vx_softc *vs;
36925881Ssam 	register struct vxcmd *cp;
37025933Ssam 	int s, unit = minor(dev);
37124003Ssam 
37225933Ssam 	tp = &vx_tty[unit];
37330372Skarels 	if ((tp->t_ispeed)==0) {
37430372Skarels 		tp->t_state |= TS_HUPCLS;
37530372Skarels 		vcmodem(dev, VMOD_OFF);
37630372Skarels 		return;
37730372Skarels 	}
37825881Ssam 	vs = (struct vx_softc *)tp->t_addr;
37925881Ssam 	cp = vobtain(vs);
38024003Ssam 	s = spl8();
38125933Ssam 	/*
38225933Ssam 	 * Construct ``load parameters'' command block
38325933Ssam 	 * to setup baud rates, xon-xoff chars, parity,
38425933Ssam 	 * and stop bits for the specified port.
38525933Ssam 	 */
38625933Ssam 	cp->cmd = VXC_LPARAX;
38730372Skarels 	cp->par[1] = VXPORT(unit);
38825933Ssam 	cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc;
38925933Ssam 	cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc;
39030372Skarels #ifdef notnow
39129954Skarels 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {
39230372Skarels #endif
39330372Skarels 		cp->par[4] = BITS8;		/* 8 bits of data */
39430372Skarels 		cp->par[7] = VNOPARITY;		/* no parity */
39530372Skarels #ifdef notnow
39624003Ssam 	} else {
39730372Skarels 		cp->par[4] = BITS7;		/* 7 bits of data */
39825881Ssam 		if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
39930372Skarels 			cp->par[7] = VODDP;	/* odd parity */
40029954Skarels 		else
40130372Skarels 			cp->par[7] = VEVENP;	/* even parity */
40224003Ssam 	}
40330372Skarels #endif
40430372Skarels 	if (tp->t_ospeed == B110)
40530372Skarels 		cp->par[5] = VSTOP2;		/* 2 stop bits */
40630372Skarels 	else
40730372Skarels 		cp->par[5] = VSTOP1;		/* 1 stop bit */
40830372Skarels 	if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB)
40930372Skarels 		cp->par[6] = V19200;
41030372Skarels 	else
41130372Skarels 		cp->par[6] = tp->t_ospeed;
41230372Skarels 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
41325675Ssam 		sleep((caddr_t)cp,TTIPRI);
41424003Ssam 	splx(s);
41524003Ssam }
41624003Ssam 
41724003Ssam /*
41824003Ssam  * VIOCX command response interrupt.
41924003Ssam  * For transmission, restart output to any active port.
42024003Ssam  * For all other commands, just clean up.
42124003Ssam  */
42225881Ssam vxxint(vx, cp)
42325881Ssam 	register int vx;
42425881Ssam 	register struct vxcmd *cp;
42524003Ssam {
42630372Skarels 	register struct vxmit *vp;
42725933Ssam 	register struct tty *tp, *tp0;
42825933Ssam 	register struct vx_softc *vs;
42924003Ssam 
43025881Ssam 	vs = &vx_softc[vx];
43125881Ssam 	cp = (struct vxcmd *)((long *)cp-1);
43229954Skarels 
43325881Ssam 	switch (cp->cmd&0xff00) {
43425881Ssam 
43525881Ssam 	case VXC_LIDENT:	/* initialization complete */
43625881Ssam 		if (vs->vs_state == VXS_RESET) {
43725881Ssam 			vxfnreset(vx, cp);
43825881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
43924003Ssam 		}
44024003Ssam 		cp->cmd++;
44124003Ssam 		return;
44225881Ssam 
44325881Ssam 	case VXC_XMITDTA:
44425881Ssam 	case VXC_XMITIMM:
44524003Ssam 		break;
44625881Ssam 
44725881Ssam 	case VXC_LPARAX:
44825675Ssam 		wakeup((caddr_t)cp);
44925881Ssam 		/* fall thru... */
45025881Ssam 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
45125881Ssam 		vrelease(vs, cp);
45225881Ssam 		if (vs->vs_state == VXS_RESET)
45325881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
45424003Ssam 		return;
45524003Ssam 	}
45625881Ssam 	tp0 = &vx_tty[vx*16];
45725881Ssam 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
45825881Ssam 	for (; vp >= (struct vxmit *)cp->par; vp--) {
45925881Ssam 		tp = tp0 + (vp->line & 017);
46024003Ssam 		tp->t_state &= ~TS_BUSY;
46125881Ssam 		if (tp->t_state & TS_FLUSH) {
46224003Ssam 			tp->t_state &= ~TS_FLUSH;
46325881Ssam 			wakeup((caddr_t)&tp->t_state);
46425881Ssam 		} else
46524003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
46624003Ssam 	}
46725881Ssam 	vrelease(vs, cp);
46830372Skarels 	if (vs->vs_vers == VXV_NEW)
46932112Skarels 		(*linesw[tp->t_line].l_start)(tp);
47030372Skarels 	else {
47125881Ssam 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
47225881Ssam 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
47332112Skarels 			(*linesw[tp->t_line].l_start)(tp);
47425881Ssam 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
47525881Ssam 			vs->vs_xmtcnt++;
47630372Skarels 			(void) vcmd(vx, (caddr_t)&cp->cmd);
47724003Ssam 		}
47824003Ssam 	}
47930372Skarels 	vs->vs_xmtcnt--;
48024003Ssam }
48124003Ssam 
48224003Ssam /*
48324003Ssam  * Force out partial XMIT command after timeout
48424003Ssam  */
48525881Ssam vxforce(vs)
48625881Ssam 	register struct vx_softc *vs;
48724003Ssam {
48825881Ssam 	register struct vxcmd *cp;
48925881Ssam 	int s;
49024003Ssam 
49124003Ssam 	s = spl8();
49225881Ssam 	if ((cp = nextcmd(vs)) != NULL) {
49325881Ssam 		vs->vs_xmtcnt++;
49430372Skarels 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
49524003Ssam 	}
49624003Ssam 	splx(s);
49724003Ssam }
49824003Ssam 
49924003Ssam /*
50024003Ssam  * Start (restart) transmission on the given VX line.
50124003Ssam  */
50224003Ssam vxstart(tp)
50325881Ssam 	register struct tty *tp;
50424003Ssam {
50525675Ssam 	register short n;
50625933Ssam 	register struct vx_softc *vs;
50725933Ssam 	int s, port;
50824003Ssam 
50924003Ssam 	s = spl8();
51024003Ssam 	port = minor(tp->t_dev) & 017;
51125881Ssam 	vs = (struct vx_softc *)tp->t_addr;
51225881Ssam 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
51325881Ssam 		if (tp->t_outq.c_cc <= TTLOWAT(tp)) {
51424003Ssam 			if (tp->t_state&TS_ASLEEP) {
51524003Ssam 				tp->t_state &= ~TS_ASLEEP;
51624003Ssam 				wakeup((caddr_t)&tp->t_outq);
51724003Ssam 			}
51824003Ssam 			if (tp->t_wsel) {
51924003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
52024003Ssam 				tp->t_wsel = 0;
52124003Ssam 				tp->t_state &= ~TS_WCOLL;
52224003Ssam 			}
52324003Ssam 		}
52425881Ssam 		if (tp->t_outq.c_cc == 0) {
52524003Ssam 			splx(s);
52630372Skarels 			return;
52724003Ssam 		}
52825877Ssam 		scope_out(3);
52929954Skarels 		if (tp->t_flags & (RAW|LITOUT))
53030372Skarels 			n = ndqb(&tp->t_outq, 0);
53130372Skarels 		else {
53230372Skarels 			n = ndqb(&tp->t_outq, 0200);
53330372Skarels 			if (n == 0) {
53425675Ssam 				n = getc(&tp->t_outq);
53525881Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
53624003Ssam 				tp->t_state |= TS_TIMEOUT;
53730372Skarels 				n = 0;
53824003Ssam 			}
53930372Skarels 		}
54030372Skarels 		if (n) {
54124003Ssam 			tp->t_state |= TS_BUSY;
54230372Skarels 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
54324003Ssam 		}
54424003Ssam 	}
54524003Ssam 	splx(s);
54624003Ssam }
54724003Ssam 
54824003Ssam /*
54924003Ssam  * Stop output on a line.
55024003Ssam  */
55124003Ssam vxstop(tp)
55225881Ssam 	register struct tty *tp;
55324003Ssam {
55425881Ssam 	int s;
55524003Ssam 
55624003Ssam 	s = spl8();
55725881Ssam 	if (tp->t_state&TS_BUSY)
55825881Ssam 		if ((tp->t_state&TS_TTSTOP) == 0)
55924003Ssam 			tp->t_state |= TS_FLUSH;
56024003Ssam 	splx(s);
56124003Ssam }
56224003Ssam 
56325881Ssam static	int vxbbno = -1;
56424003Ssam /*
56524003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
56624003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
56725933Ssam  * viocx to establish interrupt vectors and logical port numbers.
56824003Ssam  */
56925881Ssam vxinit(vx, wait)
57025881Ssam 	register int vx;
57125881Ssam 	int wait;
57224003Ssam {
57325933Ssam 	register struct vx_softc *vs;
57425933Ssam 	register struct vxdevice *addr;
57525933Ssam 	register struct vxcmd *cp;
57625881Ssam 	register char *resp;
57725881Ssam 	register int j;
57830372Skarels 	char type, *typestring;
57924003Ssam 
58025881Ssam 	vs = &vx_softc[vx];
58125933Ssam 	vs->vs_type = 0;		/* vioc-x by default */
58225933Ssam 	addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
58325881Ssam 	type = addr->v_ident;
58425881Ssam 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
58525881Ssam 	if (vs->vs_vers == VXV_NEW)
58625881Ssam 		vs->vs_silosiz = addr->v_maxsilo;
58725881Ssam 	switch (type) {
58824003Ssam 
58925881Ssam 	case VXT_VIOCX:
59025881Ssam 	case VXT_VIOCX|VXT_NEW:
59130372Skarels 		typestring = "VIOC-X";
59230372Skarels 		/* set soft carrier for printer ports */
59330372Skarels 		for (j = 0; j < 16; j++)
59430372Skarels 			if (addr->v_portyp[j] == VXT_PARALLEL) {
59530372Skarels 				vs->vs_softCAR |= 1 << j;
59625881Ssam 				addr->v_dcd |= 1 << j;
59730372Skarels 			}
59825881Ssam 		break;
59924003Ssam 
60025881Ssam 	case VXT_PVIOCX:
60125881Ssam 	case VXT_PVIOCX|VXT_NEW:
60230372Skarels 		typestring = "VIOC-X (old connector panel)";
60325881Ssam 		break;
60425881Ssam 	case VXT_VIOCBOP:		/* VIOC-BOP */
60525881Ssam 		vs->vs_type = 1;
60625881Ssam 		vs->vs_bop = ++vxbbno;
60725881Ssam 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
60824003Ssam 
60925933Ssam 	default:
61025881Ssam 		printf("vx%d: unknown type %x\n", vx, type);
61130372Skarels 		vxinfo[vx]->ui_alive = 0;
61225881Ssam 		return;
61324003Ssam 	}
61425881Ssam 	vs->vs_nbr = -1;
61525933Ssam 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
61625933Ssam 	/*
61725933Ssam 	 * Initialize all cmd buffers by linking them
61825933Ssam 	 * into a free list.
61925933Ssam 	 */
62025881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
62125933Ssam 		cp = &vs->vs_lst[j];
62225933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
62325881Ssam 	}
62425881Ssam 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
62524003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
62624003Ssam 
62725933Ssam 	/*
62825933Ssam 	 * Establish the interrupt vectors and define the port numbers.
62925933Ssam 	 */
63025933Ssam 	cp = vobtain(vs);
63125933Ssam 	cp->cmd = VXC_LIDENT;
63225881Ssam 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
63325857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
63425857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
63525881Ssam 	cp->par[4] = 15;		/* max ports, no longer used */
63625881Ssam 	cp->par[5] = 0;			/* set 1st port number */
63730372Skarels 	(void) vcmd(vx, (caddr_t)&cp->cmd);
63825881Ssam 	if (!wait)
63925881Ssam 		return;
64025881Ssam 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
64125857Ssam 		;
64225857Ssam 	if (j >= 4000000)
64325881Ssam 		printf("vx%d: didn't respond to LIDENT\n", vx);
64424003Ssam 
64524003Ssam  	/* calculate address of response buffer */
64625881Ssam  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
64725933Ssam 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
64825933Ssam 		vrelease(vs, cp);	/* init failed */
64925881Ssam 		return;
65024003Ssam 	}
65125881Ssam 	vs->vs_loport = cp->par[5];
65225881Ssam 	vs->vs_hiport = cp->par[7];
65330372Skarels 	printf("vx%d: %s%s, ports %d-%d\n", vx,
65430372Skarels 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
65530372Skarels 	    vs->vs_loport, vs->vs_hiport);
65625881Ssam 	vrelease(vs, cp);
65725933Ssam 	vs->vs_nbr = vx;		/* assign board number */
65824003Ssam }
65924003Ssam 
66024003Ssam /*
66124003Ssam  * Obtain a command buffer
66224003Ssam  */
66325881Ssam struct vxcmd *
66425881Ssam vobtain(vs)
66525933Ssam 	register struct vx_softc *vs;
66624003Ssam {
66725933Ssam 	register struct vxcmd *p;
66825881Ssam 	int s;
66924003Ssam 
67024003Ssam 	s = spl8();
67125881Ssam 	p = vs->vs_avail;
67225881Ssam 	if (p == (struct vxcmd *)0) {
67324003Ssam #ifdef VX_DEBUG
67425881Ssam 		if (vxintr4&VXNOBUF)
67525881Ssam 			vxintr4 &= ~VXNOBUF;
67624003Ssam #endif
67725881Ssam 		printf("vx%d: no buffers\n", vs - vx_softc);
67825881Ssam 		vxstreset(vs - vx_softc);
67924003Ssam 		splx(s);
68025881Ssam 		return (vobtain(vs));
68124003Ssam 	}
68230372Skarels 	vs->vs_avail = p->c_fwd;
68324003Ssam 	splx(s);
68425881Ssam 	return ((struct vxcmd *)p);
68524003Ssam }
68624003Ssam 
68724003Ssam /*
68824003Ssam  * Release a command buffer
68924003Ssam  */
69025881Ssam vrelease(vs, cp)
69125933Ssam 	register struct vx_softc *vs;
69225933Ssam 	register struct vxcmd *cp;
69324003Ssam {
69425881Ssam 	int s;
69524003Ssam 
69624003Ssam #ifdef VX_DEBUG
69725881Ssam 	if (vxintr4&VXNOBUF)
69825881Ssam 		return;
69924003Ssam #endif
70024003Ssam 	s = spl8();
70125881Ssam 	cp->c_fwd = vs->vs_avail;
70225881Ssam 	vs->vs_avail = cp;
70324003Ssam 	splx(s);
70424003Ssam }
70524003Ssam 
70625881Ssam struct vxcmd *
70725881Ssam nextcmd(vs)
70825933Ssam 	register struct vx_softc *vs;
70924003Ssam {
71025933Ssam 	register struct vxcmd *cp;
71125881Ssam 	int s;
71224003Ssam 
71324003Ssam 	s = spl8();
71425881Ssam 	cp = vs->vs_build;
71525881Ssam 	vs->vs_build = (struct vxcmd *)0;
71624003Ssam 	splx(s);
71725881Ssam 	return (cp);
71824003Ssam }
71924003Ssam 
72024003Ssam /*
72125933Ssam  * Assemble transmits into a multiple command;
72230372Skarels  * up to 8 transmits to 8 lines can be assembled together
72330372Skarels  * (on PVIOCX only).
72424003Ssam  */
72525933Ssam vsetq(vs, line, addr, n)
72625933Ssam 	register struct vx_softc *vs;
72725881Ssam 	caddr_t	addr;
72824003Ssam {
72925933Ssam 	register struct vxcmd *cp;
73025933Ssam 	register struct vxmit *mp;
73124003Ssam 
73225933Ssam 	/*
73325933Ssam 	 * Grab a new command buffer or append
73425933Ssam 	 * to the current one being built.
73525933Ssam 	 */
73625881Ssam 	cp = vs->vs_build;
73725881Ssam 	if (cp == (struct vxcmd *)0) {
73825881Ssam 		cp = vobtain(vs);
73925881Ssam 		vs->vs_build = cp;
74025881Ssam 		cp->cmd = VXC_XMITDTA;
74124003Ssam 	} else {
74230372Skarels 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
74325881Ssam 			printf("vx%d: setq overflow\n", vs-vx_softc);
74430372Skarels 			vxstreset((int)vs->vs_nbr);
74530372Skarels 			return;
74624003Ssam 		}
74724003Ssam 		cp->cmd++;
74824003Ssam 	}
74925933Ssam 	/*
75025933Ssam 	 * Select the next vxmit buffer and copy the
75125933Ssam 	 * characters into the buffer (if there's room
75225933Ssam 	 * and the device supports ``immediate mode'',
75325933Ssam 	 * or store an indirect pointer to the data.
75425933Ssam 	 */
75525881Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
75625675Ssam 	mp->bcount = n-1;
75725933Ssam 	mp->line = line;
75825933Ssam 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
75925881Ssam 		cp->cmd = VXC_XMITIMM;
76030372Skarels 		bcopy(addr, mp->ostream, (unsigned)n);
76124003Ssam 	} else {
76225933Ssam 		/* get system address of clist block */
76325675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
76430372Skarels 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
76524003Ssam 	}
76630372Skarels 	/*
76730372Skarels 	 * We send the data immediately if a VIOCX,
76830372Skarels 	 * the command buffer is full, or if we've nothing
76930372Skarels 	 * currently outstanding.  If we don't send it,
77030372Skarels 	 * set a timeout to force the data to be sent soon.
77130372Skarels 	 */
77230372Skarels 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
77330372Skarels 	    vs->vs_xmtcnt == 0) {
77430372Skarels 		vs->vs_xmtcnt++;
77530372Skarels 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
77630372Skarels 		vs->vs_build = 0;
77730372Skarels 	} else
77830372Skarels 		timeout(vxforce, (caddr_t)vs, 3);
77924003Ssam }
78025881Ssam 
78125881Ssam /*
78225881Ssam  * Write a command out to the VIOC
78325881Ssam  */
78425881Ssam vcmd(vx, cmdad)
78525881Ssam 	register int vx;
78625881Ssam 	register caddr_t cmdad;
78725881Ssam {
78825933Ssam 	register struct vcmds *cp;
78925881Ssam 	register struct vx_softc *vs;
79025881Ssam 	int s;
79125881Ssam 
79225881Ssam 	s = spl8();
79325881Ssam 	vs = &vx_softc[vx];
79425933Ssam 	/*
79525933Ssam 	 * When the vioc is resetting, don't process
79625933Ssam 	 * anything other than VXC_LIDENT commands.
79725933Ssam 	 */
79825881Ssam 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
79925933Ssam 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
80025881Ssam 
80125933Ssam 		if (vcp->cmd != VXC_LIDENT) {
80225933Ssam 			vrelease(vs, vcp);
80325881Ssam 			return (0);
80425881Ssam 		}
80525881Ssam 	}
80625881Ssam 	cp = &vs->vs_cmds;
80725881Ssam 	if (cmdad != (caddr_t)0) {
80825881Ssam 		cp->cmdbuf[cp->v_fill] = cmdad;
80925881Ssam 		if (++cp->v_fill >= VC_CMDBUFL)
81025881Ssam 			cp->v_fill = 0;
81125881Ssam 		if (cp->v_fill == cp->v_empty) {
81225881Ssam 			printf("vx%d: cmd q overflow\n", vx);
81325881Ssam 			vxstreset(vx);
81425881Ssam 			splx(s);
81525881Ssam 			return (0);
81625881Ssam 		}
81725881Ssam 		cp->v_cmdsem++;
81825881Ssam 	}
81925881Ssam 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
82025881Ssam 		cp->v_cmdsem--;
82125881Ssam 		cp->v_curcnt++;
82225881Ssam 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
82325881Ssam 	}
82425881Ssam 	splx(s);
82525881Ssam 	return (1);
82625881Ssam }
82725881Ssam 
82825881Ssam /*
82925881Ssam  * VIOC acknowledge interrupt.  The VIOC has received the new
83025881Ssam  * command.  If no errors, the new command becomes one of 16 (max)
83125881Ssam  * current commands being executed.
83225881Ssam  */
83325881Ssam vackint(vx)
83425881Ssam 	register vx;
83525881Ssam {
83625933Ssam 	register struct vxdevice *vp;
83725933Ssam 	register struct vcmds *cp;
83825881Ssam 	struct vx_softc *vs;
83925881Ssam 	int s;
84025881Ssam 
84125881Ssam 	scope_out(5);
84225881Ssam 	vs = &vx_softc[vx];
84329954Skarels 	if (vs->vs_type)	/* Its a BOP */
84425881Ssam 		return;
84525881Ssam 	s = spl8();
84625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
84725881Ssam 	cp = &vs->vs_cmds;
84825933Ssam 	if (vp->v_vcid&V_ERR) {
84925881Ssam 		register char *resp;
85025881Ssam 		register i;
85125933Ssam 
85230372Skarels 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
85325881Ssam 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
85425881Ssam 		resp = (char *)vs->vs_mricmd;
85525881Ssam 		for (i = 0; i < 16; i++)
85625881Ssam 			printf("%x ", resp[i]&0xff);
85725881Ssam 		printf("\n");
85825881Ssam 		splx(s);
85925881Ssam 		vxstreset(vx);
86025881Ssam 		return;
86125881Ssam 	}
86225881Ssam 	if ((vp->v_hdwre&017) == CMDquals) {
86325881Ssam #ifdef VX_DEBUG
86425881Ssam 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
86525933Ssam 			struct vxcmd *cp1, *cp0;
86625881Ssam 
86725933Ssam 			cp0 = (struct vxcmd *)
86825933Ssam 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
86925881Ssam 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
87025881Ssam 				cp1 = vobtain(vs);
87125881Ssam 				*cp1 = *cp0;
87225881Ssam 				vxintr4 &= ~VXERR4;
87325881Ssam 				(void) vcmd(vx, &cp1->cmd);
87425881Ssam 			}
87525881Ssam 		}
87625881Ssam #endif
87725881Ssam 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
87825881Ssam 		if (++cp->v_empty >= VC_CMDBUFL)
87925881Ssam 			cp->v_empty = 0;
88025881Ssam 	}
88125881Ssam 	if (++cp->v_itrempt >= VC_IQLEN)
88225881Ssam 		cp->v_itrempt = 0;
88325881Ssam 	vintempt(vx);
88425881Ssam 	splx(s);
88525881Ssam 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
88625881Ssam }
88725881Ssam 
88825881Ssam /*
88925881Ssam  * Command Response interrupt.  The Vioc has completed
89025881Ssam  * a command.  The command may now be returned to
89125881Ssam  * the appropriate device driver.
89225881Ssam  */
89325881Ssam vcmdrsp(vx)
89425881Ssam 	register vx;
89525881Ssam {
89625933Ssam 	register struct vxdevice *vp;
89725933Ssam 	register struct vcmds *cp;
89825881Ssam 	register caddr_t cmd;
89925881Ssam 	register struct vx_softc *vs;
90025881Ssam 	register char *resp;
90125881Ssam 	register k;
90225881Ssam 	register int s;
90325881Ssam 
90425881Ssam 	scope_out(6);
90525881Ssam 	vs = &vx_softc[vx];
90625881Ssam 	if (vs->vs_type) {	/* Its a BOP */
90725881Ssam 		printf("vx%d: vcmdrsp interrupt\n", vx);
90825881Ssam 		return;
90925881Ssam 	}
91025881Ssam 	s = spl8();
91125881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
91225881Ssam 	cp = &vs->vs_cmds;
91325881Ssam 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
91425881Ssam 	if (((k = resp[1])&V_UNBSY) == 0) {
91525881Ssam 		printf("vx%d: cmdresp debug\n", vx);
91625881Ssam 		splx(s);
91725881Ssam 		vxstreset(vx);
91825881Ssam 		return;
91925881Ssam 	}
92025881Ssam 	k &= VCMDLEN-1;
92125881Ssam 	cmd = cp->v_curcmd[k];
92225881Ssam 	cp->v_curcmd[k] = (caddr_t)0;
92325881Ssam 	cp->v_curcnt--;
92425881Ssam 	k = *((short *)&resp[4]);	/* cmd operation code */
92525881Ssam 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
92625881Ssam 		for (k = 0; k < VRESPLEN; k++)
92725881Ssam 			cmd[k] = resp[k+4];
92825881Ssam 	resp[1] = 0;
92925881Ssam 	vxxint(vx, (struct vxcmd *)cmd);
93025881Ssam 	if (vs->vs_state == VXS_READY)
93125881Ssam 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
93225881Ssam 	splx(s);
93325881Ssam }
93425881Ssam 
93525881Ssam /*
93625881Ssam  * Unsolicited interrupt.
93725881Ssam  */
93825881Ssam vunsol(vx)
93925881Ssam 	register vx;
94025881Ssam {
94125933Ssam 	register struct vxdevice *vp;
94225881Ssam 	struct vx_softc *vs;
94325881Ssam 	int s;
94425881Ssam 
94525881Ssam 	scope_out(1);
94625881Ssam 	vs = &vx_softc[vx];
94725881Ssam 	if (vs->vs_type) {	/* Its a BOP */
94825881Ssam 		printf("vx%d: vunsol from BOP\n", vx);
94925881Ssam 		return;
95025881Ssam 	}
95125881Ssam 	s = spl8();
95225881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
95325881Ssam 	if (vp->v_uqual&V_UNBSY) {
95425881Ssam 		vxrint(vx);
95525881Ssam 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
95625881Ssam #ifdef notdef
95725881Ssam 	} else {
95825881Ssam 		printf("vx%d: unsolicited interrupt error\n", vx);
95925881Ssam 		splx(s);
96025881Ssam 		vxstreset(vx);
96125881Ssam #endif
96225881Ssam 	}
96325881Ssam 	splx(s);
96425881Ssam }
96525881Ssam 
96625881Ssam /*
96725933Ssam  * Enqueue an interrupt.
96825881Ssam  */
96925881Ssam vinthandl(vx, item)
97025881Ssam 	register int vx;
97125881Ssam 	register item;
97225881Ssam {
97325881Ssam 	register struct vcmds *cp;
97425881Ssam 	int empty;
97525881Ssam 
97625881Ssam 	cp = &vx_softc[vx].vs_cmds;
97725933Ssam 	empty = (cp->v_itrfill == cp->v_itrempt);
97825881Ssam 	cp->v_itrqueu[cp->v_itrfill] = item;
97925881Ssam 	if (++cp->v_itrfill >= VC_IQLEN)
98025881Ssam 		cp->v_itrfill = 0;
98125881Ssam 	if (cp->v_itrfill == cp->v_itrempt) {
98225881Ssam 		printf("vx%d: interrupt q overflow\n", vx);
98325881Ssam 		vxstreset(vx);
98425881Ssam 	} else if (empty)
98525881Ssam 		vintempt(vx);
98625881Ssam }
98725881Ssam 
98825881Ssam vintempt(vx)
98925881Ssam 	register int vx;
99025881Ssam {
99125881Ssam 	register struct vcmds *cp;
99225881Ssam 	register struct vxdevice *vp;
99325881Ssam 	register short item;
99425881Ssam 	register short *intr;
99525881Ssam 
99625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
99725881Ssam 	if (vp->v_vioc&V_BSY)
99825881Ssam 		return;
99925881Ssam 	cp = &vx_softc[vx].vs_cmds;
100025881Ssam 	if (cp->v_itrempt == cp->v_itrfill)
100125881Ssam 		return;
100225881Ssam 	item = cp->v_itrqueu[cp->v_itrempt];
100325881Ssam 	intr = (short *)&vp->v_vioc;
100425881Ssam 	switch ((item >> 8)&03) {
100525881Ssam 
100625881Ssam 	case CMDquals: {		/* command */
100725881Ssam 		int phys;
100825881Ssam 
100925881Ssam 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
101025881Ssam 			break;
101125881Ssam 		vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
101225881Ssam 		phys = vtoph((struct proc *)0,
101325881Ssam 		    (unsigned)cp->cmdbuf[cp->v_empty]);
101425881Ssam 		vp->v_vcp[0] = ((short *)&phys)[0];
101525881Ssam 		vp->v_vcp[1] = ((short *)&phys)[1];
101625881Ssam 		vp->v_vcbsy = V_BSY;
101725881Ssam 		*intr = item;
101825881Ssam 		scope_out(4);
101925881Ssam 		break;
102025881Ssam 	}
102125881Ssam 
102225881Ssam 	case RSPquals:		/* command response */
102325881Ssam 		*intr = item;
102425881Ssam 		scope_out(7);
102525881Ssam 		break;
102625881Ssam 
102725881Ssam 	case UNSquals:		/* unsolicited interrupt */
102825881Ssam 		vp->v_uqual = 0;
102925881Ssam 		*intr = item;
103025881Ssam 		scope_out(2);
103125881Ssam 		break;
103225881Ssam 	}
103325881Ssam }
103425881Ssam 
103525881Ssam /*
103625881Ssam  * Start a reset on a vioc after error (hopefully)
103725881Ssam  */
103825881Ssam vxstreset(vx)
103925881Ssam 	register vx;
104025881Ssam {
104125881Ssam 	register struct vx_softc *vs;
104225933Ssam 	register struct vxdevice *vp;
104325881Ssam 	register struct vxcmd *cp;
104425881Ssam 	register int j;
104525881Ssam 	extern int vxinreset();
104625881Ssam 	int s;
104725881Ssam 
104825881Ssam 	s = spl8() ;
104925881Ssam 	vs = &vx_softc[vx];
105025881Ssam 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
105125881Ssam 		splx(s);
105225881Ssam 		return;
105325881Ssam 	}
105425881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
105525881Ssam 	/*
105625881Ssam 	 * Zero out the vioc structures, mark the vioc as being
105725881Ssam 	 * reset, reinitialize the free command list, reset the vioc
105825881Ssam 	 * and start a timer to check on the progress of the reset.
105925881Ssam 	 */
106025881Ssam 	bzero((caddr_t)vs, (unsigned)sizeof (*vs));
106125881Ssam 
106225881Ssam 	/*
106325881Ssam 	 * Setting VXS_RESET prevents others from issuing
106425881Ssam 	 * commands while allowing currently queued commands to
106525881Ssam 	 * be passed to the VIOC.
106625881Ssam 	 */
106725881Ssam 	vs->vs_state = VXS_RESET;
106825881Ssam 	/* init all cmd buffers */
106925881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
107025933Ssam 		cp = &vs->vs_lst[j];
107125933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
107225881Ssam 	}
107325933Ssam 	vs->vs_avail = &vs->vs_lst[0];
107425933Ssam 	cp->c_fwd = (struct vxcmd *)0;
107525881Ssam 	printf("vx%d: reset...", vx);
107625881Ssam 	vp->v_fault = 0;
107725881Ssam 	vp->v_vioc = V_BSY;
107825933Ssam 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
107925881Ssam 	timeout(vxinreset, (caddr_t)vx, hz*5);
108025881Ssam 	splx(s);
108125881Ssam }
108225881Ssam 
108325881Ssam /* continue processing a reset on a vioc after an error (hopefully) */
108425881Ssam vxinreset(vx)
108525881Ssam 	int vx;
108625881Ssam {
108725933Ssam 	register struct vxdevice *vp;
108825881Ssam 	int s = spl8();
108925881Ssam 
109025881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
109125881Ssam 	/*
109225881Ssam 	 * See if the vioc has reset.
109325881Ssam 	 */
109425881Ssam 	if (vp->v_fault != VXF_READY) {
109525881Ssam 		printf("failed\n");
109625881Ssam 		splx(s);
109725881Ssam 		return;
109825881Ssam 	}
109925881Ssam 	/*
110025881Ssam 	 * Send a LIDENT to the vioc and mess with carrier flags
110125881Ssam 	 * on parallel printer ports.
110225881Ssam 	 */
110329954Skarels 	vxinit(vx, 0);
110425881Ssam 	splx(s);
110525881Ssam }
110625881Ssam 
110725881Ssam /*
110825933Ssam  * Finish the reset on the vioc after an error (hopefully).
110925933Ssam  *
111025881Ssam  * Restore modem control, parameters and restart output.
111125881Ssam  * Since the vioc can handle no more then 24 commands at a time
111225881Ssam  * and we could generate as many as 48 commands, we must do this in
111325881Ssam  * phases, issuing no more then 16 commands at a time.
111425881Ssam  */
111525881Ssam vxfnreset(vx, cp)
111625881Ssam 	register int vx;
111725881Ssam 	register struct vxcmd *cp;
111825881Ssam {
111925881Ssam 	register struct vx_softc *vs;
112025933Ssam 	register struct vxdevice *vp ;
112125881Ssam 	register struct tty *tp, *tp0;
112225881Ssam 	register int i;
112325881Ssam #ifdef notdef
112425881Ssam 	register int on;
112525881Ssam #endif
112625881Ssam 	extern int vxrestart();
112725881Ssam 	int s = spl8();
112825881Ssam 
112925881Ssam 	vs = &vx_softc[vx];
113025881Ssam 	vs->vs_loport = cp->par[5];
113125881Ssam 	vs->vs_hiport = cp->par[7];
113225881Ssam 	vrelease(vs, cp);
113325881Ssam 	vs->vs_nbr = vx;			/* assign VIOC-X board number */
113425881Ssam 	vs->vs_state = VXS_READY;
113525881Ssam 
113625881Ssam 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
113725881Ssam 	vp->v_vcid = 0;
113825881Ssam 
113925881Ssam 	/*
114025881Ssam 	 * Restore modem information and control.
114125881Ssam 	 */
114225881Ssam 	tp0 = &vx_tty[vx*16];
114325881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
114425881Ssam 		tp = tp0 + i;
114525881Ssam 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
114625881Ssam 			tp->t_state &= ~TS_CARR_ON;
114725881Ssam 			vcmodem(tp->t_dev, VMOD_ON);
114825881Ssam 			if (tp->t_state&TS_CARR_ON)
114929954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
115029954Skarels 			else if (tp->t_state & TS_ISOPEN)
115129954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
115225881Ssam 		}
115329954Skarels #ifdef notdef
115425881Ssam 		/*
115525881Ssam 		 * If carrier has changed while we were resetting,
115625881Ssam 		 * take appropriate action.
115725881Ssam 		 */
115825881Ssam 		on = vp->v_dcd & 1<<i;
115929954Skarels 		if (on && (tp->t_state&TS_CARR_ON) == 0)
116029954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
116129954Skarels 		else if (!on && tp->t_state&TS_CARR_ON)
116229954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
116325881Ssam #endif
116425881Ssam 	}
116525881Ssam 	vs->vs_state = VXS_RESET;
116625881Ssam 	timeout(vxrestart, (caddr_t)vx, hz);
116725881Ssam 	splx(s);
116825881Ssam }
116925881Ssam 
117025881Ssam /*
117125881Ssam  * Restore a particular aspect of the VIOC.
117225881Ssam  */
117325881Ssam vxrestart(vx)
117425881Ssam 	int vx;
117525881Ssam {
117625881Ssam 	register struct tty *tp, *tp0;
117725881Ssam 	register struct vx_softc *vs;
117830372Skarels 	register int i, count;
117925881Ssam 	int s = spl8();
118025881Ssam 
118130372Skarels 	count = vx >> 8;
118225881Ssam 	vx &= 0xff;
118325881Ssam 	vs = &vx_softc[vx];
118425881Ssam 	vs->vs_state = VXS_READY;
118525881Ssam 	tp0 = &vx_tty[vx*16];
118625881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
118725881Ssam 		tp = tp0 + i;
118830372Skarels 		if (count != 0) {
118925881Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
119025881Ssam 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
119125881Ssam 				vxstart(tp);	/* restart pending output */
119225881Ssam 		} else {
119325881Ssam 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
119425881Ssam 				vxcparam(tp->t_dev, 0);
119525881Ssam 		}
119625881Ssam 	}
119730372Skarels 	if (count == 0) {
119825881Ssam 		vs->vs_state = VXS_RESET;
119925881Ssam 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
120025881Ssam 	} else
120125881Ssam 		printf("done\n");
120225881Ssam 	splx(s);
120325881Ssam }
120425881Ssam 
120525881Ssam vxreset(dev)
120625881Ssam 	dev_t dev;
120725881Ssam {
120825881Ssam 
120930372Skarels 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
121025881Ssam }
121125881Ssam 
121230372Skarels #ifdef notdef
121325881Ssam vxfreset(vx)
121425881Ssam 	register int vx;
121525881Ssam {
121625881Ssam 	struct vba_device *vi;
121725881Ssam 
121825881Ssam 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
121925881Ssam 		return (ENODEV);
122025881Ssam 	vx_softc[vx].vs_state = VXS_READY;
122125881Ssam 	vxstreset(vx);
122225881Ssam 	return (0);		/* completes asynchronously */
122325881Ssam }
122430372Skarels #endif
122525881Ssam 
122625881Ssam vcmodem(dev, flag)
122725881Ssam 	dev_t dev;
122825881Ssam {
122925881Ssam 	struct tty *tp;
123025881Ssam 	register struct vxcmd *cp;
123125881Ssam 	register struct vx_softc *vs;
123225881Ssam 	register struct vxdevice *kp;
123325881Ssam 	register port;
123425881Ssam 	int unit;
123525881Ssam 
123625881Ssam 	unit = minor(dev);
123725881Ssam 	tp = &vx_tty[unit];
123825881Ssam 	vs = (struct vx_softc *)tp->t_addr;
123930372Skarels 	if (vs->vs_state != VXS_READY)
124030372Skarels 		return;
124125881Ssam 	cp = vobtain(vs);
124225881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
124325881Ssam 
124425881Ssam 	port = unit & 017;
124525881Ssam 	/*
124625881Ssam 	 * Issue MODEM command
124725881Ssam 	 */
124825881Ssam 	cp->cmd = VXC_MDMCTL;
124930372Skarels 	if (flag == VMOD_ON) {
125030372Skarels 		if (vs->vs_softCAR & (1 << port))
125130372Skarels 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
125230372Skarels 		else
125330372Skarels 			cp->par[0] = V_AUTO | V_DTR_ON | V_RTS;
125430372Skarels 	} else
125530372Skarels 		cp->par[0] = V_DTR_OFF;
125625881Ssam 	cp->par[1] = port;
125730372Skarels 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
125830372Skarels 	if (vs->vs_softCAR & (1 << port))
125930372Skarels 		kp->v_dcd |= (1 << port);
126030372Skarels 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
126130372Skarels 		tp->t_state |= TS_CARR_ON;
126225881Ssam }
126325881Ssam 
126425881Ssam /*
126525881Ssam  * VCMINTR called when an unsolicited interrup occurs signaling
126625881Ssam  * some change of modem control state.
126725881Ssam  */
126825881Ssam vcmintr(vx)
126925881Ssam 	register vx;
127025881Ssam {
127125881Ssam 	register struct vxdevice *kp;
127225881Ssam 	register struct tty *tp;
127325881Ssam 	register port;
127430372Skarels 	register struct vx_softc *vs;
127525881Ssam 
127625881Ssam 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
127725881Ssam 	port = kp->v_usdata[0] & 017;
127825881Ssam 	tp = &vx_tty[vx*16+port];
127930372Skarels 	vs = &vx_softc[vx];
128025881Ssam 
128129954Skarels 	if (kp->v_ustat & DCD_ON)
128229954Skarels 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
128329954Skarels 	else if ((kp->v_ustat & DCD_OFF) &&
128430372Skarels 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
128529954Skarels 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
128629954Skarels 		register struct vcmds *cp;
128729954Skarels 		register struct vxcmd *cmdp;
128825881Ssam 
128930372Skarels 		/* clear all pending transmits */
129029954Skarels 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
129129954Skarels 		    vs->vs_vers == VXV_NEW) {
129229954Skarels 			int i, cmdfound = 0;
129325881Ssam 
129429954Skarels 			cp = &vs->vs_cmds;
129529954Skarels 			for (i = cp->v_empty; i != cp->v_fill; ) {
129629954Skarels 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
129729954Skarels 				if ((cmdp->cmd == VXC_XMITDTA ||
129829954Skarels 				    cmdp->cmd == VXC_XMITIMM) &&
129929954Skarels 				    ((struct vxmit *)cmdp->par)->line == port) {
130029954Skarels 					cmdfound++;
130125881Ssam 					cmdp->cmd = VXC_FDTATOX;
130225881Ssam 					cmdp->par[1] = port;
130325881Ssam 				}
130429954Skarels 				if (++i >= VC_CMDBUFL)
130529954Skarels 					i = 0;
130625881Ssam 			}
130729954Skarels 			if (cmdfound)
130829954Skarels 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
130929954Skarels 			/* cmd is already in vioc, have to flush it */
131029954Skarels 			else {
131129954Skarels 				cmdp = vobtain(vs);
131229954Skarels 				cmdp->cmd = VXC_FDTATOX;
131329954Skarels 				cmdp->par[1] = port;
131430372Skarels 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
131525881Ssam 			}
131625881Ssam 		}
131729954Skarels 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
131830372Skarels 		(*linesw[tp->t_line].l_rint)((tp->t_flags & RAW) ?
131930372Skarels 		    0 : tp->t_intrc, tp);
132025881Ssam 		return;
132125881Ssam 	}
132225881Ssam }
132325881Ssam #endif
1324