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