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