xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 30294)
1 /*	cy.c	1.8	86/12/15	*/
2 
3 #include "yc.h"
4 #if NCY > 0
5 /*
6  * Cipher Tapemaster driver.
7  */
8 int	cydebug = 0;
9 #define	dlog	if (cydebug) log
10 
11 #include "param.h"
12 #include "systm.h"
13 #include "vm.h"
14 #include "buf.h"
15 #include "file.h"
16 #include "dir.h"
17 #include "user.h"
18 #include "proc.h"
19 #include "signal.h"
20 #include "uio.h"
21 #include "ioctl.h"
22 #include "mtio.h"
23 #include "errno.h"
24 #include "cmap.h"
25 #include "kernel.h"
26 #include "syslog.h"
27 #include "tty.h"
28 
29 #include "../tahoe/cpu.h"
30 #include "../tahoe/mtpr.h"
31 #include "../tahoe/pte.h"
32 
33 #include "../tahoevba/vbavar.h"
34 #define	CYERROR
35 #include "../tahoevba/cyreg.h"
36 
37 /*
38  * There is a ccybuf per tape controller.
39  * It is used as the token to pass to the internal routines
40  * to execute tape ioctls, and also acts as a lock on the slaves
41  * on the controller, since there is only one per controller.
42  * In particular, when the tape is rewinding on close we release
43  * the user process but any further attempts to use the tape drive
44  * before the rewind completes will hang waiting for ccybuf.
45  */
46 struct	buf ccybuf[NCY];
47 
48 /*
49  * Raw tape operations use rcybuf.  The driver notices when
50  * rcybuf is being used and allows the user program to contine
51  * after errors and read records not of the standard length.
52  */
53 struct	buf rcybuf[NCY];
54 
55 int	cyprobe(), cyslave(), cyattach();
56 struct	buf ycutab[NYC];
57 short	yctocy[NYC];
58 struct	vba_ctlr *cyminfo[NCY];
59 struct	vba_device *ycdinfo[NYC];
60 long	cystd[] = { 0 };
61 struct	vba_driver cydriver =
62    { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
63 
64 /* bits in minor device */
65 #define	YCUNIT(dev)	(minor(dev)&03)
66 #define	CYUNIT(dev)	(yctocy[YCUNIT(dev)])
67 #define	T_NOREWIND	0x04
68 #define	T_1600BPI	0x08
69 #define	T_3200BPI	0x10
70 
71 #define	INF	1000000L		/* close to infinity */
72 #define	CYMAXIO	(32*NBPG)		/* max i/o size */
73 
74 /*
75  * Software state and shared command areas per controller.
76  *
77  * The i/o buffer must be defined statically to insure
78  * it's address will fit in 20-bits (YECH!!!!!!!!!!!!!!)
79  */
80 struct cy_softc {
81 	struct	pte *cy_map;	/* pte's for mapped buffer i/o */
82 	caddr_t	cy_utl;		/* mapped virtual address */
83 	int	cy_bs;		/* controller's buffer size */
84 	char	cy_buf[CYMAXIO];/* intermediate buffer */
85 	struct	cyscp *cy_scp;	/* system configuration block address */
86 	struct	cyccb cy_ccb;	/* channel control block */
87 	struct	cyscb cy_scb;	/* system configuration block */
88 	struct	cytpb cy_tpb;	/* tape parameter block */
89 	struct	cytpb cy_nop;	/* nop parameter block for cyintr */
90 } cy_softc[NCY];
91 
92 /*
93  * Software state per tape transport.
94  */
95 struct	yc_softc {
96 	char	yc_openf;	/* lock against multiple opens */
97 	char	yc_lastiow;	/* last operation was a write */
98 	short	yc_tact;	/* timeout is active */
99 	long	yc_timo;	/* time until timeout expires */
100 	u_short	yc_control;	/* copy of last tpcb.tpcontrol */
101 	u_short	yc_status;	/* copy of last tpcb.tpstatus */
102 	u_short	yc_resid;	/* copy of last bc */
103 	u_short	yc_dens;	/* prototype control word with density info */
104 	struct	tty *yc_ttyp;	/* user's tty for errors */
105 	daddr_t	yc_blkno;	/* block number, for block device tape */
106 	daddr_t	yc_nxrec;	/* position of end of tape, if known */
107 } yc_softc[NYC];
108 
109 /*
110  * States for vm->um_tab.b_active, the per controller state flag.
111  * This is used to sequence control in the driver.
112  */
113 #define	SSEEK	1		/* seeking */
114 #define	SIO	2		/* doing seq i/o */
115 #define	SCOM	3		/* sending control command */
116 #define	SREW	4		/* sending a rewind */
117 #define	SERASE	5		/* erase inter-record gap */
118 #define	SERASED	6		/* erased inter-record gap */
119 
120 /* there's no way to figure these out dynamically? -- yech */
121 struct	cyscp *cyscp[] =
122     { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
123 #define	NCYSCP	(sizeof (cyscp) / sizeof (cyscp[0]))
124 
125 cyprobe(reg, vm)
126 	caddr_t reg;
127 	struct vba_ctlr *vm;
128 {
129 	register br, cvec;			/* must be r12, r11 */
130 
131 #ifdef lint
132 	br = 0; cvec = br; br = cvec;
133 	cyintr(0);
134 #endif
135 	if (badcyaddr(reg+1))
136 		return (0);
137 	if (vm->um_ctlr > NCYSCP || cyscp[vm->um_ctlr] == 0)	/* XXX */
138 		return (0);					/* XXX */
139 	cy_softc[vm->um_ctlr].cy_scp = cyscp[vm->um_ctlr];	/* XXX */
140 	/*
141 	 * Tapemaster controller must have interrupt handler
142 	 * disable interrupt, so we'll just kludge things
143 	 * (stupid multibus non-vectored interrupt crud).
144 	 */
145 	br = 0x13, cvec = 0x80;					/* XXX */
146 	return (sizeof (struct cyccb));
147 }
148 
149 /*
150  * Check to see if a drive is attached to a controller.
151  * Since we can only tell that a drive is there if a tape is loaded and
152  * the drive is placed online, we always indicate the slave is present.
153  */
154 cyslave(vi, addr)
155 	struct vba_device *vi;
156 	caddr_t addr;
157 {
158 
159 #ifdef lint
160 	vi = vi; addr = addr;
161 #endif
162 	return (1);
163 }
164 
165 cyattach(vi)
166 	struct vba_device *vi;
167 {
168 	register struct cy_softc *cy;
169 	int ctlr = vi->ui_mi->um_ctlr;
170 
171 	yctocy[vi->ui_unit] = ctlr;
172 	cy = &cy_softc[ctlr];
173 	if (cy->cy_bs == 0 && cyinit(ctlr)) {
174 		uncache(&cy->cy_tpb.tpcount);
175 		cy->cy_bs = htoms(cy->cy_tpb.tpcount);
176 		printf("cy%d: %dkb buffer\n", ctlr, cy->cy_bs/1024);
177 		/*
178 		 * Setup nop parameter block for clearing interrupts.
179 		 */
180 		cy->cy_nop.tpcmd = CY_NOP;
181 		cy->cy_nop.tpcontrol = 0;
182 		/*
183 		 * Allocate page tables.
184 		 */
185 		vbmapalloc(btoc(CYMAXIO)+1, &cy->cy_map, &cy->cy_utl);
186 	}
187 }
188 
189 /*
190  * Initialize the controller after a controller reset or
191  * during autoconfigure.  All of the system control blocks
192  * are initialized and the controller is asked to configure
193  * itself for later use.
194  */
195 cyinit(ctlr)
196 	int ctlr;
197 {
198 	register struct cy_softc *cy = &cy_softc[ctlr];
199 	register caddr_t addr = cyminfo[ctlr]->um_addr;
200 	register int *pte;
201 
202 	/*
203 	 * Initialize the system configuration pointer.
204 	 */
205 	/* make kernel writable */
206 	pte = (int *)vtopte((struct proc *)0, btop(cy->cy_scp));
207 	*pte &= ~PG_PROT; *pte |= PG_KW;
208 	mtpr(TBIS, cy->cy_scp);
209 	/* load the correct values in the scp */
210 	cy->cy_scp->csp_buswidth = CSP_16BITS;
211 	cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
212 	/* put it back to read-only */
213 	*pte &= ~PG_PROT; *pte |= PG_KR;
214 	mtpr(TBIS, cy->cy_scp);
215 
216 	/*
217 	 * Init system configuration block.
218 	 */
219 	cy->cy_scb.csb_fixed = 0x3;
220 	/* set pointer to the channel control block */
221 	cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
222 
223 	/*
224 	 * Initialize the chanel control block.
225 	 */
226 	cy->cy_ccb.cbcw = CBCW_CLRINT;
227 	cy->cy_ccb.cbgate = GATE_OPEN;
228 	/* set pointer to the tape parameter block */
229 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
230 
231 	/*
232 	 * Issue a nop cmd and get the internal buffer size for buffered i/o.
233 	 */
234 	cy->cy_tpb.tpcmd = CY_NOP;
235 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
236 	cy->cy_ccb.cbgate = GATE_CLOSED;
237 	CY_GO(addr);
238 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
239 		uncache(&cy->cy_tpb.tpstatus);
240 		printf("cy%d: timeout or err during init, status=%b\n", ctlr,
241 		    cy->cy_tpb.tpstatus, CYS_BITS);
242 		return (0);
243 	}
244 	cy->cy_tpb.tpcmd = CY_CONFIG;
245 	cy->cy_tpb.tpcontrol = CYCW_16BITS;
246 	cy->cy_ccb.cbgate = GATE_CLOSED;
247 	CY_GO(addr);
248 	if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
249 		uncache(&cy->cy_tpb.tpstatus);
250 		printf("cy%d: configuration failure, status=%b\n", ctlr,
251 		    cy->cy_tpb.tpstatus, CYS_BITS);
252 		return (0);
253 	}
254 	return (1);
255 }
256 
257 int	cytimer();
258 /*
259  * Open the device.  Tapes are unique open
260  * devices, so we refuse if it is already open.
261  * We also check that a tape is available, and
262  * don't block waiting here; if you want to wait
263  * for a tape you should timeout in user code.
264  */
265 cyopen(dev, flag)
266 	dev_t dev;
267 	register int flag;
268 {
269 	register int ycunit;
270 	register struct vba_device *vi;
271 	register struct yc_softc *yc;
272 	int s;
273 
274 	ycunit = YCUNIT(dev);
275 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
276 		return (ENXIO);
277 	if ((yc = &yc_softc[ycunit])->yc_openf)
278 		return (EBUSY);
279 #define	PACKUNIT(vi) \
280     (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
281 	/* no way to select density */
282 	yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
283 	cycommand(dev, CY_SENSE, 1);
284 	if ((yc->yc_status&CYS_OL) == 0) {	/* not on-line */
285 		uprintf("yc%d: not online\n", ycunit);
286 		return (ENXIO);
287 	}
288 	if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
289 		uprintf("yc%d: no write ring\n", ycunit);
290 		return (ENXIO);
291 	}
292 	yc->yc_openf = 1;
293 	yc->yc_blkno = (daddr_t)0;
294 	yc->yc_nxrec = INF;
295 	yc->yc_lastiow = 0;
296 	yc->yc_ttyp = u.u_ttyp;
297 	s = splclock();
298 	if (yc->yc_tact == 0) {
299 		yc->yc_timo = INF;
300 		yc->yc_tact = 1;
301 		timeout(cytimer, (caddr_t)dev, 5*hz);
302 	}
303 	splx(s);
304 	return (0);
305 }
306 
307 /*
308  * Close tape device.
309  *
310  * If tape was open for writing or last operation was a write,
311  * then write two EOF's and backspace over the last one.
312  * Unless this is a non-rewinding special file, rewind the tape.
313  * Make the tape available to others.
314  */
315 cyclose(dev, flag)
316 	dev_t dev;
317 	register int flag;
318 {
319 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
320 
321 	if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
322 		cycommand(dev, CY_WEOF, 2);
323 		cycommand(dev, CY_SREV, 1);
324 	}
325 	if ((minor(dev)&T_NOREWIND) == 0)
326 		/*
327 		 * 0 count means don't hang waiting for rewind complete
328 		 * rather ccybuf stays busy until the operation completes
329 		 * preventing further opens from completing by preventing
330 		 * a CY_SENSE from completing.
331 		 */
332 		cycommand(dev, CY_REW, 0);
333 	yc->yc_openf = 0;
334 }
335 
336 /*
337  * Execute a command on the tape drive a specified number of times.
338  */
339 cycommand(dev, com, count)
340 	dev_t dev;
341 	int com, count;
342 {
343 	register struct buf *bp;
344 	int s;
345 
346 	bp = &ccybuf[CYUNIT(dev)];
347 	s = spl3();
348 	dlog(LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
349 	    dev, com, count, bp->b_flags);
350 	while (bp->b_flags&B_BUSY) {
351 		/*
352 		 * This special check is because B_BUSY never
353 		 * gets cleared in the non-waiting rewind case.
354 		 */
355 		if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
356 			break;
357 		bp->b_flags |= B_WANTED;
358 		sleep((caddr_t)bp, PRIBIO);
359 	}
360 	bp->b_flags = B_BUSY|B_READ;
361 	splx(s);
362 	bp->b_dev = dev;
363 	bp->b_repcnt = count;
364 	bp->b_command = com;
365 	bp->b_blkno = 0;
366 	cystrategy(bp);
367 	/*
368 	 * In case of rewind from close; don't wait.
369 	 * This is the only case where count can be 0.
370 	 */
371 	if (count == 0)
372 		return;
373 	iowait(bp);
374 	if (bp->b_flags&B_WANTED)
375 		wakeup((caddr_t)bp);
376 	bp->b_flags &= B_ERROR;
377 }
378 
379 cystrategy(bp)
380 	register struct buf *bp;
381 {
382 	int ycunit = YCUNIT(bp->b_dev);
383 	register struct vba_ctlr *vm;
384 	register struct buf *dp;
385 	int s;
386 
387 	/*
388 	 * Put transfer at end of unit queue.
389 	 */
390 	dlog(LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command);
391 	dp = &ycutab[ycunit];
392 	bp->av_forw = NULL;
393 	vm = ycdinfo[ycunit]->ui_mi;
394 	/* BEGIN GROT */
395 	if (bp == &rcybuf[CYUNIT(bp->b_dev)]) {
396 		if (bp->b_bcount > CYMAXIO) {
397 			uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
398 			bp->b_error = EIO;
399 			bp->b_resid = bp->b_bcount;
400 			bp->b_flags |= B_ERROR;
401 			iodone(bp);
402 			return;
403 		}
404 		vbasetup(bp, CYMAXIO);
405 	}
406 	/* END GROT */
407 	s = spl3();
408 	if (dp->b_actf == NULL) {
409 		dp->b_actf = bp;
410 		/*
411 		 * Transport not already active...
412 		 * put at end of controller queue.
413 		 */
414 		 dp->b_forw = NULL;
415 		 if (vm->um_tab.b_actf == NULL)
416 			vm->um_tab.b_actf = dp;
417 		else
418 			vm->um_tab.b_actl->b_forw = dp;
419 	} else
420 		dp->b_actl->av_forw = bp;
421 	dp->b_actl = bp;
422 	/*
423 	 * If the controller is not busy, get it going.
424 	 */
425 	if (vm->um_tab.b_active == 0)
426 		cystart(vm);
427 	splx(s);
428 }
429 
430 /*
431  * Start activity on a cy controller.
432  */
433 cystart(vm)
434 	register struct vba_ctlr *vm;
435 {
436 	register struct buf *bp, *dp;
437 	register struct yc_softc *yc;
438 	register struct cy_softc *cy;
439 	int ycunit;
440 	daddr_t blkno;
441 
442 	dlog(LOG_INFO, "cystart()\n");
443 	/*
444 	 * Look for an idle transport on the controller.
445 	 */
446 loop:
447 	if ((dp = vm->um_tab.b_actf) == NULL)
448 		return;
449 	if ((bp = dp->b_actf) == NULL) {
450 		vm->um_tab.b_actf = dp->b_forw;
451 		goto loop;
452 	}
453 	ycunit = YCUNIT(bp->b_dev);
454 	yc = &yc_softc[ycunit];
455 	cy = &cy_softc[CYUNIT(bp->b_dev)];
456 	/*
457 	 * Default is that last command was NOT a write command;
458 	 * if we do a write command we will notice this in cyintr().
459 	 */
460 	yc->yc_lastiow = 0;
461 	if (yc->yc_openf < 0 ||
462 	    (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
463 		/*
464 		 * Have had a hard error on a non-raw tape
465 		 * or the tape unit is now unavailable (e.g.
466 		 * taken off line).
467 		 */
468 		dlog(LOG_INFO, "openf %d command %x status %b\n",
469 		    yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS);
470 		bp->b_flags |= B_ERROR;
471 		goto next;
472 	}
473 	if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
474 		/*
475 		 * Execute control operation with the specified count.
476 		 *
477 		 * Set next state; give 5 minutes to complete
478 		 * rewind or file mark search, or 10 seconds per
479 		 * iteration (minimum 60 seconds and max 5 minutes)
480 		 * to complete other ops.
481 		 */
482 		if (bp->b_command == CY_REW) {
483 			vm->um_tab.b_active = SREW;
484 			yc->yc_timo = 5*60;
485 		} else {
486 			vm->um_tab.b_active = SCOM;
487 			yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
488 		}
489 		cy->cy_tpb.tprec = htoms(bp->b_repcnt);
490 		goto dobpcmd;
491 	}
492 	/*
493 	 * The following checks handle boundary cases for operation
494 	 * on no-raw tapes.  On raw tapes the initialization of
495 	 * yc->yc_nxrec by cyphys causes them to be skipped normally
496 	 * (except in the case of retries).
497 	 */
498 	if (bdbtofsb(bp->b_blkno) > yc->yc_nxrec) {
499 		/*
500 		 * Can't read past known end-of-file.
501 		 */
502 		bp->b_flags |= B_ERROR;
503 		bp->b_error = ENXIO;
504 		goto next;
505 	}
506 	if (bdbtofsb(bp->b_blkno) == yc->yc_nxrec && bp->b_flags&B_READ) {
507 		/*
508 		 * Reading at end of file returns 0 bytes.
509 		 */
510 		bp->b_resid = bp->b_bcount;
511 		clrbuf(bp);
512 		goto next;
513 	}
514 	if ((bp->b_flags&B_READ) == 0)
515 		/*
516 		 * Writing sets EOF.
517 		 */
518 		yc->yc_nxrec = bdbtofsb(bp->b_blkno) + 1;
519 	if ((blkno = yc->yc_blkno) == bdbtofsb(bp->b_blkno)) {
520 		caddr_t addr;
521 		int cmd;
522 
523 		/*
524 		 * Choose the appropriate i/o command based on the
525 		 * transfer size and the controller's internal buffer.
526 		 * If we're retrying a read on a raw device because
527 		 * the original try was a buffer request which failed
528 		 * due to a record length error, then we force the use
529 		 * of the raw controller read (YECH!!!!).
530 		 */
531 		if (bp->b_flags&B_READ) {
532 			if (bp->b_bcount > cy->cy_bs || bp->b_errcnt)
533 				cmd = CY_RCOM;
534 			else
535 				cmd = CY_BRCOM;
536 		} else {
537 			/*
538 			 * On write error retries erase the
539 			 * inter-record gap before rewriting.
540 			 */
541 			if (vm->um_tab.b_errcnt &&
542 			    vm->um_tab.b_active != SERASED) {
543 				vm->um_tab.b_active = SERASE;
544 				bp->b_command = CY_ERASE;
545 				yc->yc_timo = 60;
546 				goto dobpcmd;
547 			}
548 			cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
549 		}
550 		vm->um_tab.b_active = SIO;
551 		addr = (caddr_t)vbastart(bp, cy->cy_buf,
552 		    (long *)cy->cy_map, cy->cy_utl);
553 		cy->cy_tpb.tpcmd = cmd;
554 		cy->cy_tpb.tpcontrol = yc->yc_dens;
555 		if (cmd == CY_RCOM || cmd == CY_WCOM)
556 			cy->cy_tpb.tpcontrol |= CYCW_LOCK;
557 		cy->cy_tpb.tpstatus = 0;
558 		cy->cy_tpb.tpcount = 0;
559 		cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
560 		cy->cy_tpb.tprec = 0;
561 		cy->cy_tpb.tpsize = htoms(bp->b_bcount);
562 		cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
563 		do
564 			uncache(&cy->cy_ccb.cbgate);
565 		while (cy->cy_ccb.cbgate == GATE_CLOSED);
566 		cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
567 		cy->cy_ccb.cbcw = CBCW_IE;
568 		cy->cy_ccb.cbgate = GATE_CLOSED;
569 		dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
570 		    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
571 		    htoms(cy->cy_tpb.tpsize));
572 		CY_GO(vm->um_addr);
573 		return;
574 	}
575 	/*
576 	 * Tape positioned incorrectly; set to seek forwards
577 	 * or backwards to the correct spot.  This happens
578 	 * for raw tapes only on error retries.
579 	 */
580 	vm->um_tab.b_active = SSEEK;
581 	if (blkno < bdbtofsb(bp->b_blkno)) {
582 		bp->b_command = CY_SFORW;
583 		cy->cy_tpb.tprec = htoms(bdbtofsb(bp->b_blkno) - blkno);
584 	} else {
585 		bp->b_command = CY_SREV;
586 		cy->cy_tpb.tprec = htoms(blkno - bdbtofsb(bp->b_blkno));
587 	}
588 	yc->yc_timo = imin(imax(10 * htoms(cy->cy_tpb.tprec), 60), 5*60);
589 dobpcmd:
590 	/*
591 	 * Do the command in bp.  Reverse direction commands
592 	 * are indicated by having CYCW_REV or'd into their
593 	 * value.  For these we must set the appropriate bit
594 	 * in the control field.
595 	 */
596 	if (bp->b_command&CYCW_REV) {
597 		cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
598 		cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
599 	} else {
600 		cy->cy_tpb.tpcmd = bp->b_command;
601 		cy->cy_tpb.tpcontrol = yc->yc_dens;
602 	}
603 	cy->cy_tpb.tpstatus = 0;
604 	cy->cy_tpb.tpcount = 0;
605 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
606 	do
607 		uncache(&cy->cy_ccb.cbgate);
608 	while (cy->cy_ccb.cbgate == GATE_CLOSED);
609 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
610 	cy->cy_ccb.cbcw = CBCW_IE;
611 	cy->cy_ccb.cbgate = GATE_CLOSED;
612 	dlog(LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
613 	    vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
614 	    htoms(cy->cy_tpb.tprec));
615 	CY_GO(vm->um_addr);
616 	return;
617 next:
618 	/*
619 	 * Done with this operation due to error or the
620 	 * fact that it doesn't do anything.  Release VERSAbus
621 	 * resource (if any), dequeue the transfer and continue
622 	 * processing this slave.
623 	 */
624 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
625 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
626 	vm->um_tab.b_errcnt = 0;
627 	dp->b_actf = bp->av_forw;
628 	iodone(bp);
629 	goto loop;
630 }
631 
632 /*
633  * Cy interrupt routine.
634  */
635 cyintr(cipher)
636 	int cipher;
637 {
638 	struct buf *dp;
639 	register struct buf *bp;
640 	register struct vba_ctlr *vm = cyminfo[cipher];
641 	register struct cy_softc *cy;
642 	register struct yc_softc *yc;
643 	int cyunit, err;
644 	register state;
645 
646 	dlog(LOG_INFO, "cyintr(%d)\n", cipher);
647 	/*
648 	 * First, turn off the interrupt from the controller
649 	 * (device uses Multibus non-vectored interrupts...yech).
650 	 */
651 	cy = &cy_softc[vm->um_ctlr];
652 	cy->cy_ccb.cbcw = CBCW_CLRINT;
653 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
654 	cy->cy_ccb.cbgate = GATE_CLOSED;
655 	CY_GO(vm->um_addr);
656 	if ((dp = vm->um_tab.b_actf) == NULL) {
657 		dlog(LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr);
658 		return;
659 	}
660 	bp = dp->b_actf;
661 	cyunit = CYUNIT(bp->b_dev);
662 	cy = &cy_softc[cyunit];
663 	cyuncachetpb(cy);
664 	yc = &yc_softc[YCUNIT(bp->b_dev)];
665 	/*
666 	 * If last command was a rewind and tape is
667 	 * still moving, wait for the operation to complete.
668 	 */
669 	if (vm->um_tab.b_active == SREW) {
670 		vm->um_tab.b_active = SCOM;
671 		if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
672 			yc->yc_timo = 5*60;	/* 5 minutes */
673 			return;
674 		}
675 	}
676 	/*
677 	 * An operation completed...record status.
678 	 */
679 	yc->yc_timo = INF;
680 	yc->yc_control = cy->cy_tpb.tpcontrol;
681 	yc->yc_status = cy->cy_tpb.tpstatus;
682 	yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
683 	dlog(LOG_INFO, "cmd %x control %b status %b resid %d\n",
684 	    cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
685 	    yc->yc_status, CYS_BITS, yc->yc_resid);
686 	if ((bp->b_flags&B_READ) == 0)
687 		yc->yc_lastiow = 1;
688 	state = vm->um_tab.b_active;
689 	vm->um_tab.b_active = 0;
690 	/*
691 	 * Check for errors.
692 	 */
693 	if (cy->cy_tpb.tpstatus&CYS_ERR) {
694 		err = cy->cy_tpb.tpstatus&CYS_ERR;
695 		dlog(LOG_INFO, "error %d\n", err);
696 		/*
697 		 * If we hit the end of tape file, update our position.
698 		 */
699 		if (err == CYER_FM) {
700 			yc->yc_status |= CYS_FM;
701 			state = SCOM;		/* force completion */
702 			cyseteof(bp);		/* set blkno and nxrec */
703 			goto opdone;
704 		}
705 		/*
706 		 * Fix up errors which occur due to backspacing over
707 		 * the beginning of the tape.
708 		 */
709 		if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
710 			yc->yc_status |= CYS_BOT;
711 			goto ignoreerr;
712 		}
713 		/*
714 		 * If we were reading raw tape and the only error was that the
715 		 * record was too long, then we don't consider this an error.
716 		 */
717 		if (bp == &rcybuf[cyunit] && (bp->b_flags&B_READ) &&
718 		    err == CYER_STROBE) {
719 			/*
720 			 * Retry reads once with the command changed to
721 			 * a raw read (if possible).  Setting b_errcnt
722 			 * here causes cystart (above) to force a CY_RCOM.
723 			 */
724 			if (bp->b_errcnt++ != 0)
725 				goto ignoreerr;
726 			yc->yc_blkno++;
727 			goto opcont;
728 		}
729 		/*
730 		 * If error is not hard, and this was an i/o operation
731 		 * retry up to 8 times.
732 		 */
733 		if (((1<<err)&CYER_SOFT) && state == SIO) {
734 			if (++vm->um_tab.b_errcnt < 7) {
735 				yc->yc_blkno++;
736 				goto opcont;
737 			}
738 		} else
739 			/*
740 			 * Hard or non-i/o errors on non-raw tape
741 			 * cause it to close.
742 			 */
743 			if (yc->yc_openf>0 && bp != &rcybuf[cyunit])
744 				yc->yc_openf = -1;
745 		/*
746 		 * Couldn't recover from error.
747 		 */
748 		tprintf(yc->yc_ttyp,
749 		    "yc%d: hard error bn%d status=%b", YCUNIT(bp->b_dev),
750 		    bp->b_blkno, yc->yc_status, CYS_BITS);
751 		if (err < NCYERROR)
752 			tprintf(yc->yc_ttyp, ", %s", cyerror[err]);
753 		tprintf(yc->yc_ttyp, "\n");
754 		bp->b_flags |= B_ERROR;
755 		goto opdone;
756 	}
757 	/*
758 	 * Advance tape control FSM.
759 	 */
760 ignoreerr:
761 	/*
762 	 * If we hit a tape mark update our position.
763 	 */
764 	if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
765 		cyseteof(bp);
766 		goto opdone;
767 	}
768 	switch (state) {
769 
770 	case SIO:
771 		/*
772 		 * Read/write increments tape block number.
773 		 */
774 		yc->yc_blkno++;
775 		goto opdone;
776 
777 	case SCOM:
778 		/*
779 		 * For forward/backward space record update current position.
780 		 */
781 		if (bp == &ccybuf[CYUNIT(bp->b_dev)])
782 			switch ((int)bp->b_command) {
783 
784 			case CY_SFORW:
785 				yc->yc_blkno -= bp->b_repcnt;
786 				break;
787 
788 			case CY_SREV:
789 				yc->yc_blkno += bp->b_repcnt;
790 				break;
791 			}
792 		goto opdone;
793 
794 	case SSEEK:
795 		yc->yc_blkno = bdbtofsb(bp->b_blkno);
796 		goto opcont;
797 
798 	case SERASE:
799 		/*
800 		 * Completed erase of the inter-record gap due to a
801 		 * write error; now retry the write operation.
802 		 */
803 		vm->um_tab.b_active = SERASED;
804 		goto opcont;
805 	}
806 
807 opdone:
808 	/*
809 	 * Reset error count and remove from device queue.
810 	 */
811 	vm->um_tab.b_errcnt = 0;
812 	dp->b_actf = bp->av_forw;
813 	/*
814 	 * Save resid and release resources.
815 	 */
816 	bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
817 	if (bp == &rcybuf[CYUNIT(bp->b_dev)])
818 		vbadone(bp, cy->cy_buf, (long *)cy->cy_map, cy->cy_utl);
819 	iodone(bp);
820 	/*
821 	 * Circulate slave to end of controller
822 	 * queue to give other slaves a chance.
823 	 */
824 	vm->um_tab.b_actf = dp->b_forw;
825 	if (dp->b_actf) {
826 		dp->b_forw = NULL;
827 		if (vm->um_tab.b_actf == NULL)
828 			vm->um_tab.b_actf = dp;
829 		else
830 			vm->um_tab.b_actl->b_forw = dp;
831 	}
832 	if (vm->um_tab.b_actf == 0)
833 		return;
834 opcont:
835 	cystart(vm);
836 }
837 
838 cytimer(dev)
839 	int dev;
840 {
841 	register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
842 	int s;
843 
844 	if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
845 		printf("yc%d: lost interrupt\n", YCUNIT(dev));
846 		yc->yc_timo = INF;
847 		s = spl3();
848 		cyintr(CYUNIT(dev));
849 		splx(s);
850 	}
851 	timeout(cytimer, (caddr_t)dev, 5*hz);
852 }
853 
854 cyseteof(bp)
855 	register struct buf *bp;
856 {
857 	register int cyunit = CYUNIT(bp->b_dev);
858 	register struct cy_softc *cy = &cy_softc[cyunit];
859 	register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
860 
861 	if (bp == &ccybuf[cyunit]) {
862 		if (yc->yc_blkno > bdbtofsb(bp->b_blkno)) {
863 			/* reversing */
864 			yc->yc_nxrec = bdbtofsb(bp->b_blkno) -
865 			    htoms(cy->cy_tpb.tpcount);
866 			yc->yc_blkno = yc->yc_nxrec;
867 		} else {
868 			yc->yc_blkno = bdbtofsb(bp->b_blkno) +
869 			    htoms(cy->cy_tpb.tpcount);
870 			yc->yc_nxrec = yc->yc_blkno - 1;
871 		}
872 		return;
873 	}
874 	/* eof on read */
875 	yc->yc_nxrec = bdbtofsb(bp->b_blkno);
876 }
877 
878 cyread(dev, uio)
879 	dev_t dev;
880 	struct uio *uio;
881 {
882 	int errno;
883 
884 	errno = cyphys(dev, uio);
885 	if (errno)
886 		return (errno);
887 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_READ, minphys, uio));
888 }
889 
890 cywrite(dev, uio)
891 	dev_t dev;
892 	struct uio *uio;
893 {
894 	int errno;
895 
896 	errno = cyphys(dev, uio);
897 	if (errno)
898 		return (errno);
899 	return (physio(cystrategy, &rcybuf[CYUNIT(dev)], dev, B_WRITE, minphys, uio));
900 }
901 
902 /*
903  * Check that a raw device exits.
904  * If it does, set up the yc_blkno and yc_nxrec
905  * so that the tape will appear positioned correctly.
906  */
907 cyphys(dev, uio)
908 	dev_t dev;
909 	struct uio *uio;
910 {
911 	register int ycunit = YCUNIT(dev);
912 	register daddr_t a;
913 	register struct yc_softc *yc;
914 	register struct vba_device *vi;
915 
916 	if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
917 		return (ENXIO);
918 	yc = &yc_softc[ycunit];
919 	a = bdbtofsb(uio->uio_offset >> DEV_BSHIFT);
920 	yc->yc_blkno = a;
921 	yc->yc_nxrec = a + 1;
922 	return (0);
923 }
924 
925 /*ARGSUSED*/
926 cyioctl(dev, cmd, data, flag)
927 	caddr_t data;
928 	dev_t dev;
929 {
930 	int ycunit = YCUNIT(dev);
931 	register struct yc_softc *yc = &yc_softc[ycunit];
932 	register struct buf *bp = &ccybuf[CYUNIT(dev)];
933 	register callcount;
934 	int fcount, op;
935 	struct mtop *mtop;
936 	struct mtget *mtget;
937 	/* we depend of the values and order of the MT codes here */
938 	static cyops[] =
939 	{CY_WEOF,CY_SFORW,CY_SREV,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
940 
941 	switch (cmd) {
942 
943 	case MTIOCTOP:	/* tape operation */
944 		mtop = (struct mtop *)data;
945 		switch (op = mtop->mt_op) {
946 
947 		case MTWEOF:
948 		case MTFSR: case MTBSR:
949 		case MTFSF: case MTBSF:
950 			callcount = mtop->mt_count;
951 			fcount = 1;
952 			break;
953 
954 		case MTREW: case MTOFFL: case MTNOP:
955 			callcount = 1;
956 			fcount = 1;
957 			break;
958 
959 		default:
960 			return (ENXIO);
961 		}
962 		if (callcount <= 0 || fcount <= 0)
963 			return (EINVAL);
964 		while (--callcount >= 0) {
965 			/*
966 			 * Gagh, this controller is the pits...
967 			 */
968 			if (op == MTFSF || op == MTBSF) {
969 				do
970 					cycommand(dev, cyops[op], 1);
971 				while ((bp->b_flags&B_ERROR) == 0 &&
972 				 (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
973 			} else
974 				cycommand(dev, cyops[op], fcount);
975 			if ((bp->b_flags&B_ERROR) ||
976 			    (yc->yc_status&(CYS_BOT|CYS_EOT)))
977 				break;
978 		}
979 		bp->b_resid = callcount + 1;
980 		return (geterror(bp));
981 
982 	case MTIOCGET:
983 		cycommand(dev, CY_SENSE, 1);
984 		mtget = (struct mtget *)data;
985 		mtget->mt_dsreg = yc->yc_status;
986 		mtget->mt_erreg = yc->yc_control;
987 		mtget->mt_resid = yc->yc_resid;
988 		mtget->mt_type = MT_ISCY;
989 		break;
990 
991 	default:
992 		return (ENXIO);
993 	}
994 	return (0);
995 }
996 
997 /*
998  * Poll until the controller is ready.
999  */
1000 cywait(cp)
1001 	register struct cyccb *cp;
1002 {
1003 	register int i = 5000;
1004 
1005 	uncache(&cp->cbgate);
1006 	while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
1007 		DELAY(1000);
1008 		uncache(&cp->cbgate);
1009 	}
1010 	return (i <= 0);
1011 }
1012 
1013 /*
1014  * Load a 20 bit pointer into an i/o register.
1015  */
1016 cyldmba(wreg, value)
1017 	short *wreg;
1018 	caddr_t value;
1019 {
1020 	register int v = (int)value;
1021 	register caddr_t reg = (caddr_t)wreg;
1022 
1023 	*reg++ = v;
1024 	*reg++ = v >> 8;
1025 	*reg++ = 0;
1026 	*reg = (v&0xf0000) >> 12;
1027 }
1028 
1029 /*
1030  * Unconditionally reset all controllers to their initial state.
1031  */
1032 cyreset(vba)
1033 	int vba;
1034 {
1035 	register caddr_t addr;
1036 	register int ctlr;
1037 
1038 	for (ctlr = 0; ctlr < NCY; ctlr++)
1039 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
1040 			addr = cyminfo[ctlr]->um_addr;
1041 			CY_RESET(addr);
1042 			if (!cyinit(ctlr)) {
1043 				printf("cy%d: reset failed\n", ctlr);
1044 				cyminfo[ctlr] = NULL;
1045 			}
1046 		}
1047 }
1048 
1049 cyuncachetpb(cy)
1050 	struct cy_softc *cy;
1051 {
1052 	register long *lp = (long *)&cy->cy_tpb;
1053 	register int i;
1054 
1055 	for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
1056 		uncache(lp++);
1057 }
1058 
1059 /*
1060  * Dump routine.
1061  */
1062 cydump(dev)
1063 	dev_t dev;
1064 {
1065 	register struct cy_softc *cy;
1066 	register int bs, num, start;
1067 	register caddr_t addr;
1068 	int unit = CYUNIT(dev), error;
1069 
1070 	if (unit >= NCY || cyminfo[unit] == 0 ||
1071 	    (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
1072 		return (ENXIO);
1073 	if (cywait(&cy->cy_ccb))
1074 		return (EFAULT);
1075 #define	phys(a)	((caddr_t)((int)(a)&~0xc0000000))
1076 	addr = phys(cyminfo[unit]->um_addr);
1077 	num = maxfree, start = NBPG*2;
1078 	while (num > 0) {
1079 		bs = num > btoc(CYMAXIO) ? btoc(CYMAXIO) : num;
1080 		error = cydwrite(cy, start, bs, addr);
1081 		if (error)
1082 			return (error);
1083 		start += bs, num -= bs;
1084 	}
1085 	cyweof(cy, addr);
1086 	cyweof(cy, addr);
1087 	uncache(&cy->cy_tpb);
1088 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1089 		return (EIO);
1090 	cyrewind(cy, addr);
1091 	return (0);
1092 }
1093 
1094 cydwrite(cy, pf, npf, addr)
1095 	register struct cy_softc *cy;
1096 	int pf, npf;
1097 	caddr_t addr;
1098 {
1099 
1100 	cy->cy_tpb.tpcmd = CY_WCOM;
1101 	cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
1102 	cy->cy_tpb.tpstatus = 0;
1103 	cy->cy_tpb.tpsize = htoms(npf*NBPG);
1104 	cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
1105 	cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
1106 	cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
1107 	cy->cy_ccb.cbgate = GATE_CLOSED;
1108 	CY_GO(addr);
1109 	if (cywait(&cy->cy_ccb))
1110 		return (EFAULT);
1111 	uncache(&cy->cy_tpb);
1112 	if (cy->cy_tpb.tpstatus&CYS_ERR)
1113 		return (EIO);
1114 	return (0);
1115 }
1116 
1117 cyweof(cy, addr)
1118 	register struct cy_softc *cy;
1119 	caddr_t addr;
1120 {
1121 
1122 	cy->cy_tpb.tpcmd = CY_WEOF;
1123 	cy->cy_tpb.tpcount = htoms(1);
1124 	cy->cy_ccb.cbgate = GATE_CLOSED;
1125 	CY_GO(addr);
1126 	(void) cywait(&cy->cy_ccb);
1127 }
1128 
1129 cyrewind(cy, addr)
1130 	register struct cy_softc *cy;
1131 	caddr_t addr;
1132 {
1133 
1134 	cy->cy_tpb.tpcmd = CY_REW;
1135 	cy->cy_tpb.tpcount = htoms(1);
1136 	cy->cy_ccb.cbgate = GATE_CLOSED;
1137 	CY_GO(addr);
1138 	(void) cywait(&cy->cy_ccb);
1139 }
1140 #endif
1141