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