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