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