/[gxemul]/trunk/src/cpus/memory_mips.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/cpus/memory_mips.c

Parent Directory Parent Directory | Revision Log Revision Log


Revision 14 - (hide annotations)
Mon Oct 8 16:18:51 2007 UTC (16 years, 6 months ago) by dpavlin
File MIME type: text/plain
File size: 11237 byte(s)
++ trunk/HISTORY	(local)
$Id: HISTORY,v 1.982 2005/10/07 22:45:32 debug Exp $
20050816	Some success in decoding the way the SGI O2 PROM draws graphics
		during bootup; lines/rectangles and bitmaps work, enough to
		show the bootlogo etc. :-)
		Adding more PPC instructions, and (dummy) BAT registers.
20050817	Updating the pckbc to support scancode type 3 keyboards
		(required in order to interact with the SGI O2 PROM).
		Adding more PPC instructions.
20050818	Adding more ARM instructions; general register forms.
		Importing armreg.h from NetBSD (ARM cpu ids). Adding a (dummy)
		CATS machine mode (using SA110 as the default CPU).
		Continuing on general dyntrans related stuff.
20050819	Register forms for ARM load/stores. Gaah! The Compaq C Compiler
		bug is triggered for ARM loads as well, not just PPC :-(
		Adding full support for ARM PC-relative load/stores, and load/
		stores where the PC register is the destination register.
		Adding support for ARM a.out binaries.
20050820	Continuing to add more ARM instructions, and correcting some
		bugs. Continuing on CATS emulation.
		More work on the PPC stuff.
20050821	Minor PPC and ARM updates. Adding more machine types.
20050822	All ARM "data processing instructions" are now generated
		automatically.
20050824	Beginning the work on the ARM system control coprocessor.
		Adding support for ARM halfword load/stores, and signed loads.
20050825	Fixing an important bug related to the ARM condition codes.
		OpenBSD/zaurus and NetBSD/netwinder now print some boot
		messages. :)
		Adding a dummy SH (Hitachi SuperH) cpu family.
		Beginning to add some ARM virtual address translation.
		MIPS bugfixes: unaligned PC now cause an ADEL exception (at
		least for non-bintrans execution), and ADEL/ADES (not
		TLBL/TLBS) are used if userland tries to access kernel space.
		(Thanks to Joshua Wise for making me aware of these bugs.)
20050827	More work on the ARM emulation, and various other updates.
20050828	More ARM updates.
		Finally taking the time to work on translation invalidation
		(i.e. invalidating translated code mappings when memory is
		written to). Hopefully this doesn't break anything.
20050829	Moving CPU related files from src/ to a new subdir, src/cpus/.
		Moving PROM emulation stuff from src/ to src/promemul/.
		Better debug instruction trace for ARM loads and stores.
20050830	Various ARM updates (correcting CMP flag calculation, etc).
20050831	PPC instruction updates. (Flag fixes, etc.)
20050901	Various minor PPC and ARM instruction emulation updates.
		Minor OpenFirmware emulation updates.
20050903	Adding support for adding arbitrary ARM coprocessors (with
		the i80321 I/O coprocessor as a first test).
		Various other ARM and PPC updates.
20050904	Adding some SHcompact disassembly routines.
20050907	(Re)adding a dummy HPPA CPU module, and a dummy i960 module.
20050908	Began hacking on some Apple Partition Table support.
20050909	Adding support for loading Mach-O (Darwin PPC) binaries.
20050910	Fixing an ARM bug (Carry flag was incorrectly updated for some
		data processing instructions); OpenBSD/cats and NetBSD/
		netwinder get quite a bit further now.
		Applying a patch to dev_wdc, and a one-liner to dev_pcic, to
		make them work better when emulating new versions of OpenBSD.
		(Thanks to Alexander Yurchenko for the patches.)
		Also doing some other minor updates to dev_wdc. (Some cleanup,
		and finally converting to devinit, etc.)
20050912	IRIX doesn't have u_int64_t by default (noticed by Andreas
		<avr@gnulinux.nl>); configure updated to reflect this.
		Working on ARM register bank switching, CPSR vs SPSR issues,
		and beginning the work on interrupt/exception support.
