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