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