134406Skarels /* 234406Skarels * Copyright (c) 1988 Regents of the University of California. 3*35057Skarels * All rights reserved. 434406Skarels * 5*35057Skarels * This code is derived from software contributed to Berkeley by 6*35057Skarels * Computer Consoles Inc. 7*35057Skarels * 8*35057Skarels * Redistribution and use in source and binary forms are permitted 9*35057Skarels * provided that the above copyright notice and this paragraph are 10*35057Skarels * duplicated in all such forms and that any documentation, 11*35057Skarels * advertising materials, and other materials related to such 12*35057Skarels * distribution and use acknowledge that the software was developed 13*35057Skarels * by the University of California, Berkeley. The name of the 14*35057Skarels * University may not be used to endorse or promote products derived 15*35057Skarels * from this software without specific prior written permission. 16*35057Skarels * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 17*35057Skarels * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 18*35057Skarels * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE. 19*35057Skarels * 20*35057Skarels * @(#)vx.c 7.2 (Berkeley) 07/09/88 2134406Skarels */ 2224003Ssam 2324003Ssam #include "vx.h" 2424003Ssam #if NVX > 0 2524003Ssam /* 2625857Ssam * VIOC-X driver 2724003Ssam */ 2825877Ssam #ifdef VXPERF 2925948Ssam #define DOSCOPE 3025877Ssam #endif 3125877Ssam 3225877Ssam #include "param.h" 3325877Ssam #include "ioctl.h" 3425877Ssam #include "tty.h" 3525877Ssam #include "dir.h" 3625877Ssam #include "user.h" 3725877Ssam #include "map.h" 3825877Ssam #include "buf.h" 3925877Ssam #include "conf.h" 4025877Ssam #include "file.h" 4125877Ssam #include "uio.h" 4225877Ssam #include "proc.h" 4325877Ssam #include "vm.h" 4425881Ssam #include "kernel.h" 4529954Skarels #include "syslog.h" 4625675Ssam 4734406Skarels #include "../tahoe/pte.h" 4834406Skarels 4925675Ssam #include "../tahoevba/vbavar.h" 5025881Ssam #include "../tahoevba/vxreg.h" 5125675Ssam #include "../tahoevba/scope.h" 5224003Ssam 5325881Ssam #ifdef VX_DEBUG 5425881Ssam long vxintr4 = 0; 5525948Ssam #define VXERR4 1 5625948Ssam #define VXNOBUF 2 5725881Ssam long vxdebug = 0; 5825948Ssam #define VXVCM 1 5925948Ssam #define VXVCC 2 6025948Ssam #define VXVCX 4 6125881Ssam #endif 6224003Ssam 6325881Ssam /* 6425881Ssam * Interrupt type bits passed to vinthandl(). 6525881Ssam */ 6625948Ssam #define CMDquals 0 /* command completed interrupt */ 6725948Ssam #define RSPquals 1 /* command response interrupt */ 6825948Ssam #define UNSquals 2 /* unsolicited interrupt */ 6924003Ssam 7030372Skarels #define VXUNIT(n) ((n) >> 4) 7130372Skarels #define VXPORT(n) ((n) & 0xf) 7230372Skarels 7325881Ssam struct tty vx_tty[NVX*16]; 7429954Skarels #ifndef lint 7529954Skarels int nvx = NVX*16; 7629954Skarels #endif 7725881Ssam int vxstart(), ttrstrt(); 7825881Ssam struct vxcmd *vobtain(), *nextcmd(); 7924003Ssam 8024003Ssam /* 8124003Ssam * Driver information for auto-configuration stuff. 8224003Ssam */ 8324003Ssam int vxprobe(), vxattach(), vxrint(); 8425881Ssam struct vba_device *vxinfo[NVX]; 8524003Ssam long vxstd[] = { 0 }; 8624003Ssam struct vba_driver vxdriver = 8725857Ssam { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; 8824003Ssam 8925881Ssam struct vx_softc { 9025881Ssam u_char vs_type; /* 0: viox-x/vioc-b, 1: vioc-bop */ 9125881Ssam u_char vs_bop; /* bop board # for vioc-bop's */ 9225881Ssam u_char vs_loport; /* low port nbr */ 9325881Ssam u_char vs_hiport; /* high port nbr */ 9425881Ssam u_short vs_nbr; /* viocx number */ 9525881Ssam u_short vs_maxcmd; /* max number of concurrent cmds */ 9625881Ssam u_short vs_silosiz; /* silo size */ 9725881Ssam short vs_vers; /* vioc/pvioc version */ 9825948Ssam #define VXV_OLD 0 /* PVIOCX | VIOCX */ 9925948Ssam #define VXV_NEW 1 /* NPVIOCX | NVIOCX */ 10025881Ssam short vs_xmtcnt; /* xmit commands pending */ 10125881Ssam short vs_brkreq; /* send break requests pending */ 10225881Ssam short vs_state; /* controller state */ 10325948Ssam #define VXS_READY 0 /* ready for commands */ 10425948Ssam #define VXS_RESET 1 /* in process of reseting */ 10530372Skarels u_short vs_softCAR; /* soft carrier */ 10625881Ssam caddr_t vs_mricmd; /* most recent issued cmd */ 10725881Ssam u_int vs_ivec; /* interrupt vector base */ 10825881Ssam struct vxcmd *vs_avail;/* next available command buffer */ 10925881Ssam struct vxcmd *vs_build; 11025881Ssam struct vxcmd vs_lst[NVCXBUFS]; 11125881Ssam struct vcmds vs_cmds; 11225881Ssam } vx_softc[NVX]; 11324003Ssam 11425857Ssam vxprobe(reg, vi) 11524003Ssam caddr_t reg; 11625857Ssam struct vba_device *vi; 11724003Ssam { 11825857Ssam register int br, cvec; /* must be r12, r11 */ 11925881Ssam register struct vxdevice *vp = (struct vxdevice *)reg; 12025881Ssam register struct vx_softc *vs; 12124003Ssam 12224003Ssam #ifdef lint 12324003Ssam br = 0; cvec = br; br = cvec; 12425675Ssam vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0); 12524003Ssam #endif 12625675Ssam if (badaddr((caddr_t)vp, 1)) 12725675Ssam return (0); 12825675Ssam vp->v_fault = 0; 12925675Ssam vp->v_vioc = V_BSY; 13025675Ssam vp->v_hdwre = V_RESET; /* reset interrupt */ 13124003Ssam DELAY(4000000); 13225881Ssam if (vp->v_fault != VXF_READY) 13325675Ssam return (0); 13425881Ssam vs = &vx_softc[vi->ui_unit]; 13525857Ssam #ifdef notdef 13625857Ssam /* 13725857Ssam * Align vioc interrupt vector base to 4 vector 13825857Ssam * boundary and fitting in 8 bits (is this necessary, 13925857Ssam * wish we had documentation). 14025857Ssam */ 14125857Ssam if ((vi->ui_hd->vh_lastiv -= 3) > 0xff) 14225857Ssam vi->ui_hd->vh_lastiv = 0xff; 14325881Ssam vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3; 14425857Ssam #else 14525881Ssam vs->vs_ivec = 0x40+vi->ui_unit*4; 14625857Ssam #endif 14725881Ssam br = 0x18, cvec = vs->vs_ivec; /* XXX */ 14825881Ssam return (sizeof (struct vxdevice)); 14924003Ssam } 15024003Ssam 15125857Ssam vxattach(vi) 15225857Ssam register struct vba_device *vi; 15324003Ssam { 15425675Ssam 15530372Skarels vx_softc[vi->ui_unit].vs_softCAR = vi->ui_flags; 15629954Skarels vxinit(vi->ui_unit, 1); 15724003Ssam } 15824003Ssam 15924003Ssam /* 16024003Ssam * Open a VX line. 16124003Ssam */ 16225675Ssam /*ARGSUSED*/ 16324003Ssam vxopen(dev, flag) 16425881Ssam dev_t dev; 16525881Ssam int flag; 16624003Ssam { 16724003Ssam register struct tty *tp; /* pointer to tty struct for port */ 16825881Ssam register struct vx_softc *vs; 16925881Ssam register struct vba_device *vi; 17025881Ssam int unit, vx, s, error; 17124003Ssam 17225881Ssam unit = minor(dev); 17330372Skarels vx = VXUNIT(unit); 17430372Skarels if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0) 17525881Ssam return (ENXIO); 17630372Skarels vs = &vx_softc[vx]; 17725881Ssam tp = &vx_tty[unit]; 17830372Skarels unit = VXPORT(unit); 17925881Ssam if (tp->t_state&TS_XCLUDE && u.u_uid != 0) 18025881Ssam return (EBUSY); 18130372Skarels if (unit < vs->vs_loport || unit > vs->vs_hiport) 18225881Ssam return (ENXIO); 18325881Ssam tp->t_addr = (caddr_t)vs; 18425881Ssam tp->t_oproc = vxstart; 18525881Ssam tp->t_dev = dev; 18625881Ssam s = spl8(); 18725881Ssam tp->t_state |= TS_WOPEN; 18825881Ssam if ((tp->t_state&TS_ISOPEN) == 0) { 18925881Ssam ttychars(tp); 19025881Ssam if (tp->t_ispeed == 0) { 19125881Ssam tp->t_ispeed = SSPEED; 19225881Ssam tp->t_ospeed = SSPEED; 19325881Ssam tp->t_flags |= ODDP|EVENP|ECHO; 19424003Ssam } 19525881Ssam vxparam(dev); 19624003Ssam } 19730372Skarels vcmodem(dev, VMOD_ON); 19830372Skarels while ((tp->t_state&TS_CARR_ON) == 0) 19930372Skarels sleep((caddr_t)&tp->t_rawq, TTIPRI); 20025881Ssam error = (*linesw[tp->t_line].l_open)(dev,tp); 20125881Ssam splx(s); 20225881Ssam return (error); 20324003Ssam } 20424003Ssam 20524003Ssam /* 20624003Ssam * Close a VX line. 20724003Ssam */ 20825675Ssam /*ARGSUSED*/ 20924003Ssam vxclose(dev, flag) 21025881Ssam dev_t dev; 21125881Ssam int flag; 21224003Ssam { 21324003Ssam register struct tty *tp; 21425881Ssam int unit, s; 21524003Ssam 21625881Ssam unit = minor(dev); 21725881Ssam tp = &vx_tty[unit]; 21825881Ssam s = spl8(); 21924003Ssam (*linesw[tp->t_line].l_close)(tp); 22030372Skarels if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0) 22130372Skarels vcmodem(dev, VMOD_OFF); 22224003Ssam /* wait for the last response */ 22325881Ssam while (tp->t_state&TS_FLUSH) 22425881Ssam sleep((caddr_t)&tp->t_state, TTOPRI); 22525881Ssam ttyclose(tp); 22625881Ssam splx(s); 22724003Ssam } 22824003Ssam 22924003Ssam /* 23024003Ssam * Read from a VX line. 23124003Ssam */ 23224003Ssam vxread(dev, uio) 23324003Ssam dev_t dev; 23424003Ssam struct uio *uio; 23524003Ssam { 23625881Ssam struct tty *tp = &vx_tty[minor(dev)]; 23725881Ssam 23825881Ssam return ((*linesw[tp->t_line].l_read)(tp, uio)); 23924003Ssam } 24024003Ssam 24124003Ssam /* 24224003Ssam * write on a VX line 24324003Ssam */ 24424003Ssam vxwrite(dev, uio) 24524003Ssam dev_t dev; 24624003Ssam struct uio *uio; 24724003Ssam { 24825881Ssam register struct tty *tp = &vx_tty[minor(dev)]; 24925881Ssam 25025881Ssam return ((*linesw[tp->t_line].l_write)(tp, uio)); 25124003Ssam } 25224003Ssam 25324003Ssam /* 25424003Ssam * VIOCX unsolicited interrupt. 25524003Ssam */ 25625881Ssam vxrint(vx) 25725881Ssam register vx; 25824003Ssam { 25925881Ssam register struct tty *tp, *tp0; 26025881Ssam register struct vxdevice *addr; 26125881Ssam register struct vx_softc *vs; 26225881Ssam struct vba_device *vi; 26325881Ssam register int nc, c; 26425881Ssam register struct silo { 26525881Ssam char data, port; 26625881Ssam } *sp; 26725881Ssam short *osp; 26825881Ssam int overrun = 0; 26924003Ssam 27025881Ssam vi = vxinfo[vx]; 27125881Ssam if (vi == 0 || vi->ui_alive == 0) 27225881Ssam return; 27325881Ssam addr = (struct vxdevice *)vi->ui_addr; 27425881Ssam switch (addr->v_uqual&037) { 27524003Ssam case 0: 27624003Ssam break; 27724003Ssam case 2: 27830372Skarels printf("vx%d: vc proc err, ustat %x\n", vx, addr->v_ustat); 27925881Ssam vxstreset(vx); 28030372Skarels return; 28124003Ssam case 3: 28225881Ssam vcmintr(vx); 28330372Skarels return; 28424003Ssam case 4: 28530372Skarels return; 28624003Ssam default: 28730372Skarels printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual); 28825881Ssam vxstreset(vx); 28930372Skarels return; 29024003Ssam } 29125881Ssam vs = &vx_softc[vx]; 29225881Ssam if (vs->vs_vers == VXV_NEW) 29325881Ssam sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata); 29425881Ssam else 29525881Ssam sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6)); 29625881Ssam nc = *(osp = (short *)sp); 29725881Ssam if (nc == 0) 29830372Skarels return; 29925881Ssam if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) { 30025881Ssam printf("vx%d: %d exceeds silo size\n", nc); 30125881Ssam nc = vs->vs_silosiz; 30224003Ssam } 30325881Ssam tp0 = &vx_tty[vx*16]; 30425881Ssam sp = (struct silo *)(((short *)sp)+1); 30525881Ssam for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) { 30625881Ssam c = sp->port & 017; 30725881Ssam if (vs->vs_loport > c || c > vs->vs_hiport) 30825881Ssam continue; 30925881Ssam tp = tp0 + c; 31025881Ssam if( (tp->t_state&TS_ISOPEN) == 0) { 31124003Ssam wakeup((caddr_t)&tp->t_rawq); 31224003Ssam continue; 31324003Ssam } 31425881Ssam c = sp->data; 31525881Ssam if ((sp->port&VX_RO) == VX_RO && !overrun) { 31629954Skarels log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit); 31725881Ssam overrun = 1; 31825881Ssam continue; 31925881Ssam } 32025881Ssam if (sp->port&VX_PE) 32125881Ssam if ((tp->t_flags&(EVENP|ODDP)) == EVENP || 32225881Ssam (tp->t_flags&(EVENP|ODDP)) == ODDP) 32324003Ssam continue; 32430372Skarels if ((tp->t_flags & (RAW | PASS8)) == 0) 32530372Skarels c &= 0177; 32625881Ssam if (sp->port&VX_FE) { 32725881Ssam /* 32825881Ssam * At framing error (break) generate 32925881Ssam * a null (in raw mode, for getty), or a 33025881Ssam * interrupt (in cooked/cbreak mode). 33125881Ssam */ 33225881Ssam if (tp->t_flags&RAW) 33325881Ssam c = 0; 33425881Ssam else 33525881Ssam c = tp->t_intrc; 33624003Ssam } 33724003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 33824003Ssam } 33925881Ssam *osp = 0; 34024003Ssam } 34124003Ssam 34224003Ssam /* 34325881Ssam * Ioctl for VX. 34424003Ssam */ 34524003Ssam vxioctl(dev, cmd, data, flag) 34625881Ssam dev_t dev; 34725881Ssam caddr_t data; 34824003Ssam { 34925881Ssam register struct tty *tp; 35025881Ssam int error; 35124003Ssam 35225881Ssam tp = &vx_tty[minor(dev)]; 35324003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 35424003Ssam if (error == 0) 35525881Ssam return (error); 35625881Ssam error = ttioctl(tp, cmd, data, flag); 35725881Ssam if (error >= 0) { 35829954Skarels if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS || 35929954Skarels cmd == TIOCLBIC || cmd == TIOCLSET) 36024003Ssam vxparam(dev); 36125881Ssam return (error); 36225881Ssam } 36325881Ssam return (ENOTTY); 36424003Ssam } 36524003Ssam 36624003Ssam vxparam(dev) 36725881Ssam dev_t dev; 36824003Ssam { 36925881Ssam 37024003Ssam vxcparam(dev, 1); 37124003Ssam } 37224003Ssam 37324003Ssam /* 37424003Ssam * Set parameters from open or stty into the VX hardware 37524003Ssam * registers. 37624003Ssam */ 37724003Ssam vxcparam(dev, wait) 37825881Ssam dev_t dev; 37925881Ssam int wait; 38024003Ssam { 38125881Ssam register struct tty *tp; 38225881Ssam register struct vx_softc *vs; 38325881Ssam register struct vxcmd *cp; 38425933Ssam int s, unit = minor(dev); 38524003Ssam 38625933Ssam tp = &vx_tty[unit]; 38730372Skarels if ((tp->t_ispeed)==0) { 38830372Skarels tp->t_state |= TS_HUPCLS; 38930372Skarels vcmodem(dev, VMOD_OFF); 39030372Skarels return; 39130372Skarels } 39225881Ssam vs = (struct vx_softc *)tp->t_addr; 39325881Ssam cp = vobtain(vs); 39424003Ssam s = spl8(); 39525933Ssam /* 39625933Ssam * Construct ``load parameters'' command block 39725933Ssam * to setup baud rates, xon-xoff chars, parity, 39825933Ssam * and stop bits for the specified port. 39925933Ssam */ 40025933Ssam cp->cmd = VXC_LPARAX; 40130372Skarels cp->par[1] = VXPORT(unit); 40225933Ssam cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc; 40325933Ssam cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc; 40430372Skarels #ifdef notnow 40529954Skarels if (tp->t_flags & (RAW|LITOUT|PASS8)) { 40630372Skarels #endif 40730372Skarels cp->par[4] = BITS8; /* 8 bits of data */ 40830372Skarels cp->par[7] = VNOPARITY; /* no parity */ 40930372Skarels #ifdef notnow 41024003Ssam } else { 41130372Skarels cp->par[4] = BITS7; /* 7 bits of data */ 41225881Ssam if ((tp->t_flags&(EVENP|ODDP)) == ODDP) 41330372Skarels cp->par[7] = VODDP; /* odd parity */ 41429954Skarels else 41530372Skarels cp->par[7] = VEVENP; /* even parity */ 41624003Ssam } 41730372Skarels #endif 41830372Skarels if (tp->t_ospeed == B110) 41930372Skarels cp->par[5] = VSTOP2; /* 2 stop bits */ 42030372Skarels else 42130372Skarels cp->par[5] = VSTOP1; /* 1 stop bit */ 42230372Skarels if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB) 42330372Skarels cp->par[6] = V19200; 42430372Skarels else 42530372Skarels cp->par[6] = tp->t_ospeed; 42630372Skarels if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait) 42725675Ssam sleep((caddr_t)cp,TTIPRI); 42824003Ssam splx(s); 42924003Ssam } 43024003Ssam 43124003Ssam /* 43224003Ssam * VIOCX command response interrupt. 43324003Ssam * For transmission, restart output to any active port. 43424003Ssam * For all other commands, just clean up. 43524003Ssam */ 43625881Ssam vxxint(vx, cp) 43725881Ssam register int vx; 43825881Ssam register struct vxcmd *cp; 43924003Ssam { 44030372Skarels register struct vxmit *vp; 44125933Ssam register struct tty *tp, *tp0; 44225933Ssam register struct vx_softc *vs; 44324003Ssam 44425881Ssam vs = &vx_softc[vx]; 44525881Ssam cp = (struct vxcmd *)((long *)cp-1); 44629954Skarels 44725881Ssam switch (cp->cmd&0xff00) { 44825881Ssam 44925881Ssam case VXC_LIDENT: /* initialization complete */ 45025881Ssam if (vs->vs_state == VXS_RESET) { 45125881Ssam vxfnreset(vx, cp); 45225881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 45324003Ssam } 45424003Ssam cp->cmd++; 45524003Ssam return; 45625881Ssam 45725881Ssam case VXC_XMITDTA: 45825881Ssam case VXC_XMITIMM: 45924003Ssam break; 46025881Ssam 46125881Ssam case VXC_LPARAX: 46225675Ssam wakeup((caddr_t)cp); 46325881Ssam /* fall thru... */ 46425881Ssam default: /* VXC_MDMCTL or VXC_FDTATOX */ 46525881Ssam vrelease(vs, cp); 46625881Ssam if (vs->vs_state == VXS_RESET) 46725881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 46824003Ssam return; 46924003Ssam } 47025881Ssam tp0 = &vx_tty[vx*16]; 47125881Ssam vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 47225881Ssam for (; vp >= (struct vxmit *)cp->par; vp--) { 47325881Ssam tp = tp0 + (vp->line & 017); 47424003Ssam tp->t_state &= ~TS_BUSY; 47525881Ssam if (tp->t_state & TS_FLUSH) { 47624003Ssam tp->t_state &= ~TS_FLUSH; 47725881Ssam wakeup((caddr_t)&tp->t_state); 47825881Ssam } else 47924003Ssam ndflush(&tp->t_outq, vp->bcount+1); 48024003Ssam } 48125881Ssam vrelease(vs, cp); 48230372Skarels if (vs->vs_vers == VXV_NEW) 48332112Skarels (*linesw[tp->t_line].l_start)(tp); 48430372Skarels else { 48525881Ssam tp0 = &vx_tty[vx*16 + vs->vs_hiport]; 48625881Ssam for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++) 48732112Skarels (*linesw[tp->t_line].l_start)(tp); 48825881Ssam if ((cp = nextcmd(vs)) != NULL) { /* command to send? */ 48925881Ssam vs->vs_xmtcnt++; 49030372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 49124003Ssam } 49224003Ssam } 49330372Skarels vs->vs_xmtcnt--; 49424003Ssam } 49524003Ssam 49624003Ssam /* 49724003Ssam * Force out partial XMIT command after timeout 49824003Ssam */ 49925881Ssam vxforce(vs) 50025881Ssam register struct vx_softc *vs; 50124003Ssam { 50225881Ssam register struct vxcmd *cp; 50325881Ssam int s; 50424003Ssam 50524003Ssam s = spl8(); 50625881Ssam if ((cp = nextcmd(vs)) != NULL) { 50725881Ssam vs->vs_xmtcnt++; 50830372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 50924003Ssam } 51024003Ssam splx(s); 51124003Ssam } 51224003Ssam 51324003Ssam /* 51424003Ssam * Start (restart) transmission on the given VX line. 51524003Ssam */ 51624003Ssam vxstart(tp) 51725881Ssam register struct tty *tp; 51824003Ssam { 51925675Ssam register short n; 52025933Ssam register struct vx_softc *vs; 52125933Ssam int s, port; 52224003Ssam 52324003Ssam s = spl8(); 52424003Ssam port = minor(tp->t_dev) & 017; 52525881Ssam vs = (struct vx_softc *)tp->t_addr; 52625881Ssam if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) { 52725881Ssam if (tp->t_outq.c_cc <= TTLOWAT(tp)) { 52824003Ssam if (tp->t_state&TS_ASLEEP) { 52924003Ssam tp->t_state &= ~TS_ASLEEP; 53024003Ssam wakeup((caddr_t)&tp->t_outq); 53124003Ssam } 53224003Ssam if (tp->t_wsel) { 53324003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 53424003Ssam tp->t_wsel = 0; 53524003Ssam tp->t_state &= ~TS_WCOLL; 53624003Ssam } 53724003Ssam } 53825881Ssam if (tp->t_outq.c_cc == 0) { 53924003Ssam splx(s); 54030372Skarels return; 54124003Ssam } 54225877Ssam scope_out(3); 54329954Skarels if (tp->t_flags & (RAW|LITOUT)) 54430372Skarels n = ndqb(&tp->t_outq, 0); 54530372Skarels else { 54630372Skarels n = ndqb(&tp->t_outq, 0200); 54730372Skarels if (n == 0) { 54825675Ssam n = getc(&tp->t_outq); 54925881Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 55024003Ssam tp->t_state |= TS_TIMEOUT; 55130372Skarels n = 0; 55224003Ssam } 55330372Skarels } 55430372Skarels if (n) { 55524003Ssam tp->t_state |= TS_BUSY; 55630372Skarels vsetq(vs, port, (char *)tp->t_outq.c_cf, n); 55724003Ssam } 55824003Ssam } 55924003Ssam splx(s); 56024003Ssam } 56124003Ssam 56224003Ssam /* 56324003Ssam * Stop output on a line. 56424003Ssam */ 56524003Ssam vxstop(tp) 56625881Ssam register struct tty *tp; 56724003Ssam { 56825881Ssam int s; 56924003Ssam 57024003Ssam s = spl8(); 57125881Ssam if (tp->t_state&TS_BUSY) 57225881Ssam if ((tp->t_state&TS_TTSTOP) == 0) 57324003Ssam tp->t_state |= TS_FLUSH; 57424003Ssam splx(s); 57524003Ssam } 57624003Ssam 57725881Ssam static int vxbbno = -1; 57824003Ssam /* 57924003Ssam * VIOCX Initialization. Makes free lists of command buffers. 58024003Ssam * Resets all viocx's. Issues a LIDENT command to each 58125933Ssam * viocx to establish interrupt vectors and logical port numbers. 58224003Ssam */ 58325881Ssam vxinit(vx, wait) 58425881Ssam register int vx; 58525881Ssam int wait; 58624003Ssam { 58725933Ssam register struct vx_softc *vs; 58825933Ssam register struct vxdevice *addr; 58925933Ssam register struct vxcmd *cp; 59025881Ssam register char *resp; 59125881Ssam register int j; 59230372Skarels char type, *typestring; 59324003Ssam 59425881Ssam vs = &vx_softc[vx]; 59525933Ssam vs->vs_type = 0; /* vioc-x by default */ 59625933Ssam addr = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 59725881Ssam type = addr->v_ident; 59825881Ssam vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD; 59925881Ssam if (vs->vs_vers == VXV_NEW) 60025881Ssam vs->vs_silosiz = addr->v_maxsilo; 60125881Ssam switch (type) { 60224003Ssam 60325881Ssam case VXT_VIOCX: 60425881Ssam case VXT_VIOCX|VXT_NEW: 60530372Skarels typestring = "VIOC-X"; 60630372Skarels /* set soft carrier for printer ports */ 60730372Skarels for (j = 0; j < 16; j++) 60830372Skarels if (addr->v_portyp[j] == VXT_PARALLEL) { 60930372Skarels vs->vs_softCAR |= 1 << j; 61025881Ssam addr->v_dcd |= 1 << j; 61130372Skarels } 61225881Ssam break; 61324003Ssam 61425881Ssam case VXT_PVIOCX: 61525881Ssam case VXT_PVIOCX|VXT_NEW: 61630372Skarels typestring = "VIOC-X (old connector panel)"; 61725881Ssam break; 61825881Ssam case VXT_VIOCBOP: /* VIOC-BOP */ 61925881Ssam vs->vs_type = 1; 62025881Ssam vs->vs_bop = ++vxbbno; 62125881Ssam printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr); 62224003Ssam 62325933Ssam default: 62425881Ssam printf("vx%d: unknown type %x\n", vx, type); 62530372Skarels vxinfo[vx]->ui_alive = 0; 62625881Ssam return; 62724003Ssam } 62825881Ssam vs->vs_nbr = -1; 62925933Ssam vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4; 63025933Ssam /* 63125933Ssam * Initialize all cmd buffers by linking them 63225933Ssam * into a free list. 63325933Ssam */ 63425881Ssam for (j = 0; j < NVCXBUFS; j++) { 63525933Ssam cp = &vs->vs_lst[j]; 63625933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 63725881Ssam } 63825881Ssam vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ 63924003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 64024003Ssam 64125933Ssam /* 64225933Ssam * Establish the interrupt vectors and define the port numbers. 64325933Ssam */ 64425933Ssam cp = vobtain(vs); 64525933Ssam cp->cmd = VXC_LIDENT; 64625881Ssam cp->par[0] = vs->vs_ivec; /* ack vector */ 64725857Ssam cp->par[1] = cp->par[0]+1; /* cmd resp vector */ 64825857Ssam cp->par[3] = cp->par[0]+2; /* unsol intr vector */ 64925881Ssam cp->par[4] = 15; /* max ports, no longer used */ 65025881Ssam cp->par[5] = 0; /* set 1st port number */ 65130372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 65225881Ssam if (!wait) 65325881Ssam return; 65425881Ssam for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++) 65525857Ssam ; 65625857Ssam if (j >= 4000000) 65725881Ssam printf("vx%d: didn't respond to LIDENT\n", vx); 65824003Ssam 65924003Ssam /* calculate address of response buffer */ 66025881Ssam resp = (char *)addr + (addr->v_rspoff&0x3fff); 66125933Ssam if (resp[0] != 0 && (resp[0]&0177) != 3) { 66225933Ssam vrelease(vs, cp); /* init failed */ 66325881Ssam return; 66424003Ssam } 66525881Ssam vs->vs_loport = cp->par[5]; 66625881Ssam vs->vs_hiport = cp->par[7]; 66730372Skarels printf("vx%d: %s%s, ports %d-%d\n", vx, 66830372Skarels (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring, 66930372Skarels vs->vs_loport, vs->vs_hiport); 67025881Ssam vrelease(vs, cp); 67125933Ssam vs->vs_nbr = vx; /* assign board number */ 67224003Ssam } 67324003Ssam 67424003Ssam /* 67524003Ssam * Obtain a command buffer 67624003Ssam */ 67725881Ssam struct vxcmd * 67825881Ssam vobtain(vs) 67925933Ssam register struct vx_softc *vs; 68024003Ssam { 68125933Ssam register struct vxcmd *p; 68225881Ssam int s; 68324003Ssam 68424003Ssam s = spl8(); 68525881Ssam p = vs->vs_avail; 68625881Ssam if (p == (struct vxcmd *)0) { 68724003Ssam #ifdef VX_DEBUG 68825881Ssam if (vxintr4&VXNOBUF) 68925881Ssam vxintr4 &= ~VXNOBUF; 69024003Ssam #endif 69125881Ssam printf("vx%d: no buffers\n", vs - vx_softc); 69225881Ssam vxstreset(vs - vx_softc); 69324003Ssam splx(s); 69425881Ssam return (vobtain(vs)); 69524003Ssam } 69630372Skarels vs->vs_avail = p->c_fwd; 69724003Ssam splx(s); 69825881Ssam return ((struct vxcmd *)p); 69924003Ssam } 70024003Ssam 70124003Ssam /* 70224003Ssam * Release a command buffer 70324003Ssam */ 70425881Ssam vrelease(vs, cp) 70525933Ssam register struct vx_softc *vs; 70625933Ssam register struct vxcmd *cp; 70724003Ssam { 70825881Ssam int s; 70924003Ssam 71024003Ssam #ifdef VX_DEBUG 71125881Ssam if (vxintr4&VXNOBUF) 71225881Ssam return; 71324003Ssam #endif 71424003Ssam s = spl8(); 71525881Ssam cp->c_fwd = vs->vs_avail; 71625881Ssam vs->vs_avail = cp; 71724003Ssam splx(s); 71824003Ssam } 71924003Ssam 72025881Ssam struct vxcmd * 72125881Ssam nextcmd(vs) 72225933Ssam register struct vx_softc *vs; 72324003Ssam { 72425933Ssam register struct vxcmd *cp; 72525881Ssam int s; 72624003Ssam 72724003Ssam s = spl8(); 72825881Ssam cp = vs->vs_build; 72925881Ssam vs->vs_build = (struct vxcmd *)0; 73024003Ssam splx(s); 73125881Ssam return (cp); 73224003Ssam } 73324003Ssam 73424003Ssam /* 73525933Ssam * Assemble transmits into a multiple command; 73630372Skarels * up to 8 transmits to 8 lines can be assembled together 73730372Skarels * (on PVIOCX only). 73824003Ssam */ 73925933Ssam vsetq(vs, line, addr, n) 74025933Ssam register struct vx_softc *vs; 74125881Ssam caddr_t addr; 74224003Ssam { 74325933Ssam register struct vxcmd *cp; 74425933Ssam register struct vxmit *mp; 74524003Ssam 74625933Ssam /* 74725933Ssam * Grab a new command buffer or append 74825933Ssam * to the current one being built. 74925933Ssam */ 75025881Ssam cp = vs->vs_build; 75125881Ssam if (cp == (struct vxcmd *)0) { 75225881Ssam cp = vobtain(vs); 75325881Ssam vs->vs_build = cp; 75425881Ssam cp->cmd = VXC_XMITDTA; 75524003Ssam } else { 75630372Skarels if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) { 75725881Ssam printf("vx%d: setq overflow\n", vs-vx_softc); 75830372Skarels vxstreset((int)vs->vs_nbr); 75930372Skarels return; 76024003Ssam } 76124003Ssam cp->cmd++; 76224003Ssam } 76325933Ssam /* 76425933Ssam * Select the next vxmit buffer and copy the 76525933Ssam * characters into the buffer (if there's room 76625933Ssam * and the device supports ``immediate mode'', 76725933Ssam * or store an indirect pointer to the data. 76825933Ssam */ 76925881Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 77025675Ssam mp->bcount = n-1; 77125933Ssam mp->line = line; 77225933Ssam if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) { 77325881Ssam cp->cmd = VXC_XMITIMM; 77430372Skarels bcopy(addr, mp->ostream, (unsigned)n); 77524003Ssam } else { 77625933Ssam /* get system address of clist block */ 77725675Ssam addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr); 77830372Skarels bcopy((caddr_t)&addr, mp->ostream, sizeof (addr)); 77924003Ssam } 78030372Skarels /* 78130372Skarels * We send the data immediately if a VIOCX, 78230372Skarels * the command buffer is full, or if we've nothing 78330372Skarels * currently outstanding. If we don't send it, 78430372Skarels * set a timeout to force the data to be sent soon. 78530372Skarels */ 78630372Skarels if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 || 78730372Skarels vs->vs_xmtcnt == 0) { 78830372Skarels vs->vs_xmtcnt++; 78930372Skarels (void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd); 79030372Skarels vs->vs_build = 0; 79130372Skarels } else 79230372Skarels timeout(vxforce, (caddr_t)vs, 3); 79324003Ssam } 79425881Ssam 79525881Ssam /* 79625881Ssam * Write a command out to the VIOC 79725881Ssam */ 79825881Ssam vcmd(vx, cmdad) 79925881Ssam register int vx; 80025881Ssam register caddr_t cmdad; 80125881Ssam { 80225933Ssam register struct vcmds *cp; 80325881Ssam register struct vx_softc *vs; 80425881Ssam int s; 80525881Ssam 80625881Ssam s = spl8(); 80725881Ssam vs = &vx_softc[vx]; 80825933Ssam /* 80925933Ssam * When the vioc is resetting, don't process 81025933Ssam * anything other than VXC_LIDENT commands. 81125933Ssam */ 81225881Ssam if (vs->vs_state == VXS_RESET && cmdad != NULL) { 81325933Ssam struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd)); 81425881Ssam 81525933Ssam if (vcp->cmd != VXC_LIDENT) { 81625933Ssam vrelease(vs, vcp); 81725881Ssam return (0); 81825881Ssam } 81925881Ssam } 82025881Ssam cp = &vs->vs_cmds; 82125881Ssam if (cmdad != (caddr_t)0) { 82225881Ssam cp->cmdbuf[cp->v_fill] = cmdad; 82325881Ssam if (++cp->v_fill >= VC_CMDBUFL) 82425881Ssam cp->v_fill = 0; 82525881Ssam if (cp->v_fill == cp->v_empty) { 82625881Ssam printf("vx%d: cmd q overflow\n", vx); 82725881Ssam vxstreset(vx); 82825881Ssam splx(s); 82925881Ssam return (0); 83025881Ssam } 83125881Ssam cp->v_cmdsem++; 83225881Ssam } 83325881Ssam if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) { 83425881Ssam cp->v_cmdsem--; 83525881Ssam cp->v_curcnt++; 83625881Ssam vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR); 83725881Ssam } 83825881Ssam splx(s); 83925881Ssam return (1); 84025881Ssam } 84125881Ssam 84225881Ssam /* 84325881Ssam * VIOC acknowledge interrupt. The VIOC has received the new 84425881Ssam * command. If no errors, the new command becomes one of 16 (max) 84525881Ssam * current commands being executed. 84625881Ssam */ 84725881Ssam vackint(vx) 84825881Ssam register vx; 84925881Ssam { 85025933Ssam register struct vxdevice *vp; 85125933Ssam register struct vcmds *cp; 85225881Ssam struct vx_softc *vs; 85325881Ssam int s; 85425881Ssam 85525881Ssam scope_out(5); 85625881Ssam vs = &vx_softc[vx]; 85729954Skarels if (vs->vs_type) /* Its a BOP */ 85825881Ssam return; 85925881Ssam s = spl8(); 86025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 86125881Ssam cp = &vs->vs_cmds; 86225933Ssam if (vp->v_vcid&V_ERR) { 86325881Ssam register char *resp; 86425881Ssam register i; 86525933Ssam 86630372Skarels printf("vx%d: ackint error type %x v_dcd %x\n", vx, 86725881Ssam vp->v_vcid & 07, vp->v_dcd & 0xff); 86825881Ssam resp = (char *)vs->vs_mricmd; 86925881Ssam for (i = 0; i < 16; i++) 87025881Ssam printf("%x ", resp[i]&0xff); 87125881Ssam printf("\n"); 87225881Ssam splx(s); 87325881Ssam vxstreset(vx); 87425881Ssam return; 87525881Ssam } 87625881Ssam if ((vp->v_hdwre&017) == CMDquals) { 87725881Ssam #ifdef VX_DEBUG 87825881Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ 87925933Ssam struct vxcmd *cp1, *cp0; 88025881Ssam 88125933Ssam cp0 = (struct vxcmd *) 88225933Ssam ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd)); 88325881Ssam if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) { 88425881Ssam cp1 = vobtain(vs); 88525881Ssam *cp1 = *cp0; 88625881Ssam vxintr4 &= ~VXERR4; 88725881Ssam (void) vcmd(vx, &cp1->cmd); 88825881Ssam } 88925881Ssam } 89025881Ssam #endif 89125881Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty]; 89225881Ssam if (++cp->v_empty >= VC_CMDBUFL) 89325881Ssam cp->v_empty = 0; 89425881Ssam } 89525881Ssam if (++cp->v_itrempt >= VC_IQLEN) 89625881Ssam cp->v_itrempt = 0; 89725881Ssam vintempt(vx); 89825881Ssam splx(s); 89925881Ssam (void) vcmd(vx, (caddr_t)0); /* queue next cmd, if any */ 90025881Ssam } 90125881Ssam 90225881Ssam /* 90325881Ssam * Command Response interrupt. The Vioc has completed 90425881Ssam * a command. The command may now be returned to 90525881Ssam * the appropriate device driver. 90625881Ssam */ 90725881Ssam vcmdrsp(vx) 90825881Ssam register vx; 90925881Ssam { 91025933Ssam register struct vxdevice *vp; 91125933Ssam register struct vcmds *cp; 91225881Ssam register caddr_t cmd; 91325881Ssam register struct vx_softc *vs; 91425881Ssam register char *resp; 91525881Ssam register k; 91625881Ssam register int s; 91725881Ssam 91825881Ssam scope_out(6); 91925881Ssam vs = &vx_softc[vx]; 92025881Ssam if (vs->vs_type) { /* Its a BOP */ 92125881Ssam printf("vx%d: vcmdrsp interrupt\n", vx); 92225881Ssam return; 92325881Ssam } 92425881Ssam s = spl8(); 92525881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 92625881Ssam cp = &vs->vs_cmds; 92725881Ssam resp = (char *)vp + (vp->v_rspoff&0x7fff); 92825881Ssam if (((k = resp[1])&V_UNBSY) == 0) { 92925881Ssam printf("vx%d: cmdresp debug\n", vx); 93025881Ssam splx(s); 93125881Ssam vxstreset(vx); 93225881Ssam return; 93325881Ssam } 93425881Ssam k &= VCMDLEN-1; 93525881Ssam cmd = cp->v_curcmd[k]; 93625881Ssam cp->v_curcmd[k] = (caddr_t)0; 93725881Ssam cp->v_curcnt--; 93825881Ssam k = *((short *)&resp[4]); /* cmd operation code */ 93925881Ssam if ((k&0xff00) == VXC_LIDENT) /* want hiport number */ 94025881Ssam for (k = 0; k < VRESPLEN; k++) 94125881Ssam cmd[k] = resp[k+4]; 94225881Ssam resp[1] = 0; 94325881Ssam vxxint(vx, (struct vxcmd *)cmd); 94425881Ssam if (vs->vs_state == VXS_READY) 94525881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 94625881Ssam splx(s); 94725881Ssam } 94825881Ssam 94925881Ssam /* 95025881Ssam * Unsolicited interrupt. 95125881Ssam */ 95225881Ssam vunsol(vx) 95325881Ssam register vx; 95425881Ssam { 95525933Ssam register struct vxdevice *vp; 95625881Ssam struct vx_softc *vs; 95725881Ssam int s; 95825881Ssam 95925881Ssam scope_out(1); 96025881Ssam vs = &vx_softc[vx]; 96125881Ssam if (vs->vs_type) { /* Its a BOP */ 96225881Ssam printf("vx%d: vunsol from BOP\n", vx); 96325881Ssam return; 96425881Ssam } 96525881Ssam s = spl8(); 96625881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 96725881Ssam if (vp->v_uqual&V_UNBSY) { 96825881Ssam vxrint(vx); 96925881Ssam vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR); 97025881Ssam #ifdef notdef 97125881Ssam } else { 97225881Ssam printf("vx%d: unsolicited interrupt error\n", vx); 97325881Ssam splx(s); 97425881Ssam vxstreset(vx); 97525881Ssam #endif 97625881Ssam } 97725881Ssam splx(s); 97825881Ssam } 97925881Ssam 98025881Ssam /* 98125933Ssam * Enqueue an interrupt. 98225881Ssam */ 98325881Ssam vinthandl(vx, item) 98425881Ssam register int vx; 98525881Ssam register item; 98625881Ssam { 98725881Ssam register struct vcmds *cp; 98825881Ssam int empty; 98925881Ssam 99025881Ssam cp = &vx_softc[vx].vs_cmds; 99125933Ssam empty = (cp->v_itrfill == cp->v_itrempt); 99225881Ssam cp->v_itrqueu[cp->v_itrfill] = item; 99325881Ssam if (++cp->v_itrfill >= VC_IQLEN) 99425881Ssam cp->v_itrfill = 0; 99525881Ssam if (cp->v_itrfill == cp->v_itrempt) { 99625881Ssam printf("vx%d: interrupt q overflow\n", vx); 99725881Ssam vxstreset(vx); 99825881Ssam } else if (empty) 99925881Ssam vintempt(vx); 100025881Ssam } 100125881Ssam 100225881Ssam vintempt(vx) 100325881Ssam register int vx; 100425881Ssam { 100525881Ssam register struct vcmds *cp; 100625881Ssam register struct vxdevice *vp; 100725881Ssam register short item; 100825881Ssam register short *intr; 100925881Ssam 101025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 101125881Ssam if (vp->v_vioc&V_BSY) 101225881Ssam return; 101325881Ssam cp = &vx_softc[vx].vs_cmds; 101425881Ssam if (cp->v_itrempt == cp->v_itrfill) 101525881Ssam return; 101625881Ssam item = cp->v_itrqueu[cp->v_itrempt]; 101725881Ssam intr = (short *)&vp->v_vioc; 101825881Ssam switch ((item >> 8)&03) { 101925881Ssam 102025881Ssam case CMDquals: { /* command */ 102125881Ssam int phys; 102225881Ssam 102325881Ssam if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 102425881Ssam break; 102525881Ssam vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 102625881Ssam phys = vtoph((struct proc *)0, 102725881Ssam (unsigned)cp->cmdbuf[cp->v_empty]); 102825881Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 102925881Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 103025881Ssam vp->v_vcbsy = V_BSY; 103125881Ssam *intr = item; 103225881Ssam scope_out(4); 103325881Ssam break; 103425881Ssam } 103525881Ssam 103625881Ssam case RSPquals: /* command response */ 103725881Ssam *intr = item; 103825881Ssam scope_out(7); 103925881Ssam break; 104025881Ssam 104125881Ssam case UNSquals: /* unsolicited interrupt */ 104225881Ssam vp->v_uqual = 0; 104325881Ssam *intr = item; 104425881Ssam scope_out(2); 104525881Ssam break; 104625881Ssam } 104725881Ssam } 104825881Ssam 104925881Ssam /* 105025881Ssam * Start a reset on a vioc after error (hopefully) 105125881Ssam */ 105225881Ssam vxstreset(vx) 105325881Ssam register vx; 105425881Ssam { 105525881Ssam register struct vx_softc *vs; 105625933Ssam register struct vxdevice *vp; 105725881Ssam register struct vxcmd *cp; 105825881Ssam register int j; 105925881Ssam extern int vxinreset(); 106025881Ssam int s; 106125881Ssam 106225881Ssam s = spl8() ; 106325881Ssam vs = &vx_softc[vx]; 106425881Ssam if (vs->vs_state == VXS_RESET) { /* avoid recursion */ 106525881Ssam splx(s); 106625881Ssam return; 106725881Ssam } 106825881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 106925881Ssam /* 107025881Ssam * Zero out the vioc structures, mark the vioc as being 107125881Ssam * reset, reinitialize the free command list, reset the vioc 107225881Ssam * and start a timer to check on the progress of the reset. 107325881Ssam */ 107425881Ssam bzero((caddr_t)vs, (unsigned)sizeof (*vs)); 107525881Ssam 107625881Ssam /* 107725881Ssam * Setting VXS_RESET prevents others from issuing 107825881Ssam * commands while allowing currently queued commands to 107925881Ssam * be passed to the VIOC. 108025881Ssam */ 108125881Ssam vs->vs_state = VXS_RESET; 108225881Ssam /* init all cmd buffers */ 108325881Ssam for (j = 0; j < NVCXBUFS; j++) { 108425933Ssam cp = &vs->vs_lst[j]; 108525933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 108625881Ssam } 108725933Ssam vs->vs_avail = &vs->vs_lst[0]; 108825933Ssam cp->c_fwd = (struct vxcmd *)0; 108925881Ssam printf("vx%d: reset...", vx); 109025881Ssam vp->v_fault = 0; 109125881Ssam vp->v_vioc = V_BSY; 109225933Ssam vp->v_hdwre = V_RESET; /* generate reset interrupt */ 109325881Ssam timeout(vxinreset, (caddr_t)vx, hz*5); 109425881Ssam splx(s); 109525881Ssam } 109625881Ssam 109725881Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 109825881Ssam vxinreset(vx) 109925881Ssam int vx; 110025881Ssam { 110125933Ssam register struct vxdevice *vp; 110225881Ssam int s = spl8(); 110325881Ssam 110425881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 110525881Ssam /* 110625881Ssam * See if the vioc has reset. 110725881Ssam */ 110825881Ssam if (vp->v_fault != VXF_READY) { 110925881Ssam printf("failed\n"); 111025881Ssam splx(s); 111125881Ssam return; 111225881Ssam } 111325881Ssam /* 111425881Ssam * Send a LIDENT to the vioc and mess with carrier flags 111525881Ssam * on parallel printer ports. 111625881Ssam */ 111729954Skarels vxinit(vx, 0); 111825881Ssam splx(s); 111925881Ssam } 112025881Ssam 112125881Ssam /* 112225933Ssam * Finish the reset on the vioc after an error (hopefully). 112325933Ssam * 112425881Ssam * Restore modem control, parameters and restart output. 112525881Ssam * Since the vioc can handle no more then 24 commands at a time 112625881Ssam * and we could generate as many as 48 commands, we must do this in 112725881Ssam * phases, issuing no more then 16 commands at a time. 112825881Ssam */ 112925881Ssam vxfnreset(vx, cp) 113025881Ssam register int vx; 113125881Ssam register struct vxcmd *cp; 113225881Ssam { 113325881Ssam register struct vx_softc *vs; 113425933Ssam register struct vxdevice *vp ; 113525881Ssam register struct tty *tp, *tp0; 113625881Ssam register int i; 113725881Ssam #ifdef notdef 113825881Ssam register int on; 113925881Ssam #endif 114025881Ssam extern int vxrestart(); 114125881Ssam int s = spl8(); 114225881Ssam 114325881Ssam vs = &vx_softc[vx]; 114425881Ssam vs->vs_loport = cp->par[5]; 114525881Ssam vs->vs_hiport = cp->par[7]; 114625881Ssam vrelease(vs, cp); 114725881Ssam vs->vs_nbr = vx; /* assign VIOC-X board number */ 114825881Ssam vs->vs_state = VXS_READY; 114925881Ssam 115025881Ssam vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 115125881Ssam vp->v_vcid = 0; 115225881Ssam 115325881Ssam /* 115425881Ssam * Restore modem information and control. 115525881Ssam */ 115625881Ssam tp0 = &vx_tty[vx*16]; 115725881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 115825881Ssam tp = tp0 + i; 115925881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 116025881Ssam tp->t_state &= ~TS_CARR_ON; 116125881Ssam vcmodem(tp->t_dev, VMOD_ON); 116225881Ssam if (tp->t_state&TS_CARR_ON) 116329954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 116429954Skarels else if (tp->t_state & TS_ISOPEN) 116529954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 116625881Ssam } 116729954Skarels #ifdef notdef 116825881Ssam /* 116925881Ssam * If carrier has changed while we were resetting, 117025881Ssam * take appropriate action. 117125881Ssam */ 117225881Ssam on = vp->v_dcd & 1<<i; 117329954Skarels if (on && (tp->t_state&TS_CARR_ON) == 0) 117429954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 117529954Skarels else if (!on && tp->t_state&TS_CARR_ON) 117629954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 117725881Ssam #endif 117825881Ssam } 117925881Ssam vs->vs_state = VXS_RESET; 118025881Ssam timeout(vxrestart, (caddr_t)vx, hz); 118125881Ssam splx(s); 118225881Ssam } 118325881Ssam 118425881Ssam /* 118525881Ssam * Restore a particular aspect of the VIOC. 118625881Ssam */ 118725881Ssam vxrestart(vx) 118825881Ssam int vx; 118925881Ssam { 119025881Ssam register struct tty *tp, *tp0; 119125881Ssam register struct vx_softc *vs; 119230372Skarels register int i, count; 119325881Ssam int s = spl8(); 119425881Ssam 119530372Skarels count = vx >> 8; 119625881Ssam vx &= 0xff; 119725881Ssam vs = &vx_softc[vx]; 119825881Ssam vs->vs_state = VXS_READY; 119925881Ssam tp0 = &vx_tty[vx*16]; 120025881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 120125881Ssam tp = tp0 + i; 120230372Skarels if (count != 0) { 120325881Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 120425881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) 120525881Ssam vxstart(tp); /* restart pending output */ 120625881Ssam } else { 120725881Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 120825881Ssam vxcparam(tp->t_dev, 0); 120925881Ssam } 121025881Ssam } 121130372Skarels if (count == 0) { 121225881Ssam vs->vs_state = VXS_RESET; 121325881Ssam timeout(vxrestart, (caddr_t)(vx + 1*256), hz); 121425881Ssam } else 121525881Ssam printf("done\n"); 121625881Ssam splx(s); 121725881Ssam } 121825881Ssam 121925881Ssam vxreset(dev) 122025881Ssam dev_t dev; 122125881Ssam { 122225881Ssam 122330372Skarels vxstreset((int)VXUNIT(minor(dev))); /* completes asynchronously */ 122425881Ssam } 122525881Ssam 122630372Skarels #ifdef notdef 122725881Ssam vxfreset(vx) 122825881Ssam register int vx; 122925881Ssam { 123025881Ssam struct vba_device *vi; 123125881Ssam 123225881Ssam if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0) 123325881Ssam return (ENODEV); 123425881Ssam vx_softc[vx].vs_state = VXS_READY; 123525881Ssam vxstreset(vx); 123625881Ssam return (0); /* completes asynchronously */ 123725881Ssam } 123830372Skarels #endif 123925881Ssam 124025881Ssam vcmodem(dev, flag) 124125881Ssam dev_t dev; 124225881Ssam { 124325881Ssam struct tty *tp; 124425881Ssam register struct vxcmd *cp; 124525881Ssam register struct vx_softc *vs; 124625881Ssam register struct vxdevice *kp; 124725881Ssam register port; 124825881Ssam int unit; 124925881Ssam 125025881Ssam unit = minor(dev); 125125881Ssam tp = &vx_tty[unit]; 125225881Ssam vs = (struct vx_softc *)tp->t_addr; 125330372Skarels if (vs->vs_state != VXS_READY) 125430372Skarels return; 125525881Ssam cp = vobtain(vs); 125625881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr; 125725881Ssam 125825881Ssam port = unit & 017; 125925881Ssam /* 126025881Ssam * Issue MODEM command 126125881Ssam */ 126225881Ssam cp->cmd = VXC_MDMCTL; 126330372Skarels if (flag == VMOD_ON) { 126430372Skarels if (vs->vs_softCAR & (1 << port)) 126530372Skarels cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS; 126630372Skarels else 126730372Skarels cp->par[0] = V_AUTO | V_DTR_ON | V_RTS; 126830372Skarels } else 126930372Skarels cp->par[0] = V_DTR_OFF; 127025881Ssam cp->par[1] = port; 127130372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 127230372Skarels if (vs->vs_softCAR & (1 << port)) 127330372Skarels kp->v_dcd |= (1 << port); 127430372Skarels if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON) 127530372Skarels tp->t_state |= TS_CARR_ON; 127625881Ssam } 127725881Ssam 127825881Ssam /* 127925881Ssam * VCMINTR called when an unsolicited interrup occurs signaling 128025881Ssam * some change of modem control state. 128125881Ssam */ 128225881Ssam vcmintr(vx) 128325881Ssam register vx; 128425881Ssam { 128525881Ssam register struct vxdevice *kp; 128625881Ssam register struct tty *tp; 128725881Ssam register port; 128830372Skarels register struct vx_softc *vs; 128925881Ssam 129025881Ssam kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr; 129125881Ssam port = kp->v_usdata[0] & 017; 129225881Ssam tp = &vx_tty[vx*16+port]; 129330372Skarels vs = &vx_softc[vx]; 129425881Ssam 129529954Skarels if (kp->v_ustat & DCD_ON) 129629954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 129729954Skarels else if ((kp->v_ustat & DCD_OFF) && 129830372Skarels ((vs->vs_softCAR & (1 << port))) == 0 && 129929954Skarels (*linesw[tp->t_line].l_modem)(tp, 0) == 0) { 130029954Skarels register struct vcmds *cp; 130129954Skarels register struct vxcmd *cmdp; 130225881Ssam 130330372Skarels /* clear all pending transmits */ 130429954Skarels if (tp->t_state&(TS_BUSY|TS_FLUSH) && 130529954Skarels vs->vs_vers == VXV_NEW) { 130629954Skarels int i, cmdfound = 0; 130725881Ssam 130829954Skarels cp = &vs->vs_cmds; 130929954Skarels for (i = cp->v_empty; i != cp->v_fill; ) { 131029954Skarels cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1); 131129954Skarels if ((cmdp->cmd == VXC_XMITDTA || 131229954Skarels cmdp->cmd == VXC_XMITIMM) && 131329954Skarels ((struct vxmit *)cmdp->par)->line == port) { 131429954Skarels cmdfound++; 131525881Ssam cmdp->cmd = VXC_FDTATOX; 131625881Ssam cmdp->par[1] = port; 131725881Ssam } 131829954Skarels if (++i >= VC_CMDBUFL) 131929954Skarels i = 0; 132025881Ssam } 132129954Skarels if (cmdfound) 132229954Skarels tp->t_state &= ~(TS_BUSY|TS_FLUSH); 132329954Skarels /* cmd is already in vioc, have to flush it */ 132429954Skarels else { 132529954Skarels cmdp = vobtain(vs); 132629954Skarels cmdp->cmd = VXC_FDTATOX; 132729954Skarels cmdp->par[1] = port; 132830372Skarels (void) vcmd(vx, (caddr_t)&cmdp->cmd); 132925881Ssam } 133025881Ssam } 133129954Skarels } else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) { 133230372Skarels (*linesw[tp->t_line].l_rint)((tp->t_flags & RAW) ? 133330372Skarels 0 : tp->t_intrc, tp); 133425881Ssam return; 133525881Ssam } 133625881Ssam } 133725881Ssam #endif 1338