xref: /csrg-svn/sys/tahoe/vba/cyreg.h (revision 25676)
1*25676Ssam /*	cyreg.h	7.1	86/01/05	*/
2*25676Ssam 
3*25676Ssam /* get controller attention and start an operation */
4*25676Ssam #define CY_ATTENTION(addr) movob(addr, 0xff)	/* also known as: GO */
5*25676Ssam #define CY_RESET(addr)    CY_ATTENTION(addr+1) /* reset controller */
6*25676Ssam #define CYUNIT(d)	  (minor(d) & 0xf)
7*25676Ssam 
8*25676Ssam #define MULTIBUS_SHORT(x) (short)((((x)>>8)&0xff) | (((x)<<8)&0xff00))
9*25676Ssam 
10*25676Ssam #define	NORMAL_INTERUPT	0x11
11*25676Ssam #define	CLEAR_INTERUPT	0x09
12*25676Ssam 
13*25676Ssam #define	T_NOREWIND	0x80
14*25676Ssam 
15*25676Ssam 
16*25676Ssam /* Tape Parameter Block definitions */
17*25676Ssam typedef struct {
18*25676Ssam 	long		cmd;		/* Command */
19*25676Ssam 	short		control;	/* Control */
20*25676Ssam 	short		count;		/* Return count */
21*25676Ssam 	short		size;		/* Buffer size */
22*25676Ssam 	short		rec_over;	/* Records/Overrun */
23*25676Ssam 	char		*data_ptr;	/* Pointer to source/dest */
24*25676Ssam 	short		status;		/* Status */
25*25676Ssam 	short		link_ptr[2];	/* Pointer to next parameter block */
26*25676Ssam } fmt_tpb;
27*25676Ssam 
28*25676Ssam /* Controller commands */
29*25676Ssam 
30*25676Ssam /* Group. I Control status/commands */
31*25676Ssam #define	CONFIG	(0x00000000)	/* configure */
32*25676Ssam #define	SET_PA	(0x08000000)	/* set page */
33*25676Ssam #define	NO_OP	(0x20000000)	/* no operation */
34*25676Ssam #define	DRIVE_S	(0x28000000)	/* drive status */
35*25676Ssam #define	TAPE_AS	(0x74000000)	/* tape assign */
36*25676Ssam #define	DRIVE_R	(0x90000000)	/* drive reset */
37*25676Ssam 
38*25676Ssam /* Group. II Tape position commands */
39*25676Ssam #define	REWD_OV	(0x04000000)	/* rewind overlapped */
40*25676Ssam #define	READ_FO	(0x1C000000)	/* read foreign tape */
41*25676Ssam #define	REWD_TA	(0x34000000)	/* rewind tape */
42*25676Ssam #define	OFF_UNL	(0x38000000)	/* off_line and unload */
43*25676Ssam #define	WRIT_FM	(0x40000000)	/* write filemark */
44*25676Ssam #define	SERH_FM	(0x44000000)	/* search filemark */
45*25676Ssam #define	SRFM_FD	(0x44000000)	/* search filemark forward */
46*25676Ssam #define	SRFM_BK	(0xC4000000)	/* search filemark backward */
47*25676Ssam #define	SPACE	(0x48000000)	/* skip record */
48*25676Ssam #define	SP_FORW	(0x48000000)	/* space forward */
49*25676Ssam #define	SP_BACK	(0xC8000000)	/* space backwords */
50*25676Ssam #define	ERASE_F	(0x4C000000)	/* erase fixed length */
51*25676Ssam #define	ERASE_T	(0x50000000)	/* erase to end of tape */
52*25676Ssam #define	SPAC_FM	(0x70000000)	/* space filemark */
53*25676Ssam #define	SP_FM_F	(0x70000000)	/* space filemark forward */
54*25676Ssam #define	SP_FM_B	(0xC9000000)	/* space filemark backward */
55*25676Ssam #define	SERH_MU	(0x94000000)	/* search multiple filemarks */
56*25676Ssam 
57*25676Ssam /* Group. III Data transfer commands */
58*25676Ssam #define	READ_BU	(0x10000000)	/* read buffered */
59*25676Ssam #define	WRIT_BU	(0x14000000)	/* write buffered */
60*25676Ssam #define	EDIT_BU	(0x18000000)	/* edit buffered */
61*25676Ssam #define	READ_TA	(0x2C000000)	/* read tape */
62*25676Ssam #define	WRIT_TA	(0x30000000)	/* write tape */
63*25676Ssam #define	EDIT_TA	(0x3C000000)	/* edit tape */
64*25676Ssam #define	READ_ST	(0x60000000)	/* read streaming */
65*25676Ssam #define	WRIT_ST	(0x64000000)	/* write streaming */
66*25676Ssam 
67*25676Ssam /* Group. IV Special commands */
68*25676Ssam #define	EXCHANG	(0x0C000000)	/* exchange system and tapemaster RAM */
69*25676Ssam #define	BLOCK_M	(0x80000000)	/* block move */
70*25676Ssam 
71*25676Ssam /* Group. V Diagnostic commands */
72*25676Ssam #define	TEST_SH	(0x54000000)	/* short memory test */
73*25676Ssam #define	TEST_LG	(0x58000000)	/* long memory test */
74*25676Ssam #define	TEST_CN	(0x5C000000)	/* controller confidence test */
75*25676Ssam #define	TEST_RW	(0x68000000)	/* test read/write timeing */
76*25676Ssam 
77*25676Ssam 
78*25676Ssam /* Control field bit definitions */
79*25676Ssam #define	CW_UNIT		(0x000c<<8) /* tape select mask, 2 bit field */
80*25676Ssam #define	CW_MAIL		(0x0010<<8) /* mailbox flag */
81*25676Ssam #define	CW_INTR		(0x0020<<8) /* interrupt flag */
82*25676Ssam #define	CW_LINK		(0x0040<<8) /* link flag */
83*25676Ssam #define	CW_LOCK		(0x0080<<8) /* bus lock flag */
84*25676Ssam #define	CW_BANK		(0x0100>>8) /* bank select */
85*25676Ssam #define	CW_REV		(0x0400>>8) /* reverse flag */
86*25676Ssam #define	CW_SPEED	(0x0800>>8) /* speed/density */
87*25676Ssam #define	    CW_25ips	0
88*25676Ssam #define	    CW_100ips	(0x0800>>8)
89*25676Ssam #define	CW_STREAM  	(0x1000>>8) /* continuous */
90*25676Ssam #define	CW_WIDTH  	(0x8000>>8) /* width */
91*25676Ssam #define	    CW_8bits	0
92*25676Ssam #define	    CW_16bits	(0x8000>>8)
93*25676Ssam 
94*25676Ssam 
95*25676Ssam /* Status field bit definitions */
96*25676Ssam #define	CS_P	(0x0002<<8)	/* Protected, no write ring */
97*25676Ssam #define	CS_FB	(0x0004<<8)	/* formatter busy */
98*25676Ssam #define	CS_RDY	(0x0008<<8)	/* drive ready */
99*25676Ssam #define	CS_EOT	(0x0010<<8)	/* end of tape detected */
100*25676Ssam #define	CS_LP	(0x0020<<8)	/* tape is at load point */
101*25676Ssam #define	CS_OL	(0x0040<<8)	/* drive on_line */
102*25676Ssam #define	CS_FM	(0x0080<<8)	/* Filemark detected */
103*25676Ssam #define	CS_ERm	(0x1F00>>8)	/* Error value mask */
104*25676Ssam #define	CS_CR	(0x2000>>8)	/* Controller executed retries */
105*25676Ssam #define	CS_CC	(0x4000>>8)	/* Command Completed successfully */
106*25676Ssam #define	CS_CE	(0x8000>>8)	/* Command execution has begun */
107*25676Ssam 
108*25676Ssam #define	CYDS_BITS "\20\6CS_CR\7CS_CC\8CS_CE\12CS_P\13CS_FB\14CS_RDY\15CS_EOT\
109*25676Ssam \16CS_LP\17CS_OL\20CS_FM"
110*25676Ssam 
111*25676Ssam /* Error value definitions for CS_ERm field */
112*25676Ssam #define	ER_TIMOUT	(0x01)	/* timed out data busy false */
113*25676Ssam #define	ER_TIMOUT1	(0x02)	/* data busy false,formatter,ready */
114*25676Ssam #define	ER_TIMOUT2	(0x03)	/* time out ready busy false */
115*25676Ssam #define	ER_TIMOUT3	(0x04)	/* time out ready busy true */
116*25676Ssam #define	ER_TIMOUT4	(0x05)	/* time out data busy true */
117*25676Ssam #define	ER_NEX		(0x06)	/* time out memory */
118*25676Ssam #define	ER_BLANK	(0X07)	/* blank tape */
119*25676Ssam #define	ER_DIAG		(0x08)	/* micro-diagnostic */
120*25676Ssam #define	ER_EOT		(0x09)	/* EOT forward, BOT rev. */
121*25676Ssam #define	ER_HARD		(0x0A)	/* retry unsuccessful */
122*25676Ssam #define	ER_FIFO		(0x0B)	/* FIFO over/under flow */
123*25676Ssam #define	ER_PARITY	(0x0D)	/* drive to tapemaster parity error */
124*25676Ssam #define	ER_CHKSUM	(0x0E)	/* prom checksum */
125*25676Ssam #define	ER_STROBE	(0x0F)	/* time out tape strobe */
126*25676Ssam #define	ER_NOTRDY	(0x10)	/* tape not ready */
127*25676Ssam #define	ER_PROT		(0x11)	/* write, no enable ring */
128*25676Ssam #define	ER_JUMPER	(0x13)	/* missing diagnostic jumper */
129*25676Ssam #define	ER_LINK		(0x14)	/* bad link, link inappropriate */
130*25676Ssam #define	ER_FM		(0x15)	/* unexpected filemark */
131*25676Ssam #define	ER_PARAM	(0x16)	/* bad parameter, byte count ? */
132*25676Ssam #define	ER_HDWERR	(0x18)	/* unidentified hardware error */
133*25676Ssam #define	ER_NOSTRM	(0x19)	/* streaming terminated */
134*25676Ssam 
135*25676Ssam 
136*25676Ssam /* Channel control block definitions */
137*25676Ssam typedef struct {
138*25676Ssam 	char	ccw;		/* channel control word */
139*25676Ssam 	char	gate;		/* Tpb access gate */
140*25676Ssam 	short	tpb_ptr[2];	/* points to first tape parameter block */
141*25676Ssam } fmt_ccb;
142*25676Ssam 
143*25676Ssam #define GATE_OPEN	(char)(0x00)
144*25676Ssam #define GATE_CLOSED	(char)(0xFF)
145*25676Ssam #define NORMAL_INTERUP	0x11
146*25676Ssam 
147*25676Ssam 
148*25676Ssam 
149*25676Ssam /* System configuration block structrure definitions */
150*25676Ssam typedef struct {
151*25676Ssam 	char	fixed_value;	/* 0x03 fixed value code */
152*25676Ssam 	char	unused_scb;
153*25676Ssam 	short	ccb_ptr[2];	/* pointer to ->CHANNEL CONTROL BLOCK */
154*25676Ssam } fmt_scb;
155*25676Ssam 
156*25676Ssam 
157*25676Ssam /* System configuration pointer structure definitions */
158*25676Ssam typedef struct {
159*25676Ssam 	char	bus_size;	/* width of system bus 0=8; 1=16 */
160*25676Ssam 	char	unused_scp;
161*25676Ssam 	short	scb_ptr[2];	/* pointer to ->SYSTEM CONFIGUREATION BLOCK */
162*25676Ssam } fmt_scp;
163*25676Ssam 
164*25676Ssam #define	_16_BITS	1
165*25676Ssam #define	_8_BITS		0
166*25676Ssam 
167