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