xref: /csrg-svn/sys/tahoe/vba/cyreg.h (revision 35478)
1*35478Sbostic /*
2*35478Sbostic  * Copyright (c) 1988 The Regents of the University of California.
3*35478Sbostic  * All rights reserved.
4*35478Sbostic  *
5*35478Sbostic  * This code is derived from software contributed to Berkeley by
6*35478Sbostic  * Computer Consoles Inc.
7*35478Sbostic  *
8*35478Sbostic  * Redistribution and use in source and binary forms are permitted
9*35478Sbostic  * provided that the above copyright notice and this paragraph are
10*35478Sbostic  * duplicated in all such forms and that any documentation,
11*35478Sbostic  * advertising materials, and other materials related to such
12*35478Sbostic  * distribution and use acknowledge that the software was developed
13*35478Sbostic  * by the University of California, Berkeley.  The name of the
14*35478Sbostic  * University may not be used to endorse or promote products derived
15*35478Sbostic  * from this software without specific prior written permission.
16*35478Sbostic  * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR
17*35478Sbostic  * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
18*35478Sbostic  * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
19*35478Sbostic  *
20*35478Sbostic  *	@(#)cyreg.h	7.7 (Berkeley) 09/09/88
21*35478Sbostic  */
2225676Ssam 
2325979Ssam /*
2425979Ssam  * Tapemaster controller definitions.
2525979Ssam  */
2625676Ssam 
2730719Skarels /*
2830719Skarels  * With 20-bit addressing, the intermediate buffer
2930719Skarels  * must be allocated early in startup().
3030719Skarels  */
3130869Skarels #define	CYMAXIO	(64*1024)		/* max i/o size + 1 */
3230719Skarels char	*cybuf;
3330719Skarels 
3425979Ssam /* for byte swapping Multibus values */
3535477Sbostic #define	htoms(x) (u_short)((((x)>>8)&0xff) | (((x)<<8)&0xff00))
3625676Ssam 
3725979Ssam #define	b_repcnt  b_bcount
3825979Ssam #define	b_command b_resid
3925676Ssam 
4025979Ssam /*
4130372Skarels  * System configuration pointer.
4230372Skarels  * Memory address is jumpered on controller.
4330372Skarels  */
4430372Skarels struct	cyscp {
4530372Skarels 	char	csp_buswidth;	/* system bus width */
4630372Skarels #define	CSP_16BITS	1	/* 16-bit system bus */
4730372Skarels #define	CSP_8BITS	0	/* 8-bit system bus */
4830372Skarels 	char	csp_unused;
4930372Skarels 	u_char	csp_scb[4];	/* point to system config block */
5030372Skarels };
5130372Skarels 
5230372Skarels /*
5330372Skarels  * System configuration block
5430372Skarels  */
5530372Skarels struct	cyscb {
5630372Skarels 	char	csb_fixed;	/* fixed value code (must be 3) */
5730372Skarels 	char	csb_unused;	/* unused */
5830372Skarels 	u_char	csb_ccb[4];	/* pointer to channel control block */
5930372Skarels };
6030372Skarels 
6130372Skarels #define	CSB_FIXED	0x3
6230372Skarels 
6330372Skarels /*
6425979Ssam  * Channel control block definitions
6525979Ssam  */
6625979Ssam struct	cyccb {
6725979Ssam 	char	cbcw;		/* channel control word */
6825979Ssam 	char	cbgate;		/* tpb access gate */
6930372Skarels 	u_char	cbtpb[4];	/* first tape parameter block */
7025979Ssam };
7125676Ssam 
7225979Ssam #define	GATE_OPEN	(char)(0x00)
7325979Ssam #define	GATE_CLOSED	(char)(0xff)
7425676Ssam 
7525979Ssam #define	CY_GO(addr)	movob((addr), 0xff)	/* channel attention */
7625979Ssam #define	CY_RESET(addr)  movob((addr)+1, 0xff) 	/* software controller reset */
7725676Ssam 
7825979Ssam #define	CBCW_IE		0x11		/* interrupt on cmd completion */
7925979Ssam #define	CBCW_CLRINT	0x09		/* clear active interrupt */
8025676Ssam 
8125979Ssam /*
8225979Ssam  * Tape parameter block definitions
8325979Ssam  */
8425979Ssam struct	cytpb {
8530869Skarels 	u_long	tpcmd;		/* command, see below */
8630869Skarels 	u_short	tpcontrol;	/* control word */
8730869Skarels 	u_short	tpcount;	/* return count */
8830869Skarels 	u_short	tpsize;		/* buffer size */
8930869Skarels 	u_short	tprec;		/* records/overrun */
9030372Skarels 	u_char	tpdata[4];	/* pointer to source/dest */
9130869Skarels 	u_short	tpstatus;	/* status */
9230372Skarels 	u_char	tplink[4];	/* pointer to next parameter block */
9325979Ssam };
9425676Ssam 
9525979Ssam /* control field bit definitions */
9625979Ssam #define	CYCW_UNIT	(0x000c<<8) 	/* unit select mask, 2 bit field */
9725979Ssam #define	CYCW_IE		(0x0020<<8)	/* interrupt enable */
9825979Ssam #define	CYCW_LOCK	(0x0080<<8)	/* bus lock flag */
9925979Ssam #define	CYCW_REV	(0x0400>>8)	/* reverse flag */
10025979Ssam #define	CYCW_SPEED	(0x0800>>8)	/* speed/density */
10125979Ssam #define	    CYCW_25IPS	0
10225979Ssam #define	    CYCW_100IPS	(0x0800>>8)
10325979Ssam #define	CYCW_WIDTH  	(0x8000>>8)	/* width */
10425979Ssam #define	    CYCW_8BITS	0
10525979Ssam #define	    CYCW_16BITS	(0x8000>>8)
10625676Ssam 
10725979Ssam #define	CYCW_BITS	"\20\3REV\005100IPS\00716BITS\16IE\20LOCK"
10825676Ssam 
10925979Ssam /*
11025979Ssam  * Controller commands
11125979Ssam  */
11225676Ssam 
11325979Ssam /* control status/commands */
11425979Ssam #define	CY_CONFIG	(0x00<<24)	/* configure */
11525979Ssam #define	CY_NOP		(0x20<<24)	/* no operation */
11630372Skarels #define	CY_SETPAGE	(0x08<<24)	/* set page (addr bits 20-23) */
11725979Ssam #define	CY_SENSE	(0x28<<24)	/* drive status */
11825979Ssam #define	CY_CLRINT	(0x9c<<24)	/* clear Multibus interrupt */
11925676Ssam 
12025979Ssam /* tape position commands */
12125979Ssam #define	CY_REW		(0x34<<24)	/* rewind tape */
12225979Ssam #define	CY_OFFL		(0x38<<24)	/* off_line and unload */
12325979Ssam #define	CY_WEOF		(0x40<<24)	/* write end-of-file mark */
12425979Ssam #define	CY_SFORW	(0x70<<24)	/* space record forward */
12530372Skarels #define	CY_SREV		(CY_SFORW|CYCW_REV) /* space record backwards */
12630372Skarels #define	CY_FSF		(0x44<<24)	/* space file forward */
12730372Skarels #define	CY_BSF		(CY_FSF|CYCW_REV) /* space file backwards */
12825979Ssam #define	CY_ERASE	(0x4c<<24)	/* erase record */
12925676Ssam 
13025979Ssam /* data transfer commands */
13125979Ssam #define	CY_BRCOM	(0x10<<24)	/* read buffered */
13225979Ssam #define	CY_BWCOM	(0x14<<24)	/* write buffered */
13325979Ssam #define	CY_RCOM		(0x2c<<24)	/* read tape unbuffered */
13425979Ssam #define	CY_WCOM		(0x30<<24)	/* write tape unbuffered */
13525676Ssam 
13625979Ssam /* status field bit definitions */
13725979Ssam #define	CYS_WP		(0x0002<<8)	/* write protected, no write ring */
13825979Ssam #define	CYS_BSY		(0x0004<<8)	/* formatter busy */
13925979Ssam #define	CYS_RDY		(0x0008<<8)	/* drive ready */
14025979Ssam #define	CYS_EOT		(0x0010<<8)	/* end of tape detected */
14125979Ssam #define	CYS_BOT		(0x0020<<8)	/* tape is at load point */
14225979Ssam #define	CYS_OL		(0x0040<<8)	/* drive on_line */
14325979Ssam #define	CYS_FM		(0x0080<<8)	/* filemark detected */
14425979Ssam #define	CYS_ERR		(0x1f00>>8)	/* error value mask */
14525979Ssam #define	CYS_CR		(0x2000>>8)	/* controller executed retries */
14625979Ssam #define	CYS_CC		(0x4000>>8)	/* command completed successfully */
14725979Ssam #define	CYS_CE		(0x8000>>8)	/* command execution has begun */
14825676Ssam 
14925979Ssam #define	CYS_BITS "\20\6CR\7CC\10CE\12WP\13BSY\14RDY\15EOT/BOT\16BOT\17OL\20FM"
15025676Ssam 
15125979Ssam /* error codes for CYS_ERR */
15225979Ssam #define	CYER_TIMOUT	0x01	/* timed out data busy false */
15325979Ssam #define	CYER_TIMOUT1	0x02	/* data busy false,formatter,ready */
15425979Ssam #define	CYER_TIMOUT2	0x03	/* time out ready busy false */
15525979Ssam #define	CYER_TIMOUT3	0x04	/* time out ready busy true */
15625979Ssam #define	CYER_TIMOUT4	0x05	/* time out data busy true */
15725979Ssam #define	CYER_NXM	0x06	/* time out memory */
15825979Ssam #define	CYER_BLANK	0x07	/* blank tape */
15925979Ssam #define	CYER_DIAG	0x08	/* micro-diagnostic */
16025979Ssam #define	CYER_EOT	0x09	/* EOT forward, BOT rev. */
16125979Ssam #define	CYER_BOT	0x09	/* EOT forward, BOT rev. */
16225979Ssam #define	CYER_HERR	0x0a	/* retry unsuccessful */
16325979Ssam #define	CYER_FIFO	0x0b	/* FIFO over/under flow */
16425979Ssam #define	CYER_PARITY	0x0d	/* drive to tapemaster parity error */
16525979Ssam #define	CYER_CKSUM	0x0e	/* prom checksum */
16625979Ssam #define	CYER_STROBE	0x0f	/* time out tape strobe */
16725979Ssam #define	CYER_NOTRDY	0x10	/* tape not ready */
16825979Ssam #define	CYER_PROT	0x11	/* write, no enable ring */
16925979Ssam #define	CYER_JUMPER	0x13	/* missing diagnostic jumper */
17025979Ssam #define	CYER_LINK	0x14	/* bad link, link inappropriate */
17125979Ssam #define	CYER_FM		0x15	/* unexpected filemark */
17225979Ssam #define	CYER_PARAM	0x16	/* bad parameter, byte count ? */
17325979Ssam #define	CYER_HDWERR	0x18	/* unidentified hardware error */
17425979Ssam #define	CYER_NOSTRM	0x19	/* streaming terminated */
17525676Ssam 
17625979Ssam #ifdef CYERROR
17725979Ssam char	*cyerror[] = {
17830372Skarels 	"no error",
17925979Ssam 	"timeout",
18025979Ssam 	"timeout1",
18125979Ssam 	"timeout2",
18225979Ssam 	"timeout3",
18325979Ssam 	"timeout4",
18430372Skarels 	"non-existent memory",
18525979Ssam 	"blank tape",
18625979Ssam 	"micro-diagnostic",
18725979Ssam 	"eot/bot detected",
18825979Ssam 	"retry unsuccessful",
18925979Ssam 	"fifo over/under-flow",
19030372Skarels 	"#0xc",
19125979Ssam 	"drive to controller parity error",
19225979Ssam 	"prom checksum",
19325979Ssam 	"time out tape strobe (record length error)",
19425979Ssam 	"tape not ready",
19525979Ssam 	"write protected",
19630372Skarels 	"#0x12",
19725979Ssam 	"missing diagnostic jumper",
19825979Ssam 	"invalid link pointer",
19925979Ssam 	"unexpected file mark",
20030372Skarels 	"invalid byte count/parameter",
20130372Skarels 	"#0x17",
20225979Ssam 	"unidentified hardware error",
20325979Ssam 	"streaming terminated"
20425979Ssam };
20525979Ssam #define	NCYERROR	(sizeof (cyerror) / sizeof (cyerror[0]))
20625979Ssam #endif
20725676Ssam 
20825979Ssam /*
20925979Ssam  * Masks defining hard and soft errors (must check against 1<<CYER_code).
21025979Ssam  */
21135477Sbostic #define	CYMASK(e)	(1 << (e))
212*35478Sbostic #define	CYER_HARD	(CYMASK(CYER_TIMOUT)|CYMASK(CYER_TIMOUT1)|\
213*35478Sbostic 	CYMASK(CYER_TIMOUT2)|CYMASK(CYER_TIMOUT3)|CYMASK(CYER_TIMOUT4)|\
214*35478Sbostic 	CYMASK(CYER_NXM)|CYMASK(CYER_DIAG)|CYMASK(CYER_JUMPER)|\
215*35478Sbostic 	CYMASK(CYER_STROBE)|CYMASK(CYER_PROT)|CYMASK(CYER_CKSUM)|\
216*35478Sbostic 	CYMASK(CYER_HERR)|CYMASK(CYER_BLANK))
217*35478Sbostic #define	CYER_RSOFT	(CYMASK(CYER_FIFO)|CYMASK(CYER_NOTRDY)|\
218*35478Sbostic 	CYMASK(CYER_PARITY))
219*35478Sbostic #define	CYER_WSOFT	(CYMASK(CYER_HERR)|CYMASK(CYER_FIFO)|\
220*35478Sbostic 	CYMASK(CYER_NOTRDY)|CYMASK(CYER_PARITY))
221