xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 44535)
134406Skarels /*
234406Skarels  * Copyright (c) 1988 Regents of the University of California.
335057Skarels  * All rights reserved.
434406Skarels  *
535057Skarels  * This code is derived from software contributed to Berkeley by
635057Skarels  * Computer Consoles Inc.
735057Skarels  *
8*44535Sbostic  * %sccs.include.redist.c%
935057Skarels  *
10*44535Sbostic  *	@(#)vx.c	7.11 (Berkeley) 06/28/90
1134406Skarels  */
1224003Ssam 
1324003Ssam #include "vx.h"
1424003Ssam #if NVX > 0
1524003Ssam /*
1625857Ssam  * VIOC-X driver
1724003Ssam  */
1825877Ssam #ifdef VXPERF
1925948Ssam #define	DOSCOPE
2025877Ssam #endif
2125877Ssam 
2225877Ssam #include "param.h"
2325877Ssam #include "ioctl.h"
2425877Ssam #include "tty.h"
2525877Ssam #include "user.h"
2625877Ssam #include "map.h"
2725877Ssam #include "buf.h"
2825877Ssam #include "conf.h"
2925877Ssam #include "file.h"
3025877Ssam #include "proc.h"
3125877Ssam #include "vm.h"
3225881Ssam #include "kernel.h"
3329954Skarels #include "syslog.h"
3425675Ssam 
3534406Skarels #include "../tahoe/pte.h"
3634406Skarels 
3725675Ssam #include "../tahoevba/vbavar.h"
3838114Sbostic #include "../tahoevba/vbaparam.h"
3925881Ssam #include "../tahoevba/vxreg.h"
4025675Ssam #include "../tahoevba/scope.h"
4124003Ssam 
4225881Ssam #ifdef VX_DEBUG
4325881Ssam long	vxintr4 = 0;
4425948Ssam #define	VXERR4	1
4525948Ssam #define	VXNOBUF	2
4625881Ssam long	vxdebug = 0;
4725948Ssam #define	VXVCM	1
4825948Ssam #define	VXVCC	2
4925948Ssam #define	VXVCX	4
5025881Ssam #endif
5124003Ssam 
5225881Ssam /*
5325881Ssam  * Interrupt type bits passed to vinthandl().
5425881Ssam  */
5525948Ssam #define	CMDquals 0		/* command completed interrupt */
5625948Ssam #define	RSPquals 1		/* command response interrupt */
5725948Ssam #define	UNSquals 2		/* unsolicited interrupt */
5824003Ssam 
5930372Skarels #define	VXUNIT(n)	((n) >> 4)
6030372Skarels #define	VXPORT(n)	((n) & 0xf)
6130372Skarels 
6225881Ssam struct	tty vx_tty[NVX*16];
6329954Skarels #ifndef lint
6429954Skarels int	nvx = NVX*16;
6529954Skarels #endif
6625881Ssam int	vxstart(), ttrstrt();
6725881Ssam struct	vxcmd *vobtain(), *nextcmd();
6824003Ssam 
6924003Ssam /*
7024003Ssam  * Driver information for auto-configuration stuff.
7124003Ssam  */
7224003Ssam int	vxprobe(), vxattach(), vxrint();
7325881Ssam struct	vba_device *vxinfo[NVX];
7424003Ssam long	vxstd[] = { 0 };
7524003Ssam struct	vba_driver vxdriver =
7625857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
7724003Ssam 
7825881Ssam struct	vx_softc {
7940738Skarels 	struct	vxdevice *vs_addr;	/* H/W address */
8025881Ssam 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
8125881Ssam 	u_char	vs_bop;		/* bop board # for vioc-bop's */
8225881Ssam 	u_char	vs_loport;	/* low port nbr */
8325881Ssam 	u_char	vs_hiport;	/* high port nbr */
8425881Ssam 	u_short	vs_nbr;		/* viocx number */
8525881Ssam 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
8625881Ssam 	u_short	vs_silosiz;	/* silo size */
8725881Ssam 	short	vs_vers;	/* vioc/pvioc version */
8825948Ssam #define	VXV_OLD	0		/* PVIOCX | VIOCX */
8925948Ssam #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
9025881Ssam 	short 	vs_state;	/* controller state */
9125948Ssam #define	VXS_READY	0	/* ready for commands */
9225948Ssam #define	VXS_RESET	1	/* in process of reseting */
9330372Skarels 	u_short	vs_softCAR;	/* soft carrier */
9440738Skarels 	u_int	vs_ivec;	/* interrupt vector base */
9525881Ssam 	caddr_t vs_mricmd;	/* most recent issued cmd */
9640738Skarels 	/* The remaining fields are zeroed on reset... */
9740738Skarels #define vs_zero vs_xmtcnt
9840738Skarels 	int	vs_xmtcnt;	/* xmit commands pending */
9925881Ssam 	struct	vxcmd *vs_avail;/* next available command buffer */
10025881Ssam 	struct	vxcmd *vs_build;
10125881Ssam 	struct	vxcmd vs_lst[NVCXBUFS];
10225881Ssam 	struct	vcmds vs_cmds;
10325881Ssam } vx_softc[NVX];
10424003Ssam 
10537608Smarc struct speedtab vxspeedtab[] = {
10637608Smarc 	EXTA,	V19200,
10737608Smarc 	EXTB,	V19200,
10837608Smarc 	19200,	V19200,
10937608Smarc 	9600,	13,
11037608Smarc 	4800,	12,
11137608Smarc 	2400,	11,
11237608Smarc 	1800,	10,
11337608Smarc 	1200,	9,
11437608Smarc 	600,	8,
11537608Smarc 	300,	7,
11637608Smarc 	200,	6,
11737608Smarc 	150,	5,
11837608Smarc 	134,	4,
11937608Smarc 	110,	3,
12037608Smarc 	75,	2,
12137608Smarc 	50,	1,
12237608Smarc 	0,	0,
12337608Smarc 	-1,	-1,
12437608Smarc };
12537608Smarc 
12625857Ssam vxprobe(reg, vi)
12724003Ssam 	caddr_t reg;
12825857Ssam 	struct vba_device *vi;
12924003Ssam {
13025857Ssam 	register int br, cvec;			/* must be r12, r11 */
13138114Sbostic 	register struct vxdevice *vp;
13225881Ssam 	register struct vx_softc *vs;
13338114Sbostic 	struct pte *dummypte;
13424003Ssam 
13524003Ssam #ifdef lint
13624003Ssam 	br = 0; cvec = br; br = cvec;
13740738Skarels 	vackint(0); vunsol(0); vcmdrsp(0);
13840738Skarels #ifdef VX_DEBUG
13940738Skarels 	vxfreset(0);
14024003Ssam #endif
14140738Skarels #endif /* lint */
14240738Skarels 	/*
14340738Skarels 	 * If on an HCX-9, the device has a 32-bit address,
14440738Skarels 	 * and we receive that address so we can set up a map.
14540738Skarels 	 * On VERSAbus devices, the address is 24-bit, and is
14640738Skarels 	 * already mapped (into vmem[]) by autoconf.
14740738Skarels 	 */
14840738Skarels 	if (!(reg >= vmem && reg < &vmem[ctob(VBIOSIZE)]) &&	/* XXX */
14940738Skarels 	    !vbmemalloc(16, reg, &dummypte, &reg)) {
15038114Sbostic 		printf("vx%d: vbmemalloc failed.\n", vi->ui_unit);
15138114Sbostic 		return(0);
15238114Sbostic 	}
15338114Sbostic 	vp = (struct vxdevice *)reg;
15425675Ssam 	if (badaddr((caddr_t)vp, 1))
15525675Ssam 		return (0);
15625675Ssam 	vp->v_fault = 0;
15725675Ssam 	vp->v_vioc = V_BSY;
15825675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
15924003Ssam 	DELAY(4000000);
16025881Ssam 	if (vp->v_fault != VXF_READY)
16125675Ssam 		return (0);
16225881Ssam 	vs = &vx_softc[vi->ui_unit];
16325857Ssam #ifdef notdef
16425857Ssam 	/*
16525857Ssam 	 * Align vioc interrupt vector base to 4 vector
16625857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
16725857Ssam 	 * wish we had documentation).
16825857Ssam 	 */
16925857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
17025857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
17125881Ssam 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
17225857Ssam #else
17325881Ssam 	vs->vs_ivec = 0x40+vi->ui_unit*4;
17425857Ssam #endif
17525881Ssam 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
17625881Ssam 	return (sizeof (struct vxdevice));
17724003Ssam }
17824003Ssam 
17925857Ssam vxattach(vi)
18025857Ssam 	register struct vba_device *vi;
18124003Ssam {
18240738Skarels 	register struct vx_softc *vs = &vx_softc[vi->ui_unit];
18325675Ssam 
18440738Skarels 	vs->vs_softCAR = vi->ui_flags;
18540738Skarels 	vs->vs_addr = (struct vxdevice *)vi->ui_addr;
18629954Skarels 	vxinit(vi->ui_unit, 1);
18724003Ssam }
18824003Ssam 
18924003Ssam /*
19024003Ssam  * Open a VX line.
19124003Ssam  */
19225675Ssam /*ARGSUSED*/
19324003Ssam vxopen(dev, flag)
19425881Ssam 	dev_t dev;
19525881Ssam 	int flag;
19624003Ssam {
19724003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
19825881Ssam 	register struct vx_softc *vs;
19925881Ssam 	register struct vba_device *vi;
20040738Skarels 	int unit, vx, s, error = 0;
20137608Smarc 	int vxparam();
20224003Ssam 
20325881Ssam 	unit = minor(dev);
20430372Skarels 	vx = VXUNIT(unit);
20530372Skarels 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
20625881Ssam 		return (ENXIO);
20730372Skarels 	vs = &vx_softc[vx];
20825881Ssam 	tp = &vx_tty[unit];
20930372Skarels 	unit = VXPORT(unit);
21025881Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
21125881Ssam 		return (EBUSY);
21230372Skarels 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
21325881Ssam 		return (ENXIO);
21425881Ssam 	tp->t_addr = (caddr_t)vs;
21525881Ssam 	tp->t_oproc = vxstart;
21637608Smarc 	tp->t_param = vxparam;
21725881Ssam 	tp->t_dev = dev;
21825881Ssam 	s = spl8();
21925881Ssam 	if ((tp->t_state&TS_ISOPEN) == 0) {
22042951Smarc 		tp->t_state |= TS_WOPEN;
22125881Ssam 		ttychars(tp);
22225881Ssam 		if (tp->t_ispeed == 0) {
22337608Smarc 			tp->t_iflag = TTYDEF_IFLAG;
22437608Smarc 			tp->t_oflag = TTYDEF_OFLAG;
22537608Smarc 			tp->t_lflag = TTYDEF_LFLAG;
22637608Smarc 			tp->t_cflag = TTYDEF_CFLAG;
22737608Smarc 			tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
22824003Ssam 		}
22937608Smarc 		vxparam(tp, &tp->t_termios);
23037608Smarc 		ttsetwater(tp);
23124003Ssam 	}
23230372Skarels 	vcmodem(dev, VMOD_ON);
23337608Smarc 	while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) &&
23442957Smarc 	      (tp->t_state&TS_CARR_ON) == 0) {
23542951Smarc 		tp->t_state |= TS_WOPEN;
23644397Smarc 		if (error = ttysleep(tp, (caddr_t)&tp->t_rawq, TTIPRI | PCATCH,
23744397Smarc 		    ttopen, 0))
23840738Skarels 			break;
23942957Smarc 	}
24040738Skarels 	if (error == 0)
24140738Skarels 		error = (*linesw[tp->t_line].l_open)(dev,tp);
24225881Ssam 	splx(s);
24325881Ssam 	return (error);
24424003Ssam }
24524003Ssam 
24624003Ssam /*
24724003Ssam  * Close a VX line.
24824003Ssam  */
24925675Ssam /*ARGSUSED*/
25024003Ssam vxclose(dev, flag)
25125881Ssam 	dev_t dev;
25225881Ssam 	int flag;
25324003Ssam {
25424003Ssam 	register struct tty *tp;
25540738Skarels 	int unit, s, error = 0;
25624003Ssam 
25725881Ssam 	unit = minor(dev);
25825881Ssam 	tp = &vx_tty[unit];
25925881Ssam 	s = spl8();
26024003Ssam 	(*linesw[tp->t_line].l_close)(tp);
26137608Smarc 	if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0)
26230372Skarels 		vcmodem(dev, VMOD_OFF);
26324003Ssam 	/* wait for the last response */
26440738Skarels 	while (tp->t_state&TS_FLUSH && error == 0)
26540738Skarels 		error = tsleep((caddr_t)&tp->t_state, TTOPRI | PCATCH,
26640738Skarels 		    ttclos, 0);
26725881Ssam 	splx(s);
26840738Skarels 	if (error)
26940738Skarels 		return (error);
27040738Skarels 	return (ttyclose(tp));
27124003Ssam }
27224003Ssam 
27324003Ssam /*
27424003Ssam  * Read from a VX line.
27524003Ssam  */
27637608Smarc vxread(dev, uio, flag)
27724003Ssam 	dev_t dev;
27824003Ssam 	struct uio *uio;
27924003Ssam {
28025881Ssam 	struct tty *tp = &vx_tty[minor(dev)];
28125881Ssam 
28237608Smarc 	return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
28324003Ssam }
28424003Ssam 
28524003Ssam /*
28624003Ssam  * write on a VX line
28724003Ssam  */
28837608Smarc vxwrite(dev, uio, flag)
28924003Ssam 	dev_t dev;
29024003Ssam 	struct uio *uio;
29124003Ssam {
29225881Ssam 	register struct tty *tp = &vx_tty[minor(dev)];
29325881Ssam 
29437608Smarc 	return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
29524003Ssam }
29624003Ssam 
29724003Ssam /*
29824003Ssam  * VIOCX unsolicited interrupt.
29924003Ssam  */
30025881Ssam vxrint(vx)
30125881Ssam 	register vx;
30224003Ssam {
30325881Ssam 	register struct tty *tp, *tp0;
30425881Ssam 	register struct vxdevice *addr;
30525881Ssam 	register struct vx_softc *vs;
30625881Ssam 	struct vba_device *vi;
30725881Ssam 	register int nc, c;
30825881Ssam 	register struct silo {
30940738Skarels 		u_char	data, port;
31025881Ssam 	} *sp;
31125881Ssam 	short *osp;
31225881Ssam 	int overrun = 0;
31324003Ssam 
31425881Ssam 	vi = vxinfo[vx];
31525881Ssam 	if (vi == 0 || vi->ui_alive == 0)
31625881Ssam 		return;
31725881Ssam 	addr = (struct vxdevice *)vi->ui_addr;
31825881Ssam 	switch (addr->v_uqual&037) {
31924003Ssam 	case 0:
32024003Ssam 		break;
32124003Ssam 	case 2:
32240738Skarels 		if (addr->v_ustat == VP_SILO_OFLOW)
32340738Skarels 			log(LOG_ERR, "vx%d: input silo overflow\n", vx);
32440738Skarels 		else {
32540738Skarels 			printf("vx%d: vc proc err, ustat %x\n",
32640738Skarels 			    vx, addr->v_ustat);
32740738Skarels 			vxstreset(vx);
32840738Skarels 		}
32930372Skarels 		return;
33024003Ssam 	case 3:
33125881Ssam 		vcmintr(vx);
33230372Skarels 		return;
33324003Ssam 	case 4:
33430372Skarels 		return;
33524003Ssam 	default:
33630372Skarels 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
33725881Ssam 		vxstreset(vx);
33830372Skarels 		return;
33924003Ssam 	}
34025881Ssam 	vs = &vx_softc[vx];
34125881Ssam 	if (vs->vs_vers == VXV_NEW)
34225881Ssam 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
34325881Ssam 	else
34425881Ssam 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
34525881Ssam 	nc = *(osp = (short *)sp);
34625881Ssam 	if (nc == 0)
34730372Skarels 		return;
34825881Ssam 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
34925881Ssam 		printf("vx%d: %d exceeds silo size\n", nc);
35025881Ssam 		nc = vs->vs_silosiz;
35124003Ssam 	}
35225881Ssam 	tp0 = &vx_tty[vx*16];
35325881Ssam 	sp = (struct silo *)(((short *)sp)+1);
35425881Ssam 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
35525881Ssam 		c = sp->port & 017;
35625881Ssam 		if (vs->vs_loport > c || c > vs->vs_hiport)
35725881Ssam 			continue;
35825881Ssam 		tp = tp0 + c;
35925881Ssam 		if( (tp->t_state&TS_ISOPEN) == 0) {
36024003Ssam 			wakeup((caddr_t)&tp->t_rawq);
36124003Ssam 			continue;
36224003Ssam 		}
36337608Smarc 		c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f);
36425881Ssam 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
36529954Skarels 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
36625881Ssam 			overrun = 1;
36725881Ssam 			continue;
36825881Ssam 		}
36925881Ssam 		if (sp->port&VX_PE)
37037608Smarc 			c |= TTY_PE;
37137608Smarc 		if (sp->port&VX_FE)
37237608Smarc 			c |= TTY_FE;
37324003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
37424003Ssam 	}
37525881Ssam 	*osp = 0;
37624003Ssam }
37724003Ssam 
37824003Ssam /*
37925881Ssam  * Ioctl for VX.
38024003Ssam  */
38124003Ssam vxioctl(dev, cmd, data, flag)
38225881Ssam 	dev_t dev;
38325881Ssam 	caddr_t	data;
38424003Ssam {
38525881Ssam 	register struct tty *tp;
38625881Ssam 	int error;
38724003Ssam 
38825881Ssam 	tp = &vx_tty[minor(dev)];
38924003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
39037608Smarc 	if (error >= 0)
39125881Ssam 		return (error);
39225881Ssam 	error = ttioctl(tp, cmd, data, flag);
39337608Smarc 	if (error >= 0)
39425881Ssam 		return (error);
39525881Ssam 	return (ENOTTY);
39624003Ssam }
39724003Ssam 
39837608Smarc vxparam(tp, t)
39937608Smarc 	struct tty *tp;
40037608Smarc 	struct termios *t;
40124003Ssam {
40225881Ssam 
40337608Smarc 	return (vxcparam(tp, t, 1));
40424003Ssam }
40524003Ssam 
40624003Ssam /*
40724003Ssam  * Set parameters from open or stty into the VX hardware
40824003Ssam  * registers.
40924003Ssam  */
41037608Smarc vxcparam(tp, t, wait)
41137608Smarc 	struct tty *tp;
41237608Smarc 	struct termios *t;
41325881Ssam 	int wait;
41424003Ssam {
41525881Ssam 	register struct vx_softc *vs;
41625881Ssam 	register struct vxcmd *cp;
41740738Skarels 	int s, error = 0;
41837608Smarc 	int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab);
41924003Ssam 
42037608Smarc 	if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed))
42140738Skarels 		return (EINVAL);
42225881Ssam 	vs = (struct vx_softc *)tp->t_addr;
42325881Ssam 	cp = vobtain(vs);
42424003Ssam 	s = spl8();
42525933Ssam 	/*
42625933Ssam 	 * Construct ``load parameters'' command block
42725933Ssam 	 * to setup baud rates, xon-xoff chars, parity,
42825933Ssam 	 * and stop bits for the specified port.
42925933Ssam 	 */
43025933Ssam 	cp->cmd = VXC_LPARAX;
43140738Skarels 	cp->par[1] = VXPORT(minor(tp->t_dev));
43237608Smarc 	/*
43337608Smarc 	 * note: if the hardware does flow control, ^V doesn't work
43437608Smarc 	 * to escape ^S
43537608Smarc 	 */
43637608Smarc 	if (t->c_iflag&IXON) {
43737608Smarc 		if (t->c_cc[VSTART] == _POSIX_VDISABLE)
43837608Smarc 			cp->par[2] = 0;
43937608Smarc 		else
44037608Smarc 			cp->par[2] = t->c_cc[VSTART];
44137608Smarc 		if (t->c_cc[VSTOP] == _POSIX_VDISABLE)
44237608Smarc 			cp->par[3] = 0;
44337608Smarc 		else
44437608Smarc 			cp->par[3] = t->c_cc[VSTOP];
44537608Smarc 	} else
44637608Smarc 		cp->par[2] = cp->par[3] = 0;
44730372Skarels #ifdef notnow
44840738Skarels 	switch (t->c_cflag & CSIZE) {	/* XXX */
44940738Skarels 	case CS8:
45030372Skarels #endif
45130372Skarels 		cp->par[4] = BITS8;		/* 8 bits of data */
45230372Skarels #ifdef notnow
45340738Skarels 		break;
45440738Skarels 	case CS7:
45530372Skarels 		cp->par[4] = BITS7;		/* 7 bits of data */
45640738Skarels 		break;
45740738Skarels 	case CS6:
45840738Skarels 		cp->par[4] = BITS6;		/* 6 bits of data */
45940738Skarels 		break;
46040738Skarels 	case CS5:
46140738Skarels 		cp->par[4] = BITS5;		/* 5 bits of data */
46240738Skarels 		break;
46324003Ssam 	}
46440738Skarels 	if ((t->c_cflag & PARENB) == 0)		/* XXX */
46530372Skarels #endif
46640738Skarels 		cp->par[7] = VNOPARITY;		/* no parity */
46740738Skarels #ifdef notnow
46840738Skarels 	else if (t->c_cflag&PARODD)
46940738Skarels 		cp->par[7] = VODDP;	/* odd parity */
47040738Skarels 	else
47140738Skarels 		cp->par[7] = VEVENP;	/* even parity */
47240738Skarels #endif
47337608Smarc 	cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1;
47437608Smarc 	cp->par[6] = speedcode;
47530372Skarels 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
47640738Skarels 		error = tsleep((caddr_t)cp, TTIPRI | PCATCH, ttyout, 0);
47737608Smarc 	if ((t->c_ospeed)==0) {
47837608Smarc 		tp->t_cflag |= HUPCL;
47940738Skarels 		vcmodem(tp->t_dev, VMOD_OFF);
48037608Smarc 	}
48124003Ssam 	splx(s);
48240738Skarels 	return (error);
48324003Ssam }
48424003Ssam 
48524003Ssam /*
48624003Ssam  * VIOCX command response interrupt.
48724003Ssam  * For transmission, restart output to any active port.
48824003Ssam  * For all other commands, just clean up.
48924003Ssam  */
49025881Ssam vxxint(vx, cp)
49125881Ssam 	register int vx;
49225881Ssam 	register struct vxcmd *cp;
49324003Ssam {
49430372Skarels 	register struct vxmit *vp;
49525933Ssam 	register struct tty *tp, *tp0;
49625933Ssam 	register struct vx_softc *vs;
49724003Ssam 
49825881Ssam 	vs = &vx_softc[vx];
49925881Ssam 	cp = (struct vxcmd *)((long *)cp-1);
50029954Skarels 
50125881Ssam 	switch (cp->cmd&0xff00) {
50225881Ssam 
50325881Ssam 	case VXC_LIDENT:	/* initialization complete */
50425881Ssam 		if (vs->vs_state == VXS_RESET) {
50525881Ssam 			vxfnreset(vx, cp);
50625881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
50724003Ssam 		}
50824003Ssam 		cp->cmd++;
50924003Ssam 		return;
51025881Ssam 
51125881Ssam 	case VXC_XMITDTA:
51225881Ssam 	case VXC_XMITIMM:
51324003Ssam 		break;
51425881Ssam 
51525881Ssam 	case VXC_LPARAX:
51625675Ssam 		wakeup((caddr_t)cp);
51725881Ssam 		/* fall thru... */
51825881Ssam 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
51925881Ssam 		vrelease(vs, cp);
52025881Ssam 		if (vs->vs_state == VXS_RESET)
52125881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
52224003Ssam 		return;
52324003Ssam 	}
52425881Ssam 	tp0 = &vx_tty[vx*16];
52525881Ssam 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
52625881Ssam 	for (; vp >= (struct vxmit *)cp->par; vp--) {
52725881Ssam 		tp = tp0 + (vp->line & 017);
52824003Ssam 		tp->t_state &= ~TS_BUSY;
52925881Ssam 		if (tp->t_state & TS_FLUSH) {
53024003Ssam 			tp->t_state &= ~TS_FLUSH;
53125881Ssam 			wakeup((caddr_t)&tp->t_state);
53225881Ssam 		} else
53324003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
53424003Ssam 	}
53525881Ssam 	vrelease(vs, cp);
53630372Skarels 	if (vs->vs_vers == VXV_NEW)
53732112Skarels 		(*linesw[tp->t_line].l_start)(tp);
53830372Skarels 	else {
53925881Ssam 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
54025881Ssam 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
54132112Skarels 			(*linesw[tp->t_line].l_start)(tp);
54225881Ssam 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
54325881Ssam 			vs->vs_xmtcnt++;
54430372Skarels 			(void) vcmd(vx, (caddr_t)&cp->cmd);
54524003Ssam 		}
54624003Ssam 	}
54730372Skarels 	vs->vs_xmtcnt--;
54824003Ssam }
54924003Ssam 
55024003Ssam /*
55124003Ssam  * Force out partial XMIT command after timeout
55224003Ssam  */
55325881Ssam vxforce(vs)
55425881Ssam 	register struct vx_softc *vs;
55524003Ssam {
55625881Ssam 	register struct vxcmd *cp;
55725881Ssam 	int s;
55824003Ssam 
55924003Ssam 	s = spl8();
56025881Ssam 	if ((cp = nextcmd(vs)) != NULL) {
56125881Ssam 		vs->vs_xmtcnt++;
56230372Skarels 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
56324003Ssam 	}
56424003Ssam 	splx(s);
56524003Ssam }
56624003Ssam 
56724003Ssam /*
56824003Ssam  * Start (restart) transmission on the given VX line.
56924003Ssam  */
57024003Ssam vxstart(tp)
57125881Ssam 	register struct tty *tp;
57224003Ssam {
57325675Ssam 	register short n;
57425933Ssam 	register struct vx_softc *vs;
57525933Ssam 	int s, port;
57624003Ssam 
57724003Ssam 	s = spl8();
57840738Skarels 	port = VXPORT(minor(tp->t_dev));
57925881Ssam 	vs = (struct vx_softc *)tp->t_addr;
58025881Ssam 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
58137608Smarc 		if (tp->t_outq.c_cc <= tp->t_lowat) {
58224003Ssam 			if (tp->t_state&TS_ASLEEP) {
58324003Ssam 				tp->t_state &= ~TS_ASLEEP;
58424003Ssam 				wakeup((caddr_t)&tp->t_outq);
58524003Ssam 			}
58624003Ssam 			if (tp->t_wsel) {
58724003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
58824003Ssam 				tp->t_wsel = 0;
58924003Ssam 				tp->t_state &= ~TS_WCOLL;
59024003Ssam 			}
59124003Ssam 		}
59225881Ssam 		if (tp->t_outq.c_cc == 0) {
59324003Ssam 			splx(s);
59430372Skarels 			return;
59524003Ssam 		}
59625877Ssam 		scope_out(3);
59737608Smarc 		if (1 || !(tp->t_oflag&OPOST))	/* XXX */
59830372Skarels 			n = ndqb(&tp->t_outq, 0);
59930372Skarels 		else {
60030372Skarels 			n = ndqb(&tp->t_outq, 0200);
60130372Skarels 			if (n == 0) {
60225675Ssam 				n = getc(&tp->t_outq);
60325881Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
60424003Ssam 				tp->t_state |= TS_TIMEOUT;
60530372Skarels 				n = 0;
60624003Ssam 			}
60730372Skarels 		}
60830372Skarels 		if (n) {
60924003Ssam 			tp->t_state |= TS_BUSY;
61030372Skarels 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
61124003Ssam 		}
61224003Ssam 	}
61324003Ssam 	splx(s);
61424003Ssam }
61524003Ssam 
61624003Ssam /*
61724003Ssam  * Stop output on a line.
61824003Ssam  */
61924003Ssam vxstop(tp)
62025881Ssam 	register struct tty *tp;
62124003Ssam {
62225881Ssam 	int s;
62324003Ssam 
62424003Ssam 	s = spl8();
62525881Ssam 	if (tp->t_state&TS_BUSY)
62625881Ssam 		if ((tp->t_state&TS_TTSTOP) == 0)
62724003Ssam 			tp->t_state |= TS_FLUSH;
62824003Ssam 	splx(s);
62924003Ssam }
63024003Ssam 
63125881Ssam static	int vxbbno = -1;
63224003Ssam /*
63324003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
63424003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
63525933Ssam  * viocx to establish interrupt vectors and logical port numbers.
63624003Ssam  */
63740738Skarels vxinit(vx, wait)
63825881Ssam 	register int vx;
63925881Ssam 	int wait;
64024003Ssam {
64125933Ssam 	register struct vx_softc *vs;
64225933Ssam 	register struct vxdevice *addr;
64325933Ssam 	register struct vxcmd *cp;
64425881Ssam 	register char *resp;
64525881Ssam 	register int j;
64630372Skarels 	char type, *typestring;
64724003Ssam 
64825881Ssam 	vs = &vx_softc[vx];
64940738Skarels 	addr = vs->vs_addr;
65025881Ssam 	type = addr->v_ident;
65125881Ssam 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
65225881Ssam 	if (vs->vs_vers == VXV_NEW)
65325881Ssam 		vs->vs_silosiz = addr->v_maxsilo;
65425881Ssam 	switch (type) {
65524003Ssam 
65625881Ssam 	case VXT_VIOCX:
65725881Ssam 	case VXT_VIOCX|VXT_NEW:
65830372Skarels 		typestring = "VIOC-X";
65930372Skarels 		/* set soft carrier for printer ports */
66030372Skarels 		for (j = 0; j < 16; j++)
66140738Skarels 			if (vs->vs_softCAR & (1 << j) ||
66240738Skarels 			    addr->v_portyp[j] == VXT_PARALLEL) {
66330372Skarels 				vs->vs_softCAR |= 1 << j;
66425881Ssam 				addr->v_dcd |= 1 << j;
66530372Skarels 			}
66625881Ssam 		break;
66724003Ssam 
66825881Ssam 	case VXT_PVIOCX:
66925881Ssam 	case VXT_PVIOCX|VXT_NEW:
67030372Skarels 		typestring = "VIOC-X (old connector panel)";
67125881Ssam 		break;
67225881Ssam 	case VXT_VIOCBOP:		/* VIOC-BOP */
67325881Ssam 		vs->vs_type = 1;
67425881Ssam 		vs->vs_bop = ++vxbbno;
67525881Ssam 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
67640738Skarels 		goto unsup;
67725933Ssam 	default:
67825881Ssam 		printf("vx%d: unknown type %x\n", vx, type);
67940738Skarels 	unsup:
68030372Skarels 		vxinfo[vx]->ui_alive = 0;
68125881Ssam 		return;
68224003Ssam 	}
68340738Skarels 	vs->vs_nbr = vx;		/* assign board number */
68425933Ssam 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
68525933Ssam 	/*
68625933Ssam 	 * Initialize all cmd buffers by linking them
68725933Ssam 	 * into a free list.
68825933Ssam 	 */
68925881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
69025933Ssam 		cp = &vs->vs_lst[j];
69125933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
69225881Ssam 	}
69325881Ssam 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
69424003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
69524003Ssam 
69625933Ssam 	/*
69725933Ssam 	 * Establish the interrupt vectors and define the port numbers.
69825933Ssam 	 */
69925933Ssam 	cp = vobtain(vs);
70025933Ssam 	cp->cmd = VXC_LIDENT;
70125881Ssam 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
70225857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
70325857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
70425881Ssam 	cp->par[4] = 15;		/* max ports, no longer used */
70525881Ssam 	cp->par[5] = 0;			/* set 1st port number */
70630372Skarels 	(void) vcmd(vx, (caddr_t)&cp->cmd);
70725881Ssam 	if (!wait)
70825881Ssam 		return;
70940738Skarels 
71025881Ssam 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
71125857Ssam 		;
71225857Ssam 	if (j >= 4000000)
71325881Ssam 		printf("vx%d: didn't respond to LIDENT\n", vx);
71424003Ssam 
71524003Ssam  	/* calculate address of response buffer */
71625881Ssam  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
71725933Ssam 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
71825933Ssam 		vrelease(vs, cp);	/* init failed */
71925881Ssam 		return;
72024003Ssam 	}
72125881Ssam 	vs->vs_loport = cp->par[5];
72225881Ssam 	vs->vs_hiport = cp->par[7];
72330372Skarels 	printf("vx%d: %s%s, ports %d-%d\n", vx,
72430372Skarels 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
72530372Skarels 	    vs->vs_loport, vs->vs_hiport);
72625881Ssam 	vrelease(vs, cp);
72724003Ssam }
72824003Ssam 
72924003Ssam /*
73024003Ssam  * Obtain a command buffer
73124003Ssam  */
73225881Ssam struct vxcmd *
73325881Ssam vobtain(vs)
73425933Ssam 	register struct vx_softc *vs;
73524003Ssam {
73625933Ssam 	register struct vxcmd *p;
73725881Ssam 	int s;
73824003Ssam 
73924003Ssam 	s = spl8();
74025881Ssam 	p = vs->vs_avail;
74125881Ssam 	if (p == (struct vxcmd *)0) {
74224003Ssam #ifdef VX_DEBUG
74325881Ssam 		if (vxintr4&VXNOBUF)
74425881Ssam 			vxintr4 &= ~VXNOBUF;
74524003Ssam #endif
74640738Skarels 		printf("vx%d: no buffers\n", vs->vs_nbr);
74740738Skarels 		vxstreset(vs->vs_nbr);
74824003Ssam 		splx(s);
74925881Ssam 		return (vobtain(vs));
75024003Ssam 	}
75130372Skarels 	vs->vs_avail = p->c_fwd;
75224003Ssam 	splx(s);
75325881Ssam 	return ((struct vxcmd *)p);
75424003Ssam }
75524003Ssam 
75624003Ssam /*
75724003Ssam  * Release a command buffer
75824003Ssam  */
75925881Ssam vrelease(vs, cp)
76025933Ssam 	register struct vx_softc *vs;
76125933Ssam 	register struct vxcmd *cp;
76224003Ssam {
76325881Ssam 	int s;
76424003Ssam 
76524003Ssam #ifdef VX_DEBUG
76625881Ssam 	if (vxintr4&VXNOBUF)
76725881Ssam 		return;
76824003Ssam #endif
76924003Ssam 	s = spl8();
77025881Ssam 	cp->c_fwd = vs->vs_avail;
77125881Ssam 	vs->vs_avail = cp;
77224003Ssam 	splx(s);
77324003Ssam }
77424003Ssam 
77525881Ssam struct vxcmd *
77625881Ssam nextcmd(vs)
77725933Ssam 	register struct vx_softc *vs;
77824003Ssam {
77925933Ssam 	register struct vxcmd *cp;
78025881Ssam 	int s;
78124003Ssam 
78224003Ssam 	s = spl8();
78325881Ssam 	cp = vs->vs_build;
78425881Ssam 	vs->vs_build = (struct vxcmd *)0;
78524003Ssam 	splx(s);
78625881Ssam 	return (cp);
78724003Ssam }
78824003Ssam 
78924003Ssam /*
79025933Ssam  * Assemble transmits into a multiple command;
79130372Skarels  * up to 8 transmits to 8 lines can be assembled together
79230372Skarels  * (on PVIOCX only).
79324003Ssam  */
79425933Ssam vsetq(vs, line, addr, n)
79525933Ssam 	register struct vx_softc *vs;
79625881Ssam 	caddr_t	addr;
79724003Ssam {
79825933Ssam 	register struct vxcmd *cp;
79925933Ssam 	register struct vxmit *mp;
80024003Ssam 
80125933Ssam 	/*
80225933Ssam 	 * Grab a new command buffer or append
80325933Ssam 	 * to the current one being built.
80425933Ssam 	 */
80525881Ssam 	cp = vs->vs_build;
80625881Ssam 	if (cp == (struct vxcmd *)0) {
80725881Ssam 		cp = vobtain(vs);
80825881Ssam 		vs->vs_build = cp;
80925881Ssam 		cp->cmd = VXC_XMITDTA;
81024003Ssam 	} else {
81130372Skarels 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
81225881Ssam 			printf("vx%d: setq overflow\n", vs-vx_softc);
81330372Skarels 			vxstreset((int)vs->vs_nbr);
81430372Skarels 			return;
81524003Ssam 		}
81624003Ssam 		cp->cmd++;
81724003Ssam 	}
81825933Ssam 	/*
81925933Ssam 	 * Select the next vxmit buffer and copy the
82025933Ssam 	 * characters into the buffer (if there's room
82125933Ssam 	 * and the device supports ``immediate mode'',
82225933Ssam 	 * or store an indirect pointer to the data.
82325933Ssam 	 */
82425881Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
82525675Ssam 	mp->bcount = n-1;
82625933Ssam 	mp->line = line;
82725933Ssam 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
82825881Ssam 		cp->cmd = VXC_XMITIMM;
82930372Skarels 		bcopy(addr, mp->ostream, (unsigned)n);
83024003Ssam 	} else {
83125933Ssam 		/* get system address of clist block */
83225675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
83330372Skarels 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
83424003Ssam 	}
83530372Skarels 	/*
83630372Skarels 	 * We send the data immediately if a VIOCX,
83730372Skarels 	 * the command buffer is full, or if we've nothing
83830372Skarels 	 * currently outstanding.  If we don't send it,
83930372Skarels 	 * set a timeout to force the data to be sent soon.
84030372Skarels 	 */
84130372Skarels 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
84230372Skarels 	    vs->vs_xmtcnt == 0) {
84330372Skarels 		vs->vs_xmtcnt++;
84430372Skarels 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
84530372Skarels 		vs->vs_build = 0;
84630372Skarels 	} else
84730372Skarels 		timeout(vxforce, (caddr_t)vs, 3);
84824003Ssam }
84925881Ssam 
85025881Ssam /*
85125881Ssam  * Write a command out to the VIOC
85225881Ssam  */
85325881Ssam vcmd(vx, cmdad)
85425881Ssam 	register int vx;
85525881Ssam 	register caddr_t cmdad;
85625881Ssam {
85725933Ssam 	register struct vcmds *cp;
85840738Skarels 	register struct vx_softc *vs = &vx_softc[vx];
85925881Ssam 	int s;
86025881Ssam 
86125881Ssam 	s = spl8();
86225933Ssam 	/*
86325933Ssam 	 * When the vioc is resetting, don't process
86425933Ssam 	 * anything other than VXC_LIDENT commands.
86525933Ssam 	 */
86625881Ssam 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
86725933Ssam 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
86825881Ssam 
86925933Ssam 		if (vcp->cmd != VXC_LIDENT) {
87025933Ssam 			vrelease(vs, vcp);
87125881Ssam 			return (0);
87225881Ssam 		}
87325881Ssam 	}
87425881Ssam 	cp = &vs->vs_cmds;
87525881Ssam 	if (cmdad != (caddr_t)0) {
87625881Ssam 		cp->cmdbuf[cp->v_fill] = cmdad;
87725881Ssam 		if (++cp->v_fill >= VC_CMDBUFL)
87825881Ssam 			cp->v_fill = 0;
87925881Ssam 		if (cp->v_fill == cp->v_empty) {
88025881Ssam 			printf("vx%d: cmd q overflow\n", vx);
88125881Ssam 			vxstreset(vx);
88225881Ssam 			splx(s);
88325881Ssam 			return (0);
88425881Ssam 		}
88525881Ssam 		cp->v_cmdsem++;
88625881Ssam 	}
88725881Ssam 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
88825881Ssam 		cp->v_cmdsem--;
88925881Ssam 		cp->v_curcnt++;
89025881Ssam 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
89125881Ssam 	}
89225881Ssam 	splx(s);
89325881Ssam 	return (1);
89425881Ssam }
89525881Ssam 
89625881Ssam /*
89725881Ssam  * VIOC acknowledge interrupt.  The VIOC has received the new
89825881Ssam  * command.  If no errors, the new command becomes one of 16 (max)
89925881Ssam  * current commands being executed.
90025881Ssam  */
90125881Ssam vackint(vx)
90225881Ssam 	register vx;
90325881Ssam {
90425933Ssam 	register struct vxdevice *vp;
90525933Ssam 	register struct vcmds *cp;
90625881Ssam 	struct vx_softc *vs;
90725881Ssam 	int s;
90825881Ssam 
90925881Ssam 	scope_out(5);
91025881Ssam 	vs = &vx_softc[vx];
91129954Skarels 	if (vs->vs_type)	/* Its a BOP */
91225881Ssam 		return;
91325881Ssam 	s = spl8();
91440738Skarels 	vp = vs->vs_addr;
91525881Ssam 	cp = &vs->vs_cmds;
91625933Ssam 	if (vp->v_vcid&V_ERR) {
91725881Ssam 		register char *resp;
91825881Ssam 		register i;
91925933Ssam 
92030372Skarels 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
92125881Ssam 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
92225881Ssam 		resp = (char *)vs->vs_mricmd;
92325881Ssam 		for (i = 0; i < 16; i++)
92425881Ssam 			printf("%x ", resp[i]&0xff);
92525881Ssam 		printf("\n");
92625881Ssam 		splx(s);
92725881Ssam 		vxstreset(vx);
92825881Ssam 		return;
92925881Ssam 	}
93025881Ssam 	if ((vp->v_hdwre&017) == CMDquals) {
93125881Ssam #ifdef VX_DEBUG
93225881Ssam 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
93325933Ssam 			struct vxcmd *cp1, *cp0;
93425881Ssam 
93525933Ssam 			cp0 = (struct vxcmd *)
93625933Ssam 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
93725881Ssam 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
93825881Ssam 				cp1 = vobtain(vs);
93925881Ssam 				*cp1 = *cp0;
94025881Ssam 				vxintr4 &= ~VXERR4;
94125881Ssam 				(void) vcmd(vx, &cp1->cmd);
94225881Ssam 			}
94325881Ssam 		}
94425881Ssam #endif
94525881Ssam 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
94625881Ssam 		if (++cp->v_empty >= VC_CMDBUFL)
94725881Ssam 			cp->v_empty = 0;
94825881Ssam 	}
94925881Ssam 	if (++cp->v_itrempt >= VC_IQLEN)
95025881Ssam 		cp->v_itrempt = 0;
95125881Ssam 	vintempt(vx);
95225881Ssam 	splx(s);
95325881Ssam 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
95425881Ssam }
95525881Ssam 
95625881Ssam /*
95725881Ssam  * Command Response interrupt.  The Vioc has completed
95825881Ssam  * a command.  The command may now be returned to
95925881Ssam  * the appropriate device driver.
96025881Ssam  */
96125881Ssam vcmdrsp(vx)
96225881Ssam 	register vx;
96325881Ssam {
96425933Ssam 	register struct vxdevice *vp;
96525933Ssam 	register struct vcmds *cp;
96625881Ssam 	register caddr_t cmd;
96725881Ssam 	register struct vx_softc *vs;
96825881Ssam 	register char *resp;
96925881Ssam 	register k;
97025881Ssam 	register int s;
97125881Ssam 
97225881Ssam 	scope_out(6);
97325881Ssam 	vs = &vx_softc[vx];
97425881Ssam 	if (vs->vs_type) {	/* Its a BOP */
97525881Ssam 		printf("vx%d: vcmdrsp interrupt\n", vx);
97625881Ssam 		return;
97725881Ssam 	}
97825881Ssam 	s = spl8();
97940738Skarels 	vp = vs->vs_addr;
98025881Ssam 	cp = &vs->vs_cmds;
98125881Ssam 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
98225881Ssam 	if (((k = resp[1])&V_UNBSY) == 0) {
98325881Ssam 		printf("vx%d: cmdresp debug\n", vx);
98425881Ssam 		splx(s);
98525881Ssam 		vxstreset(vx);
98625881Ssam 		return;
98725881Ssam 	}
98825881Ssam 	k &= VCMDLEN-1;
98925881Ssam 	cmd = cp->v_curcmd[k];
99025881Ssam 	cp->v_curcmd[k] = (caddr_t)0;
99125881Ssam 	cp->v_curcnt--;
99225881Ssam 	k = *((short *)&resp[4]);	/* cmd operation code */
99325881Ssam 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
99425881Ssam 		for (k = 0; k < VRESPLEN; k++)
99525881Ssam 			cmd[k] = resp[k+4];
99625881Ssam 	resp[1] = 0;
99725881Ssam 	vxxint(vx, (struct vxcmd *)cmd);
99825881Ssam 	if (vs->vs_state == VXS_READY)
99925881Ssam 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
100025881Ssam 	splx(s);
100125881Ssam }
100225881Ssam 
100325881Ssam /*
100425881Ssam  * Unsolicited interrupt.
100525881Ssam  */
100625881Ssam vunsol(vx)
100725881Ssam 	register vx;
100825881Ssam {
100925933Ssam 	register struct vxdevice *vp;
101025881Ssam 	struct vx_softc *vs;
101125881Ssam 	int s;
101225881Ssam 
101325881Ssam 	scope_out(1);
101425881Ssam 	vs = &vx_softc[vx];
101525881Ssam 	if (vs->vs_type) {	/* Its a BOP */
101625881Ssam 		printf("vx%d: vunsol from BOP\n", vx);
101725881Ssam 		return;
101825881Ssam 	}
101925881Ssam 	s = spl8();
102040738Skarels 	vp = vs->vs_addr;
102125881Ssam 	if (vp->v_uqual&V_UNBSY) {
102225881Ssam 		vxrint(vx);
102325881Ssam 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
102425881Ssam #ifdef notdef
102525881Ssam 	} else {
102625881Ssam 		printf("vx%d: unsolicited interrupt error\n", vx);
102725881Ssam 		splx(s);
102825881Ssam 		vxstreset(vx);
102925881Ssam #endif
103025881Ssam 	}
103125881Ssam 	splx(s);
103225881Ssam }
103325881Ssam 
103425881Ssam /*
103525933Ssam  * Enqueue an interrupt.
103625881Ssam  */
103725881Ssam vinthandl(vx, item)
103825881Ssam 	register int vx;
103925881Ssam 	register item;
104025881Ssam {
104125881Ssam 	register struct vcmds *cp;
104225881Ssam 	int empty;
104325881Ssam 
104425881Ssam 	cp = &vx_softc[vx].vs_cmds;
104525933Ssam 	empty = (cp->v_itrfill == cp->v_itrempt);
104625881Ssam 	cp->v_itrqueu[cp->v_itrfill] = item;
104725881Ssam 	if (++cp->v_itrfill >= VC_IQLEN)
104825881Ssam 		cp->v_itrfill = 0;
104925881Ssam 	if (cp->v_itrfill == cp->v_itrempt) {
105025881Ssam 		printf("vx%d: interrupt q overflow\n", vx);
105125881Ssam 		vxstreset(vx);
105225881Ssam 	} else if (empty)
105325881Ssam 		vintempt(vx);
105425881Ssam }
105525881Ssam 
105625881Ssam vintempt(vx)
105740738Skarels 	int vx;
105825881Ssam {
105925881Ssam 	register struct vcmds *cp;
106025881Ssam 	register struct vxdevice *vp;
106140738Skarels 	register struct vx_softc *vs;
106225881Ssam 	register short item;
106325881Ssam 	register short *intr;
106425881Ssam 
106540738Skarels 	vs = &vx_softc[vx];
106640738Skarels 	vp = vs->vs_addr;
106725881Ssam 	if (vp->v_vioc&V_BSY)
106825881Ssam 		return;
106940738Skarels 	cp = &vs->vs_cmds;
107025881Ssam 	if (cp->v_itrempt == cp->v_itrfill)
107125881Ssam 		return;
107225881Ssam 	item = cp->v_itrqueu[cp->v_itrempt];
107325881Ssam 	intr = (short *)&vp->v_vioc;
107425881Ssam 	switch ((item >> 8)&03) {
107525881Ssam 
107625881Ssam 	case CMDquals: {		/* command */
107725881Ssam 		int phys;
107825881Ssam 
107925881Ssam 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
108025881Ssam 			break;
108140738Skarels 		vs->vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
108225881Ssam 		phys = vtoph((struct proc *)0,
108325881Ssam 		    (unsigned)cp->cmdbuf[cp->v_empty]);
108425881Ssam 		vp->v_vcp[0] = ((short *)&phys)[0];
108525881Ssam 		vp->v_vcp[1] = ((short *)&phys)[1];
108625881Ssam 		vp->v_vcbsy = V_BSY;
108725881Ssam 		*intr = item;
108825881Ssam 		scope_out(4);
108925881Ssam 		break;
109025881Ssam 	}
109125881Ssam 
109225881Ssam 	case RSPquals:		/* command response */
109325881Ssam 		*intr = item;
109425881Ssam 		scope_out(7);
109525881Ssam 		break;
109625881Ssam 
109725881Ssam 	case UNSquals:		/* unsolicited interrupt */
109825881Ssam 		vp->v_uqual = 0;
109925881Ssam 		*intr = item;
110025881Ssam 		scope_out(2);
110125881Ssam 		break;
110225881Ssam 	}
110325881Ssam }
110425881Ssam 
110525881Ssam /*
110625881Ssam  * Start a reset on a vioc after error (hopefully)
110725881Ssam  */
110825881Ssam vxstreset(vx)
110940738Skarels 	register int vx;
111025881Ssam {
111125881Ssam 	register struct vx_softc *vs;
111225933Ssam 	register struct vxdevice *vp;
111325881Ssam 	register struct vxcmd *cp;
111425881Ssam 	register int j;
111525881Ssam 	extern int vxinreset();
111625881Ssam 	int s;
111725881Ssam 
111825881Ssam 	vs = &vx_softc[vx];
111940738Skarels 	s = spl8();
112025881Ssam 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
112125881Ssam 		splx(s);
112225881Ssam 		return;
112325881Ssam 	}
112440738Skarels 	vp = vs->vs_addr;
112525881Ssam 	/*
112625881Ssam 	 * Zero out the vioc structures, mark the vioc as being
112725881Ssam 	 * reset, reinitialize the free command list, reset the vioc
112825881Ssam 	 * and start a timer to check on the progress of the reset.
112925881Ssam 	 */
113040738Skarels 	bzero((caddr_t)&vs->vs_zero,
113140738Skarels 	    (unsigned)((caddr_t)(vs + 1) - (caddr_t)&vs->vs_zero));
113225881Ssam 
113325881Ssam 	/*
113425881Ssam 	 * Setting VXS_RESET prevents others from issuing
113525881Ssam 	 * commands while allowing currently queued commands to
113625881Ssam 	 * be passed to the VIOC.
113725881Ssam 	 */
113825881Ssam 	vs->vs_state = VXS_RESET;
113925881Ssam 	/* init all cmd buffers */
114025881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
114125933Ssam 		cp = &vs->vs_lst[j];
114225933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
114325881Ssam 	}
114425933Ssam 	vs->vs_avail = &vs->vs_lst[0];
114525933Ssam 	cp->c_fwd = (struct vxcmd *)0;
114625881Ssam 	printf("vx%d: reset...", vx);
114725881Ssam 	vp->v_fault = 0;
114825881Ssam 	vp->v_vioc = V_BSY;
114925933Ssam 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
115025881Ssam 	timeout(vxinreset, (caddr_t)vx, hz*5);
115125881Ssam 	splx(s);
115225881Ssam }
115325881Ssam 
115425881Ssam /* continue processing a reset on a vioc after an error (hopefully) */
115525881Ssam vxinreset(vx)
115625881Ssam 	int vx;
115725881Ssam {
115825933Ssam 	register struct vxdevice *vp;
115925881Ssam 	int s = spl8();
116025881Ssam 
116140738Skarels 	vp = vx_softc[vx].vs_addr;
116225881Ssam 	/*
116325881Ssam 	 * See if the vioc has reset.
116425881Ssam 	 */
116525881Ssam 	if (vp->v_fault != VXF_READY) {
116640738Skarels 		printf(" vxreset failed\n");
116725881Ssam 		splx(s);
116825881Ssam 		return;
116925881Ssam 	}
117025881Ssam 	/*
117125881Ssam 	 * Send a LIDENT to the vioc and mess with carrier flags
117225881Ssam 	 * on parallel printer ports.
117325881Ssam 	 */
117429954Skarels 	vxinit(vx, 0);
117525881Ssam 	splx(s);
117625881Ssam }
117725881Ssam 
117825881Ssam /*
117925933Ssam  * Finish the reset on the vioc after an error (hopefully).
118025933Ssam  *
118125881Ssam  * Restore modem control, parameters and restart output.
118225881Ssam  * Since the vioc can handle no more then 24 commands at a time
118325881Ssam  * and we could generate as many as 48 commands, we must do this in
118425881Ssam  * phases, issuing no more then 16 commands at a time.
118525881Ssam  */
118625881Ssam vxfnreset(vx, cp)
118725881Ssam 	register int vx;
118825881Ssam 	register struct vxcmd *cp;
118925881Ssam {
119025881Ssam 	register struct vx_softc *vs;
119140738Skarels 	register struct vxdevice *vp;
119225881Ssam 	register struct tty *tp, *tp0;
119325881Ssam 	register int i;
119425881Ssam #ifdef notdef
119525881Ssam 	register int on;
119625881Ssam #endif
119725881Ssam 	extern int vxrestart();
119825881Ssam 	int s = spl8();
119925881Ssam 
120025881Ssam 	vs = &vx_softc[vx];
120125881Ssam 	vrelease(vs, cp);
120225881Ssam 	vs->vs_state = VXS_READY;
120325881Ssam 
120440738Skarels 	vp = vs->vs_addr;
120525881Ssam 	vp->v_vcid = 0;
120625881Ssam 
120725881Ssam 	/*
120825881Ssam 	 * Restore modem information and control.
120925881Ssam 	 */
121025881Ssam 	tp0 = &vx_tty[vx*16];
121125881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
121225881Ssam 		tp = tp0 + i;
121325881Ssam 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
121425881Ssam 			tp->t_state &= ~TS_CARR_ON;
121525881Ssam 			vcmodem(tp->t_dev, VMOD_ON);
121625881Ssam 			if (tp->t_state&TS_CARR_ON)
121729954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
121829954Skarels 			else if (tp->t_state & TS_ISOPEN)
121929954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
122025881Ssam 		}
122129954Skarels #ifdef notdef
122225881Ssam 		/*
122325881Ssam 		 * If carrier has changed while we were resetting,
122425881Ssam 		 * take appropriate action.
122525881Ssam 		 */
122625881Ssam 		on = vp->v_dcd & 1<<i;
122729954Skarels 		if (on && (tp->t_state&TS_CARR_ON) == 0)
122829954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
122929954Skarels 		else if (!on && tp->t_state&TS_CARR_ON)
123029954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
123125881Ssam #endif
123225881Ssam 	}
123325881Ssam 	vs->vs_state = VXS_RESET;
123425881Ssam 	timeout(vxrestart, (caddr_t)vx, hz);
123525881Ssam 	splx(s);
123625881Ssam }
123725881Ssam 
123825881Ssam /*
123925881Ssam  * Restore a particular aspect of the VIOC.
124025881Ssam  */
124125881Ssam vxrestart(vx)
124225881Ssam 	int vx;
124325881Ssam {
124425881Ssam 	register struct tty *tp, *tp0;
124525881Ssam 	register struct vx_softc *vs;
124630372Skarels 	register int i, count;
124725881Ssam 	int s = spl8();
124825881Ssam 
124930372Skarels 	count = vx >> 8;
125025881Ssam 	vx &= 0xff;
125125881Ssam 	vs = &vx_softc[vx];
125225881Ssam 	vs->vs_state = VXS_READY;
125325881Ssam 	tp0 = &vx_tty[vx*16];
125425881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
125525881Ssam 		tp = tp0 + i;
125630372Skarels 		if (count != 0) {
125725881Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
125825881Ssam 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
125925881Ssam 				vxstart(tp);	/* restart pending output */
126025881Ssam 		} else {
126125881Ssam 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
126237608Smarc 				vxcparam(tp, &tp->t_termios, 0);
126325881Ssam 		}
126425881Ssam 	}
126530372Skarels 	if (count == 0) {
126625881Ssam 		vs->vs_state = VXS_RESET;
126725881Ssam 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
126825881Ssam 	} else
126940738Skarels 		printf(" vx reset done\n");
127025881Ssam 	splx(s);
127125881Ssam }
127225881Ssam 
127325881Ssam vxreset(dev)
127425881Ssam 	dev_t dev;
127525881Ssam {
127625881Ssam 
127730372Skarels 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
127825881Ssam }
127925881Ssam 
128040738Skarels #ifdef VX_DEBUG
128125881Ssam vxfreset(vx)
128225881Ssam 	register int vx;
128325881Ssam {
128425881Ssam 	struct vba_device *vi;
128525881Ssam 
128625881Ssam 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
128725881Ssam 		return (ENODEV);
128825881Ssam 	vx_softc[vx].vs_state = VXS_READY;
128925881Ssam 	vxstreset(vx);
129025881Ssam 	return (0);		/* completes asynchronously */
129125881Ssam }
129230372Skarels #endif
129325881Ssam 
129425881Ssam vcmodem(dev, flag)
129525881Ssam 	dev_t dev;
129625881Ssam {
129725881Ssam 	struct tty *tp;
129825881Ssam 	register struct vxcmd *cp;
129925881Ssam 	register struct vx_softc *vs;
130025881Ssam 	register struct vxdevice *kp;
130125881Ssam 	register port;
130225881Ssam 	int unit;
130325881Ssam 
130425881Ssam 	unit = minor(dev);
130525881Ssam 	tp = &vx_tty[unit];
130625881Ssam 	vs = (struct vx_softc *)tp->t_addr;
130730372Skarels 	if (vs->vs_state != VXS_READY)
130830372Skarels 		return;
130925881Ssam 	cp = vobtain(vs);
131040738Skarels 	kp = vs->vs_addr;
131125881Ssam 
131240738Skarels 	port = VXPORT(unit);
131325881Ssam 	/*
131425881Ssam 	 * Issue MODEM command
131525881Ssam 	 */
131625881Ssam 	cp->cmd = VXC_MDMCTL;
131730372Skarels 	if (flag == VMOD_ON) {
131840738Skarels 		if (vs->vs_softCAR & (1 << port)) {
131930372Skarels 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
132040738Skarels 			kp->v_dcd |= (1 << port);
132140738Skarels 		} else
132240738Skarels 			cp->par[0] = V_AUTO | V_DTR_ON;
132330372Skarels 	} else
132430372Skarels 		cp->par[0] = V_DTR_OFF;
132525881Ssam 	cp->par[1] = port;
132630372Skarels 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
132730372Skarels 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
132830372Skarels 		tp->t_state |= TS_CARR_ON;
132925881Ssam }
133025881Ssam 
133125881Ssam /*
133240738Skarels  * VCMINTR called when an unsolicited interrupt occurs signaling
133325881Ssam  * some change of modem control state.
133425881Ssam  */
133525881Ssam vcmintr(vx)
133625881Ssam 	register vx;
133725881Ssam {
133825881Ssam 	register struct vxdevice *kp;
133925881Ssam 	register struct tty *tp;
134025881Ssam 	register port;
134130372Skarels 	register struct vx_softc *vs;
134225881Ssam 
134340738Skarels 	vs = &vx_softc[vx];
134440738Skarels 	kp = vs->vs_addr;
134525881Ssam 	port = kp->v_usdata[0] & 017;
134625881Ssam 	tp = &vx_tty[vx*16+port];
134725881Ssam 
134829954Skarels 	if (kp->v_ustat & DCD_ON)
134929954Skarels 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
135029954Skarels 	else if ((kp->v_ustat & DCD_OFF) &&
135130372Skarels 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
135229954Skarels 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
135329954Skarels 		register struct vcmds *cp;
135429954Skarels 		register struct vxcmd *cmdp;
135525881Ssam 
135630372Skarels 		/* clear all pending transmits */
135729954Skarels 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
135829954Skarels 		    vs->vs_vers == VXV_NEW) {
135929954Skarels 			int i, cmdfound = 0;
136025881Ssam 
136129954Skarels 			cp = &vs->vs_cmds;
136229954Skarels 			for (i = cp->v_empty; i != cp->v_fill; ) {
136329954Skarels 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
136429954Skarels 				if ((cmdp->cmd == VXC_XMITDTA ||
136529954Skarels 				    cmdp->cmd == VXC_XMITIMM) &&
136629954Skarels 				    ((struct vxmit *)cmdp->par)->line == port) {
136729954Skarels 					cmdfound++;
136825881Ssam 					cmdp->cmd = VXC_FDTATOX;
136925881Ssam 					cmdp->par[1] = port;
137025881Ssam 				}
137129954Skarels 				if (++i >= VC_CMDBUFL)
137229954Skarels 					i = 0;
137325881Ssam 			}
137429954Skarels 			if (cmdfound)
137529954Skarels 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
137629954Skarels 			/* cmd is already in vioc, have to flush it */
137729954Skarels 			else {
137829954Skarels 				cmdp = vobtain(vs);
137929954Skarels 				cmdp->cmd = VXC_FDTATOX;
138029954Skarels 				cmdp->par[1] = port;
138130372Skarels 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
138225881Ssam 			}
138325881Ssam 		}
138429954Skarels 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
138537608Smarc 		(*linesw[tp->t_line].l_rint)(TTY_FE, tp);
138625881Ssam 		return;
138725881Ssam 	}
138825881Ssam }
138925881Ssam #endif
1390