xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 42957)
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  *
835057Skarels  * Redistribution and use in source and binary forms are permitted
935057Skarels  * provided that the above copyright notice and this paragraph are
1035057Skarels  * duplicated in all such forms and that any documentation,
1135057Skarels  * advertising materials, and other materials related to such
1235057Skarels  * distribution and use acknowledge that the software was developed
1335057Skarels  * by the University of California, Berkeley.  The name of the
1435057Skarels  * University may not be used to endorse or promote products derived
1535057Skarels  * from this software without specific prior written permission.
1635057Skarels  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
1735057Skarels  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
1835057Skarels  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
1935057Skarels  *
20*42957Smarc  *	@(#)vx.c	7.9 (Berkeley) 06/07/90
2134406Skarels  */
2224003Ssam 
2324003Ssam #include "vx.h"
2424003Ssam #if NVX > 0
2524003Ssam /*
2625857Ssam  * VIOC-X driver
2724003Ssam  */
2825877Ssam #ifdef VXPERF
2925948Ssam #define	DOSCOPE
3025877Ssam #endif
3125877Ssam 
3225877Ssam #include "param.h"
3325877Ssam #include "ioctl.h"
3425877Ssam #include "tty.h"
3525877Ssam #include "user.h"
3625877Ssam #include "map.h"
3725877Ssam #include "buf.h"
3825877Ssam #include "conf.h"
3925877Ssam #include "file.h"
4025877Ssam #include "proc.h"
4125877Ssam #include "vm.h"
4225881Ssam #include "kernel.h"
4329954Skarels #include "syslog.h"
4425675Ssam 
4534406Skarels #include "../tahoe/pte.h"
4634406Skarels 
4725675Ssam #include "../tahoevba/vbavar.h"
4838114Sbostic #include "../tahoevba/vbaparam.h"
4925881Ssam #include "../tahoevba/vxreg.h"
5025675Ssam #include "../tahoevba/scope.h"
5124003Ssam 
5225881Ssam #ifdef VX_DEBUG
5325881Ssam long	vxintr4 = 0;
5425948Ssam #define	VXERR4	1
5525948Ssam #define	VXNOBUF	2
5625881Ssam long	vxdebug = 0;
5725948Ssam #define	VXVCM	1
5825948Ssam #define	VXVCC	2
5925948Ssam #define	VXVCX	4
6025881Ssam #endif
6124003Ssam 
6225881Ssam /*
6325881Ssam  * Interrupt type bits passed to vinthandl().
6425881Ssam  */
6525948Ssam #define	CMDquals 0		/* command completed interrupt */
6625948Ssam #define	RSPquals 1		/* command response interrupt */
6725948Ssam #define	UNSquals 2		/* unsolicited interrupt */
6824003Ssam 
6930372Skarels #define	VXUNIT(n)	((n) >> 4)
7030372Skarels #define	VXPORT(n)	((n) & 0xf)
7130372Skarels 
7225881Ssam struct	tty vx_tty[NVX*16];
7329954Skarels #ifndef lint
7429954Skarels int	nvx = NVX*16;
7529954Skarels #endif
7625881Ssam int	vxstart(), ttrstrt();
7725881Ssam struct	vxcmd *vobtain(), *nextcmd();
7824003Ssam 
7924003Ssam /*
8024003Ssam  * Driver information for auto-configuration stuff.
8124003Ssam  */
8224003Ssam int	vxprobe(), vxattach(), vxrint();
8325881Ssam struct	vba_device *vxinfo[NVX];
8424003Ssam long	vxstd[] = { 0 };
8524003Ssam struct	vba_driver vxdriver =
8625857Ssam     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
8724003Ssam 
8825881Ssam struct	vx_softc {
8940738Skarels 	struct	vxdevice *vs_addr;	/* H/W address */
9025881Ssam 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
9125881Ssam 	u_char	vs_bop;		/* bop board # for vioc-bop's */
9225881Ssam 	u_char	vs_loport;	/* low port nbr */
9325881Ssam 	u_char	vs_hiport;	/* high port nbr */
9425881Ssam 	u_short	vs_nbr;		/* viocx number */
9525881Ssam 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
9625881Ssam 	u_short	vs_silosiz;	/* silo size */
9725881Ssam 	short	vs_vers;	/* vioc/pvioc version */
9825948Ssam #define	VXV_OLD	0		/* PVIOCX | VIOCX */
9925948Ssam #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
10025881Ssam 	short 	vs_state;	/* controller state */
10125948Ssam #define	VXS_READY	0	/* ready for commands */
10225948Ssam #define	VXS_RESET	1	/* in process of reseting */
10330372Skarels 	u_short	vs_softCAR;	/* soft carrier */
10440738Skarels 	u_int	vs_ivec;	/* interrupt vector base */
10525881Ssam 	caddr_t vs_mricmd;	/* most recent issued cmd */
10640738Skarels 	/* The remaining fields are zeroed on reset... */
10740738Skarels #define vs_zero vs_xmtcnt
10840738Skarels 	int	vs_xmtcnt;	/* xmit commands pending */
10925881Ssam 	struct	vxcmd *vs_avail;/* next available command buffer */
11025881Ssam 	struct	vxcmd *vs_build;
11125881Ssam 	struct	vxcmd vs_lst[NVCXBUFS];
11225881Ssam 	struct	vcmds vs_cmds;
11325881Ssam } vx_softc[NVX];
11424003Ssam 
11537608Smarc struct speedtab vxspeedtab[] = {
11637608Smarc 	EXTA,	V19200,
11737608Smarc 	EXTB,	V19200,
11837608Smarc 	19200,	V19200,
11937608Smarc 	9600,	13,
12037608Smarc 	4800,	12,
12137608Smarc 	2400,	11,
12237608Smarc 	1800,	10,
12337608Smarc 	1200,	9,
12437608Smarc 	600,	8,
12537608Smarc 	300,	7,
12637608Smarc 	200,	6,
12737608Smarc 	150,	5,
12837608Smarc 	134,	4,
12937608Smarc 	110,	3,
13037608Smarc 	75,	2,
13137608Smarc 	50,	1,
13237608Smarc 	0,	0,
13337608Smarc 	-1,	-1,
13437608Smarc };
13537608Smarc 
13625857Ssam vxprobe(reg, vi)
13724003Ssam 	caddr_t reg;
13825857Ssam 	struct vba_device *vi;
13924003Ssam {
14025857Ssam 	register int br, cvec;			/* must be r12, r11 */
14138114Sbostic 	register struct vxdevice *vp;
14225881Ssam 	register struct vx_softc *vs;
14338114Sbostic 	struct pte *dummypte;
14424003Ssam 
14524003Ssam #ifdef lint
14624003Ssam 	br = 0; cvec = br; br = cvec;
14740738Skarels 	vackint(0); vunsol(0); vcmdrsp(0);
14840738Skarels #ifdef VX_DEBUG
14940738Skarels 	vxfreset(0);
15024003Ssam #endif
15140738Skarels #endif /* lint */
15240738Skarels 	/*
15340738Skarels 	 * If on an HCX-9, the device has a 32-bit address,
15440738Skarels 	 * and we receive that address so we can set up a map.
15540738Skarels 	 * On VERSAbus devices, the address is 24-bit, and is
15640738Skarels 	 * already mapped (into vmem[]) by autoconf.
15740738Skarels 	 */
15840738Skarels 	if (!(reg >= vmem && reg < &vmem[ctob(VBIOSIZE)]) &&	/* XXX */
15940738Skarels 	    !vbmemalloc(16, reg, &dummypte, &reg)) {
16038114Sbostic 		printf("vx%d: vbmemalloc failed.\n", vi->ui_unit);
16138114Sbostic 		return(0);
16238114Sbostic 	}
16338114Sbostic 	vp = (struct vxdevice *)reg;
16425675Ssam 	if (badaddr((caddr_t)vp, 1))
16525675Ssam 		return (0);
16625675Ssam 	vp->v_fault = 0;
16725675Ssam 	vp->v_vioc = V_BSY;
16825675Ssam 	vp->v_hdwre = V_RESET;		/* reset interrupt */
16924003Ssam 	DELAY(4000000);
17025881Ssam 	if (vp->v_fault != VXF_READY)
17125675Ssam 		return (0);
17225881Ssam 	vs = &vx_softc[vi->ui_unit];
17325857Ssam #ifdef notdef
17425857Ssam 	/*
17525857Ssam 	 * Align vioc interrupt vector base to 4 vector
17625857Ssam 	 * boundary and fitting in 8 bits (is this necessary,
17725857Ssam 	 * wish we had documentation).
17825857Ssam 	 */
17925857Ssam 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
18025857Ssam 		vi->ui_hd->vh_lastiv = 0xff;
18125881Ssam 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
18225857Ssam #else
18325881Ssam 	vs->vs_ivec = 0x40+vi->ui_unit*4;
18425857Ssam #endif
18525881Ssam 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
18625881Ssam 	return (sizeof (struct vxdevice));
18724003Ssam }
18824003Ssam 
18925857Ssam vxattach(vi)
19025857Ssam 	register struct vba_device *vi;
19124003Ssam {
19240738Skarels 	register struct vx_softc *vs = &vx_softc[vi->ui_unit];
19325675Ssam 
19440738Skarels 	vs->vs_softCAR = vi->ui_flags;
19540738Skarels 	vs->vs_addr = (struct vxdevice *)vi->ui_addr;
19629954Skarels 	vxinit(vi->ui_unit, 1);
19724003Ssam }
19824003Ssam 
19924003Ssam /*
20024003Ssam  * Open a VX line.
20124003Ssam  */
20225675Ssam /*ARGSUSED*/
20324003Ssam vxopen(dev, flag)
20425881Ssam 	dev_t dev;
20525881Ssam 	int flag;
20624003Ssam {
20724003Ssam 	register struct tty *tp;	/* pointer to tty struct for port */
20825881Ssam 	register struct vx_softc *vs;
20925881Ssam 	register struct vba_device *vi;
21040738Skarels 	int unit, vx, s, error = 0;
21137608Smarc 	int vxparam();
21224003Ssam 
21325881Ssam 	unit = minor(dev);
21430372Skarels 	vx = VXUNIT(unit);
21530372Skarels 	if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
21625881Ssam 		return (ENXIO);
21730372Skarels 	vs = &vx_softc[vx];
21825881Ssam 	tp = &vx_tty[unit];
21930372Skarels 	unit = VXPORT(unit);
22025881Ssam 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
22125881Ssam 		return (EBUSY);
22230372Skarels 	if (unit < vs->vs_loport || unit > vs->vs_hiport)
22325881Ssam 		return (ENXIO);
22425881Ssam 	tp->t_addr = (caddr_t)vs;
22525881Ssam 	tp->t_oproc = vxstart;
22637608Smarc 	tp->t_param = vxparam;
22725881Ssam 	tp->t_dev = dev;
22825881Ssam 	s = spl8();
22925881Ssam 	if ((tp->t_state&TS_ISOPEN) == 0) {
23042951Smarc 		tp->t_state |= TS_WOPEN;
23125881Ssam 		ttychars(tp);
23225881Ssam 		if (tp->t_ispeed == 0) {
23337608Smarc 			tp->t_iflag = TTYDEF_IFLAG;
23437608Smarc 			tp->t_oflag = TTYDEF_OFLAG;
23537608Smarc 			tp->t_lflag = TTYDEF_LFLAG;
23637608Smarc 			tp->t_cflag = TTYDEF_CFLAG;
23737608Smarc 			tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
23824003Ssam 		}
23937608Smarc 		vxparam(tp, &tp->t_termios);
24037608Smarc 		ttsetwater(tp);
24124003Ssam 	}
24230372Skarels 	vcmodem(dev, VMOD_ON);
24337608Smarc 	while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) &&
244*42957Smarc 	      (tp->t_state&TS_CARR_ON) == 0) {
24542951Smarc 		tp->t_state |= TS_WOPEN;
24642948Smarc 		if ((error = tsleep((caddr_t)&tp->t_rawq, TTIPRI | PCATCH,
24742948Smarc 				    ttopen, 0)) ||
24842948Smarc 		    (error = ttclosed(tp)))
24940738Skarels 			break;
250*42957Smarc 	}
25140738Skarels 	if (error == 0)
25240738Skarels 		error = (*linesw[tp->t_line].l_open)(dev,tp);
25325881Ssam 	splx(s);
25425881Ssam 	return (error);
25524003Ssam }
25624003Ssam 
25724003Ssam /*
25824003Ssam  * Close a VX line.
25924003Ssam  */
26025675Ssam /*ARGSUSED*/
26124003Ssam vxclose(dev, flag)
26225881Ssam 	dev_t dev;
26325881Ssam 	int flag;
26424003Ssam {
26524003Ssam 	register struct tty *tp;
26640738Skarels 	int unit, s, error = 0;
26724003Ssam 
26825881Ssam 	unit = minor(dev);
26925881Ssam 	tp = &vx_tty[unit];
27025881Ssam 	s = spl8();
27124003Ssam 	(*linesw[tp->t_line].l_close)(tp);
27237608Smarc 	if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0)
27330372Skarels 		vcmodem(dev, VMOD_OFF);
27424003Ssam 	/* wait for the last response */
27540738Skarels 	while (tp->t_state&TS_FLUSH && error == 0)
27640738Skarels 		error = tsleep((caddr_t)&tp->t_state, TTOPRI | PCATCH,
27740738Skarels 		    ttclos, 0);
27825881Ssam 	splx(s);
27940738Skarels 	if (error)
28040738Skarels 		return (error);
28140738Skarels 	return (ttyclose(tp));
28224003Ssam }
28324003Ssam 
28424003Ssam /*
28524003Ssam  * Read from a VX line.
28624003Ssam  */
28737608Smarc vxread(dev, uio, flag)
28824003Ssam 	dev_t dev;
28924003Ssam 	struct uio *uio;
29024003Ssam {
29125881Ssam 	struct tty *tp = &vx_tty[minor(dev)];
29225881Ssam 
29337608Smarc 	return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
29424003Ssam }
29524003Ssam 
29624003Ssam /*
29724003Ssam  * write on a VX line
29824003Ssam  */
29937608Smarc vxwrite(dev, uio, flag)
30024003Ssam 	dev_t dev;
30124003Ssam 	struct uio *uio;
30224003Ssam {
30325881Ssam 	register struct tty *tp = &vx_tty[minor(dev)];
30425881Ssam 
30537608Smarc 	return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
30624003Ssam }
30724003Ssam 
30824003Ssam /*
30924003Ssam  * VIOCX unsolicited interrupt.
31024003Ssam  */
31125881Ssam vxrint(vx)
31225881Ssam 	register vx;
31324003Ssam {
31425881Ssam 	register struct tty *tp, *tp0;
31525881Ssam 	register struct vxdevice *addr;
31625881Ssam 	register struct vx_softc *vs;
31725881Ssam 	struct vba_device *vi;
31825881Ssam 	register int nc, c;
31925881Ssam 	register struct silo {
32040738Skarels 		u_char	data, port;
32125881Ssam 	} *sp;
32225881Ssam 	short *osp;
32325881Ssam 	int overrun = 0;
32424003Ssam 
32525881Ssam 	vi = vxinfo[vx];
32625881Ssam 	if (vi == 0 || vi->ui_alive == 0)
32725881Ssam 		return;
32825881Ssam 	addr = (struct vxdevice *)vi->ui_addr;
32925881Ssam 	switch (addr->v_uqual&037) {
33024003Ssam 	case 0:
33124003Ssam 		break;
33224003Ssam 	case 2:
33340738Skarels 		if (addr->v_ustat == VP_SILO_OFLOW)
33440738Skarels 			log(LOG_ERR, "vx%d: input silo overflow\n", vx);
33540738Skarels 		else {
33640738Skarels 			printf("vx%d: vc proc err, ustat %x\n",
33740738Skarels 			    vx, addr->v_ustat);
33840738Skarels 			vxstreset(vx);
33940738Skarels 		}
34030372Skarels 		return;
34124003Ssam 	case 3:
34225881Ssam 		vcmintr(vx);
34330372Skarels 		return;
34424003Ssam 	case 4:
34530372Skarels 		return;
34624003Ssam 	default:
34730372Skarels 		printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
34825881Ssam 		vxstreset(vx);
34930372Skarels 		return;
35024003Ssam 	}
35125881Ssam 	vs = &vx_softc[vx];
35225881Ssam 	if (vs->vs_vers == VXV_NEW)
35325881Ssam 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
35425881Ssam 	else
35525881Ssam 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
35625881Ssam 	nc = *(osp = (short *)sp);
35725881Ssam 	if (nc == 0)
35830372Skarels 		return;
35925881Ssam 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
36025881Ssam 		printf("vx%d: %d exceeds silo size\n", nc);
36125881Ssam 		nc = vs->vs_silosiz;
36224003Ssam 	}
36325881Ssam 	tp0 = &vx_tty[vx*16];
36425881Ssam 	sp = (struct silo *)(((short *)sp)+1);
36525881Ssam 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
36625881Ssam 		c = sp->port & 017;
36725881Ssam 		if (vs->vs_loport > c || c > vs->vs_hiport)
36825881Ssam 			continue;
36925881Ssam 		tp = tp0 + c;
37025881Ssam 		if( (tp->t_state&TS_ISOPEN) == 0) {
37124003Ssam 			wakeup((caddr_t)&tp->t_rawq);
37224003Ssam 			continue;
37324003Ssam 		}
37437608Smarc 		c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f);
37525881Ssam 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
37629954Skarels 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
37725881Ssam 			overrun = 1;
37825881Ssam 			continue;
37925881Ssam 		}
38025881Ssam 		if (sp->port&VX_PE)
38137608Smarc 			c |= TTY_PE;
38237608Smarc 		if (sp->port&VX_FE)
38337608Smarc 			c |= TTY_FE;
38424003Ssam 		(*linesw[tp->t_line].l_rint)(c, tp);
38524003Ssam 	}
38625881Ssam 	*osp = 0;
38724003Ssam }
38824003Ssam 
38924003Ssam /*
39025881Ssam  * Ioctl for VX.
39124003Ssam  */
39224003Ssam vxioctl(dev, cmd, data, flag)
39325881Ssam 	dev_t dev;
39425881Ssam 	caddr_t	data;
39524003Ssam {
39625881Ssam 	register struct tty *tp;
39725881Ssam 	int error;
39824003Ssam 
39925881Ssam 	tp = &vx_tty[minor(dev)];
40024003Ssam 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
40137608Smarc 	if (error >= 0)
40225881Ssam 		return (error);
40325881Ssam 	error = ttioctl(tp, cmd, data, flag);
40437608Smarc 	if (error >= 0)
40525881Ssam 		return (error);
40625881Ssam 	return (ENOTTY);
40724003Ssam }
40824003Ssam 
40937608Smarc vxparam(tp, t)
41037608Smarc 	struct tty *tp;
41137608Smarc 	struct termios *t;
41224003Ssam {
41325881Ssam 
41437608Smarc 	return (vxcparam(tp, t, 1));
41524003Ssam }
41624003Ssam 
41724003Ssam /*
41824003Ssam  * Set parameters from open or stty into the VX hardware
41924003Ssam  * registers.
42024003Ssam  */
42137608Smarc vxcparam(tp, t, wait)
42237608Smarc 	struct tty *tp;
42337608Smarc 	struct termios *t;
42425881Ssam 	int wait;
42524003Ssam {
42625881Ssam 	register struct vx_softc *vs;
42725881Ssam 	register struct vxcmd *cp;
42840738Skarels 	int s, error = 0;
42937608Smarc 	int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab);
43024003Ssam 
43137608Smarc 	if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed))
43240738Skarels 		return (EINVAL);
43325881Ssam 	vs = (struct vx_softc *)tp->t_addr;
43425881Ssam 	cp = vobtain(vs);
43524003Ssam 	s = spl8();
43625933Ssam 	/*
43725933Ssam 	 * Construct ``load parameters'' command block
43825933Ssam 	 * to setup baud rates, xon-xoff chars, parity,
43925933Ssam 	 * and stop bits for the specified port.
44025933Ssam 	 */
44125933Ssam 	cp->cmd = VXC_LPARAX;
44240738Skarels 	cp->par[1] = VXPORT(minor(tp->t_dev));
44337608Smarc 	/*
44437608Smarc 	 * note: if the hardware does flow control, ^V doesn't work
44537608Smarc 	 * to escape ^S
44637608Smarc 	 */
44737608Smarc 	if (t->c_iflag&IXON) {
44837608Smarc 		if (t->c_cc[VSTART] == _POSIX_VDISABLE)
44937608Smarc 			cp->par[2] = 0;
45037608Smarc 		else
45137608Smarc 			cp->par[2] = t->c_cc[VSTART];
45237608Smarc 		if (t->c_cc[VSTOP] == _POSIX_VDISABLE)
45337608Smarc 			cp->par[3] = 0;
45437608Smarc 		else
45537608Smarc 			cp->par[3] = t->c_cc[VSTOP];
45637608Smarc 	} else
45737608Smarc 		cp->par[2] = cp->par[3] = 0;
45830372Skarels #ifdef notnow
45940738Skarels 	switch (t->c_cflag & CSIZE) {	/* XXX */
46040738Skarels 	case CS8:
46130372Skarels #endif
46230372Skarels 		cp->par[4] = BITS8;		/* 8 bits of data */
46330372Skarels #ifdef notnow
46440738Skarels 		break;
46540738Skarels 	case CS7:
46630372Skarels 		cp->par[4] = BITS7;		/* 7 bits of data */
46740738Skarels 		break;
46840738Skarels 	case CS6:
46940738Skarels 		cp->par[4] = BITS6;		/* 6 bits of data */
47040738Skarels 		break;
47140738Skarels 	case CS5:
47240738Skarels 		cp->par[4] = BITS5;		/* 5 bits of data */
47340738Skarels 		break;
47424003Ssam 	}
47540738Skarels 	if ((t->c_cflag & PARENB) == 0)		/* XXX */
47630372Skarels #endif
47740738Skarels 		cp->par[7] = VNOPARITY;		/* no parity */
47840738Skarels #ifdef notnow
47940738Skarels 	else if (t->c_cflag&PARODD)
48040738Skarels 		cp->par[7] = VODDP;	/* odd parity */
48140738Skarels 	else
48240738Skarels 		cp->par[7] = VEVENP;	/* even parity */
48340738Skarels #endif
48437608Smarc 	cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1;
48537608Smarc 	cp->par[6] = speedcode;
48630372Skarels 	if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
48740738Skarels 		error = tsleep((caddr_t)cp, TTIPRI | PCATCH, ttyout, 0);
48837608Smarc 	if ((t->c_ospeed)==0) {
48937608Smarc 		tp->t_cflag |= HUPCL;
49040738Skarels 		vcmodem(tp->t_dev, VMOD_OFF);
49137608Smarc 	}
49224003Ssam 	splx(s);
49340738Skarels 	return (error);
49424003Ssam }
49524003Ssam 
49624003Ssam /*
49724003Ssam  * VIOCX command response interrupt.
49824003Ssam  * For transmission, restart output to any active port.
49924003Ssam  * For all other commands, just clean up.
50024003Ssam  */
50125881Ssam vxxint(vx, cp)
50225881Ssam 	register int vx;
50325881Ssam 	register struct vxcmd *cp;
50424003Ssam {
50530372Skarels 	register struct vxmit *vp;
50625933Ssam 	register struct tty *tp, *tp0;
50725933Ssam 	register struct vx_softc *vs;
50824003Ssam 
50925881Ssam 	vs = &vx_softc[vx];
51025881Ssam 	cp = (struct vxcmd *)((long *)cp-1);
51129954Skarels 
51225881Ssam 	switch (cp->cmd&0xff00) {
51325881Ssam 
51425881Ssam 	case VXC_LIDENT:	/* initialization complete */
51525881Ssam 		if (vs->vs_state == VXS_RESET) {
51625881Ssam 			vxfnreset(vx, cp);
51725881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
51824003Ssam 		}
51924003Ssam 		cp->cmd++;
52024003Ssam 		return;
52125881Ssam 
52225881Ssam 	case VXC_XMITDTA:
52325881Ssam 	case VXC_XMITIMM:
52424003Ssam 		break;
52525881Ssam 
52625881Ssam 	case VXC_LPARAX:
52725675Ssam 		wakeup((caddr_t)cp);
52825881Ssam 		/* fall thru... */
52925881Ssam 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
53025881Ssam 		vrelease(vs, cp);
53125881Ssam 		if (vs->vs_state == VXS_RESET)
53225881Ssam 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
53324003Ssam 		return;
53424003Ssam 	}
53525881Ssam 	tp0 = &vx_tty[vx*16];
53625881Ssam 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
53725881Ssam 	for (; vp >= (struct vxmit *)cp->par; vp--) {
53825881Ssam 		tp = tp0 + (vp->line & 017);
53924003Ssam 		tp->t_state &= ~TS_BUSY;
54025881Ssam 		if (tp->t_state & TS_FLUSH) {
54124003Ssam 			tp->t_state &= ~TS_FLUSH;
54225881Ssam 			wakeup((caddr_t)&tp->t_state);
54325881Ssam 		} else
54424003Ssam 		 	ndflush(&tp->t_outq, vp->bcount+1);
54524003Ssam 	}
54625881Ssam 	vrelease(vs, cp);
54730372Skarels 	if (vs->vs_vers == VXV_NEW)
54832112Skarels 		(*linesw[tp->t_line].l_start)(tp);
54930372Skarels 	else {
55025881Ssam 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
55125881Ssam 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
55232112Skarels 			(*linesw[tp->t_line].l_start)(tp);
55325881Ssam 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
55425881Ssam 			vs->vs_xmtcnt++;
55530372Skarels 			(void) vcmd(vx, (caddr_t)&cp->cmd);
55624003Ssam 		}
55724003Ssam 	}
55830372Skarels 	vs->vs_xmtcnt--;
55924003Ssam }
56024003Ssam 
56124003Ssam /*
56224003Ssam  * Force out partial XMIT command after timeout
56324003Ssam  */
56425881Ssam vxforce(vs)
56525881Ssam 	register struct vx_softc *vs;
56624003Ssam {
56725881Ssam 	register struct vxcmd *cp;
56825881Ssam 	int s;
56924003Ssam 
57024003Ssam 	s = spl8();
57125881Ssam 	if ((cp = nextcmd(vs)) != NULL) {
57225881Ssam 		vs->vs_xmtcnt++;
57330372Skarels 		(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
57424003Ssam 	}
57524003Ssam 	splx(s);
57624003Ssam }
57724003Ssam 
57824003Ssam /*
57924003Ssam  * Start (restart) transmission on the given VX line.
58024003Ssam  */
58124003Ssam vxstart(tp)
58225881Ssam 	register struct tty *tp;
58324003Ssam {
58425675Ssam 	register short n;
58525933Ssam 	register struct vx_softc *vs;
58625933Ssam 	int s, port;
58724003Ssam 
58824003Ssam 	s = spl8();
58940738Skarels 	port = VXPORT(minor(tp->t_dev));
59025881Ssam 	vs = (struct vx_softc *)tp->t_addr;
59125881Ssam 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
59237608Smarc 		if (tp->t_outq.c_cc <= tp->t_lowat) {
59324003Ssam 			if (tp->t_state&TS_ASLEEP) {
59424003Ssam 				tp->t_state &= ~TS_ASLEEP;
59524003Ssam 				wakeup((caddr_t)&tp->t_outq);
59624003Ssam 			}
59724003Ssam 			if (tp->t_wsel) {
59824003Ssam 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
59924003Ssam 				tp->t_wsel = 0;
60024003Ssam 				tp->t_state &= ~TS_WCOLL;
60124003Ssam 			}
60224003Ssam 		}
60325881Ssam 		if (tp->t_outq.c_cc == 0) {
60424003Ssam 			splx(s);
60530372Skarels 			return;
60624003Ssam 		}
60725877Ssam 		scope_out(3);
60837608Smarc 		if (1 || !(tp->t_oflag&OPOST))	/* XXX */
60930372Skarels 			n = ndqb(&tp->t_outq, 0);
61030372Skarels 		else {
61130372Skarels 			n = ndqb(&tp->t_outq, 0200);
61230372Skarels 			if (n == 0) {
61325675Ssam 				n = getc(&tp->t_outq);
61425881Ssam 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
61524003Ssam 				tp->t_state |= TS_TIMEOUT;
61630372Skarels 				n = 0;
61724003Ssam 			}
61830372Skarels 		}
61930372Skarels 		if (n) {
62024003Ssam 			tp->t_state |= TS_BUSY;
62130372Skarels 			vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
62224003Ssam 		}
62324003Ssam 	}
62424003Ssam 	splx(s);
62524003Ssam }
62624003Ssam 
62724003Ssam /*
62824003Ssam  * Stop output on a line.
62924003Ssam  */
63024003Ssam vxstop(tp)
63125881Ssam 	register struct tty *tp;
63224003Ssam {
63325881Ssam 	int s;
63424003Ssam 
63524003Ssam 	s = spl8();
63625881Ssam 	if (tp->t_state&TS_BUSY)
63725881Ssam 		if ((tp->t_state&TS_TTSTOP) == 0)
63824003Ssam 			tp->t_state |= TS_FLUSH;
63924003Ssam 	splx(s);
64024003Ssam }
64124003Ssam 
64225881Ssam static	int vxbbno = -1;
64324003Ssam /*
64424003Ssam  * VIOCX Initialization.  Makes free lists of command buffers.
64524003Ssam  * Resets all viocx's.  Issues a LIDENT command to each
64625933Ssam  * viocx to establish interrupt vectors and logical port numbers.
64724003Ssam  */
64840738Skarels vxinit(vx, wait)
64925881Ssam 	register int vx;
65025881Ssam 	int wait;
65124003Ssam {
65225933Ssam 	register struct vx_softc *vs;
65325933Ssam 	register struct vxdevice *addr;
65425933Ssam 	register struct vxcmd *cp;
65525881Ssam 	register char *resp;
65625881Ssam 	register int j;
65730372Skarels 	char type, *typestring;
65824003Ssam 
65925881Ssam 	vs = &vx_softc[vx];
66040738Skarels 	addr = vs->vs_addr;
66125881Ssam 	type = addr->v_ident;
66225881Ssam 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
66325881Ssam 	if (vs->vs_vers == VXV_NEW)
66425881Ssam 		vs->vs_silosiz = addr->v_maxsilo;
66525881Ssam 	switch (type) {
66624003Ssam 
66725881Ssam 	case VXT_VIOCX:
66825881Ssam 	case VXT_VIOCX|VXT_NEW:
66930372Skarels 		typestring = "VIOC-X";
67030372Skarels 		/* set soft carrier for printer ports */
67130372Skarels 		for (j = 0; j < 16; j++)
67240738Skarels 			if (vs->vs_softCAR & (1 << j) ||
67340738Skarels 			    addr->v_portyp[j] == VXT_PARALLEL) {
67430372Skarels 				vs->vs_softCAR |= 1 << j;
67525881Ssam 				addr->v_dcd |= 1 << j;
67630372Skarels 			}
67725881Ssam 		break;
67824003Ssam 
67925881Ssam 	case VXT_PVIOCX:
68025881Ssam 	case VXT_PVIOCX|VXT_NEW:
68130372Skarels 		typestring = "VIOC-X (old connector panel)";
68225881Ssam 		break;
68325881Ssam 	case VXT_VIOCBOP:		/* VIOC-BOP */
68425881Ssam 		vs->vs_type = 1;
68525881Ssam 		vs->vs_bop = ++vxbbno;
68625881Ssam 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
68740738Skarels 		goto unsup;
68825933Ssam 	default:
68925881Ssam 		printf("vx%d: unknown type %x\n", vx, type);
69040738Skarels 	unsup:
69130372Skarels 		vxinfo[vx]->ui_alive = 0;
69225881Ssam 		return;
69324003Ssam 	}
69440738Skarels 	vs->vs_nbr = vx;		/* assign board number */
69525933Ssam 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
69625933Ssam 	/*
69725933Ssam 	 * Initialize all cmd buffers by linking them
69825933Ssam 	 * into a free list.
69925933Ssam 	 */
70025881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
70125933Ssam 		cp = &vs->vs_lst[j];
70225933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
70325881Ssam 	}
70425881Ssam 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
70524003Ssam 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
70624003Ssam 
70725933Ssam 	/*
70825933Ssam 	 * Establish the interrupt vectors and define the port numbers.
70925933Ssam 	 */
71025933Ssam 	cp = vobtain(vs);
71125933Ssam 	cp->cmd = VXC_LIDENT;
71225881Ssam 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
71325857Ssam 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
71425857Ssam 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
71525881Ssam 	cp->par[4] = 15;		/* max ports, no longer used */
71625881Ssam 	cp->par[5] = 0;			/* set 1st port number */
71730372Skarels 	(void) vcmd(vx, (caddr_t)&cp->cmd);
71825881Ssam 	if (!wait)
71925881Ssam 		return;
72040738Skarels 
72125881Ssam 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
72225857Ssam 		;
72325857Ssam 	if (j >= 4000000)
72425881Ssam 		printf("vx%d: didn't respond to LIDENT\n", vx);
72524003Ssam 
72624003Ssam  	/* calculate address of response buffer */
72725881Ssam  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
72825933Ssam 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
72925933Ssam 		vrelease(vs, cp);	/* init failed */
73025881Ssam 		return;
73124003Ssam 	}
73225881Ssam 	vs->vs_loport = cp->par[5];
73325881Ssam 	vs->vs_hiport = cp->par[7];
73430372Skarels 	printf("vx%d: %s%s, ports %d-%d\n", vx,
73530372Skarels 	    (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
73630372Skarels 	    vs->vs_loport, vs->vs_hiport);
73725881Ssam 	vrelease(vs, cp);
73824003Ssam }
73924003Ssam 
74024003Ssam /*
74124003Ssam  * Obtain a command buffer
74224003Ssam  */
74325881Ssam struct vxcmd *
74425881Ssam vobtain(vs)
74525933Ssam 	register struct vx_softc *vs;
74624003Ssam {
74725933Ssam 	register struct vxcmd *p;
74825881Ssam 	int s;
74924003Ssam 
75024003Ssam 	s = spl8();
75125881Ssam 	p = vs->vs_avail;
75225881Ssam 	if (p == (struct vxcmd *)0) {
75324003Ssam #ifdef VX_DEBUG
75425881Ssam 		if (vxintr4&VXNOBUF)
75525881Ssam 			vxintr4 &= ~VXNOBUF;
75624003Ssam #endif
75740738Skarels 		printf("vx%d: no buffers\n", vs->vs_nbr);
75840738Skarels 		vxstreset(vs->vs_nbr);
75924003Ssam 		splx(s);
76025881Ssam 		return (vobtain(vs));
76124003Ssam 	}
76230372Skarels 	vs->vs_avail = p->c_fwd;
76324003Ssam 	splx(s);
76425881Ssam 	return ((struct vxcmd *)p);
76524003Ssam }
76624003Ssam 
76724003Ssam /*
76824003Ssam  * Release a command buffer
76924003Ssam  */
77025881Ssam vrelease(vs, cp)
77125933Ssam 	register struct vx_softc *vs;
77225933Ssam 	register struct vxcmd *cp;
77324003Ssam {
77425881Ssam 	int s;
77524003Ssam 
77624003Ssam #ifdef VX_DEBUG
77725881Ssam 	if (vxintr4&VXNOBUF)
77825881Ssam 		return;
77924003Ssam #endif
78024003Ssam 	s = spl8();
78125881Ssam 	cp->c_fwd = vs->vs_avail;
78225881Ssam 	vs->vs_avail = cp;
78324003Ssam 	splx(s);
78424003Ssam }
78524003Ssam 
78625881Ssam struct vxcmd *
78725881Ssam nextcmd(vs)
78825933Ssam 	register struct vx_softc *vs;
78924003Ssam {
79025933Ssam 	register struct vxcmd *cp;
79125881Ssam 	int s;
79224003Ssam 
79324003Ssam 	s = spl8();
79425881Ssam 	cp = vs->vs_build;
79525881Ssam 	vs->vs_build = (struct vxcmd *)0;
79624003Ssam 	splx(s);
79725881Ssam 	return (cp);
79824003Ssam }
79924003Ssam 
80024003Ssam /*
80125933Ssam  * Assemble transmits into a multiple command;
80230372Skarels  * up to 8 transmits to 8 lines can be assembled together
80330372Skarels  * (on PVIOCX only).
80424003Ssam  */
80525933Ssam vsetq(vs, line, addr, n)
80625933Ssam 	register struct vx_softc *vs;
80725881Ssam 	caddr_t	addr;
80824003Ssam {
80925933Ssam 	register struct vxcmd *cp;
81025933Ssam 	register struct vxmit *mp;
81124003Ssam 
81225933Ssam 	/*
81325933Ssam 	 * Grab a new command buffer or append
81425933Ssam 	 * to the current one being built.
81525933Ssam 	 */
81625881Ssam 	cp = vs->vs_build;
81725881Ssam 	if (cp == (struct vxcmd *)0) {
81825881Ssam 		cp = vobtain(vs);
81925881Ssam 		vs->vs_build = cp;
82025881Ssam 		cp->cmd = VXC_XMITDTA;
82124003Ssam 	} else {
82230372Skarels 		if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
82325881Ssam 			printf("vx%d: setq overflow\n", vs-vx_softc);
82430372Skarels 			vxstreset((int)vs->vs_nbr);
82530372Skarels 			return;
82624003Ssam 		}
82724003Ssam 		cp->cmd++;
82824003Ssam 	}
82925933Ssam 	/*
83025933Ssam 	 * Select the next vxmit buffer and copy the
83125933Ssam 	 * characters into the buffer (if there's room
83225933Ssam 	 * and the device supports ``immediate mode'',
83325933Ssam 	 * or store an indirect pointer to the data.
83425933Ssam 	 */
83525881Ssam 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
83625675Ssam 	mp->bcount = n-1;
83725933Ssam 	mp->line = line;
83825933Ssam 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
83925881Ssam 		cp->cmd = VXC_XMITIMM;
84030372Skarels 		bcopy(addr, mp->ostream, (unsigned)n);
84124003Ssam 	} else {
84225933Ssam 		/* get system address of clist block */
84325675Ssam 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
84430372Skarels 		bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
84524003Ssam 	}
84630372Skarels 	/*
84730372Skarels 	 * We send the data immediately if a VIOCX,
84830372Skarels 	 * the command buffer is full, or if we've nothing
84930372Skarels 	 * currently outstanding.  If we don't send it,
85030372Skarels 	 * set a timeout to force the data to be sent soon.
85130372Skarels 	 */
85230372Skarels 	if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
85330372Skarels 	    vs->vs_xmtcnt == 0) {
85430372Skarels 		vs->vs_xmtcnt++;
85530372Skarels 		(void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
85630372Skarels 		vs->vs_build = 0;
85730372Skarels 	} else
85830372Skarels 		timeout(vxforce, (caddr_t)vs, 3);
85924003Ssam }
86025881Ssam 
86125881Ssam /*
86225881Ssam  * Write a command out to the VIOC
86325881Ssam  */
86425881Ssam vcmd(vx, cmdad)
86525881Ssam 	register int vx;
86625881Ssam 	register caddr_t cmdad;
86725881Ssam {
86825933Ssam 	register struct vcmds *cp;
86940738Skarels 	register struct vx_softc *vs = &vx_softc[vx];
87025881Ssam 	int s;
87125881Ssam 
87225881Ssam 	s = spl8();
87325933Ssam 	/*
87425933Ssam 	 * When the vioc is resetting, don't process
87525933Ssam 	 * anything other than VXC_LIDENT commands.
87625933Ssam 	 */
87725881Ssam 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
87825933Ssam 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
87925881Ssam 
88025933Ssam 		if (vcp->cmd != VXC_LIDENT) {
88125933Ssam 			vrelease(vs, vcp);
88225881Ssam 			return (0);
88325881Ssam 		}
88425881Ssam 	}
88525881Ssam 	cp = &vs->vs_cmds;
88625881Ssam 	if (cmdad != (caddr_t)0) {
88725881Ssam 		cp->cmdbuf[cp->v_fill] = cmdad;
88825881Ssam 		if (++cp->v_fill >= VC_CMDBUFL)
88925881Ssam 			cp->v_fill = 0;
89025881Ssam 		if (cp->v_fill == cp->v_empty) {
89125881Ssam 			printf("vx%d: cmd q overflow\n", vx);
89225881Ssam 			vxstreset(vx);
89325881Ssam 			splx(s);
89425881Ssam 			return (0);
89525881Ssam 		}
89625881Ssam 		cp->v_cmdsem++;
89725881Ssam 	}
89825881Ssam 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
89925881Ssam 		cp->v_cmdsem--;
90025881Ssam 		cp->v_curcnt++;
90125881Ssam 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
90225881Ssam 	}
90325881Ssam 	splx(s);
90425881Ssam 	return (1);
90525881Ssam }
90625881Ssam 
90725881Ssam /*
90825881Ssam  * VIOC acknowledge interrupt.  The VIOC has received the new
90925881Ssam  * command.  If no errors, the new command becomes one of 16 (max)
91025881Ssam  * current commands being executed.
91125881Ssam  */
91225881Ssam vackint(vx)
91325881Ssam 	register vx;
91425881Ssam {
91525933Ssam 	register struct vxdevice *vp;
91625933Ssam 	register struct vcmds *cp;
91725881Ssam 	struct vx_softc *vs;
91825881Ssam 	int s;
91925881Ssam 
92025881Ssam 	scope_out(5);
92125881Ssam 	vs = &vx_softc[vx];
92229954Skarels 	if (vs->vs_type)	/* Its a BOP */
92325881Ssam 		return;
92425881Ssam 	s = spl8();
92540738Skarels 	vp = vs->vs_addr;
92625881Ssam 	cp = &vs->vs_cmds;
92725933Ssam 	if (vp->v_vcid&V_ERR) {
92825881Ssam 		register char *resp;
92925881Ssam 		register i;
93025933Ssam 
93130372Skarels 		printf("vx%d: ackint error type %x v_dcd %x\n", vx,
93225881Ssam 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
93325881Ssam 		resp = (char *)vs->vs_mricmd;
93425881Ssam 		for (i = 0; i < 16; i++)
93525881Ssam 			printf("%x ", resp[i]&0xff);
93625881Ssam 		printf("\n");
93725881Ssam 		splx(s);
93825881Ssam 		vxstreset(vx);
93925881Ssam 		return;
94025881Ssam 	}
94125881Ssam 	if ((vp->v_hdwre&017) == CMDquals) {
94225881Ssam #ifdef VX_DEBUG
94325881Ssam 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
94425933Ssam 			struct vxcmd *cp1, *cp0;
94525881Ssam 
94625933Ssam 			cp0 = (struct vxcmd *)
94725933Ssam 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
94825881Ssam 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
94925881Ssam 				cp1 = vobtain(vs);
95025881Ssam 				*cp1 = *cp0;
95125881Ssam 				vxintr4 &= ~VXERR4;
95225881Ssam 				(void) vcmd(vx, &cp1->cmd);
95325881Ssam 			}
95425881Ssam 		}
95525881Ssam #endif
95625881Ssam 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
95725881Ssam 		if (++cp->v_empty >= VC_CMDBUFL)
95825881Ssam 			cp->v_empty = 0;
95925881Ssam 	}
96025881Ssam 	if (++cp->v_itrempt >= VC_IQLEN)
96125881Ssam 		cp->v_itrempt = 0;
96225881Ssam 	vintempt(vx);
96325881Ssam 	splx(s);
96425881Ssam 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
96525881Ssam }
96625881Ssam 
96725881Ssam /*
96825881Ssam  * Command Response interrupt.  The Vioc has completed
96925881Ssam  * a command.  The command may now be returned to
97025881Ssam  * the appropriate device driver.
97125881Ssam  */
97225881Ssam vcmdrsp(vx)
97325881Ssam 	register vx;
97425881Ssam {
97525933Ssam 	register struct vxdevice *vp;
97625933Ssam 	register struct vcmds *cp;
97725881Ssam 	register caddr_t cmd;
97825881Ssam 	register struct vx_softc *vs;
97925881Ssam 	register char *resp;
98025881Ssam 	register k;
98125881Ssam 	register int s;
98225881Ssam 
98325881Ssam 	scope_out(6);
98425881Ssam 	vs = &vx_softc[vx];
98525881Ssam 	if (vs->vs_type) {	/* Its a BOP */
98625881Ssam 		printf("vx%d: vcmdrsp interrupt\n", vx);
98725881Ssam 		return;
98825881Ssam 	}
98925881Ssam 	s = spl8();
99040738Skarels 	vp = vs->vs_addr;
99125881Ssam 	cp = &vs->vs_cmds;
99225881Ssam 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
99325881Ssam 	if (((k = resp[1])&V_UNBSY) == 0) {
99425881Ssam 		printf("vx%d: cmdresp debug\n", vx);
99525881Ssam 		splx(s);
99625881Ssam 		vxstreset(vx);
99725881Ssam 		return;
99825881Ssam 	}
99925881Ssam 	k &= VCMDLEN-1;
100025881Ssam 	cmd = cp->v_curcmd[k];
100125881Ssam 	cp->v_curcmd[k] = (caddr_t)0;
100225881Ssam 	cp->v_curcnt--;
100325881Ssam 	k = *((short *)&resp[4]);	/* cmd operation code */
100425881Ssam 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
100525881Ssam 		for (k = 0; k < VRESPLEN; k++)
100625881Ssam 			cmd[k] = resp[k+4];
100725881Ssam 	resp[1] = 0;
100825881Ssam 	vxxint(vx, (struct vxcmd *)cmd);
100925881Ssam 	if (vs->vs_state == VXS_READY)
101025881Ssam 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
101125881Ssam 	splx(s);
101225881Ssam }
101325881Ssam 
101425881Ssam /*
101525881Ssam  * Unsolicited interrupt.
101625881Ssam  */
101725881Ssam vunsol(vx)
101825881Ssam 	register vx;
101925881Ssam {
102025933Ssam 	register struct vxdevice *vp;
102125881Ssam 	struct vx_softc *vs;
102225881Ssam 	int s;
102325881Ssam 
102425881Ssam 	scope_out(1);
102525881Ssam 	vs = &vx_softc[vx];
102625881Ssam 	if (vs->vs_type) {	/* Its a BOP */
102725881Ssam 		printf("vx%d: vunsol from BOP\n", vx);
102825881Ssam 		return;
102925881Ssam 	}
103025881Ssam 	s = spl8();
103140738Skarels 	vp = vs->vs_addr;
103225881Ssam 	if (vp->v_uqual&V_UNBSY) {
103325881Ssam 		vxrint(vx);
103425881Ssam 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
103525881Ssam #ifdef notdef
103625881Ssam 	} else {
103725881Ssam 		printf("vx%d: unsolicited interrupt error\n", vx);
103825881Ssam 		splx(s);
103925881Ssam 		vxstreset(vx);
104025881Ssam #endif
104125881Ssam 	}
104225881Ssam 	splx(s);
104325881Ssam }
104425881Ssam 
104525881Ssam /*
104625933Ssam  * Enqueue an interrupt.
104725881Ssam  */
104825881Ssam vinthandl(vx, item)
104925881Ssam 	register int vx;
105025881Ssam 	register item;
105125881Ssam {
105225881Ssam 	register struct vcmds *cp;
105325881Ssam 	int empty;
105425881Ssam 
105525881Ssam 	cp = &vx_softc[vx].vs_cmds;
105625933Ssam 	empty = (cp->v_itrfill == cp->v_itrempt);
105725881Ssam 	cp->v_itrqueu[cp->v_itrfill] = item;
105825881Ssam 	if (++cp->v_itrfill >= VC_IQLEN)
105925881Ssam 		cp->v_itrfill = 0;
106025881Ssam 	if (cp->v_itrfill == cp->v_itrempt) {
106125881Ssam 		printf("vx%d: interrupt q overflow\n", vx);
106225881Ssam 		vxstreset(vx);
106325881Ssam 	} else if (empty)
106425881Ssam 		vintempt(vx);
106525881Ssam }
106625881Ssam 
106725881Ssam vintempt(vx)
106840738Skarels 	int vx;
106925881Ssam {
107025881Ssam 	register struct vcmds *cp;
107125881Ssam 	register struct vxdevice *vp;
107240738Skarels 	register struct vx_softc *vs;
107325881Ssam 	register short item;
107425881Ssam 	register short *intr;
107525881Ssam 
107640738Skarels 	vs = &vx_softc[vx];
107740738Skarels 	vp = vs->vs_addr;
107825881Ssam 	if (vp->v_vioc&V_BSY)
107925881Ssam 		return;
108040738Skarels 	cp = &vs->vs_cmds;
108125881Ssam 	if (cp->v_itrempt == cp->v_itrfill)
108225881Ssam 		return;
108325881Ssam 	item = cp->v_itrqueu[cp->v_itrempt];
108425881Ssam 	intr = (short *)&vp->v_vioc;
108525881Ssam 	switch ((item >> 8)&03) {
108625881Ssam 
108725881Ssam 	case CMDquals: {		/* command */
108825881Ssam 		int phys;
108925881Ssam 
109025881Ssam 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
109125881Ssam 			break;
109240738Skarels 		vs->vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
109325881Ssam 		phys = vtoph((struct proc *)0,
109425881Ssam 		    (unsigned)cp->cmdbuf[cp->v_empty]);
109525881Ssam 		vp->v_vcp[0] = ((short *)&phys)[0];
109625881Ssam 		vp->v_vcp[1] = ((short *)&phys)[1];
109725881Ssam 		vp->v_vcbsy = V_BSY;
109825881Ssam 		*intr = item;
109925881Ssam 		scope_out(4);
110025881Ssam 		break;
110125881Ssam 	}
110225881Ssam 
110325881Ssam 	case RSPquals:		/* command response */
110425881Ssam 		*intr = item;
110525881Ssam 		scope_out(7);
110625881Ssam 		break;
110725881Ssam 
110825881Ssam 	case UNSquals:		/* unsolicited interrupt */
110925881Ssam 		vp->v_uqual = 0;
111025881Ssam 		*intr = item;
111125881Ssam 		scope_out(2);
111225881Ssam 		break;
111325881Ssam 	}
111425881Ssam }
111525881Ssam 
111625881Ssam /*
111725881Ssam  * Start a reset on a vioc after error (hopefully)
111825881Ssam  */
111925881Ssam vxstreset(vx)
112040738Skarels 	register int vx;
112125881Ssam {
112225881Ssam 	register struct vx_softc *vs;
112325933Ssam 	register struct vxdevice *vp;
112425881Ssam 	register struct vxcmd *cp;
112525881Ssam 	register int j;
112625881Ssam 	extern int vxinreset();
112725881Ssam 	int s;
112825881Ssam 
112925881Ssam 	vs = &vx_softc[vx];
113040738Skarels 	s = spl8();
113125881Ssam 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
113225881Ssam 		splx(s);
113325881Ssam 		return;
113425881Ssam 	}
113540738Skarels 	vp = vs->vs_addr;
113625881Ssam 	/*
113725881Ssam 	 * Zero out the vioc structures, mark the vioc as being
113825881Ssam 	 * reset, reinitialize the free command list, reset the vioc
113925881Ssam 	 * and start a timer to check on the progress of the reset.
114025881Ssam 	 */
114140738Skarels 	bzero((caddr_t)&vs->vs_zero,
114240738Skarels 	    (unsigned)((caddr_t)(vs + 1) - (caddr_t)&vs->vs_zero));
114325881Ssam 
114425881Ssam 	/*
114525881Ssam 	 * Setting VXS_RESET prevents others from issuing
114625881Ssam 	 * commands while allowing currently queued commands to
114725881Ssam 	 * be passed to the VIOC.
114825881Ssam 	 */
114925881Ssam 	vs->vs_state = VXS_RESET;
115025881Ssam 	/* init all cmd buffers */
115125881Ssam 	for (j = 0; j < NVCXBUFS; j++) {
115225933Ssam 		cp = &vs->vs_lst[j];
115325933Ssam 		cp->c_fwd = &vs->vs_lst[j+1];
115425881Ssam 	}
115525933Ssam 	vs->vs_avail = &vs->vs_lst[0];
115625933Ssam 	cp->c_fwd = (struct vxcmd *)0;
115725881Ssam 	printf("vx%d: reset...", vx);
115825881Ssam 	vp->v_fault = 0;
115925881Ssam 	vp->v_vioc = V_BSY;
116025933Ssam 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
116125881Ssam 	timeout(vxinreset, (caddr_t)vx, hz*5);
116225881Ssam 	splx(s);
116325881Ssam }
116425881Ssam 
116525881Ssam /* continue processing a reset on a vioc after an error (hopefully) */
116625881Ssam vxinreset(vx)
116725881Ssam 	int vx;
116825881Ssam {
116925933Ssam 	register struct vxdevice *vp;
117025881Ssam 	int s = spl8();
117125881Ssam 
117240738Skarels 	vp = vx_softc[vx].vs_addr;
117325881Ssam 	/*
117425881Ssam 	 * See if the vioc has reset.
117525881Ssam 	 */
117625881Ssam 	if (vp->v_fault != VXF_READY) {
117740738Skarels 		printf(" vxreset failed\n");
117825881Ssam 		splx(s);
117925881Ssam 		return;
118025881Ssam 	}
118125881Ssam 	/*
118225881Ssam 	 * Send a LIDENT to the vioc and mess with carrier flags
118325881Ssam 	 * on parallel printer ports.
118425881Ssam 	 */
118529954Skarels 	vxinit(vx, 0);
118625881Ssam 	splx(s);
118725881Ssam }
118825881Ssam 
118925881Ssam /*
119025933Ssam  * Finish the reset on the vioc after an error (hopefully).
119125933Ssam  *
119225881Ssam  * Restore modem control, parameters and restart output.
119325881Ssam  * Since the vioc can handle no more then 24 commands at a time
119425881Ssam  * and we could generate as many as 48 commands, we must do this in
119525881Ssam  * phases, issuing no more then 16 commands at a time.
119625881Ssam  */
119725881Ssam vxfnreset(vx, cp)
119825881Ssam 	register int vx;
119925881Ssam 	register struct vxcmd *cp;
120025881Ssam {
120125881Ssam 	register struct vx_softc *vs;
120240738Skarels 	register struct vxdevice *vp;
120325881Ssam 	register struct tty *tp, *tp0;
120425881Ssam 	register int i;
120525881Ssam #ifdef notdef
120625881Ssam 	register int on;
120725881Ssam #endif
120825881Ssam 	extern int vxrestart();
120925881Ssam 	int s = spl8();
121025881Ssam 
121125881Ssam 	vs = &vx_softc[vx];
121225881Ssam 	vrelease(vs, cp);
121325881Ssam 	vs->vs_state = VXS_READY;
121425881Ssam 
121540738Skarels 	vp = vs->vs_addr;
121625881Ssam 	vp->v_vcid = 0;
121725881Ssam 
121825881Ssam 	/*
121925881Ssam 	 * Restore modem information and control.
122025881Ssam 	 */
122125881Ssam 	tp0 = &vx_tty[vx*16];
122225881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
122325881Ssam 		tp = tp0 + i;
122425881Ssam 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
122525881Ssam 			tp->t_state &= ~TS_CARR_ON;
122625881Ssam 			vcmodem(tp->t_dev, VMOD_ON);
122725881Ssam 			if (tp->t_state&TS_CARR_ON)
122829954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
122929954Skarels 			else if (tp->t_state & TS_ISOPEN)
123029954Skarels 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
123125881Ssam 		}
123229954Skarels #ifdef notdef
123325881Ssam 		/*
123425881Ssam 		 * If carrier has changed while we were resetting,
123525881Ssam 		 * take appropriate action.
123625881Ssam 		 */
123725881Ssam 		on = vp->v_dcd & 1<<i;
123829954Skarels 		if (on && (tp->t_state&TS_CARR_ON) == 0)
123929954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
124029954Skarels 		else if (!on && tp->t_state&TS_CARR_ON)
124129954Skarels 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
124225881Ssam #endif
124325881Ssam 	}
124425881Ssam 	vs->vs_state = VXS_RESET;
124525881Ssam 	timeout(vxrestart, (caddr_t)vx, hz);
124625881Ssam 	splx(s);
124725881Ssam }
124825881Ssam 
124925881Ssam /*
125025881Ssam  * Restore a particular aspect of the VIOC.
125125881Ssam  */
125225881Ssam vxrestart(vx)
125325881Ssam 	int vx;
125425881Ssam {
125525881Ssam 	register struct tty *tp, *tp0;
125625881Ssam 	register struct vx_softc *vs;
125730372Skarels 	register int i, count;
125825881Ssam 	int s = spl8();
125925881Ssam 
126030372Skarels 	count = vx >> 8;
126125881Ssam 	vx &= 0xff;
126225881Ssam 	vs = &vx_softc[vx];
126325881Ssam 	vs->vs_state = VXS_READY;
126425881Ssam 	tp0 = &vx_tty[vx*16];
126525881Ssam 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
126625881Ssam 		tp = tp0 + i;
126730372Skarels 		if (count != 0) {
126825881Ssam 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
126925881Ssam 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
127025881Ssam 				vxstart(tp);	/* restart pending output */
127125881Ssam 		} else {
127225881Ssam 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
127337608Smarc 				vxcparam(tp, &tp->t_termios, 0);
127425881Ssam 		}
127525881Ssam 	}
127630372Skarels 	if (count == 0) {
127725881Ssam 		vs->vs_state = VXS_RESET;
127825881Ssam 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
127925881Ssam 	} else
128040738Skarels 		printf(" vx reset done\n");
128125881Ssam 	splx(s);
128225881Ssam }
128325881Ssam 
128425881Ssam vxreset(dev)
128525881Ssam 	dev_t dev;
128625881Ssam {
128725881Ssam 
128830372Skarels 	vxstreset((int)VXUNIT(minor(dev)));	/* completes asynchronously */
128925881Ssam }
129025881Ssam 
129140738Skarels #ifdef VX_DEBUG
129225881Ssam vxfreset(vx)
129325881Ssam 	register int vx;
129425881Ssam {
129525881Ssam 	struct vba_device *vi;
129625881Ssam 
129725881Ssam 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
129825881Ssam 		return (ENODEV);
129925881Ssam 	vx_softc[vx].vs_state = VXS_READY;
130025881Ssam 	vxstreset(vx);
130125881Ssam 	return (0);		/* completes asynchronously */
130225881Ssam }
130330372Skarels #endif
130425881Ssam 
130525881Ssam vcmodem(dev, flag)
130625881Ssam 	dev_t dev;
130725881Ssam {
130825881Ssam 	struct tty *tp;
130925881Ssam 	register struct vxcmd *cp;
131025881Ssam 	register struct vx_softc *vs;
131125881Ssam 	register struct vxdevice *kp;
131225881Ssam 	register port;
131325881Ssam 	int unit;
131425881Ssam 
131525881Ssam 	unit = minor(dev);
131625881Ssam 	tp = &vx_tty[unit];
131725881Ssam 	vs = (struct vx_softc *)tp->t_addr;
131830372Skarels 	if (vs->vs_state != VXS_READY)
131930372Skarels 		return;
132025881Ssam 	cp = vobtain(vs);
132140738Skarels 	kp = vs->vs_addr;
132225881Ssam 
132340738Skarels 	port = VXPORT(unit);
132425881Ssam 	/*
132525881Ssam 	 * Issue MODEM command
132625881Ssam 	 */
132725881Ssam 	cp->cmd = VXC_MDMCTL;
132830372Skarels 	if (flag == VMOD_ON) {
132940738Skarels 		if (vs->vs_softCAR & (1 << port)) {
133030372Skarels 			cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
133140738Skarels 			kp->v_dcd |= (1 << port);
133240738Skarels 		} else
133340738Skarels 			cp->par[0] = V_AUTO | V_DTR_ON;
133430372Skarels 	} else
133530372Skarels 		cp->par[0] = V_DTR_OFF;
133625881Ssam 	cp->par[1] = port;
133730372Skarels 	(void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
133830372Skarels 	if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
133930372Skarels 		tp->t_state |= TS_CARR_ON;
134025881Ssam }
134125881Ssam 
134225881Ssam /*
134340738Skarels  * VCMINTR called when an unsolicited interrupt occurs signaling
134425881Ssam  * some change of modem control state.
134525881Ssam  */
134625881Ssam vcmintr(vx)
134725881Ssam 	register vx;
134825881Ssam {
134925881Ssam 	register struct vxdevice *kp;
135025881Ssam 	register struct tty *tp;
135125881Ssam 	register port;
135230372Skarels 	register struct vx_softc *vs;
135325881Ssam 
135440738Skarels 	vs = &vx_softc[vx];
135540738Skarels 	kp = vs->vs_addr;
135625881Ssam 	port = kp->v_usdata[0] & 017;
135725881Ssam 	tp = &vx_tty[vx*16+port];
135825881Ssam 
135929954Skarels 	if (kp->v_ustat & DCD_ON)
136029954Skarels 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
136129954Skarels 	else if ((kp->v_ustat & DCD_OFF) &&
136230372Skarels 	    ((vs->vs_softCAR & (1 << port))) == 0 &&
136329954Skarels 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
136429954Skarels 		register struct vcmds *cp;
136529954Skarels 		register struct vxcmd *cmdp;
136625881Ssam 
136730372Skarels 		/* clear all pending transmits */
136829954Skarels 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
136929954Skarels 		    vs->vs_vers == VXV_NEW) {
137029954Skarels 			int i, cmdfound = 0;
137125881Ssam 
137229954Skarels 			cp = &vs->vs_cmds;
137329954Skarels 			for (i = cp->v_empty; i != cp->v_fill; ) {
137429954Skarels 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
137529954Skarels 				if ((cmdp->cmd == VXC_XMITDTA ||
137629954Skarels 				    cmdp->cmd == VXC_XMITIMM) &&
137729954Skarels 				    ((struct vxmit *)cmdp->par)->line == port) {
137829954Skarels 					cmdfound++;
137925881Ssam 					cmdp->cmd = VXC_FDTATOX;
138025881Ssam 					cmdp->par[1] = port;
138125881Ssam 				}
138229954Skarels 				if (++i >= VC_CMDBUFL)
138329954Skarels 					i = 0;
138425881Ssam 			}
138529954Skarels 			if (cmdfound)
138629954Skarels 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
138729954Skarels 			/* cmd is already in vioc, have to flush it */
138829954Skarels 			else {
138929954Skarels 				cmdp = vobtain(vs);
139029954Skarels 				cmdp->cmd = VXC_FDTATOX;
139129954Skarels 				cmdp->par[1] = port;
139230372Skarels 				(void) vcmd(vx, (caddr_t)&cmdp->cmd);
139325881Ssam 			}
139425881Ssam 		}
139529954Skarels 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
139637608Smarc 		(*linesw[tp->t_line].l_rint)(TTY_FE, tp);
139725881Ssam 		return;
139825881Ssam 	}
139925881Ssam }
140025881Ssam #endif
1401