xref: /original-bsd/sys/tahoe/vba/vbavar.h (revision a95f03a8)
1 /*
2  * Copyright (c) 1988 Regents of the University of California.
3  * All rights reserved.
4  *
5  * %sccs.include.redist.c%
6  *
7  *	@(#)vbavar.h	7.5 (Berkeley) 06/28/90
8  */
9 
10 /*
11  * This file contains definitions related to the kernel structures
12  * for dealing with the VERSAbus adapters.
13  *
14  * Each VERSAbus has a vba_hd structure.
15  * Each VERSAbus controller which is not a device has a vba_ctlr structure.
16  * Each VERSAbus device has a vba_device structure.
17  */
18 
19 #ifndef LOCORE
20 /*
21  * Per-vba structure.
22  */
23 struct	vba_hd {
24 	int	vh_lastiv;		/* last interrupt vector assigned */
25 };
26 
27 /*
28  * Per-controller structure.
29  * (E.g. one for each disk and tape controller, and other things
30  * which use and release buffered data paths.)
31  *
32  * If a controller has devices attached, then there are
33  * cross-referenced vba_drive structures.
34  * This structure is the one which is queued in VERSAbus resource wait,
35  * and saves the information about VERSAbus resources which are used.
36  * The queue of devices waiting to transfer is also attached here.
37  */
38 struct vba_ctlr {
39 	struct	vba_driver *um_driver;
40 	short	um_ctlr;	/* controller index in driver */
41 	short	um_vbanum;	/* the vba it is on */
42 	short	um_alive;	/* controller exists */
43 	int	(**um_intr)();	/* interrupt handler(s) */
44 	caddr_t	um_addr;	/* address of device in i/o space */
45 	struct	vba_hd *um_hd;
46 /* the driver saves the prototype command here for use in its go routine */
47 	int	um_cmd;		/* communication to dgo() */
48 	int	um_vbinfo;	/* save VERSAbus registers, etc */
49 	struct	buf um_tab;	/* queue of devices for this controller */
50 };
51 
52 /*
53  * Per ``device'' structure.
54  * (A controller has devices or uses and releases buffered data paths).
55  * (Everything else is a ``device''.)
56  *
57  * If a controller has many drives attached, then there will
58  * be several vba_device structures associated with a single vba_ctlr
59  * structure.
60  *
61  * This structure contains all the information necessary to run
62  * a VERSAbus device.  It also contains information
63  * for slaves of VERSAbus controllers as to which device on the slave
64  * this is.  A flags field here can also be given in the system specification
65  * and is used to tell which tty lines are hard wired or other device
66  * specific parameters.
67  */
68 struct vba_device {
69 	struct	vba_driver *ui_driver;
70 	short	ui_unit;	/* unit number on the system */
71 	short	ui_ctlr;	/* mass ctlr number; -1 if none */
72 	short	ui_vbanum;	/* the vba it is on */
73 	short	ui_slave;	/* slave on controller */
74 	int	(**ui_intr)();	/* interrupt handler(s) */
75 	caddr_t	ui_addr;	/* address of device in i/o space */
76 	short	ui_dk;		/* if init 1 set to number for iostat */
77 	long	ui_flags;	/* parameter from system specification */
78 	short	ui_alive;	/* device exists */
79 	short	ui_type;	/* driver specific type information */
80 	caddr_t	ui_physaddr;	/* phys addr, for standalone (dump) code */
81 /* this is the forward link in a list of devices on a controller */
82 	struct	vba_device *ui_forw;
83 /* if the device is connected to a controller, this is the controller */
84 	struct	vba_ctlr *ui_mi;
85 	struct	vba_hd *ui_hd;
86 };
87 #endif
88 
89 /*
90  * Per-driver structure.
91  *
92  * Each VERSAbus driver defines entries for a set of routines
93  * as well as an array of types which are acceptable to it.
94  * These are used at boot time by the configuration program.
95  */
96 struct vba_driver {
97 	int	(*ud_probe)();		/* see if a driver is really there */
98 	int	(*ud_slave)();		/* see if a slave is there */
99 	int	(*ud_attach)();		/* setup driver for a slave */
100 	int	(*ud_dgo)();		/* fill csr/ba to start transfer */
101 	long	*ud_addr;		/* device csr addresses */
102 	char	*ud_dname;		/* name of a device */
103 	struct	vba_device **ud_dinfo;	/* backpointers to vbdinit structs */
104 	char	*ud_mname;		/* name of a controller */
105 	struct	vba_ctlr **ud_minfo;	/* backpointers to vbminit structs */
106 };
107 
108 /*
109  * Common state for Versabus driver I/O resources,
110  * including memory for intermediate buffer and page map,
111  * allocated by vbainit.
112  */
113 struct vb_buf {
114 	/* these fields set up once by vbainit */
115 	int	vb_flags;		/* device parameters */
116 	struct	pte *vb_map;		/* private page entries */
117 	caddr_t	vb_utl;			/* virtual addresses mapped by vb_map */
118 	caddr_t	vb_rawbuf;		/* intermediate buffer */
119 	u_long	vb_physbuf;		/* phys addr of intermediate buffer */
120 	u_long	vb_bufsize;		/* intermediate buffer size */
121 	u_long	vb_maxphys;		/* physical address limit */
122 	/* remaining fields apply to current transfer: */
123 	int	vb_copy;		/* copy to/from intermediate buffer */
124 	int	vb_iskernel;		/* is to/from kernel address space */
125 };
126 
127 /*
128  * flags to vbainit
129  */
130 #define	VB_32BIT	0x00		/* device uses 32-bit addressing */
131 #define	VB_24BIT	0x01		/* device uses 24-bit addressing */
132 #define	VB_20BIT	0x02		/* device uses 20-bit addressing */
133 #define	VB_SCATTER	0x04		/* device does scatter-gather */
134 
135 /*
136  * hardware memory-addressing limits: highest physical address
137  * that each address length can use for main memory access.
138  */
139 #define	VB_MAXADDR20	0x000fffff	/* highest addr for 20-bit */
140 #define	VB_MAXADDR24	0x00efffff	/* highest addr for 23/24-bit */
141 #define	VB_MAXADDR32	0x3effffff	/* highest addr for 32-bit */
142 
143 /*
144  * Statistics on vba operations.
145  */
146 struct vbastat {
147 	u_long	k_raw;		/* to/from contiguous kernel DMA buffer */
148 	u_long	u_raw;		/* to/from contiguous user DMA buffer */
149 	u_long	k_copy;		/* copied to/from kernel */
150 	u_long	u_copy;		/* copied to/from user */
151 	u_long	k_sg;		/* scatter-gather to/from kernel */
152 	u_long	u_sg;		/* scatter-gather to/from user */
153 };
154 
155 #ifndef LOCORE
156 #ifdef KERNEL
157 /*
158  * VBA related kernel variables
159  */
160 int	numvba;					/* number of uba's */
161 struct	vba_hd vba_hd[];
162 struct	vbastat vbastat;
163 
164 /*
165  * Vbminit and vbdinit initialize the mass storage controller and
166  * device tables specifying possible devices.
167  */
168 extern	struct	vba_ctlr vbminit[];
169 extern	struct	vba_device vbdinit[];
170 
171 /*
172  * VERSAbus device address space is mapped by VMEMmap
173  * into virtual address vmem[].
174  */
175 extern	struct pte VMEMmap[];	/* vba device addr pte's */
176 extern	char vmem[];		/* vba device addr space */
177 u_long	vbasetup();
178 #endif KERNEL
179 #endif !LOCORE
180