Home | History | Annotate | Line # | Download | only in pci
if_xge.c revision 1.19.6.5
      1  1.19.6.5     skrll /*      $NetBSD: if_xge.c,v 1.19.6.5 2017/02/05 13:40:30 skrll Exp $ */
      2       1.1     ragge 
      3       1.1     ragge /*
      4       1.1     ragge  * Copyright (c) 2004, SUNET, Swedish University Computer Network.
      5       1.1     ragge  * All rights reserved.
      6       1.1     ragge  *
      7       1.1     ragge  * Written by Anders Magnusson for SUNET, Swedish University Computer Network.
      8       1.1     ragge  *
      9       1.1     ragge  * Redistribution and use in source and binary forms, with or without
     10       1.1     ragge  * modification, are permitted provided that the following conditions
     11       1.1     ragge  * are met:
     12       1.1     ragge  * 1. Redistributions of source code must retain the above copyright
     13       1.1     ragge  *    notice, this list of conditions and the following disclaimer.
     14       1.1     ragge  * 2. Redistributions in binary form must reproduce the above copyright
     15       1.1     ragge  *    notice, this list of conditions and the following disclaimer in the
     16       1.1     ragge  *    documentation and/or other materials provided with the distribution.
     17       1.1     ragge  * 3. All advertising materials mentioning features or use of this software
     18       1.1     ragge  *    must display the following acknowledgement:
     19       1.1     ragge  *      This product includes software developed for the NetBSD Project by
     20       1.1     ragge  *      SUNET, Swedish University Computer Network.
     21       1.1     ragge  * 4. The name of SUNET may not be used to endorse or promote products
     22       1.1     ragge  *    derived from this software without specific prior written permission.
     23       1.1     ragge  *
     24       1.1     ragge  * THIS SOFTWARE IS PROVIDED BY SUNET ``AS IS'' AND
     25       1.1     ragge  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
     26       1.1     ragge  * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
     27       1.1     ragge  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL SUNET
     28       1.1     ragge  * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
     29       1.1     ragge  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
     30       1.1     ragge  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
     31       1.1     ragge  * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
     32       1.1     ragge  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
     33       1.1     ragge  * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
     34       1.1     ragge  * POSSIBILITY OF SUCH DAMAGE.
     35       1.1     ragge  */
     36       1.1     ragge 
     37       1.1     ragge /*
     38       1.1     ragge  * Device driver for the S2io Xframe Ten Gigabit Ethernet controller.
     39       1.1     ragge  *
     40       1.1     ragge  * TODO (in no specific order):
     41       1.1     ragge  *	HW VLAN support.
     42       1.1     ragge  *	IPv6 HW cksum.
     43       1.1     ragge  */
     44       1.1     ragge 
     45       1.1     ragge #include <sys/cdefs.h>
     46  1.19.6.5     skrll __KERNEL_RCSID(0, "$NetBSD: if_xge.c,v 1.19.6.5 2017/02/05 13:40:30 skrll Exp $");
     47       1.1     ragge 
     48       1.1     ragge 
     49       1.1     ragge #include <sys/param.h>
     50       1.1     ragge #include <sys/systm.h>
     51       1.1     ragge #include <sys/mbuf.h>
     52       1.1     ragge #include <sys/malloc.h>
     53       1.1     ragge #include <sys/kernel.h>
     54       1.1     ragge #include <sys/socket.h>
     55       1.1     ragge #include <sys/device.h>
     56       1.1     ragge 
     57       1.1     ragge #include <net/if.h>
     58       1.1     ragge #include <net/if_dl.h>
     59       1.1     ragge #include <net/if_media.h>
     60       1.1     ragge #include <net/if_ether.h>
     61       1.1     ragge 
     62       1.1     ragge #include <net/bpf.h>
     63       1.1     ragge 
     64       1.6        ad #include <sys/bus.h>
     65       1.6        ad #include <sys/intr.h>
     66       1.1     ragge #include <machine/endian.h>
     67       1.1     ragge 
     68       1.1     ragge #include <dev/mii/mii.h>
     69       1.1     ragge #include <dev/mii/miivar.h>
     70       1.1     ragge 
     71       1.1     ragge #include <dev/pci/pcivar.h>
     72       1.1     ragge #include <dev/pci/pcireg.h>
     73       1.1     ragge #include <dev/pci/pcidevs.h>
     74       1.1     ragge 
     75       1.1     ragge #include <sys/proc.h>
     76       1.1     ragge 
     77       1.1     ragge #include <dev/pci/if_xgereg.h>
     78       1.1     ragge 
     79       1.1     ragge /*
     80       1.1     ragge  * Some tunable constants, tune with care!
     81       1.1     ragge  */
     82       1.1     ragge #define RX_MODE		RX_MODE_1  /* Receive mode (buffer usage, see below) */
     83       1.1     ragge #define NRXDESCS	1016	   /* # of receive descriptors (requested) */
     84       1.1     ragge #define NTXDESCS	8192	   /* Number of transmit descriptors */
     85       1.1     ragge #define NTXFRAGS	100	   /* Max fragments per packet */
     86       1.1     ragge #define XGE_EVENT_COUNTERS	   /* Instrumentation */
     87       1.1     ragge 
     88       1.1     ragge /*
     89       1.1     ragge  * Receive buffer modes; 1, 3 or 5 buffers.
     90       1.1     ragge  */
     91       1.1     ragge #define RX_MODE_1 1
     92       1.1     ragge #define RX_MODE_3 3
     93       1.1     ragge #define RX_MODE_5 5
     94       1.1     ragge 
     95       1.1     ragge /*
     96       1.1     ragge  * Use clever macros to avoid a bunch of #ifdef's.
     97       1.1     ragge  */
     98       1.1     ragge #define XCONCAT3(x,y,z) x ## y ## z
     99       1.1     ragge #define CONCAT3(x,y,z) XCONCAT3(x,y,z)
    100       1.1     ragge #define NDESC_BUFMODE CONCAT3(NDESC_,RX_MODE,BUFMODE)
    101       1.1     ragge #define rxd_4k CONCAT3(rxd,RX_MODE,_4k)
    102       1.1     ragge #define rxdesc ___CONCAT(rxd,RX_MODE)
    103       1.1     ragge 
    104       1.1     ragge #define NEXTTX(x)	(((x)+1) % NTXDESCS)
    105       1.1     ragge #define NRXFRAGS	RX_MODE /* hardware imposed frags */
    106       1.1     ragge #define NRXPAGES	((NRXDESCS/NDESC_BUFMODE)+1)
    107       1.1     ragge #define NRXREAL		(NRXPAGES*NDESC_BUFMODE)
    108       1.1     ragge #define RXMAPSZ		(NRXPAGES*PAGE_SIZE)
    109       1.1     ragge 
    110       1.1     ragge #ifdef XGE_EVENT_COUNTERS
    111       1.1     ragge #define XGE_EVCNT_INCR(ev)	(ev)->ev_count++
    112       1.1     ragge #else
    113       1.1     ragge #define XGE_EVCNT_INCR(ev)	/* nothing */
    114       1.1     ragge #endif
    115       1.1     ragge 
    116       1.1     ragge /*
    117       1.1     ragge  * Magics to fix a bug when the mac address can't be read correctly.
    118       1.1     ragge  * Comes from the Linux driver.
    119       1.1     ragge  */
    120       1.1     ragge static uint64_t fix_mac[] = {
    121       1.1     ragge 	0x0060000000000000ULL, 0x0060600000000000ULL,
    122       1.1     ragge 	0x0040600000000000ULL, 0x0000600000000000ULL,
    123       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    124       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    125       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    126       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    127       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    128       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    129       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    130       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    131       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    132       1.1     ragge 	0x0020600000000000ULL, 0x0060600000000000ULL,
    133       1.1     ragge 	0x0020600000000000ULL, 0x0000600000000000ULL,
    134       1.1     ragge 	0x0040600000000000ULL, 0x0060600000000000ULL,
    135       1.1     ragge };
    136       1.1     ragge 
    137       1.1     ragge 
    138       1.1     ragge struct xge_softc {
    139      1.17       chs 	device_t sc_dev;
    140       1.1     ragge 	struct ethercom sc_ethercom;
    141       1.1     ragge #define sc_if sc_ethercom.ec_if
    142       1.1     ragge 	bus_dma_tag_t sc_dmat;
    143       1.1     ragge 	bus_space_tag_t sc_st;
    144       1.1     ragge 	bus_space_handle_t sc_sh;
    145       1.1     ragge 	bus_space_tag_t sc_txt;
    146       1.1     ragge 	bus_space_handle_t sc_txh;
    147       1.1     ragge 	void *sc_ih;
    148       1.1     ragge 
    149       1.1     ragge 	struct ifmedia xena_media;
    150       1.1     ragge 	pcireg_t sc_pciregs[16];
    151       1.1     ragge 
    152       1.1     ragge 	/* Transmit structures */
    153       1.1     ragge 	struct txd *sc_txd[NTXDESCS];	/* transmit frags array */
    154       1.1     ragge 	bus_addr_t sc_txdp[NTXDESCS];	/* bus address of transmit frags */
    155       1.1     ragge 	bus_dmamap_t sc_txm[NTXDESCS];	/* transmit frags map */
    156       1.1     ragge 	struct mbuf *sc_txb[NTXDESCS];	/* transmit mbuf pointer */
    157       1.1     ragge 	int sc_nexttx, sc_lasttx;
    158       1.1     ragge 	bus_dmamap_t sc_txmap;		/* transmit descriptor map */
    159       1.1     ragge 
    160       1.1     ragge 	/* Receive data */
    161       1.1     ragge 	bus_dmamap_t sc_rxmap;		/* receive descriptor map */
    162       1.1     ragge 	struct rxd_4k *sc_rxd_4k[NRXPAGES]; /* receive desc pages */
    163       1.1     ragge 	bus_dmamap_t sc_rxm[NRXREAL];	/* receive buffer map */
    164       1.1     ragge 	struct mbuf *sc_rxb[NRXREAL];	/* mbufs on receive descriptors */
    165       1.1     ragge 	int sc_nextrx;			/* next descriptor to check */
    166       1.1     ragge 
    167       1.1     ragge #ifdef XGE_EVENT_COUNTERS
    168       1.1     ragge 	struct evcnt sc_intr;	/* # of interrupts */
    169       1.1     ragge 	struct evcnt sc_txintr;	/* # of transmit interrupts */
    170       1.1     ragge 	struct evcnt sc_rxintr;	/* # of receive interrupts */
    171       1.1     ragge 	struct evcnt sc_txqe;	/* # of xmit intrs when board queue empty */
    172       1.1     ragge #endif
    173       1.1     ragge };
    174       1.1     ragge 
    175      1.12    cegger static int xge_match(device_t parent, cfdata_t cf, void *aux);
    176      1.12    cegger static void xge_attach(device_t parent, device_t self, void *aux);
    177       1.1     ragge static int xge_alloc_txmem(struct xge_softc *);
    178       1.1     ragge static int xge_alloc_rxmem(struct xge_softc *);
    179       1.1     ragge static void xge_start(struct ifnet *);
    180       1.1     ragge static void xge_stop(struct ifnet *, int);
    181       1.1     ragge static int xge_add_rxbuf(struct xge_softc *, int);
    182       1.1     ragge static void xge_mcast_filter(struct xge_softc *sc);
    183       1.1     ragge static int xge_setup_xgxs(struct xge_softc *sc);
    184       1.5  christos static int xge_ioctl(struct ifnet *ifp, u_long cmd, void *data);
    185       1.1     ragge static int xge_init(struct ifnet *ifp);
    186       1.1     ragge static void xge_ifmedia_status(struct ifnet *, struct ifmediareq *);
    187       1.1     ragge static int xge_xgmii_mediachange(struct ifnet *);
    188       1.1     ragge static int xge_intr(void  *);
    189       1.1     ragge 
    190       1.1     ragge /*
    191       1.1     ragge  * Helpers to address registers.
    192       1.1     ragge  */
    193       1.1     ragge #define PIF_WCSR(csr, val)	pif_wcsr(sc, csr, val)
    194       1.1     ragge #define PIF_RCSR(csr)		pif_rcsr(sc, csr)
    195       1.1     ragge #define TXP_WCSR(csr, val)	txp_wcsr(sc, csr, val)
    196       1.1     ragge #define PIF_WKEY(csr, val)	pif_wkey(sc, csr, val)
    197       1.1     ragge 
    198       1.1     ragge static inline void
    199       1.1     ragge pif_wcsr(struct xge_softc *sc, bus_size_t csr, uint64_t val)
    200       1.1     ragge {
    201       1.1     ragge 	uint32_t lval, hval;
    202       1.1     ragge 
    203       1.1     ragge 	lval = val&0xffffffff;
    204       1.1     ragge 	hval = val>>32;
    205      1.18  christos 	bus_space_write_4(sc->sc_st, sc->sc_sh, csr, lval);
    206       1.1     ragge 	bus_space_write_4(sc->sc_st, sc->sc_sh, csr+4, hval);
    207       1.1     ragge }
    208       1.1     ragge 
    209       1.1     ragge static inline uint64_t
    210       1.1     ragge pif_rcsr(struct xge_softc *sc, bus_size_t csr)
    211       1.1     ragge {
    212       1.1     ragge 	uint64_t val, val2;
    213       1.1     ragge 	val = bus_space_read_4(sc->sc_st, sc->sc_sh, csr);
    214       1.1     ragge 	val2 = bus_space_read_4(sc->sc_st, sc->sc_sh, csr+4);
    215       1.1     ragge 	val |= (val2 << 32);
    216       1.1     ragge 	return val;
    217       1.1     ragge }
    218       1.1     ragge 
    219       1.1     ragge static inline void
    220       1.1     ragge txp_wcsr(struct xge_softc *sc, bus_size_t csr, uint64_t val)
    221       1.1     ragge {
    222       1.1     ragge 	uint32_t lval, hval;
    223       1.1     ragge 
    224       1.1     ragge 	lval = val&0xffffffff;
    225       1.1     ragge 	hval = val>>32;
    226      1.18  christos 	bus_space_write_4(sc->sc_txt, sc->sc_txh, csr, lval);
    227       1.1     ragge 	bus_space_write_4(sc->sc_txt, sc->sc_txh, csr+4, hval);
    228       1.1     ragge }
    229       1.1     ragge 
    230       1.1     ragge 
    231       1.1     ragge static inline void
    232       1.1     ragge pif_wkey(struct xge_softc *sc, bus_size_t csr, uint64_t val)
    233       1.1     ragge {
    234       1.1     ragge 	uint32_t lval, hval;
    235       1.1     ragge 
    236       1.1     ragge 	lval = val&0xffffffff;
    237       1.1     ragge 	hval = val>>32;
    238       1.1     ragge 	PIF_WCSR(RMAC_CFG_KEY, RMAC_KEY_VALUE);
    239      1.18  christos 	bus_space_write_4(sc->sc_st, sc->sc_sh, csr, lval);
    240       1.1     ragge 	PIF_WCSR(RMAC_CFG_KEY, RMAC_KEY_VALUE);
    241       1.1     ragge 	bus_space_write_4(sc->sc_st, sc->sc_sh, csr+4, hval);
    242       1.1     ragge }
    243       1.1     ragge 
    244       1.1     ragge 
    245      1.17       chs CFATTACH_DECL_NEW(xge, sizeof(struct xge_softc),
    246       1.1     ragge     xge_match, xge_attach, NULL, NULL);
    247       1.1     ragge 
    248      1.17       chs #define XNAME device_xname(sc->sc_dev)
    249       1.1     ragge 
    250       1.1     ragge #define XGE_RXSYNC(desc, what) \
    251       1.1     ragge 	bus_dmamap_sync(sc->sc_dmat, sc->sc_rxmap, \
    252       1.1     ragge 	(desc/NDESC_BUFMODE) * XGE_PAGE + sizeof(struct rxdesc) * \
    253       1.1     ragge 	(desc%NDESC_BUFMODE), sizeof(struct rxdesc), what)
    254       1.1     ragge #define XGE_RXD(desc)	&sc->sc_rxd_4k[desc/NDESC_BUFMODE]-> \
    255       1.1     ragge 	r4_rxd[desc%NDESC_BUFMODE]
    256       1.1     ragge 
    257       1.1     ragge /*
    258       1.1     ragge  * Non-tunable constants.
    259       1.1     ragge  */
    260       1.1     ragge #define XGE_MAX_MTU		9600
    261       1.1     ragge #define	XGE_IP_MAXPACKET	65535	/* same as IP_MAXPACKET */
    262       1.1     ragge 
    263       1.1     ragge static int
    264      1.12    cegger xge_match(device_t parent, cfdata_t cf, void *aux)
    265       1.1     ragge {
    266       1.1     ragge 	struct pci_attach_args *pa = aux;
    267       1.1     ragge 
    268       1.1     ragge 	if (PCI_VENDOR(pa->pa_id) == PCI_VENDOR_S2IO &&
    269       1.1     ragge 	    PCI_PRODUCT(pa->pa_id) == PCI_PRODUCT_S2IO_XFRAME)
    270       1.1     ragge 		return (1);
    271       1.1     ragge 
    272       1.1     ragge 	return (0);
    273       1.1     ragge }
    274       1.1     ragge 
    275       1.1     ragge void
    276      1.12    cegger xge_attach(device_t parent, device_t self, void *aux)
    277       1.1     ragge {
    278       1.1     ragge 	struct pci_attach_args *pa = aux;
    279       1.1     ragge 	struct xge_softc *sc;
    280       1.1     ragge 	struct ifnet *ifp;
    281       1.1     ragge 	pcireg_t memtype;
    282       1.1     ragge 	pci_intr_handle_t ih;
    283       1.1     ragge 	const char *intrstr = NULL;
    284       1.1     ragge 	pci_chipset_tag_t pc = pa->pa_pc;
    285       1.1     ragge 	uint8_t enaddr[ETHER_ADDR_LEN];
    286       1.1     ragge 	uint64_t val;
    287       1.1     ragge 	int i;
    288      1.19  christos 	char intrbuf[PCI_INTRSTR_LEN];
    289       1.1     ragge 
    290      1.13    cegger 	sc = device_private(self);
    291      1.17       chs 	sc->sc_dev = self;
    292       1.1     ragge 	sc->sc_dmat = pa->pa_dmat;
    293       1.1     ragge 
    294       1.1     ragge 	/* Get BAR0 address */
    295       1.1     ragge 	memtype = pci_mapreg_type(pa->pa_pc, pa->pa_tag, XGE_PIF_BAR);
    296       1.1     ragge 	if (pci_mapreg_map(pa, XGE_PIF_BAR, memtype, 0,
    297       1.1     ragge 	    &sc->sc_st, &sc->sc_sh, 0, 0)) {
    298       1.1     ragge 		aprint_error("%s: unable to map PIF BAR registers\n", XNAME);
    299       1.1     ragge 		return;
    300       1.1     ragge 	}
    301       1.1     ragge 
    302       1.1     ragge 	memtype = pci_mapreg_type(pa->pa_pc, pa->pa_tag, XGE_TXP_BAR);
    303       1.1     ragge 	if (pci_mapreg_map(pa, XGE_TXP_BAR, memtype, 0,
    304       1.1     ragge 	    &sc->sc_txt, &sc->sc_txh, 0, 0)) {
    305       1.1     ragge 		aprint_error("%s: unable to map TXP BAR registers\n", XNAME);
    306       1.1     ragge 		return;
    307       1.1     ragge 	}
    308       1.1     ragge 
    309       1.1     ragge 	/* Save PCI config space */
    310       1.1     ragge 	for (i = 0; i < 64; i += 4)
    311       1.1     ragge 		sc->sc_pciregs[i/4] = pci_conf_read(pa->pa_pc, pa->pa_tag, i);
    312       1.1     ragge 
    313       1.1     ragge #if BYTE_ORDER == LITTLE_ENDIAN
    314       1.1     ragge 	val = (uint64_t)0xFFFFFFFFFFFFFFFFULL;
    315       1.1     ragge 	val &= ~(TxF_R_SE|RxF_W_SE);
    316       1.1     ragge 	PIF_WCSR(SWAPPER_CTRL, val);
    317       1.1     ragge 	PIF_WCSR(SWAPPER_CTRL, val);
    318       1.1     ragge #elif BYTE_ORDER == BIG_ENDIAN
    319       1.1     ragge 	/* do nothing */
    320       1.1     ragge #else
    321       1.1     ragge #error bad endianness!
    322       1.1     ragge #endif
    323       1.1     ragge 
    324  1.19.6.4     skrll 	if ((val = PIF_RCSR(PIF_RD_SWAPPER_Fb)) != SWAPPER_MAGIC) {
    325  1.19.6.4     skrll 		aprint_error("%s: failed configuring endian, %llx != %llx!\n",
    326       1.1     ragge 		    XNAME, (unsigned long long)val, SWAPPER_MAGIC);
    327  1.19.6.4     skrll 		return;
    328  1.19.6.4     skrll 	}
    329       1.1     ragge 
    330       1.1     ragge 	/*
    331       1.1     ragge 	 * The MAC addr may be all FF's, which is not good.
    332      1.18  christos 	 * Resolve it by writing some magics to GPIO_CONTROL and
    333       1.1     ragge 	 * force a chip reset to read in the serial eeprom again.
    334       1.1     ragge 	 */
    335       1.1     ragge 	for (i = 0; i < sizeof(fix_mac)/sizeof(fix_mac[0]); i++) {
    336       1.1     ragge 		PIF_WCSR(GPIO_CONTROL, fix_mac[i]);
    337       1.1     ragge 		PIF_RCSR(GPIO_CONTROL);
    338       1.1     ragge 	}
    339       1.1     ragge 
    340       1.1     ragge 	/*
    341       1.1     ragge 	 * Reset the chip and restore the PCI registers.
    342       1.1     ragge 	 */
    343       1.1     ragge 	PIF_WCSR(SW_RESET, 0xa5a5a50000000000ULL);
    344       1.1     ragge 	DELAY(500000);
    345       1.1     ragge 	for (i = 0; i < 64; i += 4)
    346       1.1     ragge 		pci_conf_write(pa->pa_pc, pa->pa_tag, i, sc->sc_pciregs[i/4]);
    347       1.1     ragge 
    348       1.1     ragge 	/*
    349       1.1     ragge 	 * Restore the byte order registers.
    350       1.1     ragge 	 */
    351       1.1     ragge #if BYTE_ORDER == LITTLE_ENDIAN
    352       1.1     ragge 	val = (uint64_t)0xFFFFFFFFFFFFFFFFULL;
    353       1.1     ragge 	val &= ~(TxF_R_SE|RxF_W_SE);
    354       1.1     ragge 	PIF_WCSR(SWAPPER_CTRL, val);
    355       1.1     ragge 	PIF_WCSR(SWAPPER_CTRL, val);
    356       1.1     ragge #elif BYTE_ORDER == BIG_ENDIAN
    357       1.1     ragge 	/* do nothing */
    358       1.1     ragge #else
    359       1.1     ragge #error bad endianness!
    360       1.1     ragge #endif
    361       1.1     ragge 
    362  1.19.6.4     skrll 	if ((val = PIF_RCSR(PIF_RD_SWAPPER_Fb)) != SWAPPER_MAGIC) {
    363  1.19.6.4     skrll 		aprint_error("%s: failed configuring endian2, %llx != %llx!\n",
    364       1.1     ragge 		    XNAME, (unsigned long long)val, SWAPPER_MAGIC);
    365  1.19.6.4     skrll 		return;
    366  1.19.6.4     skrll 	}
    367       1.1     ragge 
    368       1.1     ragge 	/*
    369       1.1     ragge 	 * XGXS initialization.
    370       1.1     ragge 	 */
    371       1.1     ragge 	/* 29, reset */
    372       1.1     ragge 	PIF_WCSR(SW_RESET, 0);
    373       1.1     ragge 	DELAY(500000);
    374       1.1     ragge 
    375       1.1     ragge 	/* 30, configure XGXS transceiver */
    376       1.1     ragge 	xge_setup_xgxs(sc);
    377       1.1     ragge 
    378       1.1     ragge 	/* 33, program MAC address (not needed here) */
    379       1.1     ragge 	/* Get ethernet address */
    380       1.1     ragge 	PIF_WCSR(RMAC_ADDR_CMD_MEM,
    381       1.1     ragge 	    RMAC_ADDR_CMD_MEM_STR|RMAC_ADDR_CMD_MEM_OFF(0));
    382       1.1     ragge 	while (PIF_RCSR(RMAC_ADDR_CMD_MEM) & RMAC_ADDR_CMD_MEM_STR)
    383       1.1     ragge 		;
    384       1.1     ragge 	val = PIF_RCSR(RMAC_ADDR_DATA0_MEM);
    385       1.1     ragge 	for (i = 0; i < ETHER_ADDR_LEN; i++)
    386       1.1     ragge 		enaddr[i] = (uint8_t)(val >> (56 - (8*i)));
    387       1.1     ragge 
    388       1.1     ragge 	/*
    389       1.1     ragge 	 * Get memory for transmit descriptor lists.
    390       1.1     ragge 	 */
    391  1.19.6.4     skrll 	if (xge_alloc_txmem(sc)) {
    392  1.19.6.4     skrll 		aprint_error("%s: failed allocating txmem.\n", XNAME);
    393  1.19.6.4     skrll 		return;
    394  1.19.6.4     skrll 	}
    395       1.1     ragge 
    396       1.1     ragge 	/* 9 and 10 - set FIFO number/prio */
    397       1.1     ragge 	PIF_WCSR(TX_FIFO_P0, TX_FIFO_LEN0(NTXDESCS));
    398       1.1     ragge 	PIF_WCSR(TX_FIFO_P1, 0ULL);
    399       1.1     ragge 	PIF_WCSR(TX_FIFO_P2, 0ULL);
    400       1.1     ragge 	PIF_WCSR(TX_FIFO_P3, 0ULL);
    401       1.1     ragge 
    402       1.1     ragge 	/* 11, XXX set round-robin prio? */
    403       1.1     ragge 
    404       1.1     ragge 	/* 12, enable transmit FIFO */
    405       1.1     ragge 	val = PIF_RCSR(TX_FIFO_P0);
    406       1.1     ragge 	val |= TX_FIFO_ENABLE;
    407       1.1     ragge 	PIF_WCSR(TX_FIFO_P0, val);
    408       1.1     ragge 
    409       1.1     ragge 	/* 13, disable some error checks */
    410       1.1     ragge 	PIF_WCSR(TX_PA_CFG,
    411       1.1     ragge 	    TX_PA_CFG_IFR|TX_PA_CFG_ISO|TX_PA_CFG_ILC|TX_PA_CFG_ILE);
    412       1.1     ragge 
    413       1.1     ragge 	/*
    414       1.1     ragge 	 * Create transmit DMA maps.
    415       1.1     ragge 	 * Make them large for TSO.
    416       1.1     ragge 	 */
    417       1.1     ragge 	for (i = 0; i < NTXDESCS; i++) {
    418       1.1     ragge 		if (bus_dmamap_create(sc->sc_dmat, XGE_IP_MAXPACKET,
    419  1.19.6.4     skrll 		    NTXFRAGS, MCLBYTES, 0, 0, &sc->sc_txm[i])) {
    420  1.19.6.4     skrll 			aprint_error("%s: cannot create TX DMA maps\n", XNAME);
    421  1.19.6.4     skrll 			return;
    422  1.19.6.4     skrll 		}
    423       1.1     ragge 	}
    424       1.1     ragge 
    425       1.1     ragge 	sc->sc_lasttx = NTXDESCS-1;
    426       1.1     ragge 
    427       1.1     ragge 	/*
    428       1.1     ragge 	 * RxDMA initialization.
    429       1.1     ragge 	 * Only use one out of 8 possible receive queues.
    430       1.1     ragge 	 */
    431  1.19.6.4     skrll 	if (xge_alloc_rxmem(sc)) {	/* allocate rx descriptor memory */
    432  1.19.6.4     skrll 		aprint_error("%s: failed allocating rxmem\n", XNAME);
    433  1.19.6.4     skrll 		return;
    434  1.19.6.4     skrll 	}
    435       1.1     ragge 
    436       1.1     ragge 	/* Create receive buffer DMA maps */
    437       1.1     ragge 	for (i = 0; i < NRXREAL; i++) {
    438       1.1     ragge 		if (bus_dmamap_create(sc->sc_dmat, XGE_MAX_MTU,
    439  1.19.6.4     skrll 		    NRXFRAGS, MCLBYTES, 0, 0, &sc->sc_rxm[i])) {
    440  1.19.6.4     skrll 			aprint_error("%s: cannot create RX DMA maps\n", XNAME);
    441  1.19.6.4     skrll 			return;
    442  1.19.6.4     skrll 		}
    443       1.1     ragge 	}
    444       1.1     ragge 
    445       1.1     ragge 	/* allocate mbufs to receive descriptors */
    446       1.1     ragge 	for (i = 0; i < NRXREAL; i++)
    447       1.1     ragge 		if (xge_add_rxbuf(sc, i))
    448       1.1     ragge 			panic("out of mbufs too early");
    449       1.1     ragge 
    450       1.1     ragge 	/* 14, setup receive ring priority */
    451       1.1     ragge 	PIF_WCSR(RX_QUEUE_PRIORITY, 0ULL); /* only use one ring */
    452       1.1     ragge 
    453       1.1     ragge 	/* 15, setup receive ring round-robin calendar */
    454       1.1     ragge 	PIF_WCSR(RX_W_ROUND_ROBIN_0, 0ULL); /* only use one ring */
    455       1.1     ragge 	PIF_WCSR(RX_W_ROUND_ROBIN_1, 0ULL);
    456       1.1     ragge 	PIF_WCSR(RX_W_ROUND_ROBIN_2, 0ULL);
    457       1.1     ragge 	PIF_WCSR(RX_W_ROUND_ROBIN_3, 0ULL);
    458       1.1     ragge 	PIF_WCSR(RX_W_ROUND_ROBIN_4, 0ULL);
    459       1.1     ragge 
    460       1.1     ragge 	/* 16, write receive ring start address */
    461       1.1     ragge 	PIF_WCSR(PRC_RXD0_0, (uint64_t)sc->sc_rxmap->dm_segs[0].ds_addr);
    462       1.1     ragge 	/* PRC_RXD0_[1-7] are not used */
    463       1.1     ragge 
    464       1.1     ragge 	/* 17, Setup alarm registers */
    465       1.1     ragge 	PIF_WCSR(PRC_ALARM_ACTION, 0ULL); /* Default everything to retry */
    466       1.1     ragge 
    467       1.1     ragge 	/* 18, init receive ring controller */
    468       1.1     ragge #if RX_MODE == RX_MODE_1
    469       1.1     ragge 	val = RING_MODE_1;
    470       1.1     ragge #elif RX_MODE == RX_MODE_3
    471       1.1     ragge 	val = RING_MODE_3;
    472       1.1     ragge #else /* RX_MODE == RX_MODE_5 */
    473       1.1     ragge 	val = RING_MODE_5;
    474       1.1     ragge #endif
    475       1.1     ragge 	PIF_WCSR(PRC_CTRL_0, RC_IN_SVC|val);
    476       1.1     ragge 	/* leave 1-7 disabled */
    477       1.1     ragge 	/* XXXX snoop configuration? */
    478       1.1     ragge 
    479       1.1     ragge 	/* 19, set chip memory assigned to the queue */
    480       1.1     ragge 	PIF_WCSR(RX_QUEUE_CFG, MC_QUEUE(0, 64)); /* all 64M to queue 0 */
    481       1.1     ragge 
    482       1.1     ragge 	/* 20, setup RLDRAM parameters */
    483       1.1     ragge 	/* do not touch it for now */
    484       1.1     ragge 
    485       1.1     ragge 	/* 21, setup pause frame thresholds */
    486       1.1     ragge 	/* so not touch the defaults */
    487       1.1     ragge 	/* XXX - must 0xff be written as stated in the manual? */
    488       1.1     ragge 
    489       1.1     ragge 	/* 22, configure RED */
    490       1.1     ragge 	/* we do not want to drop packets, so ignore */
    491       1.1     ragge 
    492       1.1     ragge 	/* 23, initiate RLDRAM */
    493       1.1     ragge 	val = PIF_RCSR(MC_RLDRAM_MRS);
    494       1.1     ragge 	val |= MC_QUEUE_SIZE_ENABLE|MC_RLDRAM_MRS_ENABLE;
    495       1.1     ragge 	PIF_WCSR(MC_RLDRAM_MRS, val);
    496       1.1     ragge 	DELAY(1000);
    497       1.1     ragge 
    498       1.1     ragge 	/*
    499       1.1     ragge 	 * Setup interrupt policies.
    500       1.1     ragge 	 */
    501       1.1     ragge 	/* 40, Transmit interrupts */
    502       1.1     ragge 	PIF_WCSR(TTI_DATA1_MEM, TX_TIMER_VAL(0x1ff) | TX_TIMER_AC |
    503       1.1     ragge 	    TX_URNG_A(5) | TX_URNG_B(20) | TX_URNG_C(48));
    504       1.1     ragge 	PIF_WCSR(TTI_DATA2_MEM,
    505       1.1     ragge 	    TX_UFC_A(25) | TX_UFC_B(64) | TX_UFC_C(128) | TX_UFC_D(512));
    506       1.1     ragge 	PIF_WCSR(TTI_COMMAND_MEM, TTI_CMD_MEM_WE | TTI_CMD_MEM_STROBE);
    507       1.1     ragge 	while (PIF_RCSR(TTI_COMMAND_MEM) & TTI_CMD_MEM_STROBE)
    508       1.1     ragge 		;
    509       1.1     ragge 
    510       1.1     ragge 	/* 41, Receive interrupts */
    511       1.1     ragge 	PIF_WCSR(RTI_DATA1_MEM, RX_TIMER_VAL(0x800) | RX_TIMER_AC |
    512       1.1     ragge 	    RX_URNG_A(5) | RX_URNG_B(20) | RX_URNG_C(50));
    513       1.1     ragge 	PIF_WCSR(RTI_DATA2_MEM,
    514       1.1     ragge 	    RX_UFC_A(64) | RX_UFC_B(128) | RX_UFC_C(256) | RX_UFC_D(512));
    515       1.1     ragge 	PIF_WCSR(RTI_COMMAND_MEM, RTI_CMD_MEM_WE | RTI_CMD_MEM_STROBE);
    516       1.1     ragge 	while (PIF_RCSR(RTI_COMMAND_MEM) & RTI_CMD_MEM_STROBE)
    517       1.1     ragge 		;
    518       1.1     ragge 
    519       1.1     ragge 	/*
    520       1.1     ragge 	 * Setup media stuff.
    521       1.1     ragge 	 */
    522       1.1     ragge 	ifmedia_init(&sc->xena_media, IFM_IMASK, xge_xgmii_mediachange,
    523       1.1     ragge 	    xge_ifmedia_status);
    524       1.1     ragge 	ifmedia_add(&sc->xena_media, IFM_ETHER|IFM_10G_LR, 0, NULL);
    525       1.1     ragge 	ifmedia_set(&sc->xena_media, IFM_ETHER|IFM_10G_LR);
    526       1.1     ragge 
    527       1.1     ragge 	aprint_normal("%s: Ethernet address %s\n", XNAME,
    528       1.1     ragge 	    ether_sprintf(enaddr));
    529       1.1     ragge 
    530       1.1     ragge 	ifp = &sc->sc_ethercom.ec_if;
    531      1.17       chs 	strlcpy(ifp->if_xname, device_xname(sc->sc_dev), IFNAMSIZ);
    532       1.1     ragge 	ifp->if_baudrate = 10000000000LL;
    533       1.1     ragge 	ifp->if_init = xge_init;
    534       1.1     ragge 	ifp->if_stop = xge_stop;
    535       1.1     ragge 	ifp->if_softc = sc;
    536       1.1     ragge 	ifp->if_flags = IFF_BROADCAST | IFF_SIMPLEX | IFF_MULTICAST;
    537       1.1     ragge 	ifp->if_ioctl = xge_ioctl;
    538       1.1     ragge 	ifp->if_start = xge_start;
    539       1.1     ragge 	IFQ_SET_MAXLEN(&ifp->if_snd, max(NTXDESCS - 1, IFQ_MAXLEN));
    540       1.1     ragge 	IFQ_SET_READY(&ifp->if_snd);
    541       1.1     ragge 
    542       1.1     ragge 	/*
    543       1.1     ragge 	 * Offloading capabilities.
    544       1.1     ragge 	 */
    545       1.1     ragge 	sc->sc_ethercom.ec_capabilities |=
    546       1.1     ragge 	    ETHERCAP_JUMBO_MTU | ETHERCAP_VLAN_MTU;
    547       1.1     ragge 	ifp->if_capabilities |=
    548       1.1     ragge 	    IFCAP_CSUM_IPv4_Rx | IFCAP_CSUM_IPv4_Tx |
    549       1.1     ragge 	    IFCAP_CSUM_TCPv4_Rx | IFCAP_CSUM_TCPv4_Tx |
    550       1.1     ragge 	    IFCAP_CSUM_UDPv4_Rx | IFCAP_CSUM_UDPv4_Tx | IFCAP_TSOv4;
    551       1.1     ragge 
    552       1.1     ragge 	/*
    553       1.1     ragge 	 * Attach the interface.
    554       1.1     ragge 	 */
    555       1.1     ragge 	if_attach(ifp);
    556  1.19.6.5     skrll 	if_deferred_start_init(ifp, NULL);
    557       1.1     ragge 	ether_ifattach(ifp, enaddr);
    558       1.1     ragge 
    559       1.1     ragge 	/*
    560       1.1     ragge 	 * Setup interrupt vector before initializing.
    561       1.1     ragge 	 */
    562  1.19.6.4     skrll 	if (pci_intr_map(pa, &ih)) {
    563  1.19.6.4     skrll 		aprint_error_dev(sc->sc_dev, "unable to map interrupt\n");
    564  1.19.6.4     skrll 		return;
    565  1.19.6.4     skrll 	}
    566      1.19  christos 	intrstr = pci_intr_string(pc, ih, intrbuf, sizeof(intrbuf));
    567       1.1     ragge 	if ((sc->sc_ih =
    568  1.19.6.4     skrll 		pci_intr_establish(pc, ih, IPL_NET, xge_intr, sc)) == NULL) {
    569  1.19.6.4     skrll 		aprint_error_dev(sc->sc_dev,
    570  1.19.6.4     skrll 		    "unable to establish interrupt at %s\n",
    571       1.9    cegger 		    intrstr ? intrstr : "<unknown>");
    572  1.19.6.4     skrll 		return;
    573  1.19.6.4     skrll 	}
    574      1.17       chs 	aprint_normal_dev(sc->sc_dev, "interrupting at %s\n", intrstr);
    575       1.1     ragge 
    576       1.1     ragge #ifdef XGE_EVENT_COUNTERS
    577       1.1     ragge 	evcnt_attach_dynamic(&sc->sc_intr, EVCNT_TYPE_MISC,
    578       1.1     ragge 	    NULL, XNAME, "intr");
    579       1.1     ragge 	evcnt_attach_dynamic(&sc->sc_txintr, EVCNT_TYPE_MISC,
    580       1.1     ragge 	    NULL, XNAME, "txintr");
    581       1.1     ragge 	evcnt_attach_dynamic(&sc->sc_rxintr, EVCNT_TYPE_MISC,
    582       1.1     ragge 	    NULL, XNAME, "rxintr");
    583       1.1     ragge 	evcnt_attach_dynamic(&sc->sc_txqe, EVCNT_TYPE_MISC,
    584       1.1     ragge 	    NULL, XNAME, "txqe");
    585       1.1     ragge #endif
    586       1.1     ragge }
    587       1.1     ragge 
    588       1.1     ragge void
    589       1.1     ragge xge_ifmedia_status(struct ifnet *ifp, struct ifmediareq *ifmr)
    590       1.1     ragge {
    591       1.1     ragge 	struct xge_softc *sc = ifp->if_softc;
    592       1.1     ragge 	uint64_t reg;
    593       1.1     ragge 
    594       1.1     ragge 	ifmr->ifm_status = IFM_AVALID;
    595       1.1     ragge 	ifmr->ifm_active = IFM_ETHER|IFM_10G_LR;
    596       1.1     ragge 
    597       1.1     ragge 	reg = PIF_RCSR(ADAPTER_STATUS);
    598      1.18  christos 	if ((reg & (RMAC_REMOTE_FAULT|RMAC_LOCAL_FAULT)) == 0)
    599       1.1     ragge 		ifmr->ifm_status |= IFM_ACTIVE;
    600       1.1     ragge }
    601       1.1     ragge 
    602       1.1     ragge int
    603       1.4  christos xge_xgmii_mediachange(struct ifnet *ifp)
    604       1.1     ragge {
    605       1.1     ragge 	return 0;
    606       1.1     ragge }
    607       1.1     ragge 
    608       1.1     ragge static void
    609       1.1     ragge xge_enable(struct xge_softc *sc)
    610       1.1     ragge {
    611       1.1     ragge 	uint64_t val;
    612       1.1     ragge 
    613       1.1     ragge 	/* 2, enable adapter */
    614       1.1     ragge 	val = PIF_RCSR(ADAPTER_CONTROL);
    615       1.1     ragge 	val |= ADAPTER_EN;
    616       1.1     ragge 	PIF_WCSR(ADAPTER_CONTROL, val);
    617       1.1     ragge 
    618       1.1     ragge 	/* 3, light the card enable led */
    619       1.1     ragge 	val = PIF_RCSR(ADAPTER_CONTROL);
    620       1.1     ragge 	val |= LED_ON;
    621       1.1     ragge 	PIF_WCSR(ADAPTER_CONTROL, val);
    622       1.1     ragge 	printf("%s: link up\n", XNAME);
    623       1.1     ragge 
    624       1.1     ragge }
    625       1.1     ragge 
    626      1.18  christos int
    627       1.1     ragge xge_init(struct ifnet *ifp)
    628       1.1     ragge {
    629       1.1     ragge 	struct xge_softc *sc = ifp->if_softc;
    630       1.1     ragge 	uint64_t val;
    631       1.1     ragge 
    632       1.1     ragge 	if (ifp->if_flags & IFF_RUNNING)
    633       1.1     ragge 		return 0;
    634       1.1     ragge 
    635       1.1     ragge 	/* 31+32, setup MAC config */
    636       1.1     ragge 	PIF_WKEY(MAC_CFG, TMAC_EN|RMAC_EN|TMAC_APPEND_PAD|RMAC_STRIP_FCS|
    637       1.1     ragge 	    RMAC_BCAST_EN|RMAC_DISCARD_PFRM|RMAC_PROM_EN);
    638       1.1     ragge 
    639       1.1     ragge 	DELAY(1000);
    640       1.1     ragge 
    641       1.1     ragge 	/* 54, ensure that the adapter is 'quiescent' */
    642       1.1     ragge 	val = PIF_RCSR(ADAPTER_STATUS);
    643       1.1     ragge 	if ((val & QUIESCENT) != QUIESCENT) {
    644       1.1     ragge 		char buf[200];
    645       1.1     ragge 		printf("%s: adapter not quiescent, aborting\n", XNAME);
    646       1.1     ragge 		val = (val & QUIESCENT) ^ QUIESCENT;
    647      1.10  christos 		snprintb(buf, sizeof buf, QUIESCENT_BMSK, val);
    648       1.1     ragge 		printf("%s: ADAPTER_STATUS missing bits %s\n", XNAME, buf);
    649       1.1     ragge 		return 1;
    650       1.1     ragge 	}
    651       1.1     ragge 
    652       1.1     ragge 	/* 56, enable the transmit laser */
    653       1.1     ragge 	val = PIF_RCSR(ADAPTER_CONTROL);
    654       1.1     ragge 	val |= EOI_TX_ON;
    655       1.1     ragge 	PIF_WCSR(ADAPTER_CONTROL, val);
    656       1.1     ragge 
    657       1.1     ragge 	xge_enable(sc);
    658       1.1     ragge 	/*
    659       1.1     ragge 	 * Enable all interrupts
    660       1.1     ragge 	 */
    661       1.1     ragge 	PIF_WCSR(TX_TRAFFIC_MASK, 0);
    662       1.1     ragge 	PIF_WCSR(RX_TRAFFIC_MASK, 0);
    663       1.1     ragge 	PIF_WCSR(GENERAL_INT_MASK, 0);
    664       1.1     ragge 	PIF_WCSR(TXPIC_INT_MASK, 0);
    665       1.1     ragge 	PIF_WCSR(RXPIC_INT_MASK, 0);
    666       1.1     ragge 	PIF_WCSR(MAC_INT_MASK, MAC_TMAC_INT); /* only from RMAC */
    667       1.1     ragge 	PIF_WCSR(MAC_RMAC_ERR_MASK, ~RMAC_LINK_STATE_CHANGE_INT);
    668       1.1     ragge 
    669       1.1     ragge 
    670       1.1     ragge 	/* Done... */
    671       1.1     ragge 	ifp->if_flags |= IFF_RUNNING;
    672       1.1     ragge 	ifp->if_flags &= ~IFF_OACTIVE;
    673       1.1     ragge 
    674       1.1     ragge 	return 0;
    675       1.1     ragge }
    676       1.1     ragge 
    677       1.1     ragge static void
    678       1.4  christos xge_stop(struct ifnet *ifp, int disable)
    679       1.1     ragge {
    680       1.1     ragge 	struct xge_softc *sc = ifp->if_softc;
    681       1.1     ragge 	uint64_t val;
    682       1.1     ragge 
    683       1.1     ragge 	val = PIF_RCSR(ADAPTER_CONTROL);
    684       1.1     ragge 	val &= ~ADAPTER_EN;
    685       1.1     ragge 	PIF_WCSR(ADAPTER_CONTROL, val);
    686       1.1     ragge 
    687       1.1     ragge 	while ((PIF_RCSR(ADAPTER_STATUS) & QUIESCENT) != QUIESCENT)
    688       1.1     ragge 		;
    689       1.1     ragge }
    690       1.1     ragge 
    691       1.1     ragge int
    692       1.1     ragge xge_intr(void *pv)
    693       1.1     ragge {
    694       1.1     ragge 	struct xge_softc *sc = pv;
    695       1.1     ragge 	struct txd *txd;
    696       1.1     ragge 	struct ifnet *ifp = &sc->sc_if;
    697       1.1     ragge 	bus_dmamap_t dmp;
    698       1.1     ragge 	uint64_t val;
    699       1.1     ragge 	int i, lasttx, plen;
    700       1.1     ragge 
    701       1.1     ragge 	val = PIF_RCSR(GENERAL_INT_STATUS);
    702       1.1     ragge 	if (val == 0)
    703       1.1     ragge 		return 0; /* no interrupt here */
    704       1.1     ragge 
    705       1.1     ragge 	XGE_EVCNT_INCR(&sc->sc_intr);
    706       1.1     ragge 
    707       1.1     ragge 	PIF_WCSR(GENERAL_INT_STATUS, val);
    708       1.1     ragge 
    709       1.1     ragge 	if ((val = PIF_RCSR(MAC_RMAC_ERR_REG)) & RMAC_LINK_STATE_CHANGE_INT) {
    710       1.1     ragge 		/* Wait for quiescence */
    711       1.1     ragge 		printf("%s: link down\n", XNAME);
    712       1.1     ragge 		while ((PIF_RCSR(ADAPTER_STATUS) & QUIESCENT) != QUIESCENT)
    713       1.1     ragge 			;
    714       1.1     ragge 		PIF_WCSR(MAC_RMAC_ERR_REG, RMAC_LINK_STATE_CHANGE_INT);
    715  1.19.6.4     skrll 
    716       1.1     ragge 		val = PIF_RCSR(ADAPTER_STATUS);
    717       1.1     ragge 		if ((val & (RMAC_REMOTE_FAULT|RMAC_LOCAL_FAULT)) == 0)
    718       1.1     ragge 			xge_enable(sc); /* Only if link restored */
    719       1.1     ragge 	}
    720       1.1     ragge 
    721       1.1     ragge 	if ((val = PIF_RCSR(TX_TRAFFIC_INT))) {
    722       1.1     ragge 		XGE_EVCNT_INCR(&sc->sc_txintr);
    723       1.1     ragge 		PIF_WCSR(TX_TRAFFIC_INT, val); /* clear interrupt bits */
    724       1.1     ragge 	}
    725       1.1     ragge 	/*
    726       1.1     ragge 	 * Collect sent packets.
    727       1.1     ragge 	 */
    728       1.1     ragge 	lasttx = sc->sc_lasttx;
    729       1.1     ragge 	while ((i = NEXTTX(sc->sc_lasttx)) != sc->sc_nexttx) {
    730       1.1     ragge 		txd = sc->sc_txd[i];
    731       1.1     ragge 		dmp = sc->sc_txm[i];
    732       1.1     ragge 
    733       1.1     ragge 		bus_dmamap_sync(sc->sc_dmat, dmp, 0,
    734       1.1     ragge 		    dmp->dm_mapsize,
    735       1.1     ragge 		    BUS_DMASYNC_POSTREAD|BUS_DMASYNC_POSTWRITE);
    736       1.1     ragge 
    737       1.1     ragge 		if (txd->txd_control1 & TXD_CTL1_OWN) {
    738       1.1     ragge 			bus_dmamap_sync(sc->sc_dmat, dmp, 0,
    739       1.1     ragge 			    dmp->dm_mapsize, BUS_DMASYNC_PREREAD);
    740       1.1     ragge 			break;
    741       1.1     ragge 		}
    742       1.1     ragge 		bus_dmamap_unload(sc->sc_dmat, dmp);
    743       1.1     ragge 		m_freem(sc->sc_txb[i]);
    744       1.1     ragge 		ifp->if_opackets++;
    745       1.1     ragge 		sc->sc_lasttx = i;
    746       1.1     ragge 	}
    747       1.1     ragge 	if (i == sc->sc_nexttx) {
    748       1.1     ragge 		XGE_EVCNT_INCR(&sc->sc_txqe);
    749       1.1     ragge 	}
    750       1.1     ragge 
    751       1.1     ragge 	if (sc->sc_lasttx != lasttx)
    752       1.1     ragge 		ifp->if_flags &= ~IFF_OACTIVE;
    753       1.1     ragge 
    754  1.19.6.5     skrll 	if_schedule_deferred_start(ifp); /* Try to get more packets on the wire */
    755       1.1     ragge 
    756       1.1     ragge 	if ((val = PIF_RCSR(RX_TRAFFIC_INT))) {
    757       1.1     ragge 		XGE_EVCNT_INCR(&sc->sc_rxintr);
    758       1.1     ragge 		PIF_WCSR(RX_TRAFFIC_INT, val); /* clear interrupt bits */
    759       1.1     ragge 	}
    760       1.1     ragge 
    761       1.1     ragge 	for (;;) {
    762       1.1     ragge 		struct rxdesc *rxd;
    763       1.1     ragge 		struct mbuf *m;
    764       1.1     ragge 
    765       1.1     ragge 		XGE_RXSYNC(sc->sc_nextrx,
    766       1.1     ragge 		    BUS_DMASYNC_POSTREAD|BUS_DMASYNC_POSTWRITE);
    767       1.1     ragge 
    768       1.1     ragge 		rxd = XGE_RXD(sc->sc_nextrx);
    769       1.1     ragge 		if (rxd->rxd_control1 & RXD_CTL1_OWN) {
    770       1.1     ragge 			XGE_RXSYNC(sc->sc_nextrx, BUS_DMASYNC_PREREAD);
    771       1.1     ragge 			break;
    772       1.1     ragge 		}
    773       1.1     ragge 
    774       1.1     ragge 		/* got a packet */
    775       1.1     ragge 		m = sc->sc_rxb[sc->sc_nextrx];
    776       1.1     ragge #if RX_MODE == RX_MODE_1
    777       1.1     ragge 		plen = m->m_len = RXD_CTL2_BUF0SIZ(rxd->rxd_control2);
    778       1.1     ragge #elif RX_MODE == RX_MODE_3
    779       1.1     ragge #error Fix rxmodes in xge_intr
    780       1.1     ragge #elif RX_MODE == RX_MODE_5
    781       1.1     ragge 		plen = m->m_len = RXD_CTL2_BUF0SIZ(rxd->rxd_control2);
    782       1.1     ragge 		plen += m->m_next->m_len = RXD_CTL2_BUF1SIZ(rxd->rxd_control2);
    783       1.1     ragge 		plen += m->m_next->m_next->m_len =
    784       1.1     ragge 		    RXD_CTL2_BUF2SIZ(rxd->rxd_control2);
    785       1.1     ragge 		plen += m->m_next->m_next->m_next->m_len =
    786       1.1     ragge 		    RXD_CTL3_BUF3SIZ(rxd->rxd_control3);
    787       1.1     ragge 		plen += m->m_next->m_next->m_next->m_next->m_len =
    788       1.1     ragge 		    RXD_CTL3_BUF4SIZ(rxd->rxd_control3);
    789       1.1     ragge #endif
    790  1.19.6.3     skrll 		m_set_rcvif(m, ifp);
    791       1.1     ragge 		m->m_pkthdr.len = plen;
    792       1.1     ragge 
    793       1.1     ragge 		val = rxd->rxd_control1;
    794       1.1     ragge 
    795       1.1     ragge 		if (xge_add_rxbuf(sc, sc->sc_nextrx)) {
    796       1.1     ragge 			/* Failed, recycle this mbuf */
    797       1.1     ragge #if RX_MODE == RX_MODE_1
    798       1.1     ragge 			rxd->rxd_control2 = RXD_MKCTL2(MCLBYTES, 0, 0);
    799       1.1     ragge 			rxd->rxd_control1 = RXD_CTL1_OWN;
    800       1.1     ragge #elif RX_MODE == RX_MODE_3
    801       1.1     ragge #elif RX_MODE == RX_MODE_5
    802       1.1     ragge #endif
    803       1.1     ragge 			XGE_RXSYNC(sc->sc_nextrx,
    804       1.1     ragge 			    BUS_DMASYNC_PREREAD|BUS_DMASYNC_PREWRITE);
    805       1.1     ragge 			ifp->if_ierrors++;
    806       1.1     ragge 			break;
    807       1.1     ragge 		}
    808       1.1     ragge 
    809       1.1     ragge 		if (RXD_CTL1_PROTOS(val) & (RXD_CTL1_P_IPv4|RXD_CTL1_P_IPv6)) {
    810       1.1     ragge 			m->m_pkthdr.csum_flags |= M_CSUM_IPv4;
    811       1.1     ragge 			if (RXD_CTL1_L3CSUM(val) != 0xffff)
    812       1.1     ragge 				m->m_pkthdr.csum_flags |= M_CSUM_IPv4_BAD;
    813       1.1     ragge 		}
    814       1.1     ragge 		if (RXD_CTL1_PROTOS(val) & RXD_CTL1_P_TCP) {
    815       1.1     ragge 			m->m_pkthdr.csum_flags |= M_CSUM_TCPv4|M_CSUM_TCPv6;
    816       1.1     ragge 			if (RXD_CTL1_L4CSUM(val) != 0xffff)
    817       1.1     ragge 				m->m_pkthdr.csum_flags |= M_CSUM_TCP_UDP_BAD;
    818       1.1     ragge 		}
    819       1.1     ragge 		if (RXD_CTL1_PROTOS(val) & RXD_CTL1_P_UDP) {
    820       1.1     ragge 			m->m_pkthdr.csum_flags |= M_CSUM_UDPv4|M_CSUM_UDPv6;
    821       1.1     ragge 			if (RXD_CTL1_L4CSUM(val) != 0xffff)
    822       1.1     ragge 				m->m_pkthdr.csum_flags |= M_CSUM_TCP_UDP_BAD;
    823       1.1     ragge 		}
    824       1.1     ragge 
    825  1.19.6.2     skrll 		if_percpuq_enqueue(ifp->if_percpuq, m);
    826       1.1     ragge 
    827       1.1     ragge 		if (++sc->sc_nextrx == NRXREAL)
    828       1.1     ragge 			sc->sc_nextrx = 0;
    829       1.1     ragge 
    830       1.1     ragge 	}
    831       1.1     ragge 
    832       1.1     ragge 	return 0;
    833       1.1     ragge }
    834       1.1     ragge 
    835      1.18  christos int
    836       1.5  christos xge_ioctl(struct ifnet *ifp, u_long cmd, void *data)
    837       1.1     ragge {
    838       1.1     ragge 	struct xge_softc *sc = ifp->if_softc;
    839       1.1     ragge 	struct ifreq *ifr = (struct ifreq *) data;
    840       1.1     ragge 	int s, error = 0;
    841       1.1     ragge 
    842       1.1     ragge 	s = splnet();
    843       1.1     ragge 
    844       1.1     ragge 	switch (cmd) {
    845       1.1     ragge 	case SIOCSIFMTU:
    846       1.8    dyoung 		if (ifr->ifr_mtu < ETHERMIN || ifr->ifr_mtu > XGE_MAX_MTU)
    847       1.1     ragge 			error = EINVAL;
    848       1.8    dyoung 		else if ((error = ifioctl_common(ifp, cmd, data)) == ENETRESET){
    849       1.1     ragge 			PIF_WCSR(RMAC_MAX_PYLD_LEN,
    850       1.1     ragge 			    RMAC_PYLD_LEN(ifr->ifr_mtu));
    851       1.8    dyoung 			error = 0;
    852       1.1     ragge 		}
    853       1.1     ragge 		break;
    854       1.1     ragge 
    855       1.1     ragge 	case SIOCGIFMEDIA:
    856       1.1     ragge 	case SIOCSIFMEDIA:
    857       1.1     ragge 		error = ifmedia_ioctl(ifp, ifr, &sc->xena_media, cmd);
    858       1.1     ragge 		break;
    859       1.1     ragge 
    860       1.1     ragge 	default:
    861       1.8    dyoung 		if ((error = ether_ioctl(ifp, cmd, data)) != ENETRESET)
    862       1.8    dyoung 			break;
    863       1.8    dyoung 
    864       1.8    dyoung 		error = 0;
    865       1.8    dyoung 
    866       1.8    dyoung 		if (cmd != SIOCADDMULTI && cmd != SIOCDELMULTI)
    867       1.8    dyoung 			;
    868       1.8    dyoung 		else if (ifp->if_flags & IFF_RUNNING) {
    869       1.1     ragge 			/* Change multicast list */
    870       1.1     ragge 			xge_mcast_filter(sc);
    871       1.1     ragge 		}
    872       1.1     ragge 		break;
    873       1.1     ragge 	}
    874       1.1     ragge 
    875       1.1     ragge 	splx(s);
    876       1.1     ragge 	return(error);
    877       1.1     ragge }
    878       1.1     ragge 
    879       1.1     ragge void
    880       1.1     ragge xge_mcast_filter(struct xge_softc *sc)
    881       1.1     ragge {
    882       1.1     ragge 	struct ifnet *ifp = &sc->sc_ethercom.ec_if;
    883       1.1     ragge 	struct ethercom *ec = &sc->sc_ethercom;
    884       1.1     ragge 	struct ether_multi *enm;
    885       1.1     ragge 	struct ether_multistep step;
    886       1.1     ragge 	int i, numaddr = 1; /* first slot used for card unicast address */
    887       1.1     ragge 	uint64_t val;
    888       1.1     ragge 
    889       1.1     ragge 	ETHER_FIRST_MULTI(step, ec, enm);
    890       1.1     ragge 	while (enm != NULL) {
    891       1.1     ragge 		if (memcmp(enm->enm_addrlo, enm->enm_addrhi, ETHER_ADDR_LEN)) {
    892       1.1     ragge 			/* Skip ranges */
    893       1.1     ragge 			goto allmulti;
    894       1.1     ragge 		}
    895       1.1     ragge 		if (numaddr == MAX_MCAST_ADDR)
    896       1.1     ragge 			goto allmulti;
    897       1.1     ragge 		for (val = 0, i = 0; i < ETHER_ADDR_LEN; i++) {
    898       1.1     ragge 			val <<= 8;
    899       1.1     ragge 			val |= enm->enm_addrlo[i];
    900       1.1     ragge 		}
    901       1.1     ragge 		PIF_WCSR(RMAC_ADDR_DATA0_MEM, val << 16);
    902       1.1     ragge 		PIF_WCSR(RMAC_ADDR_DATA1_MEM, 0xFFFFFFFFFFFFFFFFULL);
    903       1.1     ragge 		PIF_WCSR(RMAC_ADDR_CMD_MEM, RMAC_ADDR_CMD_MEM_WE|
    904       1.1     ragge 		    RMAC_ADDR_CMD_MEM_STR|RMAC_ADDR_CMD_MEM_OFF(numaddr));
    905       1.1     ragge 		while (PIF_RCSR(RMAC_ADDR_CMD_MEM) & RMAC_ADDR_CMD_MEM_STR)
    906       1.1     ragge 			;
    907       1.1     ragge 		numaddr++;
    908       1.1     ragge 		ETHER_NEXT_MULTI(step, enm);
    909       1.1     ragge 	}
    910       1.1     ragge 	/* set the remaining entries to the broadcast address */
    911       1.1     ragge 	for (i = numaddr; i < MAX_MCAST_ADDR; i++) {
    912       1.1     ragge 		PIF_WCSR(RMAC_ADDR_DATA0_MEM, 0xffffffffffff0000ULL);
    913       1.1     ragge 		PIF_WCSR(RMAC_ADDR_DATA1_MEM, 0xFFFFFFFFFFFFFFFFULL);
    914       1.1     ragge 		PIF_WCSR(RMAC_ADDR_CMD_MEM, RMAC_ADDR_CMD_MEM_WE|
    915       1.1     ragge 		    RMAC_ADDR_CMD_MEM_STR|RMAC_ADDR_CMD_MEM_OFF(i));
    916       1.1     ragge 		while (PIF_RCSR(RMAC_ADDR_CMD_MEM) & RMAC_ADDR_CMD_MEM_STR)
    917       1.1     ragge 			;
    918       1.1     ragge 	}
    919       1.1     ragge 	ifp->if_flags &= ~IFF_ALLMULTI;
    920       1.1     ragge 	return;
    921       1.1     ragge 
    922       1.1     ragge allmulti:
    923       1.1     ragge 	/* Just receive everything with the multicast bit set */
    924       1.1     ragge 	ifp->if_flags |= IFF_ALLMULTI;
    925       1.1     ragge 	PIF_WCSR(RMAC_ADDR_DATA0_MEM, 0x8000000000000000ULL);
    926       1.1     ragge 	PIF_WCSR(RMAC_ADDR_DATA1_MEM, 0xF000000000000000ULL);
    927       1.1     ragge 	PIF_WCSR(RMAC_ADDR_CMD_MEM, RMAC_ADDR_CMD_MEM_WE|
    928       1.1     ragge 	    RMAC_ADDR_CMD_MEM_STR|RMAC_ADDR_CMD_MEM_OFF(1));
    929       1.1     ragge 	while (PIF_RCSR(RMAC_ADDR_CMD_MEM) & RMAC_ADDR_CMD_MEM_STR)
    930       1.1     ragge 		;
    931       1.1     ragge }
    932       1.1     ragge 
    933      1.18  christos void
    934       1.1     ragge xge_start(struct ifnet *ifp)
    935       1.1     ragge {
    936       1.1     ragge 	struct xge_softc *sc = ifp->if_softc;
    937       1.1     ragge 	struct txd *txd = NULL; /* XXX - gcc */
    938       1.1     ragge 	bus_dmamap_t dmp;
    939       1.1     ragge 	struct	mbuf *m;
    940       1.1     ragge 	uint64_t par, lcr;
    941       1.1     ragge 	int nexttx = 0, ntxd, error, i;
    942       1.1     ragge 
    943       1.1     ragge 	if ((ifp->if_flags & (IFF_RUNNING|IFF_OACTIVE)) != IFF_RUNNING)
    944       1.1     ragge 		return;
    945       1.1     ragge 
    946       1.1     ragge 	par = lcr = 0;
    947       1.1     ragge 	for (;;) {
    948       1.1     ragge 		IFQ_POLL(&ifp->if_snd, m);
    949       1.1     ragge 		if (m == NULL)
    950       1.1     ragge 			break;	/* out of packets */
    951       1.1     ragge 
    952       1.1     ragge 		if (sc->sc_nexttx == sc->sc_lasttx)
    953       1.1     ragge 			break;	/* No more space */
    954       1.1     ragge 
    955       1.1     ragge 		nexttx = sc->sc_nexttx;
    956       1.1     ragge 		dmp = sc->sc_txm[nexttx];
    957       1.1     ragge 
    958       1.1     ragge 		if ((error = bus_dmamap_load_mbuf(sc->sc_dmat, dmp, m,
    959       1.1     ragge 		    BUS_DMA_WRITE|BUS_DMA_NOWAIT)) != 0) {
    960       1.1     ragge 			printf("%s: bus_dmamap_load_mbuf error %d\n",
    961       1.1     ragge 			    XNAME, error);
    962       1.1     ragge 			break;
    963       1.1     ragge 		}
    964       1.1     ragge 		IFQ_DEQUEUE(&ifp->if_snd, m);
    965       1.1     ragge 
    966       1.1     ragge 		bus_dmamap_sync(sc->sc_dmat, dmp, 0, dmp->dm_mapsize,
    967       1.1     ragge 		    BUS_DMASYNC_PREWRITE);
    968       1.1     ragge 
    969       1.1     ragge 		txd = sc->sc_txd[nexttx];
    970       1.1     ragge 		sc->sc_txb[nexttx] = m;
    971       1.1     ragge 		for (i = 0; i < dmp->dm_nsegs; i++) {
    972       1.1     ragge 			if (dmp->dm_segs[i].ds_len == 0)
    973       1.1     ragge 				continue;
    974       1.1     ragge 			txd->txd_control1 = dmp->dm_segs[i].ds_len;
    975       1.1     ragge 			txd->txd_control2 = 0;
    976       1.1     ragge 			txd->txd_bufaddr = dmp->dm_segs[i].ds_addr;
    977       1.1     ragge 			txd++;
    978       1.1     ragge 		}
    979       1.1     ragge 		ntxd = txd - sc->sc_txd[nexttx] - 1;
    980       1.1     ragge 		txd = sc->sc_txd[nexttx];
    981       1.1     ragge 		txd->txd_control1 |= TXD_CTL1_OWN|TXD_CTL1_GCF;
    982       1.1     ragge 		txd->txd_control2 = TXD_CTL2_UTIL;
    983       1.1     ragge 		if (m->m_pkthdr.csum_flags & M_CSUM_TSOv4) {
    984       1.1     ragge 			txd->txd_control1 |= TXD_CTL1_MSS(m->m_pkthdr.segsz);
    985       1.1     ragge 			txd->txd_control1 |= TXD_CTL1_LSO;
    986       1.1     ragge 		}
    987       1.1     ragge 
    988       1.1     ragge 		if (m->m_pkthdr.csum_flags & M_CSUM_IPv4)
    989       1.1     ragge 			txd->txd_control2 |= TXD_CTL2_CIPv4;
    990       1.1     ragge 		if (m->m_pkthdr.csum_flags & M_CSUM_TCPv4)
    991       1.1     ragge 			txd->txd_control2 |= TXD_CTL2_CTCP;
    992       1.1     ragge 		if (m->m_pkthdr.csum_flags & M_CSUM_UDPv4)
    993       1.1     ragge 			txd->txd_control2 |= TXD_CTL2_CUDP;
    994       1.1     ragge 		txd[ntxd].txd_control1 |= TXD_CTL1_GCL;
    995       1.1     ragge 
    996       1.1     ragge 		bus_dmamap_sync(sc->sc_dmat, dmp, 0, dmp->dm_mapsize,
    997       1.1     ragge 		    BUS_DMASYNC_PREREAD|BUS_DMASYNC_PREWRITE);
    998       1.1     ragge 
    999       1.1     ragge 		par = sc->sc_txdp[nexttx];
   1000       1.1     ragge 		lcr = TXDL_NUMTXD(ntxd) | TXDL_LGC_FIRST | TXDL_LGC_LAST;
   1001       1.1     ragge 		if (m->m_pkthdr.csum_flags & M_CSUM_TSOv4)
   1002       1.1     ragge 			lcr |= TXDL_SFF;
   1003       1.1     ragge 		TXP_WCSR(TXDL_PAR, par);
   1004       1.1     ragge 		TXP_WCSR(TXDL_LCR, lcr);
   1005       1.1     ragge 
   1006      1.15     joerg 		bpf_mtap(ifp, m);
   1007       1.1     ragge 
   1008       1.1     ragge 		sc->sc_nexttx = NEXTTX(nexttx);
   1009       1.1     ragge 	}
   1010       1.1     ragge }
   1011       1.1     ragge 
   1012       1.1     ragge /*
   1013       1.1     ragge  * Allocate DMA memory for transmit descriptor fragments.
   1014       1.1     ragge  * Only one map is used for all descriptors.
   1015       1.1     ragge  */
   1016       1.1     ragge int
   1017       1.1     ragge xge_alloc_txmem(struct xge_softc *sc)
   1018       1.1     ragge {
   1019       1.1     ragge 	struct txd *txp;
   1020       1.1     ragge 	bus_dma_segment_t seg;
   1021       1.1     ragge 	bus_addr_t txdp;
   1022       1.5  christos 	void *kva;
   1023       1.1     ragge 	int i, rseg, state;
   1024       1.1     ragge 
   1025       1.1     ragge #define TXMAPSZ (NTXDESCS*NTXFRAGS*sizeof(struct txd))
   1026       1.1     ragge 	state = 0;
   1027       1.1     ragge 	if (bus_dmamem_alloc(sc->sc_dmat, TXMAPSZ, PAGE_SIZE, 0,
   1028       1.1     ragge 	    &seg, 1, &rseg, BUS_DMA_NOWAIT))
   1029       1.1     ragge 		goto err;
   1030       1.1     ragge 	state++;
   1031       1.1     ragge 	if (bus_dmamem_map(sc->sc_dmat, &seg, rseg, TXMAPSZ, &kva,
   1032       1.1     ragge 	    BUS_DMA_NOWAIT))
   1033       1.1     ragge 		goto err;
   1034       1.1     ragge 
   1035       1.1     ragge 	state++;
   1036       1.1     ragge 	if (bus_dmamap_create(sc->sc_dmat, TXMAPSZ, 1, TXMAPSZ, 0,
   1037       1.1     ragge 	    BUS_DMA_NOWAIT, &sc->sc_txmap))
   1038       1.1     ragge 		goto err;
   1039       1.1     ragge 	state++;
   1040       1.1     ragge 	if (bus_dmamap_load(sc->sc_dmat, sc->sc_txmap,
   1041       1.1     ragge 	    kva, TXMAPSZ, NULL, BUS_DMA_NOWAIT))
   1042       1.1     ragge 		goto err;
   1043       1.1     ragge 
   1044       1.1     ragge 	/* setup transmit array pointers */
   1045       1.1     ragge 	txp = (struct txd *)kva;
   1046       1.1     ragge 	txdp = seg.ds_addr;
   1047       1.1     ragge 	for (txp = (struct txd *)kva, i = 0; i < NTXDESCS; i++) {
   1048       1.1     ragge 		sc->sc_txd[i] = txp;
   1049       1.1     ragge 		sc->sc_txdp[i] = txdp;
   1050       1.1     ragge 		txp += NTXFRAGS;
   1051       1.1     ragge 		txdp += (NTXFRAGS * sizeof(struct txd));
   1052       1.1     ragge 	}
   1053       1.1     ragge 
   1054       1.1     ragge 	return 0;
   1055       1.1     ragge 
   1056       1.1     ragge err:
   1057       1.1     ragge 	if (state > 2)
   1058       1.1     ragge 		bus_dmamap_destroy(sc->sc_dmat, sc->sc_txmap);
   1059       1.1     ragge 	if (state > 1)
   1060       1.1     ragge 		bus_dmamem_unmap(sc->sc_dmat, kva, TXMAPSZ);
   1061       1.1     ragge 	if (state > 0)
   1062       1.1     ragge 		bus_dmamem_free(sc->sc_dmat, &seg, rseg);
   1063       1.1     ragge 	return ENOBUFS;
   1064       1.1     ragge }
   1065       1.1     ragge 
   1066       1.1     ragge /*
   1067       1.1     ragge  * Allocate DMA memory for receive descriptor,
   1068       1.1     ragge  * only one map is used for all descriptors.
   1069       1.1     ragge  * link receive descriptor pages together.
   1070       1.1     ragge  */
   1071       1.1     ragge int
   1072       1.1     ragge xge_alloc_rxmem(struct xge_softc *sc)
   1073       1.1     ragge {
   1074       1.1     ragge 	struct rxd_4k *rxpp;
   1075       1.1     ragge 	bus_dma_segment_t seg;
   1076       1.5  christos 	void *kva;
   1077       1.1     ragge 	int i, rseg, state;
   1078       1.1     ragge 
   1079       1.1     ragge 	/* sanity check */
   1080       1.1     ragge 	if (sizeof(struct rxd_4k) != XGE_PAGE) {
   1081       1.1     ragge 		printf("bad compiler struct alignment, %d != %d\n",
   1082       1.1     ragge 		    (int)sizeof(struct rxd_4k), XGE_PAGE);
   1083       1.1     ragge 		return EINVAL;
   1084       1.1     ragge 	}
   1085       1.1     ragge 
   1086       1.1     ragge 	state = 0;
   1087       1.1     ragge 	if (bus_dmamem_alloc(sc->sc_dmat, RXMAPSZ, PAGE_SIZE, 0,
   1088       1.1     ragge 	    &seg, 1, &rseg, BUS_DMA_NOWAIT))
   1089       1.1     ragge 		goto err;
   1090       1.1     ragge 	state++;
   1091       1.1     ragge 	if (bus_dmamem_map(sc->sc_dmat, &seg, rseg, RXMAPSZ, &kva,
   1092       1.1     ragge 	    BUS_DMA_NOWAIT))
   1093       1.1     ragge 		goto err;
   1094       1.1     ragge 
   1095       1.1     ragge 	state++;
   1096       1.1     ragge 	if (bus_dmamap_create(sc->sc_dmat, RXMAPSZ, 1, RXMAPSZ, 0,
   1097       1.1     ragge 	    BUS_DMA_NOWAIT, &sc->sc_rxmap))
   1098       1.1     ragge 		goto err;
   1099       1.1     ragge 	state++;
   1100       1.1     ragge 	if (bus_dmamap_load(sc->sc_dmat, sc->sc_rxmap,
   1101       1.1     ragge 	    kva, RXMAPSZ, NULL, BUS_DMA_NOWAIT))
   1102       1.1     ragge 		goto err;
   1103       1.1     ragge 
   1104       1.1     ragge 	/* setup receive page link pointers */
   1105       1.1     ragge 	for (rxpp = (struct rxd_4k *)kva, i = 0; i < NRXPAGES; i++, rxpp++) {
   1106       1.1     ragge 		sc->sc_rxd_4k[i] = rxpp;
   1107       1.1     ragge 		rxpp->r4_next = (uint64_t)sc->sc_rxmap->dm_segs[0].ds_addr +
   1108       1.1     ragge 		    (i*sizeof(struct rxd_4k)) + sizeof(struct rxd_4k);
   1109       1.1     ragge 	}
   1110      1.18  christos 	sc->sc_rxd_4k[NRXPAGES-1]->r4_next =
   1111       1.1     ragge 	    (uint64_t)sc->sc_rxmap->dm_segs[0].ds_addr;
   1112       1.1     ragge 
   1113       1.1     ragge 	return 0;
   1114       1.1     ragge 
   1115       1.1     ragge err:
   1116       1.1     ragge 	if (state > 2)
   1117       1.1     ragge 		bus_dmamap_destroy(sc->sc_dmat, sc->sc_txmap);
   1118       1.1     ragge 	if (state > 1)
   1119       1.1     ragge 		bus_dmamem_unmap(sc->sc_dmat, kva, TXMAPSZ);
   1120       1.1     ragge 	if (state > 0)
   1121       1.1     ragge 		bus_dmamem_free(sc->sc_dmat, &seg, rseg);
   1122       1.1     ragge 	return ENOBUFS;
   1123       1.1     ragge }
   1124       1.1     ragge 
   1125       1.1     ragge 
   1126       1.1     ragge /*
   1127       1.1     ragge  * Add a new mbuf chain to descriptor id.
   1128       1.1     ragge  */
   1129       1.1     ragge int
   1130       1.1     ragge xge_add_rxbuf(struct xge_softc *sc, int id)
   1131       1.1     ragge {
   1132       1.1     ragge 	struct rxdesc *rxd;
   1133       1.1     ragge 	struct mbuf *m[5];
   1134       1.1     ragge 	int page, desc, error;
   1135       1.1     ragge #if RX_MODE == RX_MODE_5
   1136       1.1     ragge 	int i;
   1137       1.1     ragge #endif
   1138       1.1     ragge 
   1139       1.1     ragge 	page = id/NDESC_BUFMODE;
   1140       1.1     ragge 	desc = id%NDESC_BUFMODE;
   1141       1.1     ragge 
   1142       1.1     ragge 	rxd = &sc->sc_rxd_4k[page]->r4_rxd[desc];
   1143       1.1     ragge 
   1144       1.1     ragge 	/*
   1145       1.1     ragge 	 * Allocate mbufs.
   1146       1.1     ragge 	 * Currently five mbufs and two clusters are used,
   1147       1.1     ragge 	 * the hardware will put (ethernet, ip, tcp/udp) headers in
   1148       1.1     ragge 	 * their own buffer and the clusters are only used for data.
   1149       1.1     ragge 	 */
   1150       1.1     ragge #if RX_MODE == RX_MODE_1
   1151       1.1     ragge 	MGETHDR(m[0], M_DONTWAIT, MT_DATA);
   1152       1.1     ragge 	if (m[0] == NULL)
   1153       1.1     ragge 		return ENOBUFS;
   1154       1.1     ragge 	MCLGET(m[0], M_DONTWAIT);
   1155       1.1     ragge 	if ((m[0]->m_flags & M_EXT) == 0) {
   1156       1.1     ragge 		m_freem(m[0]);
   1157       1.1     ragge 		return ENOBUFS;
   1158       1.1     ragge 	}
   1159       1.1     ragge 	m[0]->m_len = m[0]->m_pkthdr.len = m[0]->m_ext.ext_size;
   1160       1.1     ragge #elif RX_MODE == RX_MODE_3
   1161       1.1     ragge #error missing rxmode 3.
   1162       1.1     ragge #elif RX_MODE == RX_MODE_5
   1163       1.1     ragge 	MGETHDR(m[0], M_DONTWAIT, MT_DATA);
   1164       1.1     ragge 	for (i = 1; i < 5; i++) {
   1165       1.1     ragge 		MGET(m[i], M_DONTWAIT, MT_DATA);
   1166       1.1     ragge 	}
   1167       1.1     ragge 	if (m[3])
   1168       1.1     ragge 		MCLGET(m[3], M_DONTWAIT);
   1169       1.1     ragge 	if (m[4])
   1170       1.1     ragge 		MCLGET(m[4], M_DONTWAIT);
   1171      1.18  christos 	if (!m[0] || !m[1] || !m[2] || !m[3] || !m[4] ||
   1172       1.1     ragge 	    ((m[3]->m_flags & M_EXT) == 0) || ((m[4]->m_flags & M_EXT) == 0)) {
   1173       1.1     ragge 		/* Out of something */
   1174       1.1     ragge 		for (i = 0; i < 5; i++)
   1175       1.1     ragge 			if (m[i] != NULL)
   1176       1.1     ragge 				m_free(m[i]);
   1177       1.1     ragge 		return ENOBUFS;
   1178       1.1     ragge 	}
   1179       1.1     ragge 	/* Link'em together */
   1180       1.1     ragge 	m[0]->m_next = m[1];
   1181       1.1     ragge 	m[1]->m_next = m[2];
   1182       1.1     ragge 	m[2]->m_next = m[3];
   1183       1.1     ragge 	m[3]->m_next = m[4];
   1184       1.1     ragge #else
   1185       1.1     ragge #error bad mode RX_MODE
   1186       1.1     ragge #endif
   1187       1.1     ragge 
   1188       1.1     ragge 	if (sc->sc_rxb[id])
   1189       1.1     ragge 		bus_dmamap_unload(sc->sc_dmat, sc->sc_rxm[id]);
   1190       1.1     ragge 	sc->sc_rxb[id] = m[0];
   1191       1.1     ragge 
   1192       1.1     ragge 	error = bus_dmamap_load_mbuf(sc->sc_dmat, sc->sc_rxm[id], m[0],
   1193       1.1     ragge 	    BUS_DMA_READ|BUS_DMA_NOWAIT);
   1194       1.1     ragge 	if (error)
   1195       1.1     ragge 		return error;
   1196       1.1     ragge 	bus_dmamap_sync(sc->sc_dmat, sc->sc_rxm[id], 0,
   1197       1.1     ragge 	    sc->sc_rxm[id]->dm_mapsize, BUS_DMASYNC_PREREAD);
   1198       1.1     ragge 
   1199       1.1     ragge #if RX_MODE == RX_MODE_1
   1200       1.1     ragge 	rxd->rxd_control2 = RXD_MKCTL2(m[0]->m_len, 0, 0);
   1201       1.1     ragge 	rxd->rxd_buf0 = (uint64_t)sc->sc_rxm[id]->dm_segs[0].ds_addr;
   1202       1.1     ragge 	rxd->rxd_control1 = RXD_CTL1_OWN;
   1203       1.1     ragge #elif RX_MODE == RX_MODE_3
   1204       1.1     ragge #elif RX_MODE == RX_MODE_5
   1205       1.1     ragge 	rxd->rxd_control3 = RXD_MKCTL3(0, m[3]->m_len, m[4]->m_len);
   1206       1.1     ragge 	rxd->rxd_control2 = RXD_MKCTL2(m[0]->m_len, m[1]->m_len, m[2]->m_len);
   1207       1.1     ragge 	rxd->rxd_buf0 = (uint64_t)sc->sc_rxm[id]->dm_segs[0].ds_addr;
   1208       1.1     ragge 	rxd->rxd_buf1 = (uint64_t)sc->sc_rxm[id]->dm_segs[1].ds_addr;
   1209       1.1     ragge 	rxd->rxd_buf2 = (uint64_t)sc->sc_rxm[id]->dm_segs[2].ds_addr;
   1210       1.1     ragge 	rxd->rxd_buf3 = (uint64_t)sc->sc_rxm[id]->dm_segs[3].ds_addr;
   1211       1.1     ragge 	rxd->rxd_buf4 = (uint64_t)sc->sc_rxm[id]->dm_segs[4].ds_addr;
   1212       1.1     ragge 	rxd->rxd_control1 = RXD_CTL1_OWN;
   1213       1.1     ragge #endif
   1214       1.1     ragge 
   1215       1.1     ragge 	XGE_RXSYNC(id, BUS_DMASYNC_PREREAD|BUS_DMASYNC_PREWRITE);
   1216       1.1     ragge 	return 0;
   1217       1.1     ragge }
   1218       1.1     ragge 
   1219       1.1     ragge /*
   1220       1.1     ragge  * These magics comes from the FreeBSD driver.
   1221       1.1     ragge  */
   1222       1.1     ragge int
   1223       1.1     ragge xge_setup_xgxs(struct xge_softc *sc)
   1224       1.1     ragge {
   1225       1.1     ragge 	/* The magic numbers are described in the users guide */
   1226       1.1     ragge 
   1227       1.1     ragge 	/* Writing to MDIO 0x8000 (Global Config 0) */
   1228       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8000051500000000ULL); DELAY(50);
   1229       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80000515000000E0ULL); DELAY(50);
   1230       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80000515D93500E4ULL); DELAY(50);
   1231       1.1     ragge 
   1232       1.1     ragge 	/* Writing to MDIO 0x8000 (Global Config 1) */
   1233       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8001051500000000ULL); DELAY(50);
   1234       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80010515000000e0ULL); DELAY(50);
   1235       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80010515001e00e4ULL); DELAY(50);
   1236       1.1     ragge 
   1237       1.1     ragge 	/* Reset the Gigablaze */
   1238       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8002051500000000ULL); DELAY(50);
   1239       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80020515000000E0ULL); DELAY(50);
   1240       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80020515F21000E4ULL); DELAY(50);
   1241       1.1     ragge 
   1242       1.1     ragge 	/* read the pole settings */
   1243       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8000051500000000ULL); DELAY(50);
   1244       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80000515000000e0ULL); DELAY(50);
   1245       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80000515000000ecULL); DELAY(50);
   1246       1.1     ragge 
   1247       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8001051500000000ULL); DELAY(50);
   1248       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80010515000000e0ULL); DELAY(50);
   1249       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80010515000000ecULL); DELAY(50);
   1250       1.1     ragge 
   1251       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x8002051500000000ULL); DELAY(50);
   1252       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80020515000000e0ULL); DELAY(50);
   1253       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x80020515000000ecULL); DELAY(50);
   1254       1.1     ragge 
   1255       1.1     ragge 	/* Workaround for TX Lane XAUI initialization error.
   1256       1.1     ragge 	   Read Xpak PHY register 24 for XAUI lane status */
   1257       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x0018040000000000ULL); DELAY(50);
   1258       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00180400000000e0ULL); DELAY(50);
   1259       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00180400000000ecULL); DELAY(50);
   1260       1.1     ragge 
   1261      1.18  christos 	/*
   1262       1.1     ragge 	 * Reading the MDIO control with value 0x1804001c0F001c
   1263       1.1     ragge 	 * means the TxLanes were already in sync
   1264       1.1     ragge 	 * Reading the MDIO control with value 0x1804000c0x001c
   1265       1.1     ragge 	 * means some TxLanes are not in sync where x is a 4-bit
   1266       1.1     ragge 	 * value representing each lanes
   1267       1.1     ragge 	 */
   1268       1.1     ragge #if 0
   1269       1.1     ragge 	val = PIF_RCSR(MDIO_CONTROL);
   1270       1.1     ragge 	if (val != 0x1804001c0F001cULL) {
   1271      1.18  christos 		printf("%s: MDIO_CONTROL: %llx != %llx\n",
   1272       1.1     ragge 		    XNAME, val, 0x1804001c0F001cULL);
   1273       1.1     ragge 		return 1;
   1274       1.1     ragge 	}
   1275       1.1     ragge #endif
   1276       1.1     ragge 
   1277       1.1     ragge 	/* Set and remove the DTE XS INTLoopBackN */
   1278       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x0000051500000000ULL); DELAY(50);
   1279       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00000515604000e0ULL); DELAY(50);
   1280       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00000515604000e4ULL); DELAY(50);
   1281       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00000515204000e4ULL); DELAY(50);
   1282       1.1     ragge 	PIF_WCSR(DTX_CONTROL, 0x00000515204000ecULL); DELAY(50);
   1283       1.1     ragge 
   1284       1.1     ragge #if 0
   1285       1.1     ragge 	/* Reading the DTX control register Should be 0x5152040001c */
   1286       1.1     ragge 	val = PIF_RCSR(DTX_CONTROL);
   1287       1.1     ragge 	if (val != 0x5152040001cULL) {
   1288      1.18  christos 		printf("%s: DTX_CONTROL: %llx != %llx\n",
   1289       1.1     ragge 		    XNAME, val, 0x5152040001cULL);
   1290       1.1     ragge 		return 1;
   1291       1.1     ragge 	}
   1292       1.1     ragge #endif
   1293       1.1     ragge 
   1294       1.1     ragge 	PIF_WCSR(MDIO_CONTROL, 0x0018040000000000ULL); DELAY(50);
   1295       1.1     ragge 	PIF_WCSR(MDIO_CONTROL, 0x00180400000000e0ULL); DELAY(50);
   1296       1.1     ragge 	PIF_WCSR(MDIO_CONTROL, 0x00180400000000ecULL); DELAY(50);
   1297       1.1     ragge 
   1298       1.1     ragge #if 0
   1299       1.1     ragge 	/* Reading the MIOD control should be 0x1804001c0f001c */
   1300       1.1     ragge 	val = PIF_RCSR(MDIO_CONTROL);
   1301       1.1     ragge 	if (val != 0x1804001c0f001cULL) {
   1302       1.1     ragge 		printf("%s: MDIO_CONTROL2: %llx != %llx\n",
   1303       1.1     ragge 		    XNAME, val, 0x1804001c0f001cULL);
   1304       1.1     ragge 		return 1;
   1305       1.1     ragge 	}
   1306       1.1     ragge #endif
   1307       1.1     ragge 	return 0;
   1308       1.1     ragge }
   1309