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