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