/[gxemul]/trunk/src/devices/bus_pci.c
This is repository of my old source code which isn't updated any more. Go to git.rot13.org for current projects!
ViewVC logotype

Annotation of /trunk/src/devices/bus_pci.c

Parent Directory Parent Directory | Revision Log Revision Log


Revision 24 - (hide annotations)
Mon Oct 8 16:19:56 2007 UTC (16 years, 7 months ago) by dpavlin
File MIME type: text/plain
File size: 31349 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.1256 2006/06/23 20:43:44 debug Exp $
20060219	Various minor updates. Removing the old MIPS16 skeleton code,
		because it will need to be rewritten for dyntrans anyway.
20060220-22	Removing the non-working dyntrans backend support.
		Continuing on the 64-bit dyntrans virtual memory generalization.
20060223	More work on the 64-bit vm generalization.
20060225	Beginning on MIPS dyntrans load/store instructions.
		Minor PPC updates (64-bit load/store, etc).
		Fixes for the variable-instruction-length framework, some
		minor AVR updates (a simple Hello World program works!).
		Beginning on a skeleton for automatically generating documen-
		tation (for devices etc.).
20060226	PPC updates (adding some more 64-bit instructions, etc).
		AVR updates (more instructions).
		FINALLY found and fixed the zs bug, making NetBSD/macppc
		accept the serial console.
20060301	Adding more AVR instructions.
20060304	Continuing on AVR-related stuff. Beginning on a framework for
		cycle-accurate device emulation. Adding an experimental "PAL
		TV" device (just a dummy so far).
20060305	Adding more AVR instructions.
		Adding a dummy epcom serial controller (for TS7200 emulation).
20060310	Removing the emul() command from configuration files, so only
		net() and machine() are supported.
		Minor progress on the MIPS dyntrans rewrite.
20060311	Continuing on the MIPS dyntrans rewrite (adding more
		instructions, etc).
20060315	Adding more instructions (sllv, srav, srlv, bgtz[l], blez[l],
		beql, bnel, slti[u], various loads and stores).
20060316	Removing the ALWAYS_SIGNEXTEND_32 option, since it was rarely
		used.
		Adding more MIPS dyntrans instructions, and fixing bugs.
20060318	Implementing fast loads/stores for MIPS dyntrans (big/little
		endian, 32-bit and 64-bit modes).
20060320	Making MIPS dyntrans the default configure option; use
		"--enable-oldmips" to use the old bintrans system.
		Adding MIPS dyntrans dmult[u]; minor updates.
20060322	Continuing... adding some more instructions.
		Adding a simple skeleton for demangling C++ "_ZN" symbols.
20060323	Moving src/debugger.c into a new directory (src/debugger/).
20060324	Fixing the hack used to load PPC ELFs (useful for relocated
		Linux/ppc kernels), and adding a dummy G3 machine mode.
20060325-26	Beginning to experiment with GDB remote serial protocol
		connections; adding a -G command line option for selecting
		which TCP port to listen to.
20060330	Beginning a major cleanup to replace things like "0x%016llx"
		with more correct "0x%016"PRIx64, etc.
		Continuing on the GDB remote serial protocol support.
20060331	More cleanup, and some minor GDB remote progress.
20060402	Adding a hack to the configure script, to allow compilation
		on systems that lack PRIx64 etc.
20060406	Removing the temporary FreeBSD/arm hack in dev_ns16550.c and
		replacing it with a better fix from Olivier Houchard.
20060407	A remote debugger (gdb or ddd) can now start and stop the
		emulator using the GDB remote serial protocol, and registers
		and memory can be read. MIPS only for now.
20060408	More GDB progress: single-stepping also works, and also adding
		support for ARM, PowerPC, and Alpha targets.
		Continuing on the delay-slot-across-page-boundary issue.
20060412	Minor update: beginning to add support for the SPARC target
		to the remote GDB functionality.
20060414	Various MIPS updates: adding more instructions for dyntrans
		(eret, add), and making some exceptions work. Fixing a bug
		in dmult[u].
		Implementing the first SPARC instructions (sethi, or).
20060415	Adding "magic trap" instructions so that PROM calls can be
		software emulated in MIPS dyntrans.
		Adding more MIPS dyntrans instructions (ddiv, dadd) and
		fixing another bug in dmult.
20060416	More MIPS dyntrans progress: adding [d]addi, movn, movz, dsllv,
		rfi, an ugly hack for supporting R2000/R3000 style faked caches,
		preliminary interrupt support, and various other updates and
		bugfixes.
20060417	Adding more SPARC instructions (add, sub, sll[x], sra[x],
		srl[x]), and useful SPARC header definitions.
		Adding the first (trivial) x86/AMD64 dyntrans instructions (nop,
		cli/sti, stc/clc, std/cld, simple mov, inc ax). Various other
		x86 updates related to variable instruction length stuff.
		Adding unaligned loads/stores to the MIPS dyntrans mode (but
		still using the pre-dyntrans (slow) imlementation).
20060419	Fixing a MIPS dyntrans exception-in-delay-slot bug.
		Removing the old "show opcode statistics" functionality, since
		it wasn't really useful and isn't implemented for dyntrans.
		Single-stepping (or running with instruction trace) now looks
		ok with dyntrans with delay-slot architectures.
20060420	Minor hacks (removing the -B command line option when compiled
		for non-bintrans, and some other very minor updates).
		Adding (slow) MIPS dyntrans load-linked/store-conditional.
20060422	Applying fixes for bugs discovered by Nils Weller's nwcc
		(static DEC memmap => now per machine, and adding an extern
		keyword in cpu_arm_instr.c).
		Finally found one of the MIPS dyntrans bugs that I've been
		looking for (copy/paste spelling error BIG vs LITTLE endian in
		cpu_mips_instr_loadstore.c for 16-bit fast stores).
		FINALLY found the major MIPS dyntrans bug: slti vs sltiu
		signed/unsigned code in cpu_mips_instr.c. :-)
		Adding more MIPS dyntrans instructions (lwc1, swc1, bgezal[l],
		ctc1, tlt[u], tge[u], tne, beginning on rdhwr).
		NetBSD/hpcmips can now reach userland when using dyntrans :-)
		Adding some more x86 dyntrans instructions.
		Finally removed the old Alpha-specific virtual memory code,
		and replaced it with the generic 64-bit version.
		Beginning to add disassembly support for SPECIAL3 MIPS opcodes.
20060423	Continuing on the delay-slot-across-page-boundary issue;
		adding an end_of_page2 ic slot (like I had planned before, but
		had removed for some reason).
		Adding a quick-and-dirty fallback to legacy coprocessor 1
		code (i.e. skipping dyntrans implementation for now).
		NetBSD/hpcmips and NetBSD/pmax (when running on an emulated
		R4400) can now be installed and run. :-)  (Many bugs left
		to fix, though.)
		Adding more MIPS dyntrans instructions: madd[u], msub[u].
		Cleaning up the SPECIAL2 vs R5900/TX79/C790 "MMI" opcode
		maps somewhat (disassembly and dyntrans instruction decoding).
20060424	Adding an isa_revision field to mips_cpu_types.h, and making
		sure that SPECIAL3 opcodes cause Reserved Instruction
		exceptions on MIPS32/64 revisions lower than 2.
		Adding the SPARC 'ba', 'call', 'jmpl/retl', 'and', and 'xor'
		instructions.
