xref: /original-bsd/sys/tahoe/vba/hdreg.h (revision 6884d44a)
1 /*
2  * Copyright (c) 1988 The Regents of the University of California.
3  * All rights reserved.
4  *
5  * This code is derived from software contributed to Berkeley by
6  * Harris Corp.
7  *
8  * %sccs.include.redist.c%
9  *
10  *	@(#)hdreg.h	7.4 (Berkeley) 06/28/90
11  */
12 
13 #ifndef COMPAT_42
14 #define	COMPAT_42
15 #endif
16 
17 #define	HDC_READ	0
18 #define	HDC_WRITE	1
19 
20 #define	HDC_MAXBUS	2		/* max# buses */
21 #define	HDC_MAXCTLR	21		/* max# hdc controllers per bus */
22 #define	HDC_MAXDRIVE	4		/* max# drives per hdc controller */
23 #define	HDC_MAXMCBS	32		/* max# mcb's the hdc can handle */
24 #define	HDC_MAXCHAIN	64		/* max# of data chains */
25 #define	HDC_MAXBC	64*1024		/* max# byte count per data chain */
26 #define	HDC_MAXFLAWS	8000		/* max# flaws per hdc disk */
27 
28 #define	HDC_SPB		2		/* sectors per block for hdc's */
29 #define	HDC_VDATA_SIZE	16		/* vendor data size (long words) */
30 
31 #define	HDC_REG(x)	(hd->reg->x)	/* set an HDC register */
32 					/* number of blocks per dump record */
33 #define	HDC_DUMPSIZE	(HDC_MAXBC/DEV_BSIZE*HDC_MAXCHAIN)
34 
35 /*
36  * These are the 4 hdc i/o register addresses.  Writing to "master_mcb"
37  * tells the hdc controller where the master mcb is and initiates hdc
38  * operation. The hdc then reads the master mcb and all new mcb's in the
39  * active mcb queue.  Writing to "module_id" causes the hdc to return the
40  * hdc's module id word in the location specified by the address written
41  * into the register.  "soft_reset" causes orderly shutdown of HDC; it's
42  * unclear from the manual what "hard_reset" does, but it should never be
43  * used as use while the HDC is active may cause format errors.
44  */
45 struct registers {
46 	u_long	master_mcb,		/* set the master mcb address */
47 		module_id,		/* returns hdc's module id (hdc_mid) */
48 		soft_reset,		/* shut down the hdc */
49 		hard_reset;		/* send a system reset to the hdc */
50 };
51 
52 /*
53  * Definition for the module id returned by the hdc when "module_id"
54  * is written to.  The format is defined by the hdc microcode.
55  */
56 #define	HID_HDC		0x01		/* hvme_id for HDC */
57 #define	HDC_MID		HID_HDC		/* module id code for hdc's */
58 struct module_id {
59 	u_char	module_id,		/* module id; hdc's return HDC_MID */
60 		reserved,
61 		code_rev,		/* micro-code rev#; FF= not loaded */
62 		fit;			/* FIT test result; FF= no error */
63 };
64 
65 /*
66  * This structure defines the mcb's.  A portion of this structure is used
67  * only by the software.  The other portion is set up by software and sent
68  * to the hdc firmware to perform an operation; the order of this part of
69  * the mcb is determined by the controller firmware.
70  *
71  * "context" is the software context word.  The hdc firmware copies the
72  * contents of this word to the master mcb whenever the mcb has been
73  * completed.  The virtual address of the mcb is usually saved here.
74  *
75  * "forw_phaddr" forms a linked list of mcbs.  The addresses are physical
76  * since they are used by the hdc firmware.
77  *
78  * Bits in device control word #1 define the hdc command and control the
79  * operation of the hdc.  Bits in device control word #2 define the disk
80  * sector address for the operation defined in control word #1.
81  */
82 #define	LWC_DATA_CHAIN	0x80000000	/* mask for data chain bit in wcount */
83 struct mcb {
84 	u_long	forw_phaddr;		/* phys address of next mcb */
85 	u_int	priority  :  8,		/* device control word #1 */
86 		interrupt :  1,		/*        "               */
87 		drive     :  7,		/*        "               */
88 		command   : 16,		/*        "   (see HCMD_) */
89 		cyl       : 13,		/* device control word #2 */
90 		head      :  9,		/*        "               */
91 		sector    : 10;		/*        "               */
92 	u_long	r1, r2,
93 		context;		/* software context word */
94 	struct chain {
95 		long	wcount,		/* word count */
96 			memadr;		/* transfer address */
97 	} chain[HDC_MAXCHAIN];		/* data chain */
98 };
99 					/* defines for the "command"s */
100 #define	HCMD_STATUS	0x40		/* command: read drive status */
101 #define	HCMD_READ	0x60		/* command: read data */
102 #define	HCMD_VENDOR	0x6a		/* command: read vendor data */
103 #define	HCMD_VERIFY	0x6d		/* command: verify a track */
104 #define	HCMD_WRITE	0x70		/* command: write data */
105 #define	HCMD_FORMAT	0x7e		/* command: format a track */
106 #define	HCMD_CERTIFY	0x7f		/* command: certify a track */
107 #define	HCMD_WCS	0xd0		/* command: write control store */
108 
109 /*
110  * This structure defines the master mcb - one per hdc controller.
111  * The order of this structure is determined by the controller firmware.
112  * "R" and "W" indicate read-only and write-only.
113  *
114  * Bits in the module control long word, "mcl", control the invocation of
115  * operations on the hdc.
116  *
117  * The hdc operates in queued mode or immediate mode.  In queued mode, it
118  * grabs new mcb's, prioritizes them, and adds them to its queue; it knows
119  * if we've added any mcb's by checking forw_phaddr to see if any are
120  * linked off of there.
121  *
122  * Bits in the master mcb's status word, "mcs", indicate the status
123  * of the last-processed mcb.  The MCS_ definitions define these bits.
124  * This word is set to zero when the mcb queue is passed to the hdc
125  * controller; the hdc controller then sets bits in this word.
126  * We cannot modify the mcb queue until the hdc has completed an mcb
127  * (the hdc sets the MCS_Q_DONE bit).
128  *
129  * The "context" word is copied from the context word of the completed
130  * mcb.  It is currently the virtual pointer to the completed mcb.
131  */
132 					/* definition of master mcb "mcl" */
133 #define	MCL_QUEUED	0x00000010	/* start queued execution of mcb's */
134 #define	MCL_IMMEDIATE	0x00000001	/* start immediate xqt of an mcb */
135 					/* definition of master mcb "mcs" */
136 #define	MCS_DONE	0x00000080	/* an mcb is done; status is valid */
137 #define	MCS_FATALERROR	0x00000002	/* a fatal error occurred */
138 #define	MCS_SOFTERROR	0x00000001	/* a recoverable error occurred */
139 
140 struct master_mcb {
141 	u_long	mcw,			/* W  module control word (MCL_) */
142 		interrupt,		/* W  interrupt acknowledge word */
143 		forw_phaddr,		/* W  physical address of first mcb */
144 		r1, r2,
145 		mcs,			/* R  status for last completed mcb */
146 		cmcb_phaddr,		/* W  physical addr of completed mcb */
147 		context,		/* W  software context word */
148 #define	HDC_XSTAT_SIZE	128		/* size of extended status (lwords) */
149 		xstatus[HDC_XSTAT_SIZE];/* R  xstatus of last mcb */
150 };
151 
152 /*
153  * This structure defines the information returned by the hdc controller for
154  * a "read drive status" (HCMD_STATUS) command.  The format of this structure
155  * is determined by the hdc firmware.  r[1-11] are reserved for future use.
156  */
157 					/* defines for drive_stat drs word */
158 #define	DRS_FAULT	0x00000080	/* drive is reporting a fault */
159 #define	DRS_RESERVED	0x00000040	/* drive is reserved by other port */
160 #define	DRS_WRITE_PROT	0x00000020	/* drive is write protected */
161 #define	DRS_ON_CYLINDER	0x00000002	/* drive heads are not moving now */
162 #define	DRS_ONLINE	0x00000001	/* drive is available for operation */
163 
164 struct status {
165 	u_long	drs,			/* drive status (see DRS_) */
166 		r1, r2, r3;
167 	u_short	max_cyl,		/* max logical cylinder address */
168 		max_head,		/* max logical head address */
169 		r4,
170 		max_sector,		/* max logical sector address */
171 		def_cyl,		/* definition track cylinder address */
172 		def_cyl_count,		/* definition track cylinder count */
173 		diag_cyl,		/* diagnostic track cylinder address */
174 		diag_cyl_count,		/* diagnostic track cylinder count */
175 		max_phys_cyl,		/* max physical cylinder address */
176 		max_phys_head,		/* max physical head address */
177 		r5,
178 		max_phys_sector,	/* max physical sector address */
179 		r6,
180 		id,			/* drive id (drive model) */
181 		r7,
182 		bytes_per_sec,		/* bytes/sector -vendorflaw conversn */
183 		r8,
184 		rpm;			/* disk revolutions per minute */
185 	u_long	r9, r10, r11;
186 };
187 
188 #ifdef COMPAT_42
189 #define	GB_ID		"geometry"
190 #define	GB_ID_LEN 	sizeof(GB_ID)-1
191 #define	GB_MAXPART	8
192 #define	GB_VERSION	1
193 
194 #define	HDC_DEFPART	GB_MAXPART-1	/* partition# of def and diag cyls */
195 #define	BPS		512		/* bytes per sector */
196 
197 /*
198  * Geometry Block:
199  *
200  * The geometry block defines partition offsets and information about the
201  * flaw maps on the flaw map track.  It resides on the first sector of the
202  * flaw map track.  This structure is also used by vddc disk controllers.
203  * In this case, the block resides at sector 0 of the disk.
204  *
205  * The geometry_sector structure defines the sector containing the geometry
206  * block.  This sector is checksumed independent of the geometry information.
207  * The fields in these structured which should never be moved are the id and
208  * version fields in the geometry_block structure and the checksum field in
209  * the geometry_sector structure.  This will provide for easy extensions in
210  * the future.
211  */
212 
213 #define	DRIVE_TYPE	flaw_offset	/* For VDDC Geometry Blocks Only */
214 
215 typedef struct {
216 	char	id[GB_ID_LEN];		/* identifies the geometry block */
217 	long	version,		/* geometry block version number */
218 		flaw_offset,		/* flaw map byte offset in partition7 */
219 		flaw_size,		/* harris flaw map size in bytes */
220 		flaw_checksum,		/* sum of bytes in harris flaw map */
221 		unused[3];		/* --- available for use */
222 	struct par_tab {
223 		long	start,		/* starting 1K block number */
224 			length;		/* partition size in 1K blocks */
225 	} partition[GB_MAXPART];	/* partition definitions */
226 } geometry_block;
227 
228 typedef struct {
229 	geometry_block	geometry_block;	/* disk geometry */
230 	char	filler[BPS - sizeof(geometry_block) - sizeof(long)];
231 	long	checksum;		/* sector checksum */
232 } geometry_sector;
233 
234 /*
235  * GB_CHECKSUM:
236  *
237  * This macro computes the checksum for the geometry sector and returns the
238  * value.  Input to this macro is a pointer to the geometry_sector.  Pretty
239  * useless, should at least have done an XOR.
240  */
241 #define GB_CHECKSUM(_gs_ptr, _checksum) { \
242 	register u_char *_ptr; \
243 	register u_long _i, _xsum; \
244 	_xsum = 0; \
245 	_ptr = (u_char *)(_gs_ptr); \
246 	for (_i = 0; _i < (sizeof(geometry_sector) - sizeof(long)); _i++) \
247 		_xsum += * _ptr++; \
248 	_checksum = _xsum; \
249 }
250 #endif /* COMPAT_42 */
251