20050913	Various minor ARM updates (speeding up load/store multiple,
		and fixing a ROR bug in R(); NetBSD/cats now boots as far as
		OpenBSD/cats).
20050917	Adding a dummy Atmel AVR (8-bit) cpu family skeleton.
20050918	Various minor updates.
20050919	Symbols are now loaded from Mach-O executables.
		Continuing the work on adding ARM exception support.
20050920	More work on ARM stuff: OpenBSD/cats and NetBSD/cats reach
		userland! :-)
20050921	Some more progress on ARM interrupt specifics.
20050923	Fixing linesize for VR4121 (patch by Yurchenko). Also fixing
		linesizes/cachesizes for some other VR4xxx.
		Adding a dummy Acer Labs M1543 PCI-ISA bridge (for CATS) and a
		dummy Symphony Labs 83C553 bridge (for Netwinder), usable by 
		dev_footbridge.
20050924	Some PPC progress.
20050925	More PPC progress.
20050926	PPC progress (fixing some bugs etc); Darwin's kernel gets
		slightly further than before.
20050928	Various updates: footbridge/ISA/pciide stuff, and finally
		fixing the VGA text scroll-by-changing-the-base-offset bug.
20050930	Adding a dummy S3 ViRGE pci card for CATS emulation, which
		both NetBSD and OpenBSD detects as VGA.
		Continuing on Footbridge (timers, ISA interrupt stuff).
20051001	Continuing... there are still bugs, probably interrupt-
		related.
20051002	More work on the Footbridge (interrupt stuff).
20051003	Various minor updates. (Trying to find the bug(s).)
20051004	Continuing on the ARM stuff.
20051005	More ARM-related fixes.
20051007	FINALLY! Found and fixed 2 ARM bugs: 1 memory related, and the
		other was because of an error in the ARM manual (load multiple
		with the S-bit set should _NOT_ load usermode registers, as the
		manual says, but it should load saved registers, which may or
		may not happen to be usermode registers).
		NetBSD/cats and OpenBSD/cats seem to install fine now :-)
		except for a minor bug at the end of the OpenBSD/cats install.
		Updating the documentation, preparing for the next release.
20051008	Continuing with release testing and cleanup.