20060425	Removing the -m command line option ("run at most x 
		instructions") and -T ("single_step_on_bad_addr"), because
		they never worked correctly with dyntrans anyway.
		Freshening up the man page.
20060428	Adding more MIPS dyntrans instructions: bltzal[l], idle.
		Enabling MIPS dyntrans compare interrupts.
20060429	FINALLY found the weird dyntrans bug, causing NetBSD etc. to
		behave strangely: some floating point code (conditional
		coprocessor branches) could not be reused from the old
		non-dyntrans code. The "quick-and-dirty fallback" only appeared
		to work. Fixing by implementing bc1* for MIPS dyntrans.
		More MIPS instructions: [d]sub, sdc1, ldc1, dmtc1, dmfc1, cfc0.
		Freshening up MIPS floating point disassembly appearance.
20060430	Continuing on C790/R5900/TX79 disassembly; implementing 128-bit
		"por" and "pextlw".
20060504	Disabling -u (userland emulation) unless compiled as unstable
		development version.
		Beginning on freshening up the testmachine include files,
		to make it easier to reuse those files (placing them in
		src/include/testmachine/), and beginning on a set of "demos"
		or "tutorials" for the testmachine functionality.
		Minor updates to the MIPS GDB remote protocol stub.
		Refreshing doc/experiments.html and gdb_remote.html.
		Enabling Alpha emulation in the stable release configuration,
		even though no guest OSes for Alpha can run yet.
20060505	Adding a generic 'settings' object, which will contain
		references to settable variables (which will later be possible
		to access using the debugger).
20060506	Updating dev_disk and corresponding demo/documentation (and
		switching from SCSI to IDE disk types, so it actually works
		with current test machines :-).
20060510	Adding a -D_LARGEFILE_SOURCE hack for 64-bit Linux hosts,
		so that fseeko() doesn't give a warning.
		Updating the section about how dyntrans works (the "runnable
		IR") in doc/intro.html.
		Instruction updates (some x64=1 checks, some more R5900
		dyntrans stuff: better mul/mult separation from MIPS32/64,
		adding ei and di).
		Updating MIPS cpuregs.h to a newer one (from NetBSD).
		Adding more MIPS dyntrans instructions: deret, ehb.
20060514	Adding disassembly and beginning implementation of SPARC wr
		and wrpr instructions.
20060515	Adding a SUN SPARC machine mode, with dummy SS20 and Ultra1
		machines. Adding the 32-bit "rd psr" instruction.
20060517	Disassembly support for the general SPARC rd instruction.
		Partial implementation of the cmp (subcc) instruction.
		Some other minor updates (making sure that R5900 processors
		start up with the EIE bit enabled, otherwise Linux/playstation2
		receives no interrupts).
20060519	Minor MIPS updates/cleanups.
20060521	Moving the MeshCube machine into evbmips; this seems to work
		reasonably well with a snapshot of a NetBSD MeshCube kernel.
		Cleanup/fix of MIPS config0 register initialization.
20060529	Minor MIPS fixes, including a sign-extension fix to the
		unaligned load/store code, which makes NetBSD/pmax on R3000
		work better with dyntrans. (Ultrix and Linux/DECstation still
		don't work, though.)
20060530	Minor updates to the Alpha machine mode: adding an AlphaBook
		mode, an LCA bus (forwarding accesses to an ISA bus), etc.
20060531	Applying a bugfix for the MIPS dyntrans sc[d] instruction from
		Ondrej Palkovsky. (Many thanks.)
20060601	Minifix to allow ARM immediate msr instruction to not give
		an error for some valid values.
		More Alpha updates.
20060602	Some minor Alpha updates.
20060603	Adding the Alpha cmpbge instruction. NetBSD/alpha prints its
		first boot messages :-) on an emulated Alphabook 1.
20060612	Minor updates; adding a dev_ether.h include file for the
		testmachine ether device. Continuing the hunt for the dyntrans
		bug which makes Linux and Ultrix on DECstation behave
		strangely... FINALLY found it! It seems to be related to
		invalidation of the translation cache, on tlbw{r,i}. There
		also seems to be some remaining interrupt-related problems.
20060614	Correcting the implementation of ldc1/sdc1 for MIPS dyntrans
		(so that it uses 16 32-bit registers if the FR bit in the
		status register is not set).
20060616	REMOVING BINTRANS COMPLETELY!
		Removing the old MIPS interpretation mode.
		Removing the MFHILO_DELAY and instruction delay stuff, because
		they wouldn't work with dyntrans anyway.
20060617	Some documentation updates (adding "NetBSD-archive" to some
		URLs, and new Debian/DECstation installation screenshots).
		Removing the "tracenull" and "enable-caches" configure options.
		Improving MIPS dyntrans performance somewhat (only invalidate
		translations if necessary, on writes to the entryhi register,
		instead of doing it for all cop0 writes).
20060618	More cleanup after the removal of the old MIPS emulation.
		Trying to fix the MIPS dyntrans performance bugs/bottlenecks;
		only semi-successful so far (for R3000).
20060620	Minor update to allow clean compilation again on Tru64/Alpha.
20060622	MIPS cleanup and fixes (removing the pc_last stuff, which
		doesn't make sense with dyntrans anyway, and fixing a cross-
		page-delay-slot-with-exception case in end_of_page).
		Removing the old max_random_cycles_per_chunk stuff, and the
		concept of cycles vs instructions for MIPS emulation.
		FINALLY found and fixed the bug which caused NetBSD/pmax
		clocks to behave strangely (it was a load to the zero register,
		which was treated as a NOP; now it is treated as a load to a
		dummy scratch register).
20060623	Increasing the dyntrans chunk size back to
		N_SAFE_DYNTRANS_LIMIT, instead of N_SAFE_DYNTRANS_LIMIT/2.
		Preparing for a quick release, even though there are known
		bugs, and performance for non-R3000 MIPS emulation is very
		poor. :-/
		Reverting to half the dyntrans chunk size again, because
		NetBSD/cats seemed less stable with full size chunks. :(
		NetBSD/sgimips 3.0 can now run :-)  (With release 0.3.8, only
		NetBSD/sgimips 2.1 worked, not 3.0.)

==============  RELEASE 0.4.0  ==============


1 dpavlin 4 /*
2 dpavlin 22 * Copyright (C) 2004-2006 Anders Gavare. All rights reserved.
3 dpavlin 4 *
4     * Redistribution and use in source and binary forms, with or without
5     * modification, are permitted provided that the following conditions are met:
6     *
7     * 1. Redistributions of source code must retain the above copyright
8     * notice, this list of conditions and the following disclaimer.
9     * 2. Redistributions in binary form must reproduce the above copyright
10     * notice, this list of conditions and the following disclaimer in the
11     * documentation and/or other materials provided with the distribution.
12     * 3. The name of the author may not be used to endorse or promote products
13     * derived from this software without specific prior written permission.
14     *
15     * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16     * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17     * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18     * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19     * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20     * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21     * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22     * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23     * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24     * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25     * SUCH DAMAGE.
26     *
27     *
28 dpavlin 24 * $Id: bus_pci.c,v 1.65 2006/05/10 03:32:32 debug Exp $
29 dpavlin 4 *
30 dpavlin 20 * Generic PCI bus framework. This is not a normal "device", but is used by
31     * individual PCI controllers and devices.
32 dpavlin 4 *
33 dpavlin 20 * See NetBSD's pcidevs.h for more PCI vendor and device identifiers.
34     *
35     * TODO:
36     *
37     * x) Allow guest OSes to do runtime address fixups (i.e. actually
38     * move a device from one address to another).
39     *
40     * x) Generalize the PCI and legacy ISA interrupt routing stuff.
41     *
42     * x) Make sure that pci_little_endian is used correctly everywhere.
43 dpavlin 4 */
44    
45     #include <stdio.h>
46     #include <stdlib.h>
47     #include <string.h>
48    
49 dpavlin 20 #define BUS_PCI_C
50    
51     #include "bus_pci.h"
52     #include "cpu.h"
53     #include "device.h"
54     #include "devices.h"
55     #include "diskimage.h"
56     #include "machine.h"
57 dpavlin 4 #include "memory.h"
58     #include "misc.h"
59    
60 dpavlin 20 extern int verbose;
61 dpavlin 4
62 dpavlin 20
63 dpavlin 24 #ifdef UNSTABLE_DEVEL
64     #define debug fatal
65     #endif
66 dpavlin 4
67 dpavlin 14
68 dpavlin 22 /*
69     * bus_pci_decompose_1():
70     *
71     * Helper function for decomposing Mechanism 1 tags.
72     */
73     void bus_pci_decompose_1(uint32_t t, int *bus, int *dev, int *func, int *reg)
74 dpavlin 20 {
75 dpavlin 22 *bus = (t >> 16) & 0xff;
76     *dev = (t >> 11) & 0x1f;
77     *func = (t >> 8) & 0x7;
78     *reg = t & 0xff;
79    
80     /* Warn about unaligned register access: */
81     if (t & 3)
82     fatal("[ bus_pci_decompose_1: WARNING: reg = 0x%02x ]\n",
83     t & 0xff);
84 dpavlin 20 }
85    
86    
87 dpavlin 4 /*
88 dpavlin 20 * bus_pci_data_access():
89     *
90 dpavlin 22 * Reads from or writes to the PCI configuration registers of a device.
91 dpavlin 20 */
92 dpavlin 22 void bus_pci_data_access(struct cpu *cpu, struct pci_data *pci_data,
93     uint64_t *data, int len, int writeflag)
94 dpavlin 20 {
95     struct pci_device *dev;
96     unsigned char *cfg_base;
97     uint64_t x, idata = *data;
98 dpavlin 22 int i;
99 dpavlin 20
100     /* Scan through the list of pci_device entries. */
101     dev = pci_data->first_device;
102     while (dev != NULL) {
103 dpavlin 22 if (dev->bus == pci_data->cur_bus &&
104     dev->function == pci_data->cur_func &&
105     dev->device == pci_data->cur_device)
106 dpavlin 20 break;
107     dev = dev->next;
108     }
109    
110     /* No device? Then return emptiness. */
111     if (dev == NULL) {
112 dpavlin 22 if (writeflag == MEM_READ) {
113     if (pci_data->cur_reg == 0)
114     *data = -1;
115     else
116     *data = 0;
117     } else {
118     fatal("[ bus_pci_data_access(): write to non-existant"
119     " device? ]\n");
120     }
121 dpavlin 20 return;
122     }
123    
124     /* Return normal config data, or length data? */
125     if (pci_data->last_was_write_ffffffff &&
126 dpavlin 22 pci_data->cur_reg >= PCI_MAPREG_START &&
127     pci_data->cur_reg <= PCI_MAPREG_END - 4)
128 dpavlin 20 cfg_base = dev->cfg_mem_size;
129     else
130     cfg_base = dev->cfg_mem;
131    
132     /* Read data as little-endian: */
133     x = 0;
134 dpavlin 22 for (i=len-1; i>=0; i--) {
135     int ofs = pci_data->cur_reg + i;
136     x <<= 8;
137     x |= cfg_base[ofs & (PCI_CFG_MEM_SIZE - 1)];
138 dpavlin 20 }
139    
140     /* Register write: */
141     if (writeflag == MEM_WRITE) {
142 dpavlin 22 debug("[ bus_pci: write to PCI DATA: data = 0x%08llx ]\n",
143 dpavlin 20 (long long)idata);
144 dpavlin 22 if (idata == 0xffffffffULL &&
145     pci_data->cur_reg >= PCI_MAPREG_START &&
146     pci_data->cur_reg <= PCI_MAPREG_END - 4) {
147 dpavlin 20 pci_data->last_was_write_ffffffff = 1;
148     return;
149     }
150     /* Writes are not really supported yet: */
151     if (idata != x) {
152     debug("[ bus_pci: write to PCI DATA: data = 0x%08llx"
153     " differs from current value 0x%08llx; NOT YET"
154     " SUPPORTED. bus %i, device %i, function %i (%s)"
155     " register 0x%02x ]\n", (long long)idata,
156 dpavlin 22 (long long)x, pci_data->cur_bus,
157     pci_data->cur_device, pci_data->cur_func,
158     dev->name, pci_data->cur_reg);
159 dpavlin 20 }
160     return;
161     }
162    
163     /* Register read: */
164     *data = x;
165    
166     pci_data->last_was_write_ffffffff = 0;
167    
168 dpavlin 22 debug("[ bus_pci: read from PCI DATA, bus %i, device "
169 dpavlin 24 "%i, function %i (%s) register 0x%02x: (len=%i) 0x%08lx ]\n",
170     pci_data->cur_bus, pci_data->cur_device, pci_data->cur_func,
171     dev->name, pci_data->cur_reg, len, (long)*data);
172 dpavlin 20 }
173    
174    
175     /*
176 dpavlin 22 * bus_pci_setaddr():
177 dpavlin 4 *
178 dpavlin 22 * Sets the address in preparation for a PCI register transfer.
179 dpavlin 4 */
180 dpavlin 22 void bus_pci_setaddr(struct cpu *cpu, struct pci_data *pci_data,
181     int bus, int device, int function, int reg)
182 dpavlin 4 {
183 dpavlin 22 if (cpu == NULL || pci_data == NULL) {
184     fatal("bus_pci_setaddr(): NULL ptr\n");
185     exit(1);
186 dpavlin 4 }
187    
188 dpavlin 22 pci_data->cur_bus = bus;
189     pci_data->cur_device = device;
190     pci_data->cur_func = function;
191     pci_data->cur_reg = reg;
192 dpavlin 4 }
193    
194    
195     /*
196     * bus_pci_add():
197     *
198     * Add a PCI device to a bus_pci device.
199     */
200     void bus_pci_add(struct machine *machine, struct pci_data *pci_data,
201     struct memory *mem, int bus, int device, int function,
202 dpavlin 22 const char *name)
203 dpavlin 4 {
204 dpavlin 20 struct pci_device *pd;
205     int ofs;
206     void (*init)(struct machine *, struct memory *, struct pci_device *);
207 dpavlin 4
208 dpavlin 14 if (pci_data == NULL) {
209     fatal("bus_pci_add(): pci_data == NULL!\n");
210     exit(1);
211     }
212    
213 dpavlin 20 /* Find the PCI device: */
214     init = pci_lookup_initf(name);
215    
216 dpavlin 4 /* Make sure this bus/device/function number isn't already in use: */
217 dpavlin 20 pd = pci_data->first_device;
218     while (pd != NULL) {
219     if (pd->bus == bus && pd->device == device &&
220     pd->function == function) {
221 dpavlin 4 fatal("bus_pci_add(): (bus %i, device %i, function"
222     " %i) already in use\n", bus, device, function);
223 dpavlin 20 exit(1);
224 dpavlin 4 }
225 dpavlin 20 pd = pd->next;
226 dpavlin 4 }
227    
228 dpavlin 20 pd = malloc(sizeof(struct pci_device));
229     if (pd == NULL) {
230 dpavlin 4 fprintf(stderr, "out of memory\n");
231     exit(1);
232     }
233    
234 dpavlin 20 memset(pd, 0, sizeof(struct pci_device));
235 dpavlin 4
236     /* Add the new device first in the PCI bus' chain: */
237 dpavlin 20 pd->next = pci_data->first_device;
238     pci_data->first_device = pd;
239 dpavlin 4
240 dpavlin 20 pd->pcibus = pci_data;
241     pd->name = strdup(name);
242     pd->bus = bus;
243     pd->device = device;
244     pd->function = function;
245    
246     /*
247     * Initialize with some default values:
248     *
249 dpavlin 22 * TODO: The command status register is best to set up per device.
250     * The size registers should also be set up on a per-device basis.
251 dpavlin 20 */
252 dpavlin 22 PCI_SET_DATA(PCI_COMMAND_STATUS_REG,
253     PCI_COMMAND_IO_ENABLE | PCI_COMMAND_MEM_ENABLE);
254 dpavlin 20 for (ofs = PCI_MAPREG_START; ofs < PCI_MAPREG_END; ofs += 4)
255 dpavlin 22 PCI_SET_DATA_SIZE(ofs, 0x00100000 - 1);
256 dpavlin 20
257     if (init == NULL) {
258     fatal("No init function for PCI device \"%s\"?\n", name);
259     exit(1);
260     }
261    
262 dpavlin 4 /* Call the PCI device' init function: */
263 dpavlin 20 init(machine, mem, pd);
264 dpavlin 4 }
265    
266    
267     /*
268 dpavlin 20 * allocate_device_space():
269     *
270     * Used by glue code (see below) to allocate space for a PCI device.
271     *
272     * The returned values in portp and memp are the actual (emulated) addresses
273     * that the device should use. (Normally only one of these is actually used.)
274     *
275     * TODO: PCI irqs?
276     */
277     static void allocate_device_space(struct pci_device *pd,
278     uint64_t portsize, uint64_t memsize,
279     uint64_t *portp, uint64_t *memp)
280     {
281     uint64_t port, mem;
282    
283     /* Calculate an aligned starting port: */
284     port = pd->pcibus->cur_pci_portbase;
285     if (portsize != 0) {
286     port = ((port - 1) | (portsize - 1)) + 1;
287     pd->pcibus->cur_pci_portbase = port;
288 dpavlin 22 PCI_SET_DATA(PCI_MAPREG_START + pd->cur_mapreg_offset,
289     port | PCI_MAPREG_TYPE_IO);
290     PCI_SET_DATA_SIZE(PCI_MAPREG_START + pd->cur_mapreg_offset,
291 dpavlin 24 ((portsize - 1) & ~0xf) | 0xd);
292 dpavlin 22 pd->cur_mapreg_offset += sizeof(uint32_t);
293 dpavlin 20 }
294    
295     /* Calculate an aligned starting memory location: */
296     mem = pd->pcibus->cur_pci_membase;
297     if (memsize != 0) {
298     mem = ((mem - 1) | (memsize - 1)) + 1;
299     pd->pcibus->cur_pci_membase = mem;
300 dpavlin 22 PCI_SET_DATA(PCI_MAPREG_START + pd->cur_mapreg_offset, mem);
301     PCI_SET_DATA_SIZE(PCI_MAPREG_START + pd->cur_mapreg_offset,
302 dpavlin 24 ((memsize - 1) & ~0xf) | 0x0);
303 dpavlin 22 pd->cur_mapreg_offset += sizeof(uint32_t);
304 dpavlin 20 }
305    
306     *portp = port + pd->pcibus->pci_actual_io_offset;
307     *memp = mem + pd->pcibus->pci_actual_mem_offset;
308    
309     if (verbose >= 2) {
310     debug("pci device '%s' at", pd->name);
311     if (portsize != 0)
312     debug(" port 0x%llx-0x%llx", (long long)pd->pcibus->
313     cur_pci_portbase, (long long)(pd->pcibus->
314     cur_pci_portbase + portsize - 1));
315     if (memsize != 0)
316     debug(" mem 0x%llx-0x%llx", (long long)pd->pcibus->
317     cur_pci_membase, (long long)(pd->pcibus->
318     cur_pci_membase + memsize - 1));
319     debug("\n");
320     }
321    
322     pd->pcibus->cur_pci_portbase += portsize;
323     pd->pcibus->cur_pci_membase += memsize;
324     }
325    
326    
327 dpavlin 22 static void bus_pci_debug_dump__2(struct pci_device *pd)
328     {
329     if (pd == NULL)
330     return;
331     bus_pci_debug_dump__2(pd->next);
332     debug("bus %3i, dev %2i, func %i: %s\n",
333     pd->bus, pd->device, pd->function, pd->name);
334     }
335    
336    
337 dpavlin 20 /*
338 dpavlin 22 * bus_pci_debug_dump():
339     *
340     * Lists the attached PCI devices (in reverse).
341     */
342     void bus_pci_debug_dump(void *extra)
343     {
344     struct pci_data *d = (struct pci_data *) extra;
345     int iadd = DEBUG_INDENTATION;
346    
347     debug("pci:\n");
348     debug_indentation(iadd);
349    
350     if (d->first_device == NULL)
351     debug("no devices!\n");
352     else
353     bus_pci_debug_dump__2(d->first_device);
354    
355     debug_indentation(-iadd);
356     }
357    
358    
359     /*
360 dpavlin 4 * bus_pci_init():
361     *
362     * This doesn't register a device, but instead returns a pointer to a struct
363 dpavlin 22 * which should be passed to other bus_pci functions when accessing the bus.
364 dpavlin 20 *
365     * irq_nr is the (optional) IRQ nr that this PCI bus interrupts at.
366     *
367     * pci_portbase, pci_membase, and pci_irqbase are the port, memory, and
368     * interrupt bases for PCI devices (as found in the configuration registers).
369     *
370     * pci_actual_io_offset and pci_actual_mem_offset are the offset from
371     * the values in the configuration registers to the actual (emulated) device.
372     *
373     * isa_portbase, isa_membase, and isa_irqbase are the port, memory, and
374     * interrupt bases for legacy ISA devices.
375 dpavlin 4 */
376 dpavlin 22 struct pci_data *bus_pci_init(struct machine *machine, int irq_nr,
377 dpavlin 20 uint64_t pci_actual_io_offset, uint64_t pci_actual_mem_offset,
378     uint64_t pci_portbase, uint64_t pci_membase, int pci_irqbase,
379     uint64_t isa_portbase, uint64_t isa_membase, int isa_irqbase)
380 dpavlin 4 {
381     struct pci_data *d;
382    
383     d = malloc(sizeof(struct pci_data));
384     if (d == NULL) {
385     fprintf(stderr, "out of memory\n");
386     exit(1);
387     }
388     memset(d, 0, sizeof(struct pci_data));
389 dpavlin 20 d->irq_nr = irq_nr;
390     d->pci_actual_io_offset = pci_actual_io_offset;
391     d->pci_actual_mem_offset = pci_actual_mem_offset;
392     d->pci_portbase = pci_portbase;
393     d->pci_membase = pci_membase;
394     d->pci_irqbase = pci_irqbase;
395     d->isa_portbase = isa_portbase;
396     d->isa_membase = isa_membase;
397     d->isa_irqbase = isa_irqbase;
398 dpavlin 4
399 dpavlin 22 /* Register the bus: */
400     machine_bus_register(machine, "pci", bus_pci_debug_dump, d);
401    
402 dpavlin 20 /* Assume that the first 64KB could be used by legacy ISA devices: */
403     d->cur_pci_portbase = d->pci_portbase + 0x10000;
404     d->cur_pci_membase = d->pci_membase + 0x10000;
405    
406 dpavlin 4 return d;
407     }
408    
409 dpavlin 20
410    
411     /******************************************************************************
412 dpavlin 22 * *
413     * The following is glue code for PCI controllers and devices. The glue *
414     * code does the minimal stuff necessary to get an emulated OS to detect *
415     * the device (i.e. set up PCI configuration registers), and then if *
416     * necessary adds a "normal" device. *
417     * *
418 dpavlin 20 ******************************************************************************/
419    
420    
421    
422     /*
423     * Integraphics Systems "igsfb" Framebuffer (graphics) card.
424     *
425     * TODO
426     */
427    
428     #define PCI_VENDOR_INTEGRAPHICS 0x10ea
429    
430     PCIINIT(igsfb)
431     {
432     PCI_SET_DATA(PCI_ID_REG,
433     PCI_ID_CODE(PCI_VENDOR_INTEGRAPHICS, 0x2010));
434    
435     PCI_SET_DATA(PCI_CLASS_REG,
436     PCI_CLASS_CODE(PCI_CLASS_DISPLAY,
437     PCI_SUBCLASS_DISPLAY_VGA, 0) + 0x01);
438    
439     /* TODO */
440 dpavlin 22 PCI_SET_DATA(0x10, 0x08000000);
441 dpavlin 20
442 dpavlin 22 dev_vga_init(machine, mem, pd->pcibus->isa_membase + 0xa0000,
443     0x88800000 + 0x3c0, machine->machine_name);
444 dpavlin 20 }
445    
446    
447    
448     /*
449     * S3 ViRGE graphics.
450     *
451     * TODO: Only emulates a standard VGA card, so far.
452     */
453    
454     #define PCI_VENDOR_S3 0x5333
455     #define PCI_PRODUCT_S3_VIRGE 0x5631
456     #define PCI_PRODUCT_S3_VIRGE_DX 0x8a01
457    
458     PCIINIT(s3_virge)
459     {
460     PCI_SET_DATA(PCI_ID_REG,
461     PCI_ID_CODE(PCI_VENDOR_S3, PCI_PRODUCT_S3_VIRGE_DX));
462    
463     PCI_SET_DATA(PCI_CLASS_REG,
464     PCI_CLASS_CODE(PCI_CLASS_DISPLAY,
465     PCI_SUBCLASS_DISPLAY_VGA, 0) + 0x01);
466    
467     dev_vga_init(machine, mem, pd->pcibus->isa_membase + 0xa0000,
468     pd->pcibus->isa_portbase + 0x3c0, machine->machine_name);
469     }
470    
471    
472    
473     /*
474     * Acer Labs M5229 PCI-IDE (UDMA) controller.
475     * Acer Labs M1543 PCI->ISA bridge.
476     */
477    
478     #define PCI_VENDOR_ALI 0x10b9
479     #define PCI_PRODUCT_ALI_M1543 0x1533 /* NOTE: not 1543 */
480     #define PCI_PRODUCT_ALI_M5229 0x5229
481    
482     PCIINIT(ali_m1543)
483     {
484     PCI_SET_DATA(PCI_ID_REG,
485     PCI_ID_CODE(PCI_VENDOR_ALI, PCI_PRODUCT_ALI_M1543));
486    
487     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
488     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0xc3);
489    
490     PCI_SET_DATA(PCI_BHLC_REG,
491     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
492    
493     /* Linux uses these to detect which IRQ the IDE controller uses: */
494     PCI_SET_DATA(0x44, 0x0000000e);
495     PCI_SET_DATA(0x58, 0x00000003);
496     }
497    
498     PCIINIT(ali_m5229)
499     {
500     char tmpstr[300];
501    
502     PCI_SET_DATA(PCI_ID_REG,
503     PCI_ID_CODE(PCI_VENDOR_ALI, PCI_PRODUCT_ALI_M5229));
504    
505     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
506     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x60) + 0xc1);
507    
508     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
509     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
510     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
511     (long long)(pd->pcibus->isa_portbase + 0x1f0),
512     pd->pcibus->isa_irqbase + 14);
513     device_add(machine, tmpstr);
514     }
515    
516     /* The secondary channel is disabled. TODO: fix this. */
517     }
518    
519    
520    
521     /*
522     * Adaptec AHC SCSI controller.
523     */
524    
525     #define PCI_VENDOR_ADP 0x9004 /* Adaptec */
526     #define PCI_VENDOR_ADP2 0x9005 /* Adaptec (2nd PCI Vendor ID) */
527     #define PCI_PRODUCT_ADP_2940U 0x8178 /* AHA-2940 Ultra */
528     #define PCI_PRODUCT_ADP_2940UP 0x8778 /* AHA-2940 Ultra Pro */
529    
530     PCIINIT(ahc)
531     {
532     /* Numbers taken from a Adaptec 2940U: */
533     /* http://mail-index.netbsd.org/netbsd-bugs/2000/04/29/0000.html */
534    
535     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_ADP,
536     PCI_PRODUCT_ADP_2940U));
537    
538     PCI_SET_DATA(PCI_COMMAND_STATUS_REG, 0x02900007);
539    
540     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
541     PCI_SUBCLASS_MASS_STORAGE_SCSI, 0) + 0x01);
542    
543     PCI_SET_DATA(PCI_BHLC_REG, 0x00004008);
544    
545     /* 1 = type i/o. 0x0000e801; address? */
546     /* second address reg = 0xf1002000? */
547     PCI_SET_DATA(PCI_MAPREG_START + 0x00, 0x00000001);
548     PCI_SET_DATA(PCI_MAPREG_START + 0x04, 0x00000000);
549    
550     PCI_SET_DATA(PCI_MAPREG_START + 0x08, 0x00000000);
551     PCI_SET_DATA(PCI_MAPREG_START + 0x0c, 0x00000000);
552     PCI_SET_DATA(PCI_MAPREG_START + 0x10, 0x00000000);
553     PCI_SET_DATA(PCI_MAPREG_START + 0x14, 0x00000000);
554     PCI_SET_DATA(PCI_MAPREG_START + 0x18, 0x00000000);
555    
556     /* Subsystem vendor ID? 0x78819004? */
557     PCI_SET_DATA(PCI_MAPREG_START + 0x1c, 0x00000000);
558    
559     PCI_SET_DATA(0x30, 0xef000000);
560     PCI_SET_DATA(PCI_CAPLISTPTR_REG, 0x000000dc);
561     PCI_SET_DATA(0x38, 0x00000000);
562     PCI_SET_DATA(PCI_INTERRUPT_REG, 0x08080109); /* interrupt pin A */
563    
564     /*
565     * TODO: this address is based on what NetBSD/sgimips uses
566     * on SGI IP32 (O2). Fix this!
567     */
568    
569     device_add(machine, "ahc addr=0x18000000");
570    
571     /* OpenBSD/sgi snapshots sometime between 2005-03-11 and
572     2005-04-04 changed to using 0x1a000000: */
573     dev_ram_init(machine, 0x1a000000, 0x2000000, DEV_RAM_MIRROR,
574     0x18000000);
575     }
576    
577    
578    
579     /*
580     * Galileo Technology GT-64xxx PCI controller.
581     *
582     * GT-64011 Used in Cobalt machines.
583     * GT-64120 Used in evbmips machines (Malta).
584     *
585     * NOTE: This works in the opposite way compared to other devices; the PCI
586     * device is added from the normal device instead of the other way around.
587     */
588    
589     #define PCI_VENDOR_GALILEO 0x11ab /* Galileo Technology */
590     #define PCI_PRODUCT_GALILEO_GT64011 0x4146 /* GT-64011 System Controller */
591     #define PCI_PRODUCT_GALILEO_GT64120 0x4620 /* GT-64120 */
592 dpavlin 22 #define PCI_PRODUCT_GALILEO_GT64260 0x6430 /* GT-64260 */
593 dpavlin 20
594     PCIINIT(gt64011)
595     {
596     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_GALILEO,
597     PCI_PRODUCT_GALILEO_GT64011));
598    
599 dpavlin 22 PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
600 dpavlin 20 PCI_SUBCLASS_BRIDGE_HOST, 0) + 0x01); /* Revision 1 */
601     }
602    
603     PCIINIT(gt64120)
604     {
605     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_GALILEO,
606     PCI_PRODUCT_GALILEO_GT64120));
607    
608     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
609     PCI_SUBCLASS_BRIDGE_HOST, 0) + 0x02); /* Revision 2? */
610    
611     switch (machine->machine_type) {
612     case MACHINE_EVBMIPS:
613     PCI_SET_DATA(PCI_MAPREG_START + 0x10, 0x1be00000);
614     break;
615     }
616     }
617    
618 dpavlin 22 PCIINIT(gt64260)
619     {
620     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_GALILEO,
621     PCI_PRODUCT_GALILEO_GT64260));
622 dpavlin 20
623 dpavlin 22 PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
624     PCI_SUBCLASS_BRIDGE_HOST, 0) + 0x01); /* Revision 1? */
625     }
626 dpavlin 20
627 dpavlin 22
628    
629 dpavlin 20 /*
630 dpavlin 22 * Intel 31244 Serial ATA Controller
631     * Intel 82371SB PIIX3 PCI-ISA bridge
632     * Intel 82371AB PIIX4 PCI-ISA bridge
633     * Intel 82371SB IDE controller
634     * Intel 82371AB IDE controller
635     * Intel 82378ZB System I/O controller.
636 dpavlin 20 */
637    
638     #define PCI_VENDOR_INTEL 0x8086
639 dpavlin 22 #define PCI_PRODUCT_INTEL_31244 0x3200
640     #define PCI_PRODUCT_INTEL_82371SB_ISA 0x7000
641     #define PCI_PRODUCT_INTEL_82371SB_IDE 0x7010
642 dpavlin 20 #define PCI_PRODUCT_INTEL_82371AB_ISA 0x7110
643     #define PCI_PRODUCT_INTEL_82371AB_IDE 0x7111
644     #define PCI_PRODUCT_INTEL_SIO 0x0484
645    
646 dpavlin 22 PCIINIT(i31244)
647 dpavlin 20 {
648 dpavlin 22 uint64_t port, memaddr;
649 dpavlin 24 int irq = 0;
650 dpavlin 22
651 dpavlin 20 PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
652 dpavlin 22 PCI_PRODUCT_INTEL_31244));
653    
654     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
655     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x33) + 0x00);
656    
657     switch (machine->machine_type) {
658     case MACHINE_IQ80321:
659 dpavlin 24 /* S-PCI-X slot uses PCI IRQ A, int 29 */
660     irq = (1 << 8) + 29;
661 dpavlin 22 break;
662     default:fatal("i31244 in non-implemented machine type %i\n",
663     machine->machine_type);
664     exit(1);
665     }
666    
667 dpavlin 24 PCI_SET_DATA(PCI_INTERRUPT_REG, 0x01100000 | irq);
668 dpavlin 22
669 dpavlin 24 allocate_device_space(pd, 0x1000, 0, &port, &memaddr);
670     allocate_device_space(pd, 0x1000, 0, &port, &memaddr);
671 dpavlin 22
672     /* PCI IDE using dev_wdc: */
673     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
674     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
675     char tmpstr[150];
676     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
677     (long long)(pd->pcibus->pci_actual_io_offset + 0),
678     pd->pcibus->pci_irqbase + 0);
679     device_add(machine, tmpstr);
680     }
681     }
682    
683     PCIINIT(piix3_isa)
684     {
685     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
686     PCI_PRODUCT_INTEL_82371SB_ISA));
687    
688     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
689     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x01); /* Rev 1 */
690    
691     PCI_SET_DATA(PCI_BHLC_REG,
692     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
693     }
694    
695     PCIINIT(piix4_isa)
696     {
697     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
698 dpavlin 20 PCI_PRODUCT_INTEL_82371AB_ISA));
699    
700     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
701     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x01); /* Rev 1 */
702    
703     PCI_SET_DATA(PCI_BHLC_REG,
704     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
705     }
706    
707     PCIINIT(i82378zb)
708     {
709     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
710     PCI_PRODUCT_INTEL_SIO));
711    
712     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
713     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x43);
714    
715     PCI_SET_DATA(PCI_BHLC_REG,
716     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
717 dpavlin 22
718     PCI_SET_DATA(0x40, 0x20);
719    
720     /* PIRQ[0]=10 PIRQ[1]=11 PIRQ[2]=14 PIRQ[3]=15 */
721     PCI_SET_DATA(0x60, 0x0f0e0b0a);
722 dpavlin 20 }
723    
724 dpavlin 22 PCIINIT(piix3_ide)
725 dpavlin 20 {
726     char tmpstr[100];
727    
728     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
729 dpavlin 22 PCI_PRODUCT_INTEL_82371SB_IDE));
730    
731     /* Possibly not correct: */
732     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
733     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x00) + 0x00);
734    
735     /* PIIX_IDETIM (see NetBSD's pciide_piix_reg.h) */
736     /* channel 0 and 1 enabled as IDE */
737     PCI_SET_DATA(0x40, 0x80008000);
738    
739     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
740     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
741     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
742     (long long)(pd->pcibus->isa_portbase + 0x1f0),
743     pd->pcibus->isa_irqbase + 14);
744     device_add(machine, tmpstr);
745     }
746    
747     if (diskimage_exist(machine, 2, DISKIMAGE_IDE) ||
748     diskimage_exist(machine, 3, DISKIMAGE_IDE)) {
749     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
750     (long long)(pd->pcibus->isa_portbase + 0x170),
751     pd->pcibus->isa_irqbase + 15);
752     device_add(machine, tmpstr);
753     }
754     }
755    
756     PCIINIT(piix4_ide)
757     {
758     char tmpstr[100];
759    
760     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_INTEL,
761 dpavlin 20 PCI_PRODUCT_INTEL_82371AB_IDE));
762    
763     /* Possibly not correct: */
764     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
765     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x00) + 0x01);
766    
767     /* PIIX_IDETIM (see NetBSD's pciide_piix_reg.h) */
768     /* channel 0 and 1 enabled as IDE */
769     PCI_SET_DATA(0x40, 0x80008000);
770    
771     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
772     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
773     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
774     (long long)(pd->pcibus->isa_portbase + 0x1f0),
775     pd->pcibus->isa_irqbase + 14);
776     device_add(machine, tmpstr);
777     }
778    
779     if (diskimage_exist(machine, 2, DISKIMAGE_IDE) ||
780     diskimage_exist(machine, 3, DISKIMAGE_IDE)) {
781     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
782     (long long)(pd->pcibus->isa_portbase + 0x170),
783     pd->pcibus->isa_irqbase + 15);
784     device_add(machine, tmpstr);
785     }
786     }
787    
788    
789    
790     /*
791     * IBM ISA bridge (used by at least one PReP machine).
792     */
793    
794     #define PCI_VENDOR_IBM 0x1014
795     #define PCI_PRODUCT_IBM_ISABRIDGE 0x000a
796    
797     PCIINIT(ibm_isa)
798     {
799     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_IBM,
800     PCI_PRODUCT_IBM_ISABRIDGE));
801    
802     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
803     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x02);
804    
805     PCI_SET_DATA(PCI_BHLC_REG,
806     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
807     }
808    
809    
810    
811     /*
812     * Heuricon PCI host bridge for PM/PPC.
813     */
814    
815     #define PCI_VENDOR_HEURICON 0x1223
816     #define PCI_PRODUCT_HEURICON_PMPPC 0x000e
817    
818     PCIINIT(heuricon_pmppc)
819     {
820     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_HEURICON,
821     PCI_PRODUCT_HEURICON_PMPPC));
822    
823     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
824     PCI_SUBCLASS_BRIDGE_HOST, 0) + 0x00); /* Revision? */
825    
826     PCI_SET_DATA(PCI_BHLC_REG,
827     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
828     }
829    
830    
831    
832     /*
833     * VIATECH VT82C586 devices:
834     *
835     * vt82c586_isa PCI->ISA bridge
836     * vt82c586_ide IDE controller
837     *
838     * TODO: This more or less just a dummy device, so far.
839     */
840    
841     #define PCI_VENDOR_VIATECH 0x1106 /* VIA Technologies */
842     #define PCI_PRODUCT_VIATECH_VT82C586_IDE 0x1571 /* VT82C586 (Apollo VP)
843     IDE Controller */
844     #define PCI_PRODUCT_VIATECH_VT82C586_ISA 0x0586 /* VT82C586 (Apollo VP)
845     PCI-ISA Bridge */
846    
847     PCIINIT(vt82c586_isa)
848     {
849     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_VIATECH,
850     PCI_PRODUCT_VIATECH_VT82C586_ISA));
851    
852     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
853     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x39); /* Revision 37 or 39 */
854    
855     PCI_SET_DATA(PCI_BHLC_REG,
856     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
857     }
858    
859     PCIINIT(vt82c586_ide)
860     {
861     char tmpstr[100];
862    
863     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_VIATECH,
864     PCI_PRODUCT_VIATECH_VT82C586_IDE));
865    
866     /* Possibly not correct: */
867     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
868     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x00) + 0x01);
869    
870     /* APO_IDECONF */
871     /* channel 0 and 1 enabled */
872     PCI_SET_DATA(0x40, 0x00000003);
873    
874     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
875     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
876     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
877     (long long)(pd->pcibus->isa_portbase + 0x1f0),
878     pd->pcibus->isa_irqbase + 14);
879     device_add(machine, tmpstr);
880     }
881    
882     if (diskimage_exist(machine, 2, DISKIMAGE_IDE) ||
883     diskimage_exist(machine, 3, DISKIMAGE_IDE)) {
884     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
885     (long long)(pd->pcibus->isa_portbase + 0x170),
886     pd->pcibus->isa_irqbase + 15);
887     device_add(machine, tmpstr);
888     }
889     }
890    
891    
892    
893     /*
894     * Symphony Labs 83C553 PCI->ISA bridge.
895     * Symphony Labs 82C105 PCIIDE controller.
896     */
897    
898     #define PCI_VENDOR_SYMPHONY 0x10ad
899     #define PCI_PRODUCT_SYMPHONY_83C553 0x0565
900     #define PCI_PRODUCT_SYMPHONY_82C105 0x0105
901    
902     PCIINIT(symphony_83c553)
903     {
904     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_SYMPHONY,
905     PCI_PRODUCT_SYMPHONY_83C553));
906    
907     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
908     PCI_SUBCLASS_BRIDGE_ISA, 0) + 0x10);
909    
910     PCI_SET_DATA(PCI_BHLC_REG,
911     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
912     }
913    
914     PCIINIT(symphony_82c105)
915     {
916     char tmpstr[100];
917    
918     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_SYMPHONY,
919     PCI_PRODUCT_SYMPHONY_82C105));
920    
921     /* Possibly not correct: */
922     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_MASS_STORAGE,
923     PCI_SUBCLASS_MASS_STORAGE_IDE, 0x00) + 0x05);
924    
925     /* APO_IDECONF */
926     /* channel 0 and 1 enabled */
927     PCI_SET_DATA(0x40, 0x00000003);
928    
929     if (diskimage_exist(machine, 0, DISKIMAGE_IDE) ||
930     diskimage_exist(machine, 1, DISKIMAGE_IDE)) {
931     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
932     (long long)(pd->pcibus->isa_portbase + 0x1f0),
933     pd->pcibus->isa_irqbase + 14);
934     device_add(machine, tmpstr);
935     }
936    
937     if (diskimage_exist(machine, 2, DISKIMAGE_IDE) ||
938     diskimage_exist(machine, 3, DISKIMAGE_IDE)) {
939     snprintf(tmpstr, sizeof(tmpstr), "wdc addr=0x%llx irq=%i",
940     (long long)(pd->pcibus->isa_portbase + 0x170),
941     pd->pcibus->isa_irqbase + 15);
942     device_add(machine, tmpstr);
943     }
944     }
945    
946    
947    
948     /*
949     * DEC 21143 ("Tulip") PCI ethernet.
950     */
951    
952     #define PCI_VENDOR_DEC 0x1011 /* Digital Equipment */
953     #define PCI_PRODUCT_DEC_21142 0x0019 /* DECchip 21142/21143 10/100 Ethernet */
954    
955     PCIINIT(dec21143)
956     {
957     uint64_t port, memaddr;
958     int irq = 0; /* TODO */
959 dpavlin 22 int pci_int_line = 0x101;
960 dpavlin 20 char tmpstr[200];
961    
962     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_DEC,
963     PCI_PRODUCT_DEC_21142));
964    
965     PCI_SET_DATA(PCI_COMMAND_STATUS_REG, 0x02000017);
966    
967     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_NETWORK,
968     PCI_SUBCLASS_NETWORK_ETHERNET, 0x00) + 0x41);
969    
970     PCI_SET_DATA(PCI_BHLC_REG, PCI_BHLC_CODE(0,0,0, 0x40,0));
971    
972     switch (machine->machine_type) {
973     case MACHINE_CATS:
974 dpavlin 22 /* CATS int 18 = PCI. */
975 dpavlin 20 irq = 18;
976 dpavlin 22 pci_int_line = 0x101;
977 dpavlin 20 break;
978 dpavlin 22 case MACHINE_COBALT:
979     /* On Cobalt, IRQ 7 = PCI. */
980     irq = 8 + 7;
981     pci_int_line = 0x407;
982     break;
983     case MACHINE_ALGOR:
984     /* TODO */
985     irq = 8 + 7;
986     pci_int_line = 0x407;
987     break;
988 dpavlin 20 case MACHINE_PREP:
989 dpavlin 22 irq = 32 + 10;
990     pci_int_line = 0x20a;
991 dpavlin 20 break;
992 dpavlin 22 case MACHINE_MVMEPPC:
993     /* TODO */
994     irq = 32 + 10;
995     pci_int_line = 0x40a;
996     break;
997 dpavlin 20 case MACHINE_PMPPC:
998 dpavlin 22 /* TODO, not working yet */
999 dpavlin 20 irq = 31 - 21;
1000 dpavlin 22 pci_int_line = 0x201;
1001 dpavlin 20 break;
1002 dpavlin 22 case MACHINE_MACPPC:
1003     /* TODO, not working yet */
1004     irq = 25;
1005     pci_int_line = 0x101;
1006     break;
1007 dpavlin 20 }
1008    
1009 dpavlin 22 PCI_SET_DATA(PCI_INTERRUPT_REG, 0x28140000 | pci_int_line);
1010 dpavlin 20
1011     allocate_device_space(pd, 0x100, 0x100, &port, &memaddr);
1012    
1013     snprintf(tmpstr, sizeof(tmpstr), "dec21143 addr=0x%llx addr2=0x%llx "
1014     "irq=%i pci_little_endian=1", (long long)port, (long long)memaddr,
1015     irq);
1016     device_add(machine, tmpstr);
1017     }
1018    
1019    
1020    
1021     /*
1022     * DEC 21030 "tga" graphics.
1023     */
1024    
1025     #define PCI_PRODUCT_DEC_21030 0x0004 /* DECchip 21030 ("TGA") */
1026    
1027     PCIINIT(dec21030)
1028     {
1029     uint64_t base = 0;
1030     char tmpstr[200];
1031    
1032     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_DEC,
1033     PCI_PRODUCT_DEC_21030));
1034    
1035     PCI_SET_DATA(PCI_COMMAND_STATUS_REG, 0x02800087); /* TODO */
1036    
1037     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_DISPLAY,
1038     PCI_SUBCLASS_DISPLAY_VGA, 0x00) + 0x03);
1039    
1040     /*
1041     * See http://mail-index.netbsd.org/port-arc/2001/08/13/0000.html
1042     * for more info.
1043     */
1044    
1045     PCI_SET_DATA(PCI_BHLC_REG, 0x0000ff00);
1046    
1047     /* 8 = prefetchable */
1048     PCI_SET_DATA(0x10, 0x00000008);
1049     PCI_SET_DATA(0x30, 0x08000001);
1050     PCI_SET_DATA(PCI_INTERRUPT_REG, 0x00000100); /* interrupt pin A? */
1051    
1052     /*
1053     * Experimental:
1054     *
1055     * TODO: Base address, pci_little_endian, ...
1056     */
1057    
1058     switch (machine->machine_type) {
1059     case MACHINE_ARC:
1060     base = 0x100000000ULL;
1061     break;
1062     default:fatal("dec21030 in non-implemented machine type %i\n",
1063     machine->machine_type);
1064     exit(1);
1065     }
1066    
1067     snprintf(tmpstr, sizeof(tmpstr), "dec21030 addr=0x%llx",
1068     (long long)(base));
1069     device_add(machine, tmpstr);
1070     }
1071    
1072    
1073 dpavlin 22
1074 dpavlin 20 /*
1075     * Motorola MPC105 "Eagle" Host Bridge
1076     *
1077     * Used in at least PReP and BeBox.
1078     */
1079    
1080     #define PCI_VENDOR_MOT 0x1057
1081     #define PCI_PRODUCT_MOT_MPC105 0x0001
1082    
1083     PCIINIT(eagle)
1084     {
1085     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_MOT,
1086     PCI_PRODUCT_MOT_MPC105));
1087    
1088     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
1089     PCI_SUBCLASS_BRIDGE_HOST, 0) + 0x24);
1090    
1091     PCI_SET_DATA(PCI_BHLC_REG,
1092     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
1093     }
1094    
1095 dpavlin 22
1096    
1097     /*
1098     * Apple (MacPPC) stuff:
1099     *
1100     * Grand Central (I/O controller)
1101     * Uni-North (PCI controller)
1102     */
1103    
1104     #define PCI_VENDOR_APPLE 0x106b
1105     #define PCI_PRODUCT_APPLE_GC 0x0002
1106     #define PCI_PRODUCT_APPLE_UNINORTH1 0x001e
1107    
1108     PCIINIT(gc_obio)
1109     {
1110     uint64_t port, memaddr;
1111    
1112     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_APPLE,
1113     PCI_PRODUCT_APPLE_GC));
1114    
1115     /* TODO: */
1116     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_SYSTEM,
1117     PCI_SUBCLASS_SYSTEM_PIC, 0) + 0x00);
1118    
1119     PCI_SET_DATA(PCI_BHLC_REG,
1120     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
1121    
1122     /* TODO */
1123     allocate_device_space(pd, 0x10000, 0x10000, &port, &memaddr);
1124     }
1125    
1126     PCIINIT(uninorth)
1127     {
1128     uint64_t port, memaddr;
1129    
1130     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_APPLE,
1131     PCI_PRODUCT_APPLE_UNINORTH1));
1132    
1133     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_BRIDGE,
1134     PCI_SUBCLASS_BRIDGE_HOST, 0) + 0xff);
1135    
1136     PCI_SET_DATA(PCI_BHLC_REG,
1137     PCI_BHLC_CODE(0,0, 1 /* multi-function */, 0x40,0));
1138    
1139     /* TODO */
1140     allocate_device_space(pd, 0x10000, 0x10000, &port, &memaddr);
1141     }
1142    
1143    
1144    
1145     /*
1146     * ATI graphics cards
1147     */
1148    
1149     #define PCI_VENDOR_ATI 0x1002
1150     #define PCI_PRODUCT_ATI_RADEON_9200_2 0x5962
1151    
1152     PCIINIT(ati_radeon_9200_2)
1153     {
1154     uint64_t port, memaddr;
1155    
1156     PCI_SET_DATA(PCI_ID_REG, PCI_ID_CODE(PCI_VENDOR_ATI,
1157     PCI_PRODUCT_ATI_RADEON_9200_2));
1158    
1159     /* TODO: other subclass? */
1160     PCI_SET_DATA(PCI_CLASS_REG, PCI_CLASS_CODE(PCI_CLASS_DISPLAY,
1161     PCI_SUBCLASS_DISPLAY_VGA, 0) + 0x03);
1162    
1163     /* TODO */
1164     allocate_device_space(pd, 0x1000, 0x400000, &port, &memaddr);
1165     }
1166    

  ViewVC Help
Powered by ViewVC 1.1.26