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

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

Parent Directory Parent Directory | Revision Log Revision Log


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

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


1 dpavlin 4 /*
2 dpavlin 22 * Copyright (C) 2003-2006 Anders Gavare. All rights reserved.
3 dpavlin 4 *
4     * Redistribution and use in source and binary forms, with or without
5     * modification, are permitted provided that the following conditions are met:
6     *
7     * 1. Redistributions of source code must retain the above copyright
8     * notice, this list of conditions and the following disclaimer.
9     * 2. Redistributions in binary form must reproduce the above copyright
10     * notice, this list of conditions and the following disclaimer in the
11     * documentation and/or other materials provided with the distribution.
12     * 3. The name of the author may not be used to endorse or promote products
13     * derived from this software without specific prior written permission.
14     *
15     * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16     * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17     * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18     * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19     * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20     * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21     * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22     * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23     * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24     * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25     * SUCH DAMAGE.
26     *
27     *
28 dpavlin 24 * $Id: dev_le.c,v 1.50 2006/03/04 12:38:47 debug Exp $
29 dpavlin 4 *
30     * LANCE ethernet, as used in DECstations.
31     *
32     * This is based on "PMAD-AA TURBOchannel Ethernet Module Functional
33     * Specification". I've tried to keep symbol names in this file to what
34     * the specs use.
35     *
36     * This is what the memory layout looks like on a DECstation 5000/200:
37     *
38     * 0x000000 - 0x0fffff Ethernet SRAM buffer (should be 128KB)
39     * 0x100000 - 0x17ffff LANCE registers
40     * 0x1c0000 - 0x1fffff Ethernet Diagnostic ROM and Station
41     * Address ROM
42     *
43     * The length of the device is set to 0x1c0200, however, because Sprite
44     * tries to read TURBOchannel rom data from 0x1c03f0, and that is provided
45     * by the turbochannel device, not this device.
46     *
47     *
48     * TODO: Error conditions (such as when there are not enough receive
49     * buffers) are not emulated yet.
50 dpavlin 22 *
51     * (Old bug, but probably still valid: "UDP packets that are too
52     * large are not handled well by the Lance device.")
53 dpavlin 4 */
54    
55     #include <stdio.h>
56     #include <stdlib.h>
57     #include <string.h>
58    
59     #include "cpu.h"
60     #include "devices.h"
61     #include "emul.h"
62     #include "machine.h"
63     #include "memory.h"
64     #include "misc.h"
65     #include "net.h"
66    
67     #include "if_lereg.h"
68    
69    
70     #define LE_TICK_SHIFT 14
71    
72     /* #define LE_DEBUG */
73     /* #define debug fatal */
74    
75     extern int quiet_mode;
76    
77     #define LE_MODE_LOOP 4
78     #define LE_MODE_DTX 2
79     #define LE_MODE_DRX 1
80    
81    
82     #define N_REGISTERS 4
83     #define SRAM_SIZE (128*1024)
84     #define ROM_SIZE 32
85    
86    
87     struct le_data {
88     int irq_nr;
89    
90     uint64_t buf_start;
91     uint64_t buf_end;
92     int len;
93    
94     uint8_t rom[ROM_SIZE];
95    
96     int reg_select;
97     uint16_t reg[N_REGISTERS];
98    
99 dpavlin 12 unsigned char *sram;
100 dpavlin 4
101     /* Initialization block: */
102     uint32_t init_block_addr;
103    
104     uint16_t mode;
105     uint64_t padr; /* MAC address */
106     uint64_t ladrf;
107     uint32_t rdra; /* receive descriptor ring address */
108     int rlen; /* nr of rx descriptors */
109     uint32_t tdra; /* transmit descriptor ring address */
110     int tlen; /* nr ot tx descriptors */
111    
112     /* Current rx and tx descriptor indices: */
113     int rxp;
114     int txp;
115    
116     unsigned char *tx_packet;
117     int tx_packet_len;
118    
119     unsigned char *rx_packet;
120     int rx_packet_len;
121     int rx_packet_offset;
122     int rx_middle_bit;
123     };
124    
125    
126     /*
127     * le_read_16bit():
128     *
129     * Read a 16-bit word from the SRAM.
130     */
131     static uint64_t le_read_16bit(struct le_data *d, int addr)
132     {
133     /* TODO: This is for little endian only */
134     int x = d->sram[addr & (SRAM_SIZE-1)] +
135     (d->sram[(addr+1) & (SRAM_SIZE-1)] << 8);
136     return x;
137     }
138    
139    
140     /*
141     * le_write_16bit():
142     *
143     * Write a 16-bit word to the SRAM.
144     */
145     static void le_write_16bit(struct le_data *d, int addr, uint16_t x)
146     {
147     /* TODO: This is for little endian only */
148     d->sram[addr & (SRAM_SIZE-1)] = x & 0xff;
149     d->sram[(addr+1) & (SRAM_SIZE-1)] = (x >> 8) & 0xff;
150     }
151    
152    
153     /*
154     * le_chip_init():
155     *
156     * Initialize data structures by reading an 'initialization block' from the
157     * SRAM.
158     */
159     static void le_chip_init(struct le_data *d)
160     {
161     d->init_block_addr = (d->reg[1] & 0xffff) + ((d->reg[2] & 0xff) << 16);
162     if (d->init_block_addr & 1)
163     fatal("[ le: WARNING! initialization block address "
164     "not word aligned? ]\n");
165    
166     debug("[ le: d->init_block_addr = 0x%06x ]\n", d->init_block_addr);
167    
168     d->mode = le_read_16bit(d, d->init_block_addr + 0);
169     d->padr = le_read_16bit(d, d->init_block_addr + 2);
170     d->padr += (le_read_16bit(d, d->init_block_addr + 4) << 16);
171     d->padr += (le_read_16bit(d, d->init_block_addr + 6) << 32);
172     d->ladrf = le_read_16bit(d, d->init_block_addr + 8);
173     d->ladrf += (le_read_16bit(d, d->init_block_addr + 10) << 16);
174     d->ladrf += (le_read_16bit(d, d->init_block_addr + 12) << 32);
175     d->ladrf += (le_read_16bit(d, d->init_block_addr + 14) << 48);
176     d->rdra = le_read_16bit(d, d->init_block_addr + 16);
177     d->rdra += ((le_read_16bit(d, d->init_block_addr + 18) & 0xff) << 16);
178     d->rlen = 1 << ((le_read_16bit(d, d->init_block_addr + 18) >> 13) & 7);
179     d->tdra = le_read_16bit(d, d->init_block_addr + 20);
180     d->tdra += ((le_read_16bit(d, d->init_block_addr + 22) & 0xff) << 16);
181     d->tlen = 1 << ((le_read_16bit(d, d->init_block_addr + 22) >> 13) & 7);
182    
183     debug("[ le: DEBUG: mode %04x ]\n", d->mode);
184     debug("[ le: DEBUG: padr %016llx ]\n", (long long)d->padr);
185     debug("[ le: DEBUG: ladrf %016llx ]\n", (long long)d->ladrf);
186     debug("[ le: DEBUG: rdra %06llx ]\n", d->rdra);
187     debug("[ le: DEBUG: rlen %3i ]\n", d->rlen);
188     debug("[ le: DEBUG: tdra %06llx ]\n", d->tdra);
189     debug("[ le: DEBUG: tlen %3i ]\n", d->tlen);
190    
191     /* Set TXON and RXON, unless they are disabled by 'mode': */
192     if (d->mode & LE_MODE_DTX)
193     d->reg[0] &= ~LE_TXON;
194     else
195     d->reg[0] |= LE_TXON;
196    
197     if (d->mode & LE_MODE_DRX)
198     d->reg[0] &= ~LE_RXON;
199     else
200     d->reg[0] |= LE_RXON;
201    
202     /* Go to the start of the descriptor rings: */
203     d->rxp = d->txp = 0;
204    
205     /* Set IDON and reset the INIT bit when we are done. */
206     d->reg[0] |= LE_IDON;
207     d->reg[0] &= ~LE_INIT;
208    
209     /* Free any old packets: */
210     if (d->tx_packet != NULL)
211     free(d->tx_packet);
212     d->tx_packet = NULL;
213     d->tx_packet_len = 0;
214    
215     if (d->rx_packet != NULL)
216     free(d->rx_packet);
217     d->rx_packet = NULL;
218     d->rx_packet_len = 0;
219     d->rx_packet_offset = 0;
220     d->rx_middle_bit = 0;
221     }
222    
223    
224     /*
225     * le_tx():
226     *
227     * Check the transmitter descriptor ring for buffers that are owned by the
228     * Lance chip (that is, buffers that are to be transmitted).
229     *
230     * This routine should only be called if TXON is enabled.
231     */
232     static void le_tx(struct net *net, struct le_data *d)
233     {
234     int start_txp = d->txp;
235     uint16_t tx_descr[4];
236 dpavlin 22 int stp, enp, cur_packet_offset;
237     size_t i;
238 dpavlin 4 uint32_t bufaddr, buflen;
239    
240     /* TODO: This is just a guess: */
241     d->reg[0] &= ~LE_TDMD;
242    
243     do {
244     /* Load the 8 descriptor bytes: */
245     tx_descr[0] = le_read_16bit(d, d->tdra + d->txp*8 + 0);
246     tx_descr[1] = le_read_16bit(d, d->tdra + d->txp*8 + 2);
247     tx_descr[2] = le_read_16bit(d, d->tdra + d->txp*8 + 4);
248     tx_descr[3] = le_read_16bit(d, d->tdra + d->txp*8 + 6);
249    
250     bufaddr = tx_descr[0] + ((tx_descr[1] & 0xff) << 16);
251     stp = tx_descr[1] & LE_STP? 1 : 0;
252     enp = tx_descr[1] & LE_ENP? 1 : 0;
253     buflen = 4096 - (tx_descr[2] & 0xfff);
254    
255     /*
256     * Check the OWN bit. If it is zero, then this buffer is
257     * not ready to be transmitted yet. Also check the '1111'
258     * mark, and make sure that byte-count is reasonable.
259     */
260     if (!(tx_descr[1] & LE_OWN))
261     return;
262     if ((tx_descr[2] & 0xf000) != 0xf000)
263     return;
264     if (buflen < 12 || buflen > 1900) {
265     fatal("[ le_tx(): buflen = %i ]\n", buflen);
266     return;
267     }
268    
269     debug("[ le_tx(): descr %3i DUMP: 0x%04x 0x%04x 0x%04x 0x%04x "
270     "=> addr=0x%06x, len=%i bytes, STP=%i ENP=%i ]\n", d->txp,
271     tx_descr[0], tx_descr[1], tx_descr[2], tx_descr[3],
272     bufaddr, buflen, stp, enp);
273    
274     if (d->tx_packet == NULL && !stp) {
275     fatal("[ le_tx(): !stp but tx_packet == NULL ]\n");
276     return;
277     }
278    
279     if (d->tx_packet != NULL && stp) {
280     fatal("[ le_tx(): stp but tx_packet != NULL ]\n");
281     free(d->tx_packet);
282     d->tx_packet = NULL;
283     d->tx_packet_len = 0;
284     }
285    
286     /* Where to write to in the tx_packet: */
287     cur_packet_offset = d->tx_packet_len;
288    
289     /* Start of a new packet: */
290     if (stp) {
291     d->tx_packet_len = buflen;
292     d->tx_packet = malloc(buflen);
293     if (d->tx_packet == NULL) {
294     fprintf(stderr, "out of memory (1) in "
295     "le_tx()\n");
296     exit(1);
297     }
298     } else {
299     d->tx_packet_len += buflen;
300     d->tx_packet = realloc(d->tx_packet, d->tx_packet_len);
301     if (d->tx_packet == NULL) {
302     fprintf(stderr, "out of memory (2) in"
303     " le_tx()\n");
304     exit(1);
305     }
306     }
307    
308     /* Copy data from SRAM into the tx packet: */
309     for (i=0; i<buflen; i++) {
310     unsigned char ch;
311     ch = d->sram[(bufaddr + i) & (SRAM_SIZE-1)];
312     d->tx_packet[cur_packet_offset + i] = ch;
313     }
314    
315     /*
316     * Is this the last buffer in a packet? Then transmit
317     * it, cause an interrupt, and free the memory used by
318     * the packet.
319     */
320     if (enp) {
321     net_ethernet_tx(net, d, d->tx_packet, d->tx_packet_len);
322    
323     free(d->tx_packet);
324     d->tx_packet = NULL;
325     d->tx_packet_len = 0;
326    
327     d->reg[0] |= LE_TINT;
328     }
329    
330     /* Clear the OWN bit: */
331     tx_descr[1] &= ~LE_OWN;
332    
333     /* Write back the descriptor to SRAM: */
334     le_write_16bit(d, d->tdra + d->txp*8 + 2, tx_descr[1]);
335     le_write_16bit(d, d->tdra + d->txp*8 + 4, tx_descr[2]);
336     le_write_16bit(d, d->tdra + d->txp*8 + 6, tx_descr[3]);
337    
338     /* Go to the next descriptor: */
339     d->txp ++;
340     if (d->txp >= d->tlen)
341     d->txp = 0;
342     } while (d->txp != start_txp);
343    
344     /* We are here if all descriptors were taken care of. */
345     fatal("[ le_tx(): all TX descriptors used up? ]\n");
346     }
347    
348    
349     /*
350     * le_rx():
351     *
352     * This routine should only be called if RXON is enabled.
353     */
354     static void le_rx(struct net *net, struct le_data *d)
355     {
356 dpavlin 22 int start_rxp = d->rxp;
357     size_t i;
358 dpavlin 4 uint16_t rx_descr[4];
359     uint32_t bufaddr, buflen;
360    
361     do {
362     if (d->rx_packet == NULL)
363     return;
364    
365     /* Load the 8 descriptor bytes: */
366     rx_descr[0] = le_read_16bit(d, d->rdra + d->rxp*8 + 0);
367     rx_descr[1] = le_read_16bit(d, d->rdra + d->rxp*8 + 2);
368     rx_descr[2] = le_read_16bit(d, d->rdra + d->rxp*8 + 4);
369     rx_descr[3] = le_read_16bit(d, d->rdra + d->rxp*8 + 6);
370    
371     bufaddr = rx_descr[0] + ((rx_descr[1] & 0xff) << 16);
372     buflen = 4096 - (rx_descr[2] & 0xfff);
373    
374     /*
375     * Check the OWN bit. If it is zero, then this buffer is
376     * not ready to receive data yet. Also check the '1111'
377     * mark, and make sure that byte-count is reasonable.
378     */
379     if (!(rx_descr[1] & LE_OWN))
380     return;
381     if ((rx_descr[2] & 0xf000) != 0xf000)
382     return;
383     if (buflen < 12 || buflen > 1900) {
384     fatal("[ le_rx(): buflen = %i ]\n", buflen);
385     return;
386     }
387    
388     debug("[ le_rx(): descr %3i DUMP: 0x%04x 0x%04x 0x%04x 0x%04x "
389     "=> addr=0x%06x, len=%i bytes ]\n", d->rxp,
390     rx_descr[0], rx_descr[1], rx_descr[2], rx_descr[3],
391     bufaddr, buflen);
392    
393     /* Copy data from the packet into SRAM: */
394     for (i=0; i<buflen; i++) {
395 dpavlin 22 if (d->rx_packet_offset+(ssize_t)i >= d->rx_packet_len)
396 dpavlin 4 break;
397     d->sram[(bufaddr + i) & (SRAM_SIZE-1)] =
398     d->rx_packet[d->rx_packet_offset + i];
399     }
400    
401     /* Here, i is the number of bytes copied. */
402     d->rx_packet_offset += i;
403    
404     /* Set the ENP bit if this was the end of a packet: */
405     if (d->rx_packet_offset >= d->rx_packet_len) {
406     rx_descr[1] |= LE_ENP;
407    
408     /*
409     * NOTE: The Lance documentation that I have read
410     * says _NOTHING_ about the length being 4 more than
411     * the length of the data. You can guess how
412     * surprised I was when I saw the following in
413     * NetBSD (dev/ic/am7990.c):
414     *
415     * lance_read(sc, LE_RBUFADDR(sc, bix),
416     * (int)rmd.rmd3 - 4);
417     */
418     rx_descr[3] &= ~0xfff;
419     rx_descr[3] |= d->rx_packet_len + 4;
420    
421     free(d->rx_packet);
422     d->rx_packet = NULL;
423     d->rx_packet_len = 0;
424     d->rx_packet_offset = 0;
425     d->rx_middle_bit = 0;
426    
427     d->reg[0] |= LE_RINT;
428     }
429    
430     /* Set the STP bit if this was the start of a packet: */
431     if (!d->rx_middle_bit) {
432     rx_descr[1] |= LE_STP;
433    
434     /* Are we continuing on this packet? */
435     if (d->rx_packet != NULL)
436     d->rx_middle_bit = 1;
437     }
438    
439     /* Clear the OWN bit: */
440     rx_descr[1] &= ~LE_OWN;
441    
442     /* Write back the descriptor to SRAM: */
443     le_write_16bit(d, d->rdra + d->rxp*8 + 2, rx_descr[1]);
444     le_write_16bit(d, d->rdra + d->rxp*8 + 4, rx_descr[2]);
445     le_write_16bit(d, d->rdra + d->rxp*8 + 6, rx_descr[3]);
446    
447     /* Go to the next descriptor: */
448     d->rxp ++;
449     if (d->rxp >= d->rlen)
450     d->rxp = 0;
451     } while (d->rxp != start_rxp);
452    
453     /* We are here if all descriptors were taken care of. */
454     fatal("[ le_rx(): all RX descriptors used up? ]\n");
455     }
456    
457    
458     /*
459     * le_register_fix():
460     */
461     static void le_register_fix(struct net *net, struct le_data *d)
462     {
463     /* Init with new Initialization block, if needed. */
464     if (d->reg[0] & LE_INIT)
465     le_chip_init(d);
466    
467     #ifdef LE_DEBUG
468     {
469     static int x = 1234;
470     if (x != d->reg[0]) {
471     debug("[ le reg[0] = 0x%04x ]\n", d->reg[0]);
472     x = d->reg[0];
473     }
474     }
475     #endif
476    
477     /*
478     * If the receiver is on:
479     * If there is a current rx_packet, try to receive it into the
480     * Lance buffers. Then try to receive any additional packets.
481     */
482     if (d->reg[0] & LE_RXON) {
483     do {
484     if (d->rx_packet != NULL)
485     /* Try to receive the packet: */
486     le_rx(net, d);
487    
488     if (d->rx_packet != NULL)
489     /* If the packet wasn't fully received,
490     then abort for now. */
491     break;
492    
493     if (d->rx_packet == NULL &&
494     net_ethernet_rx_avail(net, d))
495     net_ethernet_rx(net, d,
496     &d->rx_packet, &d->rx_packet_len);
497     } while (d->rx_packet != NULL);
498     }
499    
500     /* If the transmitter is on, check for outgoing buffers: */
501     if (d->reg[0] & LE_TXON)
502     le_tx(net, d);
503    
504     /* SERR should be the OR of BABL, CERR, MISS, and MERR: */
505     d->reg[0] &= ~LE_SERR;
506     if (d->reg[0] & (LE_BABL | LE_CERR | LE_MISS | LE_MERR))
507     d->reg[0] |= LE_SERR;
508    
509     /* INTR should be the OR of BABL, MISS, MERR, RINT, TINT, IDON: */
510     d->reg[0] &= ~LE_INTR;
511     if (d->reg[0] & (LE_BABL | LE_MISS | LE_MERR | LE_RINT |
512     LE_TINT | LE_IDON))
513     d->reg[0] |= LE_INTR;
514    
515     /* The MERR bit clears some bits: */
516     if (d->reg[0] & LE_MERR)
517     d->reg[0] &= ~(LE_RXON | LE_TXON);
518    
519     /* The STOP bit clears a lot of stuff: */
520     #if 0
521     /* According to the LANCE manual: (doesn't work with Ultrix) */
522     if (d->reg[0] & LE_STOP)
523     d->reg[0] &= ~(LE_SERR | LE_BABL | LE_CERR | LE_MISS | LE_MERR
524     | LE_RINT | LE_TINT | LE_IDON | LE_INTR | LE_INEA
525     | LE_RXON | LE_TXON | LE_TDMD);
526     #else
527     /* Works with Ultrix: */
528     if (d->reg[0] & LE_STOP)
529     d->reg[0] &= ~(LE_IDON);
530     #endif
531     }
532    
533    
534     /*
535     * dev_le_tick():
536     */
537     void dev_le_tick(struct cpu *cpu, void *extra)
538     {
539     struct le_data *d = (struct le_data *) extra;
540    
541     le_register_fix(cpu->machine->emul->net, d);
542    
543     if (d->reg[0] & LE_INTR && d->reg[0] & LE_INEA)
544     cpu_interrupt(cpu, d->irq_nr);
545     else
546     cpu_interrupt_ack(cpu, d->irq_nr);
547     }
548    
549    
550     /*
551     * le_register_write():
552     *
553     * This function is called when the value 'x' is written to register 'r'.
554     */
555     void le_register_write(struct le_data *d, int r, uint32_t x)
556     {
557     switch (r) {
558     case 0: /* CSR0: */
559     /* Some bits are write-one-to-clear: */
560     if (x & LE_BABL)
561     d->reg[r] &= ~LE_BABL;
562     if (x & LE_CERR)
563     d->reg[r] &= ~LE_CERR;
564     if (x & LE_MISS)
565     d->reg[r] &= ~LE_MISS;
566     if (x & LE_MERR)
567     d->reg[r] &= ~LE_MERR;
568     if (x & LE_RINT)
569     d->reg[r] &= ~LE_RINT;
570     if (x & LE_TINT)
571     d->reg[r] &= ~LE_TINT;
572     if (x & LE_IDON)
573     d->reg[r] &= ~LE_IDON;
574    
575     /* Some bits are write-only settable, not clearable: */
576     if (x & LE_TDMD)
577     d->reg[r] |= LE_TDMD;
578     if (x & LE_STRT) {
579     d->reg[r] |= LE_STRT;
580     d->reg[r] &= ~LE_STOP;
581     }
582     if (x & LE_INIT) {
583     if (!(d->reg[r] & LE_STOP))
584     fatal("[ le: attempt to INIT before"
585     " STOPped! ]\n");
586     d->reg[r] |= LE_INIT;
587     d->reg[r] &= ~LE_STOP;
588     }
589     if (x & LE_STOP) {
590     d->reg[r] |= LE_STOP;
591     /* STOP takes precedence over STRT and INIT: */
592     d->reg[r] &= ~(LE_STRT | LE_INIT);
593     }
594    
595     /* Some bits get through, both settable and clearable: */
596     d->reg[r] &= ~LE_INEA;
597     d->reg[r] |= (x & LE_INEA);
598     break;
599    
600     default:
601     /* CSR1, CSR2, and CSR3: */
602     d->reg[r] = x;
603     }
604     }
605    
606    
607     /*
608     * dev_le_sram_access():
609     */
610 dpavlin 22 DEVICE_ACCESS(le_sram)
611 dpavlin 4 {
612 dpavlin 22 size_t i;
613     int retval;
614 dpavlin 4 struct le_data *d = extra;
615    
616     #ifdef LE_DEBUG
617     if (writeflag == MEM_WRITE) {
618     fatal("[ le_sram: write to addr 0x%06x: ", (int)relative_addr);
619     for (i=0; i<len; i++)
620     fatal("%02x ", data[i]);
621     fatal("]\n");
622     }
623     #endif
624    
625     /* Read/write of the SRAM: */
626     if (relative_addr < SRAM_SIZE && relative_addr + len <= SRAM_SIZE) {
627     if (writeflag == MEM_READ) {
628     memcpy(data, d->sram + relative_addr, len);
629     if (!quiet_mode) {
630     debug("[ le: read from SRAM offset 0x%05x:",
631     relative_addr);
632     for (i=0; i<len; i++)
633     debug(" %02x", data[i]);
634     debug(" ]\n");
635     }
636     retval = 9; /* 9 cycles */
637     } else {
638     memcpy(d->sram + relative_addr, data, len);
639     if (!quiet_mode) {
640     debug("[ le: write to SRAM offset 0x%05x:",
641     relative_addr);
642     for (i=0; i<len; i++)
643     debug(" %02x", data[i]);
644     debug(" ]\n");
645     }
646     retval = 6; /* 6 cycles */
647     }
648     return retval;
649     }
650    
651     return 0;
652     }
653    
654    
655     /*
656     * dev_le_access():
657     */
658 dpavlin 22 DEVICE_ACCESS(le)
659 dpavlin 4 {
660     uint64_t idata = 0, odata = 0;
661 dpavlin 22 size_t i;
662     int retval = 1;
663 dpavlin 4 struct le_data *d = extra;
664    
665 dpavlin 18 if (writeflag == MEM_WRITE)
666     idata = memory_readmax64(cpu, data, len);
667 dpavlin 4
668     #ifdef LE_DEBUG
669     if (writeflag == MEM_WRITE) {
670     fatal("[ le: write to addr 0x%06x: ", (int)relative_addr);
671     for (i=0; i<len; i++)
672     fatal("%02x ", data[i]);
673     fatal("]\n");
674     }
675     #endif
676    
677     /* Read from station's ROM (ethernet address): */
678     if (relative_addr >= 0xc0000 && relative_addr <= 0xfffff) {
679 dpavlin 22 uint32_t a;
680     int j = (relative_addr & 0xff) / 4;
681     a = d->rom[j & (ROM_SIZE-1)];
682 dpavlin 4
683     if (writeflag == MEM_READ) {
684 dpavlin 22 odata = (a << 24) + (a << 16) + (a << 8) + a;
685 dpavlin 4 } else {
686     fatal("[ le: WRITE to ethernet addr (%08lx):",
687     (long)relative_addr);
688     for (i=0; i<len; i++)
689     fatal(" %02x", data[i]);
690     fatal(" ]\n");
691     }
692    
693     retval = 13; /* 13 cycles */
694     goto do_return;
695     }
696    
697    
698     switch (relative_addr) {
699    
700     /* Register read/write: */
701     case 0:
702     if (writeflag==MEM_READ) {
703     odata = d->reg[d->reg_select];
704     if (!quiet_mode)
705     debug("[ le: read from register 0x%02x: 0x"
706     "%02x ]\n", d->reg_select, (int)odata);
707     /*
708     * A read from csr1..3 should return "undefined"
709     * result if the stop bit is set. However, Ultrix
710     * seems to do just that, so let's _not_ print
711     * a warning here.
712     */
713     } else {
714     if (!quiet_mode)
715     debug("[ le: write to register 0x%02x: 0x"
716     "%02x ]\n", d->reg_select, (int)idata);
717     /*
718     * A write to from csr1..3 when the stop bit is
719     * set should be ignored. However, Ultrix writes
720     * even if the stop bit is set, so let's _not_
721     * print a warning about it.
722     */
723     le_register_write(d, d->reg_select, idata);
724     }
725     break;
726    
727     /* Register select: */
728     case 4:
729     if (writeflag==MEM_READ) {
730     odata = d->reg_select;
731     if (!quiet_mode)
732     debug("[ le: read from register select: "
733     "0x%02x ]\n", (int)odata);
734     } else {
735     if (!quiet_mode)
736     debug("[ le: write to register select: "
737     "0x%02x ]\n", (int)idata);
738     d->reg_select = idata & (N_REGISTERS - 1);
739     if (idata >= N_REGISTERS)
740     fatal("[ le: WARNING! register select %i "
741     "(max is %i) ]\n", idata, N_REGISTERS - 1);
742     }
743     break;
744    
745     default:
746     if (writeflag==MEM_READ) {
747     fatal("[ le: read from UNIMPLEMENTED addr 0x%06x ]\n",
748     (int)relative_addr);
749     } else {
750     fatal("[ le: write to UNIMPLEMENTED addr 0x%06x: "
751     "0x%08x ]\n", (int)relative_addr, (int)idata);
752     }
753     }
754    
755     do_return:
756     if (writeflag == MEM_READ) {
757     memory_writemax64(cpu, data, len, odata);
758     #ifdef LE_DEBUG
759     fatal("[ le: read from addr 0x%06x: 0x%08x ]\n",
760     relative_addr, odata);
761     #endif
762     }
763    
764     dev_le_tick(cpu, extra);
765    
766     return retval;
767     }
768    
769    
770     /*
771     * dev_le_init():
772     */
773     void dev_le_init(struct machine *machine, struct memory *mem, uint64_t baseaddr,
774     uint64_t buf_start, uint64_t buf_end, int irq_nr, int len)
775     {
776     char *name2;
777 dpavlin 10 size_t nlen = 55;
778 dpavlin 4 struct le_data *d = malloc(sizeof(struct le_data));
779    
780     if (d == NULL) {
781     fprintf(stderr, "out of memory\n");
782     exit(1);
783     }
784    
785     memset(d, 0, sizeof(struct le_data));
786     d->irq_nr = irq_nr;
787    
788 dpavlin 12 d->sram = malloc(SRAM_SIZE);
789     if (d->sram == NULL) {
790     fprintf(stderr, "out of memory\n");
791     exit(1);
792     }
793     memset(d->sram, 0, SRAM_SIZE);
794    
795 dpavlin 4 /* TODO: Are these actually used yet? */
796     d->len = len;
797     d->buf_start = buf_start;
798     d->buf_end = buf_end;
799    
800     /* Initial register contents: */
801     d->reg[0] = LE_STOP;
802    
803     d->tx_packet = NULL;
804     d->rx_packet = NULL;
805    
806     /* ROM (including the MAC address): */
807     net_generate_unique_mac(machine, &d->rom[0]);
808    
809     /* Copies of the MAC address and a test pattern: */
810     d->rom[10] = d->rom[21] = d->rom[5];
811     d->rom[11] = d->rom[20] = d->rom[4];
812     d->rom[12] = d->rom[19] = d->rom[3];
813     d->rom[7] = d->rom[8] = d->rom[23] =
814     d->rom[13] = d->rom[18] = d->rom[2];
815     d->rom[6] = d->rom[9] = d->rom[22] =
816     d->rom[14] = d->rom[17] = d->rom[1];
817     d->rom[15] = d->rom[16] = d->rom[0];
818     d->rom[24] = d->rom[28] = 0xff;
819     d->rom[25] = d->rom[29] = 0x00;
820     d->rom[26] = d->rom[30] = 0x55;
821     d->rom[27] = d->rom[31] = 0xaa;
822    
823     memory_device_register(mem, "le_sram", baseaddr,
824     SRAM_SIZE, dev_le_sram_access, (void *)d,
825 dpavlin 20 DM_DYNTRANS_OK | DM_DYNTRANS_WRITE_OK
826     | DM_READS_HAVE_NO_SIDE_EFFECTS, d->sram);
827 dpavlin 4
828 dpavlin 10 name2 = malloc(nlen);
829 dpavlin 4 if (name2 == NULL) {
830     fprintf(stderr, "out of memory in dev_le_init()\n");
831     exit(1);
832     }
833 dpavlin 10 snprintf(name2, nlen, "le [%02x:%02x:%02x:%02x:%02x:%02x]",
834 dpavlin 4 d->rom[0], d->rom[1], d->rom[2], d->rom[3], d->rom[4], d->rom[5]);
835    
836     memory_device_register(mem, name2, baseaddr + 0x100000,
837 dpavlin 20 len - 0x100000, dev_le_access, (void *)d, DM_DEFAULT, NULL);
838 dpavlin 4
839 dpavlin 24 machine_add_tickfunction(machine, dev_le_tick, d, LE_TICK_SHIFT, 0.0);
840 dpavlin 4
841     net_add_nic(machine->emul->net, d, &d->rom[0]);
842     }
843    

  ViewVC Help
Powered by ViewVC 1.1.26