1*25675Ssam /* scat_vddc.c 1.2 86/01/05 */
224001Ssam
324001Ssam #include "fsd.h"
424001Ssam #if NVD > 0
524001Ssam /*
624001Ssam ** VDDC Driver - Versabus to SMD direct interface version.
724001Ssam ** Written for TAHOE vmunix, CCI-WDC 9/1/83.
824001Ssam ** Modified June 1984 to use scatter/gather.
924001Ssam */
1024001Ssam
1124001Ssam #include "../h/param.h"
1224001Ssam #include "../h/buf.h"
1324001Ssam #include "../h/cmap.h"
1424001Ssam #include "../h/conf.h"
1524001Ssam #include "../h/dir.h"
1624001Ssam #include "../h/dk.h"
1724001Ssam #include "../h/map.h"
18*25675Ssam #include "../tahoe/mtpr.h"
19*25675Ssam #include "../tahoe/pte.h"
2024001Ssam #include "../h/systm.h"
21*25675Ssam #include "../tahoevba/vbavar.h"
2224001Ssam #include "../h/user.h"
2324001Ssam #include "../h/vmmac.h"
2424001Ssam #include "../h/proc.h"
2524001Ssam #include "../h/uio.h"
26*25675Ssam #include "../tahoevba/vddc.h"
2724001Ssam
2824001Ssam int vddebug = 1; /* if = 1, error messages are printed on the console */
2924001Ssam int vdintflg = 0; /* if = 1, interrupts are handled by the driver,
3024001Ssam * otherwise they are just ignored. (during setup) */
3124001Ssam
3224001Ssam static struct size FSD[] = {
3324001Ssam 9600, 0, /* minor 0/ 8/16/24 = fsd0a - fsd3a - cyl 0 - 59*/
3424001Ssam 12000, 9600, /* minor 1/ 9/17/25 = fsd0b - fsd3b - cyl 60 - 134*/
3524001Ssam 108480, 21600, /* minor 2/10/18/26 = fsd0c - fsd3c - cyl 135 - 812*/
3624001Ssam 1600, 130080, /* minor 3/11/19/27 = fsd0d - fsd3d - cyl 813 - 822*/
3724001Ssam 130080, 0, /* minor 4/12/20/28 = fsd0e - fsd3e - cyl 0 - 812*/
3824001Ssam 131680, 0, /* minor 5/13/21/29 = fsd0f - fsd3f - cyl 0 - 822*/
3924001Ssam 0, 0, /* Non existent minor device */
4024001Ssam 0, 0, /* Non existent minor device */
4124001Ssam 0, 0, /* Non existent minor device */
4224001Ssam 0, 0, /* Non existent minor device */
4324001Ssam 0, 0, /* Non existent minor device */
4424001Ssam 0, 0, /* Non existent minor device */
4524001Ssam 0, 0, /* Non existent minor device */
4624001Ssam 0, 0, /* Non existent minor device */
4724001Ssam 0, 0, /* Non existent minor device */
4824001Ssam 0, 0, /* Non existent minor device */
4924001Ssam };
5024001Ssam
5124001Ssam static struct size SMD[]= {
5224001Ssam 20064, 0, /* minor 32/40/48/56 = smd0a - smd3a cyl 0- 65 */
5324001Ssam 13680, 20064, /* minor 33/41/49/57 = smd0b - smd3b cyl 66- 110 */
5424001Ssam 214928, 33744, /* minor 34/42/50/58 = smd0c - smd3c cyl 111-817 */
5524001Ssam 1520, 248672, /* minor 35/43/51/59 = smd0d - smd3d cyl 818-822 */
5624001Ssam 248672, 0, /* minor 36/44/52/60 = smd0e - smd3e cyl 0-817 */
5724001Ssam 250192, 0, /* minor 37/45/53/61 = smd0f - smd3f cyl 0-822 */
5824001Ssam 0, 0, /* minor 38/46/54/62 = smd0g - smd3g */
5924001Ssam 0, 0, /* minor 39/47/55/63 = smd0h - smd3h */
6024001Ssam 0, 0, /* Non existent minor device */
6124001Ssam 0, 0, /* Non existent minor device */
6224001Ssam 0, 0, /* Non existent minor device */
6324001Ssam 0, 0, /* Non existent minor device */
6424001Ssam 0, 0, /* Non existent minor device */
6524001Ssam 0, 0, /* Non existent minor device */
6624001Ssam 0, 0, /* Non existent minor device */
6724001Ssam 0, 0, /* Non existent minor device */
6824001Ssam };
6924001Ssam
7024001Ssam static struct size XFSD[] = {
7124001Ssam 20352, 0, /* minor 64/72/80/88 = xfsd0a - xfsd3a cyl 0- 52 */
7224001Ssam 20352, 20352, /* minor 65/73/81/89 = xfsd0b - xfsd3b cyl 53- 105 */
7324001Ssam 230400, 40704, /* minor 66/74/82/90 = xfsd0c - xfsd3c cyl 106-705 */
7424001Ssam 1920, 271104, /* minor 67/75/83/91 = xfsd0d - xfsd3d cyl 706-710 */
7524001Ssam 271104, 0, /* minor 68/76/84/92 = xfsd0e - xfsd3e cyl 0-705 */
7624001Ssam 273024, 0, /* minor 69/77/85/93 = xfsd0f - xfsd3f cyl 0-710 */
7724001Ssam 0, 0, /* minor 70/78/86/94 = xfsd0g - xfsd3g */
7824001Ssam 0, 0, /* minor 71/79/87/95 = xfsd0h - xfsd3h */
7924001Ssam 0, 0, /* Non existent minor device */
8024001Ssam 0, 0, /* Non existent minor device */
8124001Ssam 0, 0, /* Non existent minor device */
8224001Ssam 0, 0, /* Non existent minor device */
8324001Ssam 0, 0, /* Non existent minor device */
8424001Ssam 0, 0, /* Non existent minor device */
8524001Ssam 0, 0, /* Non existent minor device */
8624001Ssam 0, 0, /* Non existent minor device */
8724001Ssam };
8824001Ssam
8924001Ssam /*
9024001Ssam /*
9124001Ssam /* Layout of major/minor number assignments for the VDDC devices.
9224001Ssam /*
9324001Ssam /* 1
9424001Ssam /* 5 8 7 4 3 2 0
9524001Ssam /* +----------------+------+---+-----+
9624001Ssam /* | Major device # | TYPE | D | FLS |
9724001Ssam /* +----------------+------+---+-----+
9824001Ssam /* | | |_____ File system # ( 0-7 )
9924001Ssam /* | |__________ Drive # (0-3)
10024001Ssam /* |________________ Drive type ( 0-FSD, 1-SMD )
10124001Ssam /* ( 2-XFSD ) (obsolete)
10224001Ssam /*
10324001Ssam /********************************************************/
10424001Ssam
10524001Ssam #define VDUNIT(x) ((minor(x) & 0x18) >> 3)
10624001Ssam #define DRVTYPE(x) ((minor(x) & 0xe0) >> 5) (obsolete)
10724001Ssam #define FLSYS(x) (minor(x) & 0x07)
10824001Ssam #define PHYS(x) ( vtoph( &proc[2], (int) (x) ) )
10924001Ssam
11024001Ssam
11124001Ssam /* Drive types should be in order of drive capacity for auto-configuration */
11224001Ssam /* e.g: smallest capacity = drive type 0, highest capacity = type NXPDRV-1 */
11324001Ssam
11424001Ssam struct vdst {
11524001Ssam short nsect;
11624001Ssam short ntrak;
11724001Ssam short nspc;
11824001Ssam short ncyl;
11924001Ssam struct size *sizes;
12024001Ssam short dtype; /* type as in byte 5 (drive) of iopb */
12124001Ssam char *name; /* drive name for autoconf */
12224001Ssam } vdst[] = {
12324001Ssam
12424001Ssam 16, 10, 16*10, 823, FSD, 0, "160 Mb FSD " ,
12524001Ssam 16, 19, 16*19, 823, SMD, 1, "300 Mb SMD " ,
12624001Ssam 16, 24, 16*24, 711, XFSD, 2, "340 Mb FSD "
12724001Ssam };
12824001Ssam
12924001Ssam
13024001Ssam struct vba_ctlr *vdminfo[NVDDC];
13124001Ssam struct vba_device *vddinfo[NUNIT];
13224001Ssam
13324001Ssam /*
13424001Ssam ** Internal Functions
13524001Ssam */
13624001Ssam int vdopen();
13724001Ssam int vdclose();
13824001Ssam int vdprobe(); /* See if VDDC is really there */
13924001Ssam int vd_setup(); /* Called from vdprobe */
14024001Ssam int vdslave(); /* See if drive is really there */
14124001Ssam int vdattach();
14224001Ssam int vddgo();
14324001Ssam int vdstrategy(); /* VDDC strategy routine */
14424001Ssam int vdstart(); /* Top level interface to device queue */
14524001Ssam int vdintr(); /* Top Level ISR */
14624001Ssam int vdread(); /* raw i/o read routine */
14724001Ssam int vdwrite(); /* raw i/o write routine */
14824001Ssam int vddump(); /* dump routine */
14924001Ssam int vdsize(); /* sizes for swapconfig */
15024001Ssam
15124001Ssam long vdstd[] = {
15224001Ssam 0x0f2000 };
15324001Ssam
15424001Ssam struct vba_driver vddriver =
15524001Ssam {
15624001Ssam vdprobe, vdslave, vdattach, vddgo, vdstd,
15724001Ssam "smd/fsd", vddinfo, "VSMD controller ", vdminfo
15824001Ssam };
15924001Ssam
16024001Ssam struct buf vdutab[NUNIT];
16124001Ssam struct buf rvdbuf[NUNIT];
16224001Ssam char vdbuf[SECTSIZ*2];
16324001Ssam extern char vdutl[];
16424001Ssam
16524001Ssam /*
16624001Ssam ** Disk Address
16724001Ssam */
16824001Ssam struct dskadr {
16924001Ssam char track; /* all 8 bits */
17024001Ssam char sector; /* low order 5 bits */
17124001Ssam short cylinder; /* low order 12 bits */
17224001Ssam };
17324001Ssam
17424001Ssam /*
17524001Ssam ** DCB Trailer Formats
17624001Ssam **********************************/
17724001Ssam
17824001Ssam /*
17924001Ssam ** Read / Write Trailer
18024001Ssam */
18124001Ssam struct trrw {
18224001Ssam char *memadr; /* memory address */
18324001Ssam long wcount; /* 16 bit word count */
18424001Ssam struct dskadr disk; /* disk address */
18524001Ssam long scat[MAXBPTE*2+1]; /* gather/scatter trailer */
18624001Ssam };
18724001Ssam
18824001Ssam /*
18924001Ssam ** Format Trailer
19024001Ssam */
19124001Ssam struct trfmt {
19224001Ssam char *addr; /* data buffer to be filled on sector*/
19324001Ssam long nsectors; /* # of sectors to be formatted */
19424001Ssam struct dskadr disk;
19524001Ssam struct dskadr hdr;
19624001Ssam };
19724001Ssam
19824001Ssam /*
19924001Ssam ** Reset / Configure Trailer
20024001Ssam */
20124001Ssam struct treset {
20224001Ssam long ncyl; /* # cylinders */
20324001Ssam long nsurfaces; /* # surfaces */
20424001Ssam }; /* # of sectors is defined by VDDC */
20524001Ssam /* to be 32/track of 512 data bytes each */
20624001Ssam
20724001Ssam /*
20824001Ssam ** Seek Trailer
20924001Ssam */
21024001Ssam struct trseek {
21124001Ssam struct dskadr disk;
21224001Ssam };
21324001Ssam
21424001Ssam /*
21524001Ssam ** DCB Format
21624001Ssam */
21724001Ssam struct fmt_dcb {
21824001Ssam struct fmt_dcb *nxtdcb; /* next dcb in chain or End of Chain */
21924001Ssam short intflg; /* interrupt settings and flags */
22024001Ssam short opcode; /* DCB Command code etc... */
22124001Ssam long operrsta; /* Error & Status info */
22224001Ssam short fill; /* not used */
22324001Ssam char devselect; /* Drive selection */
22424001Ssam char trailcnt; /* Trailer Word Count */
22524001Ssam long err_memadr; /* Error memory address */
22624001Ssam short fill2;
22724001Ssam short err_wcount; /* Error word count */
22824001Ssam short err_track; /* Error track/sector */
22924001Ssam short err_cyl; /* Error cylinder adr */
23024001Ssam union {
23124001Ssam struct trrw rwtrail; /* read/write trailer */
23224001Ssam struct trfmt fmtrail; /* format trailer */
23324001Ssam struct treset resetrail; /* reset/configure trailer */
23424001Ssam struct trseek seektrail; /* seek trailer */
23524001Ssam } trail;
23624001Ssam };
23724001Ssam
23824001Ssam /*
23924001Ssam ** MDCB Format
24024001Ssam */
24124001Ssam struct fmt_mdcb {
24224001Ssam struct fmt_dcb *firstdcb; /* first dcb in chain */
24324001Ssam struct fmt_dcb *procdcb; /* dcb being processed */
24424001Ssam struct fmt_dcb *intdcb; /* dcb causing interrupt */
24524001Ssam long vddcstat; /* VDDC status */
24624001Ssam }mdcbx;
24724001Ssam
24824001Ssam /*
24924001Ssam ** MDCB
25024001Ssam */
25124001Ssam struct fmt_mdcb *mdcb = &mdcbx;
25224001Ssam
25324001Ssam /*
25424001Ssam ** DCB
25524001Ssam */
25624001Ssam
25724001Ssam struct fmt_dcb dcbx[NVDDC];
25824001Ssam
25924001Ssam int vdtimeout;
26024001Ssam #define POLLTILLDONE(x) { vdtimeout = 1000*(x); \
26124001Ssam uncache((char *)&dcb->operrsta); \
26224001Ssam while (! (dcb->operrsta & DCBCMP)) { \
26324001Ssam DELAY(1000); \
26424001Ssam vdtimeout--; \
26524001Ssam uncache((char *)&dcb->operrsta); \
26624001Ssam if (vdtimeout <=0) { \
26724001Ssam printf("VDDC controller timeout\n"); \
26824001Ssam return(0); \
26924001Ssam } \
27024001Ssam } \
27124001Ssam }
27224001Ssam
27324001Ssam /*
27424001Ssam ** See if the controller is really there.
27524001Ssam ** if TRUE - initialize the controller.
27624001Ssam */
vdprobe(cntrl_vaddr)27724001Ssam vdprobe(cntrl_vaddr)
27824001Ssam caddr_t cntrl_vaddr;
27924001Ssam {
28024001Ssam if ( badaddr(cntrl_vaddr,2) ) return(0); /* no controller */
28124001Ssam else
28224001Ssam if (vd_setup(cntrl_vaddr)) /* initialize the controller */
28324001Ssam return(1);
28424001Ssam else return(0); /* initialization error */
28524001Ssam }
28624001Ssam
vd_setup(cntrl_vaddr)28724001Ssam vd_setup(cntrl_vaddr)
28824001Ssam caddr_t cntrl_vaddr;
28924001Ssam {
29024001Ssam register struct fmt_dcb *dcb = &dcbx[0];
29124001Ssam int j;
29224001Ssam
29324001Ssam VDDC_RESET(cntrl_vaddr); /* Reset the controller */
29424001Ssam /* Burn some time ...... needed after accessing reset port */
29524001Ssam for (j=0; j<20; j++)
29624001Ssam DELAY(1000);
29724001Ssam
29824001Ssam /* setup & issue INIT to initialize VDDC */
29924001Ssam
30024001Ssam dcb->opcode = INIT;
30124001Ssam dcb->nxtdcb = (struct fmt_dcb *)0;
30224001Ssam dcb->intflg = NOINT;
30324001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
30424001Ssam dcb->operrsta = 0;
30524001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
30624001Ssam POLLTILLDONE(1) /* poll till done */
30724001Ssam if (dcb->operrsta & HRDERR) {
30824001Ssam if (vddebug)
30924001Ssam printf("VDDC INIT error. Status = %x\n",dcb->operrsta);
31024001Ssam return(0);
31124001Ssam }
31224001Ssam /* setup & issue DIAGNOSE */
31324001Ssam
31424001Ssam dcb->opcode = DIAG;
31524001Ssam dcb->nxtdcb = (struct fmt_dcb *)0;
31624001Ssam dcb->intflg = NOINT;
31724001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
31824001Ssam dcb->operrsta = 0;
31924001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
32024001Ssam POLLTILLDONE(1) /* poll till done */
32124001Ssam if (dcb->operrsta & HRDERR) {
32224001Ssam if (vddebug)
32324001Ssam printf("VDDC DIAGNOSE error. Status = %x\n",dcb->operrsta);
32424001Ssam return(0);
32524001Ssam }
32624001Ssam /* Start drives command */
32724001Ssam /*
32824001Ssam /* dcb->opcode = VDSTART;
32924001Ssam /* dcb->nxtdcb = (struct fmt_dcb *)0;
33024001Ssam /* dcb->intflg = NOINT;
33124001Ssam /* mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
33224001Ssam /* dcb->operrsta = 0;
33324001Ssam /* VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
33424001Ssam /* POLLTILLDONE(20) /* poll till done */
33524001Ssam /* if (dcb->operrsta & HRDERR) {
33624001Ssam /* if (vddebug)
33724001Ssam /* printf("VDDC START DRIVES error. Status = %x\n",dcb->operrsta);
33824001Ssam /* return(0);
33924001Ssam /* }
34024001Ssam /**/
34124001Ssam return(1);
34224001Ssam }
34324001Ssam
34424001Ssam /*
34524001Ssam * See if a drive is really there
34624001Ssam * Try to Reset/Configure the drive, then test its status.
34724001Ssam */
vdslave(ui,cntrl_vaddr)34824001Ssam vdslave(ui,cntrl_vaddr)
34924001Ssam register struct vba_device *ui;
35024001Ssam register caddr_t cntrl_vaddr;
35124001Ssam {
35224001Ssam register struct fmt_dcb *dcb = &dcbx[0];
35324001Ssam register struct vdst *st;
35424001Ssam int dsktype;
35524001Ssam
35624001Ssam /*
35724001Ssam ** check drive status - see if drive exists.
35824001Ssam */
35924001Ssam dcb->opcode = VDSTATUS;
36024001Ssam dcb->intflg = NOINT;
36124001Ssam dcb->operrsta = 0;
36224001Ssam dcb->devselect = (char)ui->ui_slave;
36324001Ssam dcb->trailcnt = (char)0;
36424001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
36524001Ssam mdcb->vddcstat = 0;
36624001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb)) /* do it */
36724001Ssam POLLTILLDONE(5)
36824001Ssam /*
36924001Ssam if (dcb->operrsta & HRDERR) {
37024001Ssam if (vddebug)
37124001Ssam printf("VDDC STATUS error. Status = %x, drive %d\n",dcb->operrsta,ui->ui_slave);
37224001Ssam return(0);
37324001Ssam }
37424001Ssam */
37524001Ssam uncache((char *)&mdcb->vddcstat);
37624001Ssam if (mdcb->vddcstat & DRVNRDY) return(0); /* not ready-> non existent */
37724001Ssam
37824001Ssam /*
37924001Ssam * drive is alive, now get its type!
38024001Ssam * Seek on all drive types starting from the largest one.
38124001Ssam * a sucessful seek to the last sector/cylinder/track verifies
38224001Ssam * the drive type connected to this port.
38324001Ssam */
38424001Ssam for (dsktype = NVDDRV-1; dsktype >= 0; dsktype--) {
38524001Ssam st = &vdst[dsktype];
38624001Ssam dcb->opcode = RSTCFG; /* configure drive command */
38724001Ssam dcb->intflg = NOINT;
38824001Ssam dcb->operrsta = 0;
38924001Ssam dcb->trail.resetrail.ncyl = st->ncyl;
39024001Ssam dcb->trail.resetrail.nsurfaces = st->ntrak;
39124001Ssam dcb->devselect = (char)ui->ui_slave;
39224001Ssam dcb->trailcnt = (char)2;
39324001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
39424001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
39524001Ssam POLLTILLDONE(3)
39624001Ssam if (dcb->operrsta & HRDERR) {
39724001Ssam if (vddebug)
39824001Ssam printf("VDDC RESET/CONFIGURE error. Status = %x\n",dcb->operrsta);
39924001Ssam return(0);
40024001Ssam }
40124001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
40224001Ssam dcb->intflg = NOINT;
40324001Ssam dcb->opcode = RD;
40424001Ssam dcb->operrsta = 0;
40524001Ssam dcb->devselect = (char)ui->ui_slave;
40624001Ssam dcb->trailcnt = (char)3;
40724001Ssam dcb->trail.rwtrail.memadr = (char *)PHYS(vdbuf);
40824001Ssam dcb->trail.rwtrail.wcount = SECTSIZ;
40924001Ssam dcb->trail.rwtrail.disk.cylinder = st->ncyl -2;
41024001Ssam dcb->trail.rwtrail.disk.track = st->ntrak -1;
41124001Ssam dcb->trail.rwtrail.disk.sector = 0;
41224001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
41324001Ssam POLLTILLDONE(3)
41424001Ssam if ( (dcb->operrsta & HRDERR) == 0)
41524001Ssam /* found the drive type! */
41624001Ssam break;
41724001Ssam }
41824001Ssam if (dsktype < 0) {
41924001Ssam /* If reached here, a drive which is not defined in the
42024001Ssam * 'vdst' tables is connected. Cannot set it's type.
42124001Ssam */
42224001Ssam printf("VDDC error, unrecognized drive type, drive %d\n",ui->ui_slave);
42324001Ssam return(0);
42424001Ssam }
42524001Ssam ui->ui_type = dsktype;
42624001Ssam vddriver.ud_dname = st->name;
42724001Ssam return(1);
42824001Ssam }
42924001Ssam
43024001Ssam vdattach(ui)
43124001Ssam struct vba_device *ui;
43224001Ssam {
43324001Ssam }
43424001Ssam
43524001Ssam vddgo(um)
43624001Ssam struct vba_ctlr *um;
43724001Ssam {
43824001Ssam }
43924001Ssam
44024001Ssam #define b_cylin b_resid
44124001Ssam
vdstrategy(bp)44224001Ssam vdstrategy(bp)
44324001Ssam register struct buf *bp;
44424001Ssam {
44524001Ssam register struct vba_device *ui;
44624001Ssam register struct vba_ctlr *um;
44724001Ssam register int unit;
44824001Ssam register struct buf *dp;
44924001Ssam register struct size *sizep;
45024001Ssam int index, blocks, s;
45124001Ssam
45224001Ssam vdintflg = 1; /* enable interrupts handling by the driver */
45324001Ssam blocks = (bp->b_bcount + DEV_BSIZE - 1) >> DEV_BSHIFT;
45424001Ssam if (bp->b_bcount > NBPG*MAXBPTE) {
45524001Ssam printf ("VDDC I/O length error: %d\n", bp->b_bcount);
45624001Ssam goto bad1;
45724001Ssam }
45824001Ssam unit = VDUNIT(bp->b_dev);
45924001Ssam ui = vddinfo[unit];
46024001Ssam if (ui == 0 || ui->ui_alive == 0) goto bad1;
46124001Ssam index = FLSYS(bp->b_dev); /* get file system index */
46224001Ssam sizep = vdst[ui->ui_type].sizes;
46324001Ssam if (bp->b_blkno < 0 ||
46424001Ssam (dkblock(bp)+blocks > sizep[index].nblocks)) /* disk overflow */
46524001Ssam goto bad1;
46624001Ssam s = spl8();
46724001Ssam dp = &vdutab[ui->ui_unit];
46824001Ssam bp->b_resid = bp->b_blkno ; /* block # plays same role as
46924001Ssam cylinder # for disksort, as long
47024001Ssam as increasing blocks correspond to
47124001Ssam increasing cylinders on disk */
47224001Ssam
47324001Ssam disksort(dp, bp);
47424001Ssam if (dp->b_active == 0) { /* unit is on controller queue */
47524001Ssam /* put the device on the controller queue */
47624001Ssam dp->b_forw = NULL; /* end of queue indicator */
47724001Ssam um = ui->ui_mi; /* get controller structure !! */
47824001Ssam if (um->um_tab.b_actf == NULL) /* controller queue is empty */
47924001Ssam um->um_tab.b_actf = dp;
48024001Ssam else
48124001Ssam um->um_tab.b_actl->b_forw = dp; /* add into queue */
48224001Ssam um->um_tab.b_actl = dp; /* update queue tail */
48324001Ssam dp->b_active ++;
48424001Ssam }
48524001Ssam bp = &ui->ui_mi->um_tab; /* controller structure addr */
48624001Ssam if (bp->b_actf && /* cntrl queue not empty */
48724001Ssam bp->b_active == 0) /* controller not active */
48824001Ssam (void) vdstart(ui->ui_mi);/* go start I/O */
48924001Ssam splx(s);
49024001Ssam return;
49124001Ssam
49224001Ssam bad1:
49324001Ssam bp->b_flags |= B_ERROR;
49424001Ssam iodone(bp);
49524001Ssam return;
49624001Ssam }
49724001Ssam
49824001Ssam
49924001Ssam /*
50024001Ssam * Start up a transfer on a drive.
50124001Ssam */
vdstart(um)50224001Ssam vdstart(um)
50324001Ssam register struct vba_ctlr *um;
50424001Ssam {
50524001Ssam register struct buf *bp, *dp;
50624001Ssam register struct fmt_dcb *dcb = &dcbx[um->um_ctlr];
50724001Ssam struct size *sizep; /* Pointer to one of the tables */
50824001Ssam register struct vdst *st;
50924001Ssam register int index ; /* Index in the relevant table */
51024001Ssam register int phadr; /* Buffer's physical address */
51124001Ssam register caddr_t cntrl_vaddr = um->um_addr;
51224001Ssam register struct proc *this_proc;
51324001Ssam register long phaddr, vaddr, length, i;
51424001Ssam register long *longp;
51524001Ssam int sblock, unit;
51624001Ssam
51724001Ssam loop:
51824001Ssam /*
51924001Ssam * Pull a request off the controller queue
52024001Ssam */
52124001Ssam if ((dp = um->um_tab.b_actf) == NULL)
52224001Ssam return ;
52324001Ssam if ((bp = dp->b_actf) == NULL) {
52424001Ssam dp->b_active = 0; /* device removed from ctlr queue */
52524001Ssam um->um_tab.b_actf = dp->b_forw;
52624001Ssam goto loop;
52724001Ssam }
52824001Ssam /*
52924001Ssam * Mark controller busy, and
53024001Ssam * prepare a command packet for the controller.
53124001Ssam */
53224001Ssam um->um_tab.b_active++;
53324001Ssam unit = VDUNIT(bp->b_dev);
53424001Ssam st = &vdst[vddinfo[unit]->ui_type];
53524001Ssam index = FLSYS(bp->b_dev);
53624001Ssam sizep = st->sizes;
53724001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
53824001Ssam dcb->intflg = INTDUN; /* interrupt on completion */
53924001Ssam
54024001Ssam dcb->operrsta = 0;
54124001Ssam dcb->devselect = VDUNIT(bp->b_dev);
54224001Ssam sblock = sizep[index].block0 + bp->b_blkno;
54324001Ssam dcb->trail.rwtrail.disk.cylinder = (short)(sblock / st->nspc);
54424001Ssam dcb->trail.rwtrail.disk.track=(char)((sblock % st->nspc) / st->nsect);
54524001Ssam dcb->trail.rwtrail.disk.sector = (char)(sblock*2 % (st->nsect*2));
54624001Ssam if (bp->b_flags & B_DIRTY || bp->b_proc==0) this_proc = &proc[2];
54724001Ssam else this_proc = bp->b_proc;
54824001Ssam phaddr = vtoph(this_proc, bp->b_un.b_addr); /* start addresses */
54924001Ssam vaddr = (int)bp->b_un.b_addr;
55024001Ssam length = (bp->b_bcount+1) & ~1; /* total # of bytes */
55124001Ssam printf("\nvaddr=%x length=%x\n", vaddr, length);
55224001Ssam dcb->trail.rwtrail.memadr = (char *)phaddr; /* default trailer */
55324001Ssam printf("%x ", dcb->trail.rwtrail.memadr);
55424001Ssam i = imin ( NBPG-(phaddr&PGOFSET),length); /* bytes in this page */
55524001Ssam dcb->trail.rwtrail.wcount = i/2;
55624001Ssam if (i != 0x400) printf("/%x ", i/2);
55724001Ssam dcb->trailcnt = 3;
55824001Ssam /*
55924001Ssam * If all required bytes fit into one page frame, that's it.
56024001Ssam * Otherwise we have to generate a scatter/gather trailer.
56124001Ssam */
56224001Ssam length -= i;
56324001Ssam vaddr += i;
56424001Ssam longp = dcb->trail.rwtrail.scat; /* 1'st pair address */
56524001Ssam while (length > 0) {
56624001Ssam i = imin ( NBPG-(phaddr&PGOFSET),length);
56724001Ssam *longp++ = i/2;
56824001Ssam *longp++ = vtoph (this_proc, vaddr);
56924001Ssam vaddr += i;
57024001Ssam length -= i;
57124001Ssam dcb->trailcnt += 2;
57224001Ssam }
57324001Ssam *longp++ = 0; /* End of list */
57424001Ssam *longp = 0; /* End of list */
57524001Ssam /***********
57624001Ssam dcb->trailcnt +=2 ;
57724001Ssam ***********/
57824001Ssam if (bp->b_flags & B_READ) { /* Read or read&scatter */
57924001Ssam if (dcb->trailcnt == 3) dcb->opcode = RD;
58024001Ssam else dcb->opcode = RAS;
58124001Ssam } else { /* Write or gather&write */
58224001Ssam if (dcb->trailcnt == 3) dcb->opcode = WD;
58324001Ssam else dcb->opcode = GAW;
58424001Ssam }
58524001Ssam while (longp >= (long *)dcb)
58624001Ssam printf("%x\n", *longp--);
58724001Ssam
58824001Ssam #ifdef VDDCPERF
58924001Ssam scope_out(1);
59024001Ssam #endif
59124001Ssam
59224001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb)) /* do it */
59324001Ssam }
59424001Ssam
59524001Ssam
59624001Ssam /*
59724001Ssam * Handle a disk interrupt.
59824001Ssam */
vdintr(vdnum)59924001Ssam vdintr(vdnum)
60024001Ssam register vdnum;
60124001Ssam {
60224001Ssam register struct buf *bp, *dp;
60324001Ssam register struct vba_ctlr *um = vdminfo[vdnum];
60424001Ssam register struct fmt_dcb *dcb = &dcbx[vdnum];
60524001Ssam register int cnt;
60624001Ssam
60724001Ssam #ifdef VDDCPERF
60824001Ssam scope_out(2);
60924001Ssam #endif
61024001Ssam printf("vddc 1\n");
61124001Ssam if (intenable == 0 || vdintflg == 0) /* ignore all interrupts */
61224001Ssam return;
61324001Ssam if (um->um_tab.b_active == NULL) return;/* unexpected interrupt */
61424001Ssam uncache((char *)&mdcb->intdcb);
61524001Ssam uncache((char *)&dcb->operrsta);
61624001Ssam if ( mdcb->intdcb != (struct fmt_dcb *)PHYS(dcb)) { /* dcb causing interrupt */
61724001Ssam printf("VDDC error - dcb causing interrupt (%x) is different from expected dcb (%x) Interrupt ignored\n", mdcb->intdcb,dcb);
61824001Ssam return;
61924001Ssam }
62024001Ssam if (! (dcb->operrsta & DCBCMP)) { /* unexpected interrupt */
62124001Ssam printf("VDDC Unexpected interrupt, DCB completed not set. Status = %x\n",dcb->operrsta);
62224001Ssam return;
62324001Ssam }
62424001Ssam dp = um->um_tab.b_actf; /* device queue head in ctlr queue */
62524001Ssam bp = dp->b_actf; /* first buffer in device queue */
62624001Ssam if (dcb->operrsta & HRDERR) {
62724001Ssam printf("VDDC hard error - dcb status = %x\n",dcb->operrsta);
62824001Ssam bp->b_flags |= B_ERROR;
62924001Ssam }
63024001Ssam else if (dcb->operrsta & SFTERR)
63124001Ssam printf("Soft error on VDDC,status = %x, dev=%x, block # %d\n",
63224001Ssam dcb->operrsta, bp->b_dev, bp->b_blkno);
63324001Ssam
63424001Ssam /*
63524001Ssam * If this was a read, we have to purge the data cache for the
63624001Ssam * rigth virtual pages. It could be nice to just change the
63724001Ssam * relevant process's data key but this key is in PCB, in _u,
63824001Ssam * which can be on the disk right now. And besides, what about
63924001Ssam * reads into the system space? There's no key to change there.
64024001Ssam */
64124001Ssam if (bp->b_flags & B_READ) {
64224001Ssam printf("vddc 2\n");
64324001Ssam if (dcb->opcode == RAS) { /* Multiple pages read */
64424001Ssam printf("vddc 3\n");
64524001Ssam for (cnt=bp->b_bcount; cnt>=0; cnt -= NBPG)
64624001Ssam mtpr ((caddr_t)bp->b_un.b_addr+cnt-1, P1DC);
64724001Ssam if ( ((int)bp->b_un.b_addr & PGOFSET) != 0 )
64824001Ssam mtpr ((caddr_t)bp->b_un.b_addr, P1DC);
64924001Ssam } else { /* Only one page read */
65024001Ssam mtpr ((caddr_t)bp->b_un.b_addr, P1DC);
65124001Ssam printf("vddc 4\n");
65224001Ssam }
65324001Ssam }
65424001Ssam
65524001Ssam um->um_tab.b_active = 0;
65624001Ssam um->um_tab.b_errcnt = 0;
65724001Ssam if (dp->b_forw != NULL) { /* more than 1 unit on queue */
65824001Ssam um->um_tab.b_actf = dp->b_forw; /* next device on ctlr queue */
65924001Ssam dp->b_forw = um->um_tab.b_actl->b_forw; /* be last in queue */
66024001Ssam um->um_tab.b_actl->b_forw = dp; /* last points now to dp */
66124001Ssam um->um_tab.b_actl = dp; /* pointer in ctlr structure */
66224001Ssam }
66324001Ssam dp->b_errcnt = 0;
66424001Ssam dp->b_actf = bp->av_forw; /* remove first from queue */
66524001Ssam bp->b_resid = 0; /* All data read here */
66624001Ssam
66724001Ssam #ifdef VDDCPERF
66824001Ssam scope_out(3);
66924001Ssam #endif
67024001Ssam
67124001Ssam printf("vddc 5\n");
67224001Ssam iodone(bp);
67324001Ssam printf("vddc 6\n");
67424001Ssam vdstart(um); /* start requests for next device on queue */
67524001Ssam printf("vddc 7\n");
67624001Ssam }
67724001Ssam
67824001Ssam
vdread(dev,uio)67924001Ssam vdread(dev, uio)
68024001Ssam dev_t dev;
68124001Ssam struct uio *uio;
68224001Ssam {
68324001Ssam register int unit = VDUNIT(dev);
68424001Ssam register int error;
68524001Ssam
68624001Ssam if (unit >= NUNIT) return ( ENXIO );
68724001Ssam else return
68824001Ssam (physio(vdstrategy, &rvdbuf[unit], dev, B_READ, minphys, uio));
68924001Ssam }
69024001Ssam
vdwrite(dev,uio)69124001Ssam vdwrite(dev, uio)
69224001Ssam dev_t dev;
69324001Ssam struct uio *uio;
69424001Ssam {
69524001Ssam register int unit = VDUNIT(dev);
69624001Ssam register int error;
69724001Ssam
69824001Ssam if (unit >= NUNIT) return (ENXIO);
69924001Ssam else return
70024001Ssam (physio(vdstrategy, &rvdbuf[unit], dev, B_WRITE,minphys, uio));
70124001Ssam }
70224001Ssam
70324001Ssam #define DUMPSIZE 32 /* Up to 32k at a time - controller limit */
70424001Ssam
vddump(dev)70524001Ssam vddump(dev)
70624001Ssam dev_t dev;
70724001Ssam /*
70824001Ssam * Dump the main memory to the given device.
70924001Ssam */
71024001Ssam {
71124001Ssam register struct vba_ctlr *um;
71224001Ssam register struct fmt_dcb *dcb = &dcbx[0];
71324001Ssam register struct vdst *st;
71424001Ssam register int unit;
71524001Ssam register caddr_t cntrl_vaddr ;
71624001Ssam register struct size *sizep; /* Pointer to one of the tables */
71724001Ssam int index,sblock,blkcount,thiscount;
71824001Ssam int memaddr;
71924001Ssam
72024001Ssam unit = VDUNIT(dev);
72124001Ssam um = (vddinfo[unit])->ui_mi;
72224001Ssam st = &vdst[(vddinfo[unit])->ui_type];
72324001Ssam dcb = &dcbx[um->um_ctlr];
72424001Ssam cntrl_vaddr = um->um_addr;
72524001Ssam memaddr = 0x0;
72624001Ssam index = FLSYS(dev);
72724001Ssam sizep = st->sizes;
72824001Ssam blkcount = maxfree - 2; /* In 1k byte pages */
72924001Ssam if (dumplo + blkcount > sizep[index].nblocks) return(EINVAL);
73024001Ssam sblock = sizep[index].block0 + dumplo;
73124001Ssam while (blkcount > 0) {
73224001Ssam thiscount = MIN (blkcount, DUMPSIZE);
73324001Ssam mdcb->firstdcb = (struct fmt_dcb *)PHYS(dcb);
73424001Ssam dcb->intflg = NOINT;
73524001Ssam dcb->opcode = WD;
73624001Ssam dcb->operrsta = 0;
73724001Ssam dcb->devselect = unit;
73824001Ssam dcb->trailcnt = (char)3;
73924001Ssam dcb->trail.rwtrail.memadr = (char *)memaddr;
74024001Ssam dcb->trail.rwtrail.wcount = thiscount*512;
74124001Ssam dcb->trail.rwtrail.disk.cylinder= (short)(sblock/st->nspc);
74224001Ssam dcb->trail.rwtrail.disk.track = (char)((sblock % st->nspc)
74324001Ssam / st->nsect);
74424001Ssam dcb->trail.rwtrail.disk.sector = (char)(sblock*2 % (st->nsect*2));
74524001Ssam VDDC_ATTENTION(cntrl_vaddr,PHYS(mdcb) ) /* do it */
74624001Ssam POLLTILLDONE(5);
74724001Ssam if (dcb->operrsta & HRDERR) {
74824001Ssam if (vddebug)
74924001Ssam printf("VDDC DUMP error. Status = %x\n",
75024001Ssam dcb->operrsta);
75124001Ssam return(EIO);
75224001Ssam };
75324001Ssam blkcount -= thiscount;
75424001Ssam memaddr += thiscount*NBPG;
75524001Ssam sblock += thiscount;
75624001Ssam }
75724001Ssam return(0);
75824001Ssam }
75924001Ssam
vdopen(dev,flag)76024001Ssam vdopen(dev, flag)
76124001Ssam register dev_t dev;
76224001Ssam int flag;
76324001Ssam {
76424001Ssam register struct vba_device *ui;
76524001Ssam register unit = VDUNIT(dev);
76624001Ssam
76724001Ssam ui = vddinfo[unit];
76824001Ssam if (ui == 0 || ui->ui_alive == 0 || ui->ui_type >= NVDDRV)
76924001Ssam return ENXIO;
77024001Ssam return 0;
77124001Ssam }
77224001Ssam
vdsize(dev)77324001Ssam vdsize(dev)
77424001Ssam register dev_t dev;
77524001Ssam {
77624001Ssam register struct vba_device *ui;
77724001Ssam register unit = VDUNIT(dev);
77824001Ssam
77924001Ssam ui = vddinfo[unit];
78024001Ssam if (ui == 0 || ui->ui_alive == 0 || ui->ui_type >= NVDDRV)
78124001Ssam return -1;
78224001Ssam return vdst[ui->ui_type].sizes[FLSYS(dev)].nblocks;
78324001Ssam }
78424001Ssam #endif
785