get rid of unused queue() and dequeue() (from sun!shannon)
[unix-history] / usr / src / sys / tahoe / vba / vxc.c
CommitLineData
dc2dfe78
SL
1/* vxc.c 1.1 85/07/21 */
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 "../vba/vioc.h"
16#include "../sna/snadebug.h"
17#ifdef VXPERF
18#include "../vba/scope.h"
19#endif VXPERF
20
21#define CMDquals 0
22#define RSPquals 1
23#define UNSquals 2
24
25long reinit = 0;
26extern struct vcx vcx[] ;
27extern struct tty vx_tty[];
28struct vcmds v_cmds[NVIOCX] ;
29
30extern char vxtype[];
31extern char vxbbno;
32extern char vxbopno[];
33#ifdef SNA_DEBUG
34extern vbrall();
35#endif SNA_DEBUG
36extern 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 */
45vcmd(n, cmdad)
46register int n ;
47register 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 *cp = (struct vxcmd *)
63 ((char *)cmdad - sizeof(cp->c_fwd));
64 if (cp->cmd != LIDENT) {
65 vrelease(xp, cp);
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}
87
88/*
89 * VIOC acknowledge interrupt. The VIOC has received the new
90 * command. If no errors, the new command becomes one of 16 (max)
91 * current commands being executed.
92 */
93vackint(n)
94register n ; /* VIOC number */
95{
96
97 register struct vblok *vp ;
98 register struct vcmds *cp ;
99 register s;
100
101#ifdef VXPERF
102 scope_out(5);
103#endif VXPERF
104 if (vxtype[n]) { /* Its a BOP */
105#ifdef SNA_DEBUG
106 if (snadebug & SVIOC)
107 printf("vack: interrupt from BOP at VIOC%d,1st vector.\n",n);
108 vbrall(n); /* Int. from BOP, port 0 */
109#endif
110 return;
111 }
112 s = spl8();
113 vp = VBAS(n) ;
114 cp = &v_cmds[n] ;
115 if( vp->v_vcid & V_ERR ) {
116 register char *resp;
117 register i;
118 printf ("INTR ERR type = %x VIOC = %x, v_dcd: %lx\n",
119 vp->v_vcid & 07, n, vp->v_dcd & 0xff);
120 /* resp = (char *)vp + (vp->v_rspoff & 0x7FFF); */
121 resp = (char *)(&vcx[n])->v_mricmd;
122 for(i=0; i<16; i++)
123 printf("%x ", resp[i]&0xff);
124 vpanic( "\nvcc: vackint") ;
125 splx(s);
126 vxstreset(n);
127 return ;
128 } else
129 if((vp->v_hdwre&017) == CMDquals) {
130#ifdef VX_DEBUG
131 if (vxintr4 & VXERR4) { /* causes VIOC INTR ERR 4 */
132 register struct vxcmd *cp1;
133 register struct vxcmd *cp0 = (struct vxcmd *)
134 ((long)cp->cmdbuf[cp->v_empty] - 4);
135 if ((cp0->cmd == XMITDTA) || (cp0->cmd == XMITIMM)) {
136 cp1 = vobtain(&vcx[n]);
137 *cp1 = *cp0;
138 vxintr4 &= ~VXERR4;
139 vcmd(n,&cp1->cmd);
140 }
141 }
142#endif
143 cp->v_curcmd[vp->v_vcid & VCMDLEN-1] = cp->cmdbuf[cp->v_empty] ;
144 if( ++cp->v_empty >= VC_CMDBUFL ) cp->v_empty = 0 ;
145 }
146 if( ++cp->v_itrempt >= VC_IQLEN ) cp->v_itrempt = 0 ;
147 vintempt(n) ;
148 splx(s);
149 vcmd(n, 0); /* queue next cmd, if any */
150}
151
152/*
153 * Command Response interrupt. The Vioc has completed
154 * a command. The command may now be returned to
155 * the appropriate device driver .
156 */
157vcmdrsp(n)
158register n ;
159{
160
161 register struct vblok *vp ;
162 register struct vcmds *cp ;
163 register caddr_t cmd ;
164 register char *resp ;
165 register k ;
166 register int s ;
167
168#ifdef VXPERF
169 scope_out(6);
170#endif VXPERF
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;
192 vxxint(n, cmd) ;
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
218#ifdef VXPERF
219 scope_out(1);
220#endif VXPERF
221 if (vxtype[n]) { /* Its a BOP */
222 printf("vunsol: stray interrupt from BOP at VIOC%d...\n",n);
223 return;
224 }
225 s = spl8();
226 vp = VBAS(n) ;
227 if(vp->v_uqual & V_UNBSY) {
228 vxrint(n) ;
229 vinthandl(n, ( (V_BSY | UNSquals) << 8 ) | V_INTR ) ;
230 splx(s);
231 }
232 else {
233 vpanic("vc: UNSOL INT ERR") ;
234 splx(s);
235 vxstreset(n);
236 }
237}
238
239/*
240 * Enqueue an interrupt
241 */
242vinthandl(n, item)
243register int n ;
244register item ;
245{
246
247 register struct vcmds *cp ;
248 register int empflag = 0 ;
249
250 cp = &v_cmds[n] ;
251 if( cp->v_itrfill == cp->v_itrempt ) empflag++ ;
252 cp->v_itrqueu[cp->v_itrfill] = item ;
253 if( ++cp->v_itrfill >= VC_IQLEN ) cp->v_itrfill = 0 ;
254 if(cp->v_itrfill == cp->v_itrempt) {
255 vpanic( "vc: INT Q OVFLO" ) ;
256 vxstreset(n);
257 }
258 else if( empflag ) vintempt(n) ;
259}
260
261vintempt(n)
262register int n ;
263{
264 register struct vcmds *cp ;
265 register struct vblok *vp ;
266 register short item ;
267 register short *intr ;
268
269 vp = VBAS(n) ;
270 if(vp->v_vioc & V_BSY) return ;
271 cp = &v_cmds[n] ;
272 if(cp->v_itrempt == cp->v_itrfill) return ;
273 item = cp->v_itrqueu[cp->v_itrempt] ;
274 intr = (short *)&vp->v_vioc ;
275 switch( (item >> 8) & 03 ) {
276
277 case CMDquals: /* command */
278 {
279 int phys;
280
281 if(cp->v_empty == cp->v_fill || vp->v_vcbsy&V_BSY)
282 break;
283 (&vcx[n])->v_mricmd = (caddr_t)cp->cmdbuf[cp->v_empty];
284 phys = vtoph(0, cp->cmdbuf[cp->v_empty]) ; /* should be a sys address */
285 vp->v_vcp[0] = ((short *)&phys)[0];
286 vp->v_vcp[1] = ((short *)&phys)[1];
287 vp->v_vcbsy = V_BSY ;
288 *intr = item ;
289 }
290#ifdef VXPERF
291 scope_out(4);
292#endif VXPERF
293 break ;
294
295 case RSPquals: /* command response */
296 *intr = item ;
297#ifdef VXPERF
298 scope_out(7);
299#endif VXPERF
300 break ;
301
302 case UNSquals: /* unsolicited interrupt */
303 vp->v_uqual = 0 ;
304 *intr = item ;
305#ifdef VXPERF
306 scope_out(2);
307#endif VXPERF
308 break ;
309 }
310}
311
312
313/* start a reset on a vioc after error (hopefully) */
314vxstreset(n)
315 register n;
316{
317 register struct vcx *xp;
318 register struct vblok *vp ;
319 register struct vxcmd *cp;
320 register int j;
321 extern int vxinreset();
322 int s ;
323
324 s = spl8() ;
325 vp = VBAS(n);
326 xp = &vcx[n];
327
328 if (xp->v_state&V_RESETTING)
329 /*
330 * Avoid infinite recursion.
331 */
332 return;
333
334 /*
335 * Zero out the vioc structures, mark the vioc as being
336 * reset, reinitialize the free command list, reset the vioc
337 * and start a timer to check on the progress of the reset.
338 */
339 bzero(&v_cmds[n], sizeof(struct vcmds));
340 bzero(xp, sizeof(struct vcx));
341
342 /*
343 * Setting V_RESETTING prevents others from issuing
344 * commands while allowing currently queued commands to
345 * be passed to the VIOC.
346 */
347 xp->v_state |= V_RESETTING;
348 for(j=0; j<NVCXBUFS; j++) /* init all cmd buffers */
349 {
350 cp = &xp->vx_lst[j]; /* index a buffer */
351 cp->c_fwd = &xp->vx_lst[j+1]; /* point to next buf */
352 }
353 xp->vx_avail = &xp->vx_lst[0]; /* set idx to 1st free buf */
354 cp->c_fwd = (struct vxcmd *)0; /* mark last buf in free list */
355
356 printf("resetting VIOC %x .. ", n);
357
358 vp->v_fault = 0 ;
359 vp->v_vioc = V_BSY ;
360 vp->v_hdwre = V_RESET ; /* reset interrupt */
361
362 timeout(vxinreset, (caddr_t)n, hz*5);
363 splx(s);
364 return;
365}
366
367/* continue processing a reset on a vioc after an error (hopefully) */
368vxinreset(vioc)
369caddr_t vioc;
370{
371 register struct vcx *xp;
372 register struct vblok *vp ;
373 register int n = (int)vioc;
374 int s = spl8();
375printf("vxinreset ");
376
377 vp = VBAS(n);
378 xp = &vcx[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, 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) */
404vxfnreset(n, cp)
405register int n;
406register struct vxcmd *cp;
407{
408 register struct vcx *xp;
409 register struct vblok *vp ;
410 register struct tty *tp;
411 register int i;
412 register int on;
413 extern int vxrestart();
414 int s = spl8();
415printf("vxfnreset ");
416
417 vp = VBAS(n);
418 xp = &vcx[n];
419
420 xp->v_loport = cp->par[5]; /* save low port number */
421 xp->v_hiport = cp->par[7];/* VIOC knows high port numbr */
422 vrelease(xp,cp); /* done with this control block */
423 xp->v_nbr = n; /* assign VIOC-X board number */
424
425 xp->v_state &= ~V_RESETTING;
426
427 vp->v_vcid = 0;
428
429 /*
430 * Restore modem information and control.
431 */
432 for(i=xp->v_loport; i<=xp->v_hiport; i++) {
433 tp = &vx_tty[i+n*16];
434 if (tp->t_state&(TS_ISOPEN|TS_WOPEN)) {
435 tp->t_state &= ~TS_CARR_ON;
436 vcmodem(tp->t_dev, VMOD_ON);
437 if (tp->t_state&TS_CARR_ON) {
438 wakeup((caddr_t)&tp->t_canq) ;
439 }
440 else {
441 if(tp->t_state & TS_ISOPEN) {
442 ttyflush(tp, FREAD|FWRITE);
443 if(tp->t_state&TS_FLUSH)
444 wakeup((caddr_t)&tp->t_state) ;
445 if((tp->t_flags&NOHANG)==0) {
446 gsignal(tp->t_pgrp, SIGHUP) ;
447 gsignal(tp->t_pgrp, SIGCONT);
448 }
449 }
450 }
451 }
452 /*
453 * If carrier has changed while we were resetting,
454 * take appropriate action.
455 */
456/*
457 on = vp->v_dcd & 1<<i;
458 if (on && (tp->t_state&TS_CARR_ON) == 0) {
459 tp->t_state |= TS_CARR_ON ;
460 wakeup((caddr_t)&tp->t_canq) ;
461 } else if (!on && tp->t_state&TS_CARR_ON) {
462 tp->t_state &= ~TS_CARR_ON ;
463 if(tp->t_state & TS_ISOPEN) {
464 ttyflush(tp, FREAD|FWRITE);
465 if(tp->t_state&TS_FLUSH)
466 wakeup((caddr_t)&tp->t_state) ;
467 if((tp->t_flags&NOHANG)==0) {
468 gsignal(tp->t_pgrp, SIGHUP) ;
469 gsignal(tp->t_pgrp, SIGCONT);
470 }
471 }
472 }
473*/
474 }
475
476 xp->v_state |= V_RESETTING;
477
478 timeout(vxrestart, (caddr_t)n, hz);
479 splx(s);
480}
481
482/*
483 * Restore a particular aspect of the VIOC.
484 */
485vxrestart(vioc)
486caddr_t vioc;
487{
488 register struct tty *tp, *tp0;
489 register struct vcx *xp;
490 register int i, cnt;
491 register int n = (int)vioc;
492 int s = spl8();
493
494 cnt = n>>8;
495printf("vxrestart %d ",cnt);
496 n &= 0xff;
497
498 tp0 = &vx_tty[n*16];
499 xp = &vcx[n];
500
501 xp->v_state &= ~V_RESETTING;
502
503 for(i=xp->v_loport; i<=xp->v_hiport; i++) {
504 tp = tp0 + i;
505 if (cnt != 0) {
506 tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
507 if(tp->t_state&(TS_ISOPEN|TS_WOPEN)) /* restart pending output */
508 vxstart(tp);
509 } else {
510 if (tp->t_state&(TS_WOPEN|TS_ISOPEN))
511 vxcparam(tp->t_dev, 0);
512 }
513 }
514
515 if (cnt == 0) {
516 xp->v_state |= V_RESETTING;
517 timeout(vxrestart, (caddr_t)(n + 1*256), hz);
518 } else
519 printf("done\n");
520 splx(s);
521}
522
523vxreset(dev)
524dev_t dev;
525{
526 vxstreset(minor(dev)>>4); /* completes asynchronously */
527}
528
529vxfreset(n)
530register int n;
531{
532 register struct vblok *vp;
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