xref: /csrg-svn/sys/tahoe/vba/hdreg.h (revision 33166)
132391Sbostic /*
232391Sbostic  *  Include file for HCX Disk Controller (HDC).
332391Sbostic  *
4*33166Sbostic  *	@(#)hdreg.h	7.2 (Berkeley) 12/28/87
532391Sbostic  */
632391Sbostic 
732391Sbostic #define	TRUE		1
8*33166Sbostic #define	FALSE		0
9*33166Sbostic #define	HDC_READ	0
10*33166Sbostic #define	HDC_WRITE	1
11*33166Sbostic #define	HDC_MAXBUS	2		/* max# buses */
12*33166Sbostic #define	HDC_MAXCTLR	21		/* max# hdc controllers per bus */
13*33166Sbostic #define	HDC_MAXDRIVE	4		/* max# drives per hdc controller */
14*33166Sbostic #define	HDC_UNIT(x)	(minor(x) >> 3) /* the hdc unit number (0-31) */
15*33166Sbostic #define	HDC_PARTITION(x) (minor(x)&0x07)/* the hdc partition number (0-7) */
16*33166Sbostic #define	HDC_DEFPART	GB_MAXPART-1	/* partition# of def and diag cyls */
17*33166Sbostic #define	HDC_SPB		2		/* sectors per block for hdc's */
18*33166Sbostic #define	HDC_MID		HID_HDC		/* module id code for hdc's */
19*33166Sbostic #define	HDC_REMOVABLE	80		/* lowest model# for removable disks */
20*33166Sbostic #define	HDC_PHIO_SIZE	256		/* lword size of physical io buffer */
21*33166Sbostic #define	HDC_VDATA_SIZE	16		/* vendor data size (long words) */
22*33166Sbostic #define	HDC_XSTAT_SIZE	128		/* size of extended status (lwords) */
23*33166Sbostic #define	HDC_MAXCHAIN	33		/* maximum number of data chains */
24*33166Sbostic #define	HDC_MAXBC	64*1024		/* maximum byte count per data chain */
25*33166Sbostic #define	HDC_MAXMCBS	32		/* max# mcb's the hdc can handle */
26*33166Sbostic #define	HDC_MAXFLAWS	8000		/* max number of flaws per hdc disk */
27*33166Sbostic #define	HDC_REGISTER(x)	(hc->registers->x) /* io to an hdc register */
28*33166Sbostic #define	HDC_DUMPSIZE	HDC_MAXBC/DEV_BSIZE*HDC_MAXCHAIN
2932391Sbostic 					/* number of blocks per dump record */
3032391Sbostic 
3132391Sbostic /*
3232391Sbostic  * The following buf structure defines are used by the hdc handler.
3332391Sbostic  * These are required since the handler initiates strategy calls;
3432391Sbostic  * these calls require more function codes than just read/write,
3532391Sbostic  * and they like to directly specify the cyl/head/sector.
3632391Sbostic  * Note that b_upte and B_NOT1K are never used by the handler.
3732391Sbostic  */
3832391Sbostic 
39*33166Sbostic #define	B_LOCALIO	B_NOT1K
4032391Sbostic 
41*33166Sbostic #define	b_hdccommand	b_upte[0]
42*33166Sbostic #define	b_cyl		b_upte[1]
43*33166Sbostic #define	b_head		b_upte[2]
44*33166Sbostic #define	b_sector	b_upte[3]
4532391Sbostic 
4632391Sbostic /*
4732391Sbostic  * These are the 4 hdc i/o register addresses.
4832391Sbostic  *
4932391Sbostic  * Writing to "master_mcb_reg" tells the hdc controller where the master
5032391Sbostic  * mcb is and initiates hdc operation. The hdc then reads the master mcb
5132391Sbostic  * and all new mcb's in the active mcb queue.
5232391Sbostic  *
5332391Sbostic  * Writing to "module_id_reg" causes the hdc to return the hdc's module id
5432391Sbostic  * word in the location specified by the address written into the register.
5532391Sbostic  */
5632391Sbostic 
5732391Sbostic typedef struct {
58*33166Sbostic 	unsigned long	master_mcb_reg;	/* set the master mcb address */
59*33166Sbostic 	unsigned long	module_id_reg;	/* returns hdc's module id (hdc_mid) */
60*33166Sbostic 	unsigned long	soft_reset_reg;	/* a write here shuts down the hdc */
61*33166Sbostic 	unsigned long	hard_reset_reg;	/* send a system reset to the hdc */
6232391Sbostic } hdc_regs_type;
6332391Sbostic 
6432391Sbostic /*
6532391Sbostic  * Definition for the module id returned by the hdc when "module_id_reg"
6632391Sbostic  * is written to. The format is defined by the hdc microcode.
6732391Sbostic  */
6832391Sbostic 
6932391Sbostic typedef struct {
70*33166Sbostic 	unsigned char	module_id;	/* module id; hdc's return HDC_MID */
71*33166Sbostic 	unsigned char	reserved;
72*33166Sbostic 	unsigned char	code_rev;	/* micro-code rev#; FF= not loaded */
73*33166Sbostic 	unsigned char	fit;		/* FIT test result; FF= no error */
7432391Sbostic } hdc_mid_type;
7532391Sbostic 
7632391Sbostic /*
7732391Sbostic  * This structure defines the mcb's. A portion of this structure is
7832391Sbostic  * used only by the software. The other portion is set up by software
7932391Sbostic  * and sent to the hdc firmware to perform an operation; the order
8032391Sbostic  * of this part of the mcb is determined by the controller firmware.
8132391Sbostic  *
8232391Sbostic  * "forw_mcb" and "back_mcb" form a doubly-linked list of mcb's.
8332391Sbostic  *
8432391Sbostic  * "context" is the software context word. The hdc firmware copies the
8532391Sbostic  * the contents of this word to the master mcb whenever the mcb has been
8632391Sbostic  * completed. Currently the virtual address of the mcb is saved here.
8732391Sbostic  *
8832391Sbostic  * "forw_phaddr" forms a linked list of mcbs. The addresses are physical
8932391Sbostic  * since they are used by the hdc firmware.
9032391Sbostic  *
9132391Sbostic  * Bits in device control word #1 define the hdc command and
9232391Sbostic  * control the operation of the hdc.
9332391Sbostic  *
9432391Sbostic  * Bits in device control word #2 define the disk sector address
9532391Sbostic  * for the operation defined in dcw1.
9632391Sbostic  */
9732391Sbostic 
9832391Sbostic typedef struct {
99*33166Sbostic 	long	lwc;			/* long word count & data chain bit */
100*33166Sbostic 	long	ta;			/* transfer address */
10132391Sbostic } data_chain_type;
10232391Sbostic 
103*33166Sbostic #define LWC_DATA_CHAIN	0x80000000	/* mask for data chain bit in lwc */
10432391Sbostic 
105*33166Sbostic struct mcb_struct;
106*33166Sbostic typedef struct mcb_struct mcb_type;
10732391Sbostic struct mcb_struct {
108*33166Sbostic 					/* this part used only by software */
109*33166Sbostic 	mcb_type	*forw_mcb;	/* pointer to next mcb in chain */
11032391Sbostic 	mcb_type	*back_mcb;	/* pointer to previous mcb in chain */
111*33166Sbostic 	struct buf	*buf_ptr;	/* ptr to buf structure for this mcb */
112*33166Sbostic 	long		mcb_phaddr;	/* phaddr of hw's part of this mcb */
11332391Sbostic 
114*33166Sbostic 					/* this part is sent to the hdc hw */
115*33166Sbostic 	unsigned long	forw_phaddr;	/* phys address of next mcb */
116*33166Sbostic 	unsigned	priority  :  8;	/* device control word #1 */
117*33166Sbostic 	unsigned	interrupt :  1;	/*        "               */
118*33166Sbostic 	unsigned	drive     :  7;	/*        "               */
119*33166Sbostic 	unsigned	command   : 16;	/*        "   (see HCMD_) */
120*33166Sbostic 	unsigned	cyl       : 13;	/* device control word #2 */
121*33166Sbostic 	unsigned	head      :  9;	/*        "               */
122*33166Sbostic 	unsigned	sector    : 10;	/*        "               */
123*33166Sbostic 	unsigned long	reserved[2];	/*                        */
124*33166Sbostic 	unsigned long	context;	/* software context word */
125*33166Sbostic 	data_chain_type chain[HDC_MAXCHAIN];/* data chain and lword count */
126*33166Sbostic };
127*33166Sbostic 					/* defines for the "command"s */
128*33166Sbostic #define	HCMD_STATUS	0x40		/* command: read drive status */
129*33166Sbostic #define	HCMD_READ	0x60		/* command: read data */
130*33166Sbostic #define	HCMD_VENDOR	0x6A		/* command: read vendor data */
131*33166Sbostic #define	HCMD_VERIFY	0x6D		/* command: verify a track */
132*33166Sbostic #define	HCMD_WRITE	0x70		/* command: write data */
133*33166Sbostic #define	HCMD_FORMAT	0x7E		/* command: format a track */
134*33166Sbostic #define	HCMD_CERTIFY	0x7F		/* command: certify a track */
135*33166Sbostic #define	HCMD_WCS	0xD0		/* command: write control store */
13632391Sbostic 
13732391Sbostic /*
13832391Sbostic  * This structure defines the master mcb - one per hdc controller.
13932391Sbostic  * The order of this structure is determined by the controller firmware.
14032391Sbostic  * "R" and "W" indicate read-only and write-only.
14132391Sbostic  *
14232391Sbostic  * Bits in the module control long word, "mcl", control the invocation of
14332391Sbostic  * operations on the hdc.
14432391Sbostic  *
14532391Sbostic  * The hdc operates in queued mode or immediate mode.
14632391Sbostic  * In queued mode, it grabs new mcb's, prioritizes them, and adds
14732391Sbostic  * them to its queue; it knows if we've added any mcb's by checking
14832391Sbostic  * forw_phaddr to see if any are linked off of there.
14932391Sbostic  *
15032391Sbostic  * Bits in the master mcb's status word, "mcs", indicate the status
15132391Sbostic  * of the last-processed mcb. The MCS_ definitions define these bits.
15232391Sbostic  * This word is set to zero when the mcb queue is passed to the hdc
15332391Sbostic  * controller; the hdc controller then sets bits in this word.
15432391Sbostic  * We cannot modify the mcb queue until the hdc has completed an mcb
15532391Sbostic  * (the hdc sets the MCS_Q_DONE bit).
15632391Sbostic  *
15732391Sbostic  * The "context" word is copied from the context word of the completed
15832391Sbostic  * mcb. It is currently the virtual pointer to the completed mcb.
15932391Sbostic  */
16032391Sbostic 
16132391Sbostic typedef struct {
162*33166Sbostic 	unsigned long	mcl;		/* W  module control lword (MCL_) */
163*33166Sbostic 	unsigned long	interrupt;	/* W  interrupt acknowledge word */
16432391Sbostic 	unsigned long	forw_phaddr;	/* W  physical address of first mcb */
165*33166Sbostic 	unsigned long	reserve1;
166*33166Sbostic 	unsigned long	reserve2;
16732391Sbostic 	unsigned long	mcs;		/* R  status for last completed mcb */
168*33166Sbostic 	unsigned long	cmcb_phaddr;	/* W  physical addr of completed mcb */
169*33166Sbostic 	unsigned long	context;	/* R  software context word */
170*33166Sbostic 	unsigned long	xstatus[HDC_XSTAT_SIZE];/* R  xstatus of last mcb */
17132391Sbostic } master_mcb_type;
17232391Sbostic 
173*33166Sbostic 					/* definition of master mcb "mcl" */
174*33166Sbostic #define	MCL_QUEUED	0x00000010	/* start queued execution of mcb's */
175*33166Sbostic #define	MCL_IMMEDIATE	0x00000001	/* start immediate xqt of an mcb */
17632391Sbostic 
177*33166Sbostic 					/* definition of master mcb "mcs" */
178*33166Sbostic #define	MCS_DONE	0x00000080	/* an mcb is done; status is valid */
179*33166Sbostic #define	MCS_FATALERROR	0x00000002	/* a fatal error occurred */
180*33166Sbostic #define	MCS_SOFTERROR	0x00000001	/* a recoverable error occurred */
18132391Sbostic 
18232391Sbostic /*
18332391Sbostic  * This structure defines the information returned by the hdc
18432391Sbostic  * controller for a "read drive status" (HCMD_STATUS) command.
18532391Sbostic  * The format of this structure is determined by the hdc firmware.
18632391Sbostic  * r1, r2, etc. are reserved for future use.
18732391Sbostic  */
18832391Sbostic 
18932391Sbostic typedef struct {
190*33166Sbostic 	unsigned long	drs;		/* drive status (see DRS_ below) */
191*33166Sbostic 	unsigned long	r1;
192*33166Sbostic 	unsigned long	r2;
193*33166Sbostic 	unsigned long	r3;
194*33166Sbostic 	unsigned short	max_cyl;	/* max logical cylinder address */
195*33166Sbostic 	unsigned short	max_head;	/* max logical head address */
196*33166Sbostic 	unsigned short	r4;
197*33166Sbostic 	unsigned short	max_sector;	/* max logical sector address */
198*33166Sbostic 	unsigned short	def_cyl;	/* definition track cylinder address */
199*33166Sbostic 	unsigned short	def_cyl_count;	/* definition track cylinder count */
200*33166Sbostic 	unsigned short	diag_cyl;	/* diagnostic track cylinder address */
201*33166Sbostic 	unsigned short	diag_cyl_count;	/* diagnostic track cylinder count */
202*33166Sbostic 	unsigned short	max_phys_cyl;	/* max physical cylinder address */
203*33166Sbostic 	unsigned short	max_phys_head;	/* max physical head address */
204*33166Sbostic 	unsigned short	r5;
205*33166Sbostic 	unsigned short	max_phys_sector;/* max physical sector address */
206*33166Sbostic 	unsigned short	r6;
207*33166Sbostic 	unsigned short	id;		/* drive id (drive model) */
208*33166Sbostic 	unsigned short	r7;
209*33166Sbostic 	unsigned short	bytes_per_sec;	/* bytes/sector -vendorflaw conversn */
210*33166Sbostic 	unsigned short	r8;
211*33166Sbostic 	unsigned short	rpm;		/* disk revolutions per minute */
212*33166Sbostic 	unsigned long	r9;
213*33166Sbostic 	unsigned long	r10;
214*33166Sbostic 	unsigned long	r11;
21532391Sbostic } drive_stat_type;
21632391Sbostic 
217*33166Sbostic 					/* defines for drive_stat drs word */
218*33166Sbostic #define	DRS_FAULT	0x00000080	/* drive is reporting a fault */
219*33166Sbostic #define	DRS_RESERVED	0x00000040	/* drive is reserved by other port */
220*33166Sbostic #define	DRS_WRITE_PROT	0x00000020	/* drive is write protected */
221*33166Sbostic #define	DRS_ON_CYLINDER	0x00000002	/* drive heads are not moving now */
222*33166Sbostic #define	DRS_ONLINE	0x00000001	/* drive is available for operation */
22332391Sbostic 
22432391Sbostic /*
22532391Sbostic  * hdc controller table. It contains information specific to each controller.
22632391Sbostic  */
22732391Sbostic 
22832391Sbostic typedef struct {
229*33166Sbostic 	int		ctlr;		/* controller number (0-15) */
23032391Sbostic 	hdc_regs_type	*registers;	/* base address of hdc io registers */
231*33166Sbostic 	mcb_type	*forw_active;	/* doubly linked list of */
232*33166Sbostic 	mcb_type	*back_active;	/* .. active mcb's */
233*33166Sbostic 	mcb_type	*forw_free;	/* doubly linked list of */
234*33166Sbostic 	mcb_type	*back_free;	/* .. free mcb's */
235*33166Sbostic 	mcb_type	*forw_wait;	/* doubly linked list of */
236*33166Sbostic 	mcb_type	*back_wait;	/* .. waiting mcb's */
237*33166Sbostic 	hdc_mid_type	mid;		/* the module id is read to here */
238*33166Sbostic 	long		master_phaddr;	/* physical address of master mcb */
239*33166Sbostic 	master_mcb_type master_mcb;	/* the master mcb for this hdc */
240*33166Sbostic 	mcb_type	mcbs[HDC_MAXMCBS];/* pool of mcb's for this hdc */
24132391Sbostic } hdc_ctlr_type;
24232391Sbostic 
24332391Sbostic /*
24432391Sbostic  * hdc unit table. It contains information specific to each hdc drive.
24532391Sbostic  * Some information is obtained from the profile prom and geometry block.
24632391Sbostic  */
24732391Sbostic 
24832391Sbostic typedef struct {
249*33166Sbostic 	par_tab	partition[GB_MAXPART];	/* partition definitions */
250*33166Sbostic 	int		ctlr;		/* the controller number (0-15) */
251*33166Sbostic 	int		slave;		/* the slave number (0-4) */
252*33166Sbostic 	int		unit;		/* the unit number (0-31) */
253*33166Sbostic 	int		id;		/* identifies the disk model */
254*33166Sbostic 	int		spc;		/* sectors per cylinder */
255*33166Sbostic 	int		cylinders;	/* number of logical cylinders */
256*33166Sbostic 	int		heads;		/* number of logical heads */
257*33166Sbostic 	int		sectors;	/* number of logical sectors/track */
258*33166Sbostic 	int		phys_cylinders;	/* number of physical cylinders */
259*33166Sbostic 	int		phys_heads;	/* number of physical heads */
26032391Sbostic 	int		phys_sectors;	/* number of physical sectors/track */
261*33166Sbostic 	int		def_cyl;	/* logical cylinder of drive def */
262*33166Sbostic 	int		def_cyl_count;	/* number of logical def cylinders */
263*33166Sbostic 	int		diag_cyl;	/* logical cylinder of diag area */
26432391Sbostic 	int		diag_cyl_count;	/* number of logical diag cylinders */
265*33166Sbostic 	int		rpm;		/* disk rpm */
266*33166Sbostic 	int		bytes_per_sec;	/* bytes/sector -vendorflaw conversn */
267*33166Sbostic 	int		format;		/* TRUE= format program is using dsk */
268*33166Sbostic 	mcb_type	phio_mcb;	/* mcb for handler physical io */
269*33166Sbostic 	struct buf	phio_buf;	/* buf for handler physical io */
270*33166Sbostic 	unsigned long	phio_data[HDC_PHIO_SIZE]; /* data for physical io */
271*33166Sbostic 	struct buf	raw_buf;	/* buf structure for raw i/o */
27232391Sbostic } hdc_unit_type;
273