install approved copyright notice
[unix-history] / usr / src / sys / tahoe / vba / vxc.c
CommitLineData
4db7c84e 1/* vxc.c 1.5 86/01/12 */
dc2dfe78
SL
2
3#include "vx.h"
4#if NVX > 0
5/*
4db7c84e 6 * VIOC driver
dc2dfe78 7 */
4db7c84e
SL
8#ifdef VXPERF
9#define DOSCOPE
10#endif
11
e6453f14
SL
12#include "param.h"
13#include "file.h"
14#include "ioctl.h"
15#include "tty.h"
16#include "errno.h"
17#include "time.h"
18#include "kernel.h"
19#include "proc.h"
20
9d915fad 21#include "../tahoevba/vioc.h"
e6453f14 22#include "../tahoesna/snadebug.h"
9d915fad 23#include "../tahoevba/scope.h"
dc2dfe78
SL
24
25#define CMDquals 0
26#define RSPquals 1
27#define UNSquals 2
28
dc2dfe78
SL
29extern struct vcx vcx[] ;
30extern struct tty vx_tty[];
31struct vcmds v_cmds[NVIOCX] ;
32
33extern char vxtype[];
34extern char vxbbno;
35extern char vxbopno[];
36#ifdef SNA_DEBUG
37extern vbrall();
38#endif SNA_DEBUG
39extern struct vxcmd *vobtain();
40
41#ifdef VX_DEBUG
42#include "../vba/vxdebug.h"
43#endif
44
45/*
46 * Write a command out to the VIOC
47 */
48vcmd(n, cmdad)
49register int n ;
50register caddr_t cmdad ; /* command address */
51{
52
53 register struct vcmds *cp ;
54 register struct vcx *xp;
55 int s ;
56
57 s = spl8() ;
58 cp = &v_cmds[n] ;
59 xp = &vcx[n];
60 if (xp->v_state&V_RESETTING && cmdad != NULL) {
61 /*
62 * When the vioc is resetting, don't process
63 * anything other than LIDENT commands.
64 */
9d915fad
SL
65 register struct vxcmd *cmdp = (struct vxcmd *)
66 ((char *)cmdad - sizeof(cmdp->c_fwd));
67 if (cmdp->cmd != LIDENT) {
68 vrelease(xp, cmdp);
dc2dfe78
SL
69 return(0);
70 }
71 }
72 if (cmdad != (caddr_t) 0) {
73 cp->cmdbuf[cp->v_fill] = cmdad ;
74 if( ++cp->v_fill >= VC_CMDBUFL ) cp->v_fill = 0 ;
75 if(cp->v_fill == cp->v_empty) {
76 vpanic("vc: CMD Q OVFLO") ;
77 vxstreset(n);
78 splx(s);
79 return(0);
80 }
81 cp->v_cmdsem++;
82 }
83 if(cp->v_cmdsem && cp->v_curcnt < vcx[n].v_maxcmd) {
84 cp->v_cmdsem--;
85 cp->v_curcnt++;
86 vinthandl(n, ((V_BSY | CMDquals) << 8) | V_INTR ) ;
87 }
88 splx(s) ;
9d915fad 89 return(1);
dc2dfe78
SL
90}
91
92/*
93 * VIOC acknowledge interrupt. The VIOC has received the new
94 * command. If no errors, the new command becomes one of 16 (max)
95 * current commands being executed.
96 */
97vackint(n)
98register n ; /* VIOC number */
99{
100
101 register struct vblok *vp ;
102 register struct vcmds *cp ;
103 register s;
104
dc2dfe78 105 scope_out(5);
dc2dfe78
SL
106 if (vxtype[n]) { /* Its a BOP */
107#ifdef SNA_DEBUG
108 if (snadebug & SVIOC)
109 printf("vack: interrupt from BOP at VIOC%d,1st vector.\n",n);
110 vbrall(n); /* Int. from BOP, port 0 */
111#endif
112 return;
113 }
114 s = spl8();
115 vp = VBAS(n) ;
116 cp = &v_cmds[n] ;
117 if( vp->v_vcid & V_ERR ) {
118 register char *resp;
119 register i;
120 printf ("INTR ERR type = %x VIOC = %x, v_dcd: %lx\n",
121 vp->v_vcid & 07, n, vp->v_dcd & 0xff);
122 /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */
123 resp = (char *)(&vcx[n])->v_mricmd;
124 for(i=0; i<16; i++)
125 printf("%x ", resp[i]&0xff);
126 vpanic( "\nvcc: vackint") ;
127 splx(s);
128 vxstreset(n);
129 return ;
130 } else
131 if((vp->v_hdwre&017) == CMDquals) {
132#ifdef VX_DEBUG
133 if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */
134 register struct vxcmd *cp1;
135 register struct vxcmd *cp0 = (struct vxcmd *)
136 ((long)cp->cmdbuf[cp->v_empty] - 4);
137 if ((cp0->cmd == XMITDTA) || (cp0->cmd == XMITIMM)) {
138 cp1 = vobtain(&vcx[n]);
139 *cp1 = *cp0;
140 vxintr4 &= ~VXERR4;
9d915fad 141 (void) vcmd(n,&cp1->cmd);
dc2dfe78
SL
142 }
143 }
144#endif
145 cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty] ;
146 if( ++cp->v_empty >= VC_CMDBUFL ) cp->v_empty = 0 ;
147 }
148 if( ++cp->v_itrempt >= VC_IQLEN ) cp->v_itrempt = 0 ;
149 vintempt(n) ;
150 splx(s);
9d915fad 151 (void) vcmd(n, (caddr_t)0); /* queue next cmd, if any */
dc2dfe78
SL
152}
153
154/*
155 * Command Response interrupt. The Vioc has completed
156 * a command. The command may now be returned to
157 * the appropriate device driver .
158 */
159vcmdrsp(n)
160register n ;
161{
162
163 register struct vblok *vp ;
164 register struct vcmds *cp ;
165 register caddr_t cmd ;
166 register char *resp ;
167 register k ;
168 register int s ;
169
dc2dfe78 170 scope_out(6);
dc2dfe78
SL
171 if (vxtype[n]) { /* Its a BOP */
172 printf("vcmdrsp: stray interrupt from BOP at VIOC%d...\n",n);
173 return;
174 }
175 s = spl8();
176 vp = VBAS(n) ;
177 cp = &v_cmds[n] ;
178 resp = (char *)vp;
179 resp += vp->v_rspoff & 0x7FFF;
180
181 if( (k=resp[1]) & V_UNBSY ) {
182 k &= VCMDLEN-1;
183 cmd = cp->v_curcmd[k];
184 cp->v_curcmd[k] = (caddr_t)0;
185 cp->v_curcnt--;
186 k = *((short *)&resp[4]); /* cmd operation code */
187 if((k & 0xFF00) == LIDENT) { /* want hiport number */
188 for(k=0; k<VRESPLEN; k++)
189 cmd[k] = resp[k+4];
190 }
191 resp[1] = 0;
9d915fad 192 vxxint(n, (struct vxcmd *)cmd) ;
dc2dfe78
SL
193 if ((&vcx[n])->v_state == V_RESETTING) return;
194 }
195 else {
196 vpanic( "vc, cmdresp debug") ;
197 splx(s);
198 vxstreset(n);
199 return;
200 }
201
202 vinthandl(n, ( (V_BSY | RSPquals) << 8 ) | V_INTR ) ;
203 splx(s);
204
205}
206
207
208/*
209 * Unsolicited interrupt.
210 */
211vunsol(n)
212register(n) ;
213{
214
215 register struct vblok *vp ;
216 register s;
217
dc2dfe78 218 scope_out(1);
dc2dfe78
SL
219 if (vxtype[n]) { /* Its a BOP */
220 printf("vunsol: stray interrupt from BOP at VIOC%d...\n",n);
221 return;
222 }
223 s = spl8();
224 vp = VBAS(n) ;
225 if(vp->v_uqual & V_UNBSY) {
226 vxrint(n) ;
227 vinthandl(n, ( (V_BSY | UNSquals) << 8 ) | V_INTR ) ;
336ca318
SL
228#ifdef notdef
229 } else {
dc2dfe78
SL
230 vpanic("vc: UNSOL INT ERR") ;
231 splx(s);
232 vxstreset(n);
336ca318 233#endif
dc2dfe78 234 }
336ca318 235 splx(s);
dc2dfe78
SL
236}
237
238/*
239 * Enqueue an interrupt
240 */
241vinthandl(n, item)
242register int n ;
243register item ;
244{
245
246 register struct vcmds *cp ;
247 register int empflag = 0 ;
248
249 cp = &v_cmds[n] ;
250 if( cp->v_itrfill == cp->v_itrempt ) empflag++ ;
251 cp->v_itrqueu[cp->v_itrfill] = item ;
252 if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ;
253 if(cp->v_itrfill == cp->v_itrempt) {
254 vpanic( "vc: INT Q OVFLO" ) ;
255 vxstreset(n);
256 }
257 else if( empflag ) vintempt(n) ;
258}
259
260vintempt(n)
261register int n ;
262{
263 register struct vcmds *cp ;
264 register struct vblok *vp ;
265 register short item ;
266 register short *intr ;
267
268 vp = VBAS(n) ;
269 if(vp->v_vioc & V_BSY) return ;
270 cp = &v_cmds[n] ;
271 if(cp->v_itrempt == cp->v_itrfill) return ;
272 item = cp->v_itrqueu[cp->v_itrempt] ;
273 intr = (short *)&vp->v_vioc ;
274 switch( (item >> 8) & 03 ) {
275
276 case CMDquals: /* command */
277 {
278 int phys;
279
280 if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
281 break;
282 (&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
9d915fad 283 phys = vtoph((struct proc *)0, (unsigned)cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */
dc2dfe78
SL
284 vp->v_vcp[0] = ((short *)&phys)[0];
285 vp->v_vcp[1] = ((short *)&phys)[1];
286 vp->v_vcbsy = V_BSY ;
287 *intr = item ;
288 }
4db7c84e 289 scope_out(4);
dc2dfe78
SL
290 break ;
291
292 case RSPquals: /* command response */
293 *intr = item ;
4db7c84e 294 scope_out(7);
dc2dfe78
SL
295 break ;
296
297 case UNSquals: /* unsolicited interrupt */
298 vp->v_uqual = 0 ;
299 *intr = item ;
4db7c84e 300 scope_out(2);
dc2dfe78
SL
301 break ;
302 }
303}
304
305
306/* start a reset on a vioc after error (hopefully) */
307vxstreset(n)
308 register n;
309{
310 register struct vcx *xp;
311 register struct vblok *vp ;
312 register struct vxcmd *cp;
313 register int j;
314 extern int vxinreset();
315 int s ;
316
317 s = spl8() ;
318 vp = VBAS(n);
319 xp = &vcx[n];
320
321 if (xp->v_state&V_RESETTING)
322 /*
323 * Avoid infinite recursion.
324 */
325 return;
326
327 /*
328 * Zero out the vioc structures, mark the vioc as being
329 * reset, reinitialize the free command list, reset the vioc
330 * and start a timer to check on the progress of the reset.
331 */
9d915fad
SL
332 bzero((caddr_t)&v_cmds[n], (unsigned)sizeof (struct vcmds));
333 bzero((caddr_t)xp, (unsigned)sizeof (struct vcx));
dc2dfe78
SL
334
335 /*
336 * Setting V_RESETTING prevents others from issuing
337 * commands while allowing currently queued commands to
338 * be passed to the VIOC.
339 */
340 xp->v_state |= V_RESETTING;
341 for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */
342 {
343 cp = &xp->vx_lst[j]; /* index a buffer */
344 cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */
345 }
346 xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */
347 cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */
348
349 printf("resetting VIOC %x .. ", n);
350
351 vp->v_fault = 0 ;
352 vp->v_vioc = V_BSY ;
353 vp->v_hdwre = V_RESET ; /* reset interrupt */
354
355 timeout(vxinreset, (caddr_t)n, hz*5);
356 splx(s);
357 return;
358}
359
360/* continue processing a reset on a vioc after an error (hopefully) */
361vxinreset(vioc)
362caddr_t vioc;
363{
dc2dfe78 364 register int n = (int)vioc;
9d915fad 365 register struct vblok *vp ;
dc2dfe78
SL
366 int s = spl8();
367printf("vxinreset ");
368
369 vp = VBAS(n);
dc2dfe78
SL
370
371 /*
372 * See if the vioc has reset.
373 */
374 if (vp->v_fault != VREADY) {
375 printf("failed\n");
376 splx(s);
377 return;
378 }
379
380 /*
381 * Send a LIDENT to the vioc and mess with carrier flags
382 * on parallel printer ports.
383 */
9d915fad 384 vxinit(n, (long)0);
dc2dfe78
SL
385 splx(s);
386}
387
388/*
389 * Restore modem control, parameters and restart output.
390 * Since the vioc can handle no more then 24 commands at a time
391 * and we could generate as many as 48 commands, we must do this in
392 * phases, issuing no more then 16 commands at a time.
393 */
394/* finish the reset on the vioc after an error (hopefully) */
395vxfnreset(n, cp)
396register int n;
397register struct vxcmd *cp;
398{
399 register struct vcx *xp;
400 register struct vblok *vp ;
401 register struct tty *tp;
402 register int i;
9d915fad 403#ifdef notdef
dc2dfe78 404 register int on;
9d915fad 405#endif
dc2dfe78
SL
406 extern int vxrestart();
407 int s = spl8();
408printf("vxfnreset ");
409
410 vp = VBAS(n);
411 xp = &vcx[n];
412
413 xp->v_loport = cp->par[5]; /* save low port number */
414 xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */
415 vrelease(xp,cp); /* done with this control block */
416 xp->v_nbr = n; /* assign VIOC-X board number */
417
418 xp->v_state &= ~V_RESETTING;
419
420 vp->v_vcid = 0;
421
422 /*
423 * Restore modem information and control.
424 */
425 for(i=xp->v_loport; i<=xp->v_hiport; i++) {
426 tp = &vx_tty[i+n*16];
427 if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
428 tp->t_state &= ~TS_CARR_ON;
429 vcmodem(tp->t_dev, VMOD_ON);
430 if (tp->t_state&TS_CARR_ON) {
431 wakeup((caddr_t)&tp->t_canq) ;
432 }
433 else {
434 if(tp->t_state & TS_ISOPEN) {
435 ttyflush(tp, FREAD|FWRITE);
436 if(tp->t_state&TS_FLUSH)
437 wakeup((caddr_t)&tp->t_state) ;
438 if((tp->t_flags&NOHANG)==0) {
439 gsignal(tp->t_pgrp, SIGHUP) ;
440 gsignal(tp->t_pgrp, SIGCONT);
441 }
442 }
443 }
444 }
445 /*
446 * If carrier has changed while we were resetting,
447 * take appropriate action.
448 */
9d915fad 449#ifdef notdef
dc2dfe78
SL
450 on = vp->v_dcd & 1<<i;
451 if (on && (tp->t_state&TS_CARR_ON) == 0) {
452 tp->t_state |= TS_CARR_ON ;
453 wakeup((caddr_t)&tp->t_canq) ;
454 } else if (!on && tp->t_state&TS_CARR_ON) {
455 tp->t_state &= ~TS_CARR_ON ;
456 if(tp->t_state & TS_ISOPEN) {
457 ttyflush(tp, FREAD|FWRITE);
458 if(tp->t_state&TS_FLUSH)
459 wakeup((caddr_t)&tp->t_state) ;
460 if((tp->t_flags&NOHANG)==0) {
461 gsignal(tp->t_pgrp, SIGHUP) ;
462 gsignal(tp->t_pgrp, SIGCONT);
463 }
464 }
465 }
9d915fad 466#endif
dc2dfe78
SL
467 }
468
469 xp->v_state |= V_RESETTING;
470
471 timeout(vxrestart, (caddr_t)n, hz);
472 splx(s);
473}
474
475/*
476 * Restore a particular aspect of the VIOC.
477 */
478vxrestart(vioc)
479caddr_t vioc;
480{
481 register struct tty *tp, *tp0;
482 register struct vcx *xp;
483 register int i, cnt;
484 register int n = (int)vioc;
485 int s = spl8();
486
487 cnt = n>>8;
488printf("vxrestart %d ",cnt);
489 n &= 0xff;
490
491 tp0 = &vx_tty[n*16];
492 xp = &vcx[n];
493
494 xp->v_state &= ~V_RESETTING;
495
496 for(i=xp->v_loport; i<=xp->v_hiport; i++) {
497 tp = tp0 + i;
498 if (cnt != 0) {
499 tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
500 if(tp->t_state&(TS_ISOPEN|TS_WOPEN)) /* restart pending output */
501 vxstart(tp);
502 } else {
503 if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
504 vxcparam(tp->t_dev, 0);
505 }
506 }
507
508 if (cnt == 0) {
509 xp->v_state |= V_RESETTING;
510 timeout(vxrestart, (caddr_t)(n + 1*256), hz);
511 } else
512 printf("done\n");
513 splx(s);
514}
515
516vxreset(dev)
517dev_t dev;
518{
519 vxstreset(minor(dev)>>4); /* completes asynchronously */
520}
521
522vxfreset(n)
523register int n;
524{
dc2dfe78
SL
525
526 if (n < 0 || n > NVX || VBAS(n) == NULL)
527 return(ENODEV);
528 vcx[n].v_state &= ~V_RESETTING;
529 vxstreset(n);
530 return(0); /* completes asynchronously */
531}
532#endif
533