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