xref: /csrg-svn/sys/tahoe/vba/cy.c (revision 25857)
1*25857Ssam /*	cy.c	1.3	86/01/12	*/
224000Ssam 
324000Ssam #include "cy.h"
425675Ssam #if NCY > 0
524000Ssam /*
625675Ssam  * Cipher Tapemaster driver.
724000Ssam  */
825675Ssam int	cydebug = 0;
924000Ssam 
1025675Ssam #include "../tahoe/mtpr.h"
1125675Ssam #include "../tahoe/pte.h"
1224000Ssam 
1325675Ssam #include "param.h"
1425675Ssam #include "systm.h"
1525675Ssam #include "vm.h"
1625675Ssam #include "buf.h"
1725675Ssam #include "file.h"
1825675Ssam #include "dir.h"
1925675Ssam #include "user.h"
2025675Ssam #include "proc.h"
2125675Ssam #include "signal.h"
2225675Ssam #include "uio.h"
2325675Ssam #include "ioctl.h"
2425675Ssam #include "mtio.h"
2525675Ssam #include "errno.h"
2625675Ssam #include "cmap.h"
2724000Ssam 
2825675Ssam #include "../tahoevba/vbavar.h"
2925675Ssam #include "../tahoevba/cyreg.h"
3024000Ssam 
3125675Ssam #define	MAXCONTROLLERS		4
3225675Ssam #define MAX_BLOCKSIZE		(TBUFSIZ*NBPG)
3325675Ssam #define NUM_UNIT		(NCY * 4)
3424000Ssam 
3525675Ssam #define	TRUE			1
3625675Ssam #define	FALSE			0
3724000Ssam 
3825675Ssam #define	RETRY			1
3925675Ssam #define EXTEND			2
4025675Ssam #define	FATAL			3
4124000Ssam 
4225675Ssam #define	MAINTAIN_POSITION	0
4325675Ssam #define	DONT_MAINTAIN_POSITION	1
4424000Ssam 
4525675Ssam #define	PROCESSED		0x80000000
4625675Ssam #define	SLEEPING		0x80000000
4725675Ssam #define	b_cmd	av_back		/* only unused word in request */
4824000Ssam 
4925675Ssam extern	int cywrite_filemark(), cysearch_fm_forw(), cysearch_fm_back();
5025675Ssam extern	int cy_space_forw(), cy_space_back(), cyrewind_tape_ta();
5125675Ssam extern	int cyrewind_tape_unl(), cydrive_status(), cyrewind_tape_ov();
5225675Ssam extern	int cyraw_read(), cyraw_write(), cybuf_read(), cybuf_write();
5325675Ssam extern	int cywait_until_ready(), cywrite_0_fm(), cywrite_1_fm();
5425675Ssam extern	int cywrite_2_fm(), cyno_op(), cywrite_eov();
5525675Ssam 
5625675Ssam static	int (*cmd_tbl[15])() = {
5725675Ssam 	cywrite_filemark,
5825675Ssam #define	DO_W_FM	0
5925675Ssam 	cysearch_fm_forw,
6025675Ssam #define	DO_SFMF	1
6125675Ssam 	cysearch_fm_back,
6225675Ssam #define	DO_SFMB	2
6325675Ssam 	cy_space_forw,
6425675Ssam #define	DO_SPF	3
6525675Ssam 	cy_space_back,
6625675Ssam #define	DO_SPB	4
6725675Ssam 	cyrewind_tape_ta,
6825675Ssam #define	DO_RWTA	5
6925675Ssam 	cyrewind_tape_unl,
7025675Ssam #define	DO_RWUN	6
7125675Ssam 	cydrive_status,
7225675Ssam #define	DO_STAT	7
7325675Ssam 	cyrewind_tape_ov,
7425675Ssam #define	DO_RWOV	8
7525675Ssam 	cywait_until_ready,
7625675Ssam #define DO_WAIT 9
7725675Ssam 	cywrite_eov,
7825675Ssam #define DO_WEOV	10
7925675Ssam 	cyraw_read,
8025675Ssam #define DO_RRD	11
8125675Ssam 	cyraw_write,
8225675Ssam #define DO_RWT	12
8325675Ssam 	cybuf_read,
8425675Ssam #define DO_BRD	13
8525675Ssam 	cybuf_write
8625675Ssam #define DO_BWT	14
8724000Ssam };
8824000Ssam 
8925675Ssam #if NCY > 0
9025675Ssam extern	char	cy0utl[];
9125675Ssam #endif
9225675Ssam #if NCY > 1
9325675Ssam extern	char	cy1utl[];
9425675Ssam #endif
9525675Ssam struct	vba_ctlr *cyminfo[NCY];
9625675Ssam struct	vba_device *cydinfo[NUM_UNIT];
97*25857Ssam long	cystd[] = { 0 };
98*25857Ssam int cyprobe(), cyslave(), cyattach(), cydgo();
99*25857Ssam struct	vba_driver cydriver =
100*25857Ssam    { cyprobe, cyslave, cyattach, cydgo, cystd, "yc", cydinfo, "cy", cyminfo };
101*25857Ssam fmt_scp	*cyscp[] = { (fmt_scp *)0xc0000c06, (fmt_scp *)0xc0000c16 };
102*25857Ssam unsigned cyminsize();
10324000Ssam 
10424000Ssam /*
10525675Ssam  * Per-controller data structure.
10624000Ssam  */
10725675Ssam typedef struct {
10825675Ssam 	struct pte	*map;
10925675Ssam 	char		*utl;
11025675Ssam 	int		(*interupt_path)();
11125675Ssam 	label_t		environ;  /* Environment variable for longjmps */
11225675Ssam 	struct buf	*my_request;
11325675Ssam 	struct buf	*wakeup_request;
11425675Ssam 	short		bs;	  /* buffer size */
11525675Ssam 	fmt_ccb		ccb;	  /* Channel control blocks */
11625675Ssam 	fmt_scb		scb;	  /* System configuration blocks */
11725675Ssam 	fmt_tpb		tpb;	  /* Tape parameter blocks */
11825675Ssam 	fmt_tpb		last;	  /* Tape parameter blocks */
11925675Ssam 	fmt_tpb		noop;	  /* Tape parameter blocks */
12025675Ssam 	long		rawbuf[MAX_BLOCKSIZE/sizeof(long)+1];
12125675Ssam } ctlr_tab;
12224000Ssam 
12325675Ssam extern	int cy_normal_path();
12425675Ssam ctlr_tab ctlr_info[NCY] = {
12525675Ssam #if NCY > 0
12625675Ssam 	{CY0map, cy0utl, cy_normal_path},
12725675Ssam #endif
12825675Ssam #if NCY > 1
12925675Ssam 	{CY1map, cy1utl, cy_normal_path},
13025675Ssam #endif
13125675Ssam };
13224000Ssam 
13324000Ssam /*
13425675Ssam  * Per-drive information.
13524000Ssam  */
13625675Ssam typedef struct {
13725675Ssam 	int		(*cleanup)();
13825675Ssam 	struct buf	u_queue;
13925675Ssam 	struct buf	rawbp;
14025675Ssam 	long		blkno;
14125675Ssam 	long		file_number;
14225675Ssam 	short		last_control;
14325675Ssam 	short		last_status;
14425675Ssam 	short		last_resid;
14525675Ssam 	unsigned long	bad_count;
14625675Ssam 	unsigned	control_proto: 16;
14725675Ssam 	unsigned	error_count  : 8;
14825675Ssam 	unsigned	open	     : 1;
14925675Ssam 	unsigned	eof	     : 1;
15025675Ssam 	unsigned	bot	     : 1;
15125675Ssam 	unsigned	eot	     : 1;
15225675Ssam 	char		*message;
15325675Ssam } unit_tab;
15425675Ssam unit_tab unit_info[NUM_UNIT];
15524000Ssam 
156*25857Ssam cyprobe(reg, vm)
157*25857Ssam 	caddr_t reg;
158*25857Ssam 	struct vba_ctlr *vm;
15925675Ssam {
160*25857Ssam 	register br, cvec;			/* must be r12, r11 */
16125675Ssam 
162*25857Ssam 	if (badcyaddr(reg+1))
16325675Ssam 		return (0);
164*25857Ssam 	br = 0x13, cvec = 0x80;			/* XXX */
16525675Ssam 	return (sizeof (caddr_t));		/* XXX */
16625675Ssam }
16725675Ssam 
16824000Ssam /*
169*25857Ssam  * Check to see if a drive is attached to a controller.
170*25857Ssam  * Since we can only tell that a drive is there if a tape is loaded and
171*25857Ssam  * the drive is placed online, we always indicate the slave is present.
17224000Ssam  */
173*25857Ssam cyslave(vi, addr)
174*25857Ssam 	struct vba_device *vi;
175*25857Ssam 	caddr_t addr;
17624000Ssam {
177*25857Ssam 
178*25857Ssam #ifdef lint
179*25857Ssam 	vi = vi; addr = addr;
180*25857Ssam #endif
181*25857Ssam 	return (1);
182*25857Ssam }
183*25857Ssam 
184*25857Ssam /* THIS NEEDS TO BE REWRITTEN TO MOVE STUFF TO CYPROBE */
185*25857Ssam cyattach(vi)
186*25857Ssam 	struct vba_device *vi;
187*25857Ssam {
188*25857Ssam 	register unit_tab *ui = &unit_info[vi->ui_unit];
189*25857Ssam 	register struct buf *cq = &vi->ui_mi->um_tab;
190*25857Ssam 	register struct buf *uq = cq->b_forw;
191*25857Ssam 	register struct buf *start_queue = uq;
192*25857Ssam 
193*25857Ssam 	(void) cy_init_controller(vi->ui_addr, vi->ui_ctlr, 1);
194*25857Ssam 	/* Add unit to controllers queue */
195*25857Ssam 	if (cq->b_forw == NULL) {
196*25857Ssam 		cq->b_forw = &ui->u_queue;
197*25857Ssam 		ui->u_queue.b_forw = &ui->u_queue;
198*25857Ssam 	} else {
199*25857Ssam 		while (uq->b_forw != start_queue)
200*25857Ssam 			uq = uq->b_forw;
201*25857Ssam 		ui->u_queue.b_forw = start_queue;
202*25857Ssam 		uq->b_forw = &ui->u_queue;
203*25857Ssam 	}
204*25857Ssam 	ui->cleanup = cyno_op;
205*25857Ssam 	ui->last_status = 0;
206*25857Ssam 	ui->last_control = 0;
207*25857Ssam 	ui->file_number = 0;
208*25857Ssam 	ui->bad_count = 0;
209*25857Ssam 	ui->blkno = 0;
210*25857Ssam 	ui->open = 0;
211*25857Ssam 	ui->bot = 1;
212*25857Ssam 	ui->eot = 0;
213*25857Ssam 	ui->eof = 0;
214*25857Ssam 	ui->message = NULL;
215*25857Ssam }
216*25857Ssam 
217*25857Ssam /*
218*25857Ssam  * Initialize the controller after a controller reset or
219*25857Ssam  * during autoconfigure.  All of the system control blocks
220*25857Ssam  * are initialized and the controller is asked to configure
221*25857Ssam  * itself for later use.
222*25857Ssam  */
223*25857Ssam cy_init_controller(addr, ctlr, print)
224*25857Ssam 	caddr_t addr;
225*25857Ssam 	int ctlr, print;
226*25857Ssam {
22725675Ssam 	register int *pte;
22825675Ssam 	register fmt_scp *SCP;
22925675Ssam 	register fmt_scb *SCB;
23025675Ssam 	register fmt_ccb *CCB;
23125675Ssam 	register ctlr_tab *ci;
23224000Ssam 
23324000Ssam 	/*
23425675Ssam 	 * Initialize the system configuration pointer.
23524000Ssam 	 */
236*25857Ssam 	SCP = cyscp[ctlr];
23725675Ssam 	/* make kernel writable */
23825675Ssam 	pte = (int *)vtopte((struct proc *)0, btop(SCP));
23925675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KW;
24025675Ssam 	mtpr(TBIS, SCP);
24125675Ssam 	/* load the correct values in the scp */
24225675Ssam 	SCP->bus_size = _16_BITS;
24325675Ssam 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].scb, SCP->scb_ptr);
24425675Ssam 	/* put it back to read-only */
24525675Ssam 	*pte &= ~PG_PROT; *pte |= PG_KR;
24625675Ssam 	mtpr(TBIS, SCP);
24725675Ssam 
24824000Ssam 	/*
24925675Ssam 	 * Init system configuration block.
25024000Ssam 	 */
25125675Ssam 	SCB = &ctlr_info[ctlr].scb;
25225675Ssam 	SCB->fixed_value = 0x3;
25325675Ssam 	/* set pointer to the channel control block */
25425675Ssam 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].ccb, SCB->ccb_ptr);
25525675Ssam 
25624000Ssam 	/*
25725675Ssam 	 * Initialize the chanel control block.
25824000Ssam 	 */
25925675Ssam 	CCB = &ctlr_info[ctlr].ccb;
26025675Ssam 	CCB->ccw = CLEAR_INTERUPT;
26125675Ssam 	CCB->gate = GATE_OPEN;
26225675Ssam 	/* set pointer to the tape parameter block */
26325675Ssam 	load_mbus_addr((caddr_t)&ctlr_info[ctlr].tpb, CCB->tpb_ptr);
26425675Ssam 
26524000Ssam 	/*
26625675Ssam 	 * Issue a noop cmd and get the internal buffer size for buffered i/o.
26724000Ssam 	 */
26825675Ssam 	ci = &ctlr_info[ctlr];
26925675Ssam 	/* set command to be CONFIGURE */
27025675Ssam 	ci->tpb.cmd = NO_OP;
27125675Ssam 	ci->tpb.control = CW_16bits;
27225675Ssam 	ci->ccb.gate = GATE_CLOSED;
273*25857Ssam 	CY_ATTENTION(addr);	/* execute! */
27425675Ssam 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
275*25857Ssam 		printf("cy%d: time-out during init\n", ctlr);
27625675Ssam 		return (0);
27725675Ssam 	}
27825675Ssam 	ci->tpb.cmd = CONFIG;
27925675Ssam 	ci->tpb.control = CW_16bits;
28025675Ssam 	ci->ccb.gate = GATE_CLOSED;
281*25857Ssam 	CY_ATTENTION(addr);		/* execute! */
28225675Ssam 	if (cywait(&ci->ccb) || (ci->tpb.status & CS_ERm)) {
28325675Ssam 		cyprint_err("Tapemaster configuration failure",
28425675Ssam 		    0, ci->tpb.status);
28525675Ssam 		return (0);
28625675Ssam 	}
28725675Ssam 	uncache(&ci->tpb.count);
28825675Ssam 	ci->bs = MULTIBUS_SHORT(ci->tpb.count);
28925675Ssam 	if (print)
290*25857Ssam 		printf("cy%d: %dKb buffer\n", ctlr, ci->bs/1024);
29125675Ssam 	return (1);
29224000Ssam }
29324000Ssam 
29425675Ssam cydgo()
29525675Ssam {
29625675Ssam 
29725675Ssam }
29825675Ssam 
29925675Ssam /* macro to pack the unit number into Tapemaster format */
30025675Ssam #define	UNIT(unit) \
30125675Ssam     (((cydinfo[unit]->ui_slave & 1) << 11) | \
30225675Ssam      ((cydinfo[unit]->ui_slave & 2) << 9) | \
30325675Ssam      ((cydinfo[unit]->ui_slave & 4) >> 2))
30425675Ssam 
30525675Ssam cyopen(dev, flag)
30625675Ssam 	register int flag;
30725675Ssam 	register dev_t dev;
30825675Ssam {
30925675Ssam 	register int unit = CYUNIT(dev);
31025675Ssam 	register unit_tab *ui;
31125675Ssam 
31225675Ssam 	if (unit >= NUM_UNIT || cydinfo[unit] == 0 ||
31325675Ssam 	    (ui = &unit_info[unit])->open)
31425675Ssam 		return (ENXIO);
31525675Ssam 	ui->control_proto = UNIT(unit) | CW_INTR | CW_16bits;
31625675Ssam 	ui->blkno = 0;
31725675Ssam 	ui->bad_count = 0;
31825675Ssam 	ui->eof = 0;
31925675Ssam 	ui->open = 1;
32025675Ssam 	cycmd(dev, DO_WAIT, 1);			/* wait for tape to rewind */
32125675Ssam 	if ((ui->last_status&CS_OL) == 0) {	/* not on-line */
32225675Ssam 		ui->open = 0;
32325675Ssam 		return (ENXIO);
32425675Ssam 	}
32525675Ssam 	if ((flag&FWRITE) && (ui->last_status&CS_P)) {
32625675Ssam 		uprintf("cy%d: write protected\n", unit);
32725675Ssam 		ui->open = 0;
32825675Ssam 		return (ENXIO);
32925675Ssam 	}
33025675Ssam 	if (ui->last_status&CS_LP) {
33125675Ssam 		ui->file_number = 0;
33225675Ssam 		ui->bot = 1;
33325675Ssam 		ui->eof = ui->eot = 0;
33425675Ssam 	}
33525675Ssam 	return (0);
33625675Ssam }
33725675Ssam 
33825675Ssam cyclose(dev, flag)
33925675Ssam 	register dev_t dev;
34025675Ssam 	register flag;
34125675Ssam {
34225675Ssam 	register int unit = CYUNIT(dev);
34325675Ssam 	register unit_tab *ui = &unit_info[unit];
34425675Ssam 
34525675Ssam 	if (ui->last_status&CS_OL) {
34625675Ssam 		if ((flag&FWRITE) && (minor(dev)&T_NOREWIND))
34725675Ssam 			cycmd(dev, DO_WEOV, 1);
34825675Ssam 		else if ((minor(dev) & T_NOREWIND) == 0)
34925675Ssam 			cycmd(dev, DO_RWOV, 1);
35025675Ssam 	}
35125675Ssam 	if (ui->bad_count != 0) {
35225675Ssam #ifdef notdef
35325675Ssam 		ui->bad_count *= 889;
35425675Ssam 		uprintf("cy%d: Warning - %d.%dcm of tape were used for recovering bad spots.\n", unit, ui->bad_count/100, ui->bad_count%100);
35525675Ssam #endif
35625675Ssam 		ui->bad_count = 0;
35725675Ssam 	}
35825675Ssam 	ui->open = 0;
35925675Ssam }
36025675Ssam 
36124000Ssam /*
36225675Ssam  * Cycmd is used internally to implement all the ioctl functions.
36325675Ssam  * We duplicate the code in physio
36425675Ssam  * that is used for syncronizing the processes (sleep / wakeup) so
36525675Ssam  * that we can treat our internal command requests exactly like
36625675Ssam  * regular reads and writes.  They get put on the controller queue,
36725675Ssam  * start processes them and iodone is called to wake us up on completion.
36825675Ssam  *
36925675Ssam  * We don't call physio directly because it expects data to be moved
37025675Ssam  * and has a lot more overhead than we really need.
37124000Ssam  */
37225675Ssam cycmd(dev, command, count)
37325675Ssam 	register dev_t dev;
37425675Ssam 	register int command, count;
37524000Ssam {
37625675Ssam 	register int unit = CYUNIT(dev);
37725675Ssam 	register unit_tab *ui = &unit_info[unit];
37825675Ssam 	register struct buf *uq;
37925675Ssam 	int s;
38025675Ssam 
38125675Ssam 	s = spl3();
38225675Ssam 	while (ui->rawbp.b_flags & B_BUSY) {
38325675Ssam 		ui->rawbp.b_flags |= B_WANTED;
38425675Ssam 		sleep((caddr_t)&ui->rawbp, PRIBIO+1);
38525675Ssam 	}
38625675Ssam 	splx(s);
38725675Ssam 	/* load the request queue element */
38825675Ssam 	ui->rawbp.b_error = 0;
38925675Ssam 	ui->rawbp.b_dev = dev;
39025675Ssam 	ui->rawbp.b_cmd = (struct buf *)command;
39125675Ssam 	ui->rawbp.b_bcount = count;
39225675Ssam 	ui->rawbp.b_flags = B_PHYS | B_BUSY;
39325675Ssam 	s = spl3();
39425675Ssam 	uq = &ui->u_queue;
39525675Ssam 	ui->rawbp.av_forw = NULL;
39625675Ssam 	if (uq->av_forw == NULL)
39725675Ssam 		uq->av_forw = &ui->rawbp;
39825675Ssam 	else
39925675Ssam 		uq->av_back->av_forw = &ui->rawbp;
40025675Ssam 	uq->av_back = &ui->rawbp;
40125675Ssam 	cystart(cydinfo[unit]->ui_mi, &ui->rawbp, s);
40224000Ssam 
40325675Ssam 	/* wait for operation to complete */
40425675Ssam 	while ((ui->rawbp.b_flags&B_DONE) == 0)
40525675Ssam 		sleep((caddr_t)&ui->rawbp, PRIBIO);
40625675Ssam 	ui->rawbp.b_flags &= ~(B_PHYS | B_BUSY);
40725675Ssam 	if (ui->rawbp.b_flags & B_WANTED)
40825675Ssam 		wakeup((caddr_t)&ui->rawbp);
40925675Ssam 	return (geterror(&ui->rawbp));
41024000Ssam }
41124000Ssam 
41225675Ssam cystrategy(bp)
41325675Ssam 	register struct buf *bp;
41425675Ssam {
41525675Ssam 	register int unit = CYUNIT(bp->b_dev);
41625675Ssam 	register unit_tab *ui = &unit_info[unit];
41725675Ssam 	register struct buf *uq;
41825675Ssam 	int s;
41925675Ssam 
42025675Ssam 	/* check the validity of the request */
42125675Ssam 	if (bp->b_bcount > MAX_BLOCKSIZE) {
42225675Ssam 		uprintf("cy%d: Maximum block size is %dk!\n",
42325675Ssam 		    unit, MAX_BLOCKSIZE/1024);
42425675Ssam 		bp->b_error = EIO;
42525675Ssam 		bp->b_resid = bp->b_bcount;
42625675Ssam 		bp->b_flags |= B_ERROR;
42725675Ssam 		iodone(bp);
42825675Ssam 		return;
42925675Ssam 	}
43025675Ssam 	vbasetup(bp, MAX_BLOCKSIZE);
43125675Ssam 	if (bp->b_flags & B_PHYS)
43225675Ssam 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_RRD : DO_RWT);
43325675Ssam 	else
43425675Ssam 		bp->b_cmd = (struct buf *)(bp->b_flags&B_READ? DO_BRD : DO_BWT);
43525675Ssam 	/* place request on queue and start it */
43625675Ssam 	s = spl3();
43725675Ssam 	uq = &ui->u_queue;
43825675Ssam 	bp->av_forw = NULL;
43925675Ssam 	if (uq->av_forw == NULL)
44025675Ssam 		uq->av_forw = bp;
44125675Ssam 	else
44225675Ssam 		uq->av_back->av_forw = bp;
44325675Ssam 	uq->av_back = bp;
44425675Ssam 	cystart(cydinfo[unit]->ui_mi, bp, s);
44525675Ssam }
44625675Ssam 
44725675Ssam struct	buf *cyget_next();
44825675Ssam int	cystart_timeout();
44924000Ssam /*
45025675Ssam  * Cystart is called once for every request that is placed on a
45125675Ssam  * controller's queue.  Start is responsible for fetching requests for
45225675Ssam  * a controller queue, starting the operation, and waiting for completion,
45325675Ssam  * and releasing the buf structure back to UNIX or cycmd, before fetching
45425675Ssam  * the next request.
45525675Ssam  *
45625675Ssam  * The controller's queue looks like this:
45725675Ssam  *
45825675Ssam  *                      +---------------------------------------+
45925675Ssam  *                      |                                       |
46025675Ssam  *      +-----------+   |   +-----------+        +-----------+  |
46125675Ssam  *      |  b_forw   |---+-->|  b_forw   |--~ ~-->|  b_forw   |--+
46225675Ssam  *      +-----------+       +-----------+        +-----------+
46325675Ssam  *      |  b_back   |       | ......... |        | ......... |
46425675Ssam  *      +-----------+       +-----------+        +-----------+
46525675Ssam  *      | ......... |      First unit queue     Last unit queue
46625675Ssam  *      +-----------+          element              element
46725675Ssam  * head of controller queue
46825675Ssam  *  (cyminfo[ctlr].um_tab)
46924000Ssam  */
47025675Ssam cystart(vi, bp, s)
47125675Ssam 	register struct vba_ctlr *vi;
47225675Ssam 	register struct buf *bp;
47324000Ssam {
47425675Ssam 	int unit = CYUNIT(bp->b_dev), ctlr = vi->um_ctlr;
47525675Ssam 	register struct buf *next, *cq = &vi->um_tab;
47625675Ssam 	register unit_tab *ui = &unit_info[unit];
47725675Ssam 	register ctlr_tab *ci = &ctlr_info[ctlr];
47824000Ssam 
47925675Ssam 	if (cq->b_active&SLEEPING) {
48025675Ssam 		untimeout(cystart_timeout, (caddr_t)cq);
48125675Ssam 		cystart_timeout(cq);
48224000Ssam 	}
48325675Ssam 	if (cq->b_active) {
48425675Ssam 		sleep((caddr_t)bp, PRIBIO-1);
48525675Ssam 		if (bp->b_flags&PROCESSED) {
48625675Ssam 			if (ui->message) {
48725675Ssam 				uprintf("cy%d: %s\n", unit, ui->message);
48825675Ssam 				ui->message = 0;
48925675Ssam 			}
49025675Ssam 			bp->b_flags &= ~PROCESSED;
49125675Ssam 			iodone(bp);
49225675Ssam 			return;
49325675Ssam 		}
49424000Ssam 	}
49525675Ssam 	cq->b_active = 1;
49625675Ssam 	splx(s);
49725675Ssam 	ci->my_request = bp;
49825675Ssam 	cydo_my_command(ctlr, cq, ci);
49925675Ssam 	if (ui->message) {
50025675Ssam 		uprintf("cy%d: %s\n", unit, ui->message);
50125675Ssam 		ui->message = 0;
50224000Ssam 	}
50325675Ssam 	bp->b_flags &= ~PROCESSED;
50425675Ssam 	iodone(bp);
50525675Ssam 	if ((next = cyget_next(cq)) != NULL)
50625675Ssam 		wakeup((caddr_t)next);
50725675Ssam 	else
50825675Ssam 		cq->b_active = 0;
50924000Ssam }
51024000Ssam 
51124000Ssam /*
51225675Ssam  * Cystart_timeout wakes up the start routine after it's 3
51325675Ssam  * second wait time is up or when a new command enters the queue.
51425675Ssam  * The timer is used to give up the processor while all drives
51525675Ssam  * on the queue are rewinding and we need to wait for them to be dome.
51624000Ssam  */
51725675Ssam cystart_timeout(cq)
51825675Ssam 	register struct buf *cq;
51924000Ssam {
52024000Ssam 
52125675Ssam 	cq->b_active &= ~SLEEPING;
52225675Ssam 	wakeup((caddr_t)cq);
52325675Ssam }
52425675Ssam 
52525675Ssam /*
52625675Ssam  * Cydo_my command scans the request queues once for a
52725675Ssam  * particular controller and calls the appropriate processing routine
52825675Ssam  * each time we find a request that can be started.
52925675Ssam  */
53025675Ssam cydo_my_command(ctlr, cq, ci)
53125675Ssam 	register struct buf *cq;
53225675Ssam 	register ctlr_tab *ci;
53325675Ssam {
53425675Ssam 	register struct buf *next;
53525675Ssam 
53625675Ssam 	while ((next = cyget_next(cq)) != NULL) {
53725675Ssam 		if (cq->b_forw->b_active&SLEEPING) {
53825675Ssam 			cq->b_active |= SLEEPING;
53925675Ssam 			timeout(cystart_timeout, (caddr_t)cq, 1*60);
54025675Ssam 			sleep((caddr_t)cq, PRIBIO);
54125675Ssam 			continue;
54225675Ssam 		}
54325675Ssam 		if (setjmp(&ctlr_info[ctlr].environ))
54425675Ssam 			cydone(cq);
54525675Ssam 		else {
54625675Ssam 			register int cmd = (int)next->b_cmd;
54725675Ssam 
54825675Ssam 			(*cmd_tbl[cmd])(next, cq);
54925675Ssam 		}
55025675Ssam 		if (next->b_flags & PROCESSED) {
55125675Ssam 			if (ci->my_request == next)
55225675Ssam 				break;
55325675Ssam 			wakeup((caddr_t)next);
55425675Ssam 		}
55524000Ssam 	}
55624000Ssam }
55724000Ssam 
55825675Ssam struct buf *
55925675Ssam cyget_next(cq)
56025675Ssam 	register struct	buf *cq;
56125675Ssam {
56225675Ssam 	register struct buf *bp, *uq, *next = NULL;
56324000Ssam 
56425675Ssam 	cq->b_forw = cq->b_forw->b_forw;
56525675Ssam 	uq = cq->b_forw;
56625675Ssam 	do {
56725675Ssam 		if ((bp = uq->av_forw) != NULL) {
56825675Ssam 			if ((uq->b_active&SLEEPING) == 0) {
56925675Ssam 				cq->b_forw = uq;
57025675Ssam 				return (bp);
57125675Ssam 			}
57225675Ssam 			next = uq;
57325675Ssam 		}
57425675Ssam 		uq = uq->b_forw;
57525675Ssam 	} while(uq != cq->b_forw);
57625675Ssam 	if (next != NULL) {
57725675Ssam 		cq->b_forw = next;
57825675Ssam 		return (next->av_forw);
57925675Ssam 	}
58025675Ssam 	return (NULL);
58125675Ssam }
58225675Ssam 
58324000Ssam /*
58425675Ssam  * Mark the current command on the controller's q completed and remove it.
58524000Ssam  */
58625675Ssam cydone(cq)
58725675Ssam 	struct buf *cq;
58824000Ssam {
58925675Ssam 	register struct buf *uq = cq->b_forw;
59024000Ssam 	int s;
59124000Ssam 
59225675Ssam 	uq->av_forw->b_flags |= PROCESSED;
59325675Ssam 	s = spl3();
59425675Ssam 	if ((uq->av_forw = uq->av_forw->av_forw) == NULL)
59525675Ssam 		uq->av_back = NULL;
59624000Ssam 	splx(s);
59724000Ssam }
59824000Ssam 
59924000Ssam /*
60025675Ssam  * The following routines implement the individual commands.
60125675Ssam  *
60225675Ssam  * Each command is responsible for a few things. 1) Each has to keep
60325675Ssam  * track of special cases that are related to the individual command and
60425675Ssam  * the previous commands sequence, 2) each is required to call iodone when
60525675Ssam  * command is actually finished, 3) it must use cyexecute to actually
60625675Ssam  * start the controller, and 4) they are required to keep the tape in
60725675Ssam  * a consistant state so that other commands will not be messed up.
60824000Ssam  */
60925675Ssam 
61025675Ssam /*
61125675Ssam  * Read requests from the raw device.
61225675Ssam  * The special cases are:
61325675Ssam  *  1) we can not read after a write.  (writting defines end of file)
61425675Ssam  *  2) reading past end of file returns 0 bytes;
61525675Ssam  */
61625675Ssam cyraw_read(bp, cq)
61724000Ssam 	register struct buf *bp;
61825675Ssam 	struct buf *cq;
61924000Ssam {
62025675Ssam 	int unit = CYUNIT(bp->b_dev);
62125675Ssam 	register unit_tab *ui = &unit_info[unit];
62225675Ssam 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
62325675Ssam 	int addr, lock_flag, command;
62424000Ssam 
62525675Ssam 	if (ui->cleanup != cyno_op || ui->eof) {
62625675Ssam 		bp->b_resid = bp->b_bcount;
62725675Ssam 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
62825675Ssam 		cydone(cq);
62925675Ssam 		return;
63025675Ssam 	}
63125675Ssam 	if (bp->b_bcount > ci->bs)
63225675Ssam 		command = READ_TA, lock_flag = CW_LOCK;
63325675Ssam 	else
63425675Ssam 		command = READ_BU, lock_flag = 0;
63525675Ssam 	ui->blkno++;
63625675Ssam 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
63725675Ssam 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
63825675Ssam 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
63925675Ssam 	cydone(cq);
64025675Ssam }
64125675Ssam 
64224000Ssam /*
64325675Ssam  * Write requests from the raw device.
64425675Ssam  * The special cases are:
64525675Ssam  *  1) we don't allow writes after end of tape is reached.
64624000Ssam  */
64725675Ssam cyraw_write(bp, cq)
64825675Ssam 	register struct buf *bp;
64925675Ssam 	struct buf *cq;
65025675Ssam {
65125675Ssam 	int unit = CYUNIT(bp->b_dev);
65225675Ssam 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
65325675Ssam 	register ctlr_tab *ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
65425675Ssam 	int addr, lock_flag, command;
65524000Ssam 
65625675Ssam 	if (ui->eot) {
65725675Ssam 		bp->b_resid = bp->b_bcount;
65825675Ssam 		bp->b_error = ENXIO, bp->b_flags |= B_ERROR;
65925675Ssam 		longjmp(&ci->environ);
66025675Ssam 	}
66125675Ssam 	ui->cleanup = cywrite_2_fm;
66225675Ssam 	if (bp->b_bcount > ci->bs)
66325675Ssam 		command = WRIT_TA, lock_flag = CW_LOCK;
66425675Ssam 	else
66525675Ssam 		command = WRIT_BU, lock_flag = 0;
66625675Ssam 	ui->blkno++;
66725675Ssam 	addr = vbastart(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
66825675Ssam 	cyexecute(command, bp->b_bcount, addr, lock_flag, unit, 10, FALSE);
66925675Ssam 	vbadone(bp, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
67025675Ssam 	cydone(cq);
67124000Ssam }
67224000Ssam 
67324000Ssam /*
67425675Ssam  * Write a filemark on a tape.
67524000Ssam  */
67625675Ssam cywrite_filemark(bp, cq)
67725675Ssam 	register struct buf *bp;
67825675Ssam 	struct buf *cq;
67924000Ssam {
68025675Ssam 	int unit = CYUNIT(bp->b_dev);
68125675Ssam 	register unit_tab *ui = &unit_info[CYUNIT(unit)];
68225675Ssam 
68325675Ssam 	if (bp->b_bcount == 0) {
68425675Ssam 		cydone(cq);
68524000Ssam 		return;
68624000Ssam 	}
68725675Ssam 	bp->b_bcount--;
68825675Ssam 	if (ui->cleanup == cywrite_1_fm)
68925675Ssam 		ui->cleanup = cywrite_0_fm;
69025675Ssam 	if (ui->cleanup == cywrite_2_fm || ui->cleanup == cyno_op)
69125675Ssam 		ui->cleanup = cywrite_1_fm;
69225675Ssam 	ui->file_number++;
69325675Ssam 	ui->eof = 1;
69425675Ssam 	ui->blkno = 0;
69525675Ssam 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 10, FALSE);
69625675Ssam }
69725675Ssam 
69825675Ssam /*
69925675Ssam **	cysearch_fm_forw is the ioctl to search for a filemark in the
70025675Ssam **  forward direction on tape.
70125675Ssam **
70225675Ssam **	Since only one device can be active on a given controller at any
70325675Ssam **  given instant in time, we try to be nice and let onther devices  on
70425675Ssam **  this controller be scheduled after we space over each record.  This will
70525675Ssam **  at least give the apperance of overlapped operations on the controller.
70625675Ssam **
70725675Ssam **  The special cases are:
70825675Ssam **  1) if the last command was a write the we can't search.
70925675Ssam */
71025675Ssam 
71125675Ssam cysearch_fm_forw(request, cq)
71225675Ssam register struct buf	*request;
71325675Ssam register struct buf	*cq;
71425675Ssam {
71525675Ssam 	register int		unit = CYUNIT(request->b_dev);
71625675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
71725675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
71825675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
71925675Ssam 
72025675Ssam 	if((ui->cleanup != cyno_op) || ui->eot) {
72125675Ssam 		request->b_resid = request->b_bcount;
72225675Ssam 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
72325675Ssam 		longjmp(&ci->environ);
72424000Ssam 	}
72525675Ssam 	if(request->b_bcount && !ui->eot) {
72625675Ssam 		if(!ui->eot) {
72725675Ssam 			ui->blkno++;
72825675Ssam 			cyexecute(SPAC_FM, (long)1, 0, 0, unit, 5, FALSE);
72925675Ssam 			if(!(ui->eof || ui->eot))
73025675Ssam 				return;
73124000Ssam 		}
73225675Ssam 		request->b_bcount--;
73325675Ssam 		ui->eof = FALSE;
73425675Ssam 		if(!ui->eot) {
73525675Ssam 			ui->file_number++;
73625675Ssam 			ui->blkno = 0;
73725675Ssam 			return;
73824000Ssam 		}
73924000Ssam 	}
74025675Ssam 	if(ui->eot) {
74125675Ssam 		request->b_resid = request->b_bcount;
74225675Ssam 		request->b_flags |= B_ERROR, request->b_error = ENXIO;
74324000Ssam 	}
74425675Ssam 	cydone(cq);
74525675Ssam }
74625675Ssam 
74725675Ssam 
74825675Ssam /*
74925675Ssam **	cysearch_fm_back is the ioctl to search for a filemark in the
75025675Ssam **  reverse direction on tape.
75125675Ssam **
75225675Ssam **	Since only one device can be active on a given controller at any
75325675Ssam **  given instant in time, we try to be nice and let onther devices  on
75425675Ssam **  this controller be scheduled after we space over each record.  This will
75525675Ssam **  at least give the apperance of overlapped operations on the controller.
75625675Ssam **
75725675Ssam **  The special cases are:
75825675Ssam **  1) can't search past begining of tape.
75925675Ssam **  2) if the lasr operation was a write data then we need to add
76025675Ssam **     an end of volume record before we start searching.
76125675Ssam */
76225675Ssam 
76325675Ssam cysearch_fm_back(request, cq)
76425675Ssam register struct buf	*request;
76525675Ssam register struct buf	*cq;
76625675Ssam {
76725675Ssam 	register int		unit = CYUNIT(request->b_dev);
76825675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
76925675Ssam 
77025675Ssam 	if(!ui->bot) {
77125675Ssam 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
77225675Ssam 		if(ui->blkno == 0)
77325675Ssam 			request->b_bcount++;
77425675Ssam 		ui->blkno = 0xffffffff;
77525675Ssam 		if(request->b_bcount && !ui->bot) {
77625675Ssam 			cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 6, FALSE);
77725675Ssam 			if(ui->eof) {
77825675Ssam 				ui->eof = FALSE;
77925675Ssam 				ui->file_number--;
78025675Ssam 				request->b_bcount--;
78125675Ssam 			}
78225675Ssam 			return;
78325675Ssam 		}
78425675Ssam 		if(ui->bot) {
78525675Ssam 			ui->file_number = 0;
78625675Ssam 			if(request->b_bcount) {
78725675Ssam 				request->b_resid = request->b_bcount;
78825675Ssam 				request->b_error = ENXIO;
78925675Ssam 				request->b_flags |= B_ERROR;
79025675Ssam 			}
79125675Ssam 		}
79225675Ssam 		else {
79325675Ssam 			request->b_cmd = (struct buf *)DO_SFMF;
79425675Ssam 			request->b_bcount = 1;
79525675Ssam 			return;
79625675Ssam 		}
79724000Ssam 	}
79825675Ssam 	ui->blkno = 0;
79925675Ssam 	ui->eof = FALSE;
80025675Ssam 	cydone(cq);
80125675Ssam }
80224000Ssam 
80324000Ssam 
80425675Ssam /*
80525675Ssam **	cy_space_forw is used to search forward a given number of records on
80625675Ssam **  tape.
80725675Ssam **
80825675Ssam **	Since only one device can be active on a given controller at any
80925675Ssam **  given instant in time, we try to be nice and let onther devices  on
81025675Ssam **  this controller be scheduled after we space over each record.  This will
81125675Ssam **  at least give the apperance of overlapped operations on the controller.
81225675Ssam **
81325675Ssam **  The special cases are:
81425675Ssam **  1) we can't space over a filemark.
81525675Ssam **  2) if the last command was a write data or filemark we can't space forward.
81625675Ssam */
81725675Ssam 
81825675Ssam cy_space_forw(request, cq)
81925675Ssam register struct buf	*request;
82025675Ssam register struct buf	*cq;
82125675Ssam {
82225675Ssam 	register int		unit = CYUNIT(request->b_dev);
82325675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
82425675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
82525675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
82625675Ssam 
82725675Ssam 	if((ui->cleanup != cyno_op) || ui->eof) {
82825675Ssam 		request->b_resid = request->b_bcount;
82925675Ssam 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
83025675Ssam 		longjmp(&ci->environ);
83124000Ssam 	}
83225675Ssam 	if(request->b_bcount) {
83325675Ssam 		ui->blkno++;
83425675Ssam 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
83525675Ssam 		if(!ui->eof && request->b_bcount) {
83625675Ssam 			request->b_bcount--;
83725675Ssam 			return;
83825675Ssam 		}
83924000Ssam 	}
84025675Ssam 	if(ui->eof) {
84125675Ssam 		request->b_resid = request->b_bcount;
84225675Ssam 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
84325675Ssam 	}
84425675Ssam 	cydone(cq);
84525675Ssam }
84625675Ssam 
84725675Ssam 
84825675Ssam /*
84925675Ssam **	Cy_space_back spaces backward a given number of records.
85025675Ssam **
85125675Ssam **	Since only one device can be active on a given controller at any
85225675Ssam **  given instant in time, we try to be nice and let onther devices  on
85325675Ssam **  this controller be scheduled after we space over each record.  This will
85425675Ssam **  at least give the apperance of overlapped operations on the controller.
85525675Ssam **
85625675Ssam **  The special cases are:
85725675Ssam **  1) we can't space over a filemark.
85825675Ssam **  2) we can't space past the beginning of tape.
85925675Ssam **  3) if the last operation was a write data then we need to add
86025675Ssam **     an end of volume record before we start searching.
86125675Ssam */
86225675Ssam 
86325675Ssam cy_space_back(request, cq)
86425675Ssam register struct buf	*request;
86525675Ssam register struct buf	*cq;
86625675Ssam {
86725675Ssam 	register int		unit = CYUNIT(request->b_dev);
86825675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
86925675Ssam 
87025675Ssam 	if(!ui->bot) {
87125675Ssam 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
87225675Ssam 		if(request->b_bcount+1 && !ui->bot && !ui->eof) {
87325675Ssam 			request->b_bcount--;
87425675Ssam 			ui->blkno--;
87525675Ssam 			cyexecute(SPACE, (long)1, 0, CW_REV, unit, 15, FALSE);
87625675Ssam 			return;
87724000Ssam 		}
87825675Ssam 		if(!ui->bot) {
87925675Ssam 			request->b_bcount = 1;
88025675Ssam 			cy_space_forw(request, cq);
88125675Ssam 		}
88225675Ssam 		ui->eof = FALSE;
88324000Ssam 	}
88425675Ssam 	cydone(cq);
88525675Ssam }
88624000Ssam 
88725675Ssam /*
88825675Ssam  * Rewind tape and wait for completion.
88925675Ssam  * An overlapped rewind is issued and then we change the command type to
89025675Ssam  * a wait for ready ioctl.  Wait for ready contains the logic to poll
89125675Ssam  * without blocking anything in the system, until the drive becomes ready or
89225675Ssam  * drops off line whichever comes first.
89325675Ssam  */
89425675Ssam /*ARGSUSED*/
89525675Ssam cyrewind_tape_ta(bp, cq)
89625675Ssam 	struct buf *bp, *cq;
89725675Ssam {
89825675Ssam 
89925675Ssam 	cyrewind_tape(bp, REWD_OV);
90025675Ssam 	bp->b_cmd = (struct buf *)DO_WAIT;
90124000Ssam }
90224000Ssam 
90324000Ssam /*
90425675Ssam  * Do an overlapped rewind and then unload the tape.
90525675Ssam  * This feature is handled by the individual tape drive and
90625675Ssam  * in some cases can not be performed.
90724000Ssam  */
90825675Ssam cyrewind_tape_unl(bp, cq)
90925675Ssam 	struct buf *bp, *cq;
91024000Ssam {
91125675Ssam 
91225675Ssam 	cyrewind_tape(bp, OFF_UNL);
91325675Ssam 	cydone(cq);
91424000Ssam }
91524000Ssam 
91624000Ssam /*
91725675Ssam  * Do an overlapped rewind.
91824000Ssam  */
91925675Ssam cyrewind_tape_ov(bp, cq)
92025675Ssam 	struct buf *bp, *cq;
92124000Ssam {
92225675Ssam 
92325675Ssam 	cyrewind_tape(bp, REWD_OV);
92425675Ssam 	cydone(cq);
92525675Ssam }
92625675Ssam 
92725675Ssam /*
92825675Ssam  * Common code for all rewind commands.
92925675Ssam  * The special cases are:
93025675Ssam  *  3) if the last operation was a write data then we need to add
93125675Ssam  *     an end of volume record before we start searching.
93225675Ssam  */
93325675Ssam cyrewind_tape(bp, cmd)
93424000Ssam 	register struct buf *bp;
93525675Ssam 	int cmd;
93625675Ssam {
93725675Ssam 	register int unit = CYUNIT(bp->b_dev);
93825675Ssam 	register unit_tab *ui = &unit_info[unit];
93924000Ssam 
94025675Ssam 	(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
94125675Ssam 	ui->blkno = 0;
94225675Ssam 	ui->eof = FALSE;
94325675Ssam 	ui->bot = TRUE;
94425675Ssam 	ui->eot = FALSE;
94525675Ssam 	ui->file_number = 0;
94625675Ssam 	bp->b_resid = 0;
94725675Ssam 	ui->cleanup = cyno_op;
94825675Ssam 	cyexecute(cmd, (long)0, 0, 0, unit, cmd == REWD_OV ? 10 : 10*60, 0);
94925675Ssam }
95025675Ssam 
95125675Ssam /*
95225675Ssam **	Cywait_until_ready is used to wait for rewinds to complete.
95325675Ssam **  We check the status and if the tape is still rewinding we re-enter ourself
95425675Ssam **  on the activity queue to give other requests a chance to execute before we
95525675Ssam **  check the status again.  One other thing is that we only want to  check
95625675Ssam **  the status every five seconds.  so we set a timer for five seconds and
95725675Ssam **  check the time left every time we enter this routine.  If there is still
95825675Ssam **  time left then we simply reinsert ourself on the queue again and wait
95925675Ssam **  until next time ..
96025675Ssam */
96125675Ssam cywait_until_ready(request, cq)
96225675Ssam register struct buf	*request;
96325675Ssam register struct buf	*cq;
96425675Ssam {
96525675Ssam 	extern int		cywait_timeout();
96625675Ssam 	register int		unit = CYUNIT(request->b_dev);
96725675Ssam 	register unit_tab	*ui = &unit_info[unit];
96825675Ssam 
96925675Ssam 	cyexecute(DRIVE_S, (long)0, 0, 0, unit, 10, FALSE);
97025675Ssam 	if((!(ui->last_status & CS_OL)) || (ui->last_status & CS_RDY)) {
97125675Ssam 		cydone(cq);
97224000Ssam 		return;
97324000Ssam 	}
97425675Ssam 	cq->b_forw->b_active |= SLEEPING;
97525675Ssam 	timeout(cywait_timeout, (caddr_t)cq->b_forw, 2*60);
97625675Ssam }
97725675Ssam 
97825675Ssam /*
97925675Ssam  * Reset the timing flag for nice_wait after 3 seconds.
98025675Ssam  * This makes this drive eligible for scheduling again.
98125675Ssam  */
98225675Ssam cywait_timeout(uq)
98325675Ssam 	struct buf *uq;
98425675Ssam {
98525675Ssam 
98625675Ssam 	uq->b_active &= ~SLEEPING;
98725675Ssam }
98825675Ssam 
98925675Ssam /*
99025675Ssam  * Process a status ioctl request.
99125675Ssam  * It depends entirly on the interupt routines to load the last_XXX
99225675Ssam  * registers in unit_info[].
99325675Ssam  */
99425675Ssam cydrive_status(bp, cq)
99525675Ssam 	struct buf *bp, *cq;
99625675Ssam {
99725675Ssam 
99825675Ssam 	cyexecute(DRIVE_S, (long)0, 0, 0, CYUNIT(bp->b_dev), 10, FALSE);
99925675Ssam 	cydone(cq);
100025675Ssam }
100125675Ssam 
100225675Ssam /*
100325675Ssam **	cybuf_read handles the read requests from the block device.
100425675Ssam **
100525675Ssam **  The special cases are:
100625675Ssam **  1)	we can not read after a write.  (writting defines end of file)
100725675Ssam **  2)  reading past end of file returns 0 bytes;
100825675Ssam **  3)  if we are mispositioned we have to seek to the correct block.
100925675Ssam **  4)  we can hit end of tape while seeking.
101025675Ssam **  5)  we want to be nice to other processes while seeking so we
101125675Ssam **  	break the request up into smaller requests.
101225675Ssam **  6)  returns error if the block was larger than requested.
101325675Ssam */
101425675Ssam cybuf_read(request, cq)
101525675Ssam register struct buf	*request;
101625675Ssam register struct buf	*cq;
101725675Ssam {
101825675Ssam 	register int		unit = CYUNIT(request->b_dev);
101925675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
102025675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
102125675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
102225675Ssam 	register int		addr, command, bus_lock;
102325675Ssam 
102425675Ssam 	cydebug = 1;
102525675Ssam 	if(cyseek(request, cq)) {
102625675Ssam 		if(ui->cleanup != cyno_op) {
102725675Ssam 			clrbuf(request);
102825675Ssam 			longjmp(&ci->environ);
102924000Ssam 		}
103025675Ssam 		if(request->b_bcount > ci->bs)
103125675Ssam 			command = READ_TA, bus_lock = CW_LOCK;
103225675Ssam 		else
103325675Ssam 			command = READ_BU, bus_lock = 0;
103425675Ssam 		ui->blkno++;
103525675Ssam 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
103625675Ssam 		    ci->utl);
103725675Ssam 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,8,FALSE);
103825675Ssam 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
103925675Ssam 		cydone(cq);
104024000Ssam 	}
104125675Ssam }
104225675Ssam 
104325675Ssam 
104425675Ssam /*
104525675Ssam **	cybuf_write handles the write requests from the block device.
104625675Ssam **
104725675Ssam **  The special cases are:
104825675Ssam **  1)  if we are mispositioned we have to seek to the correct block.
104925675Ssam **  2)  we can hit end of tape while seeking.
105025675Ssam **  3)  we want to be nice to other processes while seeking so we
105125675Ssam **  	break the request up into smaller requests.
105225675Ssam **  4) we don't allow writes after end of tape is reached.
105325675Ssam */
105425675Ssam 
105525675Ssam cybuf_write(request, cq)
105625675Ssam register struct buf	*request;
105725675Ssam register struct buf	*cq;
105825675Ssam {
105925675Ssam 	register int		unit = CYUNIT(request->b_dev);
106025675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
106125675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
106225675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
106325675Ssam 	register int		addr, command, bus_lock;
106425675Ssam 
106525675Ssam 	if(ui->eot && (request->b_blkno >= ui->blkno)) {
106625675Ssam 		request->b_error = ENXIO, request->b_flags |= B_ERROR;
106725675Ssam 		request->b_resid = request->b_bcount;
106825675Ssam 		longjmp(&ci->environ);
106924000Ssam 	}
107025675Ssam 	if(cyseek(request, cq)) {
107125675Ssam 		ui->cleanup = cywrite_2_fm;
107225675Ssam 		ui->blkno++;
107325675Ssam 		if(request->b_bcount > ci->bs)
107425675Ssam 			command = WRIT_TA, bus_lock = CW_LOCK;
107525675Ssam 		else
107625675Ssam 			command = WRIT_BU, bus_lock = 0;
107725675Ssam 		addr = vbastart(request, (caddr_t)ci->rawbuf, (long *)ci->map,
107825675Ssam 		    ci->utl);
107925675Ssam 		load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
108025675Ssam 		cyexecute(command,request->b_bcount,addr,bus_lock,unit,5,FALSE);
108125675Ssam 		vbadone(request, (caddr_t)ci->rawbuf, (long *)ci->map, ci->utl);
108225675Ssam 		cydone(cq);
108325675Ssam 	}
108425675Ssam }
108524000Ssam 
108624000Ssam 
108725675Ssam /*
108825675Ssam **	cyseek is used by the block device to position the tape correctly
108925675Ssam **  before each read or write request.
109025675Ssam **
109125675Ssam **  The special cases are:
109225675Ssam **  1)  we can hit end of tape while seeking.
109325675Ssam **  2)  we want to be nice to other processes while seeking so we
109425675Ssam **  	break the request up into smaller requests.
109525675Ssam */
109625675Ssam cyseek(request, cq)
109725675Ssam register struct buf	*request;
109825675Ssam register struct buf	*cq;
109925675Ssam {
110025675Ssam 	register int		unit = CYUNIT(request->b_dev);
110125675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
110225675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
110325675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
110424000Ssam 
110525675Ssam #ifdef lint
110625675Ssam 	cq = cq;
110725675Ssam #endif
110825675Ssam 	if(request->b_blkno < ui->blkno) {
110925675Ssam 		register int	count;
111024000Ssam 
111125675Ssam 		(*ui->cleanup)(unit, MAINTAIN_POSITION);
111225675Ssam 		count = ((request->b_blkno+1) == ui->blkno) ? 2 : 1;
111325675Ssam 		ui->blkno -= count;
111425675Ssam 		cyexecute(SPAC_FM, (long)1, 0, CW_REV, unit, 10, FALSE);
111525675Ssam 		if(!ui->eof)
111625675Ssam 			return FALSE;
111725675Ssam 		ui->eof = FALSE;
111825675Ssam 		request->b_blkno = ui->blkno + 1;
111925675Ssam 	}
112025675Ssam 	if(request->b_blkno > ui->blkno) {
112125675Ssam 		if((ui->cleanup != cyno_op) || ui->eof || ui->eot) {
112225675Ssam 			request->b_resid = request->b_bcount;
112325675Ssam 			request->b_error = ENXIO, request->b_flags |= B_ERROR;
112425675Ssam 			longjmp(&ci->environ);
112524000Ssam 		}
112625675Ssam 		ui->blkno++;
112725675Ssam 		cyexecute(SPAC_FM, (long)1, 0, 0, unit, 10, FALSE);
112825675Ssam 		return FALSE;
112925675Ssam 	}
113025675Ssam 	return TRUE;
113125675Ssam }
113224000Ssam 
113324000Ssam 
113425675Ssam /*
113525675Ssam */
113625675Ssam 
113725675Ssam cywrite_eov(request, cq)
113825675Ssam register struct buf	*request;
113925675Ssam register struct buf	*cq;
114025675Ssam {
114125675Ssam 	extern int		cyno_op();
114225675Ssam 	register int		unit = CYUNIT(request->b_dev);
114325675Ssam 	register unit_tab	*ui = &unit_info[CYUNIT(unit)];
114425675Ssam 
114525675Ssam 	if(ui->cleanup != cyno_op) {
114625675Ssam 		(*ui->cleanup)(unit, DONT_MAINTAIN_POSITION);
114725675Ssam 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
114825675Ssam 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
114925675Ssam 		unit_info[unit].cleanup = cyno_op;
115025675Ssam 		ui->blkno = 0;
115124000Ssam 	}
115225675Ssam 	cydone(cq);
115325675Ssam }
115425675Ssam 
115525675Ssam 
115625675Ssam /*
115725675Ssam **	Do nothing
115825675Ssam */
115925675Ssam /*ARGSUSED*/
116025675Ssam cyno_op(unit, action)
116125675Ssam int	unit, action;
116225675Ssam {
116325675Ssam }
116425675Ssam 
116525675Ssam 
116625675Ssam /*
116725675Ssam **	Write 0 file marks to tape
116825675Ssam */
116925675Ssam /*ARGSUSED*/
117025675Ssam cywrite_0_fm(unit, action)
117125675Ssam int	unit, action;
117225675Ssam {
117325675Ssam 	unit_info[unit].cleanup = cyno_op;
117425675Ssam }
117525675Ssam 
117625675Ssam 
117725675Ssam /*
117825675Ssam **	Write 1 file mark to tape
117925675Ssam */
118025675Ssam 
118125675Ssam cywrite_1_fm(unit, action)
118225675Ssam int	unit, action;
118325675Ssam {
118425675Ssam 
118525675Ssam 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
118625675Ssam 	if(action == MAINTAIN_POSITION) {
118725675Ssam 		cyexecute(SPACE, (long)2, 0, CW_REV, unit, 10, FALSE);
118825675Ssam 		cyexecute(SPACE, (long)1, 0, 0, unit, 10, FALSE);
118924000Ssam 	}
119025675Ssam 	unit_info[unit].cleanup = cyno_op;
119124000Ssam }
119224000Ssam 
119325675Ssam 
119425675Ssam /*
119525675Ssam **	Write 2 file marks to tape
119625675Ssam */
119725675Ssam 
119825675Ssam cywrite_2_fm(unit, action)
119925675Ssam int	unit, action;
120024000Ssam {
120124000Ssam 
120225675Ssam 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
120325675Ssam 	cyexecute(WRIT_FM, (long)1, 0, 0, unit, 5, FALSE);
120425675Ssam 	if(action == MAINTAIN_POSITION) {
120525675Ssam 		cyexecute(SPACE, (long)3, 0, CW_REV, unit, 10, FALSE);
120625675Ssam 		cyexecute(SPACE, (long)1, 0, 0, unit, 2, FALSE);
120724000Ssam 	}
120825675Ssam 	unit_info[unit].cleanup = cyno_op;
120924000Ssam }
121024000Ssam 
121125675Ssam 
121225675Ssam extern	int cytimeout();
121325675Ssam extern	int cy_normal_path();
121425675Ssam /*
121525675Ssam **	Cyexecute is used to start all commands to the controller.  We
121625675Ssam **  do all common code here before starting.
121725675Ssam */
121825675Ssam 
121925675Ssam cyexecute(command, count, addr, control_flags, unit, time, interupt_routine)
122025675Ssam 	register int command;
122125675Ssam 	long count;
122225675Ssam 	int addr, control_flags, unit, time, interupt_routine;
122324000Ssam {
122425675Ssam 	register int		priority;
122525675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
122625675Ssam 	register unit_tab	*ui = &unit_info[unit];
122725675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
122825675Ssam 	register struct buf	*request = ui->u_queue.av_forw;
122924000Ssam 
123025675Ssam 	ci->tpb.cmd = command;
123125675Ssam 	ci->tpb.control = ui->control_proto | control_flags;
123225675Ssam 	ci->tpb.status = ci->tpb.count = (short)0;
123325675Ssam 	load_mbus_addr((caddr_t)addr, (short *)&ci->tpb.data_ptr);
123425675Ssam 	switch(command) {
123525675Ssam 		case READ_BU:
123625675Ssam 		case READ_TA:
123725675Ssam 		case WRIT_BU:
123825675Ssam 		case WRIT_TA:
123925675Ssam 			ci->tpb.size = MULTIBUS_SHORT((short)count);
124025675Ssam 			ci->tpb.rec_over = (short)0;
124125675Ssam 			break;
124225675Ssam 		default:
124325675Ssam 			ci->tpb.size = (short)0;
124425675Ssam 			ci->tpb.rec_over = MULTIBUS_SHORT((short)count);
124525675Ssam 			break;
124625675Ssam 	}
124725675Ssam 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
124825675Ssam 	if(!interupt_routine)
124925675Ssam 		ci->last = ci->tpb;
125025675Ssam 	/*
125125675Ssam 	gag! but it the last possible moment to wait
125225675Ssam 	for this controller to get out of it's own way.....
125325675Ssam 	*/
125425675Ssam 	uncache(&ci->ccb.gate);
125525675Ssam 	while(ci->ccb.gate == GATE_CLOSED)
125625675Ssam 		uncache(&ci->ccb.gate);
125725675Ssam 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
125825675Ssam 	ci->ccb.ccw = NORMAL_INTERUPT;
125925675Ssam 	ci->ccb.gate = GATE_CLOSED;
126025675Ssam 	if(!interupt_routine)
126125675Ssam 		ci->interupt_path = cy_normal_path;
126225675Ssam 	timeout(cytimeout, (caddr_t)ctlr, time*60);
126325675Ssam 	priority = spl3();
126425675Ssam 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
126525675Ssam 	if(!interupt_routine) {
126625675Ssam 		sleep((caddr_t)ci, PRIBIO+3);
126725675Ssam 		splx(priority);
126825675Ssam 		if(request->b_flags & B_ERROR) {
126925675Ssam 			if((command == READ_BU) || (command == READ_TA) ||
127025675Ssam 			    (command == WRIT_BU) || (command == WRIT_TA))
127125675Ssam 				vbadone(request, (caddr_t)ci->rawbuf,
127225675Ssam 				     (long *)ci->map,ci->utl);
127325675Ssam 			longjmp(&ci->environ);
127424000Ssam 		}
127524000Ssam 		return;
127625675Ssam 	}
127725675Ssam 	splx(priority);
127824000Ssam }
127924000Ssam 
128025675Ssam 
128125675Ssam /*
128225675Ssam **	cytimeout is the interupt timeout routine.  We assume that a
128325675Ssam **  particular command has gone astray, so we completely reset the controller,
128425675Ssam **  and call the interupt routine to help us clean up.  Before the interupt
128525675Ssam **  routine is called we jam a controller timeout value in the status register
128625675Ssam **  to fake out the calling routines.
128725675Ssam */
128825675Ssam 
128925675Ssam cytimeout(ctlr)
129025675Ssam register int	ctlr;
129124000Ssam {
129225675Ssam 	register int	priority = spl3();
129325675Ssam 	register char	*ctlr_vaddr = cyminfo[ctlr]->um_addr;
129425675Ssam 	register int	tmp_stat;
129524000Ssam 
129625675Ssam 	uncache(&ctlr_info[ctlr].tpb.status);
129725675Ssam 	tmp_stat = ctlr_info[ctlr].tpb.status;
129825675Ssam 	CY_RESET(ctlr_vaddr);
129925675Ssam 	cy_init_controller(ctlr_vaddr, ctlr, 0);
130025675Ssam 	splx(priority);
130125675Ssam 	ctlr_info[ctlr].tpb = ctlr_info[ctlr].last;
130225675Ssam 	ctlr_info[ctlr].tpb.status = (tmp_stat & ~CS_ERm) | CS_OL | ER_TIMOUT;
130325675Ssam 	cyintr(ctlr);
130424000Ssam }
130524000Ssam 
130625675Ssam /*
130725675Ssam **	Cyintr is the interupt routine for the Tapemaster controller.
130825675Ssam **
130925675Ssam **	Due to controller problems, the first thing we have to do is turn
131025675Ssam **  off the Tapemaster interupting mechanism.  If we don't we will be flooded
131125675Ssam **  with bogus interupts and the system will spend all it's time processing
131225675Ssam **  them.  To Turn the interupts off we issue a NOOP command with the 'turn
131325675Ssam **  off interupts' code in the ccb.
131425675Ssam **
131525675Ssam **	  take note that since this command TURNS OFF the interupts it
131625675Ssam **	  itself CANNOT interupt...  This means that polling must be done
131725675Ssam **	  at sometime to make sure that tis command is completed.  The polling
131825675Ssam **	  is done before the next command is issued to reduce polling (halting
131925675Ssam **	  UNIX) time.
132025675Ssam **
132125675Ssam **	After we turn off interupts we uncache all the values in the tpb
132225675Ssam **  and call the correct processing routine.  This routine can be for normal
132325675Ssam **  interupts or for interupts generated during a retry operation.
132425675Ssam */
132525675Ssam 
132625675Ssam cyintr(ctlr)
132725675Ssam register int ctlr;
132824000Ssam {
132925675Ssam 	extern int		cytimeout();
133025675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
133124000Ssam 
133225675Ssam 	untimeout(cytimeout, (caddr_t)ctlr);
133325675Ssam 	/* turn off interupts for the stupid controller */
133425675Ssam 	ci->ccb.ccw = CLEAR_INTERUPT;
133525675Ssam 	ci->noop.cmd = NO_OP;
133625675Ssam 	ci->noop.control = (short)0;
133725675Ssam 	load_mbus_addr((caddr_t)&ci->noop, ci->ccb.tpb_ptr);
133825675Ssam 	ci->ccb.gate = GATE_CLOSED;
133925675Ssam 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
134025675Ssam 	uncache_tpb(ci);
134125675Ssam 	(*ci->interupt_path)(ctlr);
134224000Ssam }
134324000Ssam 
134424000Ssam 
134525675Ssam /*
134625675Ssam **	This is the portion of the interupt routine that processes all
134725675Ssam **  normal cases i.e. non retry cases.   We check the operations status
134825675Ssam **  if it is retryable we set the interupt path to the retry routines and
134925675Ssam **  start the backward spaceing.  when the spacing is done the retry logic
135025675Ssam **  will be called and this routine will be skipped entirely.
135125675Ssam **
135225675Ssam **	If the command is ok or not retryable we set the status accordingly
135325675Ssam **  and wakeup cyexecute to continue processing.
135425675Ssam */
135525675Ssam 
135625675Ssam cy_normal_path(ctlr)
135725675Ssam register int ctlr;
135824000Ssam {
135925675Ssam 	extern int		cy_retry_path();
136025675Ssam 	extern int		cy_extended_gap_path();
136125675Ssam 	register int		error;
136225675Ssam 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
136325675Ssam 	register struct buf	*uq = cq->b_forw;
136425675Ssam 	register struct buf	*request = uq->av_forw;
136525675Ssam 	register int		unit = CYUNIT(request->b_dev);
136625675Ssam 	register unit_tab	*ui = &unit_info[unit];
136725675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
136824000Ssam 
136925675Ssam 	if (error = cydecode_error(unit, ci->tpb.status)) {
137025675Ssam 		if(error != FATAL) {
137125675Ssam 			if (error == RETRY)
137225675Ssam 				ci->interupt_path = cy_retry_path;
137324000Ssam 			else
137425675Ssam 				ci->interupt_path = cy_extended_gap_path;
137525675Ssam 			cyexecute(SPACE, (long)2, 0, CW_REV, unit, 5, TRUE);
137625675Ssam 			return;
137724000Ssam 		}
137824000Ssam 	}
137925675Ssam 	request->b_resid=request->b_bcount-MULTIBUS_SHORT(ci->tpb.count);
138025675Ssam 	ui->error_count = 0;
138125675Ssam 	ui->last_resid = request->b_resid;
138225675Ssam 	ui->last_status = ci->tpb.status;
138325675Ssam 	ui->last_control = ci->tpb.control;
138425675Ssam 	if (error == FATAL)
138525675Ssam 		request->b_flags |= B_ERROR, request->b_error = EIO;
138625675Ssam 	wakeup((caddr_t)ci);
138724000Ssam }
138824000Ssam 
138924000Ssam 
139025675Ssam /*
139125675Ssam **	Cy_retry_path finishes up the retry sequence for the tape.
139225675Ssam ** If we were going in the reverse direction it means that we have to
139325675Ssam ** space forward to correctly position ourselfs in back of the tape gap
139425675Ssam ** instead of in front of it.  If we were going forward it means that
139525675Ssam ** we are positioned correctly and we can actually restart the instruction
139625675Ssam ** that failed before.
139725675Ssam */
139825675Ssam 
139925675Ssam cy_retry_path(ctlr)
140025675Ssam register int	ctlr;
140124000Ssam {
140225675Ssam 	extern int		cy_do_again_path();
140325675Ssam 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
140425675Ssam 	register struct buf	*uq = cq->b_forw;
140525675Ssam 	register struct buf	*request = uq->av_forw;
140625675Ssam 	register int		unit = CYUNIT(request->b_dev);
140725675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
140824000Ssam 
140925675Ssam 	if(!(ci->tpb.status & CS_OL)) {
141025675Ssam 		ci->interupt_path = cy_normal_path;
141125675Ssam 		cy_normal_path(ctlr);
141225675Ssam 		return;
141325675Ssam 	}
141425675Ssam 	if(ci->tpb.control & CW_REV) {
141525675Ssam 		if(!(ci->tpb.status & CS_LP)) {
141625675Ssam 			ci->interupt_path = cy_do_again_path;
141725675Ssam 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
141825675Ssam 			return;
141924000Ssam 		}
142025675Ssam 		cy_do_again_path(ctlr);
142125675Ssam 	}
142225675Ssam }
142325675Ssam 
142425675Ssam 
142525675Ssam /*
142625675Ssam **
142725675Ssam */
142825675Ssam 
142925675Ssam cy_extended_gap_path(ctlr)
143025675Ssam register int	ctlr;
143125675Ssam {
143225675Ssam 	extern int		cy_do_again_path();
143325675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
143425675Ssam 	register struct buf	*cq = &cyminfo[ctlr]->um_tab;
143525675Ssam 	register struct buf	*uq = cq->b_forw;
143625675Ssam 	register struct buf	*request = uq->av_forw;
143725675Ssam 	register int		unit = CYUNIT(request->b_dev);
143825675Ssam 
143925675Ssam 	if(!(ci->tpb.status & CS_OL)) {
144025675Ssam 		ci->interupt_path = cy_normal_path;
144125675Ssam 		cy_normal_path(ctlr);
144225675Ssam 		return;
144325675Ssam 	}
144425675Ssam 	if(ci->tpb.control & CW_REV) {
144525675Ssam 		if(!(ci->tpb.status & CS_LP)) {
144625675Ssam 			cyexecute(SPACE, (long)1, 0, 0, unit, 5, TRUE);
144725675Ssam 			return;
144824000Ssam 		}
144924000Ssam 	}
145025675Ssam 	ci->interupt_path = cy_do_again_path;
145125675Ssam 	cyexecute(ERASE_F, (long)unit_info[unit].error_count, 0, 0,
145225675Ssam 	    unit, 5, TRUE);
145324000Ssam }
145424000Ssam 
145524000Ssam 
145625675Ssam /*
145725675Ssam **
145825675Ssam */
145924000Ssam 
146025675Ssam cy_do_again_path(ctlr)
146125675Ssam register int	ctlr;
146225675Ssam {
146325675Ssam 	extern int		cy_normal_path();
146425675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
146525675Ssam 
146625675Ssam 	if(!(ci->tpb.status & CS_OL)) {
146725675Ssam 		ci->interupt_path = cy_normal_path;
146825675Ssam 		cy_normal_path(ctlr);
146925675Ssam 		return;
147025675Ssam 	}
147125675Ssam 	ci->tpb = ci->last;
147225675Ssam 	uncache(&ci->ccb.gate);
147325675Ssam 	while(ci->ccb.gate == GATE_CLOSED)
147425675Ssam 		uncache(&ci->ccb.gate);
147525675Ssam 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
147625675Ssam 	ci->ccb.ccw = NORMAL_INTERUPT;
147725675Ssam 	ci->ccb.gate = GATE_CLOSED;
147825675Ssam 	ci->interupt_path = cy_normal_path;
147925675Ssam 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
148025675Ssam }
148125675Ssam 
148225675Ssam 
148324000Ssam /*
148425675Ssam **	for each longword in the tpb we call uncache to  purge it from
148525675Ssam **  the cache.  This is done so that we can correctly access tpb data
148625675Ssam **  that was placed there by the controller.
148725675Ssam */
148825675Ssam 
148925675Ssam uncache_tpb(ci)
149025675Ssam ctlr_tab	*ci;
149124000Ssam {
149225675Ssam 	register long	*ptr = (long *)&ci->tpb;
149325675Ssam 	register int	i;
149424000Ssam 
149525675Ssam 	for(i=0; i<((sizeof(fmt_tpb)+sizeof(long)-1)/sizeof(long)); i++)
149625675Ssam 		uncache(ptr++);
149724000Ssam }
149824000Ssam 
149925675Ssam 
150024000Ssam /*
150125675Ssam **	Cyprint_error is the common printing routine for all messages
150225675Ssam **  that need to print the tape status along with it.  This is so we
150325675Ssam **  we can save space, have consistant messages, and we can send the messages
150425675Ssam **  to the correct places.
150525675Ssam */
150625675Ssam 
150725675Ssam cyprint_err(message, unit, status)
150825675Ssam register char	*message;
150925675Ssam register int	unit, status;
151024000Ssam {
151125675Ssam 	status &= 0xffff;
151225675Ssam 	printf("cy%d: %s!   Status = %x\n", unit, message, status);
151324000Ssam }
151424000Ssam 
151525675Ssam /*
151625675Ssam **	Decode the error to determine whether the previous command was
151725675Ssam **  ok, retryable, or fatal and return the value.  If it was a hardware
151825675Ssam **  problem we print the message to the console, otherwise we print it
151925675Ssam **  to the user's terminal later when execute returns.
152025675Ssam */
152125675Ssam 
152225675Ssam cydecode_error(unit, status)
152325675Ssam register int	unit,	status;
152425675Ssam {
152525675Ssam 	register unit_tab	*ui = &unit_info[unit];
152625675Ssam 	register ctlr_tab	*ci = &ctlr_info[cydinfo[unit]->ui_ctlr];
152725675Ssam 
152825675Ssam 	if(!(status & CS_OL) && (ci->tpb.cmd != OFF_UNL)) {
152925675Ssam 		ui->message = "Drive is not on-line";
153025675Ssam 		cyprint_err(ui->message, unit, status);
153125675Ssam 		return FATAL;
153225675Ssam 	}
153325675Ssam 	ui->bot = ((status & CS_LP) != 0);
153425675Ssam 	ui->eof = ((status & CS_FM) != 0);
153525675Ssam 	switch(status & CS_ERm) {
153625675Ssam 	case ER_EOT:
153725675Ssam 		if(ci->tpb.control & CW_REV) {
153825675Ssam 			ui->bot = TRUE;
153925675Ssam 			ui->eot = FALSE;
154025675Ssam 		}
154125675Ssam 		else if(!ui->eot){
154225675Ssam 			ui->message = "End of tape";
154325675Ssam 			ui->bot = FALSE;
154425675Ssam 			ui->eot = TRUE;
154525675Ssam 		}
154625675Ssam 	case 0 :
154725675Ssam 	case ER_FM:
154825675Ssam 	case ER_NOSTRM:
154925675Ssam 		return	0;
155025675Ssam 	case ER_TIMOUT:
155125675Ssam 	case ER_TIMOUT1:
155225675Ssam 	case ER_TIMOUT2:
155325675Ssam 	case ER_TIMOUT3:
155425675Ssam 	case ER_TIMOUT4:
155525675Ssam 		ui->message = "Drive timed out during transfer";
155625675Ssam 		cyprint_err(ui->message, unit, status);
155725675Ssam 		return FATAL;
155825675Ssam 	case ER_NEX:
155925675Ssam 		ui->message =
156025675Ssam 		    "Controller referenced non-existant system memory";
156125675Ssam 		cyprint_err(ui->message, unit, status);
156225675Ssam 		return FATAL;
156325675Ssam 	case ER_DIAG:
156425675Ssam 	case ER_JUMPER:
156525675Ssam 		ui->message = "Controller diagnostics failed";
156625675Ssam 		cyprint_err(ui->message, unit, status);
156725675Ssam 		return FATAL;
156825675Ssam 	case ER_STROBE:
156925675Ssam 		if (ci->tpb.cmd == READ_BU) {
157025675Ssam 			ci->last.cmd = READ_TA;
157125675Ssam 			return RETRY;
157225675Ssam 		}
157325675Ssam 		if(ci->tpb.cmd == READ_TA)
157425675Ssam 			return 0;
157525675Ssam 		ui->message = "Unsatisfactory media found";
157625675Ssam 		return	FATAL;
157725675Ssam 	case ER_FIFO:
157825675Ssam 	case ER_NOTRDY:
157925675Ssam 		ui->error_count = 1;
158025675Ssam 		return RETRY;
158125675Ssam 	case ER_PROT:
158225675Ssam 		ui->message = "Tape is write protected";
158325675Ssam 		return FATAL;
158425675Ssam 	case ER_CHKSUM:
158525675Ssam 		ui->message = "Checksum error in controller proms";
158625675Ssam 		cyprint_err(ui->message, unit, status);
158725675Ssam 		return FATAL;
158825675Ssam 	case ER_HARD:
158925675Ssam 		ui->error_count++;
159025675Ssam 		if((ci->tpb.cmd == WRIT_TA) ||
159125675Ssam 		    (ci->tpb.cmd == WRIT_BU) ||
159225675Ssam 		    (ci->tpb.cmd == WRIT_FM)) {
159325675Ssam 			ui->bad_count++;
159425675Ssam 			return EXTEND;
159525675Ssam 		}
159625675Ssam 		ui->message = "Unrecoverable media error during read";
159725675Ssam 		return FATAL;
159825675Ssam 	case ER_PARITY:
159925675Ssam 		if(++ui->error_count < 8)
160025675Ssam 			return	RETRY;
160125675Ssam 		ui->message = "Unrecoverable tape parity error";
160225675Ssam 		return FATAL;
160325675Ssam 	case ER_BLANK:
160425675Ssam 		ui->message="Blank tape found (data expected)";
160525675Ssam 		return FATAL;
160625675Ssam 	case ER_HDWERR:
160725675Ssam 	default:
160825675Ssam 		ui->message = "Unrecoverble hardware error";
160925675Ssam 		cyprint_err(ui->message, unit, status);
161025675Ssam 		return FATAL;
161125675Ssam 	}
161225675Ssam }
161325675Ssam 
161425675Ssam cyread(dev, uio)
161525675Ssam 	dev_t dev;
161625675Ssam 	struct uio *uio;
161725675Ssam {
161825675Ssam 	unit_tab *ui = &unit_info[CYUNIT(dev)];
161925675Ssam 
162025675Ssam 	return (physio(cystrategy, &ui->rawbp, dev, B_READ, cyminsize, uio));
162125675Ssam }
162225675Ssam 
162325675Ssam 
162425675Ssam cywrite(dev, uio)
162525675Ssam 	dev_t dev;
162625675Ssam 	struct uio *uio;
162725675Ssam {
162825675Ssam 	unit_tab *ui = &unit_info[CYUNIT(dev)];
162925675Ssam 
163025675Ssam 	return (physio(cystrategy,&ui->rawbp, dev, B_WRITE, cyminsize, uio));
163125675Ssam }
163225675Ssam 
163325675Ssam /*ARGSUSED*/
163425675Ssam cyioctl(dev, cmd, data, flag)
163525675Ssam 	dev_t dev;
163625675Ssam 	caddr_t data;
163725675Ssam {
163825675Ssam 
163925675Ssam 	switch (cmd) {
164025675Ssam 
164125675Ssam 	case MTIOCTOP: {
164225675Ssam 		struct mtop *mp = (struct mtop *)data;
164325675Ssam 
164425675Ssam 		if (mp->mt_op <= DO_WAIT)
164525675Ssam 			return (cycmd(dev, (int)mp->mt_op, (int)mp->mt_count));
164625675Ssam 		return (EIO);
164725675Ssam 	}
164825675Ssam 
164925675Ssam 	case MTIOCGET: {
165025675Ssam 		register unit_tab *ui = &unit_info[CYUNIT(dev)];
165125675Ssam 		register struct mtget *mp = (struct mtget *)data;
165225675Ssam 
165325675Ssam 		mp->mt_type = MT_ISCY;
165425675Ssam 		mp->mt_dsreg = ui->last_control;
165525675Ssam 		mp->mt_erreg = ui->last_status;
165625675Ssam 		mp->mt_resid = ui->last_resid;
165725675Ssam 		mp->mt_fileno = ui->file_number;
165825675Ssam 		mp->mt_blkno = ui->blkno;
165925675Ssam 		cycmd(dev, DO_STAT, 1);
166025675Ssam 		break;
166125675Ssam 	}
166225675Ssam 
166325675Ssam 	default:
166425675Ssam 		return (ENXIO);
166525675Ssam 	}
166625675Ssam 	return (0);
166725675Ssam }
166825675Ssam 
166925675Ssam /*
167025675Ssam  * Dump routine.
167125675Ssam  */
167224000Ssam cydump(dev)
167325675Ssam 	dev_t dev;
167424000Ssam {
167525675Ssam 	register int		unit = CYUNIT(dev);
167625675Ssam 	register int		ctlr = cydinfo[unit]->ui_ctlr;
167725675Ssam 	register unit_tab	*ui = &unit_info[unit];
167825675Ssam 	register ctlr_tab	*ci = &ctlr_info[ctlr];
167925675Ssam 	register int		blk_siz;
168025675Ssam 	register int		num = maxfree;
168125675Ssam 	register int		start = 0x800;
168224000Ssam 
168325675Ssam 	if ((unit >= NCY) || cydinfo[unit])
168424000Ssam 		return(ENXIO);
168525675Ssam 	ui->control_proto = CW_LOCK | CW_25ips | CW_16bits;
168625675Ssam 	if (cywait(&ci->ccb))
168725675Ssam 		return(EFAULT);
168824000Ssam 	while (num > 0) {
168925675Ssam 		blk_siz = num > TBUFSIZ ? TBUFSIZ : num;
169025675Ssam 		bcopy((caddr_t)(start*NBPG), (caddr_t)ci->rawbuf,
169125675Ssam 		    (unsigned)(blk_siz*NBPG));
169225675Ssam 		ci->tpb.cmd = WRIT_TA;
169325675Ssam 		ci->tpb.control = ui->control_proto;
169425675Ssam 		ci->tpb.status = 0;
169525675Ssam 		ci->tpb.size = MULTIBUS_SHORT(blk_siz*NBPG);
169625675Ssam 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
169725675Ssam 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
169825675Ssam 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
169925675Ssam 		ci->ccb.gate = GATE_CLOSED;
170025675Ssam 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
170125675Ssam 		start += blk_siz;
170225675Ssam 		num -= blk_siz;
170325675Ssam 		if (cywait(&ci->ccb))
170425675Ssam 			return(EFAULT);
170525675Ssam 		uncache(&ci->tpb);
170625675Ssam 		if (ci->tpb.status&CS_ERm)		/* error */
170724000Ssam 			return (EIO);
170824000Ssam 	}
170925675Ssam 	for(num=0; num<2; num++) {
171025675Ssam 		ci->tpb.cmd = WRIT_FM;
171125675Ssam 		ci->tpb.control = ui->control_proto;
171225675Ssam 		ci->tpb.status = ci->tpb.size = 0;
171325675Ssam 		ci->tpb.count = MULTIBUS_SHORT(1);
171425675Ssam 		load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
171525675Ssam 		load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
171625675Ssam 		load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
171725675Ssam 		ci->ccb.gate = GATE_CLOSED;
171825675Ssam 		CY_ATTENTION(cyminfo[ctlr]->um_addr);
171925675Ssam 		if (cywait(&ci->ccb))
172025675Ssam 			return(EFAULT);
172125675Ssam 		uncache(&ci->tpb);
172225675Ssam 		if (ci->tpb.status&CS_ERm)		/* error */
172325675Ssam 			return (EIO);
172425675Ssam 	}
172525675Ssam 	ci->tpb.cmd = REWD_OV;
172625675Ssam 	ci->tpb.control = ui->control_proto;
172725675Ssam 	ci->tpb.status = ci->tpb.size = 0;
172825675Ssam 	ci->tpb.count = MULTIBUS_SHORT(1);
172925675Ssam 	load_mbus_addr((caddr_t)0, ci->tpb.link_ptr);
173025675Ssam 	load_mbus_addr((caddr_t)ci->rawbuf, (short *)&ci->tpb.data_ptr);
173125675Ssam 	load_mbus_addr((caddr_t)&ci->tpb, ci->ccb.tpb_ptr);
173225675Ssam 	ci->ccb.gate = GATE_CLOSED;
173325675Ssam 	CY_ATTENTION(cyminfo[ctlr]->um_addr);
173425675Ssam 	if (cywait(&ci->ccb))
173525675Ssam 		return EFAULT;
173625675Ssam 	uncache(&ci->tpb);
173725675Ssam 	return 0;
173824000Ssam }
173924000Ssam 
174025675Ssam /*
174125675Ssam  * Poll until the controller is ready.
174225675Ssam  */
174325675Ssam cywait(cp)
174425675Ssam 	register fmt_ccb *cp;
174524000Ssam {
174625675Ssam 	register int i = 5000;
174724000Ssam 
174825675Ssam 	uncache(&cp->gate);
174925675Ssam 	while (i-- > 0 && cp->gate == GATE_CLOSED) {
175024000Ssam 		DELAY(1000);
175125675Ssam 		uncache(&cp->gate);
175224000Ssam 	}
175325675Ssam 	return (i <= 0);
175424000Ssam }
175524000Ssam 
175625675Ssam /*
175725675Ssam  * Load a 20 bit pointer into the i/o registers.
175825675Ssam  */
175925675Ssam load_mbus_addr(in, out)
176025675Ssam 	caddr_t in;
176125675Ssam 	short *out;
176224000Ssam {
176325675Ssam 	register int tmp_in = (int)in;
176425675Ssam 	register char *out_ptr = (char *)out;
176525675Ssam 
176625675Ssam 	*out_ptr++ = (char)(tmp_in & 0xff);
176725675Ssam 	*out_ptr++ = (char)((tmp_in >> 8) & 0xff);
176825675Ssam 	*out_ptr++ = (char)0;
176925675Ssam 	*out_ptr++ = (char)((tmp_in & 0xf0000) >> 12);
177024000Ssam }
177124000Ssam 
177225675Ssam /*
177325675Ssam **	CYMINSIZE s supposed to adjust the buffer size for any raw i/o.
177425675Ssam **  since tapes can not read  the tail end of partial blocks we ignore
177525675Ssam **  this request and strategy will return an appropriate error message later.
177625675Ssam **
177725675Ssam **	If this is not done UNIX will lose data that is on the tape.
177825675Ssam */
177925675Ssam unsigned
178025675Ssam cyminsize(bp)
178125675Ssam 	struct buf *bp;
178224000Ssam {
178325675Ssam 	if (bp->b_bcount > MAX_BLOCKSIZE)
178425675Ssam 		bp->b_bcount = MAX_BLOCKSIZE;
178524000Ssam }
178624000Ssam 
178725675Ssam /*
178825675Ssam  * Unconditionally reset all controllers to their initial state.
178925675Ssam  */
179025675Ssam cyreset(vba)
179125675Ssam 	int vba;
179224000Ssam {
179325675Ssam 	register caddr_t addr;
179425675Ssam 	register int ctlr;
179524000Ssam 
179625675Ssam 	for (ctlr = 0; ctlr < NCY; ctlr++)
179725675Ssam 		if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
179825675Ssam 			addr = cyminfo[ctlr]->um_addr;
179925675Ssam 			CY_RESET(addr);
180025675Ssam 			if (!cy_init_controller(addr, ctlr, 0)) {
180125675Ssam 				printf("cy%d: reset failed\n", ctlr);
180225675Ssam 				cyminfo[ctlr] = NULL;
180325675Ssam 			}
180425675Ssam 		}
180524000Ssam }
180624000Ssam #endif
1807