1 dpavlin 14 /*
2     * Copyright (C) 2003-2005 Anders Gavare. All rights reserved.
3     *
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     * $Id: memory_mips.c,v 1.1 2005/08/29 14:36:42 debug Exp $
29     *
30     * MIPS-specific memory routines. Included from cpu_mips.c.
31     */
32    
33     #include <sys/types.h>
34     #include <sys/mman.h>
35    
36    
37     /*
38     * insert_into_tiny_cache():
39     *
40     * If the tiny cache is enabled (USE_TINY_CACHE), then this routine inserts
41     * a vaddr to paddr translation first in the instruction (or data) tiny
42     * translation cache.
43     */
44     static void insert_into_tiny_cache(struct cpu *cpu, int instr, int writeflag,
45     uint64_t vaddr, uint64_t paddr)
46     {
47     #ifdef USE_TINY_CACHE
48     int wf = 1 + (writeflag == MEM_WRITE);
49    
50     if (cpu->machine->bintrans_enable)
51     return;
52    
53     paddr &= ~0xfff;
54     vaddr >>= 12;
55    
56     if (instr) {
57     /* Code: */
58     memmove(&cpu->cd.mips.translation_cache_instr[1],
59     &cpu->cd.mips.translation_cache_instr[0],
60     sizeof(struct translation_cache_entry) *
61     (N_TRANSLATION_CACHE_INSTR - 1));
62    
63     cpu->cd.mips.translation_cache_instr[0].wf = wf;
64     cpu->cd.mips.translation_cache_instr[0].vaddr_pfn = vaddr;
65     cpu->cd.mips.translation_cache_instr[0].paddr = paddr;
66     } else {
67     /* Data: */
68     memmove(&cpu->cd.mips.translation_cache_data[1],
69     &cpu->cd.mips.translation_cache_data[0],
70     sizeof(struct translation_cache_entry) *
71     (N_TRANSLATION_CACHE_DATA - 1));
72    
73     cpu->cd.mips.translation_cache_data[0].wf = wf;
74     cpu->cd.mips.translation_cache_data[0].vaddr_pfn = vaddr;
75     cpu->cd.mips.translation_cache_data[0].paddr = paddr;
76     }
77     #endif
78     }
79    
80    
81     /*
82     * memory_cache_R3000():
83     *
84     * R2000/R3000 specific cache handling.
85     *
86     * Return value is 1 if a jump to do_return_ok is supposed to happen directly
87     * after this routine is finished, 0 otherwise.
88     */
89     int memory_cache_R3000(struct cpu *cpu, int cache, uint64_t paddr,
90     int writeflag, size_t len, unsigned char *data)
91     {
92     #ifdef ENABLE_CACHE_EMULATION
93     struct r3000_cache_line *rp;
94     int cache_line;
95     uint32_t tag_mask;
96     unsigned char *memblock;
97     struct memory *mem = cpu->mem;
98     int offset;
99     #endif
100     unsigned int i;
101     int cache_isolated = 0, addr, hit, which_cache = cache;
102    
103    
104     if (len > 4 || cache == CACHE_NONE)
105     return 0;
106    
107    
108     #ifdef ENABLE_CACHE_EMULATION
109     if (cpu->cd.mips.coproc[0]->reg[COP0_STATUS] & MIPS1_SWAP_CACHES)
110     which_cache ^= 1;
111    
112     tag_mask = 0xffffffff & ~cpu->cd.mips.cache_mask[which_cache];
113     cache_line = (paddr & cpu->cd.mips.cache_mask[which_cache])
114     / cpu->cd.mips.cache_linesize[which_cache];
115     rp = (struct r3000_cache_line *) cpu->cd.mips.cache_tags[which_cache];
116    
117     /* Is this a cache hit or miss? */
118     hit = (rp[cache_line].tag_valid & R3000_TAG_VALID) &&
119     (rp[cache_line].tag_paddr == (paddr & tag_mask));
120    
121     #ifdef ENABLE_INSTRUCTION_DELAYS
122     if (!hit)
123     cpu->cd.mips.instruction_delay +=
124     cpu->cd.mips.cpu_type.instrs_per_cycle
125     * cpu->cd.mips.cache_miss_penalty[which_cache];
126     #endif
127    
128     /*
129     * The cache miss bit is only set on cache reads, and only to the
130     * data cache. (?)
131     *
132     * (TODO: is this correct? I don't remember where I got this from.)
133     */
134     if (cache == CACHE_DATA && writeflag==MEM_READ) {
135     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] &= ~MIPS1_CACHE_MISS;
136     if (!hit)
137     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] |=
138     MIPS1_CACHE_MISS;
139     }
140    
141     /*
142     * Is the Data cache isolated? Then don't access main memory:
143     */
144     if (cache == CACHE_DATA &&
145     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] & MIPS1_ISOL_CACHES)
146     cache_isolated = 1;
147    
148     addr = paddr & cpu->cd.mips.cache_mask[which_cache];
149    
150     /*
151     * If there was a miss and the cache is not isolated, then flush
152     * the old cacheline back to main memory, and read in the new
153     * cacheline.
154     *
155     * Then access the cache.
156     */
157     /*
158     fatal("L1 CACHE isolated=%i hit=%i write=%i cache=%i cacheline=%i"
159     " paddr=%08x => addr in"
160     " cache = 0x%lx\n", cache_isolated, hit, writeflag,
161     which_cache, cache_line, (int)paddr,
162     addr);
163     */
164     if (!hit && !cache_isolated) {
165     unsigned char *dst, *src;
166     uint64_t old_cached_paddr = rp[cache_line].tag_paddr
167     + cache_line * cpu->cd.mips.cache_linesize[which_cache];
168    
169     /* Flush the old cacheline to main memory: */
170     if ((rp[cache_line].tag_valid & R3000_TAG_VALID) &&
171     (rp[cache_line].tag_valid & R3000_TAG_DIRTY)) {
172     /* fatal(" FLUSHING old tag=0%08x "
173     "old_cached_paddr=0x%08x\n",
174     rp[cache_line].tag_paddr,
175     old_cached_paddr);
176     */
177     memblock = memory_paddr_to_hostaddr(
178     mem, old_cached_paddr, MEM_WRITE);
179     offset = old_cached_paddr
180     & ((1 << BITS_PER_MEMBLOCK) - 1)
181     & ~cpu->cd.mips.cache_mask[which_cache];
182    
183     src = cpu->cd.mips.cache[which_cache];
184     dst = memblock + (offset &
185     ~cpu->cd.mips.cache_mask[which_cache]);
186    
187     src += cache_line *
188     cpu->cd.mips.cache_linesize[which_cache];
189     dst += cache_line *
190     cpu->cd.mips.cache_linesize[which_cache];
191    
192     if (memblock == NULL) {
193     fatal("BUG in memory.c! Hm.\n");
194     } else {
195     memcpy(dst, src,
196     cpu->cd.mips.cache_linesize[which_cache]);
197     }
198     /* offset is the offset within
199     * the memblock:
200     * printf("read: offset = 0x%x\n", offset);
201     */
202     }
203    
204     /* Copy from main memory into the cache: */
205     memblock = memory_paddr_to_hostaddr(mem, paddr, writeflag);
206     offset = paddr & ((1 << BITS_PER_MEMBLOCK) - 1)
207     & ~cpu->cd.mips.cache_mask[which_cache];
208     /* offset is offset within the memblock:
209     * printf("write: offset = 0x%x\n", offset);
210     */
211    
212     /* fatal(" FETCHING new paddr=0%08x\n", paddr);
213     */
214     dst = cpu->cd.mips.cache[which_cache];
215    
216     if (memblock == NULL) {
217     if (writeflag == MEM_READ)
218     memset(dst, 0,
219     cpu->cd.mips.cache_linesize[which_cache]);
220     } else {
221     src = memblock + (offset &
222     ~cpu->cd.mips.cache_mask[which_cache]);
223    
224     src += cache_line *
225     cpu->cd.mips.cache_linesize[which_cache];
226     dst += cache_line *
227     cpu->cd.mips.cache_linesize[which_cache];
228     memcpy(dst, src,
229     cpu->cd.mips.cache_linesize[which_cache]);
230     }
231    
232     rp[cache_line].tag_paddr = paddr & tag_mask;
233     rp[cache_line].tag_valid = R3000_TAG_VALID;
234     }
235    
236     if (cache_isolated && writeflag == MEM_WRITE) {
237     rp[cache_line].tag_valid = 0;
238     }
239    
240     if (writeflag==MEM_READ) {
241     for (i=0; i<len; i++)
242     data[i] = cpu->cd.mips.cache[which_cache][(addr+i) &
243     cpu->cd.mips.cache_mask[which_cache]];
244     } else {
245     for (i=0; i<len; i++) {
246     if (cpu->cd.mips.cache[which_cache][(addr+i) &
247     cpu->cd.mips.cache_mask[which_cache]] != data[i]) {
248     rp[cache_line].tag_valid |= R3000_TAG_DIRTY;
249     }
250     cpu->cd.mips.cache[which_cache][(addr+i) &
251     cpu->cd.mips.cache_mask[which_cache]] = data[i];
252     }
253     }
254    
255     /* Run instructions from the right host page: */
256     if (cache == CACHE_INSTRUCTION) {
257     memblock = memory_paddr_to_hostaddr(mem, paddr, writeflag);
258     if (memblock != NULL) {
259     cpu->cd.mips.pc_last_host_4k_page = memblock +
260     (paddr & ((1 << BITS_PER_MEMBLOCK) - 1) & ~0xfff);
261     }
262     }
263    
264     /* Write-through! (Write to main memory as well.) */
265     if (writeflag == MEM_READ || cache_isolated)
266     return 1;
267    
268     #else
269    
270     /*
271     * R2000/R3000 without correct cache emulation:
272     *
273     * TODO: This is just enough to trick NetBSD/pmax and Ultrix into
274     * being able to detect the cache sizes and think that the caches
275     * are actually working, but they are not.
276     */
277    
278     if (cache != CACHE_DATA)
279     return 0;
280    
281     /* Is this a cache hit or miss? */
282     hit = (cpu->cd.mips.cache_last_paddr[which_cache]
283     & ~cpu->cd.mips.cache_mask[which_cache])
284     == (paddr & ~(cpu->cd.mips.cache_mask[which_cache]));
285    
286     #ifdef ENABLE_INSTRUCTION_DELAYS
287     if (!hit)
288     cpu->cd.mips.instruction_delay +=
289     cpu->cd.mips.cpu_type.instrs_per_cycle
290     * cpu->cd.mips.cache_miss_penalty[which_cache];
291     #endif
292    
293     /*
294     * The cache miss bit is only set on cache reads, and only to the
295     * data cache. (?)
296     *
297     * (TODO: is this correct? I don't remember where I got this from.)
298     */
299     if (cache == CACHE_DATA && writeflag==MEM_READ) {
300     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] &= ~MIPS1_CACHE_MISS;
301     if (!hit)
302     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] |=
303     MIPS1_CACHE_MISS;
304     }
305    
306     /*
307     * Is the Data cache isolated? Then don't access main memory:
308     */
309     if (cache == CACHE_DATA &&
310     cpu->cd.mips.coproc[0]->reg[COP0_STATUS] & MIPS1_ISOL_CACHES)
311     cache_isolated = 1;
312    
313     addr = paddr & cpu->cd.mips.cache_mask[which_cache];
314    
315     /* Data cache isolated? Then don't access main memory: */
316     if (cache_isolated) {
317     /* debug("ISOLATED write=%i cache=%i vaddr=%016llx "
318     "paddr=%016llx => addr in cache = 0x%lx\n",
319     writeflag, cache, (long long)vaddr,
320     (long long)paddr, addr); */
321    
322     if (writeflag==MEM_READ) {
323     for (i=0; i<len; i++)
324     data[i] = cpu->cd.mips.cache[cache][(addr+i) &
325     cpu->cd.mips.cache_mask[cache]];
326     } else {
327     for (i=0; i<len; i++)
328     cpu->cd.mips.cache[cache][(addr+i) &
329     cpu->cd.mips.cache_mask[cache]] = data[i];
330     }
331     return 1;
332     } else {
333     /* Reload caches if necessary: */
334    
335     /* No! Not when not emulating caches fully. (TODO?) */
336     cpu->cd.mips.cache_last_paddr[cache] = paddr;
337     }
338     #endif
339    
340     return 0;
341     }
342    
343    
344     #define TRANSLATE_ADDRESS translate_address_mmu3k
345     #define V2P_MMU3K
346     #include "memory_mips_v2p.c"
347     #undef TRANSLATE_ADDRESS
348     #undef V2P_MMU3K
349    
350     #define TRANSLATE_ADDRESS translate_address_mmu8k
351     #define V2P_MMU8K
352     #include "memory_mips_v2p.c"
353     #undef TRANSLATE_ADDRESS
354     #undef V2P_MMU8K
355    
356     #define TRANSLATE_ADDRESS translate_address_mmu10k
357     #define V2P_MMU10K
358     #include "memory_mips_v2p.c"
359     #undef TRANSLATE_ADDRESS
360     #undef V2P_MMU10K
361    
362     /* Almost generic :-) */
363     #define TRANSLATE_ADDRESS translate_address_mmu4100
364     #define V2P_MMU4100
365     #include "memory_mips_v2p.c"
366     #undef TRANSLATE_ADDRESS
367     #undef V2P_MMU4100
368    
369     #define TRANSLATE_ADDRESS translate_address_generic
370     #include "memory_mips_v2p.c"
371    
372    
373     #define MEMORY_RW mips_memory_rw
374     #define MEM_MIPS
375     #include "../memory_rw.c"
376     #undef MEM_MIPS
377     #undef MEMORY_RW
378    

  ViewVC Help
Powered by ViewVC 1.1.26