if_es.c revision 1.49
1/*	$NetBSD: if_es.c,v 1.49 2010/01/19 22:06:19 pooka Exp $ */
2
3/*
4 * Copyright (c) 1995 Michael L. Hitch
5 * All rights reserved.
6 *
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following conditions
9 * are met:
10 * 1. Redistributions of source code must retain the above copyright
11 *    notice, this list of conditions and the following disclaimer.
12 * 2. Redistributions in binary form must reproduce the above copyright
13 *    notice, this list of conditions and the following disclaimer in the
14 *    documentation and/or other materials provided with the distribution.
15 *
16 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
17 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
18 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
19 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
20 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
21 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
22 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
23 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
24 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
25 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
26 */
27
28/*
29 * SMC 91C90 Single-Chip Ethernet Controller
30 */
31#include "opt_ddb.h"
32#include "opt_inet.h"
33#include "opt_ns.h"
34
35#include <sys/cdefs.h>
36__KERNEL_RCSID(0, "$NetBSD: if_es.c,v 1.49 2010/01/19 22:06:19 pooka Exp $");
37
38
39#include <sys/param.h>
40#include <sys/systm.h>
41#include <sys/mbuf.h>
42#include <sys/buf.h>
43#include <sys/protosw.h>
44#include <sys/socket.h>
45#include <sys/syslog.h>
46#include <sys/ioctl.h>
47#include <sys/errno.h>
48#include <sys/device.h>
49
50#include <net/if.h>
51#include <net/if_dl.h>
52#include <net/if_ether.h>
53#include <net/if_media.h>
54
55#ifdef INET
56#include <netinet/in.h>
57#include <netinet/in_systm.h>
58#include <netinet/in_var.h>
59#include <netinet/ip.h>
60#include <netinet/if_inarp.h>
61#endif
62
63#ifdef NS
64#include <netns/ns.h>
65#include <netns/ns_if.h>
66#endif
67
68#include <machine/cpu.h>
69#include <amiga/amiga/device.h>
70#include <amiga/amiga/isr.h>
71#include <amiga/dev/zbusvar.h>
72#include <amiga/dev/if_esreg.h>
73
74#define SWAP(x) (((x & 0xff) << 8) | ((x >> 8) & 0xff))
75
76#define	USEPKTBUF
77
78/*
79 * Ethernet software status per interface.
80 *
81 * Each interface is referenced by a network interface structure,
82 * es_if, which the routing code uses to locate the interface.
83 * This structure contains the output queue for the interface, its address, ...
84 */
85struct	es_softc {
86	struct	device sc_dev;
87	struct	isr sc_isr;
88	struct	ethercom sc_ethercom;	/* common Ethernet structures */
89	struct	ifmedia sc_media;	/* our supported media */
90	void	*sc_base;		/* base address of board */
91	short	sc_iflags;
92	unsigned short sc_intctl;
93#ifdef ESDEBUG
94	int	sc_debug;
95	short	sc_intbusy;		/* counter for interrupt rentered */
96	short	sc_smcbusy;		/* counter for other rentry checks */
97#endif
98};
99
100#include <net/bpf.h>
101#include <net/bpfdesc.h>
102
103#ifdef ESDEBUG
104/* console error messages */
105int	esdebug = 0;
106int	estxints = 0;	/* IST_TX with TX enabled */
107int	estxint2 = 0;	/* IST_TX active after IST_TX_EMPTY */
108int	estxint3 = 0;	/* IST_TX interrupt processed */
109int	estxint4 = 0;	/* ~TEMPTY counts */
110int	estxint5 = 0;	/* IST_TX_EMPTY interrupts */
111void	es_dump_smcregs(char *, union smcregs *);
112#endif
113
114int esintr(void *);
115void esstart(struct ifnet *);
116void eswatchdog(struct ifnet *);
117int esioctl(struct ifnet *, u_long, void *);
118void esrint(struct es_softc *);
119void estint(struct es_softc *);
120void esinit(struct es_softc *);
121void esreset(struct es_softc *);
122void esstop(struct es_softc *);
123int esmediachange(struct ifnet *);
124void esmediastatus(struct ifnet *, struct ifmediareq *);
125
126int esmatch(struct device *, struct cfdata *, void *);
127void esattach(struct device *, struct device *, void *);
128
129CFATTACH_DECL(es, sizeof(struct es_softc),
130    esmatch, esattach, NULL, NULL);
131
132int
133esmatch(struct device *parent, struct cfdata *cfp, void *aux)
134{
135	struct zbus_args *zap = aux;
136
137	/* Ameristar A4066 ethernet card */
138	if (zap->manid == 1053 && zap->prodid == 10)
139		return(1);
140
141	return (0);
142}
143
144/*
145 * Interface exists: make available by filling in network interface
146 * record.  System will initialize the interface when it is ready
147 * to accept packets.
148 */
149void
150esattach(struct device *parent, struct device *self, void *aux)
151{
152	struct es_softc *sc = (void *)self;
153	struct zbus_args *zap = aux;
154	struct ifnet *ifp = &sc->sc_ethercom.ec_if;
155	unsigned long ser;
156	u_int8_t myaddr[ETHER_ADDR_LEN];
157
158	sc->sc_base = zap->va;
159
160	/*
161	 * Manufacturer decides the 3 first bytes, i.e. ethernet vendor ID.
162	 * (Currently only Ameristar.)
163	 */
164	myaddr[0] = 0x00;
165	myaddr[1] = 0x00;
166	myaddr[2] = 0x9f;
167
168	/*
169	 * Serial number for board contains last 3 bytes.
170	 */
171	ser = (unsigned long) zap->serno;
172
173	myaddr[3] = (ser >> 16) & 0xff;
174	myaddr[4] = (ser >>  8) & 0xff;
175	myaddr[5] = (ser      ) & 0xff;
176
177	/* Initialize ifnet structure. */
178	memcpy(ifp->if_xname, sc->sc_dev.dv_xname, IFNAMSIZ);
179	ifp->if_softc = sc;
180	ifp->if_ioctl = esioctl;
181	ifp->if_start = esstart;
182	ifp->if_watchdog = eswatchdog;
183	ifp->if_flags = IFF_BROADCAST | IFF_SIMPLEX | IFF_NOTRAILERS |
184	    IFF_MULTICAST;
185
186	ifmedia_init(&sc->sc_media, 0, esmediachange, esmediastatus);
187	ifmedia_add(&sc->sc_media, IFM_ETHER|IFM_MANUAL, 0, NULL);
188	ifmedia_set(&sc->sc_media, IFM_ETHER|IFM_MANUAL);
189
190	/* Attach the interface. */
191	if_attach(ifp);
192	ether_ifattach(ifp, myaddr);
193
194	/* Print additional info when attached. */
195	printf(": address %s\n", ether_sprintf(myaddr));
196
197	sc->sc_isr.isr_intr = esintr;
198	sc->sc_isr.isr_arg = sc;
199	sc->sc_isr.isr_ipl = 2;
200	add_isr(&sc->sc_isr);
201}
202
203#ifdef ESDEBUG
204void
205es_dump_smcregs(char *where, union smcregs *smc)
206{
207	u_short cur_bank = smc->b0.bsr & BSR_MASK;
208
209	printf("SMC registers %p from %s bank %04x\n", smc, where,
210	    smc->b0.bsr);
211	smc->b0.bsr = BSR_BANK0;
212	printf("TCR %04x EPHSR %04x RCR %04x ECR %04x MIR %04x MCR %04x\n",
213	    SWAP(smc->b0.tcr), SWAP(smc->b0.ephsr), SWAP(smc->b0.rcr),
214	    SWAP(smc->b0.ecr), SWAP(smc->b0.mir), SWAP(smc->b0.mcr));
215	smc->b1.bsr = BSR_BANK1;
216	printf("CR %04x BAR %04x IAR %04x %04x %04x GPR %04x CTR %04x\n",
217	    SWAP(smc->b1.cr), SWAP(smc->b1.bar), smc->b1.iar[0], smc->b1.iar[1],
218	    smc->b1.iar[2], smc->b1.gpr, SWAP(smc->b1.ctr));
219	smc->b2.bsr = BSR_BANK2;
220	printf("MMUCR %04x PNR %02x ARR %02x FIFO %04x PTR %04x",
221	    SWAP(smc->b2.mmucr), smc->b2.pnr, smc->b2.arr, smc->b2.fifo,
222	    SWAP(smc->b2.ptr));
223	printf(" DATA %04x %04x IST %02x MSK %02x\n", smc->b2.data,
224	    smc->b2.datax, smc->b2.ist, smc->b2.msk);
225	smc->b3.bsr = BSR_BANK3;
226	printf("MT %04x %04x %04x %04x\n",
227	    smc->b3.mt[0], smc->b3.mt[1], smc->b3.mt[2], smc->b3.mt[3]);
228	smc->b3.bsr = cur_bank;
229}
230#endif
231
232void
233esstop(struct es_softc *sc)
234{
235	union smcregs *smc = sc->sc_base;
236
237	/*
238	 * Clear interrupt mask; disable all interrupts.
239	 */
240	smc->b2.bsr = BSR_BANK2;
241	smc->b2.msk = 0;
242
243	/*
244	 * Disable transmitter and receiver.
245	 */
246	smc->b0.bsr = BSR_BANK0;
247	smc->b0.rcr = 0;
248	smc->b0.tcr = 0;
249
250	/*
251	 * Cancel watchdog timer.
252	 */
253	sc->sc_ethercom.ec_if.if_timer = 0;
254}
255
256void
257esinit(struct es_softc *sc)
258{
259	struct ifnet *ifp = &sc->sc_ethercom.ec_if;
260	union smcregs *smc = sc->sc_base;
261	int s;
262
263	s = splnet();
264
265#ifdef ESDEBUG
266	if (ifp->if_flags & IFF_RUNNING)
267		es_dump_smcregs("esinit", smc);
268#endif
269	smc->b0.bsr = BSR_BANK0;	/* Select bank 0 */
270	smc->b0.rcr = RCR_EPH_RST;
271	smc->b0.rcr = 0;
272	smc->b3.bsr = BSR_BANK3;	/* Select bank 3 */
273	smc->b3.mt[0] = 0;		/* clear Multicast table */
274	smc->b3.mt[1] = 0;
275	smc->b3.mt[2] = 0;
276	smc->b3.mt[3] = 0;
277	/* XXX set Multicast table from Multicast list */
278	smc->b1.bsr = BSR_BANK1;	/* Select bank 1 */
279	smc->b1.cr = CR_RAM32K | CR_NO_WAIT_ST | CR_SET_SQLCH;
280	smc->b1.ctr = CTR_AUTO_RLSE | CTR_TE_ENA;
281	smc->b1.iar[0] = *((const unsigned short *) &CLLADDR(ifp->if_sadl)[0]);
282	smc->b1.iar[1] = *((const unsigned short *) &CLLADDR(ifp->if_sadl)[2]);
283	smc->b1.iar[2] = *((const unsigned short *) &CLLADDR(ifp->if_sadl)[4]);
284	smc->b2.bsr = BSR_BANK2;	/* Select bank 2 */
285	smc->b2.mmucr = MMUCR_RESET;
286	smc->b0.bsr = BSR_BANK0;	/* Select bank 0 */
287	smc->b0.mcr = SWAP(0x0020);	/* reserve 8K for transmit buffers */
288	smc->b0.tcr = TCR_PAD_EN | (TCR_TXENA + TCR_MON_CSN);
289	smc->b0.rcr = RCR_FILT_CAR | RCR_STRIP_CRC | RCR_RXEN | RCR_ALLMUL;
290	/* XXX add promiscuous flags */
291	smc->b2.bsr = BSR_BANK2;	/* Select bank 2 */
292	smc->b2.msk = sc->sc_intctl = MSK_RX_OVRN | MSK_RX | MSK_EPHINT;
293
294	/* Interface is now 'running', with no output active. */
295	ifp->if_flags |= IFF_RUNNING;
296	ifp->if_flags &= ~IFF_OACTIVE;
297
298	/* Attempt to start output, if any. */
299	esstart(ifp);
300
301	splx(s);
302}
303
304int
305esintr(void *arg)
306{
307	struct es_softc *sc = arg;
308	struct ifnet *ifp = &sc->sc_ethercom.ec_if;
309	u_short intsts, intact;
310	union smcregs *smc;
311	int s = splnet();
312
313	smc = sc->sc_base;
314#ifdef ESDEBUG
315	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2 &&
316	    ifp->if_flags & IFF_RUNNING) {
317		printf("%s: intr BSR not 2: %04x\n", sc->sc_dev.dv_xname,
318		    smc->b2.bsr);
319		smc->b2.bsr = BSR_BANK2;
320	}
321#endif
322	intsts = smc->b2.ist;
323	intact = smc->b2.msk & intsts;
324	if ((intact) == 0) {
325		splx(s);
326		return (0);
327	}
328#ifdef ESDEBUG
329	if (esdebug)
330		printf ("%s: esintr ist %02x msk %02x",
331		    sc->sc_dev.dv_xname, intsts, smc->b2.msk);
332	if (sc->sc_intbusy++) {
333		printf("%s: esintr re-entered\n", sc->sc_dev.dv_xname);
334		panic("esintr re-entered");
335	}
336	if (sc->sc_smcbusy)
337		printf("%s: esintr interrupted busy %d\n", sc->sc_dev.dv_xname,
338		    sc->sc_smcbusy);
339#endif
340	smc->b2.msk = 0;
341#ifdef ESDEBUG
342	if (esdebug)
343		printf ("=>%02x%02x pnr %02x arr %02x fifo %04x\n",
344		    smc->b2.ist, smc->b2.ist, smc->b2.pnr, smc->b2.arr,
345		    smc->b2.fifo);
346#endif
347	if (intact & IST_ALLOC) {
348		sc->sc_intctl &= ~MSK_ALLOC;
349#ifdef ESDEBUG
350		if (esdebug || 1)
351			printf ("%s: ist %02x", sc->sc_dev.dv_xname,
352			    intsts);
353#endif
354		if ((smc->b2.arr & ARR_FAILED) == 0) {
355			u_char save_pnr;
356#ifdef ESDEBUG
357			if (esdebug || 1)
358				printf (" arr %02x\n", smc->b2.arr);
359#endif
360			save_pnr = smc->b2.pnr;
361			smc->b2.pnr = smc->b2.arr;
362			smc->b2.mmucr = MMUCR_RLSPKT;
363			while (smc->b2.mmucr & MMUCR_BUSY)
364				;
365			smc->b2.pnr = save_pnr;
366			ifp->if_flags &= ~IFF_OACTIVE;
367			ifp->if_timer = 0;
368		}
369#ifdef ESDEBUG
370		else if (esdebug || 1)
371			printf (" IST_ALLOC with ARR_FAILED?\n");
372#endif
373	}
374#ifdef ESDEBUG
375	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
376		printf("%s: intr+ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
377		    smc->b2.bsr);
378		smc->b2.bsr = BSR_BANK2;
379	}
380#endif
381	while ((smc->b2.fifo & FIFO_REMPTY) == 0) {
382		esrint(sc);
383	}
384#ifdef ESDEBUG
385	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
386		printf("%s: intr++ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
387		    smc->b2.bsr);
388		smc->b2.bsr = BSR_BANK2;
389	}
390#endif
391	if (intact & IST_RX_OVRN) {
392		printf ("%s: Overrun ist %02x", sc->sc_dev.dv_xname,
393		    intsts);
394		smc->b2.ist = ACK_RX_OVRN;
395		printf ("->%02x\n", smc->b2.ist);
396		ifp->if_ierrors++;
397	}
398	if (intact & IST_TX_EMPTY) {
399		u_short ecr;
400#ifdef ESDEBUG
401		if (esdebug)
402			printf ("%s: TX EMPTY %02x",
403			    sc->sc_dev.dv_xname, intsts);
404		++estxint5;		/* count # IST_TX_EMPTY ints */
405#endif
406		smc->b2.ist = ACK_TX_EMPTY;
407		sc->sc_intctl &= ~(MSK_TX_EMPTY | MSK_TX);
408		ifp->if_timer = 0;
409#ifdef ESDEBUG
410		if (esdebug)
411			printf ("->%02x intcl %x pnr %02x arr %02x\n",
412			    smc->b2.ist, sc->sc_intctl, smc->b2.pnr,
413			    smc->b2.arr);
414#endif
415		if (smc->b2.ist & IST_TX) {
416			intact |= IST_TX;
417#ifdef ESDEBUG
418			++estxint2;		/* count # TX after TX_EMPTY */
419#endif
420		} else {
421			smc->b0.bsr = BSR_BANK0;
422			ecr = smc->b0.ecr;	/* Get error counters */
423			if (ecr & 0xff00)
424				ifp->if_collisions += ((ecr >> 8) & 15) +
425				    ((ecr >> 11) & 0x1e);
426			smc->b2.bsr = BSR_BANK2;
427#if 0
428			smc->b2.mmucr = MMUCR_RESET_TX; /* XXX reset TX FIFO */
429#endif
430		}
431	}
432	if (intact & IST_TX) {
433		u_char tx_pnr, save_pnr;
434		u_short save_ptr, ephsr, tcr;
435		int n = 0;
436#ifdef ESDEBUG
437		if (esdebug) {
438			printf ("%s: TX INT ist %02x",
439			    sc->sc_dev.dv_xname, intsts);
440			printf ("->%02x\n", smc->b2.ist);
441		}
442		++estxint3;			/* count # IST_TX */
443#endif
444zzzz:
445#ifdef ESDEBUG
446		++estxint4;			/* count # ~TEMPTY */
447#endif
448		smc->b0.bsr = BSR_BANK0;
449		ephsr = smc->b0.ephsr;		/* get EPHSR */
450		tcr = smc->b0.tcr;		/* and TCR */
451		smc->b2.bsr = BSR_BANK2;
452		save_ptr = smc->b2.ptr;
453		save_pnr = smc->b2.pnr;
454		tx_pnr = smc->b2.fifo >> 8;	/* pktno from completion fifo */
455		smc->b2.pnr = tx_pnr;		/* set TX packet number */
456		smc->b2.ptr = PTR_READ;		/* point to status word */
457#if 0 /* XXXX */
458		printf("%s: esintr TXINT IST %02x PNR %02x(%d)",
459		    sc->sc_dev.dv_xname, smc->b2.ist,
460		    tx_pnr, n);
461		printf(" Status %04x", smc->b2.data);
462		printf(" EPHSR %04x\n", ephsr);
463#endif
464		if ((smc->b2.data & EPHSR_TX_SUC) == 0 && (tcr & TCR_TXENA) == 0) {
465			/*
466			 * Transmitter was stopped for some error.  Enqueue
467			 * the packet again and restart the transmitter.
468			 * May need some check to limit the number of retries.
469			 */
470			smc->b2.mmucr = MMUCR_ENQ_TX;
471			smc->b0.bsr = BSR_BANK0;
472			smc->b0.tcr |= TCR_TXENA;
473			smc->b2.bsr = BSR_BANK2;
474			ifp->if_oerrors++;
475			sc->sc_intctl |= MSK_TX_EMPTY | MSK_TX;
476		} else {
477			/*
478			 * This shouldn't have happened:  IST_TX indicates
479			 * the TX completion FIFO is not empty, but the
480			 * status for the packet on the completion FIFO
481			 * shows that the transmit was successful.  Since
482			 * AutoRelease is being used, a successful transmit
483			 * should not result in a packet on the completion
484			 * FIFO.  Also, that packet doesn't seem to want
485			 * to be acknowledged.  If this occurs, just reset
486			 * the TX FIFOs.
487			 */
488#if 1
489			if (smc->b2.ist & IST_TX_EMPTY) {
490				smc->b2.mmucr = MMUCR_RESET_TX;
491				sc->sc_intctl &= ~(MSK_TX_EMPTY | MSK_TX);
492				ifp->if_timer = 0;
493			}
494#endif
495#ifdef ESDEBUG
496			++estxints;	/* count IST_TX with TX enabled */
497#endif
498		}
499		smc->b2.pnr = save_pnr;
500		smc->b2.ptr = save_ptr;
501		smc->b2.ist = ACK_TX;
502
503		if ((smc->b2.fifo & FIFO_TEMPTY) == 0 && n++ < 32) {
504#if 0 /* XXXX */
505			printf("%s: multiple TX int(%2d) pnr %02x ist %02x fifo %04x",
506			    sc->sc_dev.dv_xname, n, tx_pnr, smc->b2.ist, smc->b2.fifo);
507			smc->w2.istmsk = ACK_TX << 8;
508			printf(" %04x\n", smc->b2.fifo);
509#endif
510			if (tx_pnr != (smc->b2.fifo >> 8))
511				goto zzzz;
512		}
513	}
514	if (intact & IST_EPHINT) {
515		ifp->if_oerrors++;
516		esreset(sc);
517	}
518	/* output packets */
519	estint(sc);
520#ifdef ESDEBUG
521	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
522		printf("%s: intr+++ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
523		    smc->b2.bsr);
524		smc->b2.bsr = BSR_BANK2;
525	}
526#endif
527	smc->b2.msk = sc->sc_intctl;
528#ifdef ESDEBUG
529	if (--sc->sc_intbusy) {
530		printf("%s: esintr busy on exit\n", sc->sc_dev.dv_xname);
531		panic("esintr busy on exit");
532	}
533#endif
534	splx(s);
535	return (1);
536}
537
538void
539esrint(struct es_softc *sc)
540{
541	union smcregs *smc = sc->sc_base;
542	u_short len;
543	short cnt;
544	u_short pktctlw, pktlen, *buf;
545	volatile u_short *data;
546#if 0
547	u_long *lbuf;
548	volatile u_long *ldata;
549#endif
550	struct ifnet *ifp;
551	struct mbuf *top, **mp, *m;
552#ifdef USEPKTBUF
553	u_char *b, pktbuf[1530];
554#endif
555#ifdef ESDEBUG
556	int i;
557#endif
558
559	ifp = &sc->sc_ethercom.ec_if;
560#ifdef ESDEBUG
561	if (esdebug)
562		printf ("%s: esrint fifo %04x", sc->sc_dev.dv_xname,
563		    smc->b2.fifo);
564	if (sc->sc_smcbusy++) {
565		printf("%s: esrint re-entered\n", sc->sc_dev.dv_xname);
566		panic("esrint re-entered");
567	}
568	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
569		printf("%s: rint BSR not 2: %04x\n", sc->sc_dev.dv_xname,
570		    smc->b2.bsr);
571		smc->b2.bsr = BSR_BANK2;
572	}
573#endif
574	data = (volatile u_short *)&smc->b2.data;
575	smc->b2.ptr = PTR_RCV | PTR_AUTOINCR | PTR_READ | SWAP(0x0002);
576	(void) smc->b2.mmucr;
577#ifdef ESDEBUG
578	if (esdebug)
579		printf ("->%04x", smc->b2.fifo);
580#endif
581	len = *data;
582	len = SWAP(len);	/* Careful of macro side-effects */
583#ifdef ESDEBUG
584	if (esdebug)
585		printf (" length %d", len);
586#endif
587	smc->b2.ptr = PTR_RCV | (PTR_AUTOINCR + PTR_READ) | SWAP(0x0000);
588	(void) smc->b2.mmucr;
589	pktctlw = *data;
590	pktlen = *data;
591	pktctlw = SWAP(pktctlw);
592	pktlen = SWAP(pktlen) - 6;
593	if (pktctlw & RFSW_ODDFRM)
594		pktlen++;
595	if (len > 1530) {
596		printf("%s: Corrupted packet length-sts %04x bytcnt %04x len %04x bank %04x\n",
597		    sc->sc_dev.dv_xname, pktctlw, pktlen, len, smc->b2.bsr);
598		/* XXX ignore packet, or just truncate? */
599#if defined(ESDEBUG) && defined(DDB)
600		if ((smc->b2.bsr & BSR_MASK) != BSR_BANK2)
601			Debugger();
602#endif
603		smc->b2.bsr = BSR_BANK2;
604		smc->b2.mmucr = MMUCR_REMRLS_RX;
605		while (smc->b2.mmucr & MMUCR_BUSY)
606			;
607		++ifp->if_ierrors;
608#ifdef ESDEBUG
609		if (--sc->sc_smcbusy) {
610			printf("%s: esrintr busy on bad packet exit\n",
611			    sc->sc_dev.dv_xname);
612			panic("esrintr busy on exit");
613		}
614#endif
615		return;
616	}
617#ifdef USEPKTBUF
618#if 0
619	lbuf = (u_long *) pktbuf;
620	ldata = (u_long *)data;
621	cnt = (len - 4) / 4;
622	while (cnt--)
623		*lbuf++ = *ldata;
624	if ((len - 4) & 2) {
625		buf = (u_short *) lbuf;
626		*buf = *data;
627	}
628#else
629	buf = (u_short *)pktbuf;
630	cnt = (len - 4) / 2;
631	while (cnt--)
632		*buf++ = *data;
633#endif
634	smc->b2.mmucr = MMUCR_REMRLS_RX;
635	while (smc->b2.mmucr & MMUCR_BUSY)
636		;
637#ifdef ESDEBUG
638	if (pktctlw & (RFSW_ALGNERR | RFSW_BADCRC | RFSW_TOOLNG | RFSW_TOOSHORT)) {
639		printf ("%s: Packet error %04x\n", sc->sc_dev.dv_xname, pktctlw);
640		/* count input error? */
641	}
642	if (esdebug) {
643		printf (" pktctlw %04x pktlen %04x fifo %04x\n", pktctlw, pktlen,
644		    smc->b2.fifo);
645		for (i = 0; i < pktlen; ++i)
646			printf ("%02x%s", pktbuf[i], ((i & 31) == 31) ? "\n" :
647			    "");
648		if (i & 31)
649			printf ("\n");
650	}
651#endif
652#else	/* USEPKTBUF */
653	/* XXX copy directly from controller to mbuf */
654#ifdef ESDEBUG
655	if (pktctlw & (RFSW_ALGNERR | RFSW_BADCRC | RFSW_TOOLNG | RFSW_TOOSHORT)) {
656		printf ("%s: Packet error %04x\n", sc->sc_dev.dv_xname, pktctlw);
657		/* count input error? */
658	}
659	if (esdebug) {
660		printf (" pktctlw %04x pktlen %04x fifo %04x\n", pktctlw, pktlen,
661		    smc->b2.fifo);
662	}
663#endif
664#endif /* USEPKTBUF */
665	ifp->if_ipackets++;
666	MGETHDR(m, M_DONTWAIT, MT_DATA);
667	if (m == NULL)
668		return;
669	m->m_pkthdr.rcvif = ifp;
670	m->m_pkthdr.len = pktlen;
671	len = MHLEN;
672	top = NULL;
673	mp = &top;
674#ifdef USEPKTBUF
675	b = pktbuf;
676#endif
677	while (pktlen > 0) {
678		if (top) {
679			MGET(m, M_DONTWAIT, MT_DATA);
680			if (m == 0) {
681				m_freem(top);
682				return;
683			}
684			len = MLEN;
685		}
686		if (pktlen >= MINCLSIZE) {
687			MCLGET(m, M_DONTWAIT);
688			if (m->m_flags & M_EXT)
689				len = MCLBYTES;
690		}
691		m->m_len = len = min(pktlen, len);
692#ifdef USEPKTBUF
693		memcpy(mtod(m, void *), (void *)b, len);
694		b += len;
695#else	/* USEPKTBUF */
696		buf = mtod(m, u_short *);
697		cnt = len / 2;
698		while (cnt--)
699			*buf++ = *data;
700		if (len & 1)
701			*buf = *data;	/* XXX should be byte store */
702#ifdef ESDEBUG
703		if (esdebug) {
704			buf = mtod(m, u_short *);
705			for (i = 0; i < len; ++i)
706				printf ("%02x%s", ((u_char *)buf)[i],
707				    ((i & 31) == 31) ? "\n" : "");
708			if (i & 31)
709				printf ("\n");
710		}
711#endif
712#endif	/* USEPKTBUF */
713		pktlen -= len;
714		*mp = m;
715		mp = &m->m_next;
716	}
717#ifndef USEPKTBUF
718	smc->b2.mmucr = MMUCR_REMRLS_RX;
719	while (smc->b2.mmucr & MMUCR_BUSY)
720		;
721#endif
722	/*
723	 * Check if there's a BPF listener on this interface.  If so, hand off
724	 * the raw packet to bpf.
725	 */
726	if (ifp->if_bpf)
727		bpf_ops->bpf_mtap(ifp->if_bpf, top);
728	(*ifp->if_input)(ifp, top);
729#ifdef ESDEBUG
730	if (--sc->sc_smcbusy) {
731		printf("%s: esintr busy on exit\n", sc->sc_dev.dv_xname);
732		panic("esintr busy on exit");
733	}
734#endif
735}
736
737void
738estint(struct es_softc *sc)
739{
740
741	esstart(&sc->sc_ethercom.ec_if);
742}
743
744void
745esstart(struct ifnet *ifp)
746{
747	struct es_softc *sc = ifp->if_softc;
748	union smcregs *smc = sc->sc_base;
749	struct mbuf *m0, *m;
750#ifdef USEPKTBUF
751	u_short pktbuf[ETHERMTU + 2];
752#else
753	u_short oddbyte, needbyte;
754#endif
755	u_short pktctlw, pktlen;
756	u_short *buf;
757	volatile u_short *data;
758#if 0
759	u_long *lbuf;
760	volatile u_long *ldata;
761#endif
762	short cnt;
763	int i;
764	u_char active_pnr;
765
766	if ((sc->sc_ethercom.ec_if.if_flags & (IFF_RUNNING | IFF_OACTIVE)) !=
767	    IFF_RUNNING)
768		return;
769
770#ifdef ESDEBUG
771	if (sc->sc_smcbusy++) {
772		printf("%s: esstart re-entered\n", sc->sc_dev.dv_xname);
773		panic("esstart re-entred");
774	}
775	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
776		printf("%s: esstart BSR not 2: %04x\n", sc->sc_dev.dv_xname,
777		    smc->b2.bsr);
778		smc->b2.bsr = BSR_BANK2;
779	}
780#endif
781	for (;;) {
782#ifdef ESDEBUG
783		u_short start_ptr, end_ptr;
784#endif
785		/*
786		 * Sneak a peek at the next packet to get the length
787		 * and see if the SMC 91C90 can accept it.
788		 */
789		m = sc->sc_ethercom.ec_if.if_snd.ifq_head;
790		if (!m)
791			break;
792#ifdef ESDEBUG
793		if (esdebug && (m->m_next || m->m_len & 1))
794			printf("%s: esstart m_next %p m_len %d\n",
795			    sc->sc_dev.dv_xname, m->m_next, m->m_len);
796#endif
797		for (m0 = m, pktlen = 0; m0; m0 = m0->m_next)
798			pktlen += m0->m_len;
799		pktctlw = 0;
800		pktlen += 4;
801		if (pktlen & 1)
802			++pktlen;	/* control byte after last byte */
803		else
804			pktlen += 2;	/* control byte after pad byte */
805		smc->b2.mmucr = MMUCR_ALLOC | (pktlen & 0x0700);
806		for (i = 0; i <= 5; ++i)
807			if ((smc->b2.arr & ARR_FAILED) == 0)
808				break;
809		if (smc->b2.arr & ARR_FAILED) {
810			sc->sc_ethercom.ec_if.if_flags |= IFF_OACTIVE;
811			sc->sc_intctl |= MSK_ALLOC;
812			sc->sc_ethercom.ec_if.if_timer = 5;
813			break;
814		}
815		active_pnr = smc->b2.pnr = smc->b2.arr;
816
817#ifdef ESDEBUG
818		while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
819			printf("%s: esstart+ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
820			    smc->b2.bsr);
821			smc->b2.bsr = BSR_BANK2;
822		}
823#endif
824		IF_DEQUEUE(&sc->sc_ethercom.ec_if.if_snd, m);
825		smc->b2.ptr = PTR_AUTOINCR;
826		(void) smc->b2.mmucr;
827		data = (volatile u_short *)&smc->b2.data;
828		*data = SWAP(pktctlw);
829		*data = SWAP(pktlen);
830#ifdef ESDEBUG
831		while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
832			printf("%s: esstart++ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
833			    smc->b2.bsr);
834			smc->b2.bsr = BSR_BANK2;
835		}
836#endif
837#ifdef USEPKTBUF
838		i = 0;
839		for (m0 = m; m; m = m->m_next) {
840			memcpy((char *)pktbuf + i, mtod(m, void *), m->m_len);
841			i += m->m_len;
842		}
843
844		if (i & 1)	/* Figure out where to put control byte */
845			pktbuf[i/2] = (pktbuf[i/2] & 0xff00) | CTLB_ODD;
846		else
847			pktbuf[i/2] = 0;
848		pktlen -= 4;
849#ifdef ESDEBUG
850		if (pktlen > sizeof(pktbuf) && i > (sizeof(pktbuf) * 2))
851			printf("%s: esstart packet longer than pktbuf\n",
852			    sc->sc_dev.dv_xname);
853#endif
854#if 0 /* doesn't quite work? */
855		lbuf = (u_long *)(pktbuf);
856		ldata = (u_long *)data;
857		cnt = pktlen / 4;
858		while(cnt--)
859			*ldata = *lbuf++;
860		if (pktlen & 2) {
861			buf = (u_short *)lbuf;
862			*data = *buf;
863		}
864#else
865#ifdef ESDEBUG
866		while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
867			printf("%s: esstart++2 BSR not 2: %04x\n", sc->sc_dev.dv_xname,
868			    smc->b2.bsr);
869			smc->b2.bsr = BSR_BANK2;
870		}
871		start_ptr = SWAP(smc->b2.ptr);	/* save PTR before copy */
872#endif
873		buf = pktbuf;
874		cnt = pktlen / 2;
875		while (cnt--)
876			*data = *buf++;
877#ifdef ESDEBUG
878		end_ptr = SWAP(smc->b2.ptr);	/* save PTR after copy */
879#endif
880#endif
881#else	/* USEPKTBUF */
882		pktctlw = 0;
883		oddbyte = needbyte = 0;
884		for (m0 = m; m; m = m->m_next) {
885			buf = mtod(m, u_short *);
886			cnt = m->m_len / 2;
887			if (needbyte) {
888				oddbyte |= *buf >> 8;
889				*data = oddbyte;
890			}
891			while (cnt--)
892				*data = *buf++;
893			if (m->m_len & 1)
894				pktctlw = (*buf & 0xff00) | CTLB_ODD;
895			if (m->m_len & 1 && m->m_next)
896				printf("%s: esstart odd byte count in mbuf\n",
897				    sc->sc_dev.dv_xname);
898		}
899		*data = pktctlw;
900#endif	/* USEPKTBUF */
901		while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
902			/*
903			 * The bank select register has changed.  This seems
904			 * to happen with my A2000/Zeus once in a while.  It
905			 * appears that the Ethernet chip resets while
906			 * copying the transmit buffer.  Requeue the current
907			 * transmit buffer and reinitialize the interface.
908			 * The initialize routine will take care of
909			 * retransmitting the buffer.  mhitch
910			 */
911#ifdef DIAGNOSTIC
912			printf("%s: esstart+++ BSR not 2: %04x\n",
913			    sc->sc_dev.dv_xname, smc->b2.bsr);
914#endif
915			smc->b2.bsr = BSR_BANK2;
916#ifdef ESDEBUG
917			printf("start_ptr %04x end_ptr %04x cur ptr %04x\n",
918			    start_ptr, end_ptr, SWAP(smc->b2.ptr));
919			--sc->sc_smcbusy;
920#endif
921			IF_PREPEND(&sc->sc_ethercom.ec_if.if_snd, m0);
922			esinit(sc);	/* It's really hosed - reset */
923			return;
924		}
925		smc->b2.mmucr = MMUCR_ENQ_TX;
926		if (smc->b2.pnr != active_pnr)
927			printf("%s: esstart - PNR changed %x->%x\n",
928			    sc->sc_dev.dv_xname, active_pnr, smc->b2.pnr);
929		if (sc->sc_ethercom.ec_if.if_bpf)
930			bpf_ops->bpf_mtap(sc->sc_ethercom.ec_if.if_bpf, m0);
931		m_freem(m0);
932		sc->sc_ethercom.ec_if.if_opackets++;	/* move to interrupt? */
933		sc->sc_intctl |= MSK_TX_EMPTY | MSK_TX;
934		sc->sc_ethercom.ec_if.if_timer = 5;
935	}
936	smc->b2.msk = sc->sc_intctl;
937#ifdef ESDEBUG
938	while ((smc->b2.bsr & BSR_MASK) != BSR_BANK2) {
939		printf("%s: esstart++++ BSR not 2: %04x\n", sc->sc_dev.dv_xname,
940		    smc->b2.bsr);
941		smc->b2.bsr = BSR_BANK2;
942	}
943	if (--sc->sc_smcbusy) {
944		printf("%s: esstart busy on exit\n", sc->sc_dev.dv_xname);
945		panic("esstart busy on exit");
946	}
947#endif
948}
949
950int
951esioctl(struct ifnet *ifp, u_long cmd, void *data)
952{
953	struct es_softc *sc = ifp->if_softc;
954	register struct ifaddr *ifa = (struct ifaddr *)data;
955	struct ifreq *ifr = (struct ifreq *)data;
956	int s, error = 0;
957
958	s = splnet();
959
960	switch (cmd) {
961
962	case SIOCINITIFADDR:
963		ifp->if_flags |= IFF_UP;
964
965		switch (ifa->ifa_addr->sa_family) {
966#ifdef INET
967		case AF_INET:
968			esinit(sc);
969			arp_ifinit(ifp, ifa);
970			break;
971#endif
972#ifdef NS
973		case AF_NS:
974		    {
975			register struct ns_addr *ina = &IA_SNS(ifa)->sns_addr;
976
977			if (ns_nullhost(*ina))
978				ina->x_host =
979				    *(union ns_host *)LLADDR(ifp->if_sadl);
980			else
981				bcopy(ina->x_host.c_host,
982				    LLADDR(ifp->if_sadl), ETHER_ADDR_LEN);
983			/* Set new address. */
984			esinit(sc);
985			break;
986		    }
987#endif
988		default:
989			esinit(sc);
990			break;
991		}
992		break;
993
994	case SIOCSIFFLAGS:
995		if ((error = ifioctl_common(ifp, cmd, data)) != 0)
996			break;
997		/* XXX see the comment in ed_ioctl() about code re-use */
998		/*
999		 * If interface is marked down and it is running, then stop it
1000		 */
1001		if ((ifp->if_flags & IFF_UP) == 0 &&
1002		    (ifp->if_flags & IFF_RUNNING) != 0) {
1003			/*
1004			 * If interface is marked down and it is running, then
1005			 * stop it.
1006			 */
1007			esstop(sc);
1008			ifp->if_flags &= ~IFF_RUNNING;
1009		} else if ((ifp->if_flags & IFF_UP) != 0 &&
1010		    	   (ifp->if_flags & IFF_RUNNING) == 0) {
1011			/*
1012			 * If interface is marked up and it is stopped, then
1013			 * start it.
1014			 */
1015			esinit(sc);
1016		} else {
1017			/*
1018			 * Reset the interface to pick up changes in any other
1019			 * flags that affect hardware registers.
1020			 */
1021			esstop(sc);
1022			esinit(sc);
1023		}
1024#ifdef ESDEBUG
1025		if (ifp->if_flags & IFF_DEBUG)
1026			esdebug = sc->sc_debug = 1;
1027		else
1028			esdebug = sc->sc_debug = 0;
1029#endif
1030		break;
1031
1032	case SIOCADDMULTI:
1033	case SIOCDELMULTI:
1034		if ((error = ether_ioctl(ifp, cmd, data)) == ENETRESET) {
1035			/*
1036			 * Multicast list has changed; set the hardware filter
1037			 * accordingly.
1038			 */
1039			if (ifp->if_flags & IFF_RUNNING) {
1040				/* XXX */
1041			}
1042			error = 0;
1043		}
1044		break;
1045
1046	case SIOCGIFMEDIA:
1047	case SIOCSIFMEDIA:
1048		error = ifmedia_ioctl(ifp, ifr, &sc->sc_media, cmd);
1049		break;
1050
1051	default:
1052		error = ether_ioctl(ifp, cmd, data);
1053		break;
1054	}
1055
1056	splx(s);
1057	return (error);
1058}
1059
1060/*
1061 * Reset the interface.
1062 */
1063void
1064esreset(struct es_softc *sc)
1065{
1066	int s;
1067
1068	s = splnet();
1069	esstop(sc);
1070	esinit(sc);
1071	splx(s);
1072}
1073
1074void
1075eswatchdog(struct ifnet *ifp)
1076{
1077	struct es_softc *sc = ifp->if_softc;
1078
1079	log(LOG_ERR, "%s: device timeout\n", sc->sc_dev.dv_xname);
1080	++ifp->if_oerrors;
1081
1082	esreset(sc);
1083}
1084
1085int
1086esmediachange(struct ifnet *ifp)
1087{
1088	return 0;
1089}
1090
1091void
1092esmediastatus(struct ifnet *ifp, struct ifmediareq *ifmr)
1093{
1094}
1095