/[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 32 - (hide annotations)
Mon Oct 8 16:20:58 2007 UTC (16 years, 7 months ago) by dpavlin
File MIME type: text/plain
File size: 36312 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.1421 2006/11/06 05:32:37 debug Exp $
20060816	Adding a framework for emulated/virtual timers (src/timer.c),
		using only setitimer().
		Rewriting the mc146818 to use the new timer framework.
20060817	Adding a call to gettimeofday() every now and then (once every
		second, at the moment) to resynch the timer if it drifts.
		Beginning to convert the ISA timer interrupt mechanism (8253
		and 8259) to use the new timer framework.
		Removing the -I command line option.
20060819	Adding the -I command line option again, with new semantics.
		Working on Footbridge timer interrupts; NetBSD/NetWinder and
		NetBSD/CATS now run at correct speed, but unfortunately with
		HUGE delays during bootup.
20060821	Some minor m68k updates. Adding the first instruction: nop. :)
		Minor Alpha emulation updates.
20060822	Adding a FreeBSD development specific YAMON environment
		variable ("khz") (as suggested by Bruce M. Simpson).
		Moving YAMON environment variable initialization from
		machine_evbmips.c into promemul/yamon.c, and adding some more
		variables.
		Continuing on the LCA PCI bus controller (for Alpha machines).
20060823	Continuing on the timer stuff: experimenting with MIPS count/
		compare interrupts connected to the timer framework.
20060825	Adding bogus SCSI commands 0x51 (SCSICDROM_READ_DISCINFO) and
		0x52 (SCSICDROM_READ_TRACKINFO) to the SCSI emulation layer,
		to allow NetBSD/pmax 4.0_BETA to be installed from CDROM.
		Minor updates to the LCA PCI controller.
20060827	Implementing a CHIP8 cpu mode, and a corresponding CHIP8
		machine, for fun. Disassembly support for all instructions,
		and most of the common instructions have been implemented: mvi,
		mov_imm, add_imm, jmp, rand, cls, sprite, skeq_imm, jsr,
		skne_imm, bcd, rts, ldr, str, mov, or, and, xor, add, sub,
		font, ssound, sdelay, gdelay, bogus skup/skpr, skeq, skne.
20060828	Beginning to convert the CHIP8 cpu in the CHIP8 machine to a
		(more correct) RCA 180x cpu. (Disassembly for all 1802
		instructions has been implemented, but no execution yet, and
		no 1805 extended instructions.)
20060829	Minor Alpha emulation updates.
20060830	Beginning to experiment a little with PCI IDE for SGI O2.
		Fixing the cursor key mappings for MobilePro 770 emulation.
		Fixing the LK201 warning caused by recent NetBSD/pmax.
		The MIPS R41xx standby, suspend, and hibernate instructions now
		behave like the RM52xx/MIPS32/MIPS64 wait instruction.
		Fixing dev_wdc so it calculates correct (64-bit) offsets before
		giving them to diskimage_access().
20060831	Continuing on Alpha emulation (OSF1 PALcode).
20060901	Minor Alpha updates; beginning on virtual memory pagetables.
		Removed the limit for max nr of devices (in preparation for
		allowing devices' base addresses to be changed during runtime).
		Adding a hack for MIPS [d]mfc0 select 0 (except the count
		register), so that the coproc register is simply copied.
		The MIPS suspend instruction now exits the emulator, instead
		of being treated as a wait instruction (this causes NetBSD/
		hpcmips to get correct 'halt' behavior).
		The VR41xx RTC now returns correct time.
		Connecting the VR41xx timer to the timer framework (fixed at
		128 Hz, for now).
		Continuing on SPARC emulation, adding more instructions:
		restore, ba_xcc, ble. The rectangle drawing demo works :)
		Removing the last traces of the old ENABLE_CACHE_EMULATION
		MIPS stuff (not usable with dyntrans anyway).
20060902	Splitting up src/net.c into several smaller files in its own
		subdirectory (src/net/).
20060903	Cleanup of the files in src/net/, to make them less ugly.
20060904	Continuing on the 'settings' subsystem.
		Minor progress on the SPARC emulation mode.
20060905	Cleanup of various things, and connecting the settings
		infrastructure to various subsystems (emul, machine, cpu, etc).
		Changing the lk201 mouse update routine to not rely on any
		emulated hardware framebuffer cursor coordinates, but instead
		always do (semi-usable) relative movements.
