xref: /csrg-svn/sys/tahoe/vba/vxc.c (revision 25675)
1 /*	vxc.c	1.2	86/01/05	*/
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 		splx(s);
232 	}
233 	else {
234 		vpanic("vc: UNSOL INT ERR") ;
235 		splx(s);
236 		vxstreset(n);
237 	}
238 }
239 
240 /*
241  * Enqueue an interrupt
242  */
243 vinthandl(n, item)
244 register int n ;
245 register item ;
246 {
247 
248 	register struct  vcmds *cp ;
249 	register int	empflag = 0 ;
250 
251 	cp = &v_cmds[n] ;
252 	if( cp->v_itrfill == cp->v_itrempt ) empflag++ ;
253 	cp->v_itrqueu[cp->v_itrfill] = item ;
254 	if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ;
255 	if(cp->v_itrfill == cp->v_itrempt) {
256 		vpanic( "vc: INT Q OVFLO" ) ;
257 		vxstreset(n);
258 	}
259 	else if( empflag ) vintempt(n) ;
260 }
261 
262 vintempt(n)
263 register int n ;
264 {
265 	register  struct  vcmds *cp ;
266 	register  struct  vblok *vp ;
267 	register  short   item ;
268 	register  short	*intr ;
269 
270 	vp = VBAS(n) ;
271 	if(vp->v_vioc & V_BSY) return ;
272 	cp = &v_cmds[n] ;
273 	if(cp->v_itrempt == cp->v_itrfill) return ;
274 	item = cp->v_itrqueu[cp->v_itrempt] ;
275 	intr = (short *)&vp->v_vioc ;
276 	switch( (item >> 8) & 03 ) {
277 
278 	case CMDquals:		/* command */
279 		{
280 		int phys;
281 
282 		if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
283 			break;
284 		(&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
285 		phys = vtoph((struct proc *)0, (unsigned)cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */
286 		vp->v_vcp[0] = ((short *)&phys)[0];
287 		vp->v_vcp[1] = ((short *)&phys)[1];
288 		vp->v_vcbsy = V_BSY ;
289 		*intr = item ;
290 		}
291 #ifdef VXPERF
292 	scope_out(4);
293 #endif VXPERF
294 		break ;
295 
296 	case RSPquals:		/* command response */
297 		*intr = item ;
298 #ifdef VXPERF
299 	scope_out(7);
300 #endif VXPERF
301 		break ;
302 
303 	case UNSquals:		/* unsolicited interrupt */
304 		vp->v_uqual = 0 ;
305 		*intr = item ;
306 #ifdef VXPERF
307 	scope_out(2);
308 #endif VXPERF
309 		break ;
310 	}
311 }
312 
313 
314 /* start a reset on a vioc after error (hopefully) */
315 vxstreset(n)
316 	register n;
317 {
318 	register struct vcx *xp;
319 	register struct	vblok *vp ;
320 	register struct vxcmd *cp;
321 	register int j;
322 	extern int vxinreset();
323 	int	s ;
324 
325 	s = spl8() ;
326 	vp = VBAS(n);
327 	xp = &vcx[n];
328 
329 	if (xp->v_state&V_RESETTING)
330 		/*
331 		 * Avoid infinite recursion.
332 		 */
333 		return;
334 
335 	/*
336 	 * Zero out the vioc structures, mark the vioc as being
337 	 * reset, reinitialize the free command list, reset the vioc
338 	 * and start a timer to check on the progress of the reset.
339 	 */
340 	bzero((caddr_t)&v_cmds[n], (unsigned)sizeof (struct vcmds));
341 	bzero((caddr_t)xp, (unsigned)sizeof (struct vcx));
342 
343 	/*
344 	 * Setting V_RESETTING prevents others from issuing
345 	 * commands while allowing currently queued commands to
346 	 * be passed to the VIOC.
347 	 */
348 	xp->v_state |= V_RESETTING;
349 	for(j=0; j<NVCXBUFS; j++)	/* init all cmd buffers */
350 	{
351 		cp = &xp->vx_lst[j];	/* index a buffer */
352 		cp->c_fwd = &xp->vx_lst[j+1];	/* point to next buf */
353 	}
354 	xp->vx_avail = &xp->vx_lst[0];	/* set idx to 1st free buf */
355 	cp->c_fwd = (struct vxcmd *)0;	/* mark last buf in free list */
356 
357 	printf("resetting VIOC %x .. ", n);
358 
359 	vp->v_fault = 0 ;
360 	vp->v_vioc = V_BSY ;
361 	vp->v_hdwre = V_RESET ;		/* reset interrupt */
362 
363 	timeout(vxinreset, (caddr_t)n, hz*5);
364 	splx(s);
365 	return;
366 }
367 
368 /* continue processing a reset on a vioc after an error (hopefully) */
369 vxinreset(vioc)
370 caddr_t vioc;
371 {
372 	register int n = (int)vioc;
373 	register struct	vblok *vp ;
374 	int s = spl8();
375 printf("vxinreset ");
376 
377 	vp = VBAS(n);
378 
379 	/*
380 	 * See if the vioc has reset.
381 	 */
382 	if (vp->v_fault != VREADY) {
383 		printf("failed\n");
384 		splx(s);
385 		return;
386 	}
387 
388 	/*
389 	 * Send a LIDENT to the vioc and mess with carrier flags
390 	 * on parallel printer ports.
391 	 */
392 	vxinit(n, (long)0);
393 	splx(s);
394 }
395 
396 /*
397  * Restore modem control, parameters and restart output.
398  * Since the vioc can handle no more then 24 commands at a time
399  * and we could generate as many as 48 commands, we must do this in
400  * phases, issuing no more then 16 commands at a time.
401  */
402 /* finish the reset on the vioc after an error (hopefully) */
403 vxfnreset(n, cp)
404 register int n;
405 register struct vxcmd *cp;
406 {
407 	register struct vcx *xp;
408 	register struct	vblok *vp ;
409 	register struct tty *tp;
410 	register int i;
411 #ifdef notdef
412 	register int on;
413 #endif
414 	extern int vxrestart();
415 	int s = spl8();
416 printf("vxfnreset ");
417 
418 	vp = VBAS(n);
419 	xp = &vcx[n];
420 
421 	xp->v_loport = cp->par[5];	/* save low port number */
422 	xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */
423 	vrelease(xp,cp);	/* done with this control block */
424 	xp->v_nbr = n;		/* assign VIOC-X board number */
425 
426 	xp->v_state &= ~V_RESETTING;
427 
428 	vp->v_vcid = 0;
429 
430 	/*
431 	 * Restore modem information and control.
432 	 */
433 	for(i=xp->v_loport; i<=xp->v_hiport; i++) {
434 		tp = &vx_tty[i+n*16];
435 		if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
436 			tp->t_state &= ~TS_CARR_ON;
437 			vcmodem(tp->t_dev, VMOD_ON);
438 			if (tp->t_state&TS_CARR_ON)  {
439 				wakeup((caddr_t)&tp->t_canq) ;
440 			}
441 			else {
442 				if(tp->t_state & TS_ISOPEN) {
443 					ttyflush(tp, FREAD|FWRITE);
444 					if(tp->t_state&TS_FLUSH)
445 						wakeup((caddr_t)&tp->t_state) ;
446 					if((tp->t_flags&NOHANG)==0) {
447 						gsignal(tp->t_pgrp, SIGHUP) ;
448 						gsignal(tp->t_pgrp, SIGCONT);
449 					}
450 				}
451 			}
452 		}
453 		/*
454 		 * If carrier has changed while we were resetting,
455 		 * take appropriate action.
456 		 */
457 #ifdef notdef
458 		on = vp->v_dcd & 1<<i;
459 		if (on && (tp->t_state&TS_CARR_ON) == 0) {
460 			tp->t_state |= TS_CARR_ON ;
461 			wakeup((caddr_t)&tp->t_canq) ;
462 		} else if (!on && tp->t_state&TS_CARR_ON) {
463 			tp->t_state &= ~TS_CARR_ON ;
464 			if(tp->t_state & TS_ISOPEN) {
465 				ttyflush(tp, FREAD|FWRITE);
466 				if(tp->t_state&TS_FLUSH)
467 					wakeup((caddr_t)&tp->t_state) ;
468 				if((tp->t_flags&NOHANG)==0) {
469 					gsignal(tp->t_pgrp, SIGHUP) ;
470 					gsignal(tp->t_pgrp, SIGCONT);
471 				}
472 			}
473 		}
474 #endif
475 	}
476 
477 	xp->v_state |= V_RESETTING;
478 
479 	timeout(vxrestart, (caddr_t)n, hz);
480 	splx(s);
481 }
482 
483 /*
484  * Restore a particular aspect of the VIOC.
485  */
486 vxrestart(vioc)
487 caddr_t vioc;
488 {
489 	register struct tty *tp, *tp0;
490 	register struct vcx *xp;
491 	register int i, cnt;
492 	register int n = (int)vioc;
493 	int s = spl8();
494 
495 	cnt = n>>8;
496 printf("vxrestart %d ",cnt);
497 	n &= 0xff;
498 
499 	tp0 = &vx_tty[n*16];
500 	xp = &vcx[n];
501 
502 	xp->v_state &= ~V_RESETTING;
503 
504 	for(i=xp->v_loport; i<=xp->v_hiport; i++) {
505 		tp = tp0 + i;
506 		if (cnt != 0) {
507 			tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
508 			if(tp->t_state&(TS_ISOPEN|TS_WOPEN))	/* restart pending output */
509 				vxstart(tp);
510 		} else {
511 			if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
512 				vxcparam(tp->t_dev, 0);
513 		}
514 	}
515 
516 	if (cnt == 0) {
517 		xp->v_state |= V_RESETTING;
518 		timeout(vxrestart, (caddr_t)(n + 1*256), hz);
519 	} else
520 		printf("done\n");
521 	splx(s);
522 }
523 
524 vxreset(dev)
525 dev_t dev;
526 {
527 	vxstreset(minor(dev)>>4);	/* completes asynchronously */
528 }
529 
530 vxfreset(n)
531 register int n;
532 {
533 
534 	if (n < 0 || n > NVX || VBAS(n) == NULL)
535 		return(ENODEV);
536 	vcx[n].v_state &= ~V_RESETTING;
537 	vxstreset(n);
538 	return(0);		/* completes asynchronously */
539 }
540 #endif
541 
542