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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 24 - (hide annotations)
Mon Oct 8 16:19:56 2007 UTC (16 years, 6 months ago) by dpavlin
File MIME type: text/plain
File size: 54216 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 14 /*
2 dpavlin 22 * Copyright (C) 2005-2006 Anders Gavare. All rights reserved.
3 dpavlin 14 *
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: pc_bios.c,v 1.6 2006/03/30 19:41:51 debug Exp $
29 dpavlin 14 *
30     * Generic PC BIOS emulation.
31     *
32     * See http://hdebruijn.soo.dto.tudelft.nl/newpage/interupt/INT.HTM for
33     * details on what different BIOS interrupts do.
34     *
35     *
36     * The BIOS address space is used as follows:
37     *
38     * 0xf1000 GDT + PD + PTs used for booting in pmode
39     * 0xf8yy0 real mode interrupt handler (int 0xyy)
40     * 0xf9000 SMP tables
41     * 0xfefc7 disk table
42     * 0xff66e 8x8 font (chars 128..255)
43     * 0xffa6e 8x8 font (chars 0..127)
44     * 0xfffd0 System Configuration Parameters (8 bytes)
45     * 0xffff0 Reboot "code".
46     *
47     * TODO: Keep the "BIOS data area" in synch. (Such as keyboard shift state,
48     * disk access, video mode, error codes, x and y charcell resolution...)
49     */
50    
51     #include <stdio.h>
52     #include <stdlib.h>
53     #include <string.h>
54     #include <time.h>
55    
56     #include "cpu.h"
57     #include "misc.h"
58    
59     #ifndef ENABLE_X86
60    
61     /* Don't include PC bios support if we don't have x86 cpu support. */
62     /* These are just do-nothing functions. */
63    
64     void pc_bios_simple_pmode_setup(struct cpu *cpu) { }
65     void pc_bios_init(struct cpu *cpu) { }
66     int pc_bios_emul(struct cpu *cpu) { return 0; }
67    
68    
69     #else
70    
71    
72     #include "console.h"
73     #include "cpu_x86.h"
74     #include "devices.h"
75     #include "diskimage.h"
76     #include "machine.h"
77     #include "memory.h"
78    
79    
80     extern int quiet_mode;
81    
82     extern unsigned char font8x8[];
83    
84     #define dec_to_bcd(x) ( (((x) / 10) << 4) + ((x) % 10) )
85    
86    
87     /*
88     * add_disk():
89     */
90     static struct pc_bios_disk *add_disk(struct machine *machine, int biosnr,
91     int id, int type)
92     {
93     struct pc_bios_disk *p = malloc(sizeof(struct pc_bios_disk));
94    
95     if (p == NULL) {
96     fprintf(stderr, "add_disk(): out of memory\n");
97     exit(1);
98     }
99    
100     p->next = machine->md.pc.first_disk;
101     machine->md.pc.first_disk = p;
102    
103     p->nr = biosnr; p->id = id; p->type = type;
104    
105     p->size = diskimage_getsize(machine, id, type);
106     diskimage_getchs(machine, id, type, &p->cylinders, &p->heads,
107     &p->sectorspertrack);
108    
109     return p;
110     }
111    
112    
113     static struct pc_bios_disk *get_disk(struct machine *machine, int biosnr)
114     {
115     struct pc_bios_disk *p = machine->md.pc.first_disk;
116     while (p != NULL) {
117     if (p->nr == biosnr)
118     break;
119     p = p->next;
120     }
121     return p;
122     }
123    
124    
125     /*
126     * output_char():
127     */
128     static void output_char(struct cpu *cpu, int x, int y, int ch, int color)
129     {
130     uint64_t addr = (y * cpu->machine->md.pc.columns + x) * 2 + 0xb8000;
131     unsigned char w[2];
132     int len = 2;
133    
134     w[0] = ch; w[1] = color;
135     if (color < 0)
136     len = 1;
137    
138     cpu->memory_rw(cpu, cpu->mem, addr, &w[0], len, MEM_WRITE,
139     CACHE_NONE | PHYSICAL);
140     }
141    
142    
143     /*
144     * cmos_write():
145     */
146     static void cmos_write(struct cpu *cpu, int addr, int value)
147     {
148     unsigned char c;
149     c = addr;
150     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x70, &c, 1, MEM_WRITE,
151     CACHE_NONE | PHYSICAL);
152     c = value;
153     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x71, &c, 1, MEM_WRITE,
154     CACHE_NONE | PHYSICAL);
155     }
156    
157    
158     /*
159     * set_cursor_pos():
160     */
161     static void set_cursor_pos(struct cpu *cpu, int x, int y)
162     {
163     int addr = y * cpu->machine->md.pc.columns + x;
164     unsigned char byte;
165     uint64_t ctrlregs = X86_IO_BASE + 0x3c0;
166    
167     byte = 0x0e;
168     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
169     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
170     byte = (addr >> 8) & 255;
171     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
172     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
173     byte = 0x0f;
174     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
175     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
176     byte = addr & 255;
177     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
178     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
179     }
180    
181    
182     /*
183     * set_cursor_scanlines():
184     */
185     static void set_cursor_scanlines(struct cpu *cpu, int start, int end)
186     {
187     unsigned char byte;
188     uint64_t ctrlregs = X86_IO_BASE + 0x3c0;
189    
190     byte = 0x0a;
191     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
192     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
193     byte = start;
194     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
195     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
196     byte = 0x0b;
197     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
198     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
199     byte = end;
200     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
201     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
202     }
203    
204    
205     /*
206     * get_cursor_pos():
207     */
208     static void get_cursor_pos(struct cpu *cpu, int *x, int *y)
209     {
210     int addr;
211     unsigned char byte;
212     uint64_t ctrlregs = X86_IO_BASE + 0x3c0;
213    
214     byte = 0x0e;
215     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
216     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
217     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
218     &byte, sizeof(byte), MEM_READ, CACHE_NONE | PHYSICAL);
219     addr = byte;
220    
221     byte = 0x0f;
222     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
223     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
224     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
225     &byte, sizeof(byte), MEM_READ, CACHE_NONE | PHYSICAL);
226     addr = addr*256 + byte;
227    
228     *x = addr % cpu->machine->md.pc.columns;
229     *y = addr / cpu->machine->md.pc.columns;
230     }
231    
232    
233     /*
234     * set_palette():
235     */
236     static void set_palette(struct cpu *cpu, int n, int r, int g, int b)
237     {
238     unsigned char byte = n;
239     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c8,
240     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
241     byte = r;
242     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
243     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
244     byte = g;
245     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
246     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
247     byte = b;
248     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
249     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
250     }
251    
252    
253     /*
254     * get_palette():
255     */
256     static void get_palette(struct cpu *cpu, int n, unsigned char *rgb)
257     {
258     unsigned char byte = n;
259     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c8,
260     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
261     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
262     &rgb[0], 1, MEM_READ, CACHE_NONE | PHYSICAL);
263     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
264     &rgb[1], 1, MEM_READ, CACHE_NONE | PHYSICAL);
265     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x3c9,
266     &rgb[2], 1, MEM_READ, CACHE_NONE | PHYSICAL);
267     }
268    
269    
270     /*
271     * scroll_up():
272     */
273     static void scroll_up(struct cpu *cpu, int x1, int y1, int x2, int y2, int attr)
274     {
275     int x, y;
276    
277     if (x1 < 0) x1 = 0;
278     if (y1 < 0) y1 = 0;
279     if (x2 >= cpu->machine->md.pc.columns)
280     x2 = cpu->machine->md.pc.columns - 1;
281     if (y2 >= cpu->machine->md.pc.rows)
282     y2 = cpu->machine->md.pc.rows - 1;
283    
284     /* Scroll up by copying lines: */
285     for (y=y1; y<=y2-1; y++) {
286     int addr = (cpu->machine->md.pc.columns*y + x1) * 2 + 0xb8000;
287     int len = (x2-x1+1) * 2;
288     unsigned char w[160];
289     addr += (cpu->machine->md.pc.columns * 2);
290     cpu->memory_rw(cpu, cpu->mem, addr, &w[0], len,
291     MEM_READ, CACHE_NONE | PHYSICAL);
292     addr -= (cpu->machine->md.pc.columns * 2);
293     cpu->memory_rw(cpu, cpu->mem, addr, &w[0], len,
294     MEM_WRITE, CACHE_NONE | PHYSICAL);
295     }
296    
297     /* Clear lowest line: */
298     for (x=x1; x<=x2; x++)
299     output_char(cpu, x, y2, ' ', attr);
300     }
301    
302    
303     /*
304     * scroll_down():
305     */
306     static void scroll_down(struct cpu *cpu, int x1, int y1, int x2, int y2,
307     int attr)
308     {
309     int x, y;
310    
311     if (x1 < 0) x1 = 0;
312     if (y1 < 0) y1 = 0;
313     if (x2 >= cpu->machine->md.pc.columns)
314     x2 = cpu->machine->md.pc.columns - 1;
315     if (y2 >= cpu->machine->md.pc.rows)
316     y2 = cpu->machine->md.pc.rows - 1;
317    
318     /* Scroll down by copying lines: */
319     for (y=y2; y>=y1+1; y--) {
320     int addr = (cpu->machine->md.pc.columns*y + x1) * 2 + 0xb8000;
321     int len = (x2-x1+1) * 2;
322     unsigned char w[160];
323     addr -= cpu->machine->md.pc.columns * 2;
324     cpu->memory_rw(cpu, cpu->mem, addr, &w[0], len,
325     MEM_READ, CACHE_NONE | PHYSICAL);
326     addr += cpu->machine->md.pc.columns * 2;
327     cpu->memory_rw(cpu, cpu->mem, addr, &w[0], len,
328     MEM_WRITE, CACHE_NONE | PHYSICAL);
329     }
330    
331     /* Clear the uppermost line: */
332     for (x=x1; x<=x2; x++)
333     output_char(cpu, x, y1, ' ', attr);
334     }
335    
336    
337     /*
338     * pc_bios_putchar():
339     */
340     static void pc_bios_putchar(struct cpu *cpu, char ch, int attr,
341     int linewrap_and_scroll)
342     {
343     int x, y;
344    
345     get_cursor_pos(cpu, &x, &y);
346    
347     if (!linewrap_and_scroll) {
348     if (x < cpu->machine->md.pc.columns &&
349     y < cpu->machine->md.pc.rows) {
350     output_char(cpu, x, y, ch, attr);
351     x++;
352     set_cursor_pos(cpu, x, y);
353     }
354     return;
355     }
356    
357     /* Put the character on the screen, move cursor, and so on: */
358     switch (ch) {
359     case '\r': x = -1; break;
360     case '\n': x = cpu->machine->md.pc.columns; break;
361     case '\b': x -= 2; break;
362     default: output_char(cpu, x, y, ch, attr);
363     }
364     x++;
365     if (x < 0)
366     x = 0;
367     if (x >= cpu->machine->md.pc.columns) {
368     x=0; y++;
369     }
370    
371     if (attr < 0)
372     attr = cpu->machine->md.pc.curcolor;
373    
374     if (y >= cpu->machine->md.pc.rows) {
375     scroll_up(cpu, 0,0, cpu->machine->md.pc.columns-1,
376     cpu->machine->md.pc.rows-1, attr);
377     x = 0; y = cpu->machine->md.pc.rows - 1;
378     }
379     set_cursor_pos(cpu, x, y);
380     }
381    
382    
383     /*
384     * pc_bios_printstr():
385     */
386     static void pc_bios_printstr(struct cpu *cpu, char *s, int attr)
387     {
388     while (*s)
389     pc_bios_putchar(cpu, *s++, attr, 1);
390     }
391    
392    
393     /*
394     * set_video_mode():
395     */
396     static void set_video_mode(struct cpu *cpu, int al)
397     {
398     uint64_t ctrlregs = X86_IO_BASE + 0x3c0;
399     int x, y, text;
400     unsigned char byte = 0xff;
401    
402     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14, &byte, sizeof(byte),
403     MEM_WRITE, CACHE_NONE | PHYSICAL);
404     byte = al;
405     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15, &byte, sizeof(byte),
406     MEM_WRITE, CACHE_NONE | PHYSICAL);
407    
408     text = 0;
409    
410     switch (al) {
411     case 0x00: /* 40x25 non-color textmode */
412     case 0x01: /* 40x25 color textmode */
413     cpu->machine->md.pc.columns = 40;
414     cpu->machine->md.pc.rows = 25;
415     text = 1;
416     break;
417     case 0x02: /* 80x25 non-color textmode */
418     case 0x03: /* 80x25 color textmode */
419     cpu->machine->md.pc.columns = 80;
420     cpu->machine->md.pc.rows = 25;
421     text = 1;
422     break;
423     case 0x19: /* ? */
424     break;
425     case 0x0d: /* 320x200 x 16 colors graphics */
426     set_cursor_scanlines(cpu, 0x40, 0);
427     break;
428     case 0x12: /* 640x480 x 16 colors graphics */
429     set_cursor_scanlines(cpu, 0x40, 0);
430     break;
431     case 0x13: /* 320x200 x 256 colors graphics */
432     set_cursor_scanlines(cpu, 0x40, 0);
433     break;
434     default:
435     fatal("[ set_video_mode(): unimplemented video mode "
436     "0x%02x ]\n", al);
437     cpu->running = 0;
438     }
439    
440     cpu->machine->md.pc.curcolor = 0x07;
441     cpu->machine->md.pc.videomode = al;
442    
443     if (text) {
444     /* Simply clear the screen and home the cursor
445     for now. TODO: More advanced stuff. */
446     set_cursor_pos(cpu, 0, 0);
447     for (y=0; y<cpu->machine->md.pc.rows; y++)
448     for (x=0; x<cpu->machine->md.pc.columns; x++)
449     output_char(cpu, x,y, ' ',
450     cpu->machine->md.pc.curcolor);
451     }
452     }
453    
454    
455     /*
456     * pc_bios_int8():
457     *
458     * Interrupt handler for the timer.
459     */
460     static int pc_bios_int8(struct cpu *cpu)
461     {
462     unsigned char ticks[4];
463     unsigned char tmpbyte;
464    
465     /* TODO: ack the timer interrupt some other way? */
466     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x43,
467     &tmpbyte, 1, MEM_READ, CACHE_NONE | PHYSICAL);
468    
469     /* EOI the interrupt. */
470     cpu->machine->isa_pic_data.pic1->isr &= ~0x01;
471    
472     /* "Call" INT 0x1C: */
473     /* TODO: how about non-real-mode? */
474     cpu->memory_rw(cpu, cpu->mem, 0x1C * 4,
475     ticks, 4, MEM_READ, CACHE_NONE | PHYSICAL);
476     cpu->pc = ticks[0] + (ticks[1] << 8);
477     reload_segment_descriptor(cpu, X86_S_CS, ticks[2] + (ticks[3] << 8),
478     NULL);
479     return 0;
480     }
481    
482    
483     /*
484     * pc_bios_int9():
485     *
486     * Interrupt handler for the keyboard.
487     */
488     static void pc_bios_int9(struct cpu *cpu)
489     {
490     uint8_t byte;
491    
492     /* Read a key from the keyboard: */
493     cpu->memory_rw(cpu, cpu->mem, X86_IO_BASE + 0x60,
494     &byte, sizeof(byte), MEM_READ, CACHE_NONE | PHYSICAL);
495    
496     /* (The read should have acknowdledged the interrupt.) */
497    
498     /* Add the key to the keyboard buffer: */
499     cpu->machine->md.pc.kbd_buf_scancode[
500     cpu->machine->md.pc.kbd_buf_tail] = byte;
501    
502     /* TODO: The shift state should be located in the BIOS
503     data area. */
504    
505     if (byte == 0x2a) {
506     cpu->machine->md.pc.shift_state |= PC_KBD_SHIFT;
507     byte = 0;
508     }
509     if (byte == 0x1d) {
510     cpu->machine->md.pc.shift_state |= PC_KBD_CTRL;
511     byte = 0;
512     }
513     if (byte == 0x2a + 0x80) {
514     cpu->machine->md.pc.shift_state &= ~PC_KBD_SHIFT;
515     byte = 0;
516     }
517     if (byte == 0x1d + 0x80) {
518     cpu->machine->md.pc.shift_state &= ~PC_KBD_CTRL;
519     byte = 0;
520     }
521    
522     /* Convert scancode into ASCII: */
523     /* (TODO: Maybe this should be somewhere else?) */
524     switch (cpu->machine->md.pc.shift_state) {
525     case 0: if (byte >= 1 && byte <= 0xf)
526     byte = "\0331234567890-=\b\t"[byte-1];
527     else if (byte >= 0x10 && byte <= 0x1b)
528     byte = "qwertyuiop[]"[byte-0x10];
529     else if (byte >= 0x1c && byte <= 0x2b)
530     byte = "\r\000asdfghjkl;'`\000\\"[byte-0x1c];
531     else if (byte >= 0x2c && byte <= 0x35)
532     byte = "zxcvbnm,./"[byte-0x2c];
533     else if (byte >= 0x37 && byte <= 0x39)
534     byte = "*\000 "[byte-0x37];
535     else
536     byte = 0;
537     break;
538     case PC_KBD_SHIFT:
539     if (byte >= 1 && byte <= 0xf)
540     byte = "\033!@#$%^&*()_+\b\t"[byte-1];
541     else if (byte >= 0x10 && byte <= 0x1b)
542     byte = "QWERTYUIOP{}"[byte-0x10];
543     else if (byte >= 0x1c && byte <= 0x2b)
544     byte = "\r\000ASDFGHJKL:\"~\000|"[byte-0x1c];
545     else if (byte >= 0x2c && byte <= 0x35)
546     byte = "ZXCVBNM<>?"[byte-0x2c];
547     else if (byte >= 0x37 && byte <= 0x39)
548     byte = "*\000 "[byte-0x37];
549     else
550     byte = 0;
551     break;
552     default:
553     byte = 0;
554     }
555    
556     cpu->machine->md.pc.kbd_buf[cpu->machine->md.pc.kbd_buf_tail] = byte;
557    
558     cpu->machine->md.pc.kbd_buf_tail ++;
559     cpu->machine->md.pc.kbd_buf_tail %= PC_BIOS_KBD_BUF_SIZE;
560    
561     /* EOI the interrupt. */
562     cpu->machine->isa_pic_data.pic1->isr &= ~0x02;
563     }
564    
565    
566     /*
567     * pc_bios_int10():
568     *
569     * Video functions.
570     */
571     static void pc_bios_int10(struct cpu *cpu)
572     {
573     uint64_t ctrlregs = X86_IO_BASE + 0x3c0;
574     unsigned char byte;
575     unsigned char rgb[3];
576     int x,y, oldx,oldy;
577     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
578     int al = cpu->cd.x86.r[X86_R_AX] & 0xff;
579     int dh = (cpu->cd.x86.r[X86_R_DX] >> 8) & 0xff;
580     int dl = cpu->cd.x86.r[X86_R_DX] & 0xff;
581     int ch = (cpu->cd.x86.r[X86_R_CX] >> 8) & 0xff;
582     int cl = cpu->cd.x86.r[X86_R_CX] & 0xff;
583     int bh = (cpu->cd.x86.r[X86_R_BX] >> 8) & 0xff;
584     int bl = cpu->cd.x86.r[X86_R_BX] & 0xff;
585     int cx = cpu->cd.x86.r[X86_R_CX] & 0xffff;
586     int dx = cpu->cd.x86.r[X86_R_DX] & 0xffff;
587     int bp = cpu->cd.x86.r[X86_R_BP] & 0xffff;
588    
589     switch (ah) {
590     case 0x00: /* Switch video mode. */
591     set_video_mode(cpu, al);
592     break;
593     case 0x01:
594     /* ch = starting line, cl = ending line */
595     /* TODO: it seems that FreeDOS uses start=6 end=7. hm */
596     if (ch == 6 && cl == 7)
597     ch = 12, cl = 14;
598     set_cursor_scanlines(cpu, ch, cl);
599     break;
600     case 0x02: /* set cursor position */
601     set_cursor_pos(cpu, dl, dh);
602     break;
603     case 0x03: /* read cursor position */
604     get_cursor_pos(cpu, &x, &y);
605     cpu->cd.x86.r[X86_R_DX] = (y << 8) + x;
606     /* ch/cl = cursor start end... TODO */
607     cpu->cd.x86.r[X86_R_CX] = 0x000f;
608     break;
609     case 0x05: /* set active display page */
610     if (al != 0)
611     fatal("WARNING: int 0x10, func 0x05, al = 0x%02\n", al);
612     break;
613     case 0x06:
614     if (al < 1)
615     al = 25;
616     while (al-- > 0)
617     scroll_up(cpu, cl, ch, dl, dh, bh);
618     break;
619     case 0x07:
620     if (al < 1)
621     al = 25;
622     while (al-- > 0)
623     scroll_down(cpu, cl, ch, dl, dh, bh);
624     break;
625     case 0x08: /* read char and attr at cur position */
626     /* TODO: return AH=attr, AL=char */
627     break;
628     case 0x09: /* write character and attribute(todo) */
629     case 0x0a: /* write character only */
630     get_cursor_pos(cpu, &oldx, &oldy);
631     while (cx-- > 0)
632     pc_bios_putchar(cpu, al, ah==9? bl : -1, 0);
633     if (ah == 9)
634     cpu->machine->md.pc.curcolor = bl;
635     set_cursor_pos(cpu, oldx, oldy);
636     break;
637     case 0x0b: /* set background palette */
638     fatal("WARNING: int 0x10, func 0x0b: TODO\n");
639     /* cpu->running = 0; */
640     break;
641     case 0x0e: /* tty output */
642     pc_bios_putchar(cpu, al, -1, 1);
643     break;
644     case 0x0f: /* get video mode */
645     cpu->cd.x86.r[X86_R_AX] = cpu->machine->md.pc.columns << 8;
646    
647     byte = 0xff;
648     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x14,
649     &byte, sizeof(byte), MEM_WRITE, CACHE_NONE | PHYSICAL);
650     cpu->memory_rw(cpu, cpu->mem, ctrlregs + 0x15,
651     &byte, sizeof(byte), MEM_READ, CACHE_NONE | PHYSICAL);
652     cpu->cd.x86.r[X86_R_AX] |= byte;
653    
654     cpu->cd.x86.r[X86_R_BX] &= ~0xff00; /* BH = pagenr */
655     break;
656     case 0x10: /* Palette stuff */
657     switch (al) {
658     case 0x00:
659     /* Hm. Is this correct? How about the upper 4
660     bits of bh? TODO */
661     set_palette(cpu, bl,
662     ((bh >> 2) & 1) * 0xaa + (bh&8? 0x55 : 0),
663     ((bh >> 1) & 1) * 0xaa + (bh&8? 0x55 : 0),
664     ((bh >> 0) & 1) * 0xaa + (bh&8? 0x55 : 0));
665     break;
666     case 0x01: /* TODO: Set border color. */
667     fatal("TODO int 10,ah=10,al=01\n");
668     break;
669     case 0x02: /* Set all palette registers. */
670     /* Load from ES:DX */
671     fatal("TODO: int10,10,02\n");
672     break;
673     case 0x03: /* TODO: intensity/blinking bit */
674     debug("TODO int 10,ah=10,al=03\n");
675     break;
676     case 0x10:
677     set_palette(cpu, bl, dh, cl, ch);
678     break;
679     case 0x12: /* Set block of palette registers. */
680     /* Load from ES:DX, BX=start color, CX =
681     nr of registers to load */
682     while (cx-- > 0) {
683     cpu->cd.x86.cursegment = X86_S_ES;
684     cpu->memory_rw(cpu, cpu->mem, dx, rgb, 3,
685     MEM_READ, CACHE_DATA | NO_EXCEPTIONS);
686     set_palette(cpu, bl, rgb[0],rgb[1],rgb[2]);
687     dx += 3;
688     bl ++;
689     }
690     break;
691     case 0x17: /* Read block of palette registers. */
692     /* Load into ES:DX, BX=start color, CX =
693     nr of registers to load */
694     while (cx-- > 0) {
695     get_palette(cpu, bl, rgb);
696     cpu->cd.x86.cursegment = X86_S_ES;
697     cpu->memory_rw(cpu, cpu->mem, dx, rgb, 3,
698     MEM_WRITE, CACHE_DATA | NO_EXCEPTIONS);
699     dx += 3;
700     bl ++;
701     }
702     break;
703     case 0x1a: /* Get DAC State: TODO */
704     cpu->cd.x86.r[X86_R_BX] &= ~0xff;
705     break;
706     default:fatal("Unimplemented INT 0x10,AH=0x10,AL=0x%02x\n", al);
707     cpu->running = 0;
708     }
709     break;
710     case 0x11: /* Character generator */
711     /* TODO */
712     switch (al) {
713     case 0x12:
714     break;
715     case 0x14:
716     break;
717     case 0x30:
718     switch (bh) {
719     case 0x03: /* 8x8 font */
720     cpu->cd.x86.r[X86_R_BP] &= ~0xffff;
721     cpu->cd.x86.r[X86_R_BP] |= 0xfa6e;
722     reload_segment_descriptor(cpu, X86_S_ES,
723     0xf000, NULL);
724     /* TODO: cx and dl, better values? */
725     cpu->cd.x86.r[X86_R_CX] &= ~0xffff;
726     cpu->cd.x86.r[X86_R_CX] |= 16;
727     cpu->cd.x86.r[X86_R_DX] &= ~0xff;
728     cpu->cd.x86.r[X86_R_DX] |= 24;
729     break;
730     default:
731     fatal("[ pc_bios: Get Font: TODO ]\n");
732     }
733     break;
734     default:fatal("Unimplemented INT 0x10,AH=0x11,AL=0x%02x\n", al);
735     cpu->running = 0;
736     }
737     break;
738     case 0x12: /* Video Subsystem Configuration */
739     /* TODO */
740     switch (bl) {
741     case 0x10:
742     cpu->cd.x86.r[X86_R_BX] &= ~0xffff;
743     cpu->cd.x86.r[X86_R_BX] |= 0x0003;
744     break;
745     case 0x30: /* select nr of scanlines (200 + 50*al) */
746     debug("[ pc_bios: %i scanlines ]\n", 200+50*al);
747     cpu->cd.x86.r[X86_R_AX] &= ~0xff;
748     cpu->cd.x86.r[X86_R_AX] |= 0x12;
749     break;
750     case 0x34: /* TODO */
751     break;
752     default:fatal("Unimplemented INT 0x10,AH=0x12,BL=0x%02x\n", bl);
753     cpu->running = 0;
754     }
755     break;
756     case 0x13: /* write string */
757     /* TODO: other flags in al */
758     get_cursor_pos(cpu, &oldx, &oldy);
759     set_cursor_pos(cpu, dl, dh);
760     while (cx-- > 0) {
761     int len = 1;
762     unsigned char byte[2];
763     byte[1] = 0x07;
764     if (al & 2)
765     len = 2;
766     cpu->cd.x86.cursegment = X86_S_ES;
767     cpu->memory_rw(cpu, cpu->mem, bp, &byte[0], len,
768     MEM_READ, CACHE_DATA | NO_EXCEPTIONS);
769     bp += len;
770     pc_bios_putchar(cpu, byte[0], byte[1], 1);
771     cpu->machine->md.pc.curcolor = byte[1];
772     }
773     if (!(al & 1))
774     set_cursor_pos(cpu, oldx, oldy);
775     break;
776     case 0x1a: /* get/set video display combination */
777     if (al != 0) {
778     fatal("FATAL: Unimplemented BIOS int 0x10 function"
779     " 0x%02x, al=0x%02\n", ah, al);
780     cpu->running = 0;
781     }
782     cpu->cd.x86.r[X86_R_AX] &= ~0xff;
783     cpu->cd.x86.r[X86_R_AX] |= 0x1a;
784     cpu->cd.x86.r[X86_R_BX] &= ~0xffff;
785     cpu->cd.x86.r[X86_R_BX] |= 0x0008;
786     break;
787     case 0x1b: /* State Information: TODO */
788     fatal("TODO: int10,1b\n");
789     break;
790     case 0x4f: /* VESA */
791     /* TODO: See http://www.uv.tietgen.dk/staff/mlha/PC/
792     Prog/asm/int/INT10.htm#4F for more info. */
793     switch (al) {
794     case 0x00: /* Detect VESA */
795     #if 0
796     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
797     cpu->cd.x86.r[X86_R_AX] |= 0x004f;
798     /* TODO: the VESA struct at ES:DI */
799     #endif
800     break;
801     case 0x01: /* Return mode info */
802     fatal("TODO: VESA mode 0x%04x\n", cx);
803     break;
804     default:
805     fatal("TODO: int 0x10, function 0x4f, al=0x%02x\n", al);
806     }
807     break;
808     case 0xef: /* Hercules Detection */
809     case 0xfa: /* EGA Register Interface Library */
810     /* TODO: How to accurately return failure? */
811     debug("TODO: int10,ah=0x%02x\n", ah);
812     break;
813     default:
814     fatal("FATAL: Unimplemented PC BIOS interrupt 0x10 function"
815     " 0x%02x.\n", ah);
816     cpu->running = 0;
817     cpu->dead = 1;
818     }
819     }
820    
821    
822     /*
823     * pc_bios_int13():
824     *
825     * Disk-related functions. These usually return CF on error.
826     */
827     static void pc_bios_int13(struct cpu *cpu)
828     {
829     struct pc_bios_disk *disk;
830     int res, nread, err;
831     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
832     int al = (cpu->cd.x86.r[X86_R_AX] >> 0) & 0xff;
833     int dh = (cpu->cd.x86.r[X86_R_DX] >> 8) & 0xff;
834     int dl = (cpu->cd.x86.r[X86_R_DX] >> 0) & 0xff;
835     int ch = (cpu->cd.x86.r[X86_R_CX] >> 8) & 0xff;
836     int cl = (cpu->cd.x86.r[X86_R_CX] >> 0) & 0xff;
837     int bx = cpu->cd.x86.r[X86_R_BX] & 0xffff;
838     uint64_t offset;
839    
840     switch (ah) {
841     case 0x00: /* Reset disk, dl = drive */
842     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
843     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
844     /* Do nothing. :-) */
845     break;
846     case 0x02: /* Read sector */
847     case 0x03: /* Write sector */
848     /*
849     * Read/Write sector(s). al = nr of sectors
850     * dh = head, dl = disk id (0-based),
851     * ch = cyl, cl = 1-based starting sector nr
852     * es:bx = destination buffer; return carryflag = error
853     */
854     cpu->cd.x86.rflags |= X86_FLAGS_CF;
855     disk = get_disk(cpu->machine, cpu->cd.x86.r[X86_R_DX] & 0xff);
856     if (disk != NULL) {
857     unsigned char *buf;
858    
859     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
860     ch = ch + ((cl >> 6) << 8);
861     cl = (cl & 0x3f) - 1;
862     offset = (cl + disk->sectorspertrack * dh +
863     disk->sectorspertrack * disk->heads * ch) * 512;
864     nread = 0; err = 0;
865     debug("[ pc_bios_int13(): reading from disk 0x%x, "
866     "CHS=%i,%i,%i ]\n", dl, ch, dh, cl);
867    
868     buf = malloc(512 * al);
869    
870     if (cl+al > disk->sectorspertrack ||
871     dh >= disk->heads || ch > disk->cylinders) {
872     al = 0; err = 4; /* sector not found */
873     fatal("[ pc_bios: attempt to %s outside the d"
874     "isk? bios id=0x%02x, chs=%i,%i,%i, acces"
875     "s at %i,%i,%i ]\n", ah==2? "read" :
876     "write", dl, disk->cylinders, disk->heads,
877     disk->sectorspertrack, ch, dh, cl);
878     }
879    
880     debug("[ pc_bios_int13(): %s biosdisk 0x%02x (offset="
881 dpavlin 24 "0x%"PRIx64") mem=0x%04x:0x%04x ]\n", ah==2?
882     "read from" : "write to", dl, (uint64_t) offset,
883 dpavlin 14 cpu->cd.x86.s[X86_S_ES], bx);
884    
885     if (ah == 3) {
886     fatal("TODO: bios disk write\n");
887     /* cpu->running = 0; */
888     /* TODO */
889     al = 0;
890     }
891     if (al > 0)
892     res = diskimage_access(cpu->machine, disk->id,
893     disk->type, 0, offset, buf, al * 512);
894     else
895     res = 0;
896     nread = al;
897     if (!res) {
898     err = 4;
899     fatal("[ pc_bios_int13(): FAILED to %s"
900 dpavlin 24 " biosdisk 0x%02x (offset=0x%"PRIx64")"
901 dpavlin 14 " ]\n", ah==2? "read from" :
902 dpavlin 24 "write to", dl, (uint64_t) offset);
903 dpavlin 14 } else if (ah == 2) {
904     cpu->cd.x86.cursegment = X86_S_ES;
905     if (bx + 512*al > 0x10000) {
906     /* DMA overrun */
907     fatal("[ pc_bios: DMA overrun ]\n");
908     err = 9;
909     nread = al = (0x10000 - bx) / 512;
910     }
911     store_buf(cpu, bx, (char *)buf, 512 * al);
912     }
913     free(buf);
914     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
915     cpu->cd.x86.r[X86_R_AX] |= nread;
916     } else
917     err = 0x80;
918     if (err) {
919     cpu->cd.x86.rflags |= X86_FLAGS_CF;
920     cpu->cd.x86.r[X86_R_AX] |= (err << 8);
921     }
922     break;
923     case 4: /* verify disk sectors */
924     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
925     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
926     /* Do nothing. :-) */
927     break;
928     case 8: /* get drive status: TODO */
929     cpu->cd.x86.rflags |= X86_FLAGS_CF;
930     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
931     cpu->cd.x86.r[X86_R_AX] |= 0x8080;
932     disk = get_disk(cpu->machine, cpu->cd.x86.r[X86_R_DX] & 0xff);
933     if (disk != NULL) {
934     int cyl_hi, cyl_lo;
935    
936     cyl_lo = disk->cylinders & 255;
937     cyl_hi = ((disk->cylinders >> 8) & 3) << 6;
938     cyl_hi |= disk->sectorspertrack;
939    
940     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
941     cpu->cd.x86.r[X86_R_BX] &= ~0xffff;
942     if (disk->type == DISKIMAGE_FLOPPY)
943     cpu->cd.x86.r[X86_R_BX] |= 4;
944     cpu->cd.x86.r[X86_R_CX] &= ~0xffff;
945     cpu->cd.x86.r[X86_R_CX] |= (cyl_lo << 8) | cyl_hi;
946     cpu->cd.x86.r[X86_R_DX] &= ~0xffff;
947     cpu->cd.x86.r[X86_R_DX] |= 0x01 |
948     ((disk->heads - 1) << 8);
949     /* TODO: dl = nr of drives */
950     /* TODO: es:di? */
951     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
952     }
953     break;
954     case 0x15: /* Read DASD Type */
955     /* TODO: generalize */
956     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
957     cpu->cd.x86.r[X86_R_AX] |= 0x0100;
958     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
959     break;
960     case 0x41: /* Check for Extended Functions */
961     /* There is no such support. :) */
962     cpu->cd.x86.rflags |= X86_FLAGS_CF;
963     break;
964     case 0x42: /* Extended Read: */
965     /* TODO */
966     cpu->cd.x86.rflags |= X86_FLAGS_CF;
967     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
968     cpu->cd.x86.r[X86_R_AX] |= 0x0100;
969     break;
970     case 0x48: /* ? */
971     /* TODO */
972     cpu->cd.x86.rflags |= X86_FLAGS_CF;
973     break;
974     case 0x4b: /* CDROM emulation (TODO) */
975     cpu->cd.x86.rflags |= X86_FLAGS_CF;
976     break;
977     case 0xfa: /* ? */
978     cpu->cd.x86.rflags |= X86_FLAGS_CF;
979     break;
980     default:
981     fatal("FATAL: Unimplemented PC BIOS interrupt 0x13 function"
982     " 0x%02x.\n", ah);
983     cpu->running = 0;
984     cpu->dead = 1;
985     }
986     }
987    
988    
989     /*
990     * pc_bios_int14():
991     *
992     * Serial port stuff.
993     */
994     static void pc_bios_int14(struct cpu *cpu)
995     {
996     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
997    
998     switch (ah) {
999     case 0: debug("[ pc_bios_14(): TODO ]\n");
1000     break;
1001     default:
1002     fatal("FATAL: Unimplemented PC BIOS interrupt 0x14 function"
1003     " 0x%02x.\n", ah);
1004     cpu->running = 0;
1005     cpu->dead = 1;
1006     }
1007     }
1008    
1009    
1010     /*
1011     * pc_bios_int15():
1012     */
1013     static void pc_bios_int15(struct cpu *cpu)
1014     {
1015     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
1016     int al = cpu->cd.x86.r[X86_R_AX] & 0xff;
1017     int cx = cpu->cd.x86.r[X86_R_CX] & 0xffff;
1018     int si = cpu->cd.x86.r[X86_R_SI] & 0xffff;
1019     int m;
1020     unsigned char src_entry[8];
1021     unsigned char dst_entry[8];
1022     uint32_t src_addr, dst_addr;
1023    
1024     switch (ah) {
1025     case 0x00: /* TODO? */
1026     fatal("[ PC BIOS int 0x15,0x00: TODO ]\n");
1027     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1028     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1029     cpu->cd.x86.r[X86_R_AX] |= 0x8600; /* TODO */
1030     break;
1031     case 0x06: /* TODO */
1032     fatal("[ PC BIOS int 0x15,0x06: TODO ]\n");
1033     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1034     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1035     cpu->cd.x86.r[X86_R_AX] |= 0x8600; /* TODO */
1036     break;
1037     case 0x24: /* TODO */
1038     fatal("[ PC BIOS int 0x15,0x24: TODO ]\n");
1039     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1040     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1041     cpu->cd.x86.r[X86_R_AX] |= 0x8600; /* TODO */
1042     break;
1043     case 0x41: /* TODO */
1044     fatal("[ PC BIOS int 0x15,0x41: TODO ]\n");
1045     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1046     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1047     cpu->cd.x86.r[X86_R_AX] |= 0x8600; /* TODO */
1048     break;
1049     case 0x4f: /* Keyboard Scancode Intercept (TODO) */
1050     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1051     break;
1052     case 0x53: /* TODO */
1053     fatal("[ PC BIOS int 0x15,0x53: TODO ]\n");
1054     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1055     break;
1056     case 0x86: /* Wait */
1057     /* No. :-) */
1058     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1059     break;
1060     case 0x87: /* Move to/from extended memory, via a GDT */
1061     cpu->cd.x86.cursegment = X86_S_ES;
1062     cpu->memory_rw(cpu, cpu->mem, si + 0x10, src_entry, 8,
1063     MEM_READ, CACHE_DATA);
1064     cpu->memory_rw(cpu, cpu->mem, si + 0x18, dst_entry, 8,
1065     MEM_READ, CACHE_DATA);
1066     src_addr = src_entry[2]+(src_entry[3]<<8)+(src_entry[4]<<16);
1067     dst_addr = dst_entry[2]+(dst_entry[3]<<8)+(dst_entry[4]<<16);
1068     if (src_entry[5] != 0x92 && src_entry[5] != 0x93)
1069     fatal("WARNING: int15,87: bad src access right?"
1070     " (0x%02x, should be 0x93)\n", src_entry[5]);
1071     if (dst_entry[5] != 0x92 && dst_entry[5] != 0x93)
1072     fatal("WARNING: int15,87: bad dst access right?"
1073     " (0x%02x, should be 0x93)\n", dst_entry[5]);
1074     debug("[ pc_bios: INT15: copying %i bytes from 0x%x to 0x%x"
1075     " ]\n", cx*2, src_addr, dst_addr);
1076     if (cx > 0x8000)
1077     fatal("WARNING! INT15 func 0x87 cx=0x%04x, max allowed"
1078     " is supposed to be 0x8000!\n", cx);
1079     while (cx*2 > 0) {
1080     unsigned char buf[2];
1081     cpu->memory_rw(cpu, cpu->mem, src_addr, buf, 2,
1082     MEM_READ, NO_SEGMENTATION | CACHE_DATA);
1083     cpu->memory_rw(cpu, cpu->mem, dst_addr, buf, 2,
1084     MEM_WRITE, NO_SEGMENTATION | CACHE_DATA);
1085     src_addr += 2; dst_addr += 2; cx --;
1086     }
1087     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1088     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1089     cpu->cd.x86.rflags |= X86_FLAGS_ZF;
1090     break;
1091     case 0x88: /* Extended Memory Size Determination */
1092     /* TODO: Max 16 or 64 MB? */
1093     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1094     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
1095     if (cpu->machine->physical_ram_in_mb <= 64)
1096     cpu->cd.x86.r[X86_R_AX] |= (cpu->machine->
1097     physical_ram_in_mb - 1) * 1024;
1098     else
1099     cpu->cd.x86.r[X86_R_AX] |= 63*1024;
1100     break;
1101     case 0x8A: /* Get "Big" memory size */
1102     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1103     m = (cpu->machine->physical_ram_in_mb - 1) * 1024;
1104     cpu->cd.x86.r[X86_R_DX] &= ~0xffff;
1105     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
1106     cpu->cd.x86.r[X86_R_DX] |= ((m >> 16) & 0xffff);
1107     cpu->cd.x86.r[X86_R_AX] |= (m & 0xffff);
1108     break;
1109     case 0x91: /* Interrupt Complete (bogus) */
1110     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1111     break;
1112     case 0xc0: /* System Config: (at 0xfffd:0) */
1113     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1114     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1115     cpu->cd.x86.r[X86_R_BX] &= ~0xffff;
1116     cpu->cd.x86.s[X86_S_ES] = 0xfffd;
1117     reload_segment_descriptor(cpu, X86_S_ES, 0xfffd, NULL);
1118     break;
1119     case 0xc1: /* Extended Bios Data-seg (TODO) */
1120     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1121     break;
1122     case 0xe8: /* TODO */
1123     switch (al) {
1124     case 0x01:
1125     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1126     m = cpu->machine->physical_ram_in_mb;
1127     if (m > 16)
1128     m = 16;
1129     m = (m - 1) * 1024;
1130     /* between 1MB and 16MB: (1KB blocks) */
1131     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
1132     cpu->cd.x86.r[X86_R_AX] |= (m & 0xffff);
1133     /* mem above 16MB, 64K blocks: */
1134     m = cpu->machine->physical_ram_in_mb;
1135     if (m < 16)
1136     m = 0;
1137     else
1138     m = (m-16) / 16;
1139     cpu->cd.x86.r[X86_R_BX] &= ~0xffff;
1140     cpu->cd.x86.r[X86_R_BX] |= (m & 0xffff);
1141     /* CX and DX are "configured" memory */
1142     cpu->cd.x86.r[X86_R_CX] &= ~0xffff;
1143     cpu->cd.x86.r[X86_R_DX] &= ~0xffff;
1144     cpu->cd.x86.r[X86_R_CX] |= (
1145     cpu->cd.x86.r[X86_R_AX] & 0xffff);
1146     cpu->cd.x86.r[X86_R_DX] |= (
1147     cpu->cd.x86.r[X86_R_BX] & 0xffff);
1148     break;
1149     case 0x20: /* Get memory map: TODO */
1150     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1151     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1152     cpu->cd.x86.r[X86_R_AX] |= 0x8600;
1153     break;
1154     default:fatal("[ PC BIOS int 0x15,0xe8: al=0x%02x "
1155     " TODO ]\n", al);
1156     cpu->running = 0;
1157     }
1158     break;
1159     default:
1160     fatal("FATAL: Unimplemented PC BIOS interrupt 0x15 function"
1161     " 0x%02x.\n", ah);
1162     cpu->running = 0;
1163     cpu->dead = 1;
1164     }
1165     }
1166    
1167    
1168     /*
1169     * pc_bios_int16():
1170     *
1171     * Keyboard-related functions.
1172     */
1173     static int pc_bios_int16(struct cpu *cpu, int *enable_ints_after_returnp)
1174     {
1175     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
1176     /* int al = cpu->cd.x86.r[X86_R_AX] & 0xff; */
1177     int scancode, asciicode;
1178     unsigned char tmpchar;
1179    
1180     switch (ah) {
1181     case 0x00: /* getchar */
1182     scancode = asciicode = 0;
1183     if (cpu->machine->md.pc.kbd_buf_head !=
1184     cpu->machine->md.pc.kbd_buf_tail) {
1185     asciicode = cpu->machine->md.pc.kbd_buf[
1186     cpu->machine->md.pc.kbd_buf_head];
1187     scancode = cpu->machine->md.pc.kbd_buf_scancode[
1188     cpu->machine->md.pc.kbd_buf_head];
1189     if (asciicode != 0) {
1190     cpu->cd.x86.r[X86_R_AX] =
1191     (scancode << 8) | asciicode;
1192     }
1193     cpu->machine->md.pc.kbd_buf_head ++;
1194     cpu->machine->md.pc.kbd_buf_head %=
1195     PC_BIOS_KBD_BUF_SIZE;
1196     }
1197     *enable_ints_after_returnp = 1;
1198     if (asciicode == 0)
1199     return 0;
1200     break;
1201     case 0x01: /* non-destructive "isavail" */
1202     cpu->cd.x86.rflags |= X86_FLAGS_ZF;
1203     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
1204     scancode = asciicode = 0;
1205     if (cpu->machine->md.pc.kbd_buf_head !=
1206     cpu->machine->md.pc.kbd_buf_tail) {
1207     asciicode = cpu->machine->md.pc.kbd_buf[
1208     cpu->machine->md.pc.kbd_buf_head];
1209     scancode = cpu->machine->md.pc.kbd_buf_scancode[
1210     cpu->machine->md.pc.kbd_buf_head];
1211     cpu->cd.x86.rflags &= ~X86_FLAGS_ZF;
1212     cpu->cd.x86.r[X86_R_AX] |= (scancode << 8) | asciicode;
1213     }
1214     *enable_ints_after_returnp = 1;
1215     break;
1216     case 0x02: /* read keyboard flags */
1217     /* TODO: keep this byte updated */
1218     cpu->memory_rw(cpu, cpu->mem, 0x417, &tmpchar, 1,
1219     MEM_READ, PHYSICAL);
1220     cpu->cd.x86.r[X86_R_AX] = (cpu->cd.x86.r[X86_R_AX] & ~0xff)
1221     | tmpchar;
1222     break;
1223     case 0x03: /* Set Keyboard Typematic Rate: TODO */
1224     break;
1225     case 0x55: /* Microsoft stuff: Ignore :-) */
1226     break;
1227     case 0x92: /* Keyboard "Capabilities Check": TODO */
1228     break;
1229     default:
1230     fatal("FATAL: Unimplemented PC BIOS interrupt 0x16 function"
1231     " 0x%02x.\n", ah);
1232     cpu->running = 0;
1233     cpu->dead = 1;
1234     }
1235    
1236     return 1;
1237     }
1238    
1239    
1240     /*
1241     * pc_bios_int17():
1242     *
1243     * Printer port stuff.
1244     */
1245     static void pc_bios_int17(struct cpu *cpu)
1246     {
1247     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
1248    
1249     switch (ah) {
1250     case 0x01:
1251     debug("[ PC BIOS int 0x17,0x01: TODO ]\n");
1252     cpu->cd.x86.r[X86_R_AX] &= ~0xff00;
1253     break;
1254     default:
1255     fatal("FATAL: Unimplemented PC BIOS interrupt 0x17 function"
1256     " 0x%02x.\n", ah);
1257     cpu->running = 0;
1258     cpu->dead = 1;
1259     }
1260     }
1261    
1262    
1263     /*
1264     * pc_bios_int1a():
1265     *
1266     * Time of Day stuff.
1267     */
1268     static void pc_bios_int1a(struct cpu *cpu)
1269     {
1270     unsigned char ticks[4];
1271     int ah = (cpu->cd.x86.r[X86_R_AX] >> 8) & 0xff;
1272     time_t tim;
1273     struct tm *tm;
1274    
1275     switch (ah) {
1276     case 0x00: /* Read tick count. */
1277     cpu->memory_rw(cpu, cpu->mem, 0x46C,
1278     ticks, sizeof(ticks), MEM_READ, CACHE_NONE | PHYSICAL);
1279     cpu->cd.x86.r[X86_R_CX] = (ticks[3] << 8) | ticks[2];
1280     cpu->cd.x86.r[X86_R_DX] = (ticks[1] << 8) | ticks[0];
1281     break;
1282     case 0x01: /* Set tick count. */
1283     ticks[0] = cpu->cd.x86.r[X86_R_DX];
1284     ticks[1] = cpu->cd.x86.r[X86_R_DX] >> 8;
1285     ticks[2] = cpu->cd.x86.r[X86_R_CX];
1286     ticks[3] = cpu->cd.x86.r[X86_R_CX] >> 8;
1287     cpu->memory_rw(cpu, cpu->mem, 0x46C,
1288     ticks, sizeof(ticks), MEM_WRITE, CACHE_NONE | PHYSICAL);
1289     break;
1290     case 0x02: /* Read real time clock time (AT,PS/2) */
1291     tim = time(NULL);
1292     tm = gmtime(&tim);
1293     cpu->cd.x86.r[X86_R_CX] &= ~0xffff;
1294     cpu->cd.x86.r[X86_R_DX] &= ~0xffff;
1295     cpu->cd.x86.r[X86_R_CX] |= (dec_to_bcd(tm->tm_hour) << 8) |
1296     dec_to_bcd(tm->tm_min);
1297     cpu->cd.x86.r[X86_R_DX] |= dec_to_bcd(tm->tm_sec) << 8;
1298     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1299     break;
1300     case 0x04: /* Read real time clock date (AT,PS/2) */
1301     tim = time(NULL);
1302     tm = gmtime(&tim);
1303     cpu->cd.x86.r[X86_R_CX] &= ~0xffff;
1304     cpu->cd.x86.r[X86_R_DX] &= ~0xffff;
1305     cpu->cd.x86.r[X86_R_CX] |=
1306     (dec_to_bcd((tm->tm_year+1900)/100) << 8) |
1307     dec_to_bcd(tm->tm_year % 100);
1308     cpu->cd.x86.r[X86_R_DX] |= (dec_to_bcd(tm->tm_mon+1) << 8) |
1309     dec_to_bcd(tm->tm_mday);
1310     cpu->cd.x86.rflags &= ~X86_FLAGS_CF;
1311     break;
1312     case 0xb1: /* Intel PCI Bios */
1313     /* ... not installed :) */
1314     cpu->cd.x86.rflags |= X86_FLAGS_CF;
1315     break;
1316     default:
1317     fatal("FATAL: Unimplemented PC BIOS interrupt 0x1a function"
1318     " 0x%02x.\n", ah);
1319     cpu->running = 0;
1320     cpu->dead = 1;
1321     }
1322     }
1323    
1324    
1325     /*
1326     * pc_bios_int1c():
1327     *
1328     * Increase the timer-tick word at 0x40:0x6C.
1329     */
1330     static void pc_bios_int1c(struct cpu *cpu)
1331     {
1332     unsigned char ticks[4];
1333 dpavlin 22 size_t i;
1334 dpavlin 14
1335     /* Increase word at 0x0040:0x006C */
1336     cpu->memory_rw(cpu, cpu->mem, 0x46C,
1337     ticks, sizeof(ticks), MEM_READ, CACHE_NONE | PHYSICAL);
1338     for (i=0; i<sizeof(ticks); i++) {
1339     ticks[i] ++;
1340     if (ticks[i] != 0)
1341     break;
1342     }
1343     cpu->memory_rw(cpu, cpu->mem, 0x46C,
1344     ticks, sizeof(ticks), MEM_WRITE, CACHE_NONE | PHYSICAL);
1345     }
1346    
1347    
1348     /*
1349     * pc_bios_smp_init():
1350     *
1351     * Initialize the "_MP_" struct in BIOS memory.
1352     *
1353     * TODO: Don't use hardcoded values like this.
1354     */
1355     void pc_bios_smp_init(struct cpu *cpu)
1356     {
1357     int i, chksum;
1358    
1359     reload_segment_descriptor(cpu, X86_S_FS, 0xf000, NULL);
1360     store_buf(cpu, 0x9000, "_MP_", 4);
1361     store_byte(cpu, 0x9004, 0x10); /* ptr to table */
1362     store_byte(cpu, 0x9005, 0x90);
1363     store_byte(cpu, 0x9006, 0x0f);
1364     store_byte(cpu, 0x9007, 0x00);
1365     store_byte(cpu, 0x9008, 0x01); /* length. should be 1 */
1366     store_byte(cpu, 0x9009, 0x04); /* version. 4 means "1.4" */
1367     /* Byte at 0x0a is checksum. TODO: make this automagic */
1368     chksum = '_' + 'M' + 'P' + '_' + 0x10 + 0x90 + 0xf + 1 + 4;
1369     store_byte(cpu, 0x900a, 0 - chksum);
1370    
1371     /* PCMP struct, at addr 0x9010. */
1372     store_buf(cpu, 0x9010, "PCMP", 4);
1373     store_16bit_word(cpu, 0x9014, 43);
1374     store_byte(cpu, 0x9016, 4); /* rev 1.4 */
1375     /* 9017 is checksum */
1376     store_buf(cpu, 0x9018, "GXemul ", 8);
1377     store_buf(cpu, 0x9020, "SMP ", 12);
1378    
1379     /* Nr of entries (one per cpu): */
1380     store_16bit_word(cpu, 0x9010 + 34, cpu->machine->ncpus);
1381    
1382     if (cpu->machine->ncpus > 16)
1383     fatal("WARNING: More than 16 CPUs?\n");
1384    
1385     for (i=0; i<cpu->machine->ncpus; i++) {
1386     int ofs = 44 + 20*i;
1387     /* 20 bytes per CPU: */
1388     store_byte(cpu, 0x9010 + ofs + 0, 0x00); /* cpu */
1389     store_byte(cpu, 0x9010 + ofs + 1, i); /* id */
1390     store_byte(cpu, 0x9010 + ofs + 3, 1 | /* enable */
1391     ((i == cpu->machine->bootstrap_cpu)? 2 : 0));
1392     }
1393     }
1394    
1395    
1396     /*
1397     * pc_bios_simple_pmode_setup():
1398     *
1399     * This function is called from emul.c before loading a 32-bit or 64-bit ELF.
1400     * Loading ELFs when the emulation is set to 16-bit real mode is not a good
1401     * thing, so this function sets up a simple GDT which maps every 0xZyyyyyyy
1402     * to 0x0yyyyyyy.
1403     *
1404     * 0xf4000 GDT:
1405     * 00 = NULL
1406     * 08 = code
1407     * 10 = data
1408     */
1409     void pc_bios_simple_pmode_setup(struct cpu *cpu)
1410     {
1411     int i, j, addr = 0, npts;
1412     uint32_t pt_base;
1413     cpu->cd.x86.cursegment = X86_S_FS;
1414     reload_segment_descriptor(cpu, X86_S_FS, 0xf100, NULL);
1415    
1416     /* 0x00 = NULL descriptor. */
1417     addr += 8;
1418    
1419     /* 0x08 = Code descriptor. */
1420     store_byte(cpu, addr + 0, 0xff);
1421     store_byte(cpu, addr + 1, 0xff);
1422     store_byte(cpu, addr + 2, 0x00);
1423     store_byte(cpu, addr + 3, 0x00);
1424     store_byte(cpu, addr + 4, 0x00);
1425     store_byte(cpu, addr + 5, 0x9f);
1426     store_byte(cpu, addr + 6, 0xcf);
1427     store_byte(cpu, addr + 7, 0x00);
1428     addr += 8;
1429    
1430     /* 0x10 = Data descriptor. */
1431     store_byte(cpu, addr + 0, 0xff);
1432     store_byte(cpu, addr + 1, 0xff);
1433     store_byte(cpu, addr + 2, 0x00);
1434     store_byte(cpu, addr + 3, 0x00);
1435     store_byte(cpu, addr + 4, 0x00);
1436     store_byte(cpu, addr + 5, 0x93);
1437     store_byte(cpu, addr + 6, 0xcf);
1438     store_byte(cpu, addr + 7, 0x00);
1439     addr += 8;
1440    
1441     cpu->cd.x86.gdtr = 0xf1000;
1442     cpu->cd.x86.gdtr_limit = 0xfff;
1443    
1444     addr = 0x1000;
1445     cpu->cd.x86.cr[3] = 0xf2000;
1446    
1447     npts = 4;
1448     pt_base = 0xf3000; /* 0xf3000, f4000, f5000, f6000 */
1449    
1450     /* Set up the page directory: */
1451     for (i=0; i<1024; i++) {
1452     uint32_t pde = pt_base + 0x03 + ((i & (npts-1)) << 12);
1453     store_32bit_word(cpu, addr + i*4, pde);
1454     }
1455     addr += 4096;
1456    
1457     /* Set up the page tables: */
1458     for (i=0; i<npts; i++) {
1459     for (j=0; j<1024; j++) {
1460     uint32_t pte = (i << 22) + (j << 12) + 0x03;
1461     store_32bit_word(cpu, addr + j*4, pte);
1462     }
1463     addr += 4096;
1464     }
1465    
1466     cpu->cd.x86.cr[0] |= X86_CR0_PE | X86_CR0_PG;
1467    
1468     /* Interrupts are dangerous when we start in pmode! */
1469     cpu->cd.x86.rflags &= ~X86_FLAGS_IF;
1470    
1471     reload_segment_descriptor(cpu, X86_S_CS, 0x08, NULL);
1472     reload_segment_descriptor(cpu, X86_S_DS, 0x10, NULL);
1473     reload_segment_descriptor(cpu, X86_S_ES, 0x10, NULL);
1474     reload_segment_descriptor(cpu, X86_S_SS, 0x10, NULL);
1475     cpu->cd.x86.r[X86_R_SP] = 0x7000;
1476     cpu->cd.x86.cursegment = X86_S_DS;
1477     }
1478    
1479    
1480     /*
1481     * pc_bios_init():
1482     */
1483     void pc_bios_init(struct cpu *cpu)
1484     {
1485     char t[81];
1486     int x, y, nboxlines, i, any_disk = 0, disknr, tmp;
1487 dpavlin 20 int old_cursegment = cpu->cd.x86.cursegment;
1488 dpavlin 14 int boot_id, boot_type, bios_boot_id = 0, nfloppies = 0, nhds = 0;
1489    
1490     /* Go to real mode: */
1491     cpu->cd.x86.cr[0] &= ~X86_CR0_PE;
1492    
1493     boot_id = diskimage_bootdev(cpu->machine, &boot_type);
1494    
1495     if (cpu->machine->md.pc.initialized) {
1496     fatal("ERROR: pc_bios_init(): Already initialized.\n");
1497     return;
1498     }
1499    
1500     if (cpu->machine->isa_pic_data.pic1 == NULL) {
1501     fatal("ERROR: No interrupt controller?\n");
1502     exit(1);
1503     } else
1504     cpu->machine->isa_pic_data.pic1->irq_base = 0x08;
1505    
1506     /* pic2 can be NULL when emulating an original XT: */
1507     if (cpu->machine->isa_pic_data.pic2 != NULL)
1508     cpu->machine->isa_pic_data.pic2->irq_base = 0x70;
1509    
1510     /* Disk Base Table (11 or 12 bytes?) at F000h:EFC7: */
1511     cpu->cd.x86.cursegment = X86_S_FS;
1512     reload_segment_descriptor(cpu, X86_S_FS, 0xf000, NULL);
1513     store_byte(cpu, 0xefc7 + 0, 0xcf);
1514     store_byte(cpu, 0xefc7 + 1, 0xb8);
1515     store_byte(cpu, 0xefc7 + 2, 1); /* timer ticks till shutoff */
1516     store_byte(cpu, 0xefc7 + 3, 2); /* 512 bytes per sector */
1517     store_byte(cpu, 0xefc7 + 4, 17);
1518     store_byte(cpu, 0xefc7 + 5, 0xd8);
1519     store_byte(cpu, 0xefc7 + 6, 0xff);
1520     store_byte(cpu, 0xefc7 + 7, 0);
1521     store_byte(cpu, 0xefc7 + 8, 0xf6);
1522     store_byte(cpu, 0xefc7 + 9, 1); /* head bounce delay in msec */
1523     store_byte(cpu, 0xefc7 + 10, 1);/* motor start time in 1/8 secs */
1524     store_byte(cpu, 0xefc7 + 11, 1);/* motor stop time in 1/4 secs */
1525    
1526     /* BIOS System Configuration Parameters (8 bytes) at 0xfffd:0: */
1527     reload_segment_descriptor(cpu, X86_S_FS, 0xfffd, NULL);
1528     store_byte(cpu, 0, 8); store_byte(cpu, 1, 0); /* len */
1529     store_byte(cpu, 2, 0xfc); /* model */
1530     store_byte(cpu, 3, 0); /* sub-model */
1531     store_byte(cpu, 4, 0); /* bios revision */
1532     store_byte(cpu, 5, 0x60); /* features */
1533     /* see http://members.tripod.com/~oldboard/assembly/
1534     int_15-c0.html for details */
1535    
1536     /* Some info in the last paragraph of the BIOS: */
1537     reload_segment_descriptor(cpu, X86_S_FS, 0xffff, NULL);
1538     /* TODO: current date :-) */
1539     store_byte(cpu, 0x05, '0'); store_byte(cpu, 0x06, '1');
1540     store_byte(cpu, 0x07, '/');
1541     store_byte(cpu, 0x08, '0'); store_byte(cpu, 0x09, '1');
1542     store_byte(cpu, 0x0a, '/');
1543     store_byte(cpu, 0x0b, '0'); store_byte(cpu, 0x0c, '5');
1544     store_byte(cpu, 0x0e, 0xfc);
1545    
1546     /* Copy the first 128 chars of the 8x8 VGA font into 0xf000:0xfa6e */
1547     reload_segment_descriptor(cpu, X86_S_FS, 0xf000, NULL);
1548     store_buf(cpu, 0xfa6e, (char *)font8x8, 8*128);
1549     store_buf(cpu, 0xfa6e - 1024, (char *)font8x8 + 1024, 8*128);
1550    
1551     /*
1552     * Initialize all real-mode interrupt vectors to point to somewhere
1553     * within the PC BIOS area (0xf000:0x8yy0), and place an IRET
1554     * instruction (too fool someone who really reads the BIOS memory).
1555     */
1556     for (i=0; i<256; i++) {
1557     if (i == 0x20)
1558     i = 0x70;
1559     if (i == 0x78)
1560     break;
1561     reload_segment_descriptor(cpu, X86_S_FS, 0x0000, NULL);
1562     store_16bit_word(cpu, i*4, 0x8000 + i*16);
1563     store_16bit_word(cpu, i*4 + 2, 0xf000);
1564    
1565     /* Exceptions: int 0x1e = ptr to disk table, 1f=fonthigh */
1566     if (i == 0x1e)
1567     store_16bit_word(cpu, i*4, 0xefc7);
1568     if (i == 0x1f)
1569     store_16bit_word(cpu, i*4, 0xfa6e - 1024);
1570    
1571     reload_segment_descriptor(cpu, X86_S_FS, 0xf000, NULL);
1572     store_byte(cpu, 0x8000 + i*16, 0xCF); /* IRET */
1573     }
1574    
1575     /* For SMP emulation, create an "MP" struct in BIOS memory: */
1576     if (cpu->machine->ncpus > 1)
1577     pc_bios_smp_init(cpu);
1578    
1579     /* Prepare for text mode: (0x03 = 80x25, 0x01 = 40x25) */
1580     set_video_mode(cpu, 0x03);
1581    
1582     cmos_write(cpu, 0x15, 640 & 255);
1583     cmos_write(cpu, 0x16, 640 >> 8);
1584     tmp = cpu->machine->physical_ram_in_mb / 1024;
1585     if (tmp > 63*1024)
1586     tmp = 63*1024;
1587     cmos_write(cpu, 0x17, tmp & 255);
1588     cmos_write(cpu, 0x18, tmp >> 8);
1589    
1590     /* Clear the screen first: */
1591     set_cursor_pos(cpu, 0, 0);
1592     for (y=0; y<cpu->machine->md.pc.rows; y++)
1593     for (x=0; x<cpu->machine->md.pc.columns; x++)
1594     output_char(cpu, x,y, ' ', 0x07);
1595    
1596     nboxlines = cpu->machine->md.pc.columns <= 40? 4 : 3;
1597    
1598     /* Draw a nice box at the top: */
1599     for (y=0; y<nboxlines; y++)
1600     for (x=0; x<cpu->machine->md.pc.columns; x++) {
1601     unsigned char ch = ' ';
1602     if (cpu->machine->use_x11) {
1603     if (y == 0) {
1604     ch = 196;
1605     if (x == 0)
1606     ch = 218;
1607     if (x == cpu->machine->md.pc.columns-1)
1608     ch = 191;
1609     } else if (y == nboxlines-1) {
1610     ch = 196;
1611     if (x == 0)
1612     ch = 192;
1613     if (x == cpu->machine->md.pc.columns-1)
1614     ch = 217;
1615     } else if (x == 0 || x ==
1616     cpu->machine->md.pc.columns-1)
1617     ch = 179;
1618     } else {
1619     if (y == 0 || y == nboxlines-1) {
1620     ch = '-';
1621     if (x == 0 || x ==
1622     cpu->machine->md.pc.columns-1)
1623     ch = '+';
1624     } else {
1625     if (x == 0 || x ==
1626     cpu->machine->md.pc.columns-1)
1627     ch = '|';
1628     }
1629     }
1630     output_char(cpu, x,y, ch, 0x19);
1631     }
1632    
1633     snprintf(t, sizeof(t), "GXemul");
1634     #ifdef VERSION
1635     snprintf(t + strlen(t), sizeof(t)-strlen(t), " "VERSION);
1636     #endif
1637     set_cursor_pos(cpu, 2, 1);
1638     pc_bios_printstr(cpu, t, 0x1f);
1639    
1640     snprintf(t, sizeof(t), "%i cpu%s (%s), %i MB memory",
1641     cpu->machine->ncpus, cpu->machine->ncpus > 1? "s" : "",
1642     cpu->cd.x86.model.name, cpu->machine->physical_ram_in_mb);
1643     if (cpu->machine->md.pc.columns <= 40)
1644     set_cursor_pos(cpu, 2, 2);
1645     else
1646     set_cursor_pos(cpu, 78 - strlen(t), 1);
1647     pc_bios_printstr(cpu, t, 0x17);
1648     if (cpu->machine->md.pc.columns <= 40)
1649     set_cursor_pos(cpu, 0, 5);
1650     else
1651     set_cursor_pos(cpu, 0, 4);
1652    
1653     cpu->machine->md.pc.curcolor = 0x07;
1654    
1655     /* "Detect" Floppies, IDE disks, and SCSI disks: */
1656     for (i=0; i<4; i++) {
1657     if (diskimage_exist(cpu->machine, i, DISKIMAGE_FLOPPY)) {
1658     struct pc_bios_disk *p;
1659     p = add_disk(cpu->machine, i, i, DISKIMAGE_FLOPPY);
1660     snprintf(t, sizeof(t), "%c%c", i<2? ('A'+i):' ',
1661     i<2? ':':' ');
1662     pc_bios_printstr(cpu, t, 0xf);
1663     if (i < 2)
1664     nfloppies ++;
1665     snprintf(t, sizeof(t), " (bios disk %02x) FLOPPY", i);
1666     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1667     snprintf(t, sizeof(t), ", %i KB", (int)(p->size/1024));
1668     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1669     if (cpu->machine->md.pc.columns <= 40)
1670     pc_bios_printstr(cpu, "\n ", 0x07);
1671     snprintf(t, sizeof(t), " (CHS=%i,%i,%i)", p->cylinders,
1672     p->heads, p->sectorspertrack);
1673     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1674     if (boot_id == i && boot_type == DISKIMAGE_FLOPPY) {
1675     bios_boot_id = i;
1676     pc_bios_printstr(cpu, " [boot device]", 0xf);
1677     }
1678     pc_bios_printstr(cpu, "\n",
1679     cpu->machine->md.pc.curcolor);
1680     any_disk = 1;
1681     }
1682     }
1683     disknr = 0x80;
1684     for (i=0; i<8; i++) {
1685     if (diskimage_exist(cpu->machine, i, DISKIMAGE_IDE)) {
1686     struct pc_bios_disk *p;
1687     p = add_disk(cpu->machine, disknr, i, DISKIMAGE_IDE);
1688     snprintf(t, sizeof(t), "%s", disknr==0x80? "C:" : " ");
1689     pc_bios_printstr(cpu, t, 0xf);
1690     nhds ++;
1691     snprintf(t, sizeof(t),
1692     " (bios disk %02x) IDE %s, id %i",
1693     disknr, diskimage_is_a_cdrom(cpu->machine, i,
1694     DISKIMAGE_IDE)? "cdrom" : (
1695     diskimage_is_a_tape(cpu->machine, i,
1696     DISKIMAGE_IDE)? "tape" : "disk"),
1697     i);
1698     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1699     if (cpu->machine->md.pc.columns <= 40)
1700     pc_bios_printstr(cpu, "\n ", 0x07);
1701     else
1702     pc_bios_printstr(cpu, ", ",
1703     cpu->machine->md.pc.curcolor);
1704     snprintf(t, sizeof(t), "%lli MB", (long long)
1705     (p->size >> 20));
1706     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1707     if (boot_id == i && boot_type == DISKIMAGE_IDE) {
1708     bios_boot_id = disknr;
1709     pc_bios_printstr(cpu, " [boot device]", 0xf);
1710     }
1711     pc_bios_printstr(cpu, "\n",
1712     cpu->machine->md.pc.curcolor);
1713     disknr++;
1714     any_disk = 1;
1715     }
1716     }
1717     for (i=0; i<8; i++) {
1718     if (diskimage_exist(cpu->machine, i, DISKIMAGE_SCSI)) {
1719     struct pc_bios_disk *p;
1720     p = add_disk(cpu->machine, disknr, i, DISKIMAGE_SCSI);
1721     snprintf(t, sizeof(t), "%s", disknr==0x80? "C:" : " ");
1722     pc_bios_printstr(cpu, t, 0xf);
1723     nhds ++;
1724     snprintf(t, sizeof(t),
1725     " (bios disk %02x) SCSI disk, id %i", disknr, i);
1726     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1727     if (cpu->machine->md.pc.columns <= 40)
1728     pc_bios_printstr(cpu, "\n ", 0x07);
1729     else
1730     pc_bios_printstr(cpu, ", ",
1731     cpu->machine->md.pc.curcolor);
1732     snprintf(t, sizeof(t), "%lli MB", (long long)
1733     (p->size >> 20));
1734     pc_bios_printstr(cpu, t, cpu->machine->md.pc.curcolor);
1735     if (boot_id == i && boot_type == DISKIMAGE_SCSI) {
1736     bios_boot_id = disknr;
1737     pc_bios_printstr(cpu, " [boot device]", 0xf);
1738     }
1739     pc_bios_printstr(cpu, "\n",
1740     cpu->machine->md.pc.curcolor);
1741     disknr++;
1742     any_disk = 1;
1743     }
1744     }
1745    
1746     if (any_disk)
1747     pc_bios_printstr(cpu, "\n", cpu->machine->md.pc.curcolor);
1748     else
1749     pc_bios_printstr(cpu, "No disks attached!\n\n", 0x0f);
1750    
1751     /* See http://members.tripod.com/~oldboard/assembly/bios_data_area.html
1752     for more info. */
1753     if (nfloppies > 0)
1754     nfloppies --;
1755    
1756     reload_segment_descriptor(cpu, X86_S_FS, 0x0000, NULL);
1757     store_16bit_word(cpu, 0x400, 0x03F8); /* COM1 */
1758     store_16bit_word(cpu, 0x402, 0x0378); /* COM2 */
1759     store_byte(cpu, 0x410, (nfloppies << 6) | 0x0f); /* nfloppies etc */
1760     store_byte(cpu, 0x411, 2 << 1); /* nserials etc */
1761     store_16bit_word(cpu, 0x413, 640); /* KB of low RAM */
1762     store_byte(cpu, 0x449, cpu->machine->md.pc.videomode); /* video mode */
1763     store_16bit_word(cpu, 0x44a, cpu->machine->md.pc.columns);/* columns */
1764     store_16bit_word(cpu, 0x463, 0x3D4); /* CRT base port */
1765     store_byte(cpu, 0x475, nhds); /* nr of harddisks */
1766     store_byte(cpu, 0x484, cpu->machine->md.pc.rows-1);/* nr of lines-1 */
1767     store_byte(cpu, 0x485, 16); /* font height */
1768    
1769     /* Registers passed to the bootsector code: */
1770     reload_segment_descriptor(cpu, X86_S_CS, 0x0000, NULL);
1771     reload_segment_descriptor(cpu, X86_S_DS, 0x0000, NULL);
1772     reload_segment_descriptor(cpu, X86_S_ES, 0x0000, NULL);
1773     reload_segment_descriptor(cpu, X86_S_SS, 0x0000, NULL);
1774    
1775     cpu->cd.x86.r[X86_R_AX] = 0xaa55;
1776     cpu->cd.x86.r[X86_R_CX] = 0x0001;
1777     cpu->cd.x86.r[X86_R_DI] = 0xffe4;
1778     cpu->cd.x86.r[X86_R_SP] = 0xfffe;
1779     cpu->cd.x86.r[X86_R_DX] = bios_boot_id;
1780    
1781     cpu->cd.x86.rflags |= X86_FLAGS_IF;
1782     cpu->pc = 0x7c00;
1783    
1784     cpu->machine->md.pc.initialized = 1;
1785 dpavlin 20
1786     cpu->cd.x86.cursegment = old_cursegment;
1787 dpavlin 14 }
1788    
1789    
1790     /*
1791     * pc_bios_emul():
1792     */
1793     int pc_bios_emul(struct cpu *cpu)
1794     {
1795     uint32_t addr = (cpu->cd.x86.s[X86_S_CS] << 4) + cpu->pc;
1796     int int_nr, flags;
1797     int enable_ints_after_return = 0;
1798     unsigned char w[2];
1799    
1800     if (addr == 0xffff0) {
1801     fatal("[ bios reboot ]\n");
1802     cpu->running = 0;
1803     return 0;
1804     }
1805    
1806     int_nr = (addr >> 4) & 0xff;
1807    
1808     if (cpu->cd.x86.cr[0] & X86_CR0_PE) {
1809     fatal("TODO: BIOS interrupt 0x%02x, but we're not in real-"
1810     "mode?\n", int_nr);
1811     cpu->running = 0;
1812     return 0;
1813     }
1814    
1815     switch (int_nr) {
1816     case 0x02: /* NMI? */
1817     debug("[ pc_bios: NMI? TODO ]\n");
1818     break;
1819     case 0x08:
1820     if (pc_bios_int8(cpu) == 0)
1821     return 0;
1822     break;
1823     case 0x09: pc_bios_int9(cpu); break;
1824     case 0x10: pc_bios_int10(cpu); break;
1825     case 0x11:
1826     /* return bios equipment data in ax */
1827     cpu->memory_rw(cpu, cpu->mem, 0x410, &w[0], sizeof(w),
1828     MEM_READ, CACHE_NONE | PHYSICAL);
1829     cpu->cd.x86.r[X86_R_AX] &= ~0xffff;
1830     cpu->cd.x86.r[X86_R_AX] |= (w[1] << 8) | w[0];
1831     break;
1832     case 0x12: /* return memory size in KBs */
1833     cpu->cd.x86.r[X86_R_AX] = 640;
1834     break;
1835     case 0x13:
1836     pc_bios_int13(cpu);
1837     enable_ints_after_return = 1;
1838     break;
1839     case 0x14: pc_bios_int14(cpu); break;
1840     case 0x15: pc_bios_int15(cpu); break;
1841     case 0x16:
1842     if (pc_bios_int16(cpu, &enable_ints_after_return) == 0) {
1843     if (enable_ints_after_return)
1844     cpu->cd.x86.rflags |= X86_FLAGS_IF;
1845     return 0;
1846     }
1847     break;
1848     case 0x17: pc_bios_int17(cpu); break;
1849     case 0x18:
1850     pc_bios_printstr(cpu, "Disk boot failed. (INT 0x18 called.)\n",
1851     0x07);
1852     cpu->running = 0;
1853     break;
1854     case 0x19:
1855     pc_bios_printstr(cpu, "Rebooting. (INT 0x19 called.)\n", 0x07);
1856     cpu->running = 0;
1857     break;
1858     case 0x1a: pc_bios_int1a(cpu); break;
1859     case 0x1c: pc_bios_int1c(cpu); break;
1860     default:
1861     fatal("FATAL: Unimplemented PC BIOS interrupt 0x%02x.\n",
1862     int_nr);
1863     cpu->running = 0;
1864     cpu->dead = 1;
1865     return 0;
1866     }
1867    
1868     /*
1869     * Return from the interrupt: Pop ip (pc), cs, and flags.
1870     */
1871     cpu->cd.x86.cursegment = X86_S_SS;
1872     cpu->pc = load_16bit_word(cpu, cpu->cd.x86.r[X86_R_SP]);
1873     reload_segment_descriptor(cpu, X86_S_CS,
1874     load_16bit_word(cpu, cpu->cd.x86.r[X86_R_SP] + 2), NULL);
1875    
1876     /* Actually, don't pop flags, because they contain result bits
1877     from interrupt calls. Only pop the Interrupt Flag. */
1878     flags = load_16bit_word(cpu, cpu->cd.x86.r[X86_R_SP] + 4);
1879     cpu->cd.x86.rflags &= ~X86_FLAGS_IF;
1880     cpu->cd.x86.rflags |= (flags & X86_FLAGS_IF);
1881    
1882     if (enable_ints_after_return)
1883     cpu->cd.x86.rflags |= X86_FLAGS_IF;
1884    
1885     cpu->cd.x86.r[X86_R_SP] = (cpu->cd.x86.r[X86_R_SP] & ~0xffff)
1886     | ((cpu->cd.x86.r[X86_R_SP] + 6) & 0xffff);
1887    
1888     return 1;
1889     }
1890    
1891    
1892     #endif /* ENABLE_X86 */

  ViewVC Help
Powered by ViewVC 1.1.26