20060906	Continuing on the lk201 mouse stuff. Mouse behaviour with
		multiple framebuffers (which was working in Ultrix) is now
		semi-broken (but it still works, in a way).
		Moving the documentation about networking into its own file
		(networking.html), and refreshing it a bit. Adding an example
		of how to use ethernet frame direct-access (udp_snoop).
20060907	Continuing on the settings infrastructure.
20060908	Minor updates to SH emulation: for 32-bit emulation: delay
		slots and the 'jsr @Rn' instruction. I'm putting 64-bit SH5 on
		ice, for now.
20060909-10	Implementing some more 32-bit SH instructions. Removing the
		64-bit mode completely. Enough has now been implemented to run
		the rectangle drawing demo. :-)
20060912	Adding more SH instructions.
20060916	Continuing on SH emulation (some more instructions: div0u,
		div1, rotcl/rotcr, more mov instructions, dt, braf, sets, sett,
		tst_imm, dmuls.l, subc, ldc_rm_vbr, movt, clrt, clrs, clrmac).
		Continuing on the settings subsystem (beginning on reading/
		writing settings, removing bugs, and connecting more cpus to
		the framework).
20060919	More work on SH emulation; adding an ldc banked instruction,
		and attaching a 640x480 framebuffer to the Dreamcast machine
		mode (NetBSD/dreamcast prints the NetBSD copyright banner :-),
		and then panics).
20060920	Continuing on the settings subsystem.
20060921	Fixing the Footbridge timer stuff so that NetBSD/cats and
		NetBSD/netwinder boot up without the delays.
20060922	Temporarily hardcoding MIPS timer interrupt to 100 Hz. With
		'wait' support disabled, NetBSD/malta and Linux/malta run at
		correct speed.
20060923	Connecting dev_gt to the timer framework, so that NetBSD/cobalt
		runs at correct speed.
		Moving SH4-specific memory mapped registers into its own
		device (dev_sh4.c).
		Running with -N now prints "idling" instead of bogus nr of
		instrs/second (which isn't valid anyway) while idling.
20060924	Algor emulation should now run at correct speed.
		Adding disassembly support for some MIPS64 revision 2
		instructions: ext, dext, dextm, dextu.
20060926	The timer framework now works also when the MIPS wait
		instruction is used.
20060928	Re-implementing checks for coprocessor availability for MIPS
		cop0 instructions. (Thanks to Carl van Schaik for noticing the
		lack of cop0 availability checks.)
20060929	Implementing an instruction combination hack which treats
		NetBSD/pmax' idle loop as a wait-like instruction.
20060930	The ENTRYHI_R_MASK was missing in (at least) memory_mips_v2p.c,
		causing TLB lookups to sometimes succeed when they should have
		failed. (A big thank you to Juli Mallett for noticing the
		problem.)
		Adding disassembly support for more MIPS64 revision 2 opcodes
		(seb, seh, wsbh, jalr.hb, jr.hb, synci, ins, dins, dinsu,
		dinsm, dsbh, dshd, ror, dror, rorv, drorv, dror32). Also
		implementing seb, seh, dsbh, dshd, and wsbh.
		Implementing an instruction combination hack for Linux/pmax'
		idle loop, similar to the NetBSD/pmax case.
20061001	Changing the NetBSD/sgimips install instructions to extract
		files from an iso image, instead of downloading them via ftp.
20061002	More-than-31-bit userland addresses in memory_mips_v2p.c were
		not actually working; applying a fix from Carl van Schaik to
		enable them to work + making some other updates (adding kuseg
		support).
		Fixing hpcmips (vr41xx) timer initialization.
		Experimenting with O(n)->O(1) reduction in the MIPS TLB lookup
		loop. Seems to work both for R3000 and non-R3000.
20061003	Continuing a little on SH emulation (adding more control
		registers; mini-cleanup of memory_sh.c).
20061004	Beginning on a dev_rtc, a clock/timer device for the test
		machines; also adding a demo, and some documentation.
		Fixing a bug in SH "mov.w @(disp,pc),Rn" (the result wasn't
		sign-extended), and adding the addc and ldtlb instructions.
20061005	Contining on SH emulation: virtual to physical address
		translation, and a skeleton exception mechanism.
20061006	Adding more SH instructions (various loads and stores, rte,
		negc, muls.w, various privileged register-move instructions).
20061007	More SH instructions: various move instructions, trapa, div0s,
		float, fdiv, ftrc.
		Continuing on dev_rtc; removing the rtc demo.
20061008	Adding a dummy Dreamcast PROM module. (Homebrew Dreamcast
		programs using KOS libs need this.)
		Adding more SH instructions: "stc vbr,rn", rotl, rotr, fsca,
		fmul, fadd, various floating-point moves, etc. A 256-byte
		demo for Dreamcast runs :-)
