134406Skarels /* 234406Skarels * Copyright (c) 1988 Regents of the University of California. 335057Skarels * All rights reserved. 434406Skarels * 535057Skarels * This code is derived from software contributed to Berkeley by 635057Skarels * Computer Consoles Inc. 735057Skarels * 835057Skarels * Redistribution and use in source and binary forms are permitted 935057Skarels * provided that the above copyright notice and this paragraph are 1035057Skarels * duplicated in all such forms and that any documentation, 1135057Skarels * advertising materials, and other materials related to such 1235057Skarels * distribution and use acknowledge that the software was developed 1335057Skarels * by the University of California, Berkeley. The name of the 1435057Skarels * University may not be used to endorse or promote products derived 1535057Skarels * from this software without specific prior written permission. 1635057Skarels * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 1735057Skarels * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 1835057Skarels * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE. 1935057Skarels * 20*42948Smarc * @(#)vx.c 7.7 (Berkeley) 06/06/90 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 "user.h" 3625877Ssam #include "map.h" 3725877Ssam #include "buf.h" 3825877Ssam #include "conf.h" 3925877Ssam #include "file.h" 4025877Ssam #include "proc.h" 4125877Ssam #include "vm.h" 4225881Ssam #include "kernel.h" 4329954Skarels #include "syslog.h" 4425675Ssam 4534406Skarels #include "../tahoe/pte.h" 4634406Skarels 4725675Ssam #include "../tahoevba/vbavar.h" 4838114Sbostic #include "../tahoevba/vbaparam.h" 4925881Ssam #include "../tahoevba/vxreg.h" 5025675Ssam #include "../tahoevba/scope.h" 5124003Ssam 5225881Ssam #ifdef VX_DEBUG 5325881Ssam long vxintr4 = 0; 5425948Ssam #define VXERR4 1 5525948Ssam #define VXNOBUF 2 5625881Ssam long vxdebug = 0; 5725948Ssam #define VXVCM 1 5825948Ssam #define VXVCC 2 5925948Ssam #define VXVCX 4 6025881Ssam #endif 6124003Ssam 6225881Ssam /* 6325881Ssam * Interrupt type bits passed to vinthandl(). 6425881Ssam */ 6525948Ssam #define CMDquals 0 /* command completed interrupt */ 6625948Ssam #define RSPquals 1 /* command response interrupt */ 6725948Ssam #define UNSquals 2 /* unsolicited interrupt */ 6824003Ssam 6930372Skarels #define VXUNIT(n) ((n) >> 4) 7030372Skarels #define VXPORT(n) ((n) & 0xf) 7130372Skarels 7225881Ssam struct tty vx_tty[NVX*16]; 7329954Skarels #ifndef lint 7429954Skarels int nvx = NVX*16; 7529954Skarels #endif 7625881Ssam int vxstart(), ttrstrt(); 7725881Ssam struct vxcmd *vobtain(), *nextcmd(); 7824003Ssam 7924003Ssam /* 8024003Ssam * Driver information for auto-configuration stuff. 8124003Ssam */ 8224003Ssam int vxprobe(), vxattach(), vxrint(); 8325881Ssam struct vba_device *vxinfo[NVX]; 8424003Ssam long vxstd[] = { 0 }; 8524003Ssam struct vba_driver vxdriver = 8625857Ssam { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo }; 8724003Ssam 8825881Ssam struct vx_softc { 8940738Skarels struct vxdevice *vs_addr; /* H/W address */ 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_state; /* controller state */ 10125948Ssam #define VXS_READY 0 /* ready for commands */ 10225948Ssam #define VXS_RESET 1 /* in process of reseting */ 10330372Skarels u_short vs_softCAR; /* soft carrier */ 10440738Skarels u_int vs_ivec; /* interrupt vector base */ 10525881Ssam caddr_t vs_mricmd; /* most recent issued cmd */ 10640738Skarels /* The remaining fields are zeroed on reset... */ 10740738Skarels #define vs_zero vs_xmtcnt 10840738Skarels int vs_xmtcnt; /* xmit commands pending */ 10925881Ssam struct vxcmd *vs_avail;/* next available command buffer */ 11025881Ssam struct vxcmd *vs_build; 11125881Ssam struct vxcmd vs_lst[NVCXBUFS]; 11225881Ssam struct vcmds vs_cmds; 11325881Ssam } vx_softc[NVX]; 11424003Ssam 11537608Smarc struct speedtab vxspeedtab[] = { 11637608Smarc EXTA, V19200, 11737608Smarc EXTB, V19200, 11837608Smarc 19200, V19200, 11937608Smarc 9600, 13, 12037608Smarc 4800, 12, 12137608Smarc 2400, 11, 12237608Smarc 1800, 10, 12337608Smarc 1200, 9, 12437608Smarc 600, 8, 12537608Smarc 300, 7, 12637608Smarc 200, 6, 12737608Smarc 150, 5, 12837608Smarc 134, 4, 12937608Smarc 110, 3, 13037608Smarc 75, 2, 13137608Smarc 50, 1, 13237608Smarc 0, 0, 13337608Smarc -1, -1, 13437608Smarc }; 13537608Smarc 13625857Ssam vxprobe(reg, vi) 13724003Ssam caddr_t reg; 13825857Ssam struct vba_device *vi; 13924003Ssam { 14025857Ssam register int br, cvec; /* must be r12, r11 */ 14138114Sbostic register struct vxdevice *vp; 14225881Ssam register struct vx_softc *vs; 14338114Sbostic struct pte *dummypte; 14424003Ssam 14524003Ssam #ifdef lint 14624003Ssam br = 0; cvec = br; br = cvec; 14740738Skarels vackint(0); vunsol(0); vcmdrsp(0); 14840738Skarels #ifdef VX_DEBUG 14940738Skarels vxfreset(0); 15024003Ssam #endif 15140738Skarels #endif /* lint */ 15240738Skarels /* 15340738Skarels * If on an HCX-9, the device has a 32-bit address, 15440738Skarels * and we receive that address so we can set up a map. 15540738Skarels * On VERSAbus devices, the address is 24-bit, and is 15640738Skarels * already mapped (into vmem[]) by autoconf. 15740738Skarels */ 15840738Skarels if (!(reg >= vmem && reg < &vmem[ctob(VBIOSIZE)]) && /* XXX */ 15940738Skarels !vbmemalloc(16, reg, &dummypte, ®)) { 16038114Sbostic printf("vx%d: vbmemalloc failed.\n", vi->ui_unit); 16138114Sbostic return(0); 16238114Sbostic } 16338114Sbostic vp = (struct vxdevice *)reg; 16425675Ssam if (badaddr((caddr_t)vp, 1)) 16525675Ssam return (0); 16625675Ssam vp->v_fault = 0; 16725675Ssam vp->v_vioc = V_BSY; 16825675Ssam vp->v_hdwre = V_RESET; /* reset interrupt */ 16924003Ssam DELAY(4000000); 17025881Ssam if (vp->v_fault != VXF_READY) 17125675Ssam return (0); 17225881Ssam vs = &vx_softc[vi->ui_unit]; 17325857Ssam #ifdef notdef 17425857Ssam /* 17525857Ssam * Align vioc interrupt vector base to 4 vector 17625857Ssam * boundary and fitting in 8 bits (is this necessary, 17725857Ssam * wish we had documentation). 17825857Ssam */ 17925857Ssam if ((vi->ui_hd->vh_lastiv -= 3) > 0xff) 18025857Ssam vi->ui_hd->vh_lastiv = 0xff; 18125881Ssam vs->vs_ivec = vi->ui_hd->vh_lastiv = vi->ui_hd->vh_lastiv &~ 0x3; 18225857Ssam #else 18325881Ssam vs->vs_ivec = 0x40+vi->ui_unit*4; 18425857Ssam #endif 18525881Ssam br = 0x18, cvec = vs->vs_ivec; /* XXX */ 18625881Ssam return (sizeof (struct vxdevice)); 18724003Ssam } 18824003Ssam 18925857Ssam vxattach(vi) 19025857Ssam register struct vba_device *vi; 19124003Ssam { 19240738Skarels register struct vx_softc *vs = &vx_softc[vi->ui_unit]; 19325675Ssam 19440738Skarels vs->vs_softCAR = vi->ui_flags; 19540738Skarels vs->vs_addr = (struct vxdevice *)vi->ui_addr; 19629954Skarels vxinit(vi->ui_unit, 1); 19724003Ssam } 19824003Ssam 19924003Ssam /* 20024003Ssam * Open a VX line. 20124003Ssam */ 20225675Ssam /*ARGSUSED*/ 20324003Ssam vxopen(dev, flag) 20425881Ssam dev_t dev; 20525881Ssam int flag; 20624003Ssam { 20724003Ssam register struct tty *tp; /* pointer to tty struct for port */ 20825881Ssam register struct vx_softc *vs; 20925881Ssam register struct vba_device *vi; 21040738Skarels int unit, vx, s, error = 0; 21137608Smarc int vxparam(); 21224003Ssam 21325881Ssam unit = minor(dev); 21430372Skarels vx = VXUNIT(unit); 21530372Skarels if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0) 21625881Ssam return (ENXIO); 21730372Skarels vs = &vx_softc[vx]; 21825881Ssam tp = &vx_tty[unit]; 21930372Skarels unit = VXPORT(unit); 22025881Ssam if (tp->t_state&TS_XCLUDE && u.u_uid != 0) 22125881Ssam return (EBUSY); 22230372Skarels if (unit < vs->vs_loport || unit > vs->vs_hiport) 22325881Ssam return (ENXIO); 22425881Ssam tp->t_addr = (caddr_t)vs; 22525881Ssam tp->t_oproc = vxstart; 22637608Smarc tp->t_param = vxparam; 22725881Ssam tp->t_dev = dev; 22825881Ssam s = spl8(); 22925881Ssam tp->t_state |= TS_WOPEN; 23025881Ssam if ((tp->t_state&TS_ISOPEN) == 0) { 23125881Ssam ttychars(tp); 23225881Ssam if (tp->t_ispeed == 0) { 23337608Smarc tp->t_iflag = TTYDEF_IFLAG; 23437608Smarc tp->t_oflag = TTYDEF_OFLAG; 23537608Smarc tp->t_lflag = TTYDEF_LFLAG; 23637608Smarc tp->t_cflag = TTYDEF_CFLAG; 23737608Smarc tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED; 23824003Ssam } 23937608Smarc vxparam(tp, &tp->t_termios); 24037608Smarc ttsetwater(tp); 24124003Ssam } 24230372Skarels vcmodem(dev, VMOD_ON); 24337608Smarc while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) && 24437608Smarc (tp->t_state&TS_CARR_ON) == 0) 245*42948Smarc if ((error = tsleep((caddr_t)&tp->t_rawq, TTIPRI | PCATCH, 246*42948Smarc ttopen, 0)) || 247*42948Smarc (error = ttclosed(tp))) 24840738Skarels break; 24940738Skarels if (error == 0) 25040738Skarels error = (*linesw[tp->t_line].l_open)(dev,tp); 25125881Ssam splx(s); 25225881Ssam return (error); 25324003Ssam } 25424003Ssam 25524003Ssam /* 25624003Ssam * Close a VX line. 25724003Ssam */ 25825675Ssam /*ARGSUSED*/ 25924003Ssam vxclose(dev, flag) 26025881Ssam dev_t dev; 26125881Ssam int flag; 26224003Ssam { 26324003Ssam register struct tty *tp; 26440738Skarels int unit, s, error = 0; 26524003Ssam 26625881Ssam unit = minor(dev); 26725881Ssam tp = &vx_tty[unit]; 26825881Ssam s = spl8(); 26924003Ssam (*linesw[tp->t_line].l_close)(tp); 27037608Smarc if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0) 27130372Skarels vcmodem(dev, VMOD_OFF); 27224003Ssam /* wait for the last response */ 27340738Skarels while (tp->t_state&TS_FLUSH && error == 0) 27440738Skarels error = tsleep((caddr_t)&tp->t_state, TTOPRI | PCATCH, 27540738Skarels ttclos, 0); 27625881Ssam splx(s); 27740738Skarels if (error) 27840738Skarels return (error); 27940738Skarels return (ttyclose(tp)); 28024003Ssam } 28124003Ssam 28224003Ssam /* 28324003Ssam * Read from a VX line. 28424003Ssam */ 28537608Smarc vxread(dev, uio, flag) 28624003Ssam dev_t dev; 28724003Ssam struct uio *uio; 28824003Ssam { 28925881Ssam struct tty *tp = &vx_tty[minor(dev)]; 29025881Ssam 29137608Smarc return ((*linesw[tp->t_line].l_read)(tp, uio, flag)); 29224003Ssam } 29324003Ssam 29424003Ssam /* 29524003Ssam * write on a VX line 29624003Ssam */ 29737608Smarc vxwrite(dev, uio, flag) 29824003Ssam dev_t dev; 29924003Ssam struct uio *uio; 30024003Ssam { 30125881Ssam register struct tty *tp = &vx_tty[minor(dev)]; 30225881Ssam 30337608Smarc return ((*linesw[tp->t_line].l_write)(tp, uio, flag)); 30424003Ssam } 30524003Ssam 30624003Ssam /* 30724003Ssam * VIOCX unsolicited interrupt. 30824003Ssam */ 30925881Ssam vxrint(vx) 31025881Ssam register vx; 31124003Ssam { 31225881Ssam register struct tty *tp, *tp0; 31325881Ssam register struct vxdevice *addr; 31425881Ssam register struct vx_softc *vs; 31525881Ssam struct vba_device *vi; 31625881Ssam register int nc, c; 31725881Ssam register struct silo { 31840738Skarels u_char data, port; 31925881Ssam } *sp; 32025881Ssam short *osp; 32125881Ssam int overrun = 0; 32224003Ssam 32325881Ssam vi = vxinfo[vx]; 32425881Ssam if (vi == 0 || vi->ui_alive == 0) 32525881Ssam return; 32625881Ssam addr = (struct vxdevice *)vi->ui_addr; 32725881Ssam switch (addr->v_uqual&037) { 32824003Ssam case 0: 32924003Ssam break; 33024003Ssam case 2: 33140738Skarels if (addr->v_ustat == VP_SILO_OFLOW) 33240738Skarels log(LOG_ERR, "vx%d: input silo overflow\n", vx); 33340738Skarels else { 33440738Skarels printf("vx%d: vc proc err, ustat %x\n", 33540738Skarels vx, addr->v_ustat); 33640738Skarels vxstreset(vx); 33740738Skarels } 33830372Skarels return; 33924003Ssam case 3: 34025881Ssam vcmintr(vx); 34130372Skarels return; 34224003Ssam case 4: 34330372Skarels return; 34424003Ssam default: 34530372Skarels printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual); 34625881Ssam vxstreset(vx); 34730372Skarels return; 34824003Ssam } 34925881Ssam vs = &vx_softc[vx]; 35025881Ssam if (vs->vs_vers == VXV_NEW) 35125881Ssam sp = (struct silo *)((caddr_t)addr + *(short *)addr->v_usdata); 35225881Ssam else 35325881Ssam sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6)); 35425881Ssam nc = *(osp = (short *)sp); 35525881Ssam if (nc == 0) 35630372Skarels return; 35725881Ssam if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) { 35825881Ssam printf("vx%d: %d exceeds silo size\n", nc); 35925881Ssam nc = vs->vs_silosiz; 36024003Ssam } 36125881Ssam tp0 = &vx_tty[vx*16]; 36225881Ssam sp = (struct silo *)(((short *)sp)+1); 36325881Ssam for (; nc > 0; nc--, sp = (struct silo *)(((short *)sp)+1)) { 36425881Ssam c = sp->port & 017; 36525881Ssam if (vs->vs_loport > c || c > vs->vs_hiport) 36625881Ssam continue; 36725881Ssam tp = tp0 + c; 36825881Ssam if( (tp->t_state&TS_ISOPEN) == 0) { 36924003Ssam wakeup((caddr_t)&tp->t_rawq); 37024003Ssam continue; 37124003Ssam } 37237608Smarc c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f); 37325881Ssam if ((sp->port&VX_RO) == VX_RO && !overrun) { 37429954Skarels log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit); 37525881Ssam overrun = 1; 37625881Ssam continue; 37725881Ssam } 37825881Ssam if (sp->port&VX_PE) 37937608Smarc c |= TTY_PE; 38037608Smarc if (sp->port&VX_FE) 38137608Smarc c |= TTY_FE; 38224003Ssam (*linesw[tp->t_line].l_rint)(c, tp); 38324003Ssam } 38425881Ssam *osp = 0; 38524003Ssam } 38624003Ssam 38724003Ssam /* 38825881Ssam * Ioctl for VX. 38924003Ssam */ 39024003Ssam vxioctl(dev, cmd, data, flag) 39125881Ssam dev_t dev; 39225881Ssam caddr_t data; 39324003Ssam { 39425881Ssam register struct tty *tp; 39525881Ssam int error; 39624003Ssam 39725881Ssam tp = &vx_tty[minor(dev)]; 39824003Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 39937608Smarc if (error >= 0) 40025881Ssam return (error); 40125881Ssam error = ttioctl(tp, cmd, data, flag); 40237608Smarc if (error >= 0) 40325881Ssam return (error); 40425881Ssam return (ENOTTY); 40524003Ssam } 40624003Ssam 40737608Smarc vxparam(tp, t) 40837608Smarc struct tty *tp; 40937608Smarc struct termios *t; 41024003Ssam { 41125881Ssam 41237608Smarc return (vxcparam(tp, t, 1)); 41324003Ssam } 41424003Ssam 41524003Ssam /* 41624003Ssam * Set parameters from open or stty into the VX hardware 41724003Ssam * registers. 41824003Ssam */ 41937608Smarc vxcparam(tp, t, wait) 42037608Smarc struct tty *tp; 42137608Smarc struct termios *t; 42225881Ssam int wait; 42324003Ssam { 42425881Ssam register struct vx_softc *vs; 42525881Ssam register struct vxcmd *cp; 42640738Skarels int s, error = 0; 42737608Smarc int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab); 42824003Ssam 42937608Smarc if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed)) 43040738Skarels return (EINVAL); 43125881Ssam vs = (struct vx_softc *)tp->t_addr; 43225881Ssam cp = vobtain(vs); 43324003Ssam s = spl8(); 43425933Ssam /* 43525933Ssam * Construct ``load parameters'' command block 43625933Ssam * to setup baud rates, xon-xoff chars, parity, 43725933Ssam * and stop bits for the specified port. 43825933Ssam */ 43925933Ssam cp->cmd = VXC_LPARAX; 44040738Skarels cp->par[1] = VXPORT(minor(tp->t_dev)); 44137608Smarc /* 44237608Smarc * note: if the hardware does flow control, ^V doesn't work 44337608Smarc * to escape ^S 44437608Smarc */ 44537608Smarc if (t->c_iflag&IXON) { 44637608Smarc if (t->c_cc[VSTART] == _POSIX_VDISABLE) 44737608Smarc cp->par[2] = 0; 44837608Smarc else 44937608Smarc cp->par[2] = t->c_cc[VSTART]; 45037608Smarc if (t->c_cc[VSTOP] == _POSIX_VDISABLE) 45137608Smarc cp->par[3] = 0; 45237608Smarc else 45337608Smarc cp->par[3] = t->c_cc[VSTOP]; 45437608Smarc } else 45537608Smarc cp->par[2] = cp->par[3] = 0; 45630372Skarels #ifdef notnow 45740738Skarels switch (t->c_cflag & CSIZE) { /* XXX */ 45840738Skarels case CS8: 45930372Skarels #endif 46030372Skarels cp->par[4] = BITS8; /* 8 bits of data */ 46130372Skarels #ifdef notnow 46240738Skarels break; 46340738Skarels case CS7: 46430372Skarels cp->par[4] = BITS7; /* 7 bits of data */ 46540738Skarels break; 46640738Skarels case CS6: 46740738Skarels cp->par[4] = BITS6; /* 6 bits of data */ 46840738Skarels break; 46940738Skarels case CS5: 47040738Skarels cp->par[4] = BITS5; /* 5 bits of data */ 47140738Skarels break; 47224003Ssam } 47340738Skarels if ((t->c_cflag & PARENB) == 0) /* XXX */ 47430372Skarels #endif 47540738Skarels cp->par[7] = VNOPARITY; /* no parity */ 47640738Skarels #ifdef notnow 47740738Skarels else if (t->c_cflag&PARODD) 47840738Skarels cp->par[7] = VODDP; /* odd parity */ 47940738Skarels else 48040738Skarels cp->par[7] = VEVENP; /* even parity */ 48140738Skarels #endif 48237608Smarc cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1; 48337608Smarc cp->par[6] = speedcode; 48430372Skarels if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait) 48540738Skarels error = tsleep((caddr_t)cp, TTIPRI | PCATCH, ttyout, 0); 48637608Smarc if ((t->c_ospeed)==0) { 48737608Smarc tp->t_cflag |= HUPCL; 48840738Skarels vcmodem(tp->t_dev, VMOD_OFF); 48937608Smarc } 49024003Ssam splx(s); 49140738Skarels return (error); 49224003Ssam } 49324003Ssam 49424003Ssam /* 49524003Ssam * VIOCX command response interrupt. 49624003Ssam * For transmission, restart output to any active port. 49724003Ssam * For all other commands, just clean up. 49824003Ssam */ 49925881Ssam vxxint(vx, cp) 50025881Ssam register int vx; 50125881Ssam register struct vxcmd *cp; 50224003Ssam { 50330372Skarels register struct vxmit *vp; 50425933Ssam register struct tty *tp, *tp0; 50525933Ssam register struct vx_softc *vs; 50624003Ssam 50725881Ssam vs = &vx_softc[vx]; 50825881Ssam cp = (struct vxcmd *)((long *)cp-1); 50929954Skarels 51025881Ssam switch (cp->cmd&0xff00) { 51125881Ssam 51225881Ssam case VXC_LIDENT: /* initialization complete */ 51325881Ssam if (vs->vs_state == VXS_RESET) { 51425881Ssam vxfnreset(vx, cp); 51525881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 51624003Ssam } 51724003Ssam cp->cmd++; 51824003Ssam return; 51925881Ssam 52025881Ssam case VXC_XMITDTA: 52125881Ssam case VXC_XMITIMM: 52224003Ssam break; 52325881Ssam 52425881Ssam case VXC_LPARAX: 52525675Ssam wakeup((caddr_t)cp); 52625881Ssam /* fall thru... */ 52725881Ssam default: /* VXC_MDMCTL or VXC_FDTATOX */ 52825881Ssam vrelease(vs, cp); 52925881Ssam if (vs->vs_state == VXS_RESET) 53025881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 53124003Ssam return; 53224003Ssam } 53325881Ssam tp0 = &vx_tty[vx*16]; 53425881Ssam vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 53525881Ssam for (; vp >= (struct vxmit *)cp->par; vp--) { 53625881Ssam tp = tp0 + (vp->line & 017); 53724003Ssam tp->t_state &= ~TS_BUSY; 53825881Ssam if (tp->t_state & TS_FLUSH) { 53924003Ssam tp->t_state &= ~TS_FLUSH; 54025881Ssam wakeup((caddr_t)&tp->t_state); 54125881Ssam } else 54224003Ssam ndflush(&tp->t_outq, vp->bcount+1); 54324003Ssam } 54425881Ssam vrelease(vs, cp); 54530372Skarels if (vs->vs_vers == VXV_NEW) 54632112Skarels (*linesw[tp->t_line].l_start)(tp); 54730372Skarels else { 54825881Ssam tp0 = &vx_tty[vx*16 + vs->vs_hiport]; 54925881Ssam for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++) 55032112Skarels (*linesw[tp->t_line].l_start)(tp); 55125881Ssam if ((cp = nextcmd(vs)) != NULL) { /* command to send? */ 55225881Ssam vs->vs_xmtcnt++; 55330372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 55424003Ssam } 55524003Ssam } 55630372Skarels vs->vs_xmtcnt--; 55724003Ssam } 55824003Ssam 55924003Ssam /* 56024003Ssam * Force out partial XMIT command after timeout 56124003Ssam */ 56225881Ssam vxforce(vs) 56325881Ssam register struct vx_softc *vs; 56424003Ssam { 56525881Ssam register struct vxcmd *cp; 56625881Ssam int s; 56724003Ssam 56824003Ssam s = spl8(); 56925881Ssam if ((cp = nextcmd(vs)) != NULL) { 57025881Ssam vs->vs_xmtcnt++; 57130372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 57224003Ssam } 57324003Ssam splx(s); 57424003Ssam } 57524003Ssam 57624003Ssam /* 57724003Ssam * Start (restart) transmission on the given VX line. 57824003Ssam */ 57924003Ssam vxstart(tp) 58025881Ssam register struct tty *tp; 58124003Ssam { 58225675Ssam register short n; 58325933Ssam register struct vx_softc *vs; 58425933Ssam int s, port; 58524003Ssam 58624003Ssam s = spl8(); 58740738Skarels port = VXPORT(minor(tp->t_dev)); 58825881Ssam vs = (struct vx_softc *)tp->t_addr; 58925881Ssam if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) { 59037608Smarc if (tp->t_outq.c_cc <= tp->t_lowat) { 59124003Ssam if (tp->t_state&TS_ASLEEP) { 59224003Ssam tp->t_state &= ~TS_ASLEEP; 59324003Ssam wakeup((caddr_t)&tp->t_outq); 59424003Ssam } 59524003Ssam if (tp->t_wsel) { 59624003Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 59724003Ssam tp->t_wsel = 0; 59824003Ssam tp->t_state &= ~TS_WCOLL; 59924003Ssam } 60024003Ssam } 60125881Ssam if (tp->t_outq.c_cc == 0) { 60224003Ssam splx(s); 60330372Skarels return; 60424003Ssam } 60525877Ssam scope_out(3); 60637608Smarc if (1 || !(tp->t_oflag&OPOST)) /* XXX */ 60730372Skarels n = ndqb(&tp->t_outq, 0); 60830372Skarels else { 60930372Skarels n = ndqb(&tp->t_outq, 0200); 61030372Skarels if (n == 0) { 61125675Ssam n = getc(&tp->t_outq); 61225881Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 61324003Ssam tp->t_state |= TS_TIMEOUT; 61430372Skarels n = 0; 61524003Ssam } 61630372Skarels } 61730372Skarels if (n) { 61824003Ssam tp->t_state |= TS_BUSY; 61930372Skarels vsetq(vs, port, (char *)tp->t_outq.c_cf, n); 62024003Ssam } 62124003Ssam } 62224003Ssam splx(s); 62324003Ssam } 62424003Ssam 62524003Ssam /* 62624003Ssam * Stop output on a line. 62724003Ssam */ 62824003Ssam vxstop(tp) 62925881Ssam register struct tty *tp; 63024003Ssam { 63125881Ssam int s; 63224003Ssam 63324003Ssam s = spl8(); 63425881Ssam if (tp->t_state&TS_BUSY) 63525881Ssam if ((tp->t_state&TS_TTSTOP) == 0) 63624003Ssam tp->t_state |= TS_FLUSH; 63724003Ssam splx(s); 63824003Ssam } 63924003Ssam 64025881Ssam static int vxbbno = -1; 64124003Ssam /* 64224003Ssam * VIOCX Initialization. Makes free lists of command buffers. 64324003Ssam * Resets all viocx's. Issues a LIDENT command to each 64425933Ssam * viocx to establish interrupt vectors and logical port numbers. 64524003Ssam */ 64640738Skarels vxinit(vx, wait) 64725881Ssam register int vx; 64825881Ssam int wait; 64924003Ssam { 65025933Ssam register struct vx_softc *vs; 65125933Ssam register struct vxdevice *addr; 65225933Ssam register struct vxcmd *cp; 65325881Ssam register char *resp; 65425881Ssam register int j; 65530372Skarels char type, *typestring; 65624003Ssam 65725881Ssam vs = &vx_softc[vx]; 65840738Skarels addr = vs->vs_addr; 65925881Ssam type = addr->v_ident; 66025881Ssam vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD; 66125881Ssam if (vs->vs_vers == VXV_NEW) 66225881Ssam vs->vs_silosiz = addr->v_maxsilo; 66325881Ssam switch (type) { 66424003Ssam 66525881Ssam case VXT_VIOCX: 66625881Ssam case VXT_VIOCX|VXT_NEW: 66730372Skarels typestring = "VIOC-X"; 66830372Skarels /* set soft carrier for printer ports */ 66930372Skarels for (j = 0; j < 16; j++) 67040738Skarels if (vs->vs_softCAR & (1 << j) || 67140738Skarels addr->v_portyp[j] == VXT_PARALLEL) { 67230372Skarels vs->vs_softCAR |= 1 << j; 67325881Ssam addr->v_dcd |= 1 << j; 67430372Skarels } 67525881Ssam break; 67624003Ssam 67725881Ssam case VXT_PVIOCX: 67825881Ssam case VXT_PVIOCX|VXT_NEW: 67930372Skarels typestring = "VIOC-X (old connector panel)"; 68025881Ssam break; 68125881Ssam case VXT_VIOCBOP: /* VIOC-BOP */ 68225881Ssam vs->vs_type = 1; 68325881Ssam vs->vs_bop = ++vxbbno; 68425881Ssam printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr); 68540738Skarels goto unsup; 68625933Ssam default: 68725881Ssam printf("vx%d: unknown type %x\n", vx, type); 68840738Skarels unsup: 68930372Skarels vxinfo[vx]->ui_alive = 0; 69025881Ssam return; 69124003Ssam } 69240738Skarels vs->vs_nbr = vx; /* assign board number */ 69325933Ssam vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4; 69425933Ssam /* 69525933Ssam * Initialize all cmd buffers by linking them 69625933Ssam * into a free list. 69725933Ssam */ 69825881Ssam for (j = 0; j < NVCXBUFS; j++) { 69925933Ssam cp = &vs->vs_lst[j]; 70025933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 70125881Ssam } 70225881Ssam vs->vs_avail = &vs->vs_lst[0]; /* set idx to 1st free buf */ 70324003Ssam cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */ 70424003Ssam 70525933Ssam /* 70625933Ssam * Establish the interrupt vectors and define the port numbers. 70725933Ssam */ 70825933Ssam cp = vobtain(vs); 70925933Ssam cp->cmd = VXC_LIDENT; 71025881Ssam cp->par[0] = vs->vs_ivec; /* ack vector */ 71125857Ssam cp->par[1] = cp->par[0]+1; /* cmd resp vector */ 71225857Ssam cp->par[3] = cp->par[0]+2; /* unsol intr vector */ 71325881Ssam cp->par[4] = 15; /* max ports, no longer used */ 71425881Ssam cp->par[5] = 0; /* set 1st port number */ 71530372Skarels (void) vcmd(vx, (caddr_t)&cp->cmd); 71625881Ssam if (!wait) 71725881Ssam return; 71840738Skarels 71925881Ssam for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++) 72025857Ssam ; 72125857Ssam if (j >= 4000000) 72225881Ssam printf("vx%d: didn't respond to LIDENT\n", vx); 72324003Ssam 72424003Ssam /* calculate address of response buffer */ 72525881Ssam resp = (char *)addr + (addr->v_rspoff&0x3fff); 72625933Ssam if (resp[0] != 0 && (resp[0]&0177) != 3) { 72725933Ssam vrelease(vs, cp); /* init failed */ 72825881Ssam return; 72924003Ssam } 73025881Ssam vs->vs_loport = cp->par[5]; 73125881Ssam vs->vs_hiport = cp->par[7]; 73230372Skarels printf("vx%d: %s%s, ports %d-%d\n", vx, 73330372Skarels (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring, 73430372Skarels vs->vs_loport, vs->vs_hiport); 73525881Ssam vrelease(vs, cp); 73624003Ssam } 73724003Ssam 73824003Ssam /* 73924003Ssam * Obtain a command buffer 74024003Ssam */ 74125881Ssam struct vxcmd * 74225881Ssam vobtain(vs) 74325933Ssam register struct vx_softc *vs; 74424003Ssam { 74525933Ssam register struct vxcmd *p; 74625881Ssam int s; 74724003Ssam 74824003Ssam s = spl8(); 74925881Ssam p = vs->vs_avail; 75025881Ssam if (p == (struct vxcmd *)0) { 75124003Ssam #ifdef VX_DEBUG 75225881Ssam if (vxintr4&VXNOBUF) 75325881Ssam vxintr4 &= ~VXNOBUF; 75424003Ssam #endif 75540738Skarels printf("vx%d: no buffers\n", vs->vs_nbr); 75640738Skarels vxstreset(vs->vs_nbr); 75724003Ssam splx(s); 75825881Ssam return (vobtain(vs)); 75924003Ssam } 76030372Skarels vs->vs_avail = p->c_fwd; 76124003Ssam splx(s); 76225881Ssam return ((struct vxcmd *)p); 76324003Ssam } 76424003Ssam 76524003Ssam /* 76624003Ssam * Release a command buffer 76724003Ssam */ 76825881Ssam vrelease(vs, cp) 76925933Ssam register struct vx_softc *vs; 77025933Ssam register struct vxcmd *cp; 77124003Ssam { 77225881Ssam int s; 77324003Ssam 77424003Ssam #ifdef VX_DEBUG 77525881Ssam if (vxintr4&VXNOBUF) 77625881Ssam return; 77724003Ssam #endif 77824003Ssam s = spl8(); 77925881Ssam cp->c_fwd = vs->vs_avail; 78025881Ssam vs->vs_avail = cp; 78124003Ssam splx(s); 78224003Ssam } 78324003Ssam 78425881Ssam struct vxcmd * 78525881Ssam nextcmd(vs) 78625933Ssam register struct vx_softc *vs; 78724003Ssam { 78825933Ssam register struct vxcmd *cp; 78925881Ssam int s; 79024003Ssam 79124003Ssam s = spl8(); 79225881Ssam cp = vs->vs_build; 79325881Ssam vs->vs_build = (struct vxcmd *)0; 79424003Ssam splx(s); 79525881Ssam return (cp); 79624003Ssam } 79724003Ssam 79824003Ssam /* 79925933Ssam * Assemble transmits into a multiple command; 80030372Skarels * up to 8 transmits to 8 lines can be assembled together 80130372Skarels * (on PVIOCX only). 80224003Ssam */ 80325933Ssam vsetq(vs, line, addr, n) 80425933Ssam register struct vx_softc *vs; 80525881Ssam caddr_t addr; 80624003Ssam { 80725933Ssam register struct vxcmd *cp; 80825933Ssam register struct vxmit *mp; 80924003Ssam 81025933Ssam /* 81125933Ssam * Grab a new command buffer or append 81225933Ssam * to the current one being built. 81325933Ssam */ 81425881Ssam cp = vs->vs_build; 81525881Ssam if (cp == (struct vxcmd *)0) { 81625881Ssam cp = vobtain(vs); 81725881Ssam vs->vs_build = cp; 81825881Ssam cp->cmd = VXC_XMITDTA; 81924003Ssam } else { 82030372Skarels if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) { 82125881Ssam printf("vx%d: setq overflow\n", vs-vx_softc); 82230372Skarels vxstreset((int)vs->vs_nbr); 82330372Skarels return; 82424003Ssam } 82524003Ssam cp->cmd++; 82624003Ssam } 82725933Ssam /* 82825933Ssam * Select the next vxmit buffer and copy the 82925933Ssam * characters into the buffer (if there's room 83025933Ssam * and the device supports ``immediate mode'', 83125933Ssam * or store an indirect pointer to the data. 83225933Ssam */ 83325881Ssam mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit)); 83425675Ssam mp->bcount = n-1; 83525933Ssam mp->line = line; 83625933Ssam if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) { 83725881Ssam cp->cmd = VXC_XMITIMM; 83830372Skarels bcopy(addr, mp->ostream, (unsigned)n); 83924003Ssam } else { 84025933Ssam /* get system address of clist block */ 84125675Ssam addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr); 84230372Skarels bcopy((caddr_t)&addr, mp->ostream, sizeof (addr)); 84324003Ssam } 84430372Skarels /* 84530372Skarels * We send the data immediately if a VIOCX, 84630372Skarels * the command buffer is full, or if we've nothing 84730372Skarels * currently outstanding. If we don't send it, 84830372Skarels * set a timeout to force the data to be sent soon. 84930372Skarels */ 85030372Skarels if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 || 85130372Skarels vs->vs_xmtcnt == 0) { 85230372Skarels vs->vs_xmtcnt++; 85330372Skarels (void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd); 85430372Skarels vs->vs_build = 0; 85530372Skarels } else 85630372Skarels timeout(vxforce, (caddr_t)vs, 3); 85724003Ssam } 85825881Ssam 85925881Ssam /* 86025881Ssam * Write a command out to the VIOC 86125881Ssam */ 86225881Ssam vcmd(vx, cmdad) 86325881Ssam register int vx; 86425881Ssam register caddr_t cmdad; 86525881Ssam { 86625933Ssam register struct vcmds *cp; 86740738Skarels register struct vx_softc *vs = &vx_softc[vx]; 86825881Ssam int s; 86925881Ssam 87025881Ssam s = spl8(); 87125933Ssam /* 87225933Ssam * When the vioc is resetting, don't process 87325933Ssam * anything other than VXC_LIDENT commands. 87425933Ssam */ 87525881Ssam if (vs->vs_state == VXS_RESET && cmdad != NULL) { 87625933Ssam struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd)); 87725881Ssam 87825933Ssam if (vcp->cmd != VXC_LIDENT) { 87925933Ssam vrelease(vs, vcp); 88025881Ssam return (0); 88125881Ssam } 88225881Ssam } 88325881Ssam cp = &vs->vs_cmds; 88425881Ssam if (cmdad != (caddr_t)0) { 88525881Ssam cp->cmdbuf[cp->v_fill] = cmdad; 88625881Ssam if (++cp->v_fill >= VC_CMDBUFL) 88725881Ssam cp->v_fill = 0; 88825881Ssam if (cp->v_fill == cp->v_empty) { 88925881Ssam printf("vx%d: cmd q overflow\n", vx); 89025881Ssam vxstreset(vx); 89125881Ssam splx(s); 89225881Ssam return (0); 89325881Ssam } 89425881Ssam cp->v_cmdsem++; 89525881Ssam } 89625881Ssam if (cp->v_cmdsem && cp->v_curcnt < vs->vs_maxcmd) { 89725881Ssam cp->v_cmdsem--; 89825881Ssam cp->v_curcnt++; 89925881Ssam vinthandl(vx, ((V_BSY|CMDquals) << 8)|V_INTR); 90025881Ssam } 90125881Ssam splx(s); 90225881Ssam return (1); 90325881Ssam } 90425881Ssam 90525881Ssam /* 90625881Ssam * VIOC acknowledge interrupt. The VIOC has received the new 90725881Ssam * command. If no errors, the new command becomes one of 16 (max) 90825881Ssam * current commands being executed. 90925881Ssam */ 91025881Ssam vackint(vx) 91125881Ssam register vx; 91225881Ssam { 91325933Ssam register struct vxdevice *vp; 91425933Ssam register struct vcmds *cp; 91525881Ssam struct vx_softc *vs; 91625881Ssam int s; 91725881Ssam 91825881Ssam scope_out(5); 91925881Ssam vs = &vx_softc[vx]; 92029954Skarels if (vs->vs_type) /* Its a BOP */ 92125881Ssam return; 92225881Ssam s = spl8(); 92340738Skarels vp = vs->vs_addr; 92425881Ssam cp = &vs->vs_cmds; 92525933Ssam if (vp->v_vcid&V_ERR) { 92625881Ssam register char *resp; 92725881Ssam register i; 92825933Ssam 92930372Skarels printf("vx%d: ackint error type %x v_dcd %x\n", vx, 93025881Ssam vp->v_vcid & 07, vp->v_dcd & 0xff); 93125881Ssam resp = (char *)vs->vs_mricmd; 93225881Ssam for (i = 0; i < 16; i++) 93325881Ssam printf("%x ", resp[i]&0xff); 93425881Ssam printf("\n"); 93525881Ssam splx(s); 93625881Ssam vxstreset(vx); 93725881Ssam return; 93825881Ssam } 93925881Ssam if ((vp->v_hdwre&017) == CMDquals) { 94025881Ssam #ifdef VX_DEBUG 94125881Ssam if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */ 94225933Ssam struct vxcmd *cp1, *cp0; 94325881Ssam 94425933Ssam cp0 = (struct vxcmd *) 94525933Ssam ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd)); 94625881Ssam if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) { 94725881Ssam cp1 = vobtain(vs); 94825881Ssam *cp1 = *cp0; 94925881Ssam vxintr4 &= ~VXERR4; 95025881Ssam (void) vcmd(vx, &cp1->cmd); 95125881Ssam } 95225881Ssam } 95325881Ssam #endif 95425881Ssam cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty]; 95525881Ssam if (++cp->v_empty >= VC_CMDBUFL) 95625881Ssam cp->v_empty = 0; 95725881Ssam } 95825881Ssam if (++cp->v_itrempt >= VC_IQLEN) 95925881Ssam cp->v_itrempt = 0; 96025881Ssam vintempt(vx); 96125881Ssam splx(s); 96225881Ssam (void) vcmd(vx, (caddr_t)0); /* queue next cmd, if any */ 96325881Ssam } 96425881Ssam 96525881Ssam /* 96625881Ssam * Command Response interrupt. The Vioc has completed 96725881Ssam * a command. The command may now be returned to 96825881Ssam * the appropriate device driver. 96925881Ssam */ 97025881Ssam vcmdrsp(vx) 97125881Ssam register vx; 97225881Ssam { 97325933Ssam register struct vxdevice *vp; 97425933Ssam register struct vcmds *cp; 97525881Ssam register caddr_t cmd; 97625881Ssam register struct vx_softc *vs; 97725881Ssam register char *resp; 97825881Ssam register k; 97925881Ssam register int s; 98025881Ssam 98125881Ssam scope_out(6); 98225881Ssam vs = &vx_softc[vx]; 98325881Ssam if (vs->vs_type) { /* Its a BOP */ 98425881Ssam printf("vx%d: vcmdrsp interrupt\n", vx); 98525881Ssam return; 98625881Ssam } 98725881Ssam s = spl8(); 98840738Skarels vp = vs->vs_addr; 98925881Ssam cp = &vs->vs_cmds; 99025881Ssam resp = (char *)vp + (vp->v_rspoff&0x7fff); 99125881Ssam if (((k = resp[1])&V_UNBSY) == 0) { 99225881Ssam printf("vx%d: cmdresp debug\n", vx); 99325881Ssam splx(s); 99425881Ssam vxstreset(vx); 99525881Ssam return; 99625881Ssam } 99725881Ssam k &= VCMDLEN-1; 99825881Ssam cmd = cp->v_curcmd[k]; 99925881Ssam cp->v_curcmd[k] = (caddr_t)0; 100025881Ssam cp->v_curcnt--; 100125881Ssam k = *((short *)&resp[4]); /* cmd operation code */ 100225881Ssam if ((k&0xff00) == VXC_LIDENT) /* want hiport number */ 100325881Ssam for (k = 0; k < VRESPLEN; k++) 100425881Ssam cmd[k] = resp[k+4]; 100525881Ssam resp[1] = 0; 100625881Ssam vxxint(vx, (struct vxcmd *)cmd); 100725881Ssam if (vs->vs_state == VXS_READY) 100825881Ssam vinthandl(vx, ((V_BSY|RSPquals) << 8)|V_INTR); 100925881Ssam splx(s); 101025881Ssam } 101125881Ssam 101225881Ssam /* 101325881Ssam * Unsolicited interrupt. 101425881Ssam */ 101525881Ssam vunsol(vx) 101625881Ssam register vx; 101725881Ssam { 101825933Ssam register struct vxdevice *vp; 101925881Ssam struct vx_softc *vs; 102025881Ssam int s; 102125881Ssam 102225881Ssam scope_out(1); 102325881Ssam vs = &vx_softc[vx]; 102425881Ssam if (vs->vs_type) { /* Its a BOP */ 102525881Ssam printf("vx%d: vunsol from BOP\n", vx); 102625881Ssam return; 102725881Ssam } 102825881Ssam s = spl8(); 102940738Skarels vp = vs->vs_addr; 103025881Ssam if (vp->v_uqual&V_UNBSY) { 103125881Ssam vxrint(vx); 103225881Ssam vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR); 103325881Ssam #ifdef notdef 103425881Ssam } else { 103525881Ssam printf("vx%d: unsolicited interrupt error\n", vx); 103625881Ssam splx(s); 103725881Ssam vxstreset(vx); 103825881Ssam #endif 103925881Ssam } 104025881Ssam splx(s); 104125881Ssam } 104225881Ssam 104325881Ssam /* 104425933Ssam * Enqueue an interrupt. 104525881Ssam */ 104625881Ssam vinthandl(vx, item) 104725881Ssam register int vx; 104825881Ssam register item; 104925881Ssam { 105025881Ssam register struct vcmds *cp; 105125881Ssam int empty; 105225881Ssam 105325881Ssam cp = &vx_softc[vx].vs_cmds; 105425933Ssam empty = (cp->v_itrfill == cp->v_itrempt); 105525881Ssam cp->v_itrqueu[cp->v_itrfill] = item; 105625881Ssam if (++cp->v_itrfill >= VC_IQLEN) 105725881Ssam cp->v_itrfill = 0; 105825881Ssam if (cp->v_itrfill == cp->v_itrempt) { 105925881Ssam printf("vx%d: interrupt q overflow\n", vx); 106025881Ssam vxstreset(vx); 106125881Ssam } else if (empty) 106225881Ssam vintempt(vx); 106325881Ssam } 106425881Ssam 106525881Ssam vintempt(vx) 106640738Skarels int vx; 106725881Ssam { 106825881Ssam register struct vcmds *cp; 106925881Ssam register struct vxdevice *vp; 107040738Skarels register struct vx_softc *vs; 107125881Ssam register short item; 107225881Ssam register short *intr; 107325881Ssam 107440738Skarels vs = &vx_softc[vx]; 107540738Skarels vp = vs->vs_addr; 107625881Ssam if (vp->v_vioc&V_BSY) 107725881Ssam return; 107840738Skarels cp = &vs->vs_cmds; 107925881Ssam if (cp->v_itrempt == cp->v_itrfill) 108025881Ssam return; 108125881Ssam item = cp->v_itrqueu[cp->v_itrempt]; 108225881Ssam intr = (short *)&vp->v_vioc; 108325881Ssam switch ((item >> 8)&03) { 108425881Ssam 108525881Ssam case CMDquals: { /* command */ 108625881Ssam int phys; 108725881Ssam 108825881Ssam if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY) 108925881Ssam break; 109040738Skarels vs->vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty]; 109125881Ssam phys = vtoph((struct proc *)0, 109225881Ssam (unsigned)cp->cmdbuf[cp->v_empty]); 109325881Ssam vp->v_vcp[0] = ((short *)&phys)[0]; 109425881Ssam vp->v_vcp[1] = ((short *)&phys)[1]; 109525881Ssam vp->v_vcbsy = V_BSY; 109625881Ssam *intr = item; 109725881Ssam scope_out(4); 109825881Ssam break; 109925881Ssam } 110025881Ssam 110125881Ssam case RSPquals: /* command response */ 110225881Ssam *intr = item; 110325881Ssam scope_out(7); 110425881Ssam break; 110525881Ssam 110625881Ssam case UNSquals: /* unsolicited interrupt */ 110725881Ssam vp->v_uqual = 0; 110825881Ssam *intr = item; 110925881Ssam scope_out(2); 111025881Ssam break; 111125881Ssam } 111225881Ssam } 111325881Ssam 111425881Ssam /* 111525881Ssam * Start a reset on a vioc after error (hopefully) 111625881Ssam */ 111725881Ssam vxstreset(vx) 111840738Skarels register int vx; 111925881Ssam { 112025881Ssam register struct vx_softc *vs; 112125933Ssam register struct vxdevice *vp; 112225881Ssam register struct vxcmd *cp; 112325881Ssam register int j; 112425881Ssam extern int vxinreset(); 112525881Ssam int s; 112625881Ssam 112725881Ssam vs = &vx_softc[vx]; 112840738Skarels s = spl8(); 112925881Ssam if (vs->vs_state == VXS_RESET) { /* avoid recursion */ 113025881Ssam splx(s); 113125881Ssam return; 113225881Ssam } 113340738Skarels vp = vs->vs_addr; 113425881Ssam /* 113525881Ssam * Zero out the vioc structures, mark the vioc as being 113625881Ssam * reset, reinitialize the free command list, reset the vioc 113725881Ssam * and start a timer to check on the progress of the reset. 113825881Ssam */ 113940738Skarels bzero((caddr_t)&vs->vs_zero, 114040738Skarels (unsigned)((caddr_t)(vs + 1) - (caddr_t)&vs->vs_zero)); 114125881Ssam 114225881Ssam /* 114325881Ssam * Setting VXS_RESET prevents others from issuing 114425881Ssam * commands while allowing currently queued commands to 114525881Ssam * be passed to the VIOC. 114625881Ssam */ 114725881Ssam vs->vs_state = VXS_RESET; 114825881Ssam /* init all cmd buffers */ 114925881Ssam for (j = 0; j < NVCXBUFS; j++) { 115025933Ssam cp = &vs->vs_lst[j]; 115125933Ssam cp->c_fwd = &vs->vs_lst[j+1]; 115225881Ssam } 115325933Ssam vs->vs_avail = &vs->vs_lst[0]; 115425933Ssam cp->c_fwd = (struct vxcmd *)0; 115525881Ssam printf("vx%d: reset...", vx); 115625881Ssam vp->v_fault = 0; 115725881Ssam vp->v_vioc = V_BSY; 115825933Ssam vp->v_hdwre = V_RESET; /* generate reset interrupt */ 115925881Ssam timeout(vxinreset, (caddr_t)vx, hz*5); 116025881Ssam splx(s); 116125881Ssam } 116225881Ssam 116325881Ssam /* continue processing a reset on a vioc after an error (hopefully) */ 116425881Ssam vxinreset(vx) 116525881Ssam int vx; 116625881Ssam { 116725933Ssam register struct vxdevice *vp; 116825881Ssam int s = spl8(); 116925881Ssam 117040738Skarels vp = vx_softc[vx].vs_addr; 117125881Ssam /* 117225881Ssam * See if the vioc has reset. 117325881Ssam */ 117425881Ssam if (vp->v_fault != VXF_READY) { 117540738Skarels printf(" vxreset failed\n"); 117625881Ssam splx(s); 117725881Ssam return; 117825881Ssam } 117925881Ssam /* 118025881Ssam * Send a LIDENT to the vioc and mess with carrier flags 118125881Ssam * on parallel printer ports. 118225881Ssam */ 118329954Skarels vxinit(vx, 0); 118425881Ssam splx(s); 118525881Ssam } 118625881Ssam 118725881Ssam /* 118825933Ssam * Finish the reset on the vioc after an error (hopefully). 118925933Ssam * 119025881Ssam * Restore modem control, parameters and restart output. 119125881Ssam * Since the vioc can handle no more then 24 commands at a time 119225881Ssam * and we could generate as many as 48 commands, we must do this in 119325881Ssam * phases, issuing no more then 16 commands at a time. 119425881Ssam */ 119525881Ssam vxfnreset(vx, cp) 119625881Ssam register int vx; 119725881Ssam register struct vxcmd *cp; 119825881Ssam { 119925881Ssam register struct vx_softc *vs; 120040738Skarels register struct vxdevice *vp; 120125881Ssam register struct tty *tp, *tp0; 120225881Ssam register int i; 120325881Ssam #ifdef notdef 120425881Ssam register int on; 120525881Ssam #endif 120625881Ssam extern int vxrestart(); 120725881Ssam int s = spl8(); 120825881Ssam 120925881Ssam vs = &vx_softc[vx]; 121025881Ssam vrelease(vs, cp); 121125881Ssam vs->vs_state = VXS_READY; 121225881Ssam 121340738Skarels vp = vs->vs_addr; 121425881Ssam vp->v_vcid = 0; 121525881Ssam 121625881Ssam /* 121725881Ssam * Restore modem information and control. 121825881Ssam */ 121925881Ssam tp0 = &vx_tty[vx*16]; 122025881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 122125881Ssam tp = tp0 + i; 122225881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) { 122325881Ssam tp->t_state &= ~TS_CARR_ON; 122425881Ssam vcmodem(tp->t_dev, VMOD_ON); 122525881Ssam if (tp->t_state&TS_CARR_ON) 122629954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 122729954Skarels else if (tp->t_state & TS_ISOPEN) 122829954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 122925881Ssam } 123029954Skarels #ifdef notdef 123125881Ssam /* 123225881Ssam * If carrier has changed while we were resetting, 123325881Ssam * take appropriate action. 123425881Ssam */ 123525881Ssam on = vp->v_dcd & 1<<i; 123629954Skarels if (on && (tp->t_state&TS_CARR_ON) == 0) 123729954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 123829954Skarels else if (!on && tp->t_state&TS_CARR_ON) 123929954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 0); 124025881Ssam #endif 124125881Ssam } 124225881Ssam vs->vs_state = VXS_RESET; 124325881Ssam timeout(vxrestart, (caddr_t)vx, hz); 124425881Ssam splx(s); 124525881Ssam } 124625881Ssam 124725881Ssam /* 124825881Ssam * Restore a particular aspect of the VIOC. 124925881Ssam */ 125025881Ssam vxrestart(vx) 125125881Ssam int vx; 125225881Ssam { 125325881Ssam register struct tty *tp, *tp0; 125425881Ssam register struct vx_softc *vs; 125530372Skarels register int i, count; 125625881Ssam int s = spl8(); 125725881Ssam 125830372Skarels count = vx >> 8; 125925881Ssam vx &= 0xff; 126025881Ssam vs = &vx_softc[vx]; 126125881Ssam vs->vs_state = VXS_READY; 126225881Ssam tp0 = &vx_tty[vx*16]; 126325881Ssam for (i = vs->vs_loport; i <= vs->vs_hiport; i++) { 126425881Ssam tp = tp0 + i; 126530372Skarels if (count != 0) { 126625881Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 126725881Ssam if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) 126825881Ssam vxstart(tp); /* restart pending output */ 126925881Ssam } else { 127025881Ssam if (tp->t_state&(TS_WOPEN|TS_ISOPEN)) 127137608Smarc vxcparam(tp, &tp->t_termios, 0); 127225881Ssam } 127325881Ssam } 127430372Skarels if (count == 0) { 127525881Ssam vs->vs_state = VXS_RESET; 127625881Ssam timeout(vxrestart, (caddr_t)(vx + 1*256), hz); 127725881Ssam } else 127840738Skarels printf(" vx reset done\n"); 127925881Ssam splx(s); 128025881Ssam } 128125881Ssam 128225881Ssam vxreset(dev) 128325881Ssam dev_t dev; 128425881Ssam { 128525881Ssam 128630372Skarels vxstreset((int)VXUNIT(minor(dev))); /* completes asynchronously */ 128725881Ssam } 128825881Ssam 128940738Skarels #ifdef VX_DEBUG 129025881Ssam vxfreset(vx) 129125881Ssam register int vx; 129225881Ssam { 129325881Ssam struct vba_device *vi; 129425881Ssam 129525881Ssam if ((unsigned)vx > NVX || (vi = vxinfo[vx]) == 0 || vi->ui_addr == 0) 129625881Ssam return (ENODEV); 129725881Ssam vx_softc[vx].vs_state = VXS_READY; 129825881Ssam vxstreset(vx); 129925881Ssam return (0); /* completes asynchronously */ 130025881Ssam } 130130372Skarels #endif 130225881Ssam 130325881Ssam vcmodem(dev, flag) 130425881Ssam dev_t dev; 130525881Ssam { 130625881Ssam struct tty *tp; 130725881Ssam register struct vxcmd *cp; 130825881Ssam register struct vx_softc *vs; 130925881Ssam register struct vxdevice *kp; 131025881Ssam register port; 131125881Ssam int unit; 131225881Ssam 131325881Ssam unit = minor(dev); 131425881Ssam tp = &vx_tty[unit]; 131525881Ssam vs = (struct vx_softc *)tp->t_addr; 131630372Skarels if (vs->vs_state != VXS_READY) 131730372Skarels return; 131825881Ssam cp = vobtain(vs); 131940738Skarels kp = vs->vs_addr; 132025881Ssam 132140738Skarels port = VXPORT(unit); 132225881Ssam /* 132325881Ssam * Issue MODEM command 132425881Ssam */ 132525881Ssam cp->cmd = VXC_MDMCTL; 132630372Skarels if (flag == VMOD_ON) { 132740738Skarels if (vs->vs_softCAR & (1 << port)) { 132830372Skarels cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS; 132940738Skarels kp->v_dcd |= (1 << port); 133040738Skarels } else 133140738Skarels cp->par[0] = V_AUTO | V_DTR_ON; 133230372Skarels } else 133330372Skarels cp->par[0] = V_DTR_OFF; 133425881Ssam cp->par[1] = port; 133530372Skarels (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd); 133630372Skarels if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON) 133730372Skarels tp->t_state |= TS_CARR_ON; 133825881Ssam } 133925881Ssam 134025881Ssam /* 134140738Skarels * VCMINTR called when an unsolicited interrupt occurs signaling 134225881Ssam * some change of modem control state. 134325881Ssam */ 134425881Ssam vcmintr(vx) 134525881Ssam register vx; 134625881Ssam { 134725881Ssam register struct vxdevice *kp; 134825881Ssam register struct tty *tp; 134925881Ssam register port; 135030372Skarels register struct vx_softc *vs; 135125881Ssam 135240738Skarels vs = &vx_softc[vx]; 135340738Skarels kp = vs->vs_addr; 135425881Ssam port = kp->v_usdata[0] & 017; 135525881Ssam tp = &vx_tty[vx*16+port]; 135625881Ssam 135729954Skarels if (kp->v_ustat & DCD_ON) 135829954Skarels (void)(*linesw[tp->t_line].l_modem)(tp, 1); 135929954Skarels else if ((kp->v_ustat & DCD_OFF) && 136030372Skarels ((vs->vs_softCAR & (1 << port))) == 0 && 136129954Skarels (*linesw[tp->t_line].l_modem)(tp, 0) == 0) { 136229954Skarels register struct vcmds *cp; 136329954Skarels register struct vxcmd *cmdp; 136425881Ssam 136530372Skarels /* clear all pending transmits */ 136629954Skarels if (tp->t_state&(TS_BUSY|TS_FLUSH) && 136729954Skarels vs->vs_vers == VXV_NEW) { 136829954Skarels int i, cmdfound = 0; 136925881Ssam 137029954Skarels cp = &vs->vs_cmds; 137129954Skarels for (i = cp->v_empty; i != cp->v_fill; ) { 137229954Skarels cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1); 137329954Skarels if ((cmdp->cmd == VXC_XMITDTA || 137429954Skarels cmdp->cmd == VXC_XMITIMM) && 137529954Skarels ((struct vxmit *)cmdp->par)->line == port) { 137629954Skarels cmdfound++; 137725881Ssam cmdp->cmd = VXC_FDTATOX; 137825881Ssam cmdp->par[1] = port; 137925881Ssam } 138029954Skarels if (++i >= VC_CMDBUFL) 138129954Skarels i = 0; 138225881Ssam } 138329954Skarels if (cmdfound) 138429954Skarels tp->t_state &= ~(TS_BUSY|TS_FLUSH); 138529954Skarels /* cmd is already in vioc, have to flush it */ 138629954Skarels else { 138729954Skarels cmdp = vobtain(vs); 138829954Skarels cmdp->cmd = VXC_FDTATOX; 138929954Skarels cmdp->par[1] = port; 139030372Skarels (void) vcmd(vx, (caddr_t)&cmdp->cmd); 139125881Ssam } 139225881Ssam } 139329954Skarels } else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) { 139437608Smarc (*linesw[tp->t_line].l_rint)(TTY_FE, tp); 139525881Ssam return; 139625881Ssam } 139725881Ssam } 139825881Ssam #endif 1399