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