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