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