134487Skarels /*
234487Skarels * Copyright (c) 1988 Regents of the University of California.
334487Skarels * All rights reserved.
434487Skarels *
534487Skarels * This code is derived from software contributed to Berkeley by
634487Skarels * Computer Consoles Inc.
734487Skarels *
844533Sbostic * %sccs.include.redist.c%
934487Skarels *
10*49432Sbostic *
11*49432Sbostic * @(#)cy.c 7.8 (Berkeley) 05/08/91
1234487Skarels */
1324000Ssam
1425979Ssam #include "yc.h"
1525675Ssam #if NCY > 0
1624000Ssam /*
1725675Ssam * Cipher Tapemaster driver.
1824000Ssam */
1930371Skarels #define CYDEBUG
2030371Skarels #ifdef CYDEBUG
2125675Ssam int cydebug = 0;
2230371Skarels #define dlog(params) if (cydebug) log params
2330371Skarels #else
2430371Skarels #define dlog(params) /* */
2530371Skarels #endif
2624000Ssam
2745798Sbostic #include "sys/param.h"
2845798Sbostic #include "sys/systm.h"
2945798Sbostic #include "sys/vm.h"
3045798Sbostic #include "sys/buf.h"
3145798Sbostic #include "sys/file.h"
3245798Sbostic #include "sys/signal.h"
3345798Sbostic #include "sys/ioctl.h"
3445798Sbostic #include "sys/mtio.h"
3545798Sbostic #include "sys/errno.h"
3645798Sbostic #include "sys/cmap.h"
3745798Sbostic #include "sys/time.h"
3845798Sbostic #include "sys/kernel.h"
3945798Sbostic #include "sys/syslog.h"
4045798Sbostic #include "sys/tprintf.h"
4124000Ssam
4245798Sbostic #include "../include/cpu.h"
4345798Sbostic #include "../include/mtpr.h"
4445798Sbostic #include "../include/pte.h"
4529952Skarels
4645798Sbostic #include "../vba/vbavar.h"
4725979Ssam #define CYERROR
4845798Sbostic #include "../vba/cyreg.h"
4924000Ssam
5025979Ssam /*
5125979Ssam * There is a ccybuf per tape controller.
5225979Ssam * It is used as the token to pass to the internal routines
5325979Ssam * to execute tape ioctls, and also acts as a lock on the slaves
5425979Ssam * on the controller, since there is only one per controller.
5525979Ssam * In particular, when the tape is rewinding on close we release
5625979Ssam * the user process but any further attempts to use the tape drive
5725979Ssam * before the rewind completes will hang waiting for ccybuf.
5825979Ssam */
5925979Ssam struct buf ccybuf[NCY];
6024000Ssam
6125979Ssam int cyprobe(), cyslave(), cyattach();
6225979Ssam struct buf ycutab[NYC];
6325979Ssam short yctocy[NYC];
6425675Ssam struct vba_ctlr *cyminfo[NCY];
6525979Ssam struct vba_device *ycdinfo[NYC];
6625857Ssam long cystd[] = { 0 };
6725857Ssam struct vba_driver cydriver =
6825979Ssam { cyprobe, cyslave, cyattach, 0, cystd, "yc", ycdinfo, "cy", cyminfo };
6924000Ssam
7025979Ssam /* bits in minor device */
7125979Ssam #define YCUNIT(dev) (minor(dev)&03)
7225979Ssam #define CYUNIT(dev) (yctocy[YCUNIT(dev)])
7325979Ssam #define T_NOREWIND 0x04
7430371Skarels #define T_1600BPI 0x00 /* pseudo */
7530371Skarels #define T_3200BPI 0x08 /* unused */
7625979Ssam
7725979Ssam #define INF 1000000L /* close to infinity */
7825979Ssam
7924000Ssam /*
8025979Ssam * Software state and shared command areas per controller.
8125979Ssam *
8230719Skarels * The i/o intermediate buffer must be allocated in startup()
8330719Skarels * so its address will fit in 20-bits (YECH!!!!!!!!!!!!!!).
8424000Ssam */
8525979Ssam struct cy_softc {
8625979Ssam int cy_bs; /* controller's buffer size */
8725979Ssam struct cyscp *cy_scp; /* system configuration block address */
8825979Ssam struct cyccb cy_ccb; /* channel control block */
8925979Ssam struct cyscb cy_scb; /* system configuration block */
9025979Ssam struct cytpb cy_tpb; /* tape parameter block */
9125979Ssam struct cytpb cy_nop; /* nop parameter block for cyintr */
9230719Skarels struct vb_buf cy_rbuf; /* vba resources */
9325979Ssam } cy_softc[NCY];
9424000Ssam
9525979Ssam /*
9625979Ssam * Software state per tape transport.
9725979Ssam */
9825979Ssam struct yc_softc {
9925979Ssam char yc_openf; /* lock against multiple opens */
10025979Ssam char yc_lastiow; /* last operation was a write */
10125979Ssam short yc_tact; /* timeout is active */
10225979Ssam long yc_timo; /* time until timeout expires */
10325979Ssam u_short yc_control; /* copy of last tpcb.tpcontrol */
10425979Ssam u_short yc_status; /* copy of last tpcb.tpstatus */
10525979Ssam u_short yc_resid; /* copy of last bc */
10625979Ssam u_short yc_dens; /* prototype control word with density info */
10744398Smarc tpr_t yc_tpr; /* handle for tprintf */
10825979Ssam daddr_t yc_blkno; /* block number, for block device tape */
10925979Ssam daddr_t yc_nxrec; /* position of end of tape, if known */
11030371Skarels int yc_blksize; /* current tape blocksize estimate */
11130371Skarels int yc_blks; /* number of I/O operations since open */
11230371Skarels int yc_softerrs; /* number of soft I/O errors since open */
11325979Ssam } yc_softc[NYC];
11424000Ssam
11524000Ssam /*
11625979Ssam * States for vm->um_tab.b_active, the per controller state flag.
11725979Ssam * This is used to sequence control in the driver.
11824000Ssam */
11925979Ssam #define SSEEK 1 /* seeking */
12025979Ssam #define SIO 2 /* doing seq i/o */
12125979Ssam #define SCOM 3 /* sending control command */
12225979Ssam #define SREW 4 /* sending a rewind */
12325979Ssam #define SERASE 5 /* erase inter-record gap */
12425979Ssam #define SERASED 6 /* erased inter-record gap */
12524000Ssam
12625979Ssam /* there's no way to figure these out dynamically? -- yech */
12725979Ssam struct cyscp *cyscp[] =
12825979Ssam { (struct cyscp *)0xc0000c06, (struct cyscp *)0xc0000c16 };
12925979Ssam #define NCYSCP (sizeof (cyscp) / sizeof (cyscp[0]))
13025979Ssam
cyprobe(reg,vm)13125857Ssam cyprobe(reg, vm)
13225857Ssam caddr_t reg;
13325857Ssam struct vba_ctlr *vm;
13425675Ssam {
13525857Ssam register br, cvec; /* must be r12, r11 */
13630371Skarels register struct cy_softc *cy;
13730371Skarels int ctlr = vm->um_ctlr;
13825675Ssam
13930294Ssam #ifdef lint
14030294Ssam br = 0; cvec = br; br = cvec;
14130294Ssam cyintr(0);
14230294Ssam #endif
14325857Ssam if (badcyaddr(reg+1))
14425675Ssam return (0);
14530371Skarels if (ctlr > NCYSCP || cyscp[ctlr] == 0) /* XXX */
14630371Skarels return (0);
14730371Skarels cy = &cy_softc[ctlr];
14830371Skarels cy->cy_scp = cyscp[ctlr]; /* XXX */
14925979Ssam /*
15025979Ssam * Tapemaster controller must have interrupt handler
15125979Ssam * disable interrupt, so we'll just kludge things
15225979Ssam * (stupid multibus non-vectored interrupt crud).
15325979Ssam */
15430371Skarels if (cyinit(ctlr, reg)) {
15530371Skarels uncache(&cy->cy_tpb.tpcount);
15630371Skarels cy->cy_bs = htoms(cy->cy_tpb.tpcount);
15730371Skarels /*
15830371Skarels * Setup nop parameter block for clearing interrupts.
15930371Skarels */
16030371Skarels cy->cy_nop.tpcmd = CY_NOP;
16130371Skarels cy->cy_nop.tpcontrol = 0;
16230371Skarels /*
16330371Skarels * Allocate page tables.
16430371Skarels */
16530719Skarels if (cybuf == 0) {
16630719Skarels printf("no cy buffer!!!\n");
16730719Skarels return (0);
16830719Skarels }
16930719Skarels cy->cy_rbuf.vb_rawbuf = cybuf + ctlr * CYMAXIO;
17031737Skarels if (vbainit(&cy->cy_rbuf, CYMAXIO, VB_20BIT) == 0) {
17131737Skarels printf("cy%d: vbainit failed\n", ctlr);
17231737Skarels return (0);
17331737Skarels }
17430371Skarels
17530371Skarels br = 0x13, cvec = 0x80; /* XXX */
17630371Skarels return (sizeof (struct cyccb));
17730371Skarels } else
17830371Skarels return (0);
17925675Ssam }
18025675Ssam
18124000Ssam /*
18225857Ssam * Check to see if a drive is attached to a controller.
18325857Ssam * Since we can only tell that a drive is there if a tape is loaded and
18425857Ssam * the drive is placed online, we always indicate the slave is present.
18524000Ssam */
18625857Ssam cyslave(vi, addr)
18725857Ssam struct vba_device *vi;
18825857Ssam caddr_t addr;
18924000Ssam {
19025857Ssam
19125857Ssam #ifdef lint
19225857Ssam vi = vi; addr = addr;
19325857Ssam #endif
19425857Ssam return (1);
19525857Ssam }
19625857Ssam
19725857Ssam cyattach(vi)
19825857Ssam struct vba_device *vi;
19925857Ssam {
20025979Ssam register struct cy_softc *cy;
20125979Ssam int ctlr = vi->ui_mi->um_ctlr;
20225857Ssam
20325979Ssam yctocy[vi->ui_unit] = ctlr;
20425979Ssam cy = &cy_softc[ctlr];
20530371Skarels if (vi->ui_slave == 0 && cy->cy_bs)
20630371Skarels printf("; %dkb buffer", cy->cy_bs/1024);
20725857Ssam }
20825857Ssam
20925857Ssam /*
21025857Ssam * Initialize the controller after a controller reset or
21125857Ssam * during autoconfigure. All of the system control blocks
21225857Ssam * are initialized and the controller is asked to configure
21325857Ssam * itself for later use.
21425857Ssam */
cyinit(ctlr,addr)21530371Skarels cyinit(ctlr, addr)
21625979Ssam int ctlr;
21730371Skarels register caddr_t addr;
21825857Ssam {
21925979Ssam register struct cy_softc *cy = &cy_softc[ctlr];
22025675Ssam register int *pte;
22124000Ssam
22224000Ssam /*
22325675Ssam * Initialize the system configuration pointer.
22424000Ssam */
22525675Ssam /* make kernel writable */
22630719Skarels pte = (int *)&Sysmap[btop((int)cy->cy_scp &~ KERNBASE)];
22725675Ssam *pte &= ~PG_PROT; *pte |= PG_KW;
22825979Ssam mtpr(TBIS, cy->cy_scp);
22925675Ssam /* load the correct values in the scp */
23025979Ssam cy->cy_scp->csp_buswidth = CSP_16BITS;
23125979Ssam cyldmba(cy->cy_scp->csp_scb, (caddr_t)&cy->cy_scb);
23225675Ssam /* put it back to read-only */
23325675Ssam *pte &= ~PG_PROT; *pte |= PG_KR;
23425979Ssam mtpr(TBIS, cy->cy_scp);
23525675Ssam
23624000Ssam /*
23725675Ssam * Init system configuration block.
23824000Ssam */
23930371Skarels cy->cy_scb.csb_fixed = CSB_FIXED;
24025675Ssam /* set pointer to the channel control block */
24125979Ssam cyldmba(cy->cy_scb.csb_ccb, (caddr_t)&cy->cy_ccb);
24225675Ssam
24324000Ssam /*
24425675Ssam * Initialize the chanel control block.
24524000Ssam */
24625979Ssam cy->cy_ccb.cbcw = CBCW_CLRINT;
24725979Ssam cy->cy_ccb.cbgate = GATE_OPEN;
24825675Ssam /* set pointer to the tape parameter block */
24925979Ssam cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
25025675Ssam
25124000Ssam /*
25225979Ssam * Issue a nop cmd and get the internal buffer size for buffered i/o.
25324000Ssam */
25425979Ssam cy->cy_tpb.tpcmd = CY_NOP;
25525979Ssam cy->cy_tpb.tpcontrol = CYCW_16BITS;
25625979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
25725979Ssam CY_GO(addr);
25825979Ssam if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
25925979Ssam uncache(&cy->cy_tpb.tpstatus);
26025979Ssam printf("cy%d: timeout or err during init, status=%b\n", ctlr,
26125979Ssam cy->cy_tpb.tpstatus, CYS_BITS);
26225675Ssam return (0);
26325675Ssam }
26425979Ssam cy->cy_tpb.tpcmd = CY_CONFIG;
26525979Ssam cy->cy_tpb.tpcontrol = CYCW_16BITS;
26625979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
26725979Ssam CY_GO(addr);
26825979Ssam if (cywait(&cy->cy_ccb) || (cy->cy_tpb.tpstatus&CYS_ERR)) {
26925979Ssam uncache(&cy->cy_tpb.tpstatus);
27025979Ssam printf("cy%d: configuration failure, status=%b\n", ctlr,
27125979Ssam cy->cy_tpb.tpstatus, CYS_BITS);
27225675Ssam return (0);
27325675Ssam }
27425675Ssam return (1);
27524000Ssam }
27624000Ssam
27725979Ssam int cytimer();
27825979Ssam /*
27925979Ssam * Open the device. Tapes are unique open
28025979Ssam * devices, so we refuse if it is already open.
28125979Ssam * We also check that a tape is available, and
28225979Ssam * don't block waiting here; if you want to wait
28325979Ssam * for a tape you should timeout in user code.
28425979Ssam */
cyopen(dev,flag)28525675Ssam cyopen(dev, flag)
28625979Ssam dev_t dev;
28725675Ssam register int flag;
28825675Ssam {
28925979Ssam register int ycunit;
29025979Ssam register struct vba_device *vi;
29125979Ssam register struct yc_softc *yc;
29225675Ssam
29325979Ssam ycunit = YCUNIT(dev);
29425979Ssam if (ycunit >= NYC || (vi = ycdinfo[ycunit]) == 0 || vi->ui_alive == 0)
29525675Ssam return (ENXIO);
29625979Ssam if ((yc = &yc_softc[ycunit])->yc_openf)
29725979Ssam return (EBUSY);
29830371Skarels yc->yc_openf = 1;
29925979Ssam #define PACKUNIT(vi) \
30025979Ssam (((vi->ui_slave&1)<<11)|((vi->ui_slave&2)<<9)|((vi->ui_slave&4)>>2))
30125979Ssam /* no way to select density */
30225979Ssam yc->yc_dens = PACKUNIT(vi)|CYCW_IE|CYCW_16BITS;
30330371Skarels if (yc->yc_tact == 0) {
30430371Skarels yc->yc_timo = INF;
30530371Skarels yc->yc_tact = 1;
30630371Skarels timeout(cytimer, (caddr_t)dev, 5*hz);
30730371Skarels }
30825979Ssam cycommand(dev, CY_SENSE, 1);
30925979Ssam if ((yc->yc_status&CYS_OL) == 0) { /* not on-line */
31034285Skarels uprintf("cy%d: not online\n", ycunit);
31130439Skarels yc->yc_openf = 0;
31230872Skarels return (EIO);
31325675Ssam }
31425979Ssam if ((flag&FWRITE) && (yc->yc_status&CYS_WP)) {
31534285Skarels uprintf("cy%d: no write ring\n", ycunit);
31630439Skarels yc->yc_openf = 0;
31730872Skarels return (EIO);
31825675Ssam }
31925979Ssam yc->yc_blkno = (daddr_t)0;
32025979Ssam yc->yc_nxrec = INF;
32125979Ssam yc->yc_lastiow = 0;
32230869Skarels yc->yc_blksize = CYMAXIO; /* guess > 0 */
32330371Skarels yc->yc_blks = 0;
32430371Skarels yc->yc_softerrs = 0;
32544398Smarc yc->yc_tpr = tprintf_open();
32625675Ssam return (0);
32725675Ssam }
32825675Ssam
32925979Ssam /*
33025979Ssam * Close tape device.
33125979Ssam *
33225979Ssam * If tape was open for writing or last operation was a write,
33325979Ssam * then write two EOF's and backspace over the last one.
33425979Ssam * Unless this is a non-rewinding special file, rewind the tape.
33525979Ssam * Make the tape available to others.
33625979Ssam */
cyclose(dev,flag)33725675Ssam cyclose(dev, flag)
33825979Ssam dev_t dev;
33930371Skarels int flag;
34025675Ssam {
34130371Skarels struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
34225675Ssam
34325979Ssam if (flag == FWRITE || (flag&FWRITE) && yc->yc_lastiow) {
34434285Skarels cycommand(dev, CY_WEOF, 1); /* can't use count with WEOF */
34534285Skarels cycommand(dev, CY_WEOF, 1);
34625979Ssam cycommand(dev, CY_SREV, 1);
34725675Ssam }
34825979Ssam if ((minor(dev)&T_NOREWIND) == 0)
34925979Ssam /*
35025979Ssam * 0 count means don't hang waiting for rewind complete
35125979Ssam * rather ccybuf stays busy until the operation completes
35225979Ssam * preventing further opens from completing by preventing
35325979Ssam * a CY_SENSE from completing.
35425979Ssam */
35525979Ssam cycommand(dev, CY_REW, 0);
35630371Skarels if (yc->yc_blks > 10 && yc->yc_softerrs > yc->yc_blks / 10)
35730371Skarels log(LOG_INFO, "yc%d: %d soft errors in %d blocks\n",
35830371Skarels YCUNIT(dev), yc->yc_softerrs, yc->yc_blks);
35930371Skarels dlog((LOG_INFO, "%d soft errors in %d blocks\n",
36030371Skarels yc->yc_softerrs, yc->yc_blks));
36144398Smarc tprintf_close(yc->yc_tpr);
36225979Ssam yc->yc_openf = 0;
36330719Skarels return (0);
36425675Ssam }
36525675Ssam
36624000Ssam /*
36725979Ssam * Execute a command on the tape drive a specified number of times.
36824000Ssam */
cycommand(dev,com,count)36925979Ssam cycommand(dev, com, count)
37025979Ssam dev_t dev;
37125979Ssam int com, count;
37224000Ssam {
37325979Ssam register struct buf *bp;
37425675Ssam int s;
37525675Ssam
37625979Ssam bp = &ccybuf[CYUNIT(dev)];
37725675Ssam s = spl3();
37830371Skarels dlog((LOG_INFO, "cycommand(%o, %x, %d), b_flags %x\n",
37930371Skarels dev, com, count, bp->b_flags));
38025979Ssam while (bp->b_flags&B_BUSY) {
38125979Ssam /*
38225979Ssam * This special check is because B_BUSY never
38325979Ssam * gets cleared in the non-waiting rewind case.
38425979Ssam */
38525979Ssam if (bp->b_repcnt == 0 && (bp->b_flags&B_DONE))
38625979Ssam break;
38725979Ssam bp->b_flags |= B_WANTED;
38825979Ssam sleep((caddr_t)bp, PRIBIO);
38925675Ssam }
39025979Ssam bp->b_flags = B_BUSY|B_READ;
39125675Ssam splx(s);
39225979Ssam bp->b_dev = dev;
39325979Ssam bp->b_repcnt = count;
39425979Ssam bp->b_command = com;
39525979Ssam bp->b_blkno = 0;
39625979Ssam cystrategy(bp);
39725979Ssam /*
39825979Ssam * In case of rewind from close; don't wait.
39925979Ssam * This is the only case where count can be 0.
40025979Ssam */
40125979Ssam if (count == 0)
40225979Ssam return;
40330371Skarels biowait(bp);
40425979Ssam if (bp->b_flags&B_WANTED)
40525979Ssam wakeup((caddr_t)bp);
40625979Ssam bp->b_flags &= B_ERROR;
40724000Ssam }
40824000Ssam
cystrategy(bp)40925675Ssam cystrategy(bp)
41025675Ssam register struct buf *bp;
41125675Ssam {
41225979Ssam int ycunit = YCUNIT(bp->b_dev);
41325979Ssam register struct vba_ctlr *vm;
41425979Ssam register struct buf *dp;
41525675Ssam int s;
41625675Ssam
41725979Ssam /*
41825979Ssam * Put transfer at end of unit queue.
41925979Ssam */
42030371Skarels dlog((LOG_INFO, "cystrategy(%o, %x)\n", bp->b_dev, bp->b_command));
42125979Ssam dp = &ycutab[ycunit];
42225675Ssam bp->av_forw = NULL;
42325979Ssam vm = ycdinfo[ycunit]->ui_mi;
42425979Ssam /* BEGIN GROT */
42534507Skarels if (bp->b_flags & B_RAW) {
42630869Skarels if (bp->b_bcount >= CYMAXIO) {
42725979Ssam uprintf("cy%d: i/o size too large\n", vm->um_ctlr);
42830869Skarels bp->b_error = EINVAL;
42925979Ssam bp->b_resid = bp->b_bcount;
43025979Ssam bp->b_flags |= B_ERROR;
43130371Skarels biodone(bp);
43225675Ssam return;
43325675Ssam }
43424000Ssam }
43525979Ssam /* END GROT */
43625675Ssam s = spl3();
43725979Ssam if (dp->b_actf == NULL) {
43825979Ssam dp->b_actf = bp;
43925979Ssam /*
44025979Ssam * Transport not already active...
44125979Ssam * put at end of controller queue.
44225979Ssam */
44325979Ssam dp->b_forw = NULL;
44425979Ssam if (vm->um_tab.b_actf == NULL)
44525979Ssam vm->um_tab.b_actf = dp;
44625979Ssam else
44725979Ssam vm->um_tab.b_actl->b_forw = dp;
44825979Ssam } else
44925979Ssam dp->b_actl->av_forw = bp;
45025979Ssam dp->b_actl = bp;
45125979Ssam /*
45225979Ssam * If the controller is not busy, get it going.
45325979Ssam */
45425979Ssam if (vm->um_tab.b_active == 0)
45525979Ssam cystart(vm);
45624000Ssam splx(s);
45724000Ssam }
45824000Ssam
45924000Ssam /*
46025979Ssam * Start activity on a cy controller.
46124000Ssam */
cystart(vm)46225979Ssam cystart(vm)
46325979Ssam register struct vba_ctlr *vm;
46424000Ssam {
46525979Ssam register struct buf *bp, *dp;
46625979Ssam register struct yc_softc *yc;
46725979Ssam register struct cy_softc *cy;
46825979Ssam int ycunit;
46925979Ssam daddr_t blkno;
47024000Ssam
47130371Skarels dlog((LOG_INFO, "cystart()\n"));
47225979Ssam /*
47325979Ssam * Look for an idle transport on the controller.
47425979Ssam */
47525979Ssam loop:
47625979Ssam if ((dp = vm->um_tab.b_actf) == NULL)
47725675Ssam return;
47825979Ssam if ((bp = dp->b_actf) == NULL) {
47925979Ssam vm->um_tab.b_actf = dp->b_forw;
48025979Ssam goto loop;
48125675Ssam }
48225979Ssam ycunit = YCUNIT(bp->b_dev);
48325979Ssam yc = &yc_softc[ycunit];
48425979Ssam cy = &cy_softc[CYUNIT(bp->b_dev)];
48525979Ssam /*
48625979Ssam * Default is that last command was NOT a write command;
48725979Ssam * if we do a write command we will notice this in cyintr().
48825979Ssam */
48925979Ssam yc->yc_lastiow = 0;
49025979Ssam if (yc->yc_openf < 0 ||
49125979Ssam (bp->b_command != CY_SENSE && (cy->cy_tpb.tpstatus&CYS_OL) == 0)) {
49225979Ssam /*
49325979Ssam * Have had a hard error on a non-raw tape
49425979Ssam * or the tape unit is now unavailable (e.g.
49525979Ssam * taken off line).
49625979Ssam */
49730371Skarels dlog((LOG_INFO, "openf %d command %x status %b\n",
49830371Skarels yc->yc_openf, bp->b_command, cy->cy_tpb.tpstatus, CYS_BITS));
49925979Ssam bp->b_flags |= B_ERROR;
50025979Ssam goto next;
50125675Ssam }
50225979Ssam if (bp == &ccybuf[CYUNIT(bp->b_dev)]) {
50325979Ssam /*
50425979Ssam * Execute control operation with the specified count.
50525979Ssam *
50625979Ssam * Set next state; give 5 minutes to complete
50725979Ssam * rewind or file mark search, or 10 seconds per
50825979Ssam * iteration (minimum 60 seconds and max 5 minutes)
50925979Ssam * to complete other ops.
51025979Ssam */
51125979Ssam if (bp->b_command == CY_REW) {
51225979Ssam vm->um_tab.b_active = SREW;
51325979Ssam yc->yc_timo = 5*60;
51430869Skarels } else if (bp->b_command == CY_FSF ||
51530869Skarels bp->b_command == CY_BSF) {
51630869Skarels vm->um_tab.b_active = SCOM;
51730869Skarels yc->yc_timo = 5*60;
51825979Ssam } else {
51925979Ssam vm->um_tab.b_active = SCOM;
52025979Ssam yc->yc_timo = imin(imax(10*(int)bp->b_repcnt,60),5*60);
52125979Ssam }
52225979Ssam cy->cy_tpb.tprec = htoms(bp->b_repcnt);
52330719Skarels dlog((LOG_INFO, "bpcmd "));
52425979Ssam goto dobpcmd;
52524000Ssam }
52625979Ssam /*
52734507Skarels * For raw I/O, save the current block
52834507Skarels * number in case we have to retry.
52925979Ssam */
53034507Skarels if (bp->b_flags & B_RAW) {
53134507Skarels if (vm->um_tab.b_errcnt == 0) {
53234507Skarels yc->yc_blkno = bp->b_blkno;
53334507Skarels yc->yc_nxrec = yc->yc_blkno + 1;
53434507Skarels }
53534507Skarels } else {
53625979Ssam /*
53734507Skarels * Handle boundary cases for operation
53834507Skarels * on non-raw tapes.
53925979Ssam */
54034507Skarels if (bp->b_blkno > yc->yc_nxrec) {
54134507Skarels /*
54234507Skarels * Can't read past known end-of-file.
54334507Skarels */
54434507Skarels bp->b_flags |= B_ERROR;
54534507Skarels bp->b_error = ENXIO;
54634507Skarels goto next;
54734507Skarels }
54834507Skarels if (bp->b_blkno == yc->yc_nxrec && bp->b_flags&B_READ) {
54934507Skarels /*
55034507Skarels * Reading at end of file returns 0 bytes.
55134507Skarels */
55234507Skarels bp->b_resid = bp->b_bcount;
55334507Skarels clrbuf(bp);
55434507Skarels goto next;
55534507Skarels }
55634507Skarels if ((bp->b_flags&B_READ) == 0)
55734507Skarels /*
55834507Skarels * Writing sets EOF.
55934507Skarels */
56034507Skarels yc->yc_nxrec = bp->b_blkno + 1;
56124000Ssam }
56230719Skarels if ((blkno = yc->yc_blkno) == bp->b_blkno) {
56325979Ssam caddr_t addr;
56425979Ssam int cmd;
56525675Ssam
56625979Ssam /*
56725979Ssam * Choose the appropriate i/o command based on the
56830371Skarels * transfer size, the estimated block size,
56930371Skarels * and the controller's internal buffer size.
57030869Skarels * If the request length is longer than the tape
57130869Skarels * block length, a buffered read will fail,
57230869Skarels * thus, we request at most the size that we expect.
57330869Skarels * We then check for larger records when the read completes.
57425979Ssam * If we're retrying a read on a raw device because
57525979Ssam * the original try was a buffer request which failed
57625979Ssam * due to a record length error, then we force the use
57725979Ssam * of the raw controller read (YECH!!!!).
57825979Ssam */
57925979Ssam if (bp->b_flags&B_READ) {
58030869Skarels if (yc->yc_blksize <= cy->cy_bs &&
58130869Skarels vm->um_tab.b_errcnt == 0)
58230869Skarels cmd = CY_BRCOM;
58330869Skarels else
58425979Ssam cmd = CY_RCOM;
58525979Ssam } else {
58625979Ssam /*
58725979Ssam * On write error retries erase the
58825979Ssam * inter-record gap before rewriting.
58925979Ssam */
59025979Ssam if (vm->um_tab.b_errcnt &&
59125979Ssam vm->um_tab.b_active != SERASED) {
59225979Ssam vm->um_tab.b_active = SERASE;
59325979Ssam bp->b_command = CY_ERASE;
59425979Ssam yc->yc_timo = 60;
59525979Ssam goto dobpcmd;
59625675Ssam }
59725979Ssam cmd = (bp->b_bcount > cy->cy_bs) ? CY_WCOM : CY_BWCOM;
59825675Ssam }
59925979Ssam vm->um_tab.b_active = SIO;
60030719Skarels addr = (caddr_t)vbasetup(bp, &cy->cy_rbuf, 1);
60125979Ssam cy->cy_tpb.tpcmd = cmd;
60225979Ssam cy->cy_tpb.tpcontrol = yc->yc_dens;
60325979Ssam if (cmd == CY_RCOM || cmd == CY_WCOM)
60425979Ssam cy->cy_tpb.tpcontrol |= CYCW_LOCK;
60525979Ssam cy->cy_tpb.tpstatus = 0;
60625979Ssam cy->cy_tpb.tpcount = 0;
60725979Ssam cyldmba(cy->cy_tpb.tpdata, (caddr_t)addr);
60825979Ssam cy->cy_tpb.tprec = 0;
60930869Skarels if (cmd == CY_BRCOM)
61034487Skarels cy->cy_tpb.tpsize = htoms(imin(yc->yc_blksize,
61134487Skarels (int)bp->b_bcount));
61230371Skarels else
61330371Skarels cy->cy_tpb.tpsize = htoms(bp->b_bcount);
61425979Ssam cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
61525979Ssam do
61625979Ssam uncache(&cy->cy_ccb.cbgate);
61725979Ssam while (cy->cy_ccb.cbgate == GATE_CLOSED);
61825979Ssam cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
61925979Ssam cy->cy_ccb.cbcw = CBCW_IE;
62025979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
62130371Skarels dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x size %d\n",
62225979Ssam vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
62330371Skarels htoms(cy->cy_tpb.tpsize)));
62425979Ssam CY_GO(vm->um_addr);
62525979Ssam return;
62624000Ssam }
62725979Ssam /*
62825979Ssam * Tape positioned incorrectly; set to seek forwards
62925979Ssam * or backwards to the correct spot. This happens
63025979Ssam * for raw tapes only on error retries.
63125979Ssam */
63225979Ssam vm->um_tab.b_active = SSEEK;
63330719Skarels if (blkno < bp->b_blkno) {
63425979Ssam bp->b_command = CY_SFORW;
63530719Skarels cy->cy_tpb.tprec = htoms(bp->b_blkno - blkno);
63625979Ssam } else {
63725979Ssam bp->b_command = CY_SREV;
63830719Skarels cy->cy_tpb.tprec = htoms(blkno - bp->b_blkno);
63924000Ssam }
64034487Skarels yc->yc_timo = imin(imax((int)(10 * htoms(cy->cy_tpb.tprec)), 60), 5*60);
64125979Ssam dobpcmd:
64225979Ssam /*
64325979Ssam * Do the command in bp. Reverse direction commands
64425979Ssam * are indicated by having CYCW_REV or'd into their
64525979Ssam * value. For these we must set the appropriate bit
64625979Ssam * in the control field.
64725979Ssam */
64825979Ssam if (bp->b_command&CYCW_REV) {
64925979Ssam cy->cy_tpb.tpcmd = bp->b_command &~ CYCW_REV;
65025979Ssam cy->cy_tpb.tpcontrol = yc->yc_dens | CYCW_REV;
65130719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
65225979Ssam } else {
65325979Ssam cy->cy_tpb.tpcmd = bp->b_command;
65425979Ssam cy->cy_tpb.tpcontrol = yc->yc_dens;
65530719Skarels dlog((LOG_INFO, "cmd %x control %x\n", cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol));
65624000Ssam }
65725979Ssam cy->cy_tpb.tpstatus = 0;
65825979Ssam cy->cy_tpb.tpcount = 0;
65925979Ssam cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
66025979Ssam do
66125979Ssam uncache(&cy->cy_ccb.cbgate);
66225979Ssam while (cy->cy_ccb.cbgate == GATE_CLOSED);
66325979Ssam cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
66425979Ssam cy->cy_ccb.cbcw = CBCW_IE;
66525979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
66630371Skarels dlog((LOG_INFO, "CY_GO(%x) cmd %x control %x rec %d\n",
66725979Ssam vm->um_addr, cy->cy_tpb.tpcmd, cy->cy_tpb.tpcontrol,
66830371Skarels htoms(cy->cy_tpb.tprec)));
66925979Ssam CY_GO(vm->um_addr);
67025979Ssam return;
67125979Ssam next:
67225979Ssam /*
67325979Ssam * Done with this operation due to error or the
67430719Skarels * fact that it doesn't do anything.
67530719Skarels * Dequeue the transfer and continue
67625979Ssam * processing this slave.
67725979Ssam */
67825979Ssam vm->um_tab.b_errcnt = 0;
67925979Ssam dp->b_actf = bp->av_forw;
68030371Skarels biodone(bp);
68125979Ssam goto loop;
68225675Ssam }
68325675Ssam
68425675Ssam /*
68525979Ssam * Cy interrupt routine.
68625675Ssam */
cyintr(cyunit)68730719Skarels cyintr(cyunit)
68830719Skarels int cyunit;
68925675Ssam {
69025979Ssam struct buf *dp;
69124000Ssam register struct buf *bp;
69230719Skarels register struct vba_ctlr *vm = cyminfo[cyunit];
69325979Ssam register struct cy_softc *cy;
69425979Ssam register struct yc_softc *yc;
69530719Skarels int err;
69625979Ssam register state;
69724000Ssam
69830719Skarels dlog((LOG_INFO, "cyintr(%d)\n", cyunit));
69925979Ssam /*
70025979Ssam * First, turn off the interrupt from the controller
70125979Ssam * (device uses Multibus non-vectored interrupts...yech).
70225979Ssam */
70325979Ssam cy = &cy_softc[vm->um_ctlr];
70425979Ssam cy->cy_ccb.cbcw = CBCW_CLRINT;
70530294Ssam cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_nop);
70625979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
70725979Ssam CY_GO(vm->um_addr);
70825979Ssam if ((dp = vm->um_tab.b_actf) == NULL) {
70930371Skarels dlog((LOG_ERR, "cy%d: stray interrupt", vm->um_ctlr));
71024000Ssam return;
71124000Ssam }
71225979Ssam bp = dp->b_actf;
71325979Ssam cy = &cy_softc[cyunit];
71425979Ssam cyuncachetpb(cy);
71530294Ssam yc = &yc_softc[YCUNIT(bp->b_dev)];
71625979Ssam /*
71725984Ssam * If last command was a rewind and tape is
71825984Ssam * still moving, wait for the operation to complete.
71925979Ssam */
72025979Ssam if (vm->um_tab.b_active == SREW) {
72125979Ssam vm->um_tab.b_active = SCOM;
72225979Ssam if ((cy->cy_tpb.tpstatus&CYS_RDY) == 0) {
72325979Ssam yc->yc_timo = 5*60; /* 5 minutes */
72425979Ssam return;
72524000Ssam }
72624000Ssam }
72725979Ssam /*
72825979Ssam * An operation completed...record status.
72925979Ssam */
73025979Ssam yc->yc_timo = INF;
73125979Ssam yc->yc_control = cy->cy_tpb.tpcontrol;
73225979Ssam yc->yc_status = cy->cy_tpb.tpstatus;
73325979Ssam yc->yc_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
73430371Skarels dlog((LOG_INFO, "cmd %x control %b status %b resid %d\n",
73525979Ssam cy->cy_tpb.tpcmd, yc->yc_control, CYCW_BITS,
73630371Skarels yc->yc_status, CYS_BITS, yc->yc_resid));
73725979Ssam if ((bp->b_flags&B_READ) == 0)
73825979Ssam yc->yc_lastiow = 1;
73925979Ssam state = vm->um_tab.b_active;
74025979Ssam vm->um_tab.b_active = 0;
74125979Ssam /*
74225979Ssam * Check for errors.
74325979Ssam */
74425979Ssam if (cy->cy_tpb.tpstatus&CYS_ERR) {
74525979Ssam err = cy->cy_tpb.tpstatus&CYS_ERR;
74630371Skarels dlog((LOG_INFO, "error %d\n", err));
74725979Ssam /*
74825979Ssam * If we hit the end of tape file, update our position.
74925979Ssam */
75025979Ssam if (err == CYER_FM) {
75125979Ssam yc->yc_status |= CYS_FM;
75225979Ssam state = SCOM; /* force completion */
75325979Ssam cyseteof(bp); /* set blkno and nxrec */
75425979Ssam goto opdone;
75525979Ssam }
75625979Ssam /*
75725979Ssam * Fix up errors which occur due to backspacing over
75825979Ssam * the beginning of the tape.
75925979Ssam */
76025979Ssam if (err == CYER_BOT && cy->cy_tpb.tpcontrol&CYCW_REV) {
76125979Ssam yc->yc_status |= CYS_BOT;
76225979Ssam goto ignoreerr;
76325979Ssam }
76425979Ssam /*
76525979Ssam * If we were reading raw tape and the only error was that the
76625979Ssam * record was too long, then we don't consider this an error.
76725979Ssam */
76834507Skarels if ((bp->b_flags & (B_READ|B_RAW)) == (B_READ|B_RAW) &&
76925979Ssam err == CYER_STROBE) {
77025979Ssam /*
77130371Skarels * Retry reads with the command changed to
77230371Skarels * a raw read if necessary. Setting b_errcnt
77325979Ssam * here causes cystart (above) to force a CY_RCOM.
77425979Ssam */
77530869Skarels if (cy->cy_tpb.tpcmd == CY_BRCOM &&
77630719Skarels vm->um_tab.b_errcnt++ == 0) {
77730371Skarels yc->yc_blkno++;
77830371Skarels goto opcont;
77930371Skarels } else
78025979Ssam goto ignoreerr;
78125979Ssam }
78225979Ssam /*
78325979Ssam * If error is not hard, and this was an i/o operation
78425979Ssam * retry up to 8 times.
78525979Ssam */
78634285Skarels if (state == SIO && (CYMASK(err) &
78734285Skarels ((bp->b_flags&B_READ) ? CYER_RSOFT : CYER_WSOFT))) {
78825979Ssam if (++vm->um_tab.b_errcnt < 7) {
78925979Ssam yc->yc_blkno++;
79025979Ssam goto opcont;
79125979Ssam }
79225979Ssam } else
79325979Ssam /*
79425979Ssam * Hard or non-i/o errors on non-raw tape
79525979Ssam * cause it to close.
79625979Ssam */
79734507Skarels if ((bp->b_flags&B_RAW) == 0 &&
79834507Skarels yc->yc_openf > 0)
79925979Ssam yc->yc_openf = -1;
80025979Ssam /*
80125979Ssam * Couldn't recover from error.
80225979Ssam */
80344398Smarc tprintf(yc->yc_tpr,
80430371Skarels "yc%d: hard error bn%d status=%b, %s\n", YCUNIT(bp->b_dev),
80530371Skarels bp->b_blkno, yc->yc_status, CYS_BITS,
80630371Skarels (err < NCYERROR) ? cyerror[err] : "");
80725979Ssam bp->b_flags |= B_ERROR;
80825979Ssam goto opdone;
80930869Skarels } else if (cy->cy_tpb.tpcmd == CY_BRCOM) {
81030869Skarels int reclen = htoms(cy->cy_tpb.tprec);
81130869Skarels
81230869Skarels /*
81330869Skarels * If we did a buffered read, check whether the read
81430869Skarels * was long enough. If we asked the controller for less
81530869Skarels * than the user asked for because the previous record
81630869Skarels * was shorter, update our notion of record size
81730869Skarels * and retry. If the record is longer than the buffer,
81830869Skarels * bump the errcnt so the retry will use direct read.
81930869Skarels */
82030869Skarels if (reclen > yc->yc_blksize && bp->b_bcount > yc->yc_blksize) {
82130869Skarels yc->yc_blksize = reclen;
82230869Skarels if (reclen > cy->cy_bs)
82330869Skarels vm->um_tab.b_errcnt++;
82430869Skarels yc->yc_blkno++;
82530869Skarels goto opcont;
82630869Skarels }
82724000Ssam }
82825979Ssam /*
82925979Ssam * Advance tape control FSM.
83025979Ssam */
83125979Ssam ignoreerr:
83225979Ssam /*
83325979Ssam * If we hit a tape mark update our position.
83425979Ssam */
83525979Ssam if (yc->yc_status&CYS_FM && bp->b_flags&B_READ) {
83625979Ssam cyseteof(bp);
83725979Ssam goto opdone;
83825675Ssam }
83925979Ssam switch (state) {
84024000Ssam
84125979Ssam case SIO:
84225979Ssam /*
84325979Ssam * Read/write increments tape block number.
84425979Ssam */
84525979Ssam yc->yc_blkno++;
84630371Skarels yc->yc_blks++;
84730371Skarels if (vm->um_tab.b_errcnt || yc->yc_status & CYS_CR)
84830371Skarels yc->yc_softerrs++;
84930371Skarels yc->yc_blksize = htoms(cy->cy_tpb.tpcount);
85030371Skarels dlog((LOG_ERR, "blocksize %d", yc->yc_blksize));
85125979Ssam goto opdone;
85224000Ssam
85325979Ssam case SCOM:
85425979Ssam /*
85525979Ssam * For forward/backward space record update current position.
85625979Ssam */
85730294Ssam if (bp == &ccybuf[CYUNIT(bp->b_dev)])
85830294Ssam switch ((int)bp->b_command) {
85924000Ssam
86030294Ssam case CY_SFORW:
86130294Ssam yc->yc_blkno -= bp->b_repcnt;
86230294Ssam break;
86324000Ssam
86430294Ssam case CY_SREV:
86530294Ssam yc->yc_blkno += bp->b_repcnt;
86630294Ssam break;
86730294Ssam }
86825979Ssam goto opdone;
86925979Ssam
87025979Ssam case SSEEK:
87130719Skarels yc->yc_blkno = bp->b_blkno;
87225979Ssam goto opcont;
87324000Ssam
87425979Ssam case SERASE:
87525979Ssam /*
87625979Ssam * Completed erase of the inter-record gap due to a
87725979Ssam * write error; now retry the write operation.
87825979Ssam */
87925979Ssam vm->um_tab.b_active = SERASED;
88025979Ssam goto opcont;
88124000Ssam }
88225675Ssam
88325979Ssam opdone:
88425979Ssam /*
88525979Ssam * Reset error count and remove from device queue.
88625979Ssam */
88725979Ssam vm->um_tab.b_errcnt = 0;
88825979Ssam dp->b_actf = bp->av_forw;
88925979Ssam /*
89025979Ssam * Save resid and release resources.
89125979Ssam */
89225979Ssam bp->b_resid = bp->b_bcount - htoms(cy->cy_tpb.tpcount);
89330719Skarels if (bp != &ccybuf[cyunit])
89430719Skarels vbadone(bp, &cy->cy_rbuf);
89530371Skarels biodone(bp);
89625979Ssam /*
89725979Ssam * Circulate slave to end of controller
89825979Ssam * queue to give other slaves a chance.
89925979Ssam */
90025979Ssam vm->um_tab.b_actf = dp->b_forw;
90125979Ssam if (dp->b_actf) {
90225979Ssam dp->b_forw = NULL;
90325979Ssam if (vm->um_tab.b_actf == NULL)
90425979Ssam vm->um_tab.b_actf = dp;
90525979Ssam else
90625979Ssam vm->um_tab.b_actl->b_forw = dp;
90724000Ssam }
90825979Ssam if (vm->um_tab.b_actf == 0)
90924000Ssam return;
91025979Ssam opcont:
91125979Ssam cystart(vm);
91224000Ssam }
91324000Ssam
cytimer(dev)91425979Ssam cytimer(dev)
91525979Ssam int dev;
91624000Ssam {
91725979Ssam register struct yc_softc *yc = &yc_softc[YCUNIT(dev)];
91825979Ssam int s;
91924000Ssam
92030371Skarels if (yc->yc_openf == 0 && yc->yc_timo == INF) {
92130371Skarels yc->yc_tact = 0;
92230371Skarels return;
92330371Skarels }
92425979Ssam if (yc->yc_timo != INF && (yc->yc_timo -= 5) < 0) {
92525979Ssam printf("yc%d: lost interrupt\n", YCUNIT(dev));
92625979Ssam yc->yc_timo = INF;
92725979Ssam s = spl3();
92825979Ssam cyintr(CYUNIT(dev));
92925979Ssam splx(s);
93024000Ssam }
93125979Ssam timeout(cytimer, (caddr_t)dev, 5*hz);
93224000Ssam }
93324000Ssam
cyseteof(bp)93425979Ssam cyseteof(bp)
93525979Ssam register struct buf *bp;
93624000Ssam {
93725979Ssam register int cyunit = CYUNIT(bp->b_dev);
93825979Ssam register struct cy_softc *cy = &cy_softc[cyunit];
93925979Ssam register struct yc_softc *yc = &yc_softc[YCUNIT(bp->b_dev)];
94024000Ssam
94125979Ssam if (bp == &ccybuf[cyunit]) {
94230719Skarels if (yc->yc_blkno > bp->b_blkno) {
94325979Ssam /* reversing */
94430719Skarels yc->yc_nxrec = bp->b_blkno - htoms(cy->cy_tpb.tpcount);
94525979Ssam yc->yc_blkno = yc->yc_nxrec;
94625979Ssam } else {
94730719Skarels yc->yc_blkno = bp->b_blkno + htoms(cy->cy_tpb.tpcount);
94825979Ssam yc->yc_nxrec = yc->yc_blkno - 1;
94924000Ssam }
95025675Ssam return;
95125675Ssam }
95225979Ssam /* eof on read */
95330719Skarels yc->yc_nxrec = bp->b_blkno;
95424000Ssam }
95524000Ssam
95625675Ssam /*ARGSUSED*/
cyioctl(dev,cmd,data,flag)95725675Ssam cyioctl(dev, cmd, data, flag)
95825979Ssam caddr_t data;
95925675Ssam dev_t dev;
96025675Ssam {
96125979Ssam int ycunit = YCUNIT(dev);
96225979Ssam register struct yc_softc *yc = &yc_softc[ycunit];
96325979Ssam register struct buf *bp = &ccybuf[CYUNIT(dev)];
96425979Ssam register callcount;
96525979Ssam int fcount, op;
96625979Ssam struct mtop *mtop;
96725979Ssam struct mtget *mtget;
96825979Ssam /* we depend of the values and order of the MT codes here */
96925979Ssam static cyops[] =
97030371Skarels {CY_WEOF,CY_FSF,CY_BSF,CY_SFORW,CY_SREV,CY_REW,CY_OFFL,CY_SENSE};
97125675Ssam
97225675Ssam switch (cmd) {
97325675Ssam
97425979Ssam case MTIOCTOP: /* tape operation */
97525979Ssam mtop = (struct mtop *)data;
97625979Ssam switch (op = mtop->mt_op) {
97725675Ssam
97825979Ssam case MTWEOF:
97930371Skarels callcount = mtop->mt_count;
98030371Skarels fcount = 1;
98130371Skarels break;
98230371Skarels
98325979Ssam case MTFSR: case MTBSR:
98430371Skarels callcount = 1;
98530371Skarels fcount = mtop->mt_count;
98630371Skarels break;
98730371Skarels
98825979Ssam case MTFSF: case MTBSF:
98925979Ssam callcount = mtop->mt_count;
99025979Ssam fcount = 1;
99125979Ssam break;
99225675Ssam
99325979Ssam case MTREW: case MTOFFL: case MTNOP:
99425979Ssam callcount = 1;
99525979Ssam fcount = 1;
99625979Ssam break;
99725675Ssam
99825979Ssam default:
99925979Ssam return (ENXIO);
100025979Ssam }
100125979Ssam if (callcount <= 0 || fcount <= 0)
100225979Ssam return (EINVAL);
100325979Ssam while (--callcount >= 0) {
100430371Skarels #ifdef notdef
100525979Ssam /*
100625979Ssam * Gagh, this controller is the pits...
100725979Ssam */
100825979Ssam if (op == MTFSF || op == MTBSF) {
100925979Ssam do
101025979Ssam cycommand(dev, cyops[op], 1);
101125979Ssam while ((bp->b_flags&B_ERROR) == 0 &&
101225979Ssam (yc->yc_status&(CYS_EOT|CYS_BOT|CYS_FM)) == 0);
101325979Ssam } else
101430371Skarels #endif
101525979Ssam cycommand(dev, cyops[op], fcount);
101630371Skarels dlog((LOG_INFO,
101730371Skarels "cyioctl: status %x, b_flags %x, resid %d\n",
101830371Skarels yc->yc_status, bp->b_flags, bp->b_resid));
101925979Ssam if ((bp->b_flags&B_ERROR) ||
102025979Ssam (yc->yc_status&(CYS_BOT|CYS_EOT)))
102125979Ssam break;
102225979Ssam }
102325979Ssam bp->b_resid = callcount + 1;
102437638Smckusick /*
102537638Smckusick * Pick up the device's error number and pass it
102637638Smckusick * to the user; if there is an error but the number
102737638Smckusick * is 0 set a generalized code.
102837638Smckusick */
102937638Smckusick if ((bp->b_flags & B_ERROR) == 0)
103037638Smckusick return (0);
103137638Smckusick if (bp->b_error)
103237638Smckusick return (bp->b_error);
103337638Smckusick return (EIO);
103425979Ssam
103525979Ssam case MTIOCGET:
103625979Ssam cycommand(dev, CY_SENSE, 1);
103725979Ssam mtget = (struct mtget *)data;
103825979Ssam mtget->mt_dsreg = yc->yc_status;
103925979Ssam mtget->mt_erreg = yc->yc_control;
104025979Ssam mtget->mt_resid = yc->yc_resid;
104125979Ssam mtget->mt_type = MT_ISCY;
104225675Ssam break;
104325675Ssam
104425675Ssam default:
104525675Ssam return (ENXIO);
104625675Ssam }
104725675Ssam return (0);
104825675Ssam }
104925675Ssam
105025675Ssam /*
105125675Ssam * Poll until the controller is ready.
105225675Ssam */
cywait(cp)105325675Ssam cywait(cp)
105425979Ssam register struct cyccb *cp;
105524000Ssam {
105625675Ssam register int i = 5000;
105724000Ssam
105825979Ssam uncache(&cp->cbgate);
105925979Ssam while (i-- > 0 && cp->cbgate == GATE_CLOSED) {
106024000Ssam DELAY(1000);
106125979Ssam uncache(&cp->cbgate);
106224000Ssam }
106325675Ssam return (i <= 0);
106424000Ssam }
106524000Ssam
106625675Ssam /*
106730371Skarels * Load a 20 bit pointer into a Tapemaster pointer.
106825675Ssam */
cyldmba(reg,value)106930371Skarels cyldmba(reg, value)
107034487Skarels register u_char *reg;
107125979Ssam caddr_t value;
107224000Ssam {
107325979Ssam register int v = (int)value;
107425675Ssam
107525979Ssam *reg++ = v;
107625979Ssam *reg++ = v >> 8;
107725979Ssam *reg++ = 0;
107825979Ssam *reg = (v&0xf0000) >> 12;
107924000Ssam }
108024000Ssam
108125675Ssam /*
108225675Ssam * Unconditionally reset all controllers to their initial state.
108325675Ssam */
cyreset(vba)108425675Ssam cyreset(vba)
108525675Ssam int vba;
108624000Ssam {
108725675Ssam register caddr_t addr;
108825675Ssam register int ctlr;
108924000Ssam
109025675Ssam for (ctlr = 0; ctlr < NCY; ctlr++)
109125675Ssam if (cyminfo[ctlr] && cyminfo[ctlr]->um_vbanum == vba) {
109225675Ssam addr = cyminfo[ctlr]->um_addr;
109325675Ssam CY_RESET(addr);
109430371Skarels if (!cyinit(ctlr, addr)) {
109525675Ssam printf("cy%d: reset failed\n", ctlr);
109625675Ssam cyminfo[ctlr] = NULL;
109725675Ssam }
109825675Ssam }
109924000Ssam }
110025979Ssam
110125979Ssam cyuncachetpb(cy)
110225979Ssam struct cy_softc *cy;
110325979Ssam {
110425979Ssam register long *lp = (long *)&cy->cy_tpb;
110525979Ssam register int i;
110625979Ssam
110725979Ssam for (i = 0; i < howmany(sizeof (struct cytpb), sizeof (long)); i++)
110825979Ssam uncache(lp++);
110925979Ssam }
111025979Ssam
111125979Ssam /*
111225979Ssam * Dump routine.
111325979Ssam */
111430869Skarels #define DUMPREC (32*1024)
cydump(dev)111525979Ssam cydump(dev)
111625979Ssam dev_t dev;
111725979Ssam {
111825979Ssam register struct cy_softc *cy;
111925979Ssam register int bs, num, start;
112025979Ssam register caddr_t addr;
112130294Ssam int unit = CYUNIT(dev), error;
112225979Ssam
112325979Ssam if (unit >= NCY || cyminfo[unit] == 0 ||
112425979Ssam (cy = &cy_softc[unit])->cy_bs == 0 || YCUNIT(dev) >= NYC)
112525979Ssam return (ENXIO);
112625979Ssam if (cywait(&cy->cy_ccb))
112725979Ssam return (EFAULT);
112825979Ssam #define phys(a) ((caddr_t)((int)(a)&~0xc0000000))
112930294Ssam addr = phys(cyminfo[unit]->um_addr);
113025979Ssam num = maxfree, start = NBPG*2;
113125979Ssam while (num > 0) {
113230869Skarels bs = num > btoc(DUMPREC) ? btoc(DUMPREC) : num;
113325979Ssam error = cydwrite(cy, start, bs, addr);
113425979Ssam if (error)
113525979Ssam return (error);
113625979Ssam start += bs, num -= bs;
113725979Ssam }
113825979Ssam cyweof(cy, addr);
113925979Ssam cyweof(cy, addr);
114025979Ssam uncache(&cy->cy_tpb);
114125979Ssam if (cy->cy_tpb.tpstatus&CYS_ERR)
114225979Ssam return (EIO);
114325979Ssam cyrewind(cy, addr);
114425979Ssam return (0);
114525979Ssam }
114625979Ssam
cydwrite(cy,pf,npf,addr)114725979Ssam cydwrite(cy, pf, npf, addr)
114825979Ssam register struct cy_softc *cy;
114925979Ssam int pf, npf;
115025979Ssam caddr_t addr;
115125979Ssam {
115225979Ssam
115325979Ssam cy->cy_tpb.tpcmd = CY_WCOM;
115425979Ssam cy->cy_tpb.tpcontrol = CYCW_LOCK|CYCW_25IPS|CYCW_16BITS;
115525979Ssam cy->cy_tpb.tpstatus = 0;
115625979Ssam cy->cy_tpb.tpsize = htoms(npf*NBPG);
115725979Ssam cyldmba(cy->cy_tpb.tplink, (caddr_t)0);
115825979Ssam cyldmba(cy->cy_tpb.tpdata, (caddr_t)(pf*NBPG));
115925979Ssam cyldmba(cy->cy_ccb.cbtpb, (caddr_t)&cy->cy_tpb);
116025979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
116125979Ssam CY_GO(addr);
116225979Ssam if (cywait(&cy->cy_ccb))
116325979Ssam return (EFAULT);
116425979Ssam uncache(&cy->cy_tpb);
116525979Ssam if (cy->cy_tpb.tpstatus&CYS_ERR)
116625979Ssam return (EIO);
116725979Ssam return (0);
116825979Ssam }
116925979Ssam
cyweof(cy,addr)117025979Ssam cyweof(cy, addr)
117125979Ssam register struct cy_softc *cy;
117225979Ssam caddr_t addr;
117325979Ssam {
117425979Ssam
117525979Ssam cy->cy_tpb.tpcmd = CY_WEOF;
117625979Ssam cy->cy_tpb.tpcount = htoms(1);
117725979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
117825979Ssam CY_GO(addr);
117925979Ssam (void) cywait(&cy->cy_ccb);
118025979Ssam }
118125979Ssam
cyrewind(cy,addr)118225979Ssam cyrewind(cy, addr)
118325979Ssam register struct cy_softc *cy;
118425979Ssam caddr_t addr;
118525979Ssam {
118625979Ssam
118725979Ssam cy->cy_tpb.tpcmd = CY_REW;
118825979Ssam cy->cy_tpb.tpcount = htoms(1);
118925979Ssam cy->cy_ccb.cbgate = GATE_CLOSED;
119025979Ssam CY_GO(addr);
119125979Ssam (void) cywait(&cy->cy_ccb);
119225979Ssam }
119324000Ssam #endif
1194