xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 25675)
1 /*	cy.c	1.2	86/01/05	*/
2 
3 #include "cy.h"
4 #if NCY > 0
5 /*
6  * Cipher Tapemaster driver.
7  */
8 int	cydebug = 0;
9 
10 #include "../tahoe/mtpr.h"
11 #include "../tahoe/pte.h"
12 
13 #include "param.h"
14 #include "systm.h"
15 #include "vm.h"
16 #include "buf.h"
17 #include "file.h"
18 #include "dir.h"
19 #include "user.h"
20 #include "proc.h"
21 #include "signal.h"
22 #include "uio.h"
23 #include "ioctl.h"
24 #include "mtio.h"
25 #include "errno.h"
26 #include "cmap.h"
27 
28 #include "../tahoevba/vbavar.h"
29 #include "../tahoevba/cyreg.h"
30 
31 #define	MAXCONTROLLERS		4
32 #define MAX_BLOCKSIZE		(TBUFSIZ*NBPG)
33 #define NUM_UNIT		(NCY * 4)
34 
35 #define	TRUE			1
36 #define	FALSE			0
37 
38 #define	RETRY			1
39 #define EXTEND			2
40 #define	FATAL			3
41 
42 #define	MAINTAIN_POSITION	0
43 #define	DONT_MAINTAIN_POSITION	1
44 
45 #define	PROCESSED		0x80000000
46 #define	SLEEPING		0x80000000
47 #define	b_cmd	av_back		/* only unused word in request */
48 
49 extern	int cywrite_filemark(), cysearch_fm_forw(), cysearch_fm_back();
50 extern	int cy_space_forw(), cy_space_back(), cyrewind_tape_ta();
51 extern	int cyrewind_tape_unl(), cydrive_status(), cyrewind_tape_ov();
52 extern	int cyraw_read(), cyraw_write(), cybuf_read(), cybuf_write();
53 extern	int cywait_until_ready(), cywrite_0_fm(), cywrite_1_fm();
54 extern	int cywrite_2_fm(), cyno_op(), cywrite_eov();
55 
56 static	int (*cmd_tbl[15])() = {
57 	cywrite_filemark,
58 #define	DO_W_FM	0
59 	cysearch_fm_forw,
60 #define	DO_SFMF	1
61 	cysearch_fm_back,
62 #define	DO_SFMB	2
63 	cy_space_forw,
64 #define	DO_SPF	3
65 	cy_space_back,
66 #define	DO_SPB	4
67 	cyrewind_tape_ta,
68 #define	DO_RWTA	5
69 	cyrewind_tape_unl,
70 #define	DO_RWUN	6
71 	cydrive_status,
72 #define	DO_STAT	7
73 	cyrewind_tape_ov,
74 #define	DO_RWOV	8
75 	cywait_until_ready,
76 #define DO_WAIT 9
77 	cywrite_eov,
78 #define DO_WEOV	10
79 	cyraw_read,
80 #define DO_RRD	11
81 	cyraw_write,
82 #define DO_RWT	12
83 	cybuf_read,
84 #define DO_BRD	13
85 	cybuf_write
86 #define DO_BWT	14
87 };
88 
89 
90 extern	int cyprobe(), cyslave(), cyattach(), cydgo();
91 extern unsigned	cyminsize();
92 #if NCY > 0
93 extern	char	cy0utl[];
94 #endif
95 #if NCY > 1
96 extern	char	cy1utl[];
97 #endif
98 static	fmt_scp *scp_ptrs[MAXCONTROLLERS] =
99     { (fmt_scp *)0xc0000c06, (fmt_scp *)0xc0000c16, };
100 struct	vba_ctlr *cyminfo[NCY];
101 struct	vba_device *cydinfo[NUM_UNIT];
102 struct vba_driver cydriver = {
103     cyprobe, cyslave, cyattach, cydgo, (long *)scp_ptrs,
104     "yc", cydinfo, "cy", cyminfo
105 };
106 
107 /*
108  * Per-controller data structure.
109  */
110 typedef struct {
111 	struct pte	*map;
112 	char		*utl;
113 	int		(*interupt_path)();
114 	label_t		environ;  /* Environment variable for longjmps */
115 	struct buf	*my_request;
116 	struct buf	*wakeup_request;
117 	short		bs;	  /* buffer size */
118 	fmt_ccb		ccb;	  /* Channel control blocks */
119 	fmt_scb		scb;	  /* System configuration blocks */
120 	fmt_tpb		tpb;	  /* Tape parameter blocks */
121 	fmt_tpb		last;	  /* Tape parameter blocks */
122 	fmt_tpb		noop;	  /* Tape parameter blocks */
123 	long		rawbuf[MAX_BLOCKSIZE/sizeof(long)+1];
124 } ctlr_tab;
125 
126 extern	int cy_normal_path();
127 ctlr_tab ctlr_info[NCY] = {
128 #if NCY > 0
129 	{CY0map, cy0utl, cy_normal_path},
130 #endif
131 #if NCY > 1
132 	{CY1map, cy1utl, cy_normal_path},
133 #endif
134 };
135 
136 /*
137  * Per-drive information.
138  */
139 typedef struct {
140 	int		(*cleanup)();
141 	struct buf	u_queue;
142 	struct buf	rawbp;
143 	long		blkno;
144 	long		file_number;
145 	short		last_control;
146 	short		last_status;
147 	short		last_resid;
148 	unsigned long	bad_count;
149 	unsigned	control_proto: 16;
150 	unsigned	error_count  : 8;
151 	unsigned	open	     : 1;
152 	unsigned	eof	     : 1;
153 	unsigned	bot	     : 1;
154 	unsigned	eot	     : 1;
155 	char		*message;
156 } unit_tab;
157 unit_tab unit_info[NUM_UNIT];
158 
159 cyprobe(ctlr_vaddr)
160 	register caddr_t ctlr_vaddr;
161 {
162 	static int ctlr = -1;			/* XXX */
163 
164 	ctlr++;
165 	if (badcyaddr(ctlr_vaddr + 1) ||
166 	    !cy_init_controller(ctlr_vaddr, ctlr, 1))
167 		return (0);
168 	return (sizeof (caddr_t));		/* XXX */
169 }
170 
171 /*
172  * Initialize the controller after a controller reset or during autoconfigure.
173  * All of the system control blocks are initialized and the controller is
174  * asked to configure itself for later use.
175  *
176  * If the print value is true cy_first_TM_attention will anounce
177  * the type of controller we are (Tapemasher) and will print the size
178  * of the internal controller buffer.
179  */
180 cy_init_controller(ctlr_vaddr, ctlr, print)
181 	register caddr_t ctlr_vaddr;
182 	register int ctlr, print;
183 {
184 	register int *pte;
185 	register fmt_scp *SCP;
186 	register fmt_scb *SCB;
187 	register fmt_ccb *CCB;
188 	register ctlr_tab *ci;
189 
190 	/*
191 	 * Initialize the system configuration pointer.
192 	 */
193 	SCP = scp_ptrs[ctlr];
194 	/* make kernel writable */
195 	pte = (int *)vtopte((struct proc *)0, btop(SCP));
196 	*pte &= ~PG_PROT; *pte |= PG_KW;
197 	mtpr(TBIS, SCP);
198 	/* load the correct values in the scp */
199 	SCP->bus_size = _16_BITS;
200 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].scb, SCP->scb_ptr);
201 	/* put it back to read-only */
202 	*pte &= ~PG_PROT; *pte |= PG_KR;
203 	mtpr(TBIS, SCP);
204 
205 	/*
206 	 * Init system configuration block.
207 	 */
208 	SCB = &ctlr_info[ctlr].scb;
209 	SCB->fixed_value = 0x3;
210 	/* set pointer to the channel control block */
211 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].ccb, SCB->ccb_ptr);
212 
213 	/*
214 	 * Initialize the chanel control block.
215 	 */
216 	CCB = &ctlr_info[ctlr].ccb;
217 	CCB->ccw = CLEAR_INTERUPT;
218 	CCB->gate = GATE_OPEN;
219 	/* set pointer to the tape parameter block */
220 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].tpb, CCB->tpb_ptr);
221 
222 	/*
223 	 * Issue a noop cmd and get the internal buffer size for buffered i/o.
224 	 */
225 	ci = &ctlr_info[ctlr];
226 	/* set command to be CONFIGURE */
227 	ci->tpb.cmd = NO_OP;
228 	ci->tpb.control = CW_16bits;
229 	ci->ccb.gate = GATE_CLOSED;
230 	CY_ATTENTION(ctlr_vaddr);	/* execute! */
231 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
232 		printf("yc%d: time-out during init\n", ctlr);
233 		return (0);
234 	}
235 	ci->tpb.cmd = CONFIG;
236 	ci->tpb.control = CW_16bits;
237 	ci->ccb.gate = GATE_CLOSED;
238 	CY_ATTENTION(ctlr_vaddr);	/* execute! */
239 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
240 		cyprint_err("Tapemaster configuration failure",
241 		    0, ci->tpb.status);
242 		return (0);
243 	}
244 	uncache(&ci->tpb.count);
245 	ci->bs = MULTIBUS_SHORT(ci->tpb.count);
246 	if (print)
247 		printf("yc%d: %dKb buffer\n", ctlr, ci->bs/1024);
248 	return (1);
249 }
250 
251 /*
252  * Check to see if a drive is attached to a controller.
253  * Since we can only tell that a drive is there if a tape is loaded and
254  * the drive is placed online, we always indicate the slave is present.
255  */
256 cyslave(vi, addr)
257 	struct vba_device *vi;
258 	caddr_t addr;
259 {
260 
261 #ifdef lint
262 	vi = vi; addr = addr;
263 #endif
264 	return (1);
265 }
266 
267 cyattach(dev_info)
268 	struct vba_device *dev_info;
269 {
270 	register unit_tab *ui = &unit_info[dev_info->ui_unit];
271 	register struct buf *cq = &dev_info->ui_mi->um_tab;
272 	register struct buf *uq = cq->b_forw;
273 	register struct buf *start_queue = uq;
274 
275 	/* Add unit to controllers queue */
276 	if (cq->b_forw == NULL) {
277 		cq->b_forw = &ui->u_queue;
278 		ui->u_queue.b_forw = &ui->u_queue;
279 	} else {
280 		while(uq->b_forw != start_queue)
281 			uq = uq->b_forw;
282 		ui->u_queue.b_forw = start_queue;
283 		uq->b_forw = &ui->u_queue;
284 	}
285 	ui->cleanup = cyno_op;
286 	ui->last_status = 0;
287 	ui->last_control = 0;
288 	ui->file_number = 0;
289 	ui->bad_count = 0;
290 	ui->blkno = 0;
291 	ui->open = FALSE;
292 	ui->bot = TRUE;
293 	ui->eot = FALSE;
294 	ui->eof = FALSE;
295 	ui->message = NULL;
296 }
297 
298 cydgo()
299 {
300 
301 }
302 
303 /* macro to pack the unit number into Tapemaster format */
304 #define	UNIT(unit) \
305     (((cydinfo[unit]->ui_slave & 1) << 11) | \
306      ((cydinfo[unit]->ui_slave & 2) << 9) | \
307      ((cydinfo[unit]->ui_slave & 4) >> 2))
308 
309 cyopen(dev, flag)
310 	register int flag;
311 	register dev_t dev;
312 {
313 	register int unit = CYUNIT(dev);
314 	register unit_tab *ui;
315 
316 	if (unit >= NUM_UNIT || cydinfo[unit] == 0 ||
317 	    (ui = &unit_info[unit])->open)
318 		return (ENXIO);
319 	ui->control_proto = UNIT(unit) | CW_INTR | CW_16bits;
320 	ui->blkno = 0;
321 	ui->bad_count = 0;
322 	ui->eof = 0;
323 	ui->open = 1;
324 	cycmd(dev, DO_WAIT, 1);			/* wait for tape to rewind */
325 	if ((ui->last_status&CS_OL) == 0) {	/* not on-line */
326 		ui->open = 0;
327 		return (ENXIO);
328 	}
329 	if ((flag&FWRITE) && (ui->last_status&CS_P)) {
330 		uprintf("cy%d: write protected\n", unit);
331 		ui->open = 0;
332 		return (ENXIO);
333 	}
334 	if (ui->last_status&CS_LP) {
335 		ui->file_number = 0;
336 		ui->bot = 1;
337 		ui->eof = ui->eot = 0;
338 	}
339 	return (0);
340 }
341 
342 cyclose(dev, flag)
343 	register dev_t dev;
344 	register flag;
345 {
346 	register int unit = CYUNIT(dev);
347 	register unit_tab *ui = &unit_info[unit];
348 
349 	if (ui->last_status&CS_OL) {
350 		if ((flag&FWRITE) && (minor(dev)&T_NOREWIND))
351 			cycmd(dev, DO_WEOV, 1);
352 		else if ((minor(dev) & T_NOREWIND) == 0)
353 			cycmd(dev, DO_RWOV, 1);
354 	}
355 	if (ui->bad_count != 0) {
356 #ifdef notdef
357 		ui->bad_count *= 889;
358 		uprintf("cy%d: Warning - %d.%dcm of tape were used for recovering bad spots.\n", unit, ui->bad_count/100, ui->bad_count%100);
359 #endif
360 		ui->bad_count = 0;
361 	}
362 	ui->open = 0;
363 }
364 
365 /*
366  * Cycmd is used internally to implement all the ioctl functions.
367  * We duplicate the code in physio
368  * that is used for syncronizing the processes (sleep / wakeup) so
369  * that we can treat our internal command requests exactly like
370  * regular reads and writes.  They get put on the controller queue,
371  * start processes them and iodone is called to wake us up on completion.
372  *
373  * We don't call physio directly because it expects data to be moved
374  * and has a lot more overhead than we really need.
375  */
376 cycmd(dev, command, count)
377 	register dev_t dev;
378 	register int command, count;
379 {
380 	register int unit = CYUNIT(dev);
381 	register unit_tab *ui = &unit_info[unit];
382 	register struct buf *uq;
383 	int s;
384 
385 	s = spl3();
386 	while (ui->rawbp.b_flags & B_BUSY) {
387 		ui->rawbp.b_flags |= B_WANTED;
388 		sleep((caddr_t)&ui->rawbp, PRIBIO+1);
389 	}
390 	splx(s);
391 	/* load the request queue element */
392 	ui->rawbp.b_error = 0;
393 	ui->rawbp.b_dev = dev;
394 	ui->rawbp.b_cmd = (struct buf *)command;
395 	ui->rawbp.b_bcount = count;
396 	ui->rawbp.b_flags = B_PHYS | B_BUSY;
397 	s = spl3();
398 	uq = &ui->u_queue;
399 	ui->rawbp.av_forw = NULL;
400 	if (uq->av_forw == NULL)
401 		uq->av_forw = &ui->rawbp;
402 	else
403 		uq->av_back->av_forw = &ui->rawbp;
404 	uq->av_back = &ui->rawbp;
405 	cystart(cydinfo[unit]->ui_mi, &ui->rawbp, s);
406 
407 	/* wait for operation to complete */
408 	while ((ui->rawbp.b_flags&B_DONE) == 0)
409 		sleep((caddr_t)&ui->rawbp, PRIBIO);
410 	ui->rawbp.b_flags &= ~(B_PHYS | B_BUSY);
411 	if (ui->rawbp.b_flags & B_WANTED)
412 		wakeup((caddr_t)&ui->rawbp);
413 	return (geterror(&ui->rawbp));
414 }
415 
416 cystrategy(bp)
417 	register struct buf *bp;
418 {
419 	register int unit = CYUNIT(bp->b_dev);
420 	register unit_tab *ui = &unit_info[unit];
421 	register struct buf *uq;
422 	int s;
423 
424 	/* check the validity of the request */
425 	if (bp->b_bcount > MAX_BLOCKSIZE) {
426 		uprintf("cy%d: Maximum block size is %dk!\n",
427 		    unit, MAX_BLOCKSIZE/1024);
428 		bp->b_error = EIO;
429 		bp->b_resid = bp->b_bcount;
430 		bp->b_flags |= B_ERROR;
431 		iodone(bp);
432 		return;
433 	}
434 	vbasetup(bp, MAX_BLOCKSIZE);
435 	if (bp->b_flags & B_PHYS)
436 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_RRD : DO_RWT);
437 	else
438 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_BRD : DO_BWT);
439 	/* place request on queue and start it */
440 	s = spl3();
441 	uq = &ui->u_queue;
442 	bp->av_forw = NULL;
443 	if (uq->av_forw == NULL)
444 		uq->av_forw = bp;
445 	else
446 		uq->av_back->av_forw = bp;
447 	uq->av_back = bp;
448 	cystart(cydinfo[unit]->ui_mi, bp, s);
449 }
450 
451 struct	buf *cyget_next();
452 int	cystart_timeout();
453 /*
454  * Cystart is called once for every request that is placed on a
455  * controller's queue.  Start is responsible for fetching requests for
456  * a controller queue, starting the operation, and waiting for completion,
457  * and releasing the buf structure back to UNIX or cycmd, before fetching
458  * the next request.
459  *
460  * The controller's queue looks like this:
461  *
462  *                      +---------------------------------------+
463  *                      |                                       |
464  *      +-----------+   |   +-----------+        +-----------+  |
465  *      |  b_forw   |---+-->|  b_forw   |--~ ~-->|  b_forw   |--+
466  *      +-----------+       +-----------+        +-----------+
467  *      |  b_back   |       | ......... |        | ......... |
468  *      +-----------+       +-----------+        +-----------+
469  *      | ......... |      First unit queue     Last unit queue
470  *      +-----------+          element              element
471  * head of controller queue
472  *  (cyminfo[ctlr].um_tab)
473  */
474 cystart(vi, bp, s)
475 	register struct vba_ctlr *vi;
476 	register struct buf *bp;
477 {
478 	int unit = CYUNIT(bp->b_dev), ctlr = vi->um_ctlr;
479 	register struct buf *next, *cq = &vi->um_tab;
480 	register unit_tab *ui = &unit_info[unit];
481 	register ctlr_tab *ci = &ctlr_info[ctlr];
482 
483 	if (cq->b_active&SLEEPING) {
484 		untimeout(cystart_timeout, (caddr_t)cq);
485 		cystart_timeout(cq);
486 	}
487 	if (cq->b_active) {
488 		sleep((caddr_t)bp, PRIBIO-1);
489 		if (bp->b_flags&PROCESSED) {
490 			if (ui->message) {
491 				uprintf("cy%d: %s\n", unit, ui->message);
492 				ui->message = 0;
493 			}
494 			bp->b_flags &= ~PROCESSED;
495 			iodone(bp);
496 			return;
497 		}
498 	}
499 	cq->b_active = 1;
500 	splx(s);
501 	ci->my_request = bp;
502 	cydo_my_command(ctlr, cq, ci);
503 	if (ui->message) {
504 		uprintf("cy%d: %s\n", unit, ui->message);
505 		ui->message = 0;
506 	}
507 	bp->b_flags &= ~PROCESSED;
508 	iodone(bp);
509 	if ((next = cyget_next(cq)) != NULL)
510 		wakeup((caddr_t)next);
511 	else
512 		cq->b_active = 0;
513 }
514 
515 /*
516  * Cystart_timeout wakes up the start routine after it's 3
517  * second wait time is up or when a new command enters the queue.
518  * The timer is used to give up the processor while all drives
519  * on the queue are rewinding and we need to wait for them to be dome.
520  */
521 cystart_timeout(cq)
522 	register struct buf *cq;
523 {
524 
525 	cq->b_active &= ~SLEEPING;
526 	wakeup((caddr_t)cq);
527 }
528 
529 /*
530  * Cydo_my command scans the request queues once for a
531  * particular controller and calls the appropriate processing routine
532  * each time we find a request that can be started.
533  */
534 cydo_my_command(ctlr, cq, ci)
535 	register struct buf *cq;
536 	register ctlr_tab *ci;
537 {
538 	register struct buf *next;
539 
540 	while ((next = cyget_next(cq)) != NULL) {
541 		if (cq->b_forw->b_active&SLEEPING) {
542 			cq->b_active |= SLEEPING;
543 			timeout(cystart_timeout, (caddr_t)cq, 1*60);
544 			sleep((caddr_t)cq, PRIBIO);
545 			continue;
546 		}
547 		if (setjmp(&ctlr_info[ctlr].environ))
548 			cydone(cq);
549 		else {
550 			register int cmd = (int)next->b_cmd;
551 
552 			(*cmd_tbl[cmd])(next, cq);
553 		}
554 		if (next->b_flags & PROCESSED) {
555 			if (ci->my_request == next)
556 				break;
557 			wakeup((caddr_t)next);
558 		}
559 	}
560 }
561 
562 struct buf *
563 cyget_next(cq)
564 	register struct	buf *cq;
565 {
566 	register struct buf *bp, *uq, *next = NULL;
567 
568 	cq->b_forw = cq->b_forw->b_forw;
569 	uq = cq->b_forw;
570 	do {
571 		if ((bp = uq->av_forw) != NULL) {
572 			if ((uq->b_active&SLEEPING) == 0) {
573 				cq->b_forw = uq;
574 				return (bp);
575 			}
576 			next = uq;
577 		}
578 		uq = uq->b_forw;
579 	} while(uq != cq->b_forw);
580 	if (next != NULL) {
581 		cq->b_forw = next;
582 		return (next->av_forw);
583 	}
584 	return (NULL);
585 }
586 
587 /*
588  * Mark the current command on the controller's q completed and remove it.
589  */
590 cydone(cq)
591 	struct buf *cq;
592 {
593 	register struct buf *uq = cq->b_forw;
594 	int s;
595 
596 	uq->av_forw->b_flags |= PROCESSED;
597 	s = spl3();
598 	if ((uq->av_forw = uq->av_forw->av_forw) == NULL)
599 		uq->av_back = NULL;
600 	splx(s);
601 }
602 
603 /*
604  * The following routines implement the individual commands.
605  *
606  * Each command is responsible for a few things. 1) Each has to keep
607  * track of special cases that are related to the individual command and
608  * the previous commands sequence, 2) each is required to call iodone when
609  * command is actually finished, 3) it must use cyexecute to actually
610  * start the controller, and 4) they are required to keep the tape in
611  * a consistant state so that other commands will not be messed up.
612  */
613 
614 /*
615  * Read requests from the raw device.
616  * The special cases are:
617  *  1) we can not read after a write.  (writting defines end of file)
618  *  2) reading past end of file returns 0 bytes;
619  */
620 cyraw_read(bp, cq)
621 	register struct buf *bp;
622 	struct buf *cq;
623 {
624 	int unit = CYUNIT(bp->b_dev);
625 	register unit_tab *ui = &unit_info[unit];
626 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
627 	int addr, lock_flag, command;
628 
629 	if (ui->cleanup != cyno_op || ui->eof) {
630 		bp->b_resid = bp->b_bcount;
631 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
632 		cydone(cq);
633 		return;
634 	}
635 	if (bp->b_bcount > ci->bs)
636 		command = READ_TA, lock_flag = CW_LOCK;
637 	else
638 		command = READ_BU, lock_flag = 0;
639 	ui->blkno++;
640 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
641 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
642 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
643 	cydone(cq);
644 }
645 
646 /*
647  * Write requests from the raw device.
648  * The special cases are:
649  *  1) we don't allow writes after end of tape is reached.
650  */
651 cyraw_write(bp, cq)
652 	register struct buf *bp;
653 	struct buf *cq;
654 {
655 	int unit = CYUNIT(bp->b_dev);
656 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
657 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
658 	int addr, lock_flag, command;
659 
660 	if (ui->eot) {
661 		bp->b_resid = bp->b_bcount;
662 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
663 		longjmp(&ci->environ);
664 	}
665 	ui->cleanup = cywrite_2_fm;
666 	if (bp->b_bcount > ci->bs)
667 		command = WRIT_TA, lock_flag = CW_LOCK;
668 	else
669 		command = WRIT_BU, lock_flag = 0;
670 	ui->blkno++;
671 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
672 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
673 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
674 	cydone(cq);
675 }
676 
677 /*
678  * Write a filemark on a tape.
679  */
680 cywrite_filemark(bp, cq)
681 	register struct buf *bp;
682 	struct buf *cq;
683 {
684 	int unit = CYUNIT(bp->b_dev);
685 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
686 
687 	if (bp->b_bcount == 0) {
688 		cydone(cq);
689 		return;
690 	}
691 	bp->b_bcount--;
692 	if (ui->cleanup == cywrite_1_fm)
693 		ui->cleanup = cywrite_0_fm;
694 	if (ui->cleanup == cywrite_2_fm || ui->cleanup == cyno_op)
695 		ui->cleanup = cywrite_1_fm;
696 	ui->file_number++;
697 	ui->eof = 1;
698 	ui->blkno = 0;
699 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 10, FALSE);
700 }
701 
702 /*
703 **	cysearch_fm_forw is the ioctl to search for a filemark in the
704 **  forward direction on tape.
705 **
706 **	Since only one device can be active on a given controller at any
707 **  given instant in time, we try to be nice and let onther devices  on
708 **  this controller be scheduled after we space over each record.  This will
709 **  at least give the apperance of overlapped operations on the controller.
710 **
711 **  The special cases are:
712 **  1) if the last command was a write the we can't search.
713 */
714 
715 cysearch_fm_forw(request, cq)
716 register struct buf	*request;
717 register struct buf	*cq;
718 {
719 	register int		unit = CYUNIT(request->b_dev);
720 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
721 	register int		ctlr = cydinfo[unit]->ui_ctlr;
722 	register ctlr_tab	*ci = &ctlr_info[ctlr];
723 
724 	if((ui->cleanup != cyno_op) || ui->eot) {
725 		request->b_resid = request->b_bcount;
726 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
727 		longjmp(&ci->environ);
728 	}
729 	if(request->b_bcount && !ui->eot) {
730 		if(!ui->eot) {
731 			ui->blkno++;
732 			cyexecute(SPAC_FM, (long)1, 0, 0, unit, 5, FALSE);
733 			if(!(ui->eof || ui->eot))
734 				return;
735 		}
736 		request->b_bcount--;
737 		ui->eof = FALSE;
738 		if(!ui->eot) {
739 			ui->file_number++;
740 			ui->blkno = 0;
741 			return;
742 		}
743 	}
744 	if(ui->eot) {
745 		request->b_resid = request->b_bcount;
746 		request->b_flags |= B_ERROR, request->b_error = ENXIO;
747 	}
748 	cydone(cq);
749 }
750 
751 
752 /*
753 **	cysearch_fm_back is the ioctl to search for a filemark in the
754 **  reverse direction on tape.
755 **
756 **	Since only one device can be active on a given controller at any
757 **  given instant in time, we try to be nice and let onther devices  on
758 **  this controller be scheduled after we space over each record.  This will
759 **  at least give the apperance of overlapped operations on the controller.
760 **
761 **  The special cases are:
762 **  1) can't search past begining of tape.
763 **  2) if the lasr operation was a write data then we need to add
764 **     an end of volume record before we start searching.
765 */
766 
767 cysearch_fm_back(request, cq)
768 register struct buf	*request;
769 register struct buf	*cq;
770 {
771 	register int		unit = CYUNIT(request->b_dev);
772 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
773 
774 	if(!ui->bot) {
775 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
776 		if(ui->blkno == 0)
777 			request->b_bcount++;
778 		ui->blkno = 0xffffffff;
779 		if(request->b_bcount && !ui->bot) {
780 			cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 6, FALSE);
781 			if(ui->eof) {
782 				ui->eof = FALSE;
783 				ui->file_number--;
784 				request->b_bcount--;
785 			}
786 			return;
787 		}
788 		if(ui->bot) {
789 			ui->file_number = 0;
790 			if(request->b_bcount) {
791 				request->b_resid = request->b_bcount;
792 				request->b_error = ENXIO;
793 				request->b_flags |= B_ERROR;
794 			}
795 		}
796 		else {
797 			request->b_cmd = (struct buf *)DO_SFMF;
798 			request->b_bcount = 1;
799 			return;
800 		}
801 	}
802 	ui->blkno = 0;
803 	ui->eof = FALSE;
804 	cydone(cq);
805 }
806 
807 
808 /*
809 **	cy_space_forw is used to search forward a given number of records on
810 **  tape.
811 **
812 **	Since only one device can be active on a given controller at any
813 **  given instant in time, we try to be nice and let onther devices  on
814 **  this controller be scheduled after we space over each record.  This will
815 **  at least give the apperance of overlapped operations on the controller.
816 **
817 **  The special cases are:
818 **  1) we can't space over a filemark.
819 **  2) if the last command was a write data or filemark we can't space forward.
820 */
821 
822 cy_space_forw(request, cq)
823 register struct buf	*request;
824 register struct buf	*cq;
825 {
826 	register int		unit = CYUNIT(request->b_dev);
827 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
828 	register int		ctlr = cydinfo[unit]->ui_ctlr;
829 	register ctlr_tab	*ci = &ctlr_info[ctlr];
830 
831 	if((ui->cleanup != cyno_op) || ui->eof) {
832 		request->b_resid = request->b_bcount;
833 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
834 		longjmp(&ci->environ);
835 	}
836 	if(request->b_bcount) {
837 		ui->blkno++;
838 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
839 		if(!ui->eof && request->b_bcount) {
840 			request->b_bcount--;
841 			return;
842 		}
843 	}
844 	if(ui->eof) {
845 		request->b_resid = request->b_bcount;
846 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
847 	}
848 	cydone(cq);
849 }
850 
851 
852 /*
853 **	Cy_space_back spaces backward a given number of records.
854 **
855 **	Since only one device can be active on a given controller at any
856 **  given instant in time, we try to be nice and let onther devices  on
857 **  this controller be scheduled after we space over each record.  This will
858 **  at least give the apperance of overlapped operations on the controller.
859 **
860 **  The special cases are:
861 **  1) we can't space over a filemark.
862 **  2) we can't space past the beginning of tape.
863 **  3) if the last operation was a write data then we need to add
864 **     an end of volume record before we start searching.
865 */
866 
867 cy_space_back(request, cq)
868 register struct buf	*request;
869 register struct buf	*cq;
870 {
871 	register int		unit = CYUNIT(request->b_dev);
872 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
873 
874 	if(!ui->bot) {
875 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
876 		if(request->b_bcount+1 && !ui->bot && !ui->eof) {
877 			request->b_bcount--;
878 			ui->blkno--;
879 			cyexecute(SPACE, (long)1, 0, CW_REV, unit, 15, FALSE);
880 			return;
881 		}
882 		if(!ui->bot) {
883 			request->b_bcount = 1;
884 			cy_space_forw(request, cq);
885 		}
886 		ui->eof = FALSE;
887 	}
888 	cydone(cq);
889 }
890 
891 /*
892  * Rewind tape and wait for completion.
893  * An overlapped rewind is issued and then we change the command type to
894  * a wait for ready ioctl.  Wait for ready contains the logic to poll
895  * without blocking anything in the system, until the drive becomes ready or
896  * drops off line whichever comes first.
897  */
898 /*ARGSUSED*/
899 cyrewind_tape_ta(bp, cq)
900 	struct buf *bp, *cq;
901 {
902 
903 	cyrewind_tape(bp, REWD_OV);
904 	bp->b_cmd = (struct buf *)DO_WAIT;
905 }
906 
907 /*
908  * Do an overlapped rewind and then unload the tape.
909  * This feature is handled by the individual tape drive and
910  * in some cases can not be performed.
911  */
912 cyrewind_tape_unl(bp, cq)
913 	struct buf *bp, *cq;
914 {
915 
916 	cyrewind_tape(bp, OFF_UNL);
917 	cydone(cq);
918 }
919 
920 /*
921  * Do an overlapped rewind.
922  */
923 cyrewind_tape_ov(bp, cq)
924 	struct buf *bp, *cq;
925 {
926 
927 	cyrewind_tape(bp, REWD_OV);
928 	cydone(cq);
929 }
930 
931 /*
932  * Common code for all rewind commands.
933  * The special cases are:
934  *  3) if the last operation was a write data then we need to add
935  *     an end of volume record before we start searching.
936  */
937 cyrewind_tape(bp, cmd)
938 	register struct buf *bp;
939 	int cmd;
940 {
941 	register int unit = CYUNIT(bp->b_dev);
942 	register unit_tab *ui = &unit_info[unit];
943 
944 	(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
945 	ui->blkno = 0;
946 	ui->eof = FALSE;
947 	ui->bot = TRUE;
948 	ui->eot = FALSE;
949 	ui->file_number = 0;
950 	bp->b_resid = 0;
951 	ui->cleanup = cyno_op;
952 	cyexecute(cmd, (long)0, 0, 0, unit, cmd == REWD_OV ? 10 : 10*60, 0);
953 }
954 
955 /*
956 **	Cywait_until_ready is used to wait for rewinds to complete.
957 **  We check the status and if the tape is still rewinding we re-enter ourself
958 **  on the activity queue to give other requests a chance to execute before we
959 **  check the status again.  One other thing is that we only want to  check
960 **  the status every five seconds.  so we set a timer for five seconds and
961 **  check the time left every time we enter this routine.  If there is still
962 **  time left then we simply reinsert ourself on the queue again and wait
963 **  until next time ..
964 */
965 cywait_until_ready(request, cq)
966 register struct buf	*request;
967 register struct buf	*cq;
968 {
969 	extern int		cywait_timeout();
970 	register int		unit = CYUNIT(request->b_dev);
971 	register unit_tab	*ui = &unit_info[unit];
972 
973 	cyexecute(DRIVE_S, (long)0, 0, 0, unit, 10, FALSE);
974 	if((!(ui->last_status & CS_OL)) || (ui->last_status & CS_RDY)) {
975 		cydone(cq);
976 		return;
977 	}
978 	cq->b_forw->b_active |= SLEEPING;
979 	timeout(cywait_timeout, (caddr_t)cq->b_forw, 2*60);
980 }
981 
982 /*
983  * Reset the timing flag for nice_wait after 3 seconds.
984  * This makes this drive eligible for scheduling again.
985  */
986 cywait_timeout(uq)
987 	struct buf *uq;
988 {
989 
990 	uq->b_active &= ~SLEEPING;
991 }
992 
993 /*
994  * Process a status ioctl request.
995  * It depends entirly on the interupt routines to load the last_XXX
996  * registers in unit_info[].
997  */
998 cydrive_status(bp, cq)
999 	struct buf *bp, *cq;
1000 {
1001 
1002 	cyexecute(DRIVE_S, (long)0, 0, 0, CYUNIT(bp->b_dev), 10, FALSE);
1003 	cydone(cq);
1004 }
1005 
1006 /*
1007 **	cybuf_read handles the read requests from the block device.
1008 **
1009 **  The special cases are:
1010 **  1)	we can not read after a write.  (writting defines end of file)
1011 **  2)  reading past end of file returns 0 bytes;
1012 **  3)  if we are mispositioned we have to seek to the correct block.
1013 **  4)  we can hit end of tape while seeking.
1014 **  5)  we want to be nice to other processes while seeking so we
1015 **  	break the request up into smaller requests.
1016 **  6)  returns error if the block was larger than requested.
1017 */
1018 cybuf_read(request, cq)
1019 register struct buf	*request;
1020 register struct buf	*cq;
1021 {
1022 	register int		unit = CYUNIT(request->b_dev);
1023 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1024 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1025 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1026 	register int		addr, command, bus_lock;
1027 
1028 	cydebug = 1;
1029 	if(cyseek(request, cq)) {
1030 		if(ui->cleanup != cyno_op) {
1031 			clrbuf(request);
1032 			longjmp(&ci->environ);
1033 		}
1034 		if(request->b_bcount > ci->bs)
1035 			command = READ_TA, bus_lock = CW_LOCK;
1036 		else
1037 			command = READ_BU, bus_lock = 0;
1038 		ui->blkno++;
1039 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
1040 		    ci->utl);
1041 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,8,FALSE);
1042 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
1043 		cydone(cq);
1044 	}
1045 }
1046 
1047 
1048 /*
1049 **	cybuf_write handles the write requests from the block device.
1050 **
1051 **  The special cases are:
1052 **  1)  if we are mispositioned we have to seek to the correct block.
1053 **  2)  we can hit end of tape while seeking.
1054 **  3)  we want to be nice to other processes while seeking so we
1055 **  	break the request up into smaller requests.
1056 **  4) we don't allow writes after end of tape is reached.
1057 */
1058 
1059 cybuf_write(request, cq)
1060 register struct buf	*request;
1061 register struct buf	*cq;
1062 {
1063 	register int		unit = CYUNIT(request->b_dev);
1064 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1065 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1066 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1067 	register int		addr, command, bus_lock;
1068 
1069 	if(ui->eot && (request->b_blkno >= ui->blkno)) {
1070 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
1071 		request->b_resid = request->b_bcount;
1072 		longjmp(&ci->environ);
1073 	}
1074 	if(cyseek(request, cq)) {
1075 		ui->cleanup = cywrite_2_fm;
1076 		ui->blkno++;
1077 		if(request->b_bcount > ci->bs)
1078 			command = WRIT_TA, bus_lock = CW_LOCK;
1079 		else
1080 			command = WRIT_BU, bus_lock = 0;
1081 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
1082 		    ci->utl);
1083 		load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
1084 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,5,FALSE);
1085 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
1086 		cydone(cq);
1087 	}
1088 }
1089 
1090 
1091 /*
1092 **	cyseek is used by the block device to position the tape correctly
1093 **  before each read or write request.
1094 **
1095 **  The special cases are:
1096 **  1)  we can hit end of tape while seeking.
1097 **  2)  we want to be nice to other processes while seeking so we
1098 **  	break the request up into smaller requests.
1099 */
1100 cyseek(request, cq)
1101 register struct buf	*request;
1102 register struct buf	*cq;
1103 {
1104 	register int		unit = CYUNIT(request->b_dev);
1105 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1106 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1107 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1108 
1109 #ifdef lint
1110 	cq = cq;
1111 #endif
1112 	if(request->b_blkno < ui->blkno) {
1113 		register int	count;
1114 
1115 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
1116 		count = ((request->b_blkno+1) == ui->blkno) ? 2 : 1;
1117 		ui->blkno -= count;
1118 		cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 10, FALSE);
1119 		if(!ui->eof)
1120 			return FALSE;
1121 		ui->eof = FALSE;
1122 		request->b_blkno = ui->blkno + 1;
1123 	}
1124 	if(request->b_blkno > ui->blkno) {
1125 		if((ui->cleanup != cyno_op) || ui->eof || ui->eot) {
1126 			request->b_resid = request->b_bcount;
1127 			request->b_error = ENXIO, request->b_flags |= B_ERROR;
1128 			longjmp(&ci->environ);
1129 		}
1130 		ui->blkno++;
1131 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
1132 		return FALSE;
1133 	}
1134 	return TRUE;
1135 }
1136 
1137 
1138 /*
1139 */
1140 
1141 cywrite_eov(request, cq)
1142 register struct buf	*request;
1143 register struct buf	*cq;
1144 {
1145 	extern int		cyno_op();
1146 	register int		unit = CYUNIT(request->b_dev);
1147 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
1148 
1149 	if(ui->cleanup != cyno_op) {
1150 		(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
1151 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
1152 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
1153 		unit_info[unit].cleanup = cyno_op;
1154 		ui->blkno = 0;
1155 	}
1156 	cydone(cq);
1157 }
1158 
1159 
1160 /*
1161 **	Do nothing
1162 */
1163 /*ARGSUSED*/
1164 cyno_op(unit, action)
1165 int	unit, action;
1166 {
1167 }
1168 
1169 
1170 /*
1171 **	Write 0 file marks to tape
1172 */
1173 /*ARGSUSED*/
1174 cywrite_0_fm(unit, action)
1175 int	unit, action;
1176 {
1177 	unit_info[unit].cleanup = cyno_op;
1178 }
1179 
1180 
1181 /*
1182 **	Write 1 file mark to tape
1183 */
1184 
1185 cywrite_1_fm(unit, action)
1186 int	unit, action;
1187 {
1188 
1189 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1190 	if(action == MAINTAIN_POSITION) {
1191 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
1192 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
1193 	}
1194 	unit_info[unit].cleanup = cyno_op;
1195 }
1196 
1197 
1198 /*
1199 **	Write 2 file marks to tape
1200 */
1201 
1202 cywrite_2_fm(unit, action)
1203 int	unit, action;
1204 {
1205 
1206 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1207 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
1208 	if(action == MAINTAIN_POSITION) {
1209 		cyexecute(SPACE, (long)3, 0, CW_REV, unit, 10, FALSE);
1210 		cyexecute(SPACE, (long)1, 0, 0, unit, 2, FALSE);
1211 	}
1212 	unit_info[unit].cleanup = cyno_op;
1213 }
1214 
1215 
1216 extern	int cytimeout();
1217 extern	int cy_normal_path();
1218 /*
1219 **	Cyexecute is used to start all commands to the controller.  We
1220 **  do all common code here before starting.
1221 */
1222 
1223 cyexecute(command, count, addr, control_flags, unit, time, interupt_routine)
1224 	register int command;
1225 	long count;
1226 	int addr, control_flags, unit, time, interupt_routine;
1227 {
1228 	register int		priority;
1229 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1230 	register unit_tab	*ui = &unit_info[unit];
1231 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1232 	register struct buf	*request = ui->u_queue.av_forw;
1233 
1234 	ci->tpb.cmd = command;
1235 	ci->tpb.control = ui->control_proto | control_flags;
1236 	ci->tpb.status = ci->tpb.count = (short)0;
1237 	load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
1238 	switch(command) {
1239 		case READ_BU:
1240 		case READ_TA:
1241 		case WRIT_BU:
1242 		case WRIT_TA:
1243 			ci->tpb.size = MULTIBUS_SHORT((short)count);
1244 			ci->tpb.rec_over = (short)0;
1245 			break;
1246 		default:
1247 			ci->tpb.size = (short)0;
1248 			ci->tpb.rec_over = MULTIBUS_SHORT((short)count);
1249 			break;
1250 	}
1251 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1252 	if(!interupt_routine)
1253 		ci->last = ci->tpb;
1254 	/*
1255 	gag! but it the last possible moment to wait
1256 	for this controller to get out of it's own way.....
1257 	*/
1258 	uncache(&ci->ccb.gate);
1259 	while(ci->ccb.gate == GATE_CLOSED)
1260 		uncache(&ci->ccb.gate);
1261 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1262 	ci->ccb.ccw = NORMAL_INTERUPT;
1263 	ci->ccb.gate = GATE_CLOSED;
1264 	if(!interupt_routine)
1265 		ci->interupt_path = cy_normal_path;
1266 	timeout(cytimeout, (caddr_t)ctlr, time*60);
1267 	priority = spl3();
1268 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1269 	if(!interupt_routine) {
1270 		sleep((caddr_t)ci, PRIBIO+3);
1271 		splx(priority);
1272 		if(request->b_flags & B_ERROR) {
1273 			if((command == READ_BU) || (command == READ_TA) ||
1274 			    (command == WRIT_BU) || (command == WRIT_TA))
1275 				vbadone(request, (caddr_t)ci->rawbuf,
1276 				     (long *)ci->map,ci->utl);
1277 			longjmp(&ci->environ);
1278 		}
1279 		return;
1280 	}
1281 	splx(priority);
1282 }
1283 
1284 
1285 /*
1286 **	cytimeout is the interupt timeout routine.  We assume that a
1287 **  particular command has gone astray, so we completely reset the controller,
1288 **  and call the interupt routine to help us clean up.  Before the interupt
1289 **  routine is called we jam a controller timeout value in the status register
1290 **  to fake out the calling routines.
1291 */
1292 
1293 cytimeout(ctlr)
1294 register int	ctlr;
1295 {
1296 	register int	priority = spl3();
1297 	register char	*ctlr_vaddr = cyminfo[ctlr]->um_addr;
1298 	register int	tmp_stat;
1299 
1300 	uncache(&ctlr_info[ctlr].tpb.status);
1301 	tmp_stat = ctlr_info[ctlr].tpb.status;
1302 	CY_RESET(ctlr_vaddr);
1303 	cy_init_controller(ctlr_vaddr, ctlr, 0);
1304 	splx(priority);
1305 	ctlr_info[ctlr].tpb = ctlr_info[ctlr].last;
1306 	ctlr_info[ctlr].tpb.status = (tmp_stat & ~CS_ERm) | CS_OL | ER_TIMOUT;
1307 	cyintr(ctlr);
1308 }
1309 
1310 /*
1311 **	Cyintr is the interupt routine for the Tapemaster controller.
1312 **
1313 **	Due to controller problems, the first thing we have to do is turn
1314 **  off the Tapemaster interupting mechanism.  If we don't we will be flooded
1315 **  with bogus interupts and the system will spend all it's time processing
1316 **  them.  To Turn the interupts off we issue a NOOP command with the 'turn
1317 **  off interupts' code in the ccb.
1318 **
1319 **	  take note that since this command TURNS OFF the interupts it
1320 **	  itself CANNOT interupt...  This means that polling must be done
1321 **	  at sometime to make sure that tis command is completed.  The polling
1322 **	  is done before the next command is issued to reduce polling (halting
1323 **	  UNIX) time.
1324 **
1325 **	After we turn off interupts we uncache all the values in the tpb
1326 **  and call the correct processing routine.  This routine can be for normal
1327 **  interupts or for interupts generated during a retry operation.
1328 */
1329 
1330 cyintr(ctlr)
1331 register int ctlr;
1332 {
1333 	extern int		cytimeout();
1334 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1335 
1336 	untimeout(cytimeout, (caddr_t)ctlr);
1337 	/* turn off interupts for the stupid controller */
1338 	ci->ccb.ccw = CLEAR_INTERUPT;
1339 	ci->noop.cmd = NO_OP;
1340 	ci->noop.control = (short)0;
1341 	load_mbus_addr((caddr_t)&ci->noop, ci->ccb.tpb_ptr);
1342 	ci->ccb.gate = GATE_CLOSED;
1343 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1344 	uncache_tpb(ci);
1345 	(*ci->interupt_path)(ctlr);
1346 }
1347 
1348 
1349 /*
1350 **	This is the portion of the interupt routine that processes all
1351 **  normal cases i.e. non retry cases.   We check the operations status
1352 **  if it is retryable we set the interupt path to the retry routines and
1353 **  start the backward spaceing.  when the spacing is done the retry logic
1354 **  will be called and this routine will be skipped entirely.
1355 **
1356 **	If the command is ok or not retryable we set the status accordingly
1357 **  and wakeup cyexecute to continue processing.
1358 */
1359 
1360 cy_normal_path(ctlr)
1361 register int ctlr;
1362 {
1363 	extern int		cy_retry_path();
1364 	extern int		cy_extended_gap_path();
1365 	register int		error;
1366 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1367 	register struct buf	*uq = cq->b_forw;
1368 	register struct buf	*request = uq->av_forw;
1369 	register int		unit = CYUNIT(request->b_dev);
1370 	register unit_tab	*ui = &unit_info[unit];
1371 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1372 
1373 	if (error = cydecode_error(unit, ci->tpb.status)) {
1374 		if(error != FATAL) {
1375 			if (error == RETRY)
1376 				ci->interupt_path = cy_retry_path;
1377 			else
1378 				ci->interupt_path = cy_extended_gap_path;
1379 			cyexecute(SPACE, (long)2, 0, CW_REV, unit, 5, TRUE);
1380 			return;
1381 		}
1382 	}
1383 	request->b_resid=request->b_bcount-MULTIBUS_SHORT(ci->tpb.count);
1384 	ui->error_count = 0;
1385 	ui->last_resid = request->b_resid;
1386 	ui->last_status = ci->tpb.status;
1387 	ui->last_control = ci->tpb.control;
1388 	if (error == FATAL)
1389 		request->b_flags |= B_ERROR, request->b_error = EIO;
1390 	wakeup((caddr_t)ci);
1391 }
1392 
1393 
1394 /*
1395 **	Cy_retry_path finishes up the retry sequence for the tape.
1396 ** If we were going in the reverse direction it means that we have to
1397 ** space forward to correctly position ourselfs in back of the tape gap
1398 ** instead of in front of it.  If we were going forward it means that
1399 ** we are positioned correctly and we can actually restart the instruction
1400 ** that failed before.
1401 */
1402 
1403 cy_retry_path(ctlr)
1404 register int	ctlr;
1405 {
1406 	extern int		cy_do_again_path();
1407 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1408 	register struct buf	*uq = cq->b_forw;
1409 	register struct buf	*request = uq->av_forw;
1410 	register int		unit = CYUNIT(request->b_dev);
1411 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1412 
1413 	if(!(ci->tpb.status & CS_OL)) {
1414 		ci->interupt_path = cy_normal_path;
1415 		cy_normal_path(ctlr);
1416 		return;
1417 	}
1418 	if(ci->tpb.control & CW_REV) {
1419 		if(!(ci->tpb.status & CS_LP)) {
1420 			ci->interupt_path = cy_do_again_path;
1421 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
1422 			return;
1423 		}
1424 		cy_do_again_path(ctlr);
1425 	}
1426 }
1427 
1428 
1429 /*
1430 **
1431 */
1432 
1433 cy_extended_gap_path(ctlr)
1434 register int	ctlr;
1435 {
1436 	extern int		cy_do_again_path();
1437 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1438 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
1439 	register struct buf	*uq = cq->b_forw;
1440 	register struct buf	*request = uq->av_forw;
1441 	register int		unit = CYUNIT(request->b_dev);
1442 
1443 	if(!(ci->tpb.status & CS_OL)) {
1444 		ci->interupt_path = cy_normal_path;
1445 		cy_normal_path(ctlr);
1446 		return;
1447 	}
1448 	if(ci->tpb.control & CW_REV) {
1449 		if(!(ci->tpb.status & CS_LP)) {
1450 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
1451 			return;
1452 		}
1453 	}
1454 	ci->interupt_path = cy_do_again_path;
1455 	cyexecute(ERASE_F, (long)unit_info[unit].error_count, 0, 0,
1456 	    unit, 5, TRUE);
1457 }
1458 
1459 
1460 /*
1461 **
1462 */
1463 
1464 cy_do_again_path(ctlr)
1465 register int	ctlr;
1466 {
1467 	extern int		cy_normal_path();
1468 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1469 
1470 	if(!(ci->tpb.status & CS_OL)) {
1471 		ci->interupt_path = cy_normal_path;
1472 		cy_normal_path(ctlr);
1473 		return;
1474 	}
1475 	ci->tpb = ci->last;
1476 	uncache(&ci->ccb.gate);
1477 	while(ci->ccb.gate == GATE_CLOSED)
1478 		uncache(&ci->ccb.gate);
1479 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1480 	ci->ccb.ccw = NORMAL_INTERUPT;
1481 	ci->ccb.gate = GATE_CLOSED;
1482 	ci->interupt_path = cy_normal_path;
1483 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1484 }
1485 
1486 
1487 /*
1488 **	for each longword in the tpb we call uncache to  purge it from
1489 **  the cache.  This is done so that we can correctly access tpb data
1490 **  that was placed there by the controller.
1491 */
1492 
1493 uncache_tpb(ci)
1494 ctlr_tab	*ci;
1495 {
1496 	register long	*ptr = (long *)&ci->tpb;
1497 	register int	i;
1498 
1499 	for(i=0; i<((sizeof(fmt_tpb)+sizeof(long)-1)/sizeof(long)); i++)
1500 		uncache(ptr++);
1501 }
1502 
1503 
1504 /*
1505 **	Cyprint_error is the common printing routine for all messages
1506 **  that need to print the tape status along with it.  This is so we
1507 **  we can save space, have consistant messages, and we can send the messages
1508 **  to the correct places.
1509 */
1510 
1511 cyprint_err(message, unit, status)
1512 register char	*message;
1513 register int	unit, status;
1514 {
1515 	status &= 0xffff;
1516 	printf("cy%d: %s!   Status = %x\n", unit, message, status);
1517 }
1518 
1519 /*
1520 **	Decode the error to determine whether the previous command was
1521 **  ok, retryable, or fatal and return the value.  If it was a hardware
1522 **  problem we print the message to the console, otherwise we print it
1523 **  to the user's terminal later when execute returns.
1524 */
1525 
1526 cydecode_error(unit, status)
1527 register int	unit,	status;
1528 {
1529 	register unit_tab	*ui = &unit_info[unit];
1530 	register ctlr_tab	*ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
1531 
1532 	if(!(status & CS_OL) && (ci->tpb.cmd != OFF_UNL)) {
1533 		ui->message = "Drive is not on-line";
1534 		cyprint_err(ui->message, unit, status);
1535 		return FATAL;
1536 	}
1537 	ui->bot = ((status & CS_LP) != 0);
1538 	ui->eof = ((status & CS_FM) != 0);
1539 	switch(status & CS_ERm) {
1540 	case ER_EOT:
1541 		if(ci->tpb.control & CW_REV) {
1542 			ui->bot = TRUE;
1543 			ui->eot = FALSE;
1544 		}
1545 		else if(!ui->eot){
1546 			ui->message = "End of tape";
1547 			ui->bot = FALSE;
1548 			ui->eot = TRUE;
1549 		}
1550 	case 0 :
1551 	case ER_FM:
1552 	case ER_NOSTRM:
1553 		return	0;
1554 	case ER_TIMOUT:
1555 	case ER_TIMOUT1:
1556 	case ER_TIMOUT2:
1557 	case ER_TIMOUT3:
1558 	case ER_TIMOUT4:
1559 		ui->message = "Drive timed out during transfer";
1560 		cyprint_err(ui->message, unit, status);
1561 		return FATAL;
1562 	case ER_NEX:
1563 		ui->message =
1564 		    "Controller referenced non-existant system memory";
1565 		cyprint_err(ui->message, unit, status);
1566 		return FATAL;
1567 	case ER_DIAG:
1568 	case ER_JUMPER:
1569 		ui->message = "Controller diagnostics failed";
1570 		cyprint_err(ui->message, unit, status);
1571 		return FATAL;
1572 	case ER_STROBE:
1573 		if (ci->tpb.cmd == READ_BU) {
1574 			ci->last.cmd = READ_TA;
1575 			return RETRY;
1576 		}
1577 		if(ci->tpb.cmd == READ_TA)
1578 			return 0;
1579 		ui->message = "Unsatisfactory media found";
1580 		return	FATAL;
1581 	case ER_FIFO:
1582 	case ER_NOTRDY:
1583 		ui->error_count = 1;
1584 		return RETRY;
1585 	case ER_PROT:
1586 		ui->message = "Tape is write protected";
1587 		return FATAL;
1588 	case ER_CHKSUM:
1589 		ui->message = "Checksum error in controller proms";
1590 		cyprint_err(ui->message, unit, status);
1591 		return FATAL;
1592 	case ER_HARD:
1593 		ui->error_count++;
1594 		if((ci->tpb.cmd == WRIT_TA) ||
1595 		    (ci->tpb.cmd == WRIT_BU) ||
1596 		    (ci->tpb.cmd == WRIT_FM)) {
1597 			ui->bad_count++;
1598 			return EXTEND;
1599 		}
1600 		ui->message = "Unrecoverable media error during read";
1601 		return FATAL;
1602 	case ER_PARITY:
1603 		if(++ui->error_count < 8)
1604 			return	RETRY;
1605 		ui->message = "Unrecoverable tape parity error";
1606 		return FATAL;
1607 	case ER_BLANK:
1608 		ui->message="Blank tape found (data expected)";
1609 		return FATAL;
1610 	case ER_HDWERR:
1611 	default:
1612 		ui->message = "Unrecoverble hardware error";
1613 		cyprint_err(ui->message, unit, status);
1614 		return FATAL;
1615 	}
1616 }
1617 
1618 cyread(dev, uio)
1619 	dev_t dev;
1620 	struct uio *uio;
1621 {
1622 	unit_tab *ui = &unit_info[CYUNIT(dev)];
1623 
1624 	return (physio(cystrategy, &ui->rawbp, dev, B_READ, cyminsize, uio));
1625 }
1626 
1627 
1628 cywrite(dev, uio)
1629 	dev_t dev;
1630 	struct uio *uio;
1631 {
1632 	unit_tab *ui = &unit_info[CYUNIT(dev)];
1633 
1634 	return (physio(cystrategy,&ui->rawbp, dev, B_WRITE, cyminsize, uio));
1635 }
1636 
1637 /*ARGSUSED*/
1638 cyioctl(dev, cmd, data, flag)
1639 	dev_t dev;
1640 	caddr_t data;
1641 {
1642 
1643 	switch (cmd) {
1644 
1645 	case MTIOCTOP: {
1646 		struct mtop *mp = (struct mtop *)data;
1647 
1648 		if (mp->mt_op <= DO_WAIT)
1649 			return (cycmd(dev, (int)mp->mt_op, (int)mp->mt_count));
1650 		return (EIO);
1651 	}
1652 
1653 	case MTIOCGET: {
1654 		register unit_tab *ui = &unit_info[CYUNIT(dev)];
1655 		register struct mtget *mp = (struct mtget *)data;
1656 
1657 		mp->mt_type = MT_ISCY;
1658 		mp->mt_dsreg = ui->last_control;
1659 		mp->mt_erreg = ui->last_status;
1660 		mp->mt_resid = ui->last_resid;
1661 		mp->mt_fileno = ui->file_number;
1662 		mp->mt_blkno = ui->blkno;
1663 		cycmd(dev, DO_STAT, 1);
1664 		break;
1665 	}
1666 
1667 	default:
1668 		return (ENXIO);
1669 	}
1670 	return (0);
1671 }
1672 
1673 /*
1674  * Dump routine.
1675  */
1676 cydump(dev)
1677 	dev_t dev;
1678 {
1679 	register int		unit = CYUNIT(dev);
1680 	register int		ctlr = cydinfo[unit]->ui_ctlr;
1681 	register unit_tab	*ui = &unit_info[unit];
1682 	register ctlr_tab	*ci = &ctlr_info[ctlr];
1683 	register int		blk_siz;
1684 	register int		num = maxfree;
1685 	register int		start = 0x800;
1686 
1687 	if ((unit >= NCY) || cydinfo[unit])
1688 		return(ENXIO);
1689 	ui->control_proto = CW_LOCK | CW_25ips | CW_16bits;
1690 	if (cywait(&ci->ccb))
1691 		return(EFAULT);
1692 	while (num > 0) {
1693 		blk_siz = num > TBUFSIZ ? TBUFSIZ : num;
1694 		bcopy((caddr_t)(start*NBPG), (caddr_t)ci->rawbuf,
1695 		    (unsigned)(blk_siz*NBPG));
1696 		ci->tpb.cmd = WRIT_TA;
1697 		ci->tpb.control = ui->control_proto;
1698 		ci->tpb.status = 0;
1699 		ci->tpb.size = MULTIBUS_SHORT(blk_siz*NBPG);
1700 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1701 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1702 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1703 		ci->ccb.gate = GATE_CLOSED;
1704 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
1705 		start += blk_siz;
1706 		num -= blk_siz;
1707 		if (cywait(&ci->ccb))
1708 			return(EFAULT);
1709 		uncache(&ci->tpb);
1710 		if (ci->tpb.status&CS_ERm)		/* error */
1711 			return (EIO);
1712 	}
1713 	for(num=0; num<2; num++) {
1714 		ci->tpb.cmd = WRIT_FM;
1715 		ci->tpb.control = ui->control_proto;
1716 		ci->tpb.status = ci->tpb.size = 0;
1717 		ci->tpb.count = MULTIBUS_SHORT(1);
1718 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1719 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1720 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1721 		ci->ccb.gate = GATE_CLOSED;
1722 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
1723 		if (cywait(&ci->ccb))
1724 			return(EFAULT);
1725 		uncache(&ci->tpb);
1726 		if (ci->tpb.status&CS_ERm)		/* error */
1727 			return (EIO);
1728 	}
1729 	ci->tpb.cmd = REWD_OV;
1730 	ci->tpb.control = ui->control_proto;
1731 	ci->tpb.status = ci->tpb.size = 0;
1732 	ci->tpb.count = MULTIBUS_SHORT(1);
1733 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
1734 	load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
1735 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
1736 	ci->ccb.gate = GATE_CLOSED;
1737 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
1738 	if (cywait(&ci->ccb))
1739 		return EFAULT;
1740 	uncache(&ci->tpb);
1741 	return 0;
1742 }
1743 
1744 /*
1745  * Poll until the controller is ready.
1746  */
1747 cywait(cp)
1748 	register fmt_ccb *cp;
1749 {
1750 	register int i = 5000;
1751 
1752 	uncache(&cp->gate);
1753 	while (i-- > 0 && cp->gate == GATE_CLOSED) {
1754 		DELAY(1000);
1755 		uncache(&cp->gate);
1756 	}
1757 	return (i <= 0);
1758 }
1759 
1760 /*
1761  * Load a 20 bit pointer into the i/o registers.
1762  */
1763 load_mbus_addr(in, out)
1764 	caddr_t in;
1765 	short *out;
1766 {
1767 	register int tmp_in = (int)in;
1768 	register char *out_ptr = (char *)out;
1769 
1770 	*out_ptr++ = (char)(tmp_in & 0xff);
1771 	*out_ptr++ = (char)((tmp_in >> 8) & 0xff);
1772 	*out_ptr++ = (char)0;
1773 	*out_ptr++ = (char)((tmp_in & 0xf0000) >> 12);
1774 }
1775 
1776 /*
1777 **	CYMINSIZE s supposed to adjust the buffer size for any raw i/o.
1778 **  since tapes can not read  the tail end of partial blocks we ignore
1779 **  this request and strategy will return an appropriate error message later.
1780 **
1781 **	If this is not done UNIX will lose data that is on the tape.
1782 */
1783 unsigned
1784 cyminsize(bp)
1785 	struct buf *bp;
1786 {
1787 	if (bp->b_bcount > MAX_BLOCKSIZE)
1788 		bp->b_bcount = MAX_BLOCKSIZE;
1789 }
1790 
1791 /*
1792  * Unconditionally reset all controllers to their initial state.
1793  */
1794 cyreset(vba)
1795 	int vba;
1796 {
1797 	register caddr_t addr;
1798 	register int ctlr;
1799 
1800 	for (ctlr = 0; ctlr < NCY; ctlr++)
1801 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
1802 			addr = cyminfo[ctlr]->um_addr;
1803 			CY_RESET(addr);
1804 			if (!cy_init_controller(addr, ctlr, 0)) {
1805 				printf("cy%d: reset failed\n", ctlr);
1806 				cyminfo[ctlr] = NULL;
1807 			}
1808 		}
1809 }
1810 #endif
1811