bring up to revision 7 for tahoe release
[unix-history] / usr / src / sys / tahoe / vba / hdreg.h
CommitLineData
a45c3f80
KB
1/*
2 * Include file for HCX Disk Controller (HDC).
3 *
674aaabc 4 * @(#)hdreg.h 7.2 (Berkeley) %G%
a45c3f80
KB
5 */
6
7#define TRUE 1
674aaabc
KB
8#define FALSE 0
9#define HDC_READ 0
10#define HDC_WRITE 1
11#define HDC_MAXBUS 2 /* max# buses */
12#define HDC_MAXCTLR 21 /* max# hdc controllers per bus */
13#define HDC_MAXDRIVE 4 /* max# drives per hdc controller */
14#define HDC_UNIT(x) (minor(x) >> 3) /* the hdc unit number (0-31) */
15#define HDC_PARTITION(x) (minor(x)&0x07)/* the hdc partition number (0-7) */
16#define HDC_DEFPART GB_MAXPART-1 /* partition# of def and diag cyls */
17#define HDC_SPB 2 /* sectors per block for hdc's */
18#define HDC_MID HID_HDC /* module id code for hdc's */
19#define HDC_REMOVABLE 80 /* lowest model# for removable disks */
20#define HDC_PHIO_SIZE 256 /* lword size of physical io buffer */
21#define HDC_VDATA_SIZE 16 /* vendor data size (long words) */
22#define HDC_XSTAT_SIZE 128 /* size of extended status (lwords) */
23#define HDC_MAXCHAIN 33 /* maximum number of data chains */
24#define HDC_MAXBC 64*1024 /* maximum byte count per data chain */
25#define HDC_MAXMCBS 32 /* max# mcb's the hdc can handle */
26#define HDC_MAXFLAWS 8000 /* max number of flaws per hdc disk */
27#define HDC_REGISTER(x) (hc->registers->x) /* io to an hdc register */
28#define HDC_DUMPSIZE HDC_MAXBC/DEV_BSIZE*HDC_MAXCHAIN
a45c3f80
KB
29 /* number of blocks per dump record */
30
31/*
32 * The following buf structure defines are used by the hdc handler.
33 * These are required since the handler initiates strategy calls;
34 * these calls require more function codes than just read/write,
35 * and they like to directly specify the cyl/head/sector.
36 * Note that b_upte and B_NOT1K are never used by the handler.
37 */
38
674aaabc 39#define B_LOCALIO B_NOT1K
a45c3f80 40
674aaabc
KB
41#define b_hdccommand b_upte[0]
42#define b_cyl b_upte[1]
43#define b_head b_upte[2]
44#define b_sector b_upte[3]
a45c3f80
KB
45
46/*
47 * These are the 4 hdc i/o register addresses.
48 *
49 * Writing to "master_mcb_reg" tells the hdc controller where the master
50 * mcb is and initiates hdc operation. The hdc then reads the master mcb
51 * and all new mcb's in the active mcb queue.
52 *
53 * Writing to "module_id_reg" causes the hdc to return the hdc's module id
54 * word in the location specified by the address written into the register.
55 */
56
57typedef struct {
674aaabc
KB
58 unsigned long master_mcb_reg; /* set the master mcb address */
59 unsigned long module_id_reg; /* returns hdc's module id (hdc_mid) */
60 unsigned long soft_reset_reg; /* a write here shuts down the hdc */
61 unsigned long hard_reset_reg; /* send a system reset to the hdc */
a45c3f80
KB
62} hdc_regs_type;
63
64/*
65 * Definition for the module id returned by the hdc when "module_id_reg"
66 * is written to. The format is defined by the hdc microcode.
67 */
68
69typedef struct {
674aaabc
KB
70 unsigned char module_id; /* module id; hdc's return HDC_MID */
71 unsigned char reserved;
72 unsigned char code_rev; /* micro-code rev#; FF= not loaded */
73 unsigned char fit; /* FIT test result; FF= no error */
a45c3f80
KB
74} hdc_mid_type;
75
76/*
77 * This structure defines the mcb's. A portion of this structure is
78 * used only by the software. The other portion is set up by software
79 * and sent to the hdc firmware to perform an operation; the order
80 * of this part of the mcb is determined by the controller firmware.
81 *
82 * "forw_mcb" and "back_mcb" form a doubly-linked list of mcb's.
83 *
84 * "context" is the software context word. The hdc firmware copies the
85 * the contents of this word to the master mcb whenever the mcb has been
86 * completed. Currently the virtual address of the mcb is saved here.
87 *
88 * "forw_phaddr" forms a linked list of mcbs. The addresses are physical
89 * since they are used by the hdc firmware.
90 *
91 * Bits in device control word #1 define the hdc command and
92 * control the operation of the hdc.
93 *
94 * Bits in device control word #2 define the disk sector address
95 * for the operation defined in dcw1.
96 */
97
98typedef struct {
674aaabc
KB
99 long lwc; /* long word count & data chain bit */
100 long ta; /* transfer address */
a45c3f80
KB
101} data_chain_type;
102
674aaabc 103#define LWC_DATA_CHAIN 0x80000000 /* mask for data chain bit in lwc */
a45c3f80 104
674aaabc
KB
105struct mcb_struct;
106typedef struct mcb_struct mcb_type;
a45c3f80 107struct mcb_struct {
674aaabc
KB
108 /* this part used only by software */
109 mcb_type *forw_mcb; /* pointer to next mcb in chain */
a45c3f80 110 mcb_type *back_mcb; /* pointer to previous mcb in chain */
674aaabc
KB
111 struct buf *buf_ptr; /* ptr to buf structure for this mcb */
112 long mcb_phaddr; /* phaddr of hw's part of this mcb */
a45c3f80 113
674aaabc
KB
114 /* this part is sent to the hdc hw */
115 unsigned long forw_phaddr; /* phys address of next mcb */
116 unsigned priority : 8; /* device control word #1 */
117 unsigned interrupt : 1; /* " */
118 unsigned drive : 7; /* " */
119 unsigned command : 16; /* " (see HCMD_) */
120 unsigned cyl : 13; /* device control word #2 */
121 unsigned head : 9; /* " */
122 unsigned sector : 10; /* " */
123 unsigned long reserved[2]; /* */
124 unsigned long context; /* software context word */
125 data_chain_type chain[HDC_MAXCHAIN];/* data chain and lword count */
126};
127 /* defines for the "command"s */
128#define HCMD_STATUS 0x40 /* command: read drive status */
129#define HCMD_READ 0x60 /* command: read data */
130#define HCMD_VENDOR 0x6A /* command: read vendor data */
131#define HCMD_VERIFY 0x6D /* command: verify a track */
132#define HCMD_WRITE 0x70 /* command: write data */
133#define HCMD_FORMAT 0x7E /* command: format a track */
134#define HCMD_CERTIFY 0x7F /* command: certify a track */
135#define HCMD_WCS 0xD0 /* command: write control store */
a45c3f80
KB
136
137/*
138 * This structure defines the master mcb - one per hdc controller.
139 * The order of this structure is determined by the controller firmware.
140 * "R" and "W" indicate read-only and write-only.
141 *
142 * Bits in the module control long word, "mcl", control the invocation of
143 * operations on the hdc.
144 *
145 * The hdc operates in queued mode or immediate mode.
146 * In queued mode, it grabs new mcb's, prioritizes them, and adds
147 * them to its queue; it knows if we've added any mcb's by checking
148 * forw_phaddr to see if any are linked off of there.
149 *
150 * Bits in the master mcb's status word, "mcs", indicate the status
151 * of the last-processed mcb. The MCS_ definitions define these bits.
152 * This word is set to zero when the mcb queue is passed to the hdc
153 * controller; the hdc controller then sets bits in this word.
154 * We cannot modify the mcb queue until the hdc has completed an mcb
155 * (the hdc sets the MCS_Q_DONE bit).
156 *
157 * The "context" word is copied from the context word of the completed
158 * mcb. It is currently the virtual pointer to the completed mcb.
159 */
160
161typedef struct {
674aaabc
KB
162 unsigned long mcl; /* W module control lword (MCL_) */
163 unsigned long interrupt; /* W interrupt acknowledge word */
a45c3f80 164 unsigned long forw_phaddr; /* W physical address of first mcb */
674aaabc
KB
165 unsigned long reserve1;
166 unsigned long reserve2;
a45c3f80 167 unsigned long mcs; /* R status for last completed mcb */
674aaabc
KB
168 unsigned long cmcb_phaddr; /* W physical addr of completed mcb */
169 unsigned long context; /* R software context word */
170 unsigned long xstatus[HDC_XSTAT_SIZE];/* R xstatus of last mcb */
a45c3f80
KB
171} master_mcb_type;
172
674aaabc
KB
173 /* definition of master mcb "mcl" */
174#define MCL_QUEUED 0x00000010 /* start queued execution of mcb's */
175#define MCL_IMMEDIATE 0x00000001 /* start immediate xqt of an mcb */
a45c3f80 176
674aaabc
KB
177 /* definition of master mcb "mcs" */
178#define MCS_DONE 0x00000080 /* an mcb is done; status is valid */
179#define MCS_FATALERROR 0x00000002 /* a fatal error occurred */
180#define MCS_SOFTERROR 0x00000001 /* a recoverable error occurred */
a45c3f80
KB
181
182/*
183 * This structure defines the information returned by the hdc
184 * controller for a "read drive status" (HCMD_STATUS) command.
185 * The format of this structure is determined by the hdc firmware.
186 * r1, r2, etc. are reserved for future use.
187 */
188
189typedef struct {
674aaabc
KB
190 unsigned long drs; /* drive status (see DRS_ below) */
191 unsigned long r1;
192 unsigned long r2;
193 unsigned long r3;
194 unsigned short max_cyl; /* max logical cylinder address */
195 unsigned short max_head; /* max logical head address */
196 unsigned short r4;
197 unsigned short max_sector; /* max logical sector address */
198 unsigned short def_cyl; /* definition track cylinder address */
199 unsigned short def_cyl_count; /* definition track cylinder count */
200 unsigned short diag_cyl; /* diagnostic track cylinder address */
201 unsigned short diag_cyl_count; /* diagnostic track cylinder count */
202 unsigned short max_phys_cyl; /* max physical cylinder address */
203 unsigned short max_phys_head; /* max physical head address */
204 unsigned short r5;
205 unsigned short max_phys_sector;/* max physical sector address */
206 unsigned short r6;
207 unsigned short id; /* drive id (drive model) */
208 unsigned short r7;
209 unsigned short bytes_per_sec; /* bytes/sector -vendorflaw conversn */
210 unsigned short r8;
211 unsigned short rpm; /* disk revolutions per minute */
212 unsigned long r9;
213 unsigned long r10;
214 unsigned long r11;
a45c3f80
KB
215} drive_stat_type;
216
674aaabc
KB
217 /* defines for drive_stat drs word */
218#define DRS_FAULT 0x00000080 /* drive is reporting a fault */
219#define DRS_RESERVED 0x00000040 /* drive is reserved by other port */
220#define DRS_WRITE_PROT 0x00000020 /* drive is write protected */
221#define DRS_ON_CYLINDER 0x00000002 /* drive heads are not moving now */
222#define DRS_ONLINE 0x00000001 /* drive is available for operation */
a45c3f80
KB
223
224/*
225 * hdc controller table. It contains information specific to each controller.
226 */
227
228typedef struct {
674aaabc 229 int ctlr; /* controller number (0-15) */
a45c3f80 230 hdc_regs_type *registers; /* base address of hdc io registers */
674aaabc
KB
231 mcb_type *forw_active; /* doubly linked list of */
232 mcb_type *back_active; /* .. active mcb's */
233 mcb_type *forw_free; /* doubly linked list of */
234 mcb_type *back_free; /* .. free mcb's */
235 mcb_type *forw_wait; /* doubly linked list of */
236 mcb_type *back_wait; /* .. waiting mcb's */
237 hdc_mid_type mid; /* the module id is read to here */
238 long master_phaddr; /* physical address of master mcb */
239 master_mcb_type master_mcb; /* the master mcb for this hdc */
240 mcb_type mcbs[HDC_MAXMCBS];/* pool of mcb's for this hdc */
a45c3f80
KB
241} hdc_ctlr_type;
242
243/*
244 * hdc unit table. It contains information specific to each hdc drive.
245 * Some information is obtained from the profile prom and geometry block.
246 */
247
248typedef struct {
674aaabc
KB
249 par_tab partition[GB_MAXPART]; /* partition definitions */
250 int ctlr; /* the controller number (0-15) */
251 int slave; /* the slave number (0-4) */
252 int unit; /* the unit number (0-31) */
253 int id; /* identifies the disk model */
254 int spc; /* sectors per cylinder */
255 int cylinders; /* number of logical cylinders */
256 int heads; /* number of logical heads */
257 int sectors; /* number of logical sectors/track */
258 int phys_cylinders; /* number of physical cylinders */
259 int phys_heads; /* number of physical heads */
a45c3f80 260 int phys_sectors; /* number of physical sectors/track */
674aaabc
KB
261 int def_cyl; /* logical cylinder of drive def */
262 int def_cyl_count; /* number of logical def cylinders */
263 int diag_cyl; /* logical cylinder of diag area */
a45c3f80 264 int diag_cyl_count; /* number of logical diag cylinders */
674aaabc
KB
265 int rpm; /* disk rpm */
266 int bytes_per_sec; /* bytes/sector -vendorflaw conversn */
267 int format; /* TRUE= format program is using dsk */
268 mcb_type phio_mcb; /* mcb for handler physical io */
269 struct buf phio_buf; /* buf for handler physical io */
270 unsigned long phio_data[HDC_PHIO_SIZE]; /* data for physical io */
271 struct buf raw_buf; /* buf structure for raw i/o */
a45c3f80 272} hdc_unit_type;