xref: /csrg-svn/sys/tahoe/vba/cyreg.h (revision 30719)
1 /*	cyreg.h	7.4	87/04/01	*/
2 
3 /*
4  * Tapemaster controller definitions.
5  */
6 
7 /*
8  * With 20-bit addressing, the intermediate buffer
9  * must be allocated early in startup().
10  */
11 #define	CYMAXIO	(32*NBPG)		/* max i/o size */
12 char	*cybuf;
13 
14 /* for byte swapping Multibus values */
15 #define	htoms(x) (short)((((x)>>8)&0xff) | (((x)<<8)&0xff00))
16 
17 #define	b_repcnt  b_bcount
18 #define	b_command b_resid
19 
20 /*
21  * System configuration pointer.
22  * Memory address is jumpered on controller.
23  */
24 struct	cyscp {
25 	char	csp_buswidth;	/* system bus width */
26 #define	CSP_16BITS	1	/* 16-bit system bus */
27 #define	CSP_8BITS	0	/* 8-bit system bus */
28 	char	csp_unused;
29 	u_char	csp_scb[4];	/* point to system config block */
30 };
31 
32 /*
33  * System configuration block
34  */
35 struct	cyscb {
36 	char	csb_fixed;	/* fixed value code (must be 3) */
37 	char	csb_unused;	/* unused */
38 	u_char	csb_ccb[4];	/* pointer to channel control block */
39 };
40 
41 #define	CSB_FIXED	0x3
42 
43 /*
44  * Channel control block definitions
45  */
46 struct	cyccb {
47 	char	cbcw;		/* channel control word */
48 	char	cbgate;		/* tpb access gate */
49 	u_char	cbtpb[4];	/* first tape parameter block */
50 };
51 
52 #define	GATE_OPEN	(char)(0x00)
53 #define	GATE_CLOSED	(char)(0xff)
54 
55 #define	CY_GO(addr)	movob((addr), 0xff)	/* channel attention */
56 #define	CY_RESET(addr)  movob((addr)+1, 0xff) 	/* software controller reset */
57 
58 #define	CBCW_IE		0x11		/* interrupt on cmd completion */
59 #define	CBCW_CLRINT	0x09		/* clear active interrupt */
60 
61 /*
62  * Tape parameter block definitions
63  */
64 struct	cytpb {
65 	long	tpcmd;		/* command, see below */
66 	short	tpcontrol;	/* control word */
67 	short	tpcount;	/* return count */
68 	short	tpsize;		/* buffer size */
69 	short	tprec;		/* records/overrun */
70 	u_char	tpdata[4];	/* pointer to source/dest */
71 	short	tpstatus;	/* status */
72 	u_char	tplink[4];	/* pointer to next parameter block */
73 };
74 
75 /* control field bit definitions */
76 #define	CYCW_UNIT	(0x000c<<8) 	/* unit select mask, 2 bit field */
77 #define	CYCW_IE		(0x0020<<8)	/* interrupt enable */
78 #define	CYCW_LOCK	(0x0080<<8)	/* bus lock flag */
79 #define	CYCW_REV	(0x0400>>8)	/* reverse flag */
80 #define	CYCW_SPEED	(0x0800>>8)	/* speed/density */
81 #define	    CYCW_25IPS	0
82 #define	    CYCW_100IPS	(0x0800>>8)
83 #define	CYCW_WIDTH  	(0x8000>>8)	/* width */
84 #define	    CYCW_8BITS	0
85 #define	    CYCW_16BITS	(0x8000>>8)
86 
87 #define	CYCW_BITS	"\20\3REV\005100IPS\00716BITS\16IE\20LOCK"
88 
89 /*
90  * Controller commands
91  */
92 
93 /* control status/commands */
94 #define	CY_CONFIG	(0x00<<24)	/* configure */
95 #define	CY_NOP		(0x20<<24)	/* no operation */
96 #define	CY_SETPAGE	(0x08<<24)	/* set page (addr bits 20-23) */
97 #define	CY_SENSE	(0x28<<24)	/* drive status */
98 #define	CY_CLRINT	(0x9c<<24)	/* clear Multibus interrupt */
99 
100 /* tape position commands */
101 #define	CY_REW		(0x34<<24)	/* rewind tape */
102 #define	CY_OFFL		(0x38<<24)	/* off_line and unload */
103 #define	CY_WEOF		(0x40<<24)	/* write end-of-file mark */
104 #define	CY_SFORW	(0x70<<24)	/* space record forward */
105 #define	CY_SREV		(CY_SFORW|CYCW_REV) /* space record backwards */
106 #define	CY_FSF		(0x44<<24)	/* space file forward */
107 #define	CY_BSF		(CY_FSF|CYCW_REV) /* space file backwards */
108 #define	CY_ERASE	(0x4c<<24)	/* erase record */
109 
110 /* data transfer commands */
111 #define	CY_BRCOM	(0x10<<24)	/* read buffered */
112 #define	CY_BWCOM	(0x14<<24)	/* write buffered */
113 #define	CY_RCOM		(0x2c<<24)	/* read tape unbuffered */
114 #define	CY_WCOM		(0x30<<24)	/* write tape unbuffered */
115 
116 /* status field bit definitions */
117 #define	CYS_WP		(0x0002<<8)	/* write protected, no write ring */
118 #define	CYS_BSY		(0x0004<<8)	/* formatter busy */
119 #define	CYS_RDY		(0x0008<<8)	/* drive ready */
120 #define	CYS_EOT		(0x0010<<8)	/* end of tape detected */
121 #define	CYS_BOT		(0x0020<<8)	/* tape is at load point */
122 #define	CYS_OL		(0x0040<<8)	/* drive on_line */
123 #define	CYS_FM		(0x0080<<8)	/* filemark detected */
124 #define	CYS_ERR		(0x1f00>>8)	/* error value mask */
125 #define	CYS_CR		(0x2000>>8)	/* controller executed retries */
126 #define	CYS_CC		(0x4000>>8)	/* command completed successfully */
127 #define	CYS_CE		(0x8000>>8)	/* command execution has begun */
128 
129 #define	CYS_BITS "\20\6CR\7CC\10CE\12WP\13BSY\14RDY\15EOT/BOT\16BOT\17OL\20FM"
130 
131 /* error codes for CYS_ERR */
132 #define	CYER_TIMOUT	0x01	/* timed out data busy false */
133 #define	CYER_TIMOUT1	0x02	/* data busy false,formatter,ready */
134 #define	CYER_TIMOUT2	0x03	/* time out ready busy false */
135 #define	CYER_TIMOUT3	0x04	/* time out ready busy true */
136 #define	CYER_TIMOUT4	0x05	/* time out data busy true */
137 #define	CYER_NXM	0x06	/* time out memory */
138 #define	CYER_BLANK	0x07	/* blank tape */
139 #define	CYER_DIAG	0x08	/* micro-diagnostic */
140 #define	CYER_EOT	0x09	/* EOT forward, BOT rev. */
141 #define	CYER_BOT	0x09	/* EOT forward, BOT rev. */
142 #define	CYER_HERR	0x0a	/* retry unsuccessful */
143 #define	CYER_FIFO	0x0b	/* FIFO over/under flow */
144 #define	CYER_PARITY	0x0d	/* drive to tapemaster parity error */
145 #define	CYER_CKSUM	0x0e	/* prom checksum */
146 #define	CYER_STROBE	0x0f	/* time out tape strobe */
147 #define	CYER_NOTRDY	0x10	/* tape not ready */
148 #define	CYER_PROT	0x11	/* write, no enable ring */
149 #define	CYER_JUMPER	0x13	/* missing diagnostic jumper */
150 #define	CYER_LINK	0x14	/* bad link, link inappropriate */
151 #define	CYER_FM		0x15	/* unexpected filemark */
152 #define	CYER_PARAM	0x16	/* bad parameter, byte count ? */
153 #define	CYER_HDWERR	0x18	/* unidentified hardware error */
154 #define	CYER_NOSTRM	0x19	/* streaming terminated */
155 
156 #ifdef CYERROR
157 char	*cyerror[] = {
158 	"no error",
159 	"timeout",
160 	"timeout1",
161 	"timeout2",
162 	"timeout3",
163 	"timeout4",
164 	"non-existent memory",
165 	"blank tape",
166 	"micro-diagnostic",
167 	"eot/bot detected",
168 	"retry unsuccessful",
169 	"fifo over/under-flow",
170 	"#0xc",
171 	"drive to controller parity error",
172 	"prom checksum",
173 	"time out tape strobe (record length error)",
174 	"tape not ready",
175 	"write protected",
176 	"#0x12",
177 	"missing diagnostic jumper",
178 	"invalid link pointer",
179 	"unexpected file mark",
180 	"invalid byte count/parameter",
181 	"#0x17",
182 	"unidentified hardware error",
183 	"streaming terminated"
184 };
185 #define	NCYERROR	(sizeof (cyerror) / sizeof (cyerror[0]))
186 #endif
187 
188 /*
189  * Masks defining hard and soft errors (must check against 1<<CYER_code).
190  */
191 #define	CYMASK(e)	(1<<(CYER_/**/e))
192 #define	CYER_HARD	(CYMASK(TIMOUT)|CYMASK(TIMOUT1)|CYMASK(TIMOUT2)|\
193     CYMASK(TIMOUT3)|CYMASK(TIMOUT4)|CYMASK(NXM)|CYMASK(DIAG)|CYMASK(JUMPER)|\
194     CYMASK(STROBE)|CYMASK(PROT)|CYMASK(CKSUM)|CYMASK(HERR)|CYMASK(BLANK))
195 #define	CYER_SOFT	(CYMASK(FIFO)|CYMASK(NOTRDY)|CYMASK(PARITY))
196