new copyright notice
[unix-history] / usr / src / sys / tahoe / vba / vx.c
index dc35b21..bf2cc64 100644 (file)
@@ -1,4 +1,14 @@
-/*     vx.c    1.7     86/01/21        */
+/*
+ * Copyright (c) 1988 Regents of the University of California.
+ * All rights reserved.
+ *
+ * This code is derived from software contributed to Berkeley by
+ * Computer Consoles Inc.
+ *
+ * %sccs.include.redist.c%
+ *
+ *     @(#)vx.c        7.11 (Berkeley) %G%
+ */
 
 #include "vx.h"
 #if NVX > 0
 
 #include "vx.h"
 #if NVX > 0
 #define        DOSCOPE
 #endif
 
 #define        DOSCOPE
 #endif
 
-#include "../tahoe/pte.h"
-
 #include "param.h"
 #include "ioctl.h"
 #include "tty.h"
 #include "param.h"
 #include "ioctl.h"
 #include "tty.h"
-#include "dir.h"
 #include "user.h"
 #include "map.h"
 #include "buf.h"
 #include "conf.h"
 #include "file.h"
 #include "user.h"
 #include "map.h"
 #include "buf.h"
 #include "conf.h"
 #include "file.h"
-#include "uio.h"
 #include "proc.h"
 #include "vm.h"
 #include "kernel.h"
 #include "proc.h"
 #include "vm.h"
 #include "kernel.h"
+#include "syslog.h"
+
+#include "../tahoe/pte.h"
 
 #include "../tahoevba/vbavar.h"
 
 #include "../tahoevba/vbavar.h"
+#include "../tahoevba/vbaparam.h"
 #include "../tahoevba/vxreg.h"
 #include "../tahoevba/scope.h"
 #include "../tahoevba/vxreg.h"
 #include "../tahoevba/scope.h"
-#include "vbsc.h"
-#if NVBSC > 0
-#include "../tahoebsc/bscio.h"
-#include "../tahoebsc/bsc.h"
-#ifdef BSC_DEBUG
-#include "../tahoebsc/bscdebug.h"
-#endif
-
-char   bscport[NVX*16];
-#endif
 
 #ifdef VX_DEBUG
 long   vxintr4 = 0;
 
 #ifdef VX_DEBUG
 long   vxintr4 = 0;
-#define VXERR4 1
-#define VXNOBUF        2
+#define        VXERR4  1
+#define        VXNOBUF 2
 long   vxdebug = 0;
 long   vxdebug = 0;
-#define VXVCM  1
-#define VXVCC  2
-#define VXVCX  4
-#include "../tahoesna/snadebug.h"
+#define        VXVCM   1
+#define        VXVCC   2
+#define        VXVCX   4
 #endif
 
 /*
  * Interrupt type bits passed to vinthandl().
  */
 #endif
 
 /*
  * Interrupt type bits passed to vinthandl().
  */
-#define CMDquals 0             /* command completed interrupt */
-#define RSPquals 1             /* command response interrupt */
-#define UNSquals 2             /* unsolicited interrupt */
+#define        CMDquals 0              /* command completed interrupt */
+#define        RSPquals 1              /* command response interrupt */
+#define        UNSquals 2              /* unsolicited interrupt */
+
+#define        VXUNIT(n)       ((n) >> 4)
+#define        VXPORT(n)       ((n) & 0xf)
 
 struct tty vx_tty[NVX*16];
 
 struct tty vx_tty[NVX*16];
+#ifndef lint
+int    nvx = NVX*16;
+#endif
 int    vxstart(), ttrstrt();
 struct vxcmd *vobtain(), *nextcmd();
 
 int    vxstart(), ttrstrt();
 struct vxcmd *vobtain(), *nextcmd();
 
