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