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