@@ -71,6 +76,7 @@ struct        vba_driver vxdriver =
     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
 
 struct vx_softc {
     { vxprobe, 0, vxattach, 0, vxstd, "vx", vxinfo };
 
 struct vx_softc {
+       struct  vxdevice *vs_addr;      /* H/W address */
        u_char  vs_type;        /* 0: viox-x/vioc-b, 1: vioc-bop */
        u_char  vs_bop;         /* bop board # for vioc-bop's */
        u_char  vs_loport;      /* low port nbr */
        u_char  vs_type;        /* 0: viox-x/vioc-b, 1: vioc-bop */
        u_char  vs_bop;         /* bop board # for vioc-bop's */
        u_char  vs_loport;      /* low port nbr */
@@ -81,32 +87,70 @@ struct      vx_softc {
        short   vs_vers;        /* vioc/pvioc version */
 #define        VXV_OLD 0               /* PVIOCX | VIOCX */
 #define        VXV_NEW 1               /* NPVIOCX | NVIOCX */
        short   vs_vers;        /* vioc/pvioc version */
 #define        VXV_OLD 0               /* PVIOCX | VIOCX */
 #define        VXV_NEW 1               /* NPVIOCX | NVIOCX */
-       short   vs_xmtcnt;      /* xmit commands pending */
-       short   vs_brkreq;      /* send break requests pending */
-       short   vs_active;      /* active port bit array or flag */
        short   vs_state;       /* controller state */
 #define        VXS_READY       0       /* ready for commands */
        short   vs_state;       /* controller state */
 #define        VXS_READY       0       /* ready for commands */
-#define VXS_RESET      1       /* in process of reseting */
-       caddr_t vs_mricmd;      /* most recent issued cmd */
+#define        VXS_RESET       1       /* in process of reseting */
+       u_short vs_softCAR;     /* soft carrier */
        u_int   vs_ivec;        /* interrupt vector base */
        u_int   vs_ivec;        /* interrupt vector base */
+       caddr_t vs_mricmd;      /* most recent issued cmd */
+       /* The remaining fields are zeroed on reset... */
+#define vs_zero vs_xmtcnt
+       int     vs_xmtcnt;      /* xmit commands pending */
        struct  vxcmd *vs_avail;/* next available command buffer */
        struct  vxcmd *vs_build;
        struct  vxcmd vs_lst[NVCXBUFS];
        struct  vcmds vs_cmds;
 } vx_softc[NVX];
 
        struct  vxcmd *vs_avail;/* next available command buffer */
        struct  vxcmd *vs_build;
        struct  vxcmd vs_lst[NVCXBUFS];
        struct  vcmds vs_cmds;
 } vx_softc[NVX];
 
+struct speedtab vxspeedtab[] = {
+       EXTA,   V19200,
+       EXTB,   V19200,
+       19200,  V19200,
+       9600,   13,
+       4800,   12,
+       2400,   11,
+       1800,   10,
+       1200,   9,
+       600,    8,
+       300,    7,
+       200,    6,
+       150,    5,
+       134,    4,
+       110,    3,
+       75,     2,
+       50,     1,
+       0,      0,
+       -1,     -1,
+};
+
 vxprobe(reg, vi)
        caddr_t reg;
        struct vba_device *vi;
 {
        register int br, cvec;                  /* must be r12, r11 */
 vxprobe(reg, vi)
        caddr_t reg;
        struct vba_device *vi;
 {
        register int br, cvec;                  /* must be r12, r11 */
-       register struct vxdevice *vp = (struct vxdevice *)reg;
+       register struct vxdevice *vp;
        register struct vx_softc *vs;
        register struct vx_softc *vs;
+       struct pte *dummypte;
 
 #ifdef lint
        br = 0; cvec = br; br = cvec;
 
 #ifdef lint
        br = 0; cvec = br; br = cvec;
-       vackint(0); vunsol(0); vcmdrsp(0); vxfreset(0);
+       vackint(0); vunsol(0); vcmdrsp(0);
+#ifdef VX_DEBUG
+       vxfreset(0);
 #endif
 #endif
+#endif /* lint */
+       /*
+        * If on an HCX-9, the device has a 32-bit address,
+        * and we receive that address so we can set up a map.
+        * On VERSAbus devices, the address is 24-bit, and is
+        * already mapped (into vmem[]) by autoconf.
+        */
+       if (!(reg >= vmem && reg < &vmem[ctob(VBIOSIZE)]) &&    /* XXX */
+           !vbmemalloc(16, reg, &dummypte, &reg)) {
+               printf("vx%d: vbmemalloc failed.\n", vi->ui_unit);
+               return(0);
+       }
+       vp = (struct vxdevice *)reg;
        if (badaddr((caddr_t)vp, 1))
                return (0);
        vp->v_fault = 0;
        if (badaddr((caddr_t)vp, 1))
                return (0);
        vp->v_fault = 0;
@@ -135,8 +179,11 @@ vxprobe(reg, vi)
 vxattach(vi)
        register struct vba_device *vi;
 {
 vxattach(vi)
        register struct vba_device *vi;
 {
+       register struct vx_softc *vs = &vx_softc[vi->ui_unit];
 
 
-       vxinit(vi->ui_unit, (long)1);
+       vs->vs_softCAR = vi->ui_flags;
+       vs->vs_addr = (struct vxdevice *)vi->ui_addr;
+       vxinit(vi->ui_unit, 1);
 }
 
 /*
 }
 
 /*
@@ -150,38 +197,48 @@ vxopen(dev, flag)
        register struct tty *tp;        /* pointer to tty struct for port */
        register struct vx_softc *vs;
        register struct vba_device *vi;
        register struct tty *tp;        /* pointer to tty struct for port */
        register struct vx_softc *vs;
        register struct vba_device *vi;
-       int unit, vx, s, error;
+       int unit, vx, s, error = 0;
+       int vxparam();
 
        unit = minor(dev);
 
        unit = minor(dev);
-       vx = unit >> 4;
-       if (unit >= NVX*16 || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
+       vx = VXUNIT(unit);
+       if (vx >= NVX || (vi = vxinfo[vx])== 0 || vi->ui_alive == 0)
                return (ENXIO);
                return (ENXIO);
+       vs = &vx_softc[vx];
        tp = &vx_tty[unit];
        tp = &vx_tty[unit];
+       unit = VXPORT(unit);
        if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
                return (EBUSY);
        if (tp->t_state&TS_XCLUDE && u.u_uid != 0)
                return (EBUSY);
-       vs = &vx_softc[vx];
-#ifdef notdef
-       if (unit < vs->vs_loport || vs->vs_hiport < unit)       /* ??? */
+       if (unit < vs->vs_loport || unit > vs->vs_hiport)
                return (ENXIO);
                return (ENXIO);
-#endif
        tp->t_addr = (caddr_t)vs;
        tp->t_oproc = vxstart;
        tp->t_addr = (caddr_t)vs;
        tp->t_oproc = vxstart;
+       tp->t_param = vxparam;
        tp->t_dev = dev;
        s = spl8();
        tp->t_dev = dev;
        s = spl8();
-       tp->t_state |= TS_WOPEN;
        if ((tp->t_state&TS_ISOPEN) == 0) {
        if ((tp->t_state&TS_ISOPEN) == 0) {
+               tp->t_state |= TS_WOPEN;
                ttychars(tp);
                if (tp->t_ispeed == 0) {
                ttychars(tp);
                if (tp->t_ispeed == 0) {
-                       tp->t_ispeed = SSPEED;
-                       tp->t_ospeed = SSPEED;
-                       tp->t_flags |= ODDP|EVENP|ECHO;
+                       tp->t_iflag = TTYDEF_IFLAG;
+                       tp->t_oflag = TTYDEF_OFLAG;
+                       tp->t_lflag = TTYDEF_LFLAG;
+                       tp->t_cflag = TTYDEF_CFLAG;
+                       tp->t_ispeed = tp->t_ospeed = TTYDEF_SPEED;
                }
                }
-               vxparam(dev);
+               vxparam(tp, &tp->t_termios);
+               ttsetwater(tp);
+       }
+       vcmodem(dev, VMOD_ON);
+       while (!(flag&O_NONBLOCK) && !(tp->t_cflag&CLOCAL) && 
+             (tp->t_state&TS_CARR_ON) == 0) {
+               tp->t_state |= TS_WOPEN;
+               if (error = ttysleep(tp, (caddr_t)&tp->t_rawq, TTIPRI | PCATCH,
+                   ttopen, 0))
+                       break;
        }
        }
-       if (!vcmodem(dev, VMOD_ON))
-               while ((tp->t_state&TS_CARR_ON) == 0)
-                       sleep((caddr_t)&tp->t_canq, TTIPRI);
-       error = (*linesw[tp->t_line].l_open)(dev,tp);
+       if (error == 0)
+               error = (*linesw[tp->t_line].l_open)(dev,tp);
        splx(s);
        return (error);
 }
        splx(s);
        return (error);
 }
@@ -195,44 +252,46 @@ vxclose(dev, flag)
        int flag;
 {
        register struct tty *tp;
        int flag;
 {
        register struct tty *tp;
-       int unit, s;
+       int unit, s, error = 0;
 
        unit = minor(dev);
        tp = &vx_tty[unit];
        s = spl8();
        (*linesw[tp->t_line].l_close)(tp);
 
        unit = minor(dev);
        tp = &vx_tty[unit];
        s = spl8();
        (*linesw[tp->t_line].l_close)(tp);
-       if ((tp->t_state & (TS_ISOPEN|TS_HUPCLS)) == (TS_ISOPEN|TS_HUPCLS))
-               if (!vcmodem(dev, VMOD_OFF))
-                       tp->t_state &= ~TS_CARR_ON;
+       if (tp->t_cflag & HUPCL || (tp->t_state & TS_ISOPEN) == 0)
+               vcmodem(dev, VMOD_OFF);
        /* wait for the last response */
        /* wait for the last response */
-       while (tp->t_state&TS_FLUSH)
-               sleep((caddr_t)&tp->t_state, TTOPRI);
-       ttyclose(tp);
+       while (tp->t_state&TS_FLUSH && error == 0)
+               error = tsleep((caddr_t)&tp->t_state, TTOPRI | PCATCH,
+                   ttclos, 0);
        splx(s);
        splx(s);
+       if (error)
+               return (error);
+       return (ttyclose(tp));
 }
 
 /*
  * Read from a VX line.
  */
 }
 
 /*
  * Read from a VX line.
  */
-vxread(dev, uio)
+vxread(dev, uio, flag)
        dev_t dev;
        struct uio *uio;
 {
        struct tty *tp = &vx_tty[minor(dev)];
 
        dev_t dev;
        struct uio *uio;
 {
        struct tty *tp = &vx_tty[minor(dev)];
 
-       return ((*linesw[tp->t_line].l_read)(tp, uio));
+       return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
 }
 
 /*
  * write on a VX line
  */
 }
 
 /*
  * write on a VX line
  */
-vxwrite(dev, uio)
+vxwrite(dev, uio, flag)
        dev_t dev;
        struct uio *uio;
 {
        register struct tty *tp = &vx_tty[minor(dev)];
 
        dev_t dev;
        struct uio *uio;
 {
        register struct tty *tp = &vx_tty[minor(dev)];
 
-       return ((*linesw[tp->t_line].l_write)(tp, uio));
+       return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
 }
 
 /*
 }
 
 /*
@@ -247,7 +306,7 @@ vxrint(vx)
        struct vba_device *vi;
        register int nc, c;
        register struct silo {
        struct vba_device *vi;
        register int nc, c;
        register struct silo {
-               char    data, port;
+               u_char  data, port;
        } *sp;
        short *osp;
        int overrun = 0;
        } *sp;
        short *osp;
        int overrun = 0;
@@ -260,18 +319,23 @@ vxrint(vx)
        case 0:
                break;
        case 2:
        case 0:
                break;
        case 2:
-               printf("vx%d: vc proc err, ustat %x\n", addr->v_ustat);
-               vxstreset(vx);
-               return (0);
+               if (addr->v_ustat == VP_SILO_OFLOW)
+                       log(LOG_ERR, "vx%d: input silo overflow\n", vx);
+               else {
+                       printf("vx%d: vc proc err, ustat %x\n",
+                           vx, addr->v_ustat);
+                       vxstreset(vx);
+               }
+               return;
        case 3:
                vcmintr(vx);
        case 3:
                vcmintr(vx);
-               return (1);
+               return;
        case 4:
        case 4:
-               return (1);
+               return;
        default:
        default:
-               printf("vx%d: vc uqual err, uqual %x\n", addr->v_uqual);
+               printf("vx%d: vc uqual err, uqual %x\n", vx, addr->v_uqual);
                vxstreset(vx);
                vxstreset(vx);
-               return (0);
+               return;
        }
        vs = &vx_softc[vx];
        if (vs->vs_vers == VXV_NEW)
        }
        vs = &vx_softc[vx];
        if (vs->vs_vers == VXV_NEW)
@@ -280,7 +344,7 @@ vxrint(vx)
                sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
        nc = *(osp = (short *)sp);
        if (nc == 0)
                sp = (struct silo *)((caddr_t)addr+VX_SILO+(addr->v_usdata[0]<<6));
        nc = *(osp = (short *)sp);
        if (nc == 0)
-               return (1);
+               return;
        if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
                printf("vx%d: %d exceeds silo size\n", nc);
                nc = vs->vs_silosiz;
        if (vs->vs_vers == VXV_NEW && nc > vs->vs_silosiz) {
                printf("vx%d: %d exceeds silo size\n", nc);
                nc = vs->vs_silosiz;
@@ -296,31 +360,19 @@ vxrint(vx)
                        wakeup((caddr_t)&tp->t_rawq);
                        continue;
                }
                        wakeup((caddr_t)&tp->t_rawq);
                        continue;
                }
-               c = sp->data;
+               c = sp->data&((tp->t_cflag&CSIZE)==CS8 ? 0xff : 0x7f);
                if ((sp->port&VX_RO) == VX_RO && !overrun) {
                if ((sp->port&VX_RO) == VX_RO && !overrun) {
-                       printf("vx%d: receiver overrun\n", vi->ui_unit);
+                       log(LOG_ERR, "vx%d: receiver overrun\n", vi->ui_unit);
                        overrun = 1;
                        continue;
                }
                if (sp->port&VX_PE)
                        overrun = 1;
                        continue;
                }
                if (sp->port&VX_PE)
-                       if ((tp->t_flags&(EVENP|ODDP)) == EVENP ||
-                           (tp->t_flags&(EVENP|ODDP)) == ODDP)
-                               continue;
-               if (sp->port&VX_FE) {
-                       /*
-                        * At framing error (break) generate
-                        * a null (in raw mode, for getty), or a
-                        * interrupt (in cooked/cbreak mode).
-                        */
-                       if (tp->t_flags&RAW)
-                               c = 0;
-                       else
-                               c = tp->t_intrc;
-               }
+                       c |= TTY_PE;
+               if (sp->port&VX_FE) 
+                       c |= TTY_FE;
                (*linesw[tp->t_line].l_rint)(c, tp);
        }
        *osp = 0;
                (*linesw[tp->t_line].l_rint)(c, tp);
        }
        *osp = 0;
-       return (1);
 }
 
 /*
 }
 
 /*
@@ -335,63 +387,99 @@ vxioctl(dev, cmd, data, flag)
 
        tp = &vx_tty[minor(dev)];
        error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
 
        tp = &vx_tty[minor(dev)];
        error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
-       if (error == 0)
+       if (error >= 0)
                return (error);
        error = ttioctl(tp, cmd, data, flag);
                return (error);
        error = ttioctl(tp, cmd, data, flag);
-       if (error >= 0) {
-               if (cmd == TIOCSETP || cmd == TIOCSETN)
-                       vxparam(dev);
+       if (error >= 0) 
                return (error);
                return (error);
-       }
        return (ENOTTY);
 }
 
        return (ENOTTY);
 }
 
-vxparam(dev)
-       dev_t dev;
+vxparam(tp, t)
+       struct tty *tp;
+       struct termios *t;
 {
 
 {
 
-       vxcparam(dev, 1);
+       return (vxcparam(tp, t, 1));
 }
 
 /*
  * Set parameters from open or stty into the VX hardware
  * registers.
  */
 }
 
 /*
  * Set parameters from open or stty into the VX hardware
  * registers.
  */
