xref: /original-bsd/sys/tahoe/vba/cyvar.h (revision 047ca643)
1*047ca643Ssam /*	cyvar.h	1.1	85/07/21	*/
2*047ca643Ssam 
3*047ca643Ssam #define TM_ATTENTION(addr,x) 	movob(x,addr)	/* also known as: GO */
4*047ca643Ssam 
5*047ca643Ssam #define TM_RESET(addr,x) TM_ATTENTION((addr+1),x) /* reset controller */
6*047ca643Ssam #define TM_SHORT(x)	(short)((((x) >> 8) & 0xff) + (((x) << 8) & 0xff00))
7*047ca643Ssam 
8*047ca643Ssam #define GATE_OPEN			(char)(0x00)
9*047ca643Ssam #define GATE_CLOSED			(char)(0xFF)
10*047ca643Ssam 
11*047ca643Ssam #define cyaddr	((char *)(0xf4000 + IOBASE))	/* controller physical addr */
12*047ca643Ssam #define b_repcnt  b_bcount
13*047ca643Ssam #define b_command b_resid
14*047ca643Ssam 
15*047ca643Ssam /* Group. I Control status/commands */
16*047ca643Ssam #define CONFIG	(0x00000000L)	/* configure */
17*047ca643Ssam #define SET_PA	(0x08000000L)	/* set page */
18*047ca643Ssam #define NO_OP	(0x20000000L)	/* no operation */
19*047ca643Ssam #define DRIVE_S	(0x28000000L)	/* drive status */
20*047ca643Ssam #define TAPE_AS	(0x74000000L)	/* tape assign */
21*047ca643Ssam #define DRIVE_R	(0x90000000L)	/* drive reset */
22*047ca643Ssam 
23*047ca643Ssam /* Group. II Tape position commands */
24*047ca643Ssam #define REWD_OV	(0x04000000L)	/* rewind overlapped */
25*047ca643Ssam #define READ_FO	(0x1C000000L)	/* read foreign tape */
26*047ca643Ssam #define REWD_TA	(0x34000000L)	/* rewind tape */
27*047ca643Ssam #define OFF_UNL	(0x38000000L)	/* off_line and unload */
28*047ca643Ssam #define WRIT_FM	(0x40000000L)	/* write filemark */
29*047ca643Ssam #define SERH_FM	(0x44000000L)	/* search filemark */
30*047ca643Ssam #define SRFM_FD	(0x44000000L)	/* search filemark forward */
31*047ca643Ssam #define SRFM_BK	(0xC4000000L)	/* search filemark backward */
32*047ca643Ssam #define SPACE	(0x48000000L)	/* skip record */
33*047ca643Ssam #define SP_FORW	(0x48000000L)	/* space forward */
34*047ca643Ssam #define SP_BACK	(0xC8000000L)	/* space backwords */
35*047ca643Ssam #define ERASE_F	(0x4C000000L)	/* erase fixed length */
36*047ca643Ssam #define ERASE_T	(0x50000000L)	/* erase to end of tape */
37*047ca643Ssam #define SPAC_FM	(0x70000000L)	/* space filemark */
38*047ca643Ssam #define SERH_MU	(0x94000000L)	/* search multiple filemarks */
39*047ca643Ssam 
40*047ca643Ssam /* Group. III Data transfer commands */
41*047ca643Ssam #define READ_BU	(0x10000000L)	/* read buffered */
42*047ca643Ssam #define WRIT_BU	(0x14000000L)	/* write buffered */
43*047ca643Ssam #define EDIT_BU	(0x18000000L)	/* edit buffered */
44*047ca643Ssam #define READ_TA	(0x2C000000L)	/* read tape */
45*047ca643Ssam #define WRIT_TA	(0x30000000L)	/* write tape */
46*047ca643Ssam #define EDIT_TA	(0x3C000000L)	/* edit tape */
47*047ca643Ssam #define READ_ST	(0x60000000L)	/* read streaming */
48*047ca643Ssam #define WRIT_ST	(0x64000000L)	/* write streaming */
49*047ca643Ssam 
50*047ca643Ssam /* Group. IV Special commands */
51*047ca643Ssam #define EXCHANG	(0x0C000000L)	/* exchange system and tapemaster RAM */
52*047ca643Ssam #define BLOCK_M	(0x80000000L)	/* block move */
53*047ca643Ssam 
54*047ca643Ssam /* Group. V Diagnostic commands */
55*047ca643Ssam #define TEST_SH	(0x54000000L)	/* short memory test */
56*047ca643Ssam #define TEST_LG	(0x58000000L)	/* long memory test */
57*047ca643Ssam #define TEST_CN	(0x5C000000L)	/* controller confidence test */
58*047ca643Ssam #define TEST_RW	(0x68000000L)	/* test read/write timeing */
59*047ca643Ssam /* Control byte[0] bit assignments */
60*047ca643Ssam #define CW_TSm	(0x0C)	/* tape select mask, 2 bit field */
61*047ca643Ssam #define CW_TSs	(2)	/* tape select shift, 2 bit field <<shift */
62*047ca643Ssam #define CW_M	(0x10)	/* mailbox flag */
63*047ca643Ssam #define CW_I	(0x20)	/* interrupt flag */
64*047ca643Ssam #define CW_L	(0x40)	/* link flag */
65*047ca643Ssam #define CW_BL	(0x80)	/* bus lock flag */
66*047ca643Ssam 
67*047ca643Ssam /* Control byte[1] bit assignments */
68*047ca643Ssam #define CW_BS	(0x01)	/* bank select */
69*047ca643Ssam #define CW_R	(0x04)	/* reverse flag */
70*047ca643Ssam #define CW_SD	(0x08)	/* speed/density */
71*047ca643Ssam #define CW_25ips	(0x00)	/* 25 inches per second speed */
72*047ca643Ssam #define CW_100ips	(0x08)	/* 100 inches per second speed */
73*047ca643Ssam #define CW_C	(0x10)	/* continuous */
74*047ca643Ssam #define CW_W	(0x80)	/* width */
75*047ca643Ssam #define CW_8bits	(0x00)	/* width 8 bits */
76*047ca643Ssam #define CW_16bits	(0x80)	/* width 16 bits */
77*047ca643Ssam 
78*047ca643Ssam /* status byte[0] bit assignements */
79*047ca643Ssam #define CS_P	(0x02)	/* Protected, no write ring */
80*047ca643Ssam #define CS_FB	(0x04)	/* formatter busy */
81*047ca643Ssam #define CS_DR	(0x08)	/* drive ready */
82*047ca643Ssam #define CS_EOT	(0x10)	/* end of tape detected */
83*047ca643Ssam #define CS_LP	(0x20)	/* tape is at load point */
84*047ca643Ssam #define CS_OL	(0x40)	/* drive on_line */
85*047ca643Ssam #define CS_FM	(0x80)	/* Filemark detected */
86*047ca643Ssam 
87*047ca643Ssam /* status byte[1] bit assignements */
88*047ca643Ssam #define CS_ERm	(0x1F)	/* Command (Error) mask */
89*047ca643Ssam #define CS_CR	(0x20)	/* Command (Retry) */
90*047ca643Ssam #define CS_CC	(0x40)	/* Command (Complete) */
91*047ca643Ssam #define CS_CE	(0x80)	/* Command (Entered) */
92*047ca643Ssam 
93*047ca643Ssam /* block move control byte[0] bit assignments */
94*047ca643Ssam #define BM_SI	(0x01)	/* increment source address */
95*047ca643Ssam #define BM_SW	(0x02)	/* source width */
96*047ca643Ssam #define BM_DI	(0x04)	/* increment destination address */
97*047ca643Ssam #define BM_DW	(0x08)	/* destination width */
98*047ca643Ssam #define BM_M	(0x10)	/* mailbox flag */
99*047ca643Ssam #define BM_I	(0x20)	/* interrupt flag */
100*047ca643Ssam #define BM_L	(0x40)	/* link flag */
101*047ca643Ssam #define BM_BL	(0x80)	/* bus lock flag */
102*047ca643Ssam 
103*047ca643Ssam /* block move control byte[1] bit assignments */
104*047ca643Ssam #define BM_T	(0x01)	/* translate flag */
105*047ca643Ssam #define BM_S	(0x02)	/* search flag */
106*047ca643Ssam #define BM_NC	(0x04)	/* non_compare flag */
107*047ca643Ssam #define BM_TH	(0x08)	/* throttle flag */
108*047ca643Ssam #define BM_SL	(0x10)	/* source local flag */
109*047ca643Ssam #define BM_DL	(0x20)	/* destination local flag */
110*047ca643Ssam 
111*047ca643Ssam /* block move status bit assignments */
112*047ca643Ssam #define BS_ERm	(0x1F)	/* Command (Error) mask */
113*047ca643Ssam #define BS_HIT	(0x20)	/* found match during search */
114*047ca643Ssam #define BS_CC	(0x40)	/* Command (Complete) */
115*047ca643Ssam #define BS_CE	(0x80)	/* Command (Entered) */
116*047ca643Ssam /* SC_ERROR & BM_ERROR codes */
117*047ca643Ssam #define ER_NONE	(0x00)		/* no error */
118*047ca643Ssam #define ER_TO1	(0x01)		/* timed out data busy false */
119*047ca643Ssam #define ER_TO2	(0x02)		/* data busy false,formatter,ready */
120*047ca643Ssam #define ER_T03	(0x03)		/* time out ready busy false */
121*047ca643Ssam #define ER_T04	(0x04)		/* time out ready busy true */
122*047ca643Ssam #define ER_T05	(0x05)		/* time out data busy true */
123*047ca643Ssam #define ER_T06	(0x06)		/* time out memory */
124*047ca643Ssam #define ER_BLAN	(0X07)		/* blank tape */
125*047ca643Ssam #define ER_DIAG	(0x08)		/* micro-diagnostic */
126*047ca643Ssam #define ER_END	(0x09)		/* EOT forward, BOT rev. */
127*047ca643Ssam #define ER_HARD	(0x0A)		/* retry unsuccessful */
128*047ca643Ssam #define ER_FIFO	(0x0B)		/* FIFO over/under flow */
129*047ca643Ssam /*		(0x0C)		/* Not used */
130*047ca643Ssam #define ER_PARI	(0x0D)		/* drive to tapemaster parity error */
131*047ca643Ssam #define ER_PSUM	(0x0E)		/* prom checksum */
132*047ca643Ssam #define ER_TOF	(0x0F)		/* time out tape strobe */
133*047ca643Ssam #define ER_TRN	(0x10)		/* tape not ready */
134*047ca643Ssam #define ER_PRO	(0x11)		/* write, no enable ring */
135*047ca643Ssam /*		(0x12)		/* Not used */
136*047ca643Ssam #define ER_JUMP	(0x13)		/* missing diagnostic jumper */
137*047ca643Ssam #define ER_BLIN	(0x14)		/* bad link, link inappropriate */
138*047ca643Ssam #define ER_FMAR	(0x15)		/* unexpected filemark */
139*047ca643Ssam #define ER_PARA	(0x16)		/* bad parameter, byte count ? */
140*047ca643Ssam /*		(0x17)		/* Not used */
141*047ca643Ssam #define ER_ER	(0x18)		/* unidentified hardware error */
142*047ca643Ssam #define ER_STER	(0x19)		/* streaming terminated */
143*047ca643Ssam 
144*047ca643Ssam #define WRITE_FMARK	5
145