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