20061012	Adding the SH "lds Rm,pr" and bsr instructions.
20061013	More SH instructions: "sts fpscr,rn", tas.b, and some more
		floating point instructions, cmp/str, and more moves.
		Adding a dummy dev_pvr (Dreamcast graphics controller).
20061014	Generalizing the expression evaluator (used in the built-in
		debugger) to support parentheses and +-*/%^&|.
20061015	Removing the experimental tlb index hint code in
		mips_memory_v2p.c, since it didn't really have any effect.
20061017	Minor SH updates; adding the "sts pr,Rn", fcmp/gt, fneg,
		frchg, and some other instructions. Fixing missing sign-
		extension in an 8-bit load instruction.
20061019	Adding a simple dev_dreamcast_rtc.
		Implementing memory-mapped access to the SH ITLB/UTLB arrays.
20061021	Continuing on various SH and Dreamcast things: sh4 timers,
		debug messages for dev_pvr, fixing some virtual address
		translation bugs, adding the bsrf instruction.
		The NetBSD/dreamcast GENERIC_MD kernel now reaches userland :)
		Adding a dummy dev_dreamcast_asic.c (not really useful yet).
		Implementing simple support for Store Queues.
		Beginning on the PVR Tile Accelerator.
20061022	Generalizing the PVR framebuffer to support off-screen drawing,
		multiple bit-depths, etc. (A small speed penalty, but most
		likely worth it.)
		Adding more SH instructions (mulu.w, fcmp/eq, fsub, fmac,
		fschg, and some more); correcting bugs in "fsca" and "float".
20061024	Adding the SH ftrv (matrix * vector) instruction. Marcus
		Comstedt's "tatest" example runs :) (wireframe only).
		Correcting disassembly for SH floating point instructions that
		use the xd* registers.
		Adding the SH fsts instruction.
		In memory_device_dyntrans_access(), only the currently used
		range is now invalidated, and not the entire device range.
20061025	Adding a dummy AVR32 cpu mode skeleton.
20061026	Various Dreamcast updates; beginning on a Maple bus controller.
20061027	Continuing on the Maple bus. A bogus Controller, Keyboard, and
		Mouse can now be detected by NetBSD and KOS homebrew programs.
		Cleaning up the SH4 Timer Management Unit, and beginning on
		SH4 interrupts.
		Implementing the Dreamcast SYSASIC.
20061028	Continuing on the SYSASIC.
		Adding the SH fsqrt instruction.
		memory_sh.c now actually scans the ITLB.
		Fixing a bug in dev_sh4.c, related to associative writes into
		the memory-mapped UTLB array. NetBSD/dreamcast now reaches
		userland stably, and prints the "Terminal type?" message :-]
		Implementing enough of the Dreamcast keyboard to make NetBSD
		accept it for input.
		Enabling SuperH for stable (non-development) builds.
		Adding NetBSD/dreamcast to the documentation, although it
		doesn't support root-on-nfs yet.
20061029	Changing usleep(1) calls in the debugger to to usleep(10000)
		(according to Brian Foley, this makes GXemul run better on
		MacOS X).
		Making the Maple "Controller" do something (enough to barely
		interact with dcircus.elf).
20061030-31	Some progress on the PVR. More test programs start running (but
		with strange output).
		Various other SH4-related updates.
20061102	Various Dreamcast and SH4 updates; more KOS demos run now.
20061104	Adding a skeleton dev_mb8696x.c (the Dreamcast's LAN adapter).
20061105	Continuing on the MB8696x; NetBSD/dreamcast detects it as mbe0.
		Testing for the release.

==============  RELEASE 0.4.3  ==============


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

  ViewVC Help
Powered by ViewVC 1.1.26