xref: /csrg-svn/sys/tahoe/vba/vx.c (revision 29954)
1 /*	vx.c	1.9	86/11/03	*/
2 
3 #include "vx.h"
4 #if NVX > 0
5 /*
6  * VIOC-X driver
7  */
8 #ifdef VXPERF
9 #define	DOSCOPE
10 #endif
11 
12 #include "../tahoe/pte.h"
13 
14 #include "param.h"
15 #include "ioctl.h"
16 #include "tty.h"
17 #include "dir.h"
18 #include "user.h"
19 #include "map.h"
20 #include "buf.h"
21 #include "conf.h"
22 #include "file.h"
23 #include "uio.h"
24 #include "proc.h"
25 #include "vm.h"
26 #include "kernel.h"
27 #include "syslog.h"
28 
29 #include "../tahoevba/vbavar.h"
30 #include "../tahoevba/vxreg.h"
31 #include "../tahoevba/scope.h"
32 
33 #ifdef VX_DEBUG
34 long	vxintr4 = 0;
35 #define	VXERR4	1
36 #define	VXNOBUF	2
37 long	vxdebug = 0;
38 #define	VXVCM	1
39 #define	VXVCC	2
40 #define	VXVCX	4
41 #include "../tahoesna/snadebug.h"
42 #endif
43 
44 /*
45  * Interrupt type bits passed to vinthandl().
46  */
47 #define	CMDquals 0		/* command completed interrupt */
48 #define	RSPquals 1		/* command response interrupt */
49 #define	UNSquals 2		/* unsolicited interrupt */
50 
51 struct	tty vx_tty[NVX*16];
52 #ifndef lint
53 int	nvx = NVX*16;
54 #endif
55 int	vxstart(), ttrstrt();
56 struct	vxcmd *vobtain(), *nextcmd();
57 
58 /*
59  * Driver information for auto-configuration stuff.
60  */
61 int	vxprobe(), vxattach(), vxrint();
62 struct	vba_device *vxinfo[NVX];
63 long	vxstd[] = { 0 };
64 struct	vba_driver vxdriver =
65     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
66 
67 struct	vx_softc {
68 	u_char	vs_type;	/* 0: viox-x/vioc-b, 1: vioc-bop */
69 	u_char	vs_bop;		/* bop board # for vioc-bop's */
70 	u_char	vs_loport;	/* low port nbr */
71 	u_char	vs_hiport;	/* high port nbr */
72 	u_short	vs_nbr;		/* viocx number */
73 	u_short	vs_maxcmd;	/* max number of concurrent cmds */
74 	u_short	vs_silosiz;	/* silo size */
75 	short	vs_vers;	/* vioc/pvioc version */
76 #define	VXV_OLD	0		/* PVIOCX | VIOCX */
77 #define	VXV_NEW	1		/* NPVIOCX | NVIOCX */
78 	short	vs_xmtcnt;	/* xmit commands pending */
79 	short	vs_brkreq;	/* send break requests pending */
80 	short	vs_active;	/* active port bit array or flag */
81 	short 	vs_state;	/* controller state */
82 #define	VXS_READY	0	/* ready for commands */
83 #define	VXS_RESET	1	/* in process of reseting */
84 	caddr_t vs_mricmd;	/* most recent issued cmd */
85 	u_int	vs_ivec;	/* interrupt vector base */
86 	struct	vxcmd *vs_avail;/* next available command buffer */
87 	struct	vxcmd *vs_build;
88 	struct	vxcmd vs_lst[NVCXBUFS];
89 	struct	vcmds vs_cmds;
90 } vx_softc[NVX];
91 
92 vxprobe(reg, vi)
93 	caddr_t reg;
94 	struct vba_device *vi;
95 {
96 	register int br, cvec;			/* must be r12, r11 */
97 	register struct vxdevice *vp = (struct vxdevice *)reg;
98 	register struct vx_softc *vs;
99 
100 #ifdef lint
101 	br = 0; cvec = br; br = cvec;
102 	vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
103 #endif
104 	if (badaddr((caddr_t)vp, 1))
105 		return (0);
106 	vp->v_fault = 0;
107 	vp->v_vioc = V_BSY;
108 	vp->v_hdwre = V_RESET;		/* reset interrupt */
109 	DELAY(4000000);
110 	if (vp->v_fault != VXF_READY)
111 		return (0);
112 	vs = &vx_softc[vi->ui_unit];
113 #ifdef notdef
114 	/*
115 	 * Align vioc interrupt vector base to 4 vector
116 	 * boundary and fitting in 8 bits (is this necessary,
117 	 * wish we had documentation).
118 	 */
119 	if ((vi->ui_hd->vh_lastiv -= 3) > 0xff)
120 		vi->ui_hd->vh_lastiv = 0xff;
121 	vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3;
122 #else
123 	vs->vs_ivec = 0x40+vi->ui_unit*4;
124 #endif
125 	br = 0x18, cvec = vs->vs_ivec;	/* XXX */
126 	return (sizeof (struct vxdevice));
127 }
128 
129 vxattach(vi)
130 	register struct vba_device *vi;
131 {
132 
133 	vxinit(vi->ui_unit, 1);
134 }
135 
136 /*
137  * Open a VX line.
138  */
139 /*ARGSUSED*/
140 vxopen(dev, flag)
141 	dev_t dev;
142 	int flag;
143 {
144 	register struct tty *tp;	/* pointer to tty struct for port */
145 	register struct vx_softc *vs;
146 	register struct vba_device *vi;
147 	int unit, vx, s, error;
148 
149 	unit = minor(dev);
150 	vx = unit >> 4;
151 	if (unit >= NVX*16 || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
152 		return (ENXIO);
153 	tp = &vx_tty[unit];
154 	if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
155 		return (EBUSY);
156 	vs = &vx_softc[vx];
157 #ifdef notdef
158 	if (unit < vs->vs_loport || vs->vs_hiport < unit)	/* ??? */
159 		return (ENXIO);
160 #endif
161 	tp->t_addr = (caddr_t)vs;
162 	tp->t_oproc = vxstart;
163 	tp->t_dev = dev;
164 	s = spl8();
165 	tp->t_state |= TS_WOPEN;
166 	if ((tp->t_state&TS_ISOPEN) == 0) {
167 		ttychars(tp);
168 		if (tp->t_ispeed == 0) {
169 			tp->t_ispeed = SSPEED;
170 			tp->t_ospeed = SSPEED;
171 			tp->t_flags |= ODDP|EVENP|ECHO;
172 		}
173 		vxparam(dev);
174 	}
175 	if (!vcmodem(dev, VMOD_ON))
176 		while ((tp->t_state&TS_CARR_ON) == 0)
177 			sleep((caddr_t)&tp->t_rawq, TTIPRI);
178 	error = (*linesw[tp->t_line].l_open)(dev,tp);
179 	splx(s);
180 	return (error);
181 }
182 
183 /*
184  * Close a VX line.
185  */
186 /*ARGSUSED*/
187 vxclose(dev, flag)
188 	dev_t dev;
189 	int flag;
190 {
191 	register struct tty *tp;
192 	int unit, s;
193 
194 	unit = minor(dev);
195 	tp = &vx_tty[unit];
196 	s = spl8();
197 	(*linesw[tp->t_line].l_close)(tp);
198 	if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0) {
199 		if (!vcmodem(dev, VMOD_OFF))
200 			tp->t_state &= ~TS_CARR_ON;
201 	}
202 	/* wait for the last response */
203 	while (tp->t_state&TS_FLUSH)
204 		sleep((caddr_t)&tp->t_state, TTOPRI);
205 	ttyclose(tp);
206 	splx(s);
207 }
208 
209 /*
210  * Read from a VX line.
211  */
212 vxread(dev, uio)
213 	dev_t dev;
214 	struct uio *uio;
215 {
216 	struct tty *tp = &vx_tty[minor(dev)];
217 
218 	return ((*linesw[tp->t_line].l_read)(tp, uio));
219 }
220 
221 /*
222  * write on a VX line
223  */
224 vxwrite(dev, uio)
225 	dev_t dev;
226 	struct uio *uio;
227 {
228 	register struct tty *tp = &vx_tty[minor(dev)];
229 
230 	return ((*linesw[tp->t_line].l_write)(tp, uio));
231 }
232 
233 /*
234  * VIOCX unsolicited interrupt.
235  */
236 vxrint(vx)
237 	register vx;
238 {
239 	register struct tty *tp, *tp0;
240 	register struct vxdevice *addr;
241 	register struct vx_softc *vs;
242 	struct vba_device *vi;
243 	register int nc, c;
244 	register struct silo {
245 		char	data, port;
246 	} *sp;
247 	short *osp;
248 	int overrun = 0;
249 
250 	vi = vxinfo[vx];
251 	if (vi == 0 || vi->ui_alive == 0)
252 		return;
253 	addr = (struct vxdevice *)vi->ui_addr;
254 	switch (addr->v_uqual&037) {
255 	case 0:
256 		break;
257 	case 2:
258 		printf("vx%d: vc proc err, ustat %x\n", addr->v_ustat);
259 		vxstreset(vx);
260 		return (0);
261 	case 3:
262 		vcmintr(vx);
263 		return (1);
264 	case 4:
265 		return (1);
266 	default:
267 		printf("vx%d: vc uqual err, uqual %x\n", addr->v_uqual);
268 		vxstreset(vx);
269 		return (0);
270 	}
271 	vs = &vx_softc[vx];
272 	if (vs->vs_vers == VXV_NEW)
273 		sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata);
274 	else
275 		sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
276 	nc = *(osp = (short *)sp);
277 	if (nc == 0)
278 		return (1);
279 	if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
280 		printf("vx%d: %d exceeds silo size\n", nc);
281 		nc = vs->vs_silosiz;
282 	}
283 	tp0 = &vx_tty[vx*16];
284 	sp = (struct silo *)(((short *)sp)+1);
285 	for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) {
286 		c = sp->port & 017;
287 		if (vs->vs_loport > c || c > vs->vs_hiport)
288 			continue;
289 		tp = tp0 + c;
290 		if( (tp->t_state&TS_ISOPEN) == 0) {
291 			wakeup((caddr_t)&tp->t_rawq);
292 			continue;
293 		}
294 		c = sp->data;
295 		if ((sp->port&VX_RO) == VX_RO && !overrun) {
296 			log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
297 			overrun = 1;
298 			continue;
299 		}
300 		if (sp->port&VX_PE)
301 			if ((tp->t_flags&(EVENP|ODDP)) == EVENP ||
302 			    (tp->t_flags&(EVENP|ODDP)) == ODDP)
303 				continue;
304 		if (sp->port&VX_FE) {
305 			/*
306 			 * At framing error (break) generate
307 			 * a null (in raw mode, for getty), or a
308 			 * interrupt (in cooked/cbreak mode).
309 			 */
310 			if (tp->t_flags&RAW)
311 				c = 0;
312 			else
313 				c = tp->t_intrc;
314 		}
315 		(*linesw[tp->t_line].l_rint)(c, tp);
316 	}
317 	*osp = 0;
318 	return (1);
319 }
320 
321 /*
322  * Ioctl for VX.
323  */
324 vxioctl(dev, cmd, data, flag)
325 	dev_t dev;
326 	caddr_t	data;
327 {
328 	register struct tty *tp;
329 	int error;
330 
331 	tp = &vx_tty[minor(dev)];
332 	error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
333 	if (error == 0)
334 		return (error);
335 	error = ttioctl(tp, cmd, data, flag);
336 	if (error >= 0) {
337 		if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS ||
338 		    cmd == TIOCLBIC || cmd == TIOCLSET)
339 			vxparam(dev);
340 		return (error);
341 	}
342 	return (ENOTTY);
343 }
344 
345 vxparam(dev)
346 	dev_t dev;
347 {
348 
349 	vxcparam(dev, 1);
350 }
351 
352 /*
353  * Set parameters from open or stty into the VX hardware
354  * registers.
355  */
356 vxcparam(dev, wait)
357 	dev_t dev;
358 	int wait;
359 {
360 	register struct tty *tp;
361 	register struct vx_softc *vs;
362 	register struct vxcmd *cp;
363 	int s, unit = minor(dev);
364 
365 	tp = &vx_tty[unit];
366 	vs = (struct vx_softc *)tp->t_addr;
367 	cp = vobtain(vs);
368 	s = spl8();
369 	/*
370 	 * Construct ``load parameters'' command block
371 	 * to setup baud rates, xon-xoff chars, parity,
372 	 * and stop bits for the specified port.
373 	 */
374 	cp->cmd = VXC_LPARAX;
375 	cp->par[1] = unit & 017;	/* port number */
376 	cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc;
377 	cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc;
378 	if (tp->t_flags & (RAW|LITOUT|PASS8)) {
379 		cp->par[4] = 0xc0;	/* 8 bits of data */
380 		cp->par[7] = 0;		/* no parity */
381 	} else {
382 		cp->par[4] = 0x40;	/* 7 bits of data */
383 		if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
384 			cp->par[7] = 1;		/* odd parity */
385 		else
386 			cp->par[7] = 3;		/* even parity */
387 	}
388 	cp->par[5] = 0x4;			/* 1 stop bit - XXX */
389 	cp->par[6] = tp->t_ospeed;
390 	if (vcmd(vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
391 		sleep((caddr_t)cp,TTIPRI);
392 	splx(s);
393 }
394 
395 /*
396  * VIOCX command response interrupt.
397  * For transmission, restart output to any active port.
398  * For all other commands, just clean up.
399  */
400 vxxint(vx, cp)
401 	register int vx;
402 	register struct vxcmd *cp;
403 {
404 	register struct vxmit *vp, *pvp;
405 	register struct tty *tp, *tp0;
406 	register struct vx_softc *vs;
407 	register struct tty *hp;
408 
409 	vs = &vx_softc[vx];
410 	cp = (struct vxcmd *)((long *)cp-1);
411 
412 	switch (cp->cmd&0xff00) {
413 
414 	case VXC_LIDENT:	/* initialization complete */
415 		if (vs->vs_state == VXS_RESET) {
416 			vxfnreset(vx, cp);
417 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
418 		}
419 		cp->cmd++;
420 		return;
421 
422 	case VXC_XMITDTA:
423 	case VXC_XMITIMM:
424 		break;
425 
426 	case VXC_LPARAX:
427 		wakeup((caddr_t)cp);
428 		/* fall thru... */
429 	default:	/* VXC_MDMCTL or VXC_FDTATOX */
430 		vrelease(vs, cp);
431 		if (vs->vs_state == VXS_RESET)
432 			vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
433 		return;
434 	}
435 	tp0 = &vx_tty[vx*16];
436 	vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
437 	for (; vp >= (struct vxmit *)cp->par; vp--) {
438 		tp = tp0 + (vp->line & 017);
439 		pvp = vp;
440 		tp->t_state &= ~TS_BUSY;
441 		if (tp->t_state & TS_FLUSH) {
442 			tp->t_state &= ~TS_FLUSH;
443 			wakeup((caddr_t)&tp->t_state);
444 		} else
445 		 	ndflush(&tp->t_outq, vp->bcount+1);
446 	}
447 	vs->vs_xmtcnt--;
448 	vrelease(vs, cp);
449 	if (vs->vs_vers == VXV_NEW) {
450 		vp = pvp;
451 		vs->vs_active |= 1 << ((vp->line & 017) - vs->vs_loport);
452 		if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) {
453 			vs->vs_xmtcnt++;
454 			vcmd(vx, (caddr_t)&cp->cmd);
455 			return;
456 		}
457 		vs->vs_active &= ~(1 << ((vp->line & 017) - vs->vs_loport));
458 	} else {
459 		vs->vs_active = -1;
460 		tp0 = &vx_tty[vx*16 + vs->vs_hiport];
461 		for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
462 			if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) {
463 				vs->vs_xmtcnt++;
464 				vcmd(vx, (caddr_t)&cp->cmd);
465 			}
466 		if ((cp = nextcmd(vs)) != NULL) {	/* command to send? */
467 			vs->vs_xmtcnt++;
468 			vcmd(vx, (caddr_t)&cp->cmd);
469 		}
470 		vs->vs_active = 0;
471 	}
472 }
473 
474 /*
475  * Force out partial XMIT command after timeout
476  */
477 vxforce(vs)
478 	register struct vx_softc *vs;
479 {
480 	register struct vxcmd *cp;
481 	int s;
482 
483 	s = spl8();
484 	if ((cp = nextcmd(vs)) != NULL) {
485 		vs->vs_xmtcnt++;
486 		vcmd(vs->vs_nbr, (caddr_t)&cp->cmd);
487 	}
488 	splx(s);
489 }
490 
491 /*
492  * Start (restart) transmission on the given VX line.
493  */
494 vxstart(tp)
495 	register struct tty *tp;
496 {
497 	register short n;
498 	register struct vx_softc *vs;
499 	register full;
500 	int s, port;
501 
502 	s = spl8();
503 	port = minor(tp->t_dev) & 017;
504 	vs = (struct vx_softc *)tp->t_addr;
505 	if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
506 		if (tp->t_outq.c_cc <= TTLOWAT(tp)) {
507 			if (tp->t_state&TS_ASLEEP) {
508 				tp->t_state &= ~TS_ASLEEP;
509 				wakeup((caddr_t)&tp->t_outq);
510 			}
511 			if (tp->t_wsel) {
512 				selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
513 				tp->t_wsel = 0;
514 				tp->t_state &= ~TS_WCOLL;
515 			}
516 		}
517 		if (tp->t_outq.c_cc == 0) {
518 			splx(s);
519 			return (0);
520 		}
521 		scope_out(3);
522 		if (tp->t_flags & (RAW|LITOUT))
523 			full = 0;
524 		else
525 			full = 0200;
526 		if ((n = ndqb(&tp->t_outq, full)) == 0) {
527 			if (full) {
528 				n = getc(&tp->t_outq);
529 				timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
530 				tp->t_state |= TS_TIMEOUT;
531 				full = 0;
532 			}
533 		} else {
534 			char *cp = (char *)tp->t_outq.c_cf;
535 
536 			tp->t_state |= TS_BUSY;
537 			full = vsetq(vs, port, cp, n);
538 			/*
539 			 * If the port is not currently active, try to
540 			 * send the data.  We send it immediately if the
541 			 * command buffer is full, or if we've nothing
542 			 * currently outstanding.  If we don't send it,
543 			 * set a timeout to force the data to be sent soon.
544 			 */
545 			if ((vs->vs_active & (1 << (port-vs->vs_loport))) == 0)
546 				if (full || vs->vs_xmtcnt == 0) {
547 					cp = (char *)&nextcmd(vs)->cmd;
548 					vs->vs_xmtcnt++;
549 					vcmd(vs->vs_nbr, cp);
550 				} else
551 					timeout(vxforce, (caddr_t)vs, 3);
552 		}
553 	}
554 	splx(s);
555 	return (full);	/* indicate if max commands or not */
556 }
557 
558 /*
559  * Stop output on a line.
560  */
561 vxstop(tp)
562 	register struct tty *tp;
563 {
564 	int s;
565 
566 	s = spl8();
567 	if (tp->t_state&TS_BUSY)
568 		if ((tp->t_state&TS_TTSTOP) == 0)
569 			tp->t_state |= TS_FLUSH;
570 	splx(s);
571 }
572 
573 static	int vxbbno = -1;
574 /*
575  * VIOCX Initialization.  Makes free lists of command buffers.
576  * Resets all viocx's.  Issues a LIDENT command to each
577  * viocx to establish interrupt vectors and logical port numbers.
578  */
579 vxinit(vx, wait)
580 	register int vx;
581 	int wait;
582 {
583 	register struct vx_softc *vs;
584 	register struct vxdevice *addr;
585 	register struct vxcmd *cp;
586 	register char *resp;
587 	register int j;
588 	char type;
589 
590 	vs = &vx_softc[vx];
591 	vs->vs_type = 0;		/* vioc-x by default */
592 	addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
593 	type = addr->v_ident;
594 	vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
595 	if (vs->vs_vers == VXV_NEW)
596 		vs->vs_silosiz = addr->v_maxsilo;
597 	switch (type) {
598 
599 	case VXT_VIOCX:
600 	case VXT_VIOCX|VXT_NEW:
601 		/* set dcd for printer ports */
602 		for (j = 0; j < 16;j++)
603 			if (addr->v_portyp[j] == 4)
604 				addr->v_dcd |= 1 << j;
605 		break;
606 
607 	case VXT_PVIOCX:
608 	case VXT_PVIOCX|VXT_NEW:
609 		break;
610 	case VXT_VIOCBOP:		/* VIOC-BOP */
611 		vs->vs_type = 1;
612 		vs->vs_bop = ++vxbbno;
613 		printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
614 
615 	default:
616 		printf("vx%d: unknown type %x\n", vx, type);
617 		return;
618 	}
619 	vs->vs_nbr = -1;
620 	vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
621 	/*
622 	 * Initialize all cmd buffers by linking them
623 	 * into a free list.
624 	 */
625 	for (j = 0; j < NVCXBUFS; j++) {
626 		cp = &vs->vs_lst[j];
627 		cp->c_fwd = &vs->vs_lst[j+1];
628 	}
629 	vs->vs_avail = &vs->vs_lst[0];	/* set idx to 1st free buf */
630 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
631 
632 	/*
633 	 * Establish the interrupt vectors and define the port numbers.
634 	 */
635 	cp = vobtain(vs);
636 	cp->cmd = VXC_LIDENT;
637 	cp->par[0] = vs->vs_ivec; 	/* ack vector */
638 	cp->par[1] = cp->par[0]+1;	/* cmd resp vector */
639 	cp->par[3] = cp->par[0]+2;	/* unsol intr vector */
640 	cp->par[4] = 15;		/* max ports, no longer used */
641 	cp->par[5] = 0;			/* set 1st port number */
642 	vcmd(vx, (caddr_t)&cp->cmd);
643 	if (!wait)
644 		return;
645 	for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
646 		;
647 	if (j >= 4000000)
648 		printf("vx%d: didn't respond to LIDENT\n", vx);
649 
650  	/* calculate address of response buffer */
651  	resp = (char *)addr + (addr->v_rspoff&0x3fff);
652 	if (resp[0] != 0 && (resp[0]&0177) != 3) {
653 		vrelease(vs, cp);	/* init failed */
654 		return;
655 	}
656 	vs->vs_loport = cp->par[5];
657 	vs->vs_hiport = cp->par[7];
658 	vrelease(vs, cp);
659 	vs->vs_nbr = vx;		/* assign board number */
660 }
661 
662 /*
663  * Obtain a command buffer
664  */
665 struct vxcmd *
666 vobtain(vs)
667 	register struct vx_softc *vs;
668 {
669 	register struct vxcmd *p;
670 	int s;
671 
672 	s = spl8();
673 	p = vs->vs_avail;
674 	if (p == (struct vxcmd *)0) {
675 #ifdef VX_DEBUG
676 		if (vxintr4&VXNOBUF)
677 			vxintr4 &= ~VXNOBUF;
678 #endif
679 		printf("vx%d: no buffers\n", vs - vx_softc);
680 		vxstreset(vs - vx_softc);
681 		splx(s);
682 		return (vobtain(vs));
683 	}
684 	vs->vs_avail = vs->vs_avail->c_fwd;
685 	splx(s);
686 	return ((struct vxcmd *)p);
687 }
688 
689 /*
690  * Release a command buffer
691  */
692 vrelease(vs, cp)
693 	register struct vx_softc *vs;
694 	register struct vxcmd *cp;
695 {
696 	int s;
697 
698 #ifdef VX_DEBUG
699 	if (vxintr4&VXNOBUF)
700 		return;
701 #endif
702 	s = spl8();
703 	cp->c_fwd = vs->vs_avail;
704 	vs->vs_avail = cp;
705 	splx(s);
706 }
707 
708 struct vxcmd *
709 nextcmd(vs)
710 	register struct vx_softc *vs;
711 {
712 	register struct vxcmd *cp;
713 	int s;
714 
715 	s = spl8();
716 	cp = vs->vs_build;
717 	vs->vs_build = (struct vxcmd *)0;
718 	splx(s);
719 	return (cp);
720 }
721 
722 /*
723  * Assemble transmits into a multiple command;
724  * up to 8 transmits to 8 lines can be assembled together.
725  */
726 vsetq(vs, line, addr, n)
727 	register struct vx_softc *vs;
728 	caddr_t	addr;
729 {
730 	register struct vxcmd *cp;
731 	register struct vxmit *mp;
732 
733 	/*
734 	 * Grab a new command buffer or append
735 	 * to the current one being built.
736 	 */
737 	cp = vs->vs_build;
738 	if (cp == (struct vxcmd *)0) {
739 		cp = vobtain(vs);
740 		vs->vs_build = cp;
741 		cp->cmd = VXC_XMITDTA;
742 	} else {
743 		if ((cp->cmd & 07) == 07) {
744 			printf("vx%d: setq overflow\n", vs-vx_softc);
745 			vxstreset(vs->vs_nbr);
746 			return (0);
747 		}
748 		cp->cmd++;
749 	}
750 	/*
751 	 * Select the next vxmit buffer and copy the
752 	 * characters into the buffer (if there's room
753 	 * and the device supports ``immediate mode'',
754 	 * or store an indirect pointer to the data.
755 	 */
756 	mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
757 	mp->bcount = n-1;
758 	mp->line = line;
759 	if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
760 		cp->cmd = VXC_XMITIMM;
761 		bcopy(addr, mp->ostream, n);
762 	} else {
763 		/* get system address of clist block */
764 		addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
765 		bcopy(&addr, mp->ostream, sizeof (addr));
766 	}
767 	return (vs->vs_vers == VXV_NEW ? 1 : (cp->cmd&07) == 7);
768 }
769 
770 /*
771  * Write a command out to the VIOC
772  */
773 vcmd(vx, cmdad)
774 	register int vx;
775 	register caddr_t cmdad;
776 {
777 	register struct vcmds *cp;
778 	register struct vx_softc *vs;
779 	int s;
780 
781 	s = spl8();
782 	vs = &vx_softc[vx];
783 	/*
784 	 * When the vioc is resetting, don't process
785 	 * anything other than VXC_LIDENT commands.
786 	 */
787 	if (vs->vs_state == VXS_RESET && cmdad != NULL) {
788 		struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
789 
790 		if (vcp->cmd != VXC_LIDENT) {
791 			vrelease(vs, vcp);
792 			return (0);
793 		}
794 	}
795 	cp = &vs->vs_cmds;
796 	if (cmdad != (caddr_t)0) {
797 		cp->cmdbuf[cp->v_fill] = cmdad;
798 		if (++cp->v_fill >= VC_CMDBUFL)
799 			cp->v_fill = 0;
800 		if (cp->v_fill == cp->v_empty) {
801 			printf("vx%d: cmd q overflow\n", vx);
802 			vxstreset(vx);
803 			splx(s);
804 			return (0);
805 		}
806 		cp->v_cmdsem++;
807 	}
808 	if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) {
809 		cp->v_cmdsem--;
810 		cp->v_curcnt++;
811 		vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR);
812 	}
813 	splx(s);
814 	return (1);
815 }
816 
817 /*
818  * VIOC acknowledge interrupt.  The VIOC has received the new
819  * command.  If no errors, the new command becomes one of 16 (max)
820  * current commands being executed.
821  */
822 vackint(vx)
823 	register vx;
824 {
825 	register struct vxdevice *vp;
826 	register struct vcmds *cp;
827 	struct vx_softc *vs;
828 	int s;
829 
830 	scope_out(5);
831 	vs = &vx_softc[vx];
832 	if (vs->vs_type)	/* Its a BOP */
833 		return;
834 	s = spl8();
835 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
836 	cp = &vs->vs_cmds;
837 	if (vp->v_vcid&V_ERR) {
838 		register char *resp;
839 		register i;
840 
841 		printf("vx%d INTR ERR type %x v_dcd %x\n", vx,
842 		    vp->v_vcid & 07, vp->v_dcd & 0xff);
843 		resp = (char *)vs->vs_mricmd;
844 		for (i = 0; i < 16; i++)
845 			printf("%x ", resp[i]&0xff);
846 		printf("\n");
847 		splx(s);
848 		vxstreset(vx);
849 		return;
850 	}
851 	if ((vp->v_hdwre&017) == CMDquals) {
852 #ifdef VX_DEBUG
853 		if (vxintr4 & VXERR4) {	/* causes VIOC INTR ERR 4 */
854 			struct vxcmd *cp1, *cp0;
855 
856 			cp0 = (struct vxcmd *)
857 			    ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
858 			if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
859 				cp1 = vobtain(vs);
860 				*cp1 = *cp0;
861 				vxintr4 &= ~VXERR4;
862 				(void) vcmd(vx, &cp1->cmd);
863 			}
864 		}
865 #endif
866 		cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty];
867 		if (++cp->v_empty >= VC_CMDBUFL)
868 			cp->v_empty = 0;
869 	}
870 	if (++cp->v_itrempt >= VC_IQLEN)
871 		cp->v_itrempt = 0;
872 	vintempt(vx);
873 	splx(s);
874 	(void) vcmd(vx, (caddr_t)0);	/* queue next cmd, if any */
875 }
876 
877 /*
878  * Command Response interrupt.  The Vioc has completed
879  * a command.  The command may now be returned to
880  * the appropriate device driver.
881  */
882 vcmdrsp(vx)
883 	register vx;
884 {
885 	register struct vxdevice *vp;
886 	register struct vcmds *cp;
887 	register caddr_t cmd;
888 	register struct vx_softc *vs;
889 	register char *resp;
890 	register k;
891 	register int s;
892 
893 	scope_out(6);
894 	vs = &vx_softc[vx];
895 	if (vs->vs_type) {	/* Its a BOP */
896 		printf("vx%d: vcmdrsp interrupt\n", vx);
897 		return;
898 	}
899 	s = spl8();
900 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
901 	cp = &vs->vs_cmds;
902 	resp = (char *)vp + (vp->v_rspoff&0x7fff);
903 	if (((k = resp[1])&V_UNBSY) == 0) {
904 		printf("vx%d: cmdresp debug\n", vx);
905 		splx(s);
906 		vxstreset(vx);
907 		return;
908 	}
909 	k &= VCMDLEN-1;
910 	cmd = cp->v_curcmd[k];
911 	cp->v_curcmd[k] = (caddr_t)0;
912 	cp->v_curcnt--;
913 	k = *((short *)&resp[4]);	/* cmd operation code */
914 	if ((k&0xff00) == VXC_LIDENT)	/* want hiport number */
915 		for (k = 0; k < VRESPLEN; k++)
916 			cmd[k] = resp[k+4];
917 	resp[1] = 0;
918 	vxxint(vx, (struct vxcmd *)cmd);
919 	if (vs->vs_state == VXS_READY)
920 		vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR);
921 	splx(s);
922 }
923 
924 /*
925  * Unsolicited interrupt.
926  */
927 vunsol(vx)
928 	register vx;
929 {
930 	register struct vxdevice *vp;
931 	struct vx_softc *vs;
932 	int s;
933 
934 	scope_out(1);
935 	vs = &vx_softc[vx];
936 	if (vs->vs_type) {	/* Its a BOP */
937 		printf("vx%d: vunsol from BOP\n", vx);
938 		return;
939 	}
940 	s = spl8();
941 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
942 	if (vp->v_uqual&V_UNBSY) {
943 		vxrint(vx);
944 		vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
945 #ifdef notdef
946 	} else {
947 		printf("vx%d: unsolicited interrupt error\n", vx);
948 		splx(s);
949 		vxstreset(vx);
950 #endif
951 	}
952 	splx(s);
953 }
954 
955 /*
956  * Enqueue an interrupt.
957  */
958 vinthandl(vx, item)
959 	register int vx;
960 	register item;
961 {
962 	register struct vcmds *cp;
963 	int empty;
964 
965 	cp = &vx_softc[vx].vs_cmds;
966 	empty = (cp->v_itrfill == cp->v_itrempt);
967 	cp->v_itrqueu[cp->v_itrfill] = item;
968 	if (++cp->v_itrfill >= VC_IQLEN)
969 		cp->v_itrfill = 0;
970 	if (cp->v_itrfill == cp->v_itrempt) {
971 		printf("vx%d: interrupt q overflow\n", vx);
972 		vxstreset(vx);
973 	} else if (empty)
974 		vintempt(vx);
975 }
976 
977 vintempt(vx)
978 	register int vx;
979 {
980 	register struct vcmds *cp;
981 	register struct vxdevice *vp;
982 	register short item;
983 	register short *intr;
984 
985 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
986 	if (vp->v_vioc&V_BSY)
987 		return;
988 	cp = &vx_softc[vx].vs_cmds;
989 	if (cp->v_itrempt == cp->v_itrfill)
990 		return;
991 	item = cp->v_itrqueu[cp->v_itrempt];
992 	intr = (short *)&vp->v_vioc;
993 	switch ((item >> 8)&03) {
994 
995 	case CMDquals: {		/* command */
996 		int phys;
997 
998 		if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
999 			break;
1000 		vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
1001 		phys = vtoph((struct proc *)0,
1002 		    (unsigned)cp->cmdbuf[cp->v_empty]);
1003 		vp->v_vcp[0] = ((short *)&phys)[0];
1004 		vp->v_vcp[1] = ((short *)&phys)[1];
1005 		vp->v_vcbsy = V_BSY;
1006 		*intr = item;
1007 		scope_out(4);
1008 		break;
1009 	}
1010 
1011 	case RSPquals:		/* command response */
1012 		*intr = item;
1013 		scope_out(7);
1014 		break;
1015 
1016 	case UNSquals:		/* unsolicited interrupt */
1017 		vp->v_uqual = 0;
1018 		*intr = item;
1019 		scope_out(2);
1020 		break;
1021 	}
1022 }
1023 
1024 /*
1025  * Start a reset on a vioc after error (hopefully)
1026  */
1027 vxstreset(vx)
1028 	register vx;
1029 {
1030 	register struct vx_softc *vs;
1031 	register struct vxdevice *vp;
1032 	register struct vxcmd *cp;
1033 	register int j;
1034 	extern int vxinreset();
1035 	int s;
1036 
1037 	s = spl8() ;
1038 	vs = &vx_softc[vx];
1039 	if (vs->vs_state == VXS_RESET) {	/* avoid recursion */
1040 		splx(s);
1041 		return;
1042 	}
1043 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1044 	/*
1045 	 * Zero out the vioc structures, mark the vioc as being
1046 	 * reset, reinitialize the free command list, reset the vioc
1047 	 * and start a timer to check on the progress of the reset.
1048 	 */
1049 	bzero((caddr_t)vs, (unsigned)sizeof (*vs));
1050 
1051 	/*
1052 	 * Setting VXS_RESET prevents others from issuing
1053 	 * commands while allowing currently queued commands to
1054 	 * be passed to the VIOC.
1055 	 */
1056 	vs->vs_state = VXS_RESET;
1057 	/* init all cmd buffers */
1058 	for (j = 0; j < NVCXBUFS; j++) {
1059 		cp = &vs->vs_lst[j];
1060 		cp->c_fwd = &vs->vs_lst[j+1];
1061 	}
1062 	vs->vs_avail = &vs->vs_lst[0];
1063 	cp->c_fwd = (struct vxcmd *)0;
1064 	printf("vx%d: reset...", vx);
1065 	vp->v_fault = 0;
1066 	vp->v_vioc = V_BSY;
1067 	vp->v_hdwre = V_RESET;		/* generate reset interrupt */
1068 	timeout(vxinreset, (caddr_t)vx, hz*5);
1069 	splx(s);
1070 }
1071 
1072 /* continue processing a reset on a vioc after an error (hopefully) */
1073 vxinreset(vx)
1074 	int vx;
1075 {
1076 	register struct vxdevice *vp;
1077 	int s = spl8();
1078 
1079 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1080 	/*
1081 	 * See if the vioc has reset.
1082 	 */
1083 	if (vp->v_fault != VXF_READY) {
1084 		printf("failed\n");
1085 		splx(s);
1086 		return;
1087 	}
1088 	/*
1089 	 * Send a LIDENT to the vioc and mess with carrier flags
1090 	 * on parallel printer ports.
1091 	 */
1092 	vxinit(vx, 0);
1093 	splx(s);
1094 }
1095 
1096 /*
1097  * Finish the reset on the vioc after an error (hopefully).
1098  *
1099  * Restore modem control, parameters and restart output.
1100  * Since the vioc can handle no more then 24 commands at a time
1101  * and we could generate as many as 48 commands, we must do this in
1102  * phases, issuing no more then 16 commands at a time.
1103  */
1104 vxfnreset(vx, cp)
1105 	register int vx;
1106 	register struct vxcmd *cp;
1107 {
1108 	register struct vx_softc *vs;
1109 	register struct vxdevice *vp ;
1110 	register struct tty *tp, *tp0;
1111 	register int i;
1112 #ifdef notdef
1113 	register int on;
1114 #endif
1115 	extern int vxrestart();
1116 	int s = spl8();
1117 
1118 	vs = &vx_softc[vx];
1119 	vs->vs_loport = cp->par[5];
1120 	vs->vs_hiport = cp->par[7];
1121 	vrelease(vs, cp);
1122 	vs->vs_nbr = vx;			/* assign VIOC-X board number */
1123 	vs->vs_state = VXS_READY;
1124 
1125 	vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1126 	vp->v_vcid = 0;
1127 
1128 	/*
1129 	 * Restore modem information and control.
1130 	 */
1131 	tp0 = &vx_tty[vx*16];
1132 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
1133 		tp = tp0 + i;
1134 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
1135 			tp->t_state &= ~TS_CARR_ON;
1136 			vcmodem(tp->t_dev, VMOD_ON);
1137 			if (tp->t_state&TS_CARR_ON)
1138 				(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1139 			else if (tp->t_state & TS_ISOPEN)
1140 				(void)(*linesw[tp->t_line].l_modem)(tp, 0);
1141 		}
1142 #ifdef notdef
1143 		/*
1144 		 * If carrier has changed while we were resetting,
1145 		 * take appropriate action.
1146 		 */
1147 		on = vp->v_dcd & 1<<i;
1148 		if (on && (tp->t_state&TS_CARR_ON) == 0)
1149 			(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1150 		else if (!on && tp->t_state&TS_CARR_ON)
1151 			(void)(*linesw[tp->t_line].l_modem)(tp, 0);
1152 #endif
1153 	}
1154 	vs->vs_state = VXS_RESET;
1155 	timeout(vxrestart, (caddr_t)vx, hz);
1156 	splx(s);
1157 }
1158 
1159 /*
1160  * Restore a particular aspect of the VIOC.
1161  */
1162 vxrestart(vx)
1163 	int vx;
1164 {
1165 	register struct tty *tp, *tp0;
1166 	register struct vx_softc *vs;
1167 	register int i, cnt;
1168 	int s = spl8();
1169 
1170 	cnt = vx >> 8;
1171 	vx &= 0xff;
1172 	vs = &vx_softc[vx];
1173 	vs->vs_state = VXS_READY;
1174 	tp0 = &vx_tty[vx*16];
1175 	for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
1176 		tp = tp0 + i;
1177 		if (cnt != 0) {
1178 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
1179 			if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
1180 				vxstart(tp);	/* restart pending output */
1181 		} else {
1182 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
1183 				vxcparam(tp->t_dev, 0);
1184 		}
1185 	}
1186 	if (cnt == 0) {
1187 		vs->vs_state = VXS_RESET;
1188 		timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
1189 	} else
1190 		printf("done\n");
1191 	splx(s);
1192 }
1193 
1194 vxreset(dev)
1195 	dev_t dev;
1196 {
1197 
1198 	vxstreset(minor(dev) >> 4);	/* completes asynchronously */
1199 }
1200 
1201 vxfreset(vx)
1202 	register int vx;
1203 {
1204 	struct vba_device *vi;
1205 
1206 	if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0)
1207 		return (ENODEV);
1208 	vx_softc[vx].vs_state = VXS_READY;
1209 	vxstreset(vx);
1210 	return (0);		/* completes asynchronously */
1211 }
1212 
1213 vcmodem(dev, flag)
1214 	dev_t dev;
1215 {
1216 	struct tty *tp;
1217 	register struct vxcmd *cp;
1218 	register struct vx_softc *vs;
1219 	register struct vxdevice *kp;
1220 	register port;
1221 	int unit;
1222 
1223 	unit = minor(dev);
1224 	tp = &vx_tty[unit];
1225 	vs = (struct vx_softc *)tp->t_addr;
1226 	cp = vobtain(vs);
1227 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
1228 
1229 	port = unit & 017;
1230 	/*
1231 	 * Issue MODEM command
1232 	 */
1233 	cp->cmd = VXC_MDMCTL;
1234 	cp->par[0] = (flag == VMOD_ON) ? V_ENAB : V_DISAB;
1235 	cp->par[1] = port;
1236 	vcmd(vs->vs_nbr, (caddr_t)&cp->cmd);
1237 	port -= vs->vs_loport;
1238 	if ((kp->v_dcd >> port) & 1) {
1239 		if (flag == VMOD_ON)
1240 			tp->t_state |= TS_CARR_ON;
1241 		return (1);
1242 	}
1243 	return (0);
1244 }
1245 
1246 /*
1247  * VCMINTR called when an unsolicited interrup occurs signaling
1248  * some change of modem control state.
1249  */
1250 vcmintr(vx)
1251 	register vx;
1252 {
1253 	register struct vxdevice *kp;
1254 	register struct tty *tp;
1255 	register port;
1256 
1257 	kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
1258 	port = kp->v_usdata[0] & 017;
1259 	tp = &vx_tty[vx*16+port];
1260 
1261 	if (kp->v_ustat & DCD_ON)
1262 		(void)(*linesw[tp->t_line].l_modem)(tp, 1);
1263 	else if ((kp->v_ustat & DCD_OFF) &&
1264 	    (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
1265 		register struct vx_softc *vs;
1266 		register struct vcmds *cp;
1267 		register struct vxcmd *cmdp;
1268 
1269 		/* clear all pending trnansmits */
1270 		vs = &vx_softc[vx];
1271 		if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
1272 		    vs->vs_vers == VXV_NEW) {
1273 			int i, cmdfound = 0;
1274 
1275 			cp = &vs->vs_cmds;
1276 			for (i = cp->v_empty; i != cp->v_fill; ) {
1277 				cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
1278 				if ((cmdp->cmd == VXC_XMITDTA ||
1279 				    cmdp->cmd == VXC_XMITIMM) &&
1280 				    ((struct vxmit *)cmdp->par)->line == port) {
1281 					cmdfound++;
1282 					cmdp->cmd = VXC_FDTATOX;
1283 					cmdp->par[1] = port;
1284 				}
1285 				if (++i >= VC_CMDBUFL)
1286 					i = 0;
1287 			}
1288 			if (cmdfound)
1289 				tp->t_state &= ~(TS_BUSY|TS_FLUSH);
1290 			/* cmd is already in vioc, have to flush it */
1291 			else {
1292 				cmdp = vobtain(vs);
1293 				cmdp->cmd = VXC_FDTATOX;
1294 				cmdp->par[1] = port;
1295 				vcmd(vx, (caddr_t)&cmdp->cmd);
1296 			}
1297 		}
1298 	} else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
1299 		(*linesw[tp->t_line].l_rint)(tp->t_intrc & 0377, tp);
1300 		return;
1301 	}
1302 }
1303 #endif
1304