-vxcparam(dev, wait)
-       dev_t dev;
+vxcparam(tp, t, wait)
+       struct tty *tp;
+       struct termios *t;
        int wait;
 {
        int wait;
 {
-       register struct tty *tp;
        register struct vx_softc *vs;
        register struct vxcmd *cp;
        register struct vx_softc *vs;
        register struct vxcmd *cp;
-       int s;
+       int s, error = 0;
+       int speedcode = ttspeedtab(t->c_ospeed, vxspeedtab);
 
 
-       tp = &vx_tty[minor(dev)];
+       if (speedcode < 0 || (t->c_ispeed != t->c_ospeed && t->c_ispeed))
+               return (EINVAL);
        vs = (struct vx_softc *)tp->t_addr;
        cp = vobtain(vs);
        s = spl8();
        vs = (struct vx_softc *)tp->t_addr;
        cp = vobtain(vs);
        s = spl8();
-       cp->cmd = VXC_LPARAX;           /* set command to "load parameters" */
-       cp->par[1] = minor(dev)&017;    /* port number */
-       cp->par[2] = (tp->t_flags&RAW) ? 0 : tp->t_startc;      /* XON char */
-       cp->par[3] = (tp->t_flags&RAW) ? 0 : tp->t_stopc;       /* XOFF char */
-       if (tp->t_flags&(RAW|LITOUT) ||
-           (tp->t_flags&(EVENP|ODDP)) == (EVENP|ODDP)) {
-               cp->par[4] = 0xc0;      /* 8 bits of data */
-               cp->par[7] = 0;         /* no parity */
-       } else {
-               cp->par[4] = 0x40;      /* 7 bits of data */
-               if ((tp->t_flags&(EVENP|ODDP)) == ODDP)
-                       cp->par[7] = 1;         /* odd parity */
-               else if((tp->t_flags&(EVENP|ODDP)) == EVENP)
-                       cp->par[7] = 3;         /* even parity */
+       /*
+        * Construct ``load parameters'' command block
+        * to setup baud rates, xon-xoff chars, parity,
+        * and stop bits for the specified port.
+        */
+       cp->cmd = VXC_LPARAX;
+       cp->par[1] = VXPORT(minor(tp->t_dev));
+       /*
+        * note: if the hardware does flow control, ^V doesn't work
+        * to escape ^S
+        */
+       if (t->c_iflag&IXON) {
+               if (t->c_cc[VSTART] == _POSIX_VDISABLE)
+                       cp->par[2] = 0;
+               else
+                       cp->par[2] = t->c_cc[VSTART];
+               if (t->c_cc[VSTOP] == _POSIX_VDISABLE)
+                       cp->par[3] = 0;
                else
                else
-                       cp->par[7] = 0;         /* no parity */
+                       cp->par[3] = t->c_cc[VSTOP];
+       } else 
+               cp->par[2] = cp->par[3] = 0;
+#ifdef notnow
+       switch (t->c_cflag & CSIZE) {   /* XXX */
+       case CS8:
+#endif
+               cp->par[4] = BITS8;             /* 8 bits of data */
+#ifdef notnow
+               break;
+       case CS7:
+               cp->par[4] = BITS7;             /* 7 bits of data */
+               break;
+       case CS6:
+               cp->par[4] = BITS6;             /* 6 bits of data */
+               break;
+       case CS5:
+               cp->par[4] = BITS5;             /* 5 bits of data */
+               break;
+       }
+       if ((t->c_cflag & PARENB) == 0)         /* XXX */
+#endif
+               cp->par[7] = VNOPARITY;         /* no parity */
+#ifdef notnow
+       else if (t->c_cflag&PARODD)
+               cp->par[7] = VODDP;     /* odd parity */
+       else
+               cp->par[7] = VEVENP;    /* even parity */
+#endif
+       cp->par[5] = (t->c_cflag&CSTOPB) ? VSTOP2 : VSTOP1;
+       cp->par[6] = speedcode;
+       if (vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
+               error = tsleep((caddr_t)cp, TTIPRI | PCATCH, ttyout, 0);
+       if ((t->c_ospeed)==0) {
+               tp->t_cflag |= HUPCL;
+               vcmodem(tp->t_dev, VMOD_OFF);
        }
        }
-       cp->par[5] = 0x4;                       /* 1 stop bit */
-       cp->par[6] = tp->t_ospeed;
-       if (vcmd(vs->vs_nbr, (caddr_t)&cp->cmd) && wait)
-               sleep((caddr_t)cp,TTIPRI);
        splx(s);
        splx(s);
+       return (error);
 }
 
 /*
 }
 
 /*
@@ -403,21 +491,13 @@ vxxint(vx, cp)
        register int vx;
        register struct vxcmd *cp;
 {
        register int vx;
        register struct vxcmd *cp;
 {
-       register struct vxmit *vp, *pvp;
-       register struct tty *tp, *tp0;
-       register struct vx_softc *vs;
-       register struct tty *hp;
+       register struct vxmit *vp;
+       register struct tty *tp, *tp0;
+       register struct vx_softc *vs;
 
        vs = &vx_softc[vx];
        cp = (struct vxcmd *)((long *)cp-1);
 
        vs = &vx_softc[vx];
        cp = (struct vxcmd *)((long *)cp-1);
-#if NVBSC > 0
-       if (cp->cmd == VXC_MDMCTL1 || cp->cmd == VXC_HUNTMD1 ||
-           cp->cmd == VXC_LPARAX1) {
-               vrelease(vs, cp);
-               wakeup((caddr_t)cp);
-               return;
-       }
-#endif
+
        switch (cp->cmd&0xff00) {
 
        case VXC_LIDENT:        /* initialization complete */
        switch (cp->cmd&0xff00) {
 
        case VXC_LIDENT:        /* initialization complete */
@@ -445,14 +525,6 @@ vxxint(vx, cp)
        vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
        for (; vp >= (struct vxmit *)cp->par; vp--) {
                tp = tp0 + (vp->line & 017);
        vp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
        for (; vp >= (struct vxmit *)cp->par; vp--) {
                tp = tp0 + (vp->line & 017);
-#if NVBSC > 0
-               if (tp->t_line == LDISP) {
-                       vrelease(xp, cp);
-                       bsctxd(vp->line & 017);
-                       return;
-               }
-#endif
-               pvp = vp;
                tp->t_state &= ~TS_BUSY;
                if (tp->t_state & TS_FLUSH) {
                        tp->t_state &= ~TS_FLUSH;
                tp->t_state &= ~TS_BUSY;
                if (tp->t_state & TS_FLUSH) {
                        tp->t_state &= ~TS_FLUSH;
@@ -460,31 +532,19 @@ vxxint(vx, cp)
                } else
                        ndflush(&tp->t_outq, vp->bcount+1);
        }
                } else
                        ndflush(&tp->t_outq, vp->bcount+1);
        }
-       vs->vs_xmtcnt--;
        vrelease(vs, cp);
        vrelease(vs, cp);
-       if (vs->vs_vers == VXV_NEW) {
-               vp = pvp;
-               vs->vs_active |= 1 << ((vp->line & 017) - vs->vs_loport);
-               if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) {
-                       vs->vs_xmtcnt++;
-                       vcmd(vx, (caddr_t)&cp->cmd);
-                       return;
-               }
-               vs->vs_active &= ~(1 << ((vp->line & 017) - vs->vs_loport));
-       } else {
-               vs->vs_active = 1;
+       if (vs->vs_vers == VXV_NEW)
+               (*linesw[tp->t_line].l_start)(tp);
+       else {
                tp0 = &vx_tty[vx*16 + vs->vs_hiport];
                for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
                tp0 = &vx_tty[vx*16 + vs->vs_hiport];
                for(tp = &vx_tty[vx*16 + vs->vs_loport]; tp <= tp0; tp++)
-                       if (vxstart(tp) && (cp = nextcmd(vs)) != NULL) {
-                               vs->vs_xmtcnt++;
-                               vcmd(vx, (caddr_t)&cp->cmd);
-                       }
+                       (*linesw[tp->t_line].l_start)(tp);
                if ((cp = nextcmd(vs)) != NULL) {       /* command to send? */
                        vs->vs_xmtcnt++;
                if ((cp = nextcmd(vs)) != NULL) {       /* command to send? */
                        vs->vs_xmtcnt++;
-                       vcmd(vx, (caddr_t)&cp->cmd);
+                       (void) vcmd(vx, (caddr_t)&cp->cmd);
                }
                }
-               vs->vs_active = 0;
        }
        }
+       vs->vs_xmtcnt--;
 }
 
 /*
 }
 
 /*
@@ -499,7 +559,7 @@ vxforce(vs)
        s = spl8();
        if ((cp = nextcmd(vs)) != NULL) {
                vs->vs_xmtcnt++;
        s = spl8();
        if ((cp = nextcmd(vs)) != NULL) {
                vs->vs_xmtcnt++;
-               vcmd(vs->vs_nbr, (caddr_t)&cp->cmd);
+               (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
        }
        splx(s);
 }
        }
        splx(s);
 }
@@ -511,16 +571,14 @@ vxstart(tp)
        register struct tty *tp;
 {
        register short n;
        register struct tty *tp;
 {
        register short n;
-       register struct vx_softc *vs;
-       register char *outb;
-       register full = 0;
-       int k, s, port;
+       register struct vx_softc *vs;
+       int s, port;
 
        s = spl8();
 
        s = spl8();
-       port = minor(tp->t_dev) & 017;
+       port = VXPORT(minor(tp->t_dev));
        vs = (struct vx_softc *)tp->t_addr;
        if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
        vs = (struct vx_softc *)tp->t_addr;
        if ((tp->t_state&(TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) == 0) {
-               if (tp->t_outq.c_cc <= TTLOWAT(tp)) {
+               if (tp->t_outq.c_cc <= tp->t_lowat) {
                        if (tp->t_state&TS_ASLEEP) {
                                tp->t_state &= ~TS_ASLEEP;
                                wakeup((caddr_t)&tp->t_outq);
                        if (tp->t_state&TS_ASLEEP) {
                                tp->t_state &= ~TS_ASLEEP;
                                wakeup((caddr_t)&tp->t_outq);
@@ -533,38 +591,26 @@ vxstart(tp)
                }
                if (tp->t_outq.c_cc == 0) {
                        splx(s);
                }
                if (tp->t_outq.c_cc == 0) {
                        splx(s);
-                       return (0);
+                       return;
                }
                scope_out(3);
                }
                scope_out(3);
-               if ((tp->t_flags&(RAW|LITOUT)) == 0)  
-                       full = 0200;
-               if ((n = ndqb(&tp->t_outq, full)) == 0) {
-                       if (full) {
+               if (1 || !(tp->t_oflag&OPOST))  /* XXX */
+                       n = ndqb(&tp->t_outq, 0);
+               else {
+                       n = ndqb(&tp->t_outq, 0200);
+                       if (n == 0) {
                                n = getc(&tp->t_outq);
                                timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
                                tp->t_state |= TS_TIMEOUT;
                                n = getc(&tp->t_outq);
                                timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
                                tp->t_state |= TS_TIMEOUT;
-                               full = 0;
+                               n = 0;
                        }
                        }
-               } else {
-                       outb = (char *)tp->t_outq.c_cf;
+               }
+               if (n) {
                        tp->t_state |= TS_BUSY;
                        tp->t_state |= TS_BUSY;
-                       if (vs->vs_vers == VXV_NEW)
-                               k = vs->vs_active & (1 << (port-vs->vs_loport));
-                       else
-                               k = vs->vs_active;
-                       full = vsetq(vs, port, outb, n);
-                       if ((k&1) == 0) {       /* not called from vxxint */
-                               if (full || vs->vs_xmtcnt == 0) {
-                                       outb = (char *)(&nextcmd(vs)->cmd);
-                                       vs->vs_xmtcnt++;
-                                       vcmd(vs->vs_nbr, outb);
-                               } else
-                                       timeout(vxforce, (caddr_t)vs, 3);
-                       }
+                       vsetq(vs, port, (char *)tp->t_outq.c_cf, n);
                }
        }
        splx(s);
                }
        }
        splx(s);
-       return (full);  /* indicate if max commands or not */
 }
 
 /*
 }
 
 /*
@@ -586,23 +632,21 @@ static    int vxbbno = -1;
 /*
  * VIOCX Initialization.  Makes free lists of command buffers.
  * Resets all viocx's.  Issues a LIDENT command to each
 /*
  * VIOCX Initialization.  Makes free lists of command buffers.
  * Resets all viocx's.  Issues a LIDENT command to each
- * viocx which establishes interrupt vectors and logical
- * port numbers
+ * viocx to establish interrupt vectors and logical port numbers.
  */
  */
-vxinit(vx, wait) 
+vxinit(vx, wait)
        register int vx;
        int wait;
 {
        register int vx;
        int wait;
 {
-       register struct vx_softc *vs;
-       register struct vxdevice *addr;
-       register struct vxcmd *cp;
+       register struct vx_softc *vs;
+       register struct vxdevice *addr;
+       register struct vxcmd *cp;
        register char *resp;
        register int j;
        register char *resp;
        register int j;
-       char type;
+       char type, *typestring;
 
        vs = &vx_softc[vx];
 
        vs = &vx_softc[vx];
-       vs->vs_type = 0;                /* viox-x by default */
-       addr = (struct vxdevice *)(((struct vba_device *)vxinfo[vx])->ui_addr);
+       addr = vs->vs_addr;
        type = addr->v_ident;
        vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
        if (vs->vs_vers == VXV_NEW)
        type = addr->v_ident;
        vs->vs_vers = (type&VXT_NEW) ? VXV_NEW : VXV_OLD;
        if (vs->vs_vers == VXV_NEW)
@@ -611,60 +655,58 @@ vxinit(vx, wait)
 
        case VXT_VIOCX:
        case VXT_VIOCX|VXT_NEW:
 
        case VXT_VIOCX:
        case VXT_VIOCX|VXT_NEW:
-               /* set dcd for printer ports */
-               for (j = 0;j < 16;j++)
-                       if (addr->v_portyp[j] == 4)
+               typestring = "VIOC-X";
+               /* set soft carrier for printer ports */
+               for (j = 0; j < 16; j++)
+                       if (vs->vs_softCAR & (1 << j) ||
+                           addr->v_portyp[j] == VXT_PARALLEL) {
+                               vs->vs_softCAR |= 1 << j;
                                addr->v_dcd |= 1 << j;
                                addr->v_dcd |= 1 << j;
+                       }
                break;
 
        case VXT_PVIOCX:
        case VXT_PVIOCX|VXT_NEW:
                break;
 
        case VXT_PVIOCX:
        case VXT_PVIOCX|VXT_NEW:
+               typestring = "VIOC-X (old connector panel)";
                break;
                break;
-#if NVBSC > 0
-       case VX_VIOCB:                  /* old f/w bisync */
-       case VX_VIOCB|VXT_NEW: {        /* new f/w bisync */
-               register struct bsc *bp;
-               extern struct bsc bsc[];
-
-               printf("%X: %x%x %s VIOC-B, ", (long)addr, (int)addr->v_ident,
-                   (int)addr->v_fault, vs->vs_vers == VXV_OLD ? "old" : "16k");
-               for (bp = &bsc[0]; bp <= &bsc[NBSC]; bp++)
-                       bp->b_devregs = (caddr_t)vs;
-               printf("%d BSC Ports initialized.\n", NBSC);
-               break;
-               if (vs->vs_vers == VXV_NEW && CBSIZE > addr->v_maxxmt)
-                       printf("vxinit: Warning CBSIZE > maxxmt\n");
-               break;
-#endif
        case VXT_VIOCBOP:               /* VIOC-BOP */
                vs->vs_type = 1;
                vs->vs_bop = ++vxbbno;
                printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
        case VXT_VIOCBOP:               /* VIOC-BOP */
                vs->vs_type = 1;
                vs->vs_bop = ++vxbbno;
                printf("VIOC-BOP no. %d at %x\n", vs->vs_bop, addr);
-
-       default:                /* unknown viocx type */
+               goto unsup;
+       default:
                printf("vx%d: unknown type %x\n", vx, type);
                printf("vx%d: unknown type %x\n", vx, type);
+       unsup:
+               vxinfo[vx]->ui_alive = 0;
                return;
        }
                return;
        }
-       vs->vs_nbr = -1;
-       vs->vs_maxcmd = vs->vs_vers == VXV_NEW ? 24 : 4;
-       /* init all cmd buffers */
+       vs->vs_nbr = vx;                /* assign board number */
+       vs->vs_maxcmd = (vs->vs_vers == VXV_NEW) ? 24 : 4;
+       /*
+        * Initialize all cmd buffers by linking them
+        * into a free list.
+        */
        for (j = 0; j < NVCXBUFS; j++) {
        for (j = 0; j < NVCXBUFS; j++) {
-               cp = &vs->vs_lst[j];    /* index a buffer */
-               cp->c_fwd = &vs->vs_lst[j+1];   /* point to next buf */
+               cp = &vs->vs_lst[j];
+               cp->c_fwd = &vs->vs_lst[j+1];
        }
        vs->vs_avail = &vs->vs_lst[0];  /* set idx to 1st free buf */
        cp->c_fwd = (struct vxcmd *)0;  /* mark last buf in free list */
 
        }
        vs->vs_avail = &vs->vs_lst[0];  /* set idx to 1st free buf */
        cp->c_fwd = (struct vxcmd *)0;  /* mark last buf in free list */
 
-       cp = vobtain(vs);               /* grab the control block */
-       cp->cmd = VXC_LIDENT;           /* set command type */
+       /*
+        * Establish the interrupt vectors and define the port numbers.
+        */
+       cp = vobtain(vs);
+       cp->cmd = VXC_LIDENT;
        cp->par[0] = vs->vs_ivec;       /* ack vector */
        cp->par[1] = cp->par[0]+1;      /* cmd resp vector */
        cp->par[3] = cp->par[0]+2;      /* unsol intr vector */
        cp->par[4] = 15;                /* max ports, no longer used */
        cp->par[5] = 0;                 /* set 1st port number */
        cp->par[0] = vs->vs_ivec;       /* ack vector */
        cp->par[1] = cp->par[0]+1;      /* cmd resp vector */
        cp->par[3] = cp->par[0]+2;      /* unsol intr vector */
        cp->par[4] = 15;                /* max ports, no longer used */
        cp->par[5] = 0;                 /* set 1st port number */
-       vcmd(vx, (caddr_t)&cp->cmd);    /* initialize the VIOC-X */
+       (void) vcmd(vx, (caddr_t)&cp->cmd);
        if (!wait)
                return;
        if (!wait)
                return;
+
        for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
                ;
        if (j >= 4000000)
        for (j = 0; cp->cmd == VXC_LIDENT && j < 4000000; j++)
                ;
        if (j >= 4000000)
@@ -672,14 +714,16 @@ vxinit(vx, wait)
 
        /* calculate address of response buffer */
        resp = (char *)addr + (addr->v_rspoff&0x3fff);
 
        /* calculate address of response buffer */
        resp = (char *)addr + (addr->v_rspoff&0x3fff);
-       if (resp[0] != 0 && (resp[0]&0177) != 3) {      /* did init work? */
-               vrelease(vs, cp);
+       if (resp[0] != 0 && (resp[0]&0177) != 3) {
+               vrelease(vs, cp);       /* init failed */
                return;
        }
        vs->vs_loport = cp->par[5];
        vs->vs_hiport = cp->par[7];
                return;
        }
        vs->vs_loport = cp->par[5];
        vs->vs_hiport = cp->par[7];
+       printf("vx%d: %s%s, ports %d-%d\n", vx,
+           (vs->vs_vers == VXV_NEW) ? "" : "old ", typestring,
+           vs->vs_loport, vs->vs_hiport);
        vrelease(vs, cp);
        vrelease(vs, cp);
-       vs->vs_nbr = vx;                /* assign VIOC-X board number */
 }
 
 /*
 }
 
 /*
@@ -687,9 +731,9 @@ vxinit(vx, wait)
  */
 struct vxcmd *
 vobtain(vs)
  */
 struct vxcmd *
 vobtain(vs)
-       register struct vx_softc *vs;
+       register struct vx_softc *vs;
 {
 {
-       register struct vxcmd *p;
+       register struct vxcmd *p;
        int s;
 
        s = spl8();
        int s;
 
        s = spl8();
@@ -699,12 +743,12 @@ vobtain(vs)
                if (vxintr4&VXNOBUF)
                        vxintr4 &= ~VXNOBUF;
 #endif
                if (vxintr4&VXNOBUF)
                        vxintr4 &= ~VXNOBUF;
 #endif
-               printf("vx%d: no buffers\n", vs - vx_softc);
-               vxstreset(vs - vx_softc);
+               printf("vx%d: no buffers\n", vs->vs_nbr);
+               vxstreset(vs->vs_nbr);
                splx(s);
                return (vobtain(vs));
        }
                splx(s);
                return (vobtain(vs));
        }
-       vs->vs_avail = vs->vs_avail->c_fwd;
+       vs->vs_avail = p->c_fwd;
        splx(s);
        return ((struct vxcmd *)p);
 }
        splx(s);
        return ((struct vxcmd *)p);
 }
@@ -713,8 +757,8 @@ vobtain(vs)
  * Release a command buffer
  */
 vrelease(vs, cp)
  * Release a command buffer
  */
 vrelease(vs, cp)
-       register struct vx_softc *vs;
-       register struct vxcmd *cp;
+       register struct vx_softc *vs;
+       register struct vxcmd *cp;
 {
        int s;
 
 {
        int s;
 
@@ -728,15 +772,11 @@ vrelease(vs, cp)
        splx(s);
 }
 
        splx(s);
 }
 
-/*
- * vxcmd - 
- *
- */
 struct vxcmd *
 nextcmd(vs)
 struct vxcmd *
 nextcmd(vs)
-       register struct vx_softc *vs;
+       register struct vx_softc *vs;
 {
 {
-       register struct vxcmd *cp;
+       register struct vxcmd *cp;
        int s;
 
        s = spl8();
        int s;
 
        s = spl8();
@@ -747,49 +787,64 @@ nextcmd(vs)
 }
 
 /*
 }
 
 /*
- * assemble transmits into a multiple command.
+ * Assemble transmits into a multiple command;
  * up to 8 transmits to 8 lines can be assembled together
  * up to 8 transmits to 8 lines can be assembled together
+ * (on PVIOCX only).
  */
  */
-vsetq(vs ,d ,addr, n)
-       register struct vx_softc *vs;
+vsetq(vs, line, addr, n)
+       register struct vx_softc *vs;
        caddr_t addr;
 {
        caddr_t addr;
 {
-       register struct vxcmd *cp;
-       register struct vxmit *mp;
-       register char *p;
-       register i;
+       register struct vxcmd *cp;
+       register struct vxmit *mp;
 
 
+       /*
+        * Grab a new command buffer or append
+        * to the current one being built.
+        */
        cp = vs->vs_build;
        if (cp == (struct vxcmd *)0) {
                cp = vobtain(vs);
                vs->vs_build = cp;
                cp->cmd = VXC_XMITDTA;
        } else {
        cp = vs->vs_build;
        if (cp == (struct vxcmd *)0) {
                cp = vobtain(vs);
                vs->vs_build = cp;
                cp->cmd = VXC_XMITDTA;
        } else {
-               if ((cp->cmd & 07) == 07) {
+               if ((cp->cmd & 07) == 07 || vs->vs_vers == VXV_NEW) {
                        printf("vx%d: setq overflow\n", vs-vx_softc);
                        printf("vx%d: setq overflow\n", vs-vx_softc);
-                       vxstreset(vs->vs_nbr);
-                       return (0);
+                       vxstreset((int)vs->vs_nbr);
+                       return;
                }
                cp->cmd++;
        }
                }
                cp->cmd++;
        }
+       /*
+        * Select the next vxmit buffer and copy the
+        * characters into the buffer (if there's room
+        * and the device supports ``immediate mode'',
+        * or store an indirect pointer to the data.
+        */
        mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
        mp->bcount = n-1;
        mp = (struct vxmit *)(cp->par + (cp->cmd & 07)*sizeof (struct vxmit));
        mp->bcount = n-1;
-       mp->line = d;
-       if (vs->vs_vers == VXV_NEW && n <= 6) {
+       mp->line = line;
+       if (vs->vs_vers == VXV_NEW && n <= sizeof (mp->ostream)) {
                cp->cmd = VXC_XMITIMM;
                cp->cmd = VXC_XMITIMM;
-               p = addr;
-               /* bcopy(addr, &(char *)mp->ostream, n) ; */
+               bcopy(addr, mp->ostream, (unsigned)n);
        } else {
        } else {
+               /* get system address of clist block */
                addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
                addr = (caddr_t)vtoph((struct proc *)0, (unsigned)addr);
-                               /* should be a sys address */
-               p = (char *)&addr;
-               n = sizeof addr;
-               /* mp->ostream = addr ; */
+               bcopy((caddr_t)&addr, mp->ostream, sizeof (addr));
        }
        }
-       for (i = 0; i < n; i++)
-               mp->ostream[i] = *p++;
-       if (vs->vs_vers == VXV_NEW)
-       return (vs->vs_vers == VXV_NEW ? 1 : (cp->cmd&07) == 7);
+       /*
+        * We send the data immediately if a VIOCX,
+        * the command buffer is full, or if we've nothing
+        * currently outstanding.  If we don't send it,
+        * set a timeout to force the data to be sent soon.
+        */
+       if (vs->vs_vers == VXV_NEW || (cp->cmd & 07) == 7 ||
+           vs->vs_xmtcnt == 0) {
+               vs->vs_xmtcnt++;
+               (void) vcmd((int)vs->vs_nbr, (char *)&cp->cmd);
+               vs->vs_build = 0;
+       } else
+               timeout(vxforce, (caddr_t)vs, 3);
 }
 
 /*
 }
 
 /*
@@ -799,22 +854,20 @@ vcmd(vx, cmdad)
        register int vx;
        register caddr_t cmdad;
 {
        register int vx;
        register caddr_t cmdad;
 {
-       register struct vcmds *cp;
-       register struct vx_softc *vs;
+       register struct vcmds *cp;
+       register struct vx_softc *vs = &vx_softc[vx];
        int s;
 
        s = spl8();
        int s;
 
        s = spl8();
-       vs = &vx_softc[vx];
+       /*
+        * When the vioc is resetting, don't process
+        * anything other than VXC_LIDENT commands.
+        */
        if (vs->vs_state == VXS_RESET && cmdad != NULL) {
        if (vs->vs_state == VXS_RESET && cmdad != NULL) {
-               /*
-                * When the vioc is resetting, don't process
-                * anything other than LIDENT commands.
-                */
-               register struct vxcmd *cmdp = (struct vxcmd *)
-                       ((char *)cmdad - sizeof (cmdp->c_fwd));
+               struct vxcmd *vcp = (struct vxcmd *)(cmdad-sizeof (vcp->c_fwd));
 
 
-               if (cmdp->cmd != VXC_LIDENT) {
-                       vrelease(vs, cmdp);
+               if (vcp->cmd != VXC_LIDENT) {
+                       vrelease(vs, vcp);
                        return (0);
                }
        }
                        return (0);
                }
        }
@@ -848,32 +901,24 @@ vcmd(vx, cmdad)
 vackint(vx)
        register vx;
 {
 vackint(vx)
        register vx;
 {
-       register struct vxdevice *vp;
-       register struct vcmds *cp;
+       register struct vxdevice *vp;
+       register struct vcmds *cp;
        struct vx_softc *vs;
        int s;
 
        scope_out(5);
        vs = &vx_softc[vx];
        struct vx_softc *vs;
        int s;
 
        scope_out(5);
        vs = &vx_softc[vx];
-       if (vs->vs_type) {      /* Its a BOP */
-#ifdef SNA_DEBUG
-               extern vbrall();
-
-               if (snadebug & SVIOC)
-                       printf("vx%d: vack interrupt from BOP\n", vx);
-               vbrall(vx);     /* Int. from BOP, port 0 */
-#endif
+       if (vs->vs_type)        /* Its a BOP */
                return;
                return;
-       }
        s = spl8();
        s = spl8();
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vs->vs_addr;
        cp = &vs->vs_cmds;
        cp = &vs->vs_cmds;
-       if (vp->v_vcid & V_ERR) {
+       if (vp->v_vcid&V_ERR) {
                register char *resp;
                register i;
                register char *resp;
                register i;
-               printf("vx%d INTR ERR type %x v_dcd %x\n", vx,
+
+               printf("vx%d: ackint error type %x v_dcd %x\n", vx,
                    vp->v_vcid & 07, vp->v_dcd & 0xff);
                    vp->v_vcid & 07, vp->v_dcd & 0xff);
-               /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */
                resp = (char *)vs->vs_mricmd;
                for (i = 0; i < 16; i++)
                        printf("%x ", resp[i]&0xff);
                resp = (char *)vs->vs_mricmd;
                for (i = 0; i < 16; i++)
                        printf("%x ", resp[i]&0xff);
@@ -885,10 +930,10 @@ vackint(vx)
        if ((vp->v_hdwre&017) == CMDquals) {
 #ifdef VX_DEBUG
                if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */
        if ((vp->v_hdwre&017) == CMDquals) {
 #ifdef VX_DEBUG
                if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */
-                       register struct vxcmd *cp1;
-                       register struct vxcmd *cp0 = (struct vxcmd *)
-                               ((long)cp->cmdbuf[cp->v_empty] - 4);
+                       struct vxcmd *cp1, *cp0;
 
 
+                       cp0 = (struct vxcmd *)
+                           ((caddr_t)cp->cmdbuf[cp->v_empty]-sizeof (cp0->c_fwd));
                        if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
                                cp1 = vobtain(vs);
                                *cp1 = *cp0;
                        if (cp0->cmd == VXC_XMITDTA || cp0->cmd == VXC_XMITIMM) {
                                cp1 = vobtain(vs);
                                *cp1 = *cp0;
@@ -916,8 +961,8 @@ vackint(vx)
 vcmdrsp(vx)
        register vx;
 {
 vcmdrsp(vx)
        register vx;
 {
-       register struct vxdevice *vp;
-       register struct vcmds *cp;
+       register struct vxdevice *vp;
+       register struct vcmds *cp;
        register caddr_t cmd;
        register struct vx_softc *vs;
        register char *resp;
        register caddr_t cmd;
        register struct vx_softc *vs;
        register char *resp;
@@ -931,7 +976,7 @@ vcmdrsp(vx)
                return;
        }
        s = spl8();
                return;
        }
        s = spl8();
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vs->vs_addr;
        cp = &vs->vs_cmds;
        resp = (char *)vp + (vp->v_rspoff&0x7fff);
        if (((k = resp[1])&V_UNBSY) == 0) {
        cp = &vs->vs_cmds;
        resp = (char *)vp + (vp->v_rspoff&0x7fff);
        if (((k = resp[1])&V_UNBSY) == 0) {
@@ -961,7 +1006,7 @@ vcmdrsp(vx)
 vunsol(vx)
        register vx;
 {
 vunsol(vx)
        register vx;
 {
-       register struct vxdevice *vp;
+       register struct vxdevice *vp;
        struct vx_softc *vs;
        int s;
 
        struct vx_softc *vs;
        int s;
 
@@ -972,7 +1017,7 @@ vunsol(vx)
                return;
        }
        s = spl8();
                return;
        }
        s = spl8();
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vs->vs_addr;
        if (vp->v_uqual&V_UNBSY) {
                vxrint(vx);
                vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
        if (vp->v_uqual&V_UNBSY) {
                vxrint(vx);
                vinthandl(vx, ((V_BSY|UNSquals) << 8)|V_INTR);
@@ -987,7 +1032,7 @@ vunsol(vx)
 }
 
 /*
 }
 
 /*
- * Enqueue an interrupt
+ * Enqueue an interrupt.
  */
 vinthandl(vx, item)
        register int vx;
  */
 vinthandl(vx, item)
        register int vx;
@@ -997,7 +1042,7 @@ vinthandl(vx, item)
        int empty;
 
        cp = &vx_softc[vx].vs_cmds;
        int empty;
 
        cp = &vx_softc[vx].vs_cmds;
-       empty = cp->v_itrfill == cp->v_itrempt;
+       empty = (cp->v_itrfill == cp->v_itrempt);
        cp->v_itrqueu[cp->v_itrfill] = item;
        if (++cp->v_itrfill >= VC_IQLEN)
                cp->v_itrfill = 0;
        cp->v_itrqueu[cp->v_itrfill] = item;
        if (++cp->v_itrfill >= VC_IQLEN)
                cp->v_itrfill = 0;
@@ -1009,17 +1054,19 @@ vinthandl(vx, item)
 }
 
 vintempt(vx)
 }
 
 vintempt(vx)
-       register int vx;
+       int vx;
 {
        register struct vcmds *cp;
        register struct vxdevice *vp;
 {
        register struct vcmds *cp;
        register struct vxdevice *vp;
+       register struct vx_softc *vs;
        register short item;
        register short *intr;
 
        register short item;
        register short *intr;
 
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vs = &vx_softc[vx];
+       vp = vs->vs_addr;
        if (vp->v_vioc&V_BSY)
                return;
        if (vp->v_vioc&V_BSY)
                return;
-       cp = &vx_softc[vx].vs_cmds;
+       cp = &vs->vs_cmds;
        if (cp->v_itrempt == cp->v_itrfill)
                return;
        item = cp->v_itrqueu[cp->v_itrempt];
        if (cp->v_itrempt == cp->v_itrfill)
                return;
        item = cp->v_itrqueu[cp->v_itrempt];
@@ -1031,7 +1078,7 @@ vintempt(vx)
 
                if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
                        break;
 
                if (cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
                        break;
-               vx_softc[vx].vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
+               vs->vs_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
                phys = vtoph((struct proc *)0, 
                    (unsigned)cp->cmdbuf[cp->v_empty]);
                vp->v_vcp[0] = ((short *)&phys)[0];
                phys = vtoph((struct proc *)0, 
                    (unsigned)cp->cmdbuf[cp->v_empty]);
                vp->v_vcp[0] = ((short *)&phys)[0];
@@ -1059,28 +1106,29 @@ vintempt(vx)
  * Start a reset on a vioc after error (hopefully)
  */
 vxstreset(vx)
  * Start a reset on a vioc after error (hopefully)
  */
 vxstreset(vx)
-       register vx;
+       register int vx;
 {
        register struct vx_softc *vs;
 {
        register struct vx_softc *vs;
-       register struct vxdevice *vp;
+       register struct vxdevice *vp;
        register struct vxcmd *cp;
        register int j;
        extern int vxinreset();
        int s;
 
        register struct vxcmd *cp;
        register int j;
        extern int vxinreset();
        int s;
 
-       s = spl8() ;
        vs = &vx_softc[vx];
        vs = &vx_softc[vx];
+       s = spl8();
        if (vs->vs_state == VXS_RESET) {        /* avoid recursion */
                splx(s);
                return;
        }
        if (vs->vs_state == VXS_RESET) {        /* avoid recursion */
                splx(s);
                return;
        }
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vs->vs_addr;
        /*
         * Zero out the vioc structures, mark the vioc as being
         * reset, reinitialize the free command list, reset the vioc
         * and start a timer to check on the progress of the reset.
         */
        /*
         * Zero out the vioc structures, mark the vioc as being
         * reset, reinitialize the free command list, reset the vioc
         * and start a timer to check on the progress of the reset.
         */
-       bzero((caddr_t)vs, (unsigned)sizeof (*vs));
+       bzero((caddr_t)&vs->vs_zero,
+           (unsigned)((caddr_t)(vs + 1) - (caddr_t)&vs->vs_zero));
 
        /*
         * Setting VXS_RESET prevents others from issuing
 
        /*
         * Setting VXS_RESET prevents others from issuing
@@ -1090,15 +1138,15 @@ vxstreset(vx)
        vs->vs_state = VXS_RESET;
        /* init all cmd buffers */
        for (j = 0; j < NVCXBUFS; j++) {
        vs->vs_state = VXS_RESET;
        /* init all cmd buffers */
        for (j = 0; j < NVCXBUFS; j++) {
-               cp = &vs->vs_lst[j];    /* index a buffer */
-               cp->c_fwd = &vs->vs_lst[j+1];   /* point to next buf */
+               cp = &vs->vs_lst[j];
+               cp->c_fwd = &vs->vs_lst[j+1];
        }
        }
-       vs->vs_avail = &vs->vs_lst[0];  /* set idx to 1st free buf */
-       cp->c_fwd = (struct vxcmd *)0;  /* mark last buf in free list */
+       vs->vs_avail = &vs->vs_lst[0];
+       cp->c_fwd = (struct vxcmd *)0;
        printf("vx%d: reset...", vx);
        vp->v_fault = 0;
        vp->v_vioc = V_BSY;
        printf("vx%d: reset...", vx);
        vp->v_fault = 0;
        vp->v_vioc = V_BSY;
-       vp->v_hdwre = V_RESET;          /* reset interrupt */
+       vp->v_hdwre = V_RESET;          /* generate reset interrupt */
        timeout(vxinreset, (caddr_t)vx, hz*5);
        splx(s);
 }
        timeout(vxinreset, (caddr_t)vx, hz*5);
        splx(s);
 }
@@ -1107,15 +1155,15 @@ vxstreset(vx)
 vxinreset(vx)
        int vx;
 {
 vxinreset(vx)
        int vx;
 {
-       register struct vxdevice *vp;
+       register struct vxdevice *vp;
        int s = spl8();
 
        int s = spl8();
 
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vx_softc[vx].vs_addr;
        /*
         * See if the vioc has reset.
         */
        if (vp->v_fault != VXF_READY) {
        /*
         * See if the vioc has reset.
         */
        if (vp->v_fault != VXF_READY) {
-               printf("failed\n");
+               printf(" vxreset failed\n");
                splx(s);
                return;
        }
                splx(s);
                return;
        }
@@ -1123,23 +1171,24 @@ vxinreset(vx)
         * Send a LIDENT to the vioc and mess with carrier flags
         * on parallel printer ports.
         */
         * Send a LIDENT to the vioc and mess with carrier flags
         * on parallel printer ports.
         */
-       vxinit(vx, (long)0);
+       vxinit(vx, 0);
        splx(s);
 }
 
 /*
        splx(s);
 }
 
 /*
+ * Finish the reset on the vioc after an error (hopefully).
+ *
  * Restore modem control, parameters and restart output.
  * Since the vioc can handle no more then 24 commands at a time
  * and we could generate as many as 48 commands, we must do this in
  * phases, issuing no more then 16 commands at a time.
  */
  * Restore modem control, parameters and restart output.
  * Since the vioc can handle no more then 24 commands at a time
  * and we could generate as many as 48 commands, we must do this in
  * phases, issuing no more then 16 commands at a time.
  */
-/* finish the reset on the vioc after an error (hopefully) */
 vxfnreset(vx, cp)
        register int vx;
        register struct vxcmd *cp;
 {
        register struct vx_softc *vs;
 vxfnreset(vx, cp)
        register int vx;
        register struct vxcmd *cp;
 {
        register struct vx_softc *vs;
-       register struct vxdevice *vp ;
+       register struct vxdevice *vp;
        register struct tty *tp, *tp0;
        register int i;
 #ifdef notdef
        register struct tty *tp, *tp0;
        register int i;
 #ifdef notdef
@@ -1149,13 +1198,10 @@ vxfnreset(vx, cp)
        int s = spl8();
 
        vs = &vx_softc[vx];
        int s = spl8();
 
        vs = &vx_softc[vx];
-       vs->vs_loport = cp->par[5];
-       vs->vs_hiport = cp->par[7];
        vrelease(vs, cp);
        vrelease(vs, cp);
-       vs->vs_nbr = vx;                        /* assign VIOC-X board number */
        vs->vs_state = VXS_READY;
 
        vs->vs_state = VXS_READY;
 
-       vp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vp = vs->vs_addr;
        vp->v_vcid = 0;
 
        /*
        vp->v_vcid = 0;
 
        /*
@@ -1168,38 +1214,20 @@ vxfnreset(vx, cp)
                        tp->t_state &= ~TS_CARR_ON;
                        vcmodem(tp->t_dev, VMOD_ON);
                        if (tp->t_state&TS_CARR_ON)
                        tp->t_state &= ~TS_CARR_ON;
                        vcmodem(tp->t_dev, VMOD_ON);
                        if (tp->t_state&TS_CARR_ON)
-                               wakeup((caddr_t)&tp->t_canq);
-                       else if (tp->t_state & TS_ISOPEN) {
-                               ttyflush(tp, FREAD|FWRITE);
-                               if (tp->t_state&TS_FLUSH)
-                                       wakeup((caddr_t)&tp->t_state);
-                               if ((tp->t_flags&NOHANG) == 0) {
-                                       gsignal(tp->t_pgrp, SIGHUP);
-                                       gsignal(tp->t_pgrp, SIGCONT);
-                               }
-                       }
+                               (void)(*linesw[tp->t_line].l_modem)(tp, 1);
+                       else if (tp->t_state & TS_ISOPEN)
+                               (void)(*linesw[tp->t_line].l_modem)(tp, 0);
                }
                }
+#ifdef notdef
                /*
                 * If carrier has changed while we were resetting,
                 * take appropriate action.
                 */
                /*
                 * If carrier has changed while we were resetting,
                 * take appropriate action.
                 */
-#ifdef notdef
                on = vp->v_dcd & 1<<i;
                on = vp->v_dcd & 1<<i;
-               if (on && (tp->t_state&TS_CARR_ON) == 0) {
-                       tp->t_state |= TS_CARR_ON;
-                       wakeup((caddr_t)&tp->t_canq);
-               } else if (!on && tp->t_state&TS_CARR_ON) {
-                       tp->t_state &= ~TS_CARR_ON;
-                       if (tp->t_state & TS_ISOPEN) {
-                               ttyflush(tp, FREAD|FWRITE);
-                               if (tp->t_state&TS_FLUSH)
-                                       wakeup((caddr_t)&tp->t_state);
-                               if ((tp->t_flags&NOHANG) == 0) {
-                                       gsignal(tp->t_pgrp, SIGHUP);
-                                       gsignal(tp->t_pgrp, SIGCONT);
-                               }
-                       }
-               }
+               if (on && (tp->t_state&TS_CARR_ON) == 0)
+                       (void)(*linesw[tp->t_line].l_modem)(tp, 1);
+               else if (!on && tp->t_state&TS_CARR_ON)
+                       (void)(*linesw[tp->t_line].l_modem)(tp, 0);
 #endif
        }
        vs->vs_state = VXS_RESET;
 #endif
        }
        vs->vs_state = VXS_RESET;
@@ -1215,30 +1243,30 @@ vxrestart(vx)
 {
        register struct tty *tp, *tp0;
        register struct vx_softc *vs;
 {
        register struct tty *tp, *tp0;
        register struct vx_softc *vs;
-       register int i, cnt;
+       register int i, count;
        int s = spl8();
 
        int s = spl8();
 
-       cnt = vx >> 8;
+       count = vx >> 8;
        vx &= 0xff;
        vs = &vx_softc[vx];
        vs->vs_state = VXS_READY;
        tp0 = &vx_tty[vx*16];
        for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
                tp = tp0 + i;
        vx &= 0xff;
        vs = &vx_softc[vx];
        vs->vs_state = VXS_READY;
        tp0 = &vx_tty[vx*16];
        for (i = vs->vs_loport; i <= vs->vs_hiport; i++) {
                tp = tp0 + i;
-               if (cnt != 0) {
+               if (count != 0) {
                        tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
                        if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
                                vxstart(tp);    /* restart pending output */
                } else {
                        if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
                        tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
                        if (tp->t_state&(TS_ISOPEN|TS_WOPEN))
                                vxstart(tp);    /* restart pending output */
                } else {
                        if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
-                               vxcparam(tp->t_dev, 0);
+                               vxcparam(tp, &tp->t_termios, 0);
                }
        }
                }
        }
-       if (cnt == 0) {
+       if (count == 0) {
                vs->vs_state = VXS_RESET;
                timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
        } else
                vs->vs_state = VXS_RESET;
                timeout(vxrestart, (caddr_t)(vx + 1*256), hz);
        } else
-               printf("done\n");
+               printf(" vx reset done\n");
        splx(s);
 }
 
        splx(s);
 }
 
@@ -1246,9 +1274,10 @@ vxreset(dev)
        dev_t dev;
 {
 
        dev_t dev;
 {
 
-       vxstreset(minor(dev) >> 4);     /* completes asynchronously */
+       vxstreset((int)VXUNIT(minor(dev)));     /* completes asynchronously */
 }
 
 }
 
+#ifdef VX_DEBUG
 vxfreset(vx)
        register int vx;
 {
 vxfreset(vx)
        register int vx;
 {
@@ -1260,6 +1289,7 @@ vxfreset(vx)
        vxstreset(vx);
        return (0);             /* completes asynchronously */
 }
        vxstreset(vx);
        return (0);             /* completes asynchronously */
 }
+#endif
 
 vcmodem(dev, flag)
        dev_t dev;
 
 vcmodem(dev, flag)
        dev_t dev;
@@ -1274,28 +1304,32 @@ vcmodem(dev, flag)
        unit = minor(dev);
        tp = &vx_tty[unit];
        vs = (struct vx_softc *)tp->t_addr;
        unit = minor(dev);
        tp = &vx_tty[unit];
        vs = (struct vx_softc *)tp->t_addr;
+       if (vs->vs_state != VXS_READY)
+               return;
        cp = vobtain(vs);
        cp = vobtain(vs);
-       kp = (struct vxdevice *)((struct vba_device *)vxinfo[vs->vs_nbr])->ui_addr;
+       kp = vs->vs_addr;
 
 
-       port = unit & 017;
+       port = VXPORT(unit);
        /*
         * Issue MODEM command
         */
        cp->cmd = VXC_MDMCTL;
        /*
         * Issue MODEM command
         */
        cp->cmd = VXC_MDMCTL;
-       cp->par[0] = (flag == VMOD_ON) ? V_ENAB : V_DISAB;
+       if (flag == VMOD_ON) {
+               if (vs->vs_softCAR & (1 << port)) {
+                       cp->par[0] = V_MANUAL | V_DTR_ON | V_RTS;
+                       kp->v_dcd |= (1 << port);
+               } else
+                       cp->par[0] = V_AUTO | V_DTR_ON;
+       } else
+               cp->par[0] = V_DTR_OFF;
        cp->par[1] = port;
        cp->par[1] = port;
-       vcmd(vs->vs_nbr, (caddr_t)&cp->cmd);
-       port -= vs->vs_loport;
-       if ((kp->v_dcd >> port) & 1) {
-               if (flag == VMOD_ON)
-                       tp->t_state |= TS_CARR_ON;
-               return (1);
-       }
-       return (0);
+       (void) vcmd((int)vs->vs_nbr, (caddr_t)&cp->cmd);
+       if ((kp->v_dcd | vs->vs_softCAR) & (1 << port) && flag == VMOD_ON)
+               tp->t_state |= TS_CARR_ON;
 }
 
 /*
 }
 
 /*
- * VCMINTR called when an unsolicited interrup occurs signaling
+ * VCMINTR called when an unsolicited interrupt occurs signaling
  * some change of modem control state.
  */
 vcmintr(vx)
  * some change of modem control state.
  */
 vcmintr(vx)
@@ -1304,81 +1338,51 @@ vcmintr(vx)
        register struct vxdevice *kp;
        register struct tty *tp;
        register port;
        register struct vxdevice *kp;
        register struct tty *tp;
        register port;
+       register struct vx_softc *vs;
 
 
-       kp = (struct vxdevice *)((struct vba_device *)vxinfo[vx])->ui_addr;
+       vs = &vx_softc[vx];
+       kp = vs->vs_addr;
        port = kp->v_usdata[0] & 017;
        tp = &vx_tty[vx*16+port];
        port = kp->v_usdata[0] & 017;
        tp = &vx_tty[vx*16+port];
-#if NVBSC > 0
-       /*
-        * Check for change in DSR for BISYNC port.
-        */
-       if (bscport[vx*16+port]&BISYNC) {
-               if (kp->v_ustat&DSR_CHG) {
-                       register struct vx_softc *xp;
-                       register struct bsc *bp;
-                       extern struct bsc bsc[];
-
-                       vs = (struct vx_softc *)tp->t_addr;
-                       bp = &bsc[minor(tp->t_dev)] ;
-                       bp->b_hlflgs &= ~BSC_DSR ;
-                       if (kp->v_ustat & DSR_ON)
-                               bp->b_hlflgs |= BSC_DSR ;
-                       printf("BSC DSR Chg: %x\n", kp->v_ustat&DSR_CHG);/*XXX*/
-               }
-               return;
-       }
-#endif
-       if ((kp->v_ustat&DCD_ON) && ((tp->t_state&TS_CARR_ON) == 0)) {
-               tp->t_state |= TS_CARR_ON;
-               wakeup((caddr_t)&tp->t_canq);
-               return;
-       }
-       if ((kp->v_ustat&DCD_OFF) && (tp->t_state&TS_CARR_ON)) {
-               tp->t_state &= ~TS_CARR_ON;
-               if (tp->t_state&TS_ISOPEN) {
-                       register struct vx_softc *vs;
-                       register struct vcmds *cp;
-                       register struct vxcmd *cmdp;
-
-                       ttyflush(tp, FREAD|FWRITE);
-                       /* clear all pending trnansmits */
-                       vs = &vx_softc[vx];
-                       if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
-                           vs->vs_vers == VXV_NEW) {
-                               int i, cmdfound = 0;
-
-                               cp = &vs->vs_cmds;
-                               for (i = cp->v_empty; i != cp->v_fill; ) {
-                                       cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
-                                       if ((cmdp->cmd == VXC_XMITDTA ||
-                                           cmdp->cmd == VXC_XMITIMM) &&
-                                           ((struct vxmit *)cmdp->par)->line == port) {
-                                               cmdfound++;
-                                               cmdp->cmd = VXC_FDTATOX;
-                                               cmdp->par[1] = port;
-                                       }
-                                       if (++i >= VC_CMDBUFL)
-                                               i = 0;
-                               }
-                               if (cmdfound)
-                                       tp->t_state &= ~(TS_BUSY|TS_FLUSH);
-                               /* cmd is already in vioc, have to flush it */
-                               else {
-                                       cmdp = vobtain(vs);
+
+       if (kp->v_ustat & DCD_ON)
+               (void)(*linesw[tp->t_line].l_modem)(tp, 1);
+       else if ((kp->v_ustat & DCD_OFF) &&
+           ((vs->vs_softCAR & (1 << port))) == 0 &&
+           (*linesw[tp->t_line].l_modem)(tp, 0) == 0) {
+               register struct vcmds *cp;
+               register struct vxcmd *cmdp;
+
+               /* clear all pending transmits */
+               if (tp->t_state&(TS_BUSY|TS_FLUSH) &&
+                   vs->vs_vers == VXV_NEW) {
+                       int i, cmdfound = 0;
+
+                       cp = &vs->vs_cmds;
+                       for (i = cp->v_empty; i != cp->v_fill; ) {
+                               cmdp = (struct vxcmd *)((long *)cp->cmdbuf[i]-1);
+                               if ((cmdp->cmd == VXC_XMITDTA ||
+                                   cmdp->cmd == VXC_XMITIMM) &&
+                                   ((struct vxmit *)cmdp->par)->line == port) {
+                                       cmdfound++;
                                        cmdp->cmd = VXC_FDTATOX;
                                        cmdp->par[1] = port;
                                        cmdp->cmd = VXC_FDTATOX;
                                        cmdp->par[1] = port;
-                                       vcmd(vx, (caddr_t)&cmdp->cmd);
                                }
                                }
+                               if (++i >= VC_CMDBUFL)
+                                       i = 0;
                        }
                        }
-                       if ((tp->t_flags&NOHANG) == 0) {
-                               gsignal(tp->t_pgrp, SIGHUP);
-                               gsignal(tp->t_pgrp, SIGCONT);
+                       if (cmdfound)
+                               tp->t_state &= ~(TS_BUSY|TS_FLUSH);
+                       /* cmd is already in vioc, have to flush it */
+                       else {
+                               cmdp = vobtain(vs);
+                               cmdp->cmd = VXC_FDTATOX;
+                               cmdp->par[1] = port;
+                               (void) vcmd(vx, (caddr_t)&cmdp->cmd);
                        }
                }
                        }
                }
-               return;
-       }
-       if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
-               (*linesw[tp->t_line].l_rint)(tp->t_intrc & 0377, tp);
+       } else if ((kp->v_ustat&BRK_CHR) && (tp->t_state&TS_ISOPEN)) {
+               (*linesw[tp->t_line].l_rint)(TTY_FE, tp);
                return;
        }
 }
                return;
        }
 }