1*25677Ssam /* vdreg.h 1.1 86/01/05 */ 2*25677Ssam 3*25677Ssam /* 4*25677Ssam * VDDC (Versabus Direct Disk Controller) definitions. 5*25677Ssam */ 6*25677Ssam 7*25677Ssam /* 8*25677Ssam * DCB Command Codes 9*25677Ssam */ 10*25677Ssam #define RD 0x80 /* Read Data */ 11*25677Ssam #define FTR 0xc0 /* Full Track Read */ 12*25677Ssam #define RAS 0x90 /* Read and Scatter */ 13*25677Ssam #define C 0xa0 /* Compare */ 14*25677Ssam #define FTC 0xe0 /* Full Track Compare */ 15*25677Ssam #define RHDE 0x180 /* Read Header, Data & ECC (not used) */ 16*25677Ssam #define WD 0x00 /* Write Data */ 17*25677Ssam #define FTW 0x40 /* Full Track Write */ 18*25677Ssam #define WTC 0x20 /* Write Then Compare */ 19*25677Ssam #define FTWTC 0x60 /* Full Track Write Then Compare */ 20*25677Ssam #define GAW 0x10 /* Gather and Write */ 21*25677Ssam #define WDE 0x100 /* Write Data & ECC (not used) */ 22*25677Ssam #define FSECT 0x900 /* Format Sector */ 23*25677Ssam #define GWC 0x30 /* Gather Write & Compare */ 24*25677Ssam #define VDSTART 0x800 /* Start drives */ 25*25677Ssam #define VDRELEASE 0xa00 /* Stop drives */ 26*25677Ssam #define SEEK 0xb00 /* Seek */ 27*25677Ssam #define INIT 0xc00 /* Initialize VDDC */ 28*25677Ssam #define DIAG 0xd00 /* Diagnose (self-test) VDDC */ 29*25677Ssam #define RSTCFG 0xe00 /* Reset/Configure VDDC/DDI/Drive(s) */ 30*25677Ssam #define VDSTATUS 0xf00 /* VDDC Status */ 31*25677Ssam 32*25677Ssam #define ABORT 0x80000000 /* ABORT active i/o */ 33*25677Ssam 34*25677Ssam /* 35*25677Ssam * Error/status codes. 36*25677Ssam */ 37*25677Ssam #define HCRCERR 0x1 /* Header CRC Error */ 38*25677Ssam #define HCMPERR 0x2 /* Header Compare Error */ 39*25677Ssam #define WPTERR 0x4 /* Write Protect Error/Status */ 40*25677Ssam #define CTLRERR 0x8 /* Controller Error */ 41*25677Ssam #define DSEEKERR 0x10 /* Disk Seek Error */ 42*25677Ssam #define UCDATERR 0x20 /* Uncorrectable Data Error */ 43*25677Ssam #define NOTCYLERR 0x40 /* Not on Cylinder Error */ 44*25677Ssam #define DRVNRDY 0x80 /* Drive Not Ready Error/Status */ 45*25677Ssam #define ALTACC 0x100 /* Alternate (track) accessed Status */ 46*25677Ssam #define SEEKSTRT 0x200 /* Seek Started Status */ 47*25677Ssam #define INVDADR 0x400 /* Invalid Disk Address Error */ 48*25677Ssam #define DNEMEM 0x800 /* Non-Existant Memory Error */ 49*25677Ssam #define PARERR 0x1000 /* Memory Parity Error */ 50*25677Ssam #define DCOMPERR 0x2000 /* Data Compare Error */ 51*25677Ssam #define DDIRDY 0x4000 /* DDI Ready Error/Status */ 52*25677Ssam #define OPABRT 0x8000 /* Operator Abort (Host) Error/Status */ 53*25677Ssam #define DSERLY 0x10000 /* Data Strobe Early */ 54*25677Ssam #define DSLATE 0x20000 /* Data Strobe Late */ 55*25677Ssam #define TOPLUS 0x40000 /* Track Offset Plus */ 56*25677Ssam #define TOMNUS 0x80000 /* Track Offset Minus */ 57*25677Ssam #define CPDCRT 0x100000 /* Cntlr Performed Data Correction */ 58*25677Ssam #define HRDERR 0x200000 /* Hard Error */ 59*25677Ssam #define SFTERR 0x400000 /* Soft Error (retry succesful) */ 60*25677Ssam #define ANYERR 0x800000 /* Any Error */ 61*25677Ssam #define INVCMD 0x1000000 /* Programmer error */ 62*25677Ssam 63*25677Ssam /* hard error */ 64*25677Ssam #define HTYPES \ 65*25677Ssam (HCRCERR|HCMPERR|WPTERR|CTLRERR|DSEEKERR|UCDATERR|NOTCYLERR|DRVNRDY|\ 66*25677Ssam INVDADR|DNEMEM|PARERR|DCOMPERR) 67*25677Ssam 68*25677Ssam #define ERRS 0x3FFF 69*25677Ssam /* retryable errors */ 70*25677Ssam #define CANRETRY \ 71*25677Ssam (CTLRERR|DSEEKERR|NOTCYLERR|DCOMPERR|UCDATERR|PARERR|DNEMEM|HCRCERR|HCMPERR) 72*25677Ssam 73*25677Ssam #define ERRBITS "\20\1HCRC\2HCMP\3WPT\4CTLR\5DSEEK\6UCDATA\7NOTCYL\10DRVNRDY\ 74*25677Ssam \11ALTACC\12SEEKSTRT\13INVDADR\14DNEMEM\15PAR\16DCOMP\17DDIRDY\20OPABRT\ 75*25677Ssam \21DSERLY\22DSLATE\23TOPLUS\24TOPMNUS\25CPDCRT\26HRDERR\27SFTERR\30ANYERR\ 76*25677Ssam \31INVCMD" 77*25677Ssam 78*25677Ssam /* 79*25677Ssam * DCB status codes. 80*25677Ssam */ 81*25677Ssam #define DCBABT 0x10000000 /* DCB Aborted */ 82*25677Ssam #define DCBUSC 0x20000000 /* DCB Unsuccesfully Completed */ 83*25677Ssam #define DCBCMP 0x40000000 /* DCB Complete */ 84*25677Ssam #define DCBSTR 0x80000000 /* DCB Started */ 85*25677Ssam 86*25677Ssam /* 87*25677Ssam * MDCB status codes. 88*25677Ssam */ 89*25677Ssam #define CTLRBSY 0x10000000 /* Cntlr Busy */ 90*25677Ssam #define INTCCDE 0x60000000 /* Interrupt Cause Code */ 91*25677Ssam #define DCBINT 0x80000000 /* DCB Interrupt Flag */ 92*25677Ssam 93*25677Ssam /* 94*25677Ssam * VDDC interrupt modes. 95*25677Ssam */ 96*25677Ssam #define NOINT 0x0 /* No Interrupt */ 97*25677Ssam #define INTERR 0x2 /* Interrupt on Error */ 98*25677Ssam #define INTSUC 0x1 /* Interrupt on Success */ 99*25677Ssam #define INTDONE 0x3 /* Interrupt on Error or Success */ 100*25677Ssam 101*25677Ssam 102*25677Ssam /* 103*25677Ssam * Constrol status definitions. 104*25677Ssam */ 105*25677Ssam #define CS_SCS 0xf /* Status Change Source (drive number) */ 106*25677Ssam #define CS_ELC 0x10 /* Error on Last Command */ 107*25677Ssam #define CS_ICC 0x60 /* Interupt Cause Code */ 108*25677Ssam #define ICC_NOI 0x00 /* No interupt */ 109*25677Ssam #define ICC_DUN 0x20 /* No interupt */ 110*25677Ssam #define ICC_ERR 0x40 /* No interupt */ 111*25677Ssam #define ICC_SUC 0x60 /* No interupt */ 112*25677Ssam #define CS_GO 0x80 /* Go bit (controller working) */ 113*25677Ssam #define CS_BE 0x100 /* Buss Error */ 114*25677Ssam #define CS_BOK 0x4000 /* Board O.K. */ 115*25677Ssam #define CS_SFL 0x8000 /* System fail */ 116*25677Ssam #define CS_LEC 0xff000000 /* Last Error Code */ 117*25677Ssam 118*25677Ssam /* Status word bit assignments */ 119*25677Ssam #define STA_UR 0x1 /* Unit Ready */ 120*25677Ssam #define STA_OC 0x2 /* On Cylinder */ 121*25677Ssam #define STA_SE 0x4 /* Seek Error */ 122*25677Ssam #define STA_DF 0x8 /* Drive Fault */ 123*25677Ssam #define STA_WP 0x10 /* Write Protected */ 124*25677Ssam #define STA_US 0x20 /* Unit Selected */ 125*25677Ssam 126*25677Ssam /* Interupt Control Field bit assignments */ 127*25677Ssam #define ICF_IPL 0x7 /* Interupt Priority Level */ 128*25677Ssam #define ICF_IEN 0x8 /* Interupt ENable */ 129*25677Ssam #define ICF_IV 0xff00 /* Interupt Vector */ 130*25677Ssam 131*25677Ssam /* Transfer Control Format bit assignments */ 132*25677Ssam #define TCF_AM 0xff /* Address Modifier */ 133*25677Ssam #define AM_SNPDA 0x01 /* Standard Non-Privileged Data Access */ 134*25677Ssam #define AM_SASA 0x81 /* Standard Ascending Sequential Access */ 135*25677Ssam #define AM_ENPDA 0xf1 /* Extended Non-Privileged Data Access */ 136*25677Ssam #define AM_EASA 0xe1 /* Extended Ascending Sequential Access */ 137*25677Ssam #define TCF_BTE 0x800 /* Block Transfer Enable */ 138*25677Ssam 139*25677Ssam /* Controller Configuration Flags bit assignments */ 140*25677Ssam #define CCF_STS 0x1 /* Sectors per Track Selectable */ 141*25677Ssam #define CCF_EAV 0x2 /* Enable Auto Vector */ 142*25677Ssam #define CCF_ERR 0x4 /* Enable Reset Register */ 143*25677Ssam #define CCF_XMD 0x60 /* XMD transfer mode (buss size) */ 144*25677Ssam #define XMD_8BIT 0x20 /* Do only 8 bit transfers */ 145*25677Ssam #define XMD_16BIT 0x40 /* Do only 16 bit transfers */ 146*25677Ssam #define XMD_32BIT 0x60 /* Do only 32 bit transfers */ 147*25677Ssam #define CCF_BSZ 0x300 /* Burst SiZe */ 148*25677Ssam #define BSZ_16WRD 0x000 /* 16 word transfer burst */ 149*25677Ssam #define BSZ_12WRD 0x100 /* 12 word transfer burst */ 150*25677Ssam #define BSZ_8WRD 0x200 /* 8 word transfer burst */ 151*25677Ssam #define BSZ_4WRD 0x300 /* 4 word transfer burst */ 152*25677Ssam #define CCF_ENP 0x1000 /* ENable Parity */ 153*25677Ssam #define CCF_EPE 0x2000 /* Enable Parity Errors */ 154*25677Ssam #define CCF_EDE 0x10000 /* Error Detection Enable */ 155*25677Ssam #define CCF_ECE 0x20000 /* Error Correction Enable */ 156*25677Ssam 157*25677Ssam /* 158*25677Ssam * Diagnostic register definitions. 159*25677Ssam */ 160*25677Ssam #define DIA_DC 0x7f /* Dump count mask */ 161*25677Ssam #define DIA_DWR 0x80 /* Dump Write / Read flag */ 162*25677Ssam #define DIA_ARE 0x100 /* Auto Rebuild Enable */ 163*25677Ssam #define DIA_CEN 0x200 /* Call ENable flag */ 164*25677Ssam #define DIA_KEY 0xAA550000 /* Reset KEY */ 165*25677Ssam 166*25677Ssam /* Sector Header bit assignments */ 167*25677Ssam #define VDMF 0x8000 /* Manufacturer Fault 1=good sector */ 168*25677Ssam #define VDUF 0x4000 /* User Fault 1=good sector */ 169*25677Ssam #define VDALT 0x2000 /* Alternate Sector 1=alternate */ 170*25677Ssam #define VDWPT 0x1000 /* Write Protect 1=Read Only Sector */ 171*25677Ssam 172*25677Ssam /* DCB Bit assignments */ 173*25677Ssam #define INT_IC 0x3 /* Interupt Control */ 174*25677Ssam #define IC_NOI 0x0 /* NO Interupt */ 175*25677Ssam #define IC_IOD 0x1 /* Interupt On Done */ 176*25677Ssam #define IC_IOE 0x2 /* Interupt On Error */ 177*25677Ssam #define IC_IOS 0x3 /* Interupt On Success */ 178*25677Ssam #define INT_PBA 0x4 /* Proceed before ACK */ 179*25677Ssam 180*25677Ssam /* 181*25677Ssam * Perform a reset on the controller. 182*25677Ssam */ 183*25677Ssam #define VDDC_RESET(addr, type) { \ 184*25677Ssam if (type == SMD_ECTLR) { \ 185*25677Ssam (addr)->diag_flags = DIA_KEY|DIA_CEN; \ 186*25677Ssam (addr)->cdr_mdcb_ptr = (fmt_mdcb *)0xffffffff; \ 187*25677Ssam DELAY(5000000); \ 188*25677Ssam } else { \ 189*25677Ssam (addr)->cdr_reset = 0x0; \ 190*25677Ssam DELAY(1500000); \ 191*25677Ssam } \ 192*25677Ssam } 193*25677Ssam 194*25677Ssam /* 195*25677Ssam * Abort a controller operation. 196*25677Ssam */ 197*25677Ssam #define VDDC_ABORT(a, type) { \ 198*25677Ssam if ((type) == SMDCTLR) { \ 199*25677Ssam movow(a, (ABORT & 0xffff0000) >> 16) ; \ 200*25677Ssam movow((int)(a)+2, ABORT & 0xffff); \ 201*25677Ssam } else \ 202*25677Ssam (a)->cdr_mdcb_ptr = (fmt_mdcb *)ABORT; \ 203*25677Ssam DELAY(1000000); \ 204*25677Ssam } 205*25677Ssam 206*25677Ssam /* 207*25677Ssam * Start i/o on controller. 208*25677Ssam */ 209*25677Ssam #define VDDC_ATTENTION(ctlr, mdcbadr, type) {\ 210*25677Ssam if (type == SMDCTLR) { \ 211*25677Ssam movow(ctlr, ((int)mdcbadr & 0xffff0000) >> 16) ; \ 212*25677Ssam movow((int)(ctlr)+2, (int)mdcbadr & 0xffff); \ 213*25677Ssam } else \ 214*25677Ssam (ctlr)->cdr_mdcb_ptr = mdcbadr; \ 215*25677Ssam } 216*25677Ssam 217*25677Ssam /* 218*25677Ssam * Poll controller until operation completes 219*25677Ssam * or timeout expires. 220*25677Ssam * YECH!!!! THIS SHOULD BE A SUBROUTINE!!! 221*25677Ssam */ 222*25677Ssam #define POLLTILLDONE(c, a, x, t) { \ 223*25677Ssam vdtimeout = 1000 * (x); \ 224*25677Ssam uncache(&(a)->operrsta); \ 225*25677Ssam while ((((a)->operrsta) & (DCBCMP|DCBABT)) == 0) { \ 226*25677Ssam DELAY(1000); \ 227*25677Ssam vdtimeout--; \ 228*25677Ssam uncache(&(a)->operrsta); \ 229*25677Ssam if (vdtimeout <= 0) { \ 230*25677Ssam printf("vd%d: controller timeout", c); \ 231*25677Ssam VDDC_ABORT(c, t); \ 232*25677Ssam DELAY(30000); \ 233*25677Ssam break; \ 234*25677Ssam } \ 235*25677Ssam } \ 236*25677Ssam if (vdtimeout > 0) \ 237*25677Ssam if ((t) == SMD_ECTLR && vdtimeout > 0) { \ 238*25677Ssam uncache(&(c)->cdr_csr); \ 239*25677Ssam while((c)->cdr_csr&CS_GO) { \ 240*25677Ssam DELAY(50); \ 241*25677Ssam uncache(&(c)->cdr_csr); \ 242*25677Ssam } \ 243*25677Ssam DELAY(500); \ 244*25677Ssam } else \ 245*25677Ssam DELAY(200); \ 246*25677Ssam uncache(&(a)->operrsta); \ 247*25677Ssam } 248*25677Ssam 249*25677Ssam /* 250*25677Ssam * A disk address. 251*25677Ssam */ 252*25677Ssam typedef struct { 253*25677Ssam char track; /* all 8 bits */ 254*25677Ssam char sector; /* all 8 bits */ 255*25677Ssam short cylinder; /* low order 12 bits */ 256*25677Ssam } dskadr; 257*25677Ssam 258*25677Ssam /* 259*25677Ssam * Sector formats. 260*25677Ssam */ 261*25677Ssam typedef union { 262*25677Ssam struct { 263*25677Ssam dskadr hdr_addr; 264*25677Ssam short smd_crc; 265*25677Ssam } smd; 266*25677Ssam struct { 267*25677Ssam dskadr physical; 268*25677Ssam dskadr logical; 269*25677Ssam long smd_e_crc; 270*25677Ssam } smd_e; 271*25677Ssam } fmt_hdr; 272*25677Ssam 273*25677Ssam /* 274*25677Ssam * DCB trailer formats. 275*25677Ssam */ 276*25677Ssam /* read/write trailer */ 277*25677Ssam typedef struct { 278*25677Ssam char *memadr; /* memory address */ 279*25677Ssam u_long wcount; /* 16 bit word count */ 280*25677Ssam dskadr disk; /* disk address */ 281*25677Ssam } trrw; 282*25677Ssam 283*25677Ssam /* scatter/gather trailer */ 284*25677Ssam typedef struct { 285*25677Ssam trrw start_addr; 286*25677Ssam struct { 287*25677Ssam char *nxt_addr; 288*25677Ssam u_long nxt_len; 289*25677Ssam } addr_chain[126]; 290*25677Ssam } trsg; 291*25677Ssam 292*25677Ssam /* seek trailer format */ 293*25677Ssam typedef struct { 294*25677Ssam dskadr skaddr; 295*25677Ssam } trseek; 296*25677Ssam 297*25677Ssam /* format trailer */ 298*25677Ssam typedef struct { 299*25677Ssam char *addr; /* data buffer to be filled on sector*/ 300*25677Ssam long nsectors; /* # of sectors to be formatted */ 301*25677Ssam dskadr disk; /* disk physical address info */ 302*25677Ssam dskadr hdr; /* header address info */ 303*25677Ssam } trfmt; 304*25677Ssam 305*25677Ssam /* reset/configure trailer */ 306*25677Ssam typedef struct { 307*25677Ssam long ncyl; /* # cylinders */ 308*25677Ssam long nsurfaces; /* # surfaces */ 309*25677Ssam long nsectors; /* # sectors */ 310*25677Ssam long slip_sec; /* # of slip sectors */ 311*25677Ssam } treset; 312*25677Ssam 313*25677Ssam /* 314*25677Ssam * DCB layout. 315*25677Ssam */ 316*25677Ssam typedef struct fmtdcb { 317*25677Ssam struct fmtdcb *nxtdcb; /* next dcb */ 318*25677Ssam short intflg; /* interrupt settings and flags */ 319*25677Ssam short opcode; /* DCB command code etc... */ 320*25677Ssam long operrsta; /* error & status info */ 321*25677Ssam short fill; /* not used */ 322*25677Ssam char devselect; /* drive selection */ 323*25677Ssam char trailcnt; /* trailer Word Count */ 324*25677Ssam long err_memadr; /* error memory address */ 325*25677Ssam char err_code; /* error codes for SMD/E */ 326*25677Ssam char fill2; /* not used */ 327*25677Ssam short err_wcount; /* error word count */ 328*25677Ssam char err_trk; /* error track/sector */ 329*25677Ssam char err_sec; /* error track/sector */ 330*25677Ssam short err_cyl; /* error cylinder adr */ 331*25677Ssam union { 332*25677Ssam trseek sktrail; /* seek command trailer */ 333*25677Ssam #ifdef notdef 334*25677Ssam trsg sgtrail; /* scatter/gather trailer */ 335*25677Ssam #endif 336*25677Ssam trrw rwtrail; /* read/write trailer */ 337*25677Ssam trfmt fmtrail; /* format trailer */ 338*25677Ssam treset rstrail; /* reset/configure trailer */ 339*25677Ssam } trail; 340*25677Ssam } fmt_dcb; 341*25677Ssam 342*25677Ssam /* 343*25677Ssam * MDCB layout. 344*25677Ssam */ 345*25677Ssam typedef struct { 346*25677Ssam fmt_dcb *firstdcb; /* first dcb in chain */ 347*25677Ssam fmt_dcb *procdcb; /* dcb being processed */ 348*25677Ssam fmt_dcb *intdcb; /* dcb causing interrupt */ 349*25677Ssam long vddcstat; /* VDDC status */ 350*25677Ssam } fmt_mdcb; 351*25677Ssam 352*25677Ssam /* 353*25677Ssam * Control-status communications block. 354*25677Ssam */ 355*25677Ssam typedef struct { 356*25677Ssam fmt_mdcb *cdr_mdcb_ptr; /* controller's mdcb */ 357*25677Ssam u_long cdr_reset; /* controller reset register */ 358*25677Ssam u_long cdr_csr; /* control/status register */ 359*25677Ssam long cdr_reserved; /* reserved */ 360*25677Ssam u_short cdr_status[16]; /* per-drive status register */ 361*25677Ssam u_short stat_chng; /* status change interupt register */ 362*25677Ssam u_short done_icf; /* interupt-complete register */ 363*25677Ssam u_short error_icf; /* error-interupt register */ 364*25677Ssam u_short success_icf; /* success-interupt register */ 365*25677Ssam u_short mdcb_tcf; /* mdcb transfer control register */ 366*25677Ssam u_short dcb_tcf; /* dcb transfer control register */ 367*25677Ssam u_short trail_tcf; /* trail transfer control register */ 368*25677Ssam u_short data_tcf; /* data transfer control register */ 369*25677Ssam u_long cdr_ccf; /* controller configuration flags */ 370*25677Ssam u_long sec_size; /* drive sector size */ 371*25677Ssam u_long diag_flags; /* diagnostic flag register */ 372*25677Ssam u_long diag_dump; /* pointer for diagnostic addresses */ 373*25677Ssam } cdr; 374*25677Ssam 375*25677Ssam /* controller types */ 376*25677Ssam #define UNKNOWN -1 377*25677Ssam #define SMDCTLR 1 /* smd interface */ 378*25677Ssam #define SMD_ECTLR 2 /* extended-smd interface */ 379*25677Ssam 380*25677Ssam /* drive types */ 381*25677Ssam #define XSD 0 382*25677Ssam #define FUJ 1 /* fujitsu */ 383*25677Ssam #define XFD 2 /* CDC 340Mb Winchester */ 384*25677Ssam #define SMD 3 /* CDC 9766 or equivalent */ 385*25677Ssam #define FSD 4 386*25677Ssam 387*25677Ssam /* 388*25677Ssam * Drive logical partitions. 389*25677Ssam */ 390*25677Ssam typedef struct { 391*25677Ssam long par_start; /* starting sector # */ 392*25677Ssam long par_len; /* size in sectors */ 393*25677Ssam } par_tab; 394*25677Ssam 395*25677Ssam typedef struct { 396*25677Ssam int secsize; /* bytes/sector */ 397*25677Ssam int nsec; /* sectors/track */ 398*25677Ssam int ntrak; /* tracks/cylinder */ 399*25677Ssam int ncyl; /* # cylinders */ 400*25677Ssam int nslip; /* # slip sectors */ 401*25677Ssam int rpm; /* revolutions/minute */ 402*25677Ssam int nbits; /* bits/track */ 403*25677Ssam char *type_name; /* drive name */ 404*25677Ssam long fmt_pat[16]; /* patterns to be used for formatting */ 405*25677Ssam par_tab partition[8]; /* partition tables */ 406*25677Ssam } fs_tab; 407*25677Ssam 408*25677Ssam /* physical information for known disk drives. */ 409*25677Ssam #ifdef VDGENDATA 410*25677Ssam long vddcaddr[] = { 0xf2000, 0xf2100, 0xf2200, 0xf2300 }; 411*25677Ssam long vdtimeout = 0; 412*25677Ssam 413*25677Ssam fs_tab vdst[] = { 414*25677Ssam {512, 48, 24, 711, 0, 3600, 0, "xsd", /* 515 Mb FSD */ 415*25677Ssam { 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98, 416*25677Ssam 0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980, 417*25677Ssam 0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800, 418*25677Ssam 0x4c993000, 0x99326000, 0x3264c000, 0x54c98000}, 419*25677Ssam {{0, 30528}, /* xsd0a cyl 0 - 52 */ 420*25677Ssam {30528, 30528}, /* xsd0b cyl 53 - 105 */ 421*25677Ssam {61056, 345600}, /* xsd0c cyl 106 - 705 */ 422*25677Ssam {0, 61056}, /* xsd0d cyl 709 - 710 (a & b) */ 423*25677Ssam {0, 406656}, /* xsd0e cyl 0 - 705 */ 424*25677Ssam {30528, 376128}, /* xsd0f cyl 53 - 705 (b & c) */ 425*25677Ssam {61056, 172800}, /* xsd0g cyl 106 - 405 (1/2 of c) */ 426*25677Ssam {233856, 172800}} /* xsd0h cyl 406 - 705 (1/2 of c) */ 427*25677Ssam }, 428*25677Ssam {512, 64, 10, 823, 0, 3600, 0, "fuj", /* 360 Mb Fujitsu */ 429*25677Ssam { 0x0264c993, 0x04c99326, 0x0993264c, 0x13264c98, 430*25677Ssam 0x264c9930, 0x4c993260, 0x993264c0, 0x3264c980, 431*25677Ssam 0x64c99300, 0xc9932600, 0x93264c00, 0x264c9800, 432*25677Ssam 0x4c993000, 0x99326000, 0x3264c000, 0x54c98000}, 433*25677Ssam {{0, 19200}, /* fuj0a cyl 0 - 59 */ 434*25677Ssam {19200, 24000}, /* fuj0b cyl 60 - 134 */ 435*25677Ssam {43200, 218560}, /* fuj0c cyl 135 - 817 */ 436*25677Ssam {0, 43200}, /* fuj0d cyl 821 - 822 (a & b) */ 437*25677Ssam {0, 261760}, /* fuj0e cyl 0 - 817 */ 438*25677Ssam {19200, 242560}, /* fuj0f cyl 0 - 134 (b & c) */ 439*25677Ssam {43200, 109440}, /* fuj0g cyl 135 - 476 (1/2 of c) */ 440*25677Ssam {152640, 109120}} /* fug0h cyl 477 - 817 (1/2 of c) */ 441*25677Ssam }, 442*25677Ssam {512, 32, 24, 711, 0, 3600, 0, "xfd", /* 340 Mb FSD */ 443*25677Ssam { 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360, 444*25677Ssam 0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600, 445*25677Ssam 0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000, 446*25677Ssam 0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000}, 447*25677Ssam #ifdef MICKEY 448*25677Ssam {{ 0, 20352 }, /* xfd0a cyl 0-52 */ 449*25677Ssam { 20352, 20352 }, /* xfd0b cyl 53-105 */ 450*25677Ssam { 40704, 230400 }, /* xfd0c cyl 106-705 */ 451*25677Ssam { 271104,1920 }, /* xfd0d cyl 706-710 */ 452*25677Ssam { 0, 271104 }, /* xfd0e cyl 0-705 */ 453*25677Ssam { 0, 273024 }}, /* xfd0f cyl 0-710 */ 454*25677Ssam #else 455*25677Ssam {{ 0, 20352 }, /* xfd0a cyl 0 - 52 */ 456*25677Ssam { 20352, 20352 }, /* xfd0b cyl 53 - 105 */ 457*25677Ssam { 40704, 230400 }, /* xfd0c cyl 106 - 705 */ 458*25677Ssam { 0, 40704 }, /* xfd0d cyl 709 - 710 (a & b) */ 459*25677Ssam { 0, 271104 }, /* xfd0e cyl 0 - 705 */ 460*25677Ssam { 20352, 250752 }, /* xfd0f cyl 53 - 705 (b & c) */ 461*25677Ssam { 40704, 115200 }, /* xfd0g cyl 106 - 405 (1/2 of c) */ 462*25677Ssam { 155904,115200 }} /* xfd0h cyl 406 - 705 (1/2 of c) */ 463*25677Ssam #endif 464*25677Ssam }, 465*25677Ssam {512, 32, 19, 823, 0, 3600, 0, "smd", /* 300 Mb SMD */ 466*25677Ssam { 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360, 467*25677Ssam 0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600, 468*25677Ssam 0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000, 469*25677Ssam 0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000}, 470*25677Ssam {{ 0, 20064}, /* smd0a cyl 0-65 */ 471*25677Ssam { 20064, 13680}, /* smd0b cyl 66-110 */ 472*25677Ssam { 33744, 214928}, /* smd0c cyl 111-817 */ 473*25677Ssam { 248672,1520 }, /* smd0d cyl 818-822 */ 474*25677Ssam { 0, 248672 }, /* smd0e cyl 0-817 */ 475*25677Ssam { 0, 250192 }}, /* smd0f cyl 0-822 */ 476*25677Ssam }, 477*25677Ssam {512, 32, 10, 823, 0, 3600, 0, "fsd", /* 160 Mb FSD */ 478*25677Ssam { 0x0d9b366c, 0x1b366cd8, 0x366cd9b0, 0x6cd9b360, 479*25677Ssam 0xd9b366c0, 0xb366cd80, 0x66cd9b00, 0xcd9b3600, 480*25677Ssam 0x9b366300, 0x366cd800, 0x6cd9b000, 0xd9b36000, 481*25677Ssam 0xb366c000, 0x66cd8000, 0xcd9b0000, 0x9b360000}, 482*25677Ssam {{0, 9600}, /* fsd0a cyl 0 - 59 */ 483*25677Ssam {9600, 12000}, /* fsd0b cyl 60 - 134 */ 484*25677Ssam {21600, 109280}, /* fsd0c cyl 135 - 817 */ 485*25677Ssam {0, 21600}, /* fsd0d cyl 0 - 134 (a & b) */ 486*25677Ssam {0, 130880}, /* fsd0e cyl 0 - 817 */ 487*25677Ssam {9600, 121280}, /* fsd0f cyl 60 - 817 (b & c) */ 488*25677Ssam {21600, 54240}, /* fsd0g cyl 135 - 473 (1/2 of c) */ 489*25677Ssam {75840, 55040}} /* fsd0h cyl 474 - 817 (1/2 of c) */ 490*25677Ssam } 491*25677Ssam }; 492*25677Ssam 493*25677Ssam int nvddrv = (sizeof (vdst) / sizeof (fs_tab)); 494*25677Ssam 495*25677Ssam #else 496*25677Ssam #ifdef STANDALONE 497*25677Ssam extern long vddcaddr[]; 498*25677Ssam extern long vdtimeout; 499*25677Ssam extern fs_tab vdst[]; 500*25677Ssam extern int nvddrv; 501*25677Ssam #endif 502*25677Ssam #endif 503