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