1*30372Skarels /* vx.c 1.10 87/01/11 */ 224003Ssam 324003Ssam #include "vx.h" 424003Ssam #if NVX > 0 524003Ssam /* 625857Ssam * VIOC-X driver 724003Ssam */ 825877Ssam #ifdef VXPERF 925948Ssam #define DOSCOPE 1025877Ssam #endif 1125877Ssam 1225675Ssam #include "../tahoe/pte.h" 1324003Ssam 1425877Ssam #include "param.h" 1525877Ssam #include "ioctl.h" 1625877Ssam #include "tty.h" 1725877Ssam #include "dir.h" 1825877Ssam #include "user.h" 1925877Ssam #include "map.h" 2025877Ssam #include "buf.h" 2125877Ssam #include "conf.h" 2225877Ssam #include "file.h" 2325877Ssam #include "uio.h" 2425877Ssam #include "proc.h" 2525877Ssam #include "vm.h" 2625881Ssam #include "kernel.h" 2729954Skarels #include "syslog.h" 2825675Ssam 2925675Ssam #include "../tahoevba/vbavar.h" 3025881Ssam #include "../tahoevba/vxreg.h" 3125675Ssam #include "../tahoevba/scope.h" 3224003Ssam 3325881Ssam #ifdef VX_DEBUG 3425881Ssam long vxintr4 = 0; 3525948Ssam #define VXERR4 1 3625948Ssam #define VXNOBUF 2 3725881Ssam long vxdebug = 0; 3825948Ssam #define VXVCM 1 3925948Ssam #define VXVCC 2 4025948Ssam #define VXVCX 4 4125881Ssam #endif 4224003Ssam 4325881Ssam /* 4425881Ssam * Interrupt type bits passed to vinthandl(). 4525881Ssam */ 4625948Ssam #define CMDquals 0 /* command completed interrupt */ 4725948Ssam #define RSPquals 1 /* command response interrupt */ 4825948Ssam #define UNSquals 2 /* unsolicited interrupt */ 4924003Ssam 50*30372Skarels #define VXUNIT(n) ((n) >> 4) 51*30372Skarels #define VXPORT(n) ((n) & 0xf) 52*30372Skarels 5325881Ssam struct tty vx_tty[NVX*16]; 5429954Skarels #ifndef lint 5529954Skarels int nvx = NVX*16; 5629954Skarels #endif 5725881Ssam int vxstart(), ttrstrt(); 5825881Ssam struct vxcmd *vobtain(), *nextcmd(); 5924003Ssam 6024003Ssam /* 6124003Ssam * Driver information for auto-configuration stuff. 6224003Ssam */ 6324003Ssam int vxprobe(), vxattach(), vxrint(); 6425881Ssam struct vba_device *vxinfo[NVX]; 6524003Ssam long vxstd[] = { 0 }; 6624003Ssam struct vba_driver vxdriver = 6725857Ssam { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; 6824003Ssam 6925881Ssam struct vx_softc { 7025881Ssam u_char vs_type; /* 0: viox-x/vioc-b, 1: vioc-bop */ 7125881Ssam u_char vs_bop; /* bop board # for vioc-bop's */ 7225881Ssam u_char vs_loport; /* low port nbr */ 7325881Ssam u_char vs_hiport; /* high port nbr */ 7425881Ssam u_short vs_nbr; /* viocx number */ 7525881Ssam u_short vs_maxcmd; /* max number of concurrent cmds */ 7625881Ssam u_short vs_silosiz; /* silo size */ 7725881Ssam short vs_vers; /* vioc/pvioc version */ 7825948Ssam #define VXV_OLD 0 /* PVIOCX | VIOCX */ 7925948Ssam #define VXV_NEW 1 /* NPVIOCX | NVIOCX */ 8025881Ssam short vs_xmtcnt; /* xmit commands pending */ 8125881Ssam short vs_brkreq; /* send break requests pending */ 8225881Ssam short vs_state; /* controller state */ 8325948Ssam #define VXS_READY 0 /* ready for commands */ 8425948Ssam #define VXS_RESET 1 /* in process of reseting */ 85*30372Skarels u_short vs_softCAR; /* soft carrier */ 8625881Ssam caddr_t vs_mricmd; /* most recent issued cmd */ 8725881Ssam u_int vs_ivec; /* interrupt vector base */ 8825881Ssam struct vxcmd *vs_avail;/* next available command buffer */ 8925881Ssam struct vxcmd *vs_build; 9025881Ssam struct vxcmd vs_lst[NVCXBUFS]; 9125881Ssam struct vcmds vs_cmds; 9225881Ssam } vx_softc[NVX]; 9324003Ssam 9425857Ssam vxprobe(reg, vi) 9524003Ssam caddr_t reg; 9625857Ssam struct vba_device *vi; 9724003Ssam { 9825857Ssam register int br, cvec; /* must be r12, r11 */ 9925881Ssam register struct vxdevice *vp = (struct vxdevice *)reg; 10025881Ssam register struct vx_softc *vs; 10124003Ssam 10224003Ssam #ifdef lint 10324003Ssam br = 0; cvec = br; br = cvec; 10425675Ssam vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0); 10524003Ssam #endif 10625675Ssam if (badaddr((caddr_t)vp, 1)) 10725675Ssam return (0); 10825675Ssam vp->v_fault = 0; 10925675Ssam vp->v_vioc = V_BSY; 11025675Ssam vp->v_hdwre = V_RESET; /* reset interrupt */ 11124003Ssam DELAY(4000000); 11225881Ssam if (vp->v_fault != VXF_READY) 11325675Ssam return (0); 11425881Ssam vs = &vx_softc[vi->ui_unit]; 11525857Ssam #ifdef notdef 11625857Ssam /* 11725857Ssam * Align vioc interrupt vector base to 4 vector 11825857Ssam * boundary and fitting in 8 bits (is this necessary, 11925857Ssam * wish we had documentation). 12025857Ssam */ 12125857Ssam if ((vi->ui_hd->vh_lastiv -= 3) > 0xff) 12225857Ssam vi->ui_hd->vh_lastiv = 0xff; 12325881Ssam vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3; 12425857Ssam #else 12525881Ssam vs->vs_ivec = 0x40+vi->ui_unit*4; 12625857Ssam #endif 12725881Ssam br = 0x18, cvec = vs->vs_ivec; /* XXX */ 12825881Ssam return (sizeof (struct vxdevice)); 12924003Ssam } 13024003Ssam 13125857Ssam vxattach(vi) 13225857Ssam register struct vba_device *vi; 13324003Ssam { 13425675Ssam 135*30372Skarels vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags; 13629954Skarels vxinit(vi->ui_unit, 1); 13724003Ssam } 13824003Ssam 13924003Ssam /* 14024003Ssam * Open a VX line. 14124003Ssam */ 14225675Ssam /*ARGSUSED*/ 14324003Ssam vxopen(dev, flag) 14425881Ssam dev_t dev; 14525881Ssam int flag; 14624003Ssam { 14724003Ssam register struct tty *tp; /* pointer to tty struct for port */ 14825881Ssam register struct vx_softc *vs; 14925881Ssam register struct vba_device *vi; 15025881Ssam int unit, vx, s, error; 15124003Ssam 15225881Ssam unit = minor(dev); 153*30372Skarels vx = VXUNIT(unit); 154*30372Skarels if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0) 15525881Ssam return (ENXIO); 156*30372Skarels vs = &vx_softc[vx]; 15725881Ssam tp = &vx_tty[unit]; 158*30372Skarels unit = VXPORT(unit); 15925881Ssam if (tp->t_state&TS_XCLUDE && u.u_uid != 0) 16025881Ssam return (EBUSY); 161*30372Skarels if (unit < vs->vs_loport || unit > vs->vs_hiport) 16225881Ssam return (ENXIO); 16325881Ssam tp->t_addr = (caddr_t)vs; 16425881Ssam tp->t_oproc = vxstart; 16525881Ssam tp->t_dev = dev; 16625881Ssam s = spl8(); 16725881Ssam tp->t_state |= TS_WOPEN; 16825881Ssam if ((tp->t_state&TS_ISOPEN) == 0) { 16925881Ssam ttychars(tp); 17025881Ssam if (tp->t_ispeed == 0) { 17125881Ssam tp->t_ispeed = SSPEED; 17225881Ssam tp->t_ospeed = SSPEED; 17325881Ssam tp->t_flags |= ODDP|EVENP|ECHO; 17424003Ssam } 17525881Ssam vxparam(dev); 17624003Ssam } 177*30372Skarels vcmodem(dev, VMOD_ON); 178*30372Skarels while ((tp->t_state&TS_CARR_ON) == 0) 179*30372Skarels sleep((caddr_t)&tp->t_rawq, TTIPRI); 18025881Ssam error = (*linesw[tp->t_line].l_open)(dev,tp); 18125881Ssam splx(s); 18225881Ssam return (error); 18324003Ssam } 18424003Ssam 18524003Ssam /* 18624003Ssam * Close a VX line. 18724003Ssam */ 18825675Ssam /*ARGSUSED*/ 18924003Ssam vxclose(dev, flag) 19025881Ssam dev_t dev; 19125881Ssam int flag; 19224003Ssam { 19324003Ssam register struct tty *tp; 19425881Ssam int unit, s; 19524003Ssam 19625881Ssam unit = minor(dev); 19725881Ssam tp = &vx_tty[unit]; 19825881Ssam s = spl8(); 19924003Ssam (*linesw[tp->t_line].l_close)(tp); 200*30372Skarels if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0) 201*30372Skarels vcmodem(dev, VMOD_OFF); 20224003Ssam /* wait for the last response */ 20325881Ssam while (tp->t_state&TS_FLUSH) 20425881Ssam sleep((caddr_t)&tp->t_state, TTOPRI); 20525881Ssam ttyclose(tp); 20625881Ssam splx(s); 20724003Ssam } 20824003Ssam 20924003Ssam /* 21024003Ssam * Read from a VX line. 21124003Ssam */ 21224003Ssam vxread(dev, uio) 21324003Ssam dev_t dev; 21424003Ssam struct uio *uio; 21524003Ssam { 21625881Ssam struct tty *tp = &vx_tty[minor(dev)]; 21725881Ssam 21825881Ssam return ((*linesw[tp->t_line].l_read)(tp, uio)); 21924003Ssam } 22024003Ssam 22124003Ssam /* 22224003Ssam * write on a VX line 22324003Ssam */ 22424003Ssam vxwrite(dev, uio) 22524003Ssam dev_t dev; 22624003Ssam struct uio *uio; 22724003Ssam { 22825881Ssam register struct tty *tp = &vx_tty[minor(dev)]; 22925881Ssam 23025881Ssam return ((*linesw[tp->t_line].l_write)(tp, uio)); 23124003Ssam } 23224003Ssam 23324003Ssam /* 23424003Ssam * VIOCX unsolicited interrupt. 23524003Ssam */ 23625881Ssam vxrint(vx) 23725881Ssam register vx; 23824003Ssam { 23925881Ssam register struct tty *tp, *tp0; 24025881Ssam register struct vxdevice *addr; 24125881Ssam register struct vx_softc *vs; 24225881Ssam struct vba_device *vi; 24325881Ssam register int nc, c; 24425881Ssam register struct silo { 24525881Ssam char data, port; 24625881Ssam } *sp; 24725881Ssam short *osp; 24825881Ssam int overrun = 0; 24924003Ssam 25025881Ssam vi = vxinfo[vx]; 25125881Ssam if (vi == 0 || vi->ui_alive == 0) 25225881Ssam return; 25325881Ssam addr = (struct vxdevice *)vi->ui_addr; 25425881Ssam switch (addr->v_uqual&037) { 25524003Ssam case 0: 25624003Ssam break; 25724003Ssam case 2: 258*30372Skarels printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat); 25925881Ssam vxstreset(vx); 260*30372Skarels return; 26124003Ssam case 3: 26225881Ssam vcmintr(vx); 263*30372Skarels return; 26424003Ssam case 4: 265*30372Skarels return; 26624003Ssam default: 267*30372Skarels printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual); 26825881Ssam vxstreset(vx); 269*30372Skarels return; 27024003Ssam } 27125881Ssam vs = &vx_softc[vx]; 27225881Ssam if (vs->vs_vers == VXV_NEW) 27325881Ssam sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata); 27425881Ssam else 27525881Ssam sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6)); 27625881Ssam nc = *(osp = (short *)sp); 27725881Ssam if (nc == 0) 278*30372Skarels return; 27925881Ssam if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) { 28025881Ssam printf("vx%d: %d exceeds silo size\n", nc); 28125881Ssam nc = vs->vs_silosiz; 28224003Ssam } 28325881Ssam tp0 = &vx_tty[vx*16]; 28425881Ssam sp = (struct silo *)(((short *)sp)+1); 28525881Ssam for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) { 28625881Ssam c = sp->port & 017; 28725881Ssam if (vs->vs_loport > c || c > vs->vs_hiport) 28825881Ssam continue; 28925881Ssam tp = tp0 + c; 29025881Ssam if( (tp->t_state&TS_ISOPEN) == 0) { 29124003Ssam wakeup((caddr_t)&tp->t_rawq); 29224003Ssam continue; 29324003Ssam } 29425881Ssam c = sp->data; 29525881Ssam if ((sp->port&VX_RO) == VX_RO && !overrun) { 29629954Skarels log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit); 29725881Ssam overrun = 1; 29825881Ssam continue; 29925881Ssam } 30025881Ssam if (sp->port&VX_PE) 30125881Ssam if ((tp->t_flags&(EVENP|ODDP)) == EVENP || 30225881Ssam (tp->t_flags&(EVENP|ODDP)) == ODDP) 30324003Ssam continue; 304*30372Skarels if ((tp->t_flags & (RAW | PASS8)) == 0) 305*30372Skarels c &= 0177; 30625881Ssam if (sp->port&VX_FE) { 30725881Ssam /* 30825881Ssam * At framing error (break) generate 30925881Ssam * a null (in raw mode, for getty), or a 31025881Ssam * interrupt (in cooked/cbreak mode). 31125881Ssam */ 31225881Ssam if (tp->t_flags&RAW) 31325881Ssam c = 0; 31425881Ssam else 31525881Ssam c = tp->t_intrc; 31624003Ssam } 31724003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 31824003Ssam } 31925881Ssam *osp = 0; 32024003Ssam } 32124003Ssam 32224003Ssam /* 32325881Ssam * Ioctl for VX. 32424003Ssam */ 32524003Ssam vxioctl(dev, cmd, data, flag) 32625881Ssam dev_t dev; 32725881Ssam caddr_t data; 32824003Ssam { 32925881Ssam register struct tty *tp; 33025881Ssam int error; 33124003Ssam 33225881Ssam tp = &vx_tty[minor(dev)]; 33324003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 33424003Ssam if (error == 0) 33525881Ssam return (error); 33625881Ssam error = ttioctl(tp, cmd, data, flag); 33725881Ssam if (error >= 0) { 33829954Skarels if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS || 33929954Skarels cmd == TIOCLBIC || cmd == TIOCLSET) 34024003Ssam vxparam(dev); 34125881Ssam return (error); 34225881Ssam } 34325881Ssam return (ENOTTY); 34424003Ssam } 34524003Ssam 34624003Ssam vxparam(dev) 34725881Ssam dev_t dev; 34824003Ssam { 34925881Ssam 35024003Ssam vxcparam(dev, 1); 35124003Ssam } 35224003Ssam 35324003Ssam /* 35424003Ssam * Set parameters from open or stty into the VX hardware 35524003Ssam * registers. 35624003Ssam */ 35724003Ssam vxcparam(dev, wait) 35825881Ssam dev_t dev; 35925881Ssam int wait; 36024003Ssam { 36125881Ssam register struct tty *tp; 36225881Ssam register struct vx_softc *vs; 36325881Ssam register struct vxcmd *cp; 36425933Ssam int s, unit = minor(dev); 36524003Ssam 36625933Ssam tp = &vx_tty[unit]; 367*30372Skarels if ((tp->t_ispeed)==0) { 368*30372Skarels tp->t_state |= TS_HUPCLS; 369*30372Skarels vcmodem(dev, VMOD_OFF); 370*30372Skarels return; 371*30372Skarels } 37225881Ssam vs = (struct vx_softc *)tp->t_addr; 37325881Ssam cp = vobtain(vs); 37424003Ssam s = spl8(); 37525933Ssam /* 37625933Ssam * Construct ``load parameters'' command block 37725933Ssam * to setup baud rates, xon-xoff chars, parity, 37825933Ssam * and stop bits for the specified port. 37925933Ssam */ 38025933Ssam cp->cmd = VXC_LPARAX; 381*30372Skarels cp->par[1] = VXPORT(unit); 38225933Ssam cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc; 38325933Ssam cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc; 384*30372Skarels #ifdef notnow 38529954Skarels if (tp->t_flags & (RAW|LITOUT|PASS8)) { 386*30372Skarels #endif 387*30372Skarels cp->par[4] = BITS8; /* 8 bits of data */ 388*30372Skarels cp->par[7] = VNOPARITY; /* no parity */ 389*30372Skarels #ifdef notnow 39024003Ssam } else { 391*30372Skarels cp->par[4] = BITS7; /* 7 bits of data */ 39225881Ssam if ((tp->t_flags&(EVENP|ODDP)) == ODDP) 393*30372Skarels cp->par[7] = VODDP; /* odd parity */ 39429954Skarels else 395*30372Skarels cp->par[7] = VEVENP; /* even parity */ 39624003Ssam } 397*30372Skarels #endif 398*30372Skarels if (tp->t_ospeed == B110) 399*30372Skarels cp->par[5] = VSTOP2; /* 2 stop bits */ 400*30372Skarels else 401*30372Skarels cp->par[5] = VSTOP1; /* 1 stop bit */ 402*30372Skarels if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB) 403*30372Skarels cp->par[6] = V19200; 404*30372Skarels else 405*30372Skarels cp->par[6] = tp->t_ospeed; 406*30372Skarels if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait) 40725675Ssam sleep((caddr_t)cp,TTIPRI); 40824003Ssam splx(s); 40924003Ssam } 41024003Ssam 41124003Ssam /* 41224003Ssam * VIOCX command response interrupt. 41324003Ssam * For transmission, restart output to any active port. 41424003Ssam * For all other commands, just clean up. 41524003Ssam */ 41625881Ssam vxxint(vx, cp) 41725881Ssam register int vx; 41825881Ssam register struct vxcmd *cp; 41924003Ssam { 420*30372Skarels register struct vxmit *vp; 42125933Ssam register struct tty *tp, *tp0; 42225933Ssam register struct vx_softc *vs; 42324003Ssam 42425881Ssam vs = &vx_softc[vx]; 42525881Ssam cp = (struct vxcmd *)((long *)cp-1); 42629954Skarels 42725881Ssam switch (cp->cmd&0xff00) { 42825881Ssam 42925881Ssam case VXC_LIDENT: /* initialization complete */ 43025881Ssam if (vs->vs_state == VXS_RESET) { 43125881Ssam vxfnreset(vx, cp); 43225881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 43324003Ssam } 43424003Ssam cp->cmd++; 43524003Ssam return; 43625881Ssam 43725881Ssam case VXC_XMITDTA: 43825881Ssam case VXC_XMITIMM: 43924003Ssam break; 44025881Ssam 44125881Ssam case VXC_LPARAX: 44225675Ssam wakeup((caddr_t)cp); 44325881Ssam /* fall thru... */ 44425881Ssam default: /* VXC_MDMCTL or VXC_FDTATOX */ 44525881Ssam vrelease(vs, cp); 44625881Ssam if (vs->vs_state == VXS_RESET) 44725881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 44824003Ssam return; 44924003Ssam } 45025881Ssam tp0 = &vx_tty[vx*16]; 45125881Ssam vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 45225881Ssam for (; vp >= (struct vxmit *)cp->par; vp--) { 45325881Ssam tp = tp0 + (vp->line & 017); 45424003Ssam tp->t_state &= ~TS_BUSY; 45525881Ssam if (tp->t_state & TS_FLUSH) { 45624003Ssam tp->t_state &= ~TS_FLUSH; 45725881Ssam wakeup((caddr_t)&tp->t_state); 45825881Ssam } else 45924003Ssam ndflush(&tp->t_outq, vp->bcount+1); 46024003Ssam } 46125881Ssam vrelease(vs, cp); 462*30372Skarels if (vs->vs_vers == VXV_NEW) 463*30372Skarels vxstart(tp); 464*30372Skarels else { 46525881Ssam tp0 = &vx_tty[vx*16 + vs->vs_hiport]; 46625881Ssam for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++) 467*30372Skarels vxstart(tp); 46825881Ssam if ((cp = nextcmd(vs)) != NULL) { /* command to send? */ 46925881Ssam vs->vs_xmtcnt++; 470*30372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 47124003Ssam } 47224003Ssam } 473*30372Skarels vs->vs_xmtcnt--; 47424003Ssam } 47524003Ssam 47624003Ssam /* 47724003Ssam * Force out partial XMIT command after timeout 47824003Ssam */ 47925881Ssam vxforce(vs) 48025881Ssam register struct vx_softc *vs; 48124003Ssam { 48225881Ssam register struct vxcmd *cp; 48325881Ssam int s; 48424003Ssam 48524003Ssam s = spl8(); 48625881Ssam if ((cp = nextcmd(vs)) != NULL) { 48725881Ssam vs->vs_xmtcnt++; 488*30372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 48924003Ssam } 49024003Ssam splx(s); 49124003Ssam } 49224003Ssam 49324003Ssam /* 49424003Ssam * Start (restart) transmission on the given VX line. 49524003Ssam */ 49624003Ssam vxstart(tp) 49725881Ssam register struct tty *tp; 49824003Ssam { 49925675Ssam register short n; 50025933Ssam register struct vx_softc *vs; 50125933Ssam int s, port; 50224003Ssam 50324003Ssam s = spl8(); 50424003Ssam port = minor(tp->t_dev) & 017; 50525881Ssam vs = (struct vx_softc *)tp->t_addr; 50625881Ssam if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) { 50725881Ssam if (tp->t_outq.c_cc <= TTLOWAT(tp)) { 50824003Ssam if (tp->t_state&TS_ASLEEP) { 50924003Ssam tp->t_state &= ~TS_ASLEEP; 51024003Ssam wakeup((caddr_t)&tp->t_outq); 51124003Ssam } 51224003Ssam if (tp->t_wsel) { 51324003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 51424003Ssam tp->t_wsel = 0; 51524003Ssam tp->t_state &= ~TS_WCOLL; 51624003Ssam } 51724003Ssam } 51825881Ssam if (tp->t_outq.c_cc == 0) { 51924003Ssam splx(s); 520*30372Skarels return; 52124003Ssam } 52225877Ssam scope_out(3); 52329954Skarels if (tp->t_flags & (RAW|LITOUT)) 524*30372Skarels n = ndqb(&tp->t_outq, 0); 525*30372Skarels else { 526*30372Skarels n = ndqb(&tp->t_outq, 0200); 527*30372Skarels if (n == 0) { 52825675Ssam n = getc(&tp->t_outq); 52925881Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 53024003Ssam tp->t_state |= TS_TIMEOUT; 531*30372Skarels n = 0; 53224003Ssam } 533*30372Skarels } 534*30372Skarels if (n) { 53524003Ssam tp->t_state |= TS_BUSY; 536*30372Skarels vsetq(vs, port, (char *)tp->t_outq.c_cf, n); 53724003Ssam } 53824003Ssam } 53924003Ssam splx(s); 54024003Ssam } 54124003Ssam 54224003Ssam /* 54324003Ssam * Stop output on a line. 54424003Ssam */ 54524003Ssam vxstop(tp) 54625881Ssam register struct tty *tp; 54724003Ssam { 54825881Ssam int s; 54924003Ssam 55024003Ssam s = spl8(); 55125881Ssam if (tp->t_state&TS_BUSY) 55225881Ssam if ((tp->t_state&TS_TTSTOP) == 0) 55324003Ssam tp->t_state |= TS_FLUSH; 55424003Ssam splx(s); 55524003Ssam } 55624003Ssam 55725881Ssam static int vxbbno = -1; 55824003Ssam /* 55924003Ssam * VIOCX Initialization. Makes free lists of command buffers. 56024003Ssam * Resets all viocx's. Issues a LIDENT command to each 56125933Ssam * viocx to establish interrupt vectors and logical port numbers. 56224003Ssam */ 56325881Ssam vxinit(vx, wait) 56425881Ssam register int vx; 56525881Ssam int wait; 56624003Ssam { 56725933Ssam register struct vx_softc *vs; 56825933Ssam register struct vxdevice *addr; 56925933Ssam register struct vxcmd *cp; 57025881Ssam register char *resp; 57125881Ssam register int j; 572*30372Skarels char type, *typestring; 57324003Ssam 57425881Ssam vs = &vx_softc[vx]; 57525933Ssam vs->vs_type = 0; /* vioc-x by default */ 57625933Ssam addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 57725881Ssam type = addr->v_ident; 57825881Ssam vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD; 57925881Ssam if (vs->vs_vers == VXV_NEW) 58025881Ssam vs->vs_silosiz = addr->v_maxsilo; 58125881Ssam switch (type) { 58224003Ssam 58325881Ssam case VXT_VIOCX: 58425881Ssam case VXT_VIOCX|VXT_NEW: 585*30372Skarels typestring = "VIOC-X"; 586*30372Skarels /* set soft carrier for printer ports */ 587*30372Skarels for (j = 0; j < 16; j++) 588*30372Skarels if (addr->v_portyp[j] == VXT_PARALLEL) { 589*30372Skarels vs->vs_softCAR |= 1 << j; 59025881Ssam addr->v_dcd |= 1 << j; 591*30372Skarels } 59225881Ssam break; 59324003Ssam 59425881Ssam case VXT_PVIOCX: 59525881Ssam case VXT_PVIOCX|VXT_NEW: 596*30372Skarels typestring = "VIOC-X (old connector panel)"; 59725881Ssam break; 59825881Ssam case VXT_VIOCBOP: /* VIOC-BOP */ 59925881Ssam vs->vs_type = 1; 60025881Ssam vs->vs_bop = ++vxbbno; 60125881Ssam printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr); 60224003Ssam 60325933Ssam default: 60425881Ssam printf("vx%d: unknown type %x\n", vx, type); 605*30372Skarels vxinfo[vx]->ui_alive = 0; 60625881Ssam return; 60724003Ssam } 60825881Ssam vs->vs_nbr = -1; 60925933Ssam vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4; 61025933Ssam /* 61125933Ssam * Initialize all cmd buffers by linking them 61225933Ssam * into a free list. 61325933Ssam */ 61425881Ssam for (j = 0; j < NVCXBUFS; j++) { 61525933Ssam cp = &vs->vs_lst[j]; 61625933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 61725881Ssam } 61825881Ssam vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ 61924003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 62024003Ssam 62125933Ssam /* 62225933Ssam * Establish the interrupt vectors and define the port numbers. 62325933Ssam */ 62425933Ssam cp = vobtain(vs); 62525933Ssam cp->cmd = VXC_LIDENT; 62625881Ssam cp->par[0] = vs->vs_ivec; /* ack vector */ 62725857Ssam cp->par[1] = cp->par[0]+1; /* cmd resp vector */ 62825857Ssam cp->par[3] = cp->par[0]+2; /* unsol intr vector */ 62925881Ssam cp->par[4] = 15; /* max ports, no longer used */ 63025881Ssam cp->par[5] = 0; /* set 1st port number */ 631*30372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 63225881Ssam if (!wait) 63325881Ssam return; 63425881Ssam for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++) 63525857Ssam ; 63625857Ssam if (j >= 4000000) 63725881Ssam printf("vx%d: didn't respond to LIDENT\n", vx); 63824003Ssam 63924003Ssam /* calculate address of response buffer */ 64025881Ssam resp = (char *)addr + (addr->v_rspoff&0x3fff); 64125933Ssam if (resp[0] != 0 && (resp[0]&0177) != 3) { 64225933Ssam vrelease(vs, cp); /* init failed */ 64325881Ssam return; 64424003Ssam } 64525881Ssam vs->vs_loport = cp->par[5]; 64625881Ssam vs->vs_hiport = cp->par[7]; 647*30372Skarels printf("vx%d: %s%s, ports %d-%d\n", vx, 648*30372Skarels (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring, 649*30372Skarels vs->vs_loport, vs->vs_hiport); 65025881Ssam vrelease(vs, cp); 65125933Ssam vs->vs_nbr = vx; /* assign board number */ 65224003Ssam } 65324003Ssam 65424003Ssam /* 65524003Ssam * Obtain a command buffer 65624003Ssam */ 65725881Ssam struct vxcmd * 65825881Ssam vobtain(vs) 65925933Ssam register struct vx_softc *vs; 66024003Ssam { 66125933Ssam register struct vxcmd *p; 66225881Ssam int s; 66324003Ssam 66424003Ssam s = spl8(); 66525881Ssam p = vs->vs_avail; 66625881Ssam if (p == (struct vxcmd *)0) { 66724003Ssam #ifdef VX_DEBUG 66825881Ssam if (vxintr4&VXNOBUF) 66925881Ssam vxintr4 &= ~VXNOBUF; 67024003Ssam #endif 67125881Ssam printf("vx%d: no buffers\n", vs - vx_softc); 67225881Ssam vxstreset(vs - vx_softc); 67324003Ssam splx(s); 67425881Ssam return (vobtain(vs)); 67524003Ssam } 676*30372Skarels vs->vs_avail = p->c_fwd; 67724003Ssam splx(s); 67825881Ssam return ((struct vxcmd *)p); 67924003Ssam } 68024003Ssam 68124003Ssam /* 68224003Ssam * Release a command buffer 68324003Ssam */ 68425881Ssam vrelease(vs, cp) 68525933Ssam register struct vx_softc *vs; 68625933Ssam register struct vxcmd *cp; 68724003Ssam { 68825881Ssam int s; 68924003Ssam 69024003Ssam #ifdef VX_DEBUG 69125881Ssam if (vxintr4&VXNOBUF) 69225881Ssam return; 69324003Ssam #endif 69424003Ssam s = spl8(); 69525881Ssam cp->c_fwd = vs->vs_avail; 69625881Ssam vs->vs_avail = cp; 69724003Ssam splx(s); 69824003Ssam } 69924003Ssam 70025881Ssam struct vxcmd * 70125881Ssam nextcmd(vs) 70225933Ssam register struct vx_softc *vs; 70324003Ssam { 70425933Ssam register struct vxcmd *cp; 70525881Ssam int s; 70624003Ssam 70724003Ssam s = spl8(); 70825881Ssam cp = vs->vs_build; 70925881Ssam vs->vs_build = (struct vxcmd *)0; 71024003Ssam splx(s); 71125881Ssam return (cp); 71224003Ssam } 71324003Ssam 71424003Ssam /* 71525933Ssam * Assemble transmits into a multiple command; 716*30372Skarels * up to 8 transmits to 8 lines can be assembled together 717*30372Skarels * (on PVIOCX only). 71824003Ssam */ 71925933Ssam vsetq(vs, line, addr, n) 72025933Ssam register struct vx_softc *vs; 72125881Ssam caddr_t addr; 72224003Ssam { 72325933Ssam register struct vxcmd *cp; 72425933Ssam register struct vxmit *mp; 72524003Ssam 72625933Ssam /* 72725933Ssam * Grab a new command buffer or append 72825933Ssam * to the current one being built. 72925933Ssam */ 73025881Ssam cp = vs->vs_build; 73125881Ssam if (cp == (struct vxcmd *)0) { 73225881Ssam cp = vobtain(vs); 73325881Ssam vs->vs_build = cp; 73425881Ssam cp->cmd = VXC_XMITDTA; 73524003Ssam } else { 736*30372Skarels if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) { 73725881Ssam printf("vx%d: setq overflow\n", vs-vx_softc); 738*30372Skarels vxstreset((int)vs->vs_nbr); 739*30372Skarels return; 74024003Ssam } 74124003Ssam cp->cmd++; 74224003Ssam } 74325933Ssam /* 74425933Ssam * Select the next vxmit buffer and copy the 74525933Ssam * characters into the buffer (if there's room 74625933Ssam * and the device supports ``immediate mode'', 74725933Ssam * or store an indirect pointer to the data. 74825933Ssam */ 74925881Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 75025675Ssam mp->bcount = n-1; 75125933Ssam mp->line = line; 75225933Ssam if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) { 75325881Ssam cp->cmd = VXC_XMITIMM; 754*30372Skarels bcopy(addr, mp->ostream, (unsigned)n); 75524003Ssam } else { 75625933Ssam /* get system address of clist block */ 75725675Ssam addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr); 758*30372Skarels bcopy((caddr_t)&addr, mp->ostream, sizeof (addr)); 75924003Ssam } 760*30372Skarels /* 761*30372Skarels * We send the data immediately if a VIOCX, 762*30372Skarels * the command buffer is full, or if we've nothing 763*30372Skarels * currently outstanding. If we don't send it, 764*30372Skarels * set a timeout to force the data to be sent soon. 765*30372Skarels */ 766*30372Skarels if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 || 767*30372Skarels vs->vs_xmtcnt == 0) { 768*30372Skarels vs->vs_xmtcnt++; 769*30372Skarels (void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd); 770*30372Skarels vs->vs_build = 0; 771*30372Skarels } else 772*30372Skarels timeout(vxforce, (caddr_t)vs, 3); 77324003Ssam } 77425881Ssam 77525881Ssam /* 77625881Ssam * Write a command out to the VIOC 77725881Ssam */ 77825881Ssam vcmd(vx, cmdad) 77925881Ssam register int vx; 78025881Ssam register caddr_t cmdad; 78125881Ssam { 78225933Ssam register struct vcmds *cp; 78325881Ssam register struct vx_softc *vs; 78425881Ssam int s; 78525881Ssam 78625881Ssam s = spl8(); 78725881Ssam vs = &vx_softc[vx]; 78825933Ssam /* 78925933Ssam * When the vioc is resetting, don't process 79025933Ssam * anything other than VXC_LIDENT commands. 79125933Ssam */ 79225881Ssam if (vs->vs_state == VXS_RESET && cmdad != NULL) { 79325933Ssam struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd)); 79425881Ssam 79525933Ssam if (vcp->cmd != VXC_LIDENT) { 79625933Ssam vrelease(vs, vcp); 79725881Ssam return (0); 79825881Ssam } 79925881Ssam } 80025881Ssam cp = &vs->vs_cmds; 80125881Ssam if (cmdad != (caddr_t)0) { 80225881Ssam cp->cmdbuf[cp->v_fill] = cmdad; 80325881Ssam if (++cp->v_fill >= VC_CMDBUFL) 80425881Ssam cp->v_fill = 0; 80525881Ssam if (cp->v_fill == cp->v_empty) { 80625881Ssam printf("vx%d: cmd q overflow\n", vx); 80725881Ssam vxstreset(vx); 80825881Ssam splx(s); 80925881Ssam return (0); 81025881Ssam } 81125881Ssam cp->v_cmdsem++; 81225881Ssam } 81325881Ssam if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) { 81425881Ssam cp->v_cmdsem--; 81525881Ssam cp->v_curcnt++; 81625881Ssam vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR); 81725881Ssam } 81825881Ssam splx(s); 81925881Ssam return (1); 82025881Ssam } 82125881Ssam 82225881Ssam /* 82325881Ssam * VIOC acknowledge interrupt. The VIOC has received the new 82425881Ssam * command. If no errors, the new command becomes one of 16 (max) 82525881Ssam * current commands being executed. 82625881Ssam */ 82725881Ssam vackint(vx) 82825881Ssam register vx; 82925881Ssam { 83025933Ssam register struct vxdevice *vp; 83125933Ssam register struct vcmds *cp; 83225881Ssam struct vx_softc *vs; 83325881Ssam int s; 83425881Ssam 83525881Ssam scope_out(5); 83625881Ssam vs = &vx_softc[vx]; 83729954Skarels if (vs->vs_type) /* Its a BOP */ 83825881Ssam return; 83925881Ssam s = spl8(); 84025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 84125881Ssam cp = &vs->vs_cmds; 84225933Ssam if (vp->v_vcid&V_ERR) { 84325881Ssam register char *resp; 84425881Ssam register i; 84525933Ssam 846*30372Skarels printf("vx%d: ackint error type %x v_dcd %x\n", vx, 84725881Ssam vp->v_vcid & 07, vp->v_dcd & 0xff); 84825881Ssam resp = (char *)vs->vs_mricmd; 84925881Ssam for (i = 0; i < 16; i++) 85025881Ssam printf("%x ", resp[i]&0xff); 85125881Ssam printf("\n"); 85225881Ssam splx(s); 85325881Ssam vxstreset(vx); 85425881Ssam return; 85525881Ssam } 85625881Ssam if ((vp->v_hdwre&017) == CMDquals) { 85725881Ssam #ifdef VX_DEBUG 85825881Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ 85925933Ssam struct vxcmd *cp1, *cp0; 86025881Ssam 86125933Ssam cp0 = (struct vxcmd *) 86225933Ssam ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd)); 86325881Ssam if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) { 86425881Ssam cp1 = vobtain(vs); 86525881Ssam *cp1 = *cp0; 86625881Ssam vxintr4 &= ~VXERR4; 86725881Ssam (void) vcmd(vx, &cp1->cmd); 86825881Ssam } 86925881Ssam } 87025881Ssam #endif 87125881Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty]; 87225881Ssam if (++cp->v_empty >= VC_CMDBUFL) 87325881Ssam cp->v_empty = 0; 87425881Ssam } 87525881Ssam if (++cp->v_itrempt >= VC_IQLEN) 87625881Ssam cp->v_itrempt = 0; 87725881Ssam vintempt(vx); 87825881Ssam splx(s); 87925881Ssam (void) vcmd(vx, (caddr_t)0); /* queue next cmd, if any */ 88025881Ssam } 88125881Ssam 88225881Ssam /* 88325881Ssam * Command Response interrupt. The Vioc has completed 88425881Ssam * a command. The command may now be returned to 88525881Ssam * the appropriate device driver. 88625881Ssam */ 88725881Ssam vcmdrsp(vx) 88825881Ssam register vx; 88925881Ssam { 89025933Ssam register struct vxdevice *vp; 89125933Ssam register struct vcmds *cp; 89225881Ssam register caddr_t cmd; 89325881Ssam register struct vx_softc *vs; 89425881Ssam register char *resp; 89525881Ssam register k; 89625881Ssam register int s; 89725881Ssam 89825881Ssam scope_out(6); 89925881Ssam vs = &vx_softc[vx]; 90025881Ssam if (vs->vs_type) { /* Its a BOP */ 90125881Ssam printf("vx%d: vcmdrsp interrupt\n", vx); 90225881Ssam return; 90325881Ssam } 90425881Ssam s = spl8(); 90525881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 90625881Ssam cp = &vs->vs_cmds; 90725881Ssam resp = (char *)vp + (vp->v_rspoff&0x7fff); 90825881Ssam if (((k = resp[1])&V_UNBSY) == 0) { 90925881Ssam printf("vx%d: cmdresp debug\n", vx); 91025881Ssam splx(s); 91125881Ssam vxstreset(vx); 91225881Ssam return; 91325881Ssam } 91425881Ssam k &= VCMDLEN-1; 91525881Ssam cmd = cp->v_curcmd[k]; 91625881Ssam cp->v_curcmd[k] = (caddr_t)0; 91725881Ssam cp->v_curcnt--; 91825881Ssam k = *((short *)&resp[4]); /* cmd operation code */ 91925881Ssam if ((k&0xff00) == VXC_LIDENT) /* want hiport number */ 92025881Ssam for (k = 0; k < VRESPLEN; k++) 92125881Ssam cmd[k] = resp[k+4]; 92225881Ssam resp[1] = 0; 92325881Ssam vxxint(vx, (struct vxcmd *)cmd); 92425881Ssam if (vs->vs_state == VXS_READY) 92525881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 92625881Ssam splx(s); 92725881Ssam } 92825881Ssam 92925881Ssam /* 93025881Ssam * Unsolicited interrupt. 93125881Ssam */ 93225881Ssam vunsol(vx) 93325881Ssam register vx; 93425881Ssam { 93525933Ssam register struct vxdevice *vp; 93625881Ssam struct vx_softc *vs; 93725881Ssam int s; 93825881Ssam 93925881Ssam scope_out(1); 94025881Ssam vs = &vx_softc[vx]; 94125881Ssam if (vs->vs_type) { /* Its a BOP */ 94225881Ssam printf("vx%d: vunsol from BOP\n", vx); 94325881Ssam return; 94425881Ssam } 94525881Ssam s = spl8(); 94625881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 94725881Ssam if (vp->v_uqual&V_UNBSY) { 94825881Ssam vxrint(vx); 94925881Ssam vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR); 95025881Ssam #ifdef notdef 95125881Ssam } else { 95225881Ssam printf("vx%d: unsolicited interrupt error\n", vx); 95325881Ssam splx(s); 95425881Ssam vxstreset(vx); 95525881Ssam #endif 95625881Ssam } 95725881Ssam splx(s); 95825881Ssam } 95925881Ssam 96025881Ssam /* 96125933Ssam * Enqueue an interrupt. 96225881Ssam */ 96325881Ssam vinthandl(vx, item) 96425881Ssam register int vx; 96525881Ssam register item; 96625881Ssam { 96725881Ssam register struct vcmds *cp; 96825881Ssam int empty; 96925881Ssam 97025881Ssam cp = &vx_softc[vx].vs_cmds; 97125933Ssam empty = (cp->v_itrfill == cp->v_itrempt); 97225881Ssam cp->v_itrqueu[cp->v_itrfill] = item; 97325881Ssam if (++cp->v_itrfill >= VC_IQLEN) 97425881Ssam cp->v_itrfill = 0; 97525881Ssam if (cp->v_itrfill == cp->v_itrempt) { 97625881Ssam printf("vx%d: interrupt q overflow\n", vx); 97725881Ssam vxstreset(vx); 97825881Ssam } else if (empty) 97925881Ssam vintempt(vx); 98025881Ssam } 98125881Ssam 98225881Ssam vintempt(vx) 98325881Ssam register int vx; 98425881Ssam { 98525881Ssam register struct vcmds *cp; 98625881Ssam register struct vxdevice *vp; 98725881Ssam register short item; 98825881Ssam register short *intr; 98925881Ssam 99025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 99125881Ssam if (vp->v_vioc&V_BSY) 99225881Ssam return; 99325881Ssam cp = &vx_softc[vx].vs_cmds; 99425881Ssam if (cp->v_itrempt == cp->v_itrfill) 99525881Ssam return; 99625881Ssam item = cp->v_itrqueu[cp->v_itrempt]; 99725881Ssam intr = (short *)&vp->v_vioc; 99825881Ssam switch ((item >> 8)&03) { 99925881Ssam 100025881Ssam case CMDquals: { /* command */ 100125881Ssam int phys; 100225881Ssam 100325881Ssam if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 100425881Ssam break; 100525881Ssam vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 100625881Ssam phys = vtoph((struct proc *)0, 100725881Ssam (unsigned)cp->cmdbuf[cp->v_empty]); 100825881Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 100925881Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 101025881Ssam vp->v_vcbsy = V_BSY; 101125881Ssam *intr = item; 101225881Ssam scope_out(4); 101325881Ssam break; 101425881Ssam } 101525881Ssam 101625881Ssam case RSPquals: /* command response */ 101725881Ssam *intr = item; 101825881Ssam scope_out(7); 101925881Ssam break; 102025881Ssam 102125881Ssam case UNSquals: /* unsolicited interrupt */ 102225881Ssam vp->v_uqual = 0; 102325881Ssam *intr = item; 102425881Ssam scope_out(2); 102525881Ssam break; 102625881Ssam } 102725881Ssam } 102825881Ssam 102925881Ssam /* 103025881Ssam * Start a reset on a vioc after error (hopefully) 103125881Ssam */ 103225881Ssam vxstreset(vx) 103325881Ssam register vx; 103425881Ssam { 103525881Ssam register struct vx_softc *vs; 103625933Ssam register struct vxdevice *vp; 103725881Ssam register struct vxcmd *cp; 103825881Ssam register int j; 103925881Ssam extern int vxinreset(); 104025881Ssam int s; 104125881Ssam 104225881Ssam s = spl8() ; 104325881Ssam vs = &vx_softc[vx]; 104425881Ssam if (vs->vs_state == VXS_RESET) { /* avoid recursion */ 104525881Ssam splx(s); 104625881Ssam return; 104725881Ssam } 104825881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 104925881Ssam /* 105025881Ssam * Zero out the vioc structures, mark the vioc as being 105125881Ssam * reset, reinitialize the free command list, reset the vioc 105225881Ssam * and start a timer to check on the progress of the reset. 105325881Ssam */ 105425881Ssam bzero((caddr_t)vs, (unsigned)sizeof (*vs)); 105525881Ssam 105625881Ssam /* 105725881Ssam * Setting VXS_RESET prevents others from issuing 105825881Ssam * commands while allowing currently queued commands to 105925881Ssam * be passed to the VIOC. 106025881Ssam */ 106125881Ssam vs->vs_state = VXS_RESET; 106225881Ssam /* init all cmd buffers */ 106325881Ssam for (j = 0; j < NVCXBUFS; j++) { 106425933Ssam cp = &vs->vs_lst[j]; 106525933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 106625881Ssam } 106725933Ssam vs->vs_avail = &vs->vs_lst[0]; 106825933Ssam cp->c_fwd = (struct vxcmd *)0; 106925881Ssam printf("vx%d: reset...", vx); 107025881Ssam vp->v_fault = 0; 107125881Ssam vp->v_vioc = V_BSY; 107225933Ssam vp->v_hdwre = V_RESET; /* generate reset interrupt */ 107325881Ssam timeout(vxinreset, (caddr_t)vx, hz*5); 107425881Ssam splx(s); 107525881Ssam } 107625881Ssam 107725881Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 107825881Ssam vxinreset(vx) 107925881Ssam int vx; 108025881Ssam { 108125933Ssam register struct vxdevice *vp; 108225881Ssam int s = spl8(); 108325881Ssam 108425881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 108525881Ssam /* 108625881Ssam * See if the vioc has reset. 108725881Ssam */ 108825881Ssam if (vp->v_fault != VXF_READY) { 108925881Ssam printf("failed\n"); 109025881Ssam splx(s); 109125881Ssam return; 109225881Ssam } 109325881Ssam /* 109425881Ssam * Send a LIDENT to the vioc and mess with carrier flags 109525881Ssam * on parallel printer ports. 109625881Ssam */ 109729954Skarels vxinit(vx, 0); 109825881Ssam splx(s); 109925881Ssam } 110025881Ssam 110125881Ssam /* 110225933Ssam * Finish the reset on the vioc after an error (hopefully). 110325933Ssam * 110425881Ssam * Restore modem control, parameters and restart output. 110525881Ssam * Since the vioc can handle no more then 24 commands at a time 110625881Ssam * and we could generate as many as 48 commands, we must do this in 110725881Ssam * phases, issuing no more then 16 commands at a time. 110825881Ssam */ 110925881Ssam vxfnreset(vx, cp) 111025881Ssam register int vx; 111125881Ssam register struct vxcmd *cp; 111225881Ssam { 111325881Ssam register struct vx_softc *vs; 111425933Ssam register struct vxdevice *vp ; 111525881Ssam register struct tty *tp, *tp0; 111625881Ssam register int i; 111725881Ssam #ifdef notdef 111825881Ssam register int on; 111925881Ssam #endif 112025881Ssam extern int vxrestart(); 112125881Ssam int s = spl8(); 112225881Ssam 112325881Ssam vs = &vx_softc[vx]; 112425881Ssam vs->vs_loport = cp->par[5]; 112525881Ssam vs->vs_hiport = cp->par[7]; 112625881Ssam vrelease(vs, cp); 112725881Ssam vs->vs_nbr = vx; /* assign VIOC-X board number */ 112825881Ssam vs->vs_state = VXS_READY; 112925881Ssam 113025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 113125881Ssam vp->v_vcid = 0; 113225881Ssam 113325881Ssam /* 113425881Ssam * Restore modem information and control. 113525881Ssam */ 113625881Ssam tp0 = &vx_tty[vx*16]; 113725881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 113825881Ssam tp = tp0 + i; 113925881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 114025881Ssam tp->t_state &= ~TS_CARR_ON; 114125881Ssam vcmodem(tp->t_dev, VMOD_ON); 114225881Ssam if (tp->t_state&TS_CARR_ON) 114329954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 114429954Skarels else if (tp->t_state & TS_ISOPEN) 114529954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 114625881Ssam } 114729954Skarels #ifdef notdef 114825881Ssam /* 114925881Ssam * If carrier has changed while we were resetting, 115025881Ssam * take appropriate action. 115125881Ssam */ 115225881Ssam on = vp->v_dcd & 1<<i; 115329954Skarels if (on && (tp->t_state&TS_CARR_ON) == 0) 115429954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 115529954Skarels else if (!on && tp->t_state&TS_CARR_ON) 115629954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 115725881Ssam #endif 115825881Ssam } 115925881Ssam vs->vs_state = VXS_RESET; 116025881Ssam timeout(vxrestart, (caddr_t)vx, hz); 116125881Ssam splx(s); 116225881Ssam } 116325881Ssam 116425881Ssam /* 116525881Ssam * Restore a particular aspect of the VIOC. 116625881Ssam */ 116725881Ssam vxrestart(vx) 116825881Ssam int vx; 116925881Ssam { 117025881Ssam register struct tty *tp, *tp0; 117125881Ssam register struct vx_softc *vs; 1172*30372Skarels register int i, count; 117325881Ssam int s = spl8(); 117425881Ssam 1175*30372Skarels count = vx >> 8; 117625881Ssam vx &= 0xff; 117725881Ssam vs = &vx_softc[vx]; 117825881Ssam vs->vs_state = VXS_READY; 117925881Ssam tp0 = &vx_tty[vx*16]; 118025881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 118125881Ssam tp = tp0 + i; 1182*30372Skarels if (count != 0) { 118325881Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 118425881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) 118525881Ssam vxstart(tp); /* restart pending output */ 118625881Ssam } else { 118725881Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 118825881Ssam vxcparam(tp->t_dev, 0); 118925881Ssam } 119025881Ssam } 1191*30372Skarels if (count == 0) { 119225881Ssam vs->vs_state = VXS_RESET; 119325881Ssam timeout(vxrestart, (caddr_t)(vx + 1*256), hz); 119425881Ssam } else 119525881Ssam printf("done\n"); 119625881Ssam splx(s); 119725881Ssam } 119825881Ssam 119925881Ssam vxreset(dev) 120025881Ssam dev_t dev; 120125881Ssam { 120225881Ssam 1203*30372Skarels vxstreset((int)VXUNIT(minor(dev))); /* completes asynchronously */ 120425881Ssam } 120525881Ssam 1206*30372Skarels #ifdef notdef 120725881Ssam vxfreset(vx) 120825881Ssam register int vx; 120925881Ssam { 121025881Ssam struct vba_device *vi; 121125881Ssam 121225881Ssam if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0) 121325881Ssam return (ENODEV); 121425881Ssam vx_softc[vx].vs_state = VXS_READY; 121525881Ssam vxstreset(vx); 121625881Ssam return (0); /* completes asynchronously */ 121725881Ssam } 1218*30372Skarels #endif 121925881Ssam 122025881Ssam vcmodem(dev, flag) 122125881Ssam dev_t dev; 122225881Ssam { 122325881Ssam struct tty *tp; 122425881Ssam register struct vxcmd *cp; 122525881Ssam register struct vx_softc *vs; 122625881Ssam register struct vxdevice *kp; 122725881Ssam register port; 122825881Ssam int unit; 122925881Ssam 123025881Ssam unit = minor(dev); 123125881Ssam tp = &vx_tty[unit]; 123225881Ssam vs = (struct vx_softc *)tp->t_addr; 1233*30372Skarels if (vs->vs_state != VXS_READY) 1234*30372Skarels return; 123525881Ssam cp = vobtain(vs); 123625881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr; 123725881Ssam 123825881Ssam port = unit & 017; 123925881Ssam /* 124025881Ssam * Issue MODEM command 124125881Ssam */ 124225881Ssam cp->cmd = VXC_MDMCTL; 1243*30372Skarels if (flag == VMOD_ON) { 1244*30372Skarels if (vs->vs_softCAR & (1 << port)) 1245*30372Skarels cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS; 1246*30372Skarels else 1247*30372Skarels cp->par[0] = V_AUTO | V_DTR_ON | V_RTS; 1248*30372Skarels } else 1249*30372Skarels cp->par[0] = V_DTR_OFF; 125025881Ssam cp->par[1] = port; 1251*30372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 1252*30372Skarels if (vs->vs_softCAR & (1 << port)) 1253*30372Skarels kp->v_dcd |= (1 << port); 1254*30372Skarels if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON) 1255*30372Skarels tp->t_state |= TS_CARR_ON; 125625881Ssam } 125725881Ssam 125825881Ssam /* 125925881Ssam * VCMINTR called when an unsolicited interrup occurs signaling 126025881Ssam * some change of modem control state. 126125881Ssam */ 126225881Ssam vcmintr(vx) 126325881Ssam register vx; 126425881Ssam { 126525881Ssam register struct vxdevice *kp; 126625881Ssam register struct tty *tp; 126725881Ssam register port; 1268*30372Skarels register struct vx_softc *vs; 126925881Ssam 127025881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 127125881Ssam port = kp->v_usdata[0] & 017; 127225881Ssam tp = &vx_tty[vx*16+port]; 1273*30372Skarels vs = &vx_softc[vx]; 127425881Ssam 127529954Skarels if (kp->v_ustat & DCD_ON) 127629954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 127729954Skarels else if ((kp->v_ustat & DCD_OFF) && 1278*30372Skarels ((vs->vs_softCAR & (1 << port))) == 0 && 127929954Skarels (*linesw[tp->t_line].l_modem)(tp, 0) == 0) { 128029954Skarels register struct vcmds *cp; 128129954Skarels register struct vxcmd *cmdp; 128225881Ssam 1283*30372Skarels /* clear all pending transmits */ 128429954Skarels if (tp->t_state&(TS_BUSY|TS_FLUSH) && 128529954Skarels vs->vs_vers == VXV_NEW) { 128629954Skarels int i, cmdfound = 0; 128725881Ssam 128829954Skarels cp = &vs->vs_cmds; 128929954Skarels for (i = cp->v_empty; i != cp->v_fill; ) { 129029954Skarels cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1); 129129954Skarels if ((cmdp->cmd == VXC_XMITDTA || 129229954Skarels cmdp->cmd == VXC_XMITIMM) && 129329954Skarels ((struct vxmit *)cmdp->par)->line == port) { 129429954Skarels cmdfound++; 129525881Ssam cmdp->cmd = VXC_FDTATOX; 129625881Ssam cmdp->par[1] = port; 129725881Ssam } 129829954Skarels if (++i >= VC_CMDBUFL) 129929954Skarels i = 0; 130025881Ssam } 130129954Skarels if (cmdfound) 130229954Skarels tp->t_state &= ~(TS_BUSY|TS_FLUSH); 130329954Skarels /* cmd is already in vioc, have to flush it */ 130429954Skarels else { 130529954Skarels cmdp = vobtain(vs); 130629954Skarels cmdp->cmd = VXC_FDTATOX; 130729954Skarels cmdp->par[1] = port; 1308*30372Skarels (void) vcmd(vx, (caddr_t)&cmdp->cmd); 130925881Ssam } 131025881Ssam } 131129954Skarels } else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) { 1312*30372Skarels (*linesw[tp->t_line].l_rint)((tp->t_flags & RAW) ? 1313*30372Skarels 0 : tp->t_intrc, tp); 131425881Ssam return; 131525881Ssam } 131625881Ssam } 131725881Ssam #endif 1318