home *** CD-ROM | disk | FTP | other *** search
/ InfoMagic Source Code 1993 July / THE_SOURCE_CODE_CD_ROM.iso / bsd_srcs / sys / tahoe / vba / vx.c < prev    next >
Encoding:
C/C++ Source or Header  |  1991-05-16  |  31.8 KB  |  1,417 lines

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