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