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