summaryrefslogtreecommitdiffstats
path: root/sys/dev/pccbb
diff options
context:
space:
mode:
authorjon <jon@FreeBSD.org>2000-10-18 03:25:13 +0000
committerjon <jon@FreeBSD.org>2000-10-18 03:25:13 +0000
commit9764ffea106deb99ec9392a8d9b44a6af00d0c83 (patch)
treede924ee3021db9fa3110892757126d60330b332c /sys/dev/pccbb
parent8aa6837dc5073e0ff1bbc1f6fbdbf9a14c4444b0 (diff)
downloadFreeBSD-src-9764ffea106deb99ec9392a8d9b44a6af00d0c83.zip
FreeBSD-src-9764ffea106deb99ec9392a8d9b44a6af00d0c83.tar.gz
Initial commit of NEWCARD cardbus side (that actually compiles and works)
Files: dev/cardbus/cardbus.c dev/cardbus/cardbusreg.h dev/cardbus/cardbusvar.h dev/cardbus/cardbus_cis.c dev/cardbus/cardbus_cis.h dev/pccbb/pccbb.c dev/pccbb/pccbbreg.h dev/pccbb/pccbbvar.h dev/pccbb/pccbb_if.m This should support: - cardbus controllers: * TI 113X * TI 12XX * TI 14XX * Ricoh 47X * Ricoh 46X * ToPIC 95 * ToPIC 97 * ToPIC 100 * Cirrus Logic CLPD683x - cardbus cards * 3c575BT * 3c575CT * Xircom X3201 (includes IBM, Xircom and, Intel cards) [ 3com support already in kernel, Xircom will be committed real soon now] This doesn't work with 16bit pccards under NEWCARD. Enable in your config by having "device pccbb" and "device cardbus". (A "device pccard" will attach a pccard bus, but it means you system have a high chance of panicing when a 16bit card is inserted) It should be fairly simple to make a driver attach to cardbus under NEWCARD -- simply add an entry for attaching to cardbus on a new DRIVER_MODULE and add new device IDs as necessary. You should also make sure the card can be detached nicely without the interrupt routine doing something weird, like going into an infinite loop. Usually that should entail adding an additional check when a pci register or the bus space is read to check if it equals 0xffffffff. Any problems, please let me know. Reviewed by: imp
Diffstat (limited to 'sys/dev/pccbb')
-rw-r--r--sys/dev/pccbb/pccbb.c1713
-rw-r--r--sys/dev/pccbb/pccbb_if.m69
-rw-r--r--sys/dev/pccbb/pccbbreg.h188
-rw-r--r--sys/dev/pccbb/pccbbvar.h105
4 files changed, 2075 insertions, 0 deletions
diff --git a/sys/dev/pccbb/pccbb.c b/sys/dev/pccbb/pccbb.c
new file mode 100644
index 0000000..8f9e7ed
--- /dev/null
+++ b/sys/dev/pccbb/pccbb.c
@@ -0,0 +1,1713 @@
+/*
+ * Copyright (c) 2000,2001 Jonathan Chen.
+ * All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions
+ * are met:
+ * 1. Redistributions of source code must retain the above copyright
+ * notice, this list of conditions, and the following disclaimer,
+ * without modification, immediately at the beginning of the file.
+ * 2. Redistributions in binary form must reproduce the above copyright
+ * notice, this list of conditions and the following disclaimer in
+ * the documentation and/or other materials provided with the
+ * distribution.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
+ * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR
+ * ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ * SUCH DAMAGE.
+ *
+ * $FreeBSD$
+ */
+
+/*
+ * Driver for PCI to Cardbus Bridge chips
+ *
+ * References:
+ * TI Datasheets:
+ * http://www-s.ti.com/cgi-bin/sc/generic2.cgi?family=PCI+CARDBUS+CONTROLLERS
+ * Much of the 16-bit PC Card compatibility code stolen from dev/pcic/i82365.c
+ *
+ * Written by Jonathan Chen <jon@freebsd.org>
+ * The author would like to acknowledge:
+ * * HAYAKAWA Koichi: Author of the NetBSD code for the same thing
+ * * Warner Losh: Newbus/newcard guru and author of the pccard side of things
+ * * YAMAMOTO Shigeru: Author of another FreeBSD cardbus driver
+ * * David Cross: Author of the initial ugly hack for a specific cardbus card
+ */
+
+#define CBB_DEBUG
+
+#include <sys/param.h>
+#include <sys/systm.h>
+#include <sys/errno.h>
+#include <sys/kernel.h>
+#include <sys/kthread.h>
+#include <sys/malloc.h>
+
+#include <sys/bus.h>
+#include <machine/bus.h>
+#include <sys/rman.h>
+#include <machine/resource.h>
+
+#include <pci/pcireg.h>
+#include <pci/pcivar.h>
+#include <machine/clock.h>
+
+#include <dev/pccard/pccardreg.h>
+#include <dev/pccard/pccardvar.h>
+#include <dev/pcic/i82365reg.h>
+
+#include <dev/pccbb/pccbbreg.h>
+#include <dev/pccbb/pccbbvar.h>
+
+#include "power_if.h"
+#include "card_if.h"
+#include "pccbb_if.h"
+#include "pcib_if.h"
+
+#if defined CBB_DEBUG
+#define DPRINTF(x) printf x
+#define DEVPRINTF(x) device_printf x
+#else
+#define DPRINTF(x)
+#define DEVPRINTF(x)
+#endif
+
+#define PCI_MASK_CONFIG(DEV,REG,MASK,SIZE) \
+ pci_write_config(DEV, REG, pci_read_config(DEV, REG, SIZE) MASK, SIZE)
+#define PCI_MASK2_CONFIG(DEV,REG,MASK1,MASK2,SIZE) \
+ pci_write_config(DEV, REG, ( \
+ pci_read_config(DEV, REG, SIZE) MASK1) MASK2, SIZE)
+
+#define PCIC_READ(SC,REG) \
+ (((u_int8_t*)((SC)->sc_socketreg))[0x800+(REG)])
+#define PCIC_WRITE(SC,REG,val) \
+ (((u_int8_t*)((SC)->sc_socketreg))[0x800+(REG)]) = (val)
+#define PCIC_MASK(SC,REG,MASK) \
+ PCIC_WRITE(SC,REG,PCIC_READ(SC,REG) MASK)
+#define PCIC_MASK2(SC,REG,MASK,MASK2) \
+ PCIC_WRITE(SC,REG,(PCIC_READ(SC,REG) MASK) MASK2)
+
+#define DETACH_FORCE 0x1
+
+#if !defined(lint)
+static const char rcsid[] =
+ "$FreeBSD $";
+#endif
+
+
+struct pccbb_sclist {
+ struct pccbb_softc *sc;
+ STAILQ_ENTRY(pccbb_sclist) entries;
+};
+
+static STAILQ_HEAD(, pccbb_sclist) softcs;
+static int softcs_init = 0;
+
+
+struct yenta_chipinfo {
+ u_int32_t yc_id;
+ const char *yc_name;
+ int yc_chiptype;
+ int yc_flags;
+} yc_chipsets[] = {
+ /* Texas Instruments chips */
+ {PCI_DEVICE_ID_PCIC_TI1130, "TI1130 PCI-CardBus Bridge", CB_TI113X,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1131, "TI1131 PCI-CardBus Bridge", CB_TI113X,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+
+ {PCI_DEVICE_ID_PCIC_TI1211, "TI1211 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1220, "TI1220 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1221, "TI1221 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1225, "TI1225 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1250, "TI1250 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1251, "TI1251 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1251B,"TI1251B PCI-CardBus Bridge",CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1410, "TI1410 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1420, "TI1420 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1450, "TI1450 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_TI1451, "TI1451 PCI-CardBus Bridge", CB_TI12XX,
+ PCCBB_PCIC_IO_RELOC | PCCBB_PCIC_MEM_32},
+
+ /* Ricoh chips */
+ {PCI_DEVICE_ID_RICOH_RL5C465, "RF5C465 PCI-CardBus Bridge",
+ CB_RF5C46X, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_RICOH_RL5C466, "RF5C466 PCI-CardBus Bridge",
+ CB_RF5C46X, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_RICOH_RL5C475, "RF5C475 PCI-CardBus Bridge",
+ CB_RF5C47X, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_RICOH_RL5C476, "RF5C476 PCI-CardBus Bridge",
+ CB_RF5C47X, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_RICOH_RL5C478, "RF5C478 PCI-CardBus Bridge",
+ CB_RF5C47X, PCCBB_PCIC_MEM_32},
+
+ /* Toshiba products */
+ {PCI_DEVICE_ID_TOSHIBA_TOPIC95, "ToPIC95 PCI-CardBus Bridge",
+ CB_TOPIC95, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_TOSHIBA_TOPIC95B, "ToPIC95B PCI-CardBus Bridge",
+ CB_TOPIC95B, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_TOSHIBA_TOPIC97, "ToPIC97 PCI-CardBus Bridge",
+ CB_TOPIC97, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_TOSHIBA_TOPIC100, "ToPIC100 PCI-CardBus Bridge",
+ CB_TOPIC97, PCCBB_PCIC_MEM_32},
+
+ /* Cirrus Logic */
+ {PCI_DEVICE_ID_PCIC_CLPD6832, "CLPD6832 PCI-CardBus Bridge",
+ CB_CIRRUS, PCCBB_PCIC_MEM_32},
+ {PCI_DEVICE_ID_PCIC_CLPD6833, "CLPD6833 PCI-CardBus Bridge",
+ CB_CIRRUS, PCCBB_PCIC_MEM_32},
+
+ /* sentinel */
+ {0 /* null id */, "unknown",
+ CB_UNKNOWN, 0},
+};
+
+
+static int cb_chipset(u_int32_t pci_id, const char** namep, int* flagp);
+static int pccbb_probe(device_t dev);
+static void pccbb_chipinit(struct pccbb_softc* sc);
+static int pccbb_attach(device_t dev);
+static void pccbb_event_thread (void *arg);
+static void pccbb_create_event_thread (struct pccbb_softc *sc);
+static void pccbb_start_threads(void *arg);
+static void pccbb_insert (struct pccbb_softc *sc);
+static void pccbb_removal (struct pccbb_softc *sc);
+static void pccbb_intr(void* arg);
+static int pccbb_detect_voltage(struct pccbb_softc *sc);
+static int pccbb_power(device_t dev, int volts);
+static int pccbb_cardbus_detect_card(device_t dev);
+static int pccbb_cardbus_reset(device_t dev);
+static int pccbb_cardbus_io_open(device_t dev, int win,
+ u_int32_t start, u_int32_t end);
+static int pccbb_cardbus_mem_open(device_t dev, int win,
+ u_int32_t start, u_int32_t end);
+static void pccbb_cardbus_auto_open(struct pccbb_softc *sc, int type);
+static int pccbb_cardbus_activate_resource(device_t self, device_t child,
+ int type, int rid,
+ struct resource *r);
+static int pccbb_cardbus_deactivate_resource(device_t self, device_t child,
+ int type, int rid,
+ struct resource *r);
+static struct resource* pccbb_cardbus_alloc_resource(device_t self,
+ device_t child, int type, int* rid,
+ u_long start, u_long end, u_long count,
+ u_int flags);
+static int pccbb_cardbus_release_resource(device_t self, device_t child,
+ int type,int rid,
+ struct resource *r);
+static void pccbb_pcic_wait_ready(struct pccbb_softc *sc);
+static void pccbb_pcic_do_mem_map(struct pccbb_softc *sc, int win);
+static int pccbb_pcic_mem_map(struct pccbb_softc *sc, int kind,
+ struct resource *r, bus_addr_t card_addr,
+ int *win);
+static void pccbb_pcic_mem_unmap(struct pccbb_softc *sc, int window);
+static void pccbb_pcic_do_io_map(struct pccbb_softc *sc, int win);
+static int pccbb_pcic_io_map(struct pccbb_softc *sc, int width,
+ struct resource *r, bus_addr_t card_addr,
+ int *win);
+static void pccbb_pcic_io_unmap(struct pccbb_softc *sc, int window);
+static int pccbb_pcic_activate_resource(device_t self, device_t child,
+ int type, int rid, struct resource *r);
+static int pccbb_pcic_deactivate_resource(device_t self, device_t child,
+ int type,int rid, struct resource *r);
+static struct resource* pccbb_pcic_alloc_resource(device_t self,device_t child,
+ int type, int* rid, u_long start,
+ u_long end, u_long count, u_int flags);
+static int pccbb_pcic_release_resource(device_t self, device_t child, int type,
+ int rid, struct resource *res);
+static int pccbb_pcic_set_res_flags(device_t self, device_t child, int type,
+ int rid, u_int32_t flags);
+static int pccbb_pcic_set_memory_offset(device_t self, device_t child, int rid,
+ u_int32_t offset);
+static int pccbb_pcic_enable_socket(device_t self, device_t child);
+static void pccbb_pcic_disable_socket(device_t self, device_t child);
+static int pccbb_activate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r);
+static int pccbb_deactivate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r);
+static struct resource* pccbb_alloc_resource(device_t self, device_t child,
+ int type, int* rid, u_long start,
+ u_long end, u_long count,
+ u_int flags);
+static int pccbb_release_resource(device_t self, device_t child,
+ int type, int rid, struct resource *r);
+
+
+/************************************************************************/
+/* Probe/Attach */
+/************************************************************************/
+
+static int
+cb_chipset(u_int32_t pci_id, const char** namep, int* flagp)
+{
+ int loopend = sizeof(yc_chipsets)/sizeof(yc_chipsets[0]);
+ struct yenta_chipinfo *ycp, *ycend;
+ ycend = yc_chipsets + loopend;
+
+ for (ycp = yc_chipsets; ycp < ycend && pci_id != ycp->yc_id; ++ycp);
+ if (ycp == ycend) {
+ /* not found */
+ ycp = yc_chipsets + loopend - 1; /* to point the sentinel */
+ }
+ if (namep != NULL) {
+ *namep = ycp->yc_name;
+ }
+ if (flagp != NULL) {
+ *flagp = ycp->yc_flags;
+ }
+ return ycp->yc_chiptype;
+}
+
+static int
+pccbb_probe(device_t dev)
+{
+ const char *name;
+
+ if (cb_chipset(pci_get_devid(dev), &name, NULL) == CB_UNKNOWN)
+ return ENXIO;
+ device_set_desc(dev, name);
+ return 0;
+}
+
+static void
+pccbb_chipinit(struct pccbb_softc* sc)
+{
+ /* Set CardBus latency timer */
+ if (pci_read_config(sc->sc_dev, PCIR_SECLAT_1, 1) < 0x20)
+ pci_write_config(sc->sc_dev, PCIR_SECLAT_1, 0x20, 1);
+
+ /* Set PCI latency timer */
+ if (pci_read_config(sc->sc_dev, PCIR_LATTIMER, 1) < 0x20)
+ pci_write_config(sc->sc_dev, PCIR_LATTIMER, 0x20, 1);
+
+ /* Enable memory access */
+ PCI_MASK_CONFIG(sc->sc_dev, PCIR_COMMAND,
+ | PCIM_CMD_MEMEN
+ | PCIM_CMD_PORTEN
+ | PCIM_CMD_BUSMASTEREN, 2);
+
+ /* disable Legacy IO */
+
+ switch (sc->sc_chipset) {
+ case CB_RF5C46X:
+ PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_BRIDGECTRL,
+ & ~(PCCBBM_BRIDGECTRL_RL_3E0_EN|
+ PCCBBM_BRIDGECTRL_RL_3E2_EN), 2);
+ break;
+ default:
+ pci_write_config(sc->sc_dev, PCCBBR_LEGACY, 0x0, 4);
+ break;
+ }
+
+ /* Use PCI interrupt for interrupt routing */
+ PCI_MASK2_CONFIG(sc->sc_dev, PCCBBR_BRIDGECTRL,
+ & ~(PCCBBM_BRIDGECTRL_MASTER_ABORT |
+ PCCBBM_BRIDGECTRL_INTR_IREQ_EN),
+ | PCCBBM_BRIDGECTRL_WRITE_POST_EN,
+ 2);
+
+ switch (sc->sc_chipset) {
+ case CB_TI113X:
+ PCI_MASK2_CONFIG(sc->sc_dev, PCCBBR_CBCTRL,
+ & ~PCCBBM_CBCTRL_113X_PCI_INTR,
+ | PCCBBM_CBCTRL_113X_PCI_CSC
+ | PCCBBM_CBCTRL_113X_PCI_IRQ_EN, 1);
+ PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_DEVCTRL,
+ & ~(PCCBBM_DEVCTRL_INT_SERIAL|
+ PCCBBM_DEVCTRL_INT_PCI), 1);
+ PCIC_WRITE(sc, PCIC_INTR, PCIC_INTR_ENABLE);
+ PCIC_WRITE(sc, PCIC_CSC_INTR, 0);
+ break;
+ case CB_TI12XX:
+ PCIC_WRITE(sc, PCIC_INTR, PCIC_INTR_ENABLE);
+ PCIC_WRITE(sc, PCIC_CSC_INTR, 0);
+ break;
+ case CB_TOPIC95B:
+ PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_TOPIC_SOCKETCTRL,
+ | PCCBBM_TOPIC_SOCKETCTRL_SCR_IRQSEL, 4);
+ PCI_MASK2_CONFIG(sc->sc_dev, PCCBBR_TOPIC_SLOTCTRL,
+ | PCCBBM_TOPIC_SLOTCTRL_SLOTON
+ | PCCBBM_TOPIC_SLOTCTRL_SLOTEN
+ | PCCBBM_TOPIC_SLOTCTRL_ID_LOCK
+ | PCCBBM_TOPIC_SLOTCTRL_CARDBUS,
+ & ~PCCBBM_TOPIC_SLOTCTRL_SWDETECT, 4);
+ break;
+ }
+
+ /* close all memory and io windows */
+ pci_write_config(sc->sc_dev, PCCBBR_MEMBASE0, 0xffffffff, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_MEMLIMIT0, 0, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_MEMBASE1, 0xffffffff, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_MEMLIMIT1, 0, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_IOBASE0, 0xffffffff, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_IOLIMIT0, 0, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_IOBASE1, 0xffffffff, 4);
+ pci_write_config(sc->sc_dev, PCCBBR_IOLIMIT1, 0, 4);
+}
+
+static int
+pccbb_attach(device_t dev)
+{
+ struct pccbb_softc *sc = (struct pccbb_softc *)device_get_softc(dev);
+ int flags;
+ int rid;
+ u_int32_t tmp;
+
+ if (!softcs_init) {
+ softcs_init = 1;
+ STAILQ_INIT(&softcs);
+ }
+ sc->sc_chipset = cb_chipset(pci_get_devid(dev), NULL, &flags);
+ sc->sc_dev = dev;
+ sc->sc_flags = 0;
+ sc->sc_cbdev = NULL;
+ sc->sc_pccarddev = NULL;
+ sc->memalloc = 0;
+ sc->ioalloc = 0;
+ SLIST_INIT(&sc->rl);
+
+ /* Ths PCI bus should have given me memory... right? */
+ rid=PCCBBR_SOCKBASE;
+ sc->sc_base_res=bus_alloc_resource(dev, SYS_RES_MEMORY, &rid,
+ 0,~0,1, RF_ACTIVE);
+ if (!sc->sc_base_res){
+ /*
+ * XXX EVILE HACK BAD THING! XXX
+ * Some BIOSes doesn't assign a memory space properly.
+ * So we try to manually put one in...
+ */
+ u_int32_t sockbase;
+
+ sockbase = pci_read_config(dev, rid, 4);
+ if (sockbase < 0x100000 || sockbase >= 0xfffffff0) {
+ pci_write_config(dev, rid, 0xffffffff, 4);
+ sockbase = pci_read_config(dev, rid, 4);
+ sockbase = (sockbase & 0xfffffff0) &
+ -(sockbase & 0xfffffff0);
+ sc->sc_base_res = bus_generic_alloc_resource(
+ device_get_parent(dev), dev, SYS_RES_MEMORY,
+ &rid, CARDBUS_SYS_RES_MEMORY_START,
+ CARDBUS_SYS_RES_MEMORY_END, sockbase,
+ RF_ACTIVE|rman_make_alignment_flags(sockbase));
+ if (!sc->sc_base_res){
+ device_printf(dev,
+ "Could not grab register memory\n");
+ return ENOMEM;
+ }
+ pci_write_config(dev, PCCBBR_SOCKBASE,
+ rman_get_start(sc->sc_base_res), 4);
+ DEVPRINTF((dev, "PCI Memory allocated: %08lx\n",
+ rman_get_start(sc->sc_base_res)));
+ } else {
+ device_printf(dev, "Could not map register memory\n");
+ return ENOMEM;
+ }
+ }
+
+ sc->sc_socketreg =
+ (struct pccbb_socketreg *)rman_get_virtual(sc->sc_base_res);
+
+ pccbb_chipinit(sc);
+
+ /* CSC Interrupt: Card detect interrupt on */
+ sc->sc_socketreg->socket_mask |= PCCBB_SOCKET_MASK_CD;
+
+ /* reset interrupt */
+ tmp = sc->sc_socketreg->socket_event;
+ sc->sc_socketreg->socket_event = tmp;
+
+ /* Map and establish the interrupt. */
+ rid=0;
+ sc->sc_irq_res=bus_alloc_resource(dev, SYS_RES_IRQ, &rid, 0, ~0, 1,
+ RF_SHAREABLE | RF_ACTIVE);
+ if (sc->sc_irq_res == NULL) {
+ printf("pccbb: Unable to map IRQ...\n");
+ return ENOMEM;
+ }
+
+ if (bus_setup_intr(dev, sc->sc_irq_res, INTR_TYPE_BIO, pccbb_intr, sc,
+ &(sc->sc_intrhand))) {
+ device_printf(dev, "couldn't establish interrupt");
+ bus_release_resource(dev, SYS_RES_IRQ, 0, sc->sc_irq_res);
+ bus_release_resource(dev, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
+ sc->sc_base_res);
+ return ENOMEM;
+ }
+
+ /* attach children */
+ sc->sc_cbdev = device_add_child(dev, "cardbus", -1);
+ if (sc->sc_cbdev == NULL)
+ DEVPRINTF((dev, "Cannot add cardbus bus!\n"));
+ else if (device_probe_and_attach(sc->sc_cbdev) != 0) {
+ DEVPRINTF((dev, "Cannot attach cardbus bus!\n"));
+ sc->sc_cbdev = NULL;
+ }
+
+ sc->sc_pccarddev = device_add_child(dev, "pccard", -1);
+ if (sc->sc_pccarddev == NULL)
+ DEVPRINTF((dev, "Cannot add pccard bus!\n"));
+ else if (device_probe_and_attach(sc->sc_pccarddev) != 0) {
+ DEVPRINTF((dev, "Cannot attach pccard bus!\n"));
+ sc->sc_pccarddev = NULL;
+ }
+
+ if (sc->sc_cbdev == NULL && sc->sc_pccarddev == NULL) {
+ device_printf(dev, "Failed to attach cardbus/pccard bus!\n");
+ bus_teardown_intr(dev, sc->sc_irq_res, sc->sc_intrhand);
+ bus_release_resource(dev, SYS_RES_IRQ, 0, sc->sc_irq_res);
+ bus_release_resource(dev, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
+ sc->sc_base_res);
+ return ENOMEM;
+ }
+
+ {
+ struct pccbb_sclist *sclist;
+ sclist = malloc(sizeof(struct pccbb_sclist), M_DEVBUF,
+ M_WAITOK);
+ sclist->sc = sc;
+ STAILQ_INSERT_TAIL(&softcs, sclist, entries);
+ }
+ return 0;
+}
+
+/************************************************************************/
+/* Kthreads */
+/************************************************************************/
+
+static void
+pccbb_event_thread (void *arg)
+{
+ struct pccbb_softc *sc = arg;
+ int s;
+ u_int32_t status;
+
+ s = splhigh();
+ for(;;) {
+ if (sc->sc_flags & PCCBB_INITIALCARD)
+ sc->sc_flags &= ~PCCBB_INITIALCARD;
+ else {
+ splx (s);
+ tsleep (sc, PWAIT, "pccbbev", 0);
+ /*
+ * Delay some time, make sure the user is done with
+ * whatever he is doing.
+ */
+ DELAY(1000*1000);
+ s = splhigh();
+ }
+
+ sc->sc_flags |= PCCBB_CARDSTATUS_BUSY;
+ status = sc->sc_socketreg->socket_state;
+ if ((status & PCCBB_SOCKET_STAT_CD) == 0) {
+ if (!(sc->sc_flags & PCCBB_CARDATTACHED))
+ pccbb_insert(sc);
+ else
+ device_printf(sc->sc_dev,
+ "duplicate card insert\n");
+ } else {
+ if (!(sc->sc_flags & PCCBB_CARDATTACHED))
+ DEVPRINTF((sc->sc_dev,
+ "removal of nonexistant card!\n"));
+ else
+ pccbb_removal(sc);
+ }
+ sc->sc_flags &= ~PCCBB_CARDSTATUS_BUSY;
+ splx (s);
+ }
+ /* NOTREACHED */
+ kthread_exit(0);
+}
+
+static void
+pccbb_create_event_thread (struct pccbb_softc *sc)
+{
+ if (kthread_create(pccbb_event_thread, sc, &sc->event_thread,
+ 0, "%s%d", device_get_name(sc->sc_dev),
+ device_get_unit(sc->sc_dev))) {
+ device_printf (sc->sc_dev, "unable to create event thread.\n");
+ panic ("pccbb_create_event_thread");
+ }
+}
+
+static void
+pccbb_start_threads(void *arg)
+{
+ struct pccbb_sclist *sclist;
+
+ STAILQ_FOREACH(sclist, &softcs, entries) {
+ if (0 == (sclist->sc->sc_socketreg->socket_state &
+ PCCBB_SOCKET_STAT_CD)) {
+ sclist->sc->sc_flags |= PCCBB_INITIALCARD;
+ }
+ pccbb_create_event_thread(sclist->sc);
+ }
+}
+
+/************************************************************************/
+/* Insert/removal */
+/************************************************************************/
+
+static void
+pccbb_insert (struct pccbb_softc *sc)
+{
+ u_int32_t sockevent, sockstate;
+ int timeout = 30;
+
+ do {
+ sockevent = sc->sc_socketreg->socket_event;
+ sockstate = sc->sc_socketreg->socket_state;
+ } while (sockstate & PCCBB_SOCKET_STAT_CD && --timeout > 0);
+
+ if (timeout < 0) {
+ device_printf (sc->sc_dev, "insert timeout");
+ return;
+ }
+
+ DEVPRINTF((sc->sc_dev, "card inserted: event=0x%08x, state=%08x\n",
+ sockevent, sockstate));
+
+ if (sockstate & PCCBB_SOCKET_STAT_16BIT && sc->sc_pccarddev != NULL) {
+ sc->sc_flags |= PCCBB_CARDATTACHED | PCCBB_16BIT_CARD;
+ if (CARD_ATTACH_CARD(sc->sc_pccarddev) != 0) {
+ device_printf(sc->sc_dev, "card activation failed\n");
+ sc->sc_flags &= ~PCCBB_CARDATTACHED;
+ }
+ } else if (sockstate & PCCBB_SOCKET_STAT_CB && sc->sc_cbdev != NULL) {
+ sc->sc_flags |= PCCBB_CARDATTACHED;
+ sc->sc_flags &= ~PCCBB_16BIT_CARD;
+ if (CARD_ATTACH_CARD(sc->sc_cbdev) != 0) {
+ device_printf(sc->sc_dev, "card activation failed\n");
+ sc->sc_flags &= ~PCCBB_CARDATTACHED;
+ }
+ } else {
+ device_printf (sc->sc_dev, "Unsupported card type detected\n");
+ }
+}
+
+static void
+pccbb_removal (struct pccbb_softc *sc)
+{
+ u_int32_t sockstate;
+ struct pccbb_reslist *rle;
+
+ sockstate = sc->sc_socketreg->socket_state;
+
+ sc->sc_flags &= ~PCCBB_CARDATTACHED;
+ if (sockstate & PCCBB_16BIT_CARD)
+ CARD_DETACH_CARD(sc->sc_pccarddev, DETACH_FORCE);
+ else
+ CARD_DETACH_CARD(sc->sc_cbdev, DETACH_FORCE);
+
+ while (NULL != (rle = SLIST_FIRST(&sc->rl))) {
+ device_printf(sc->sc_dev, "WARNING: Resource left allocated! "
+ "This is a bug... (rid=%x, type=%d, addr=%x)\n",
+ rle->rid, rle->type, rle->start);
+ SLIST_REMOVE_HEAD(&sc->rl, entries);
+ }
+}
+
+/************************************************************************/
+/* Interrupt Handler */
+/************************************************************************/
+
+static void
+pccbb_intr(void* arg)
+{
+ struct pccbb_softc *sc = arg;
+ u_int32_t sockevent;
+ int tmp;
+
+ if (!(sockevent = sc->sc_socketreg->socket_event)) {
+ /* not for me. */
+ return;
+ }
+
+ /* reset bit */
+ sc->sc_socketreg->socket_event = sockevent | 0x01;
+
+ if (sockevent & PCCBB_SOCKET_EVENT_CD) {
+ for (tmp = 0; tmp <= 100 &&
+ (sc->sc_flags & PCCBB_CARDSTATUS_BUSY); tmp++) {
+ if (tmp == 0)
+ DEVPRINTF((sc->sc_dev, "(pccbbintr): busy!"));
+ else
+ DPRINTF(("."));
+ DELAY(1);
+ }
+ if (sc->sc_flags & PCCBB_CARDSTATUS_BUSY) {
+ DPRINTF(("failed! Going ahead anyway..."));
+ sc->sc_flags &= ~PCCBB_CARDSTATUS_BUSY;
+ }
+ wakeup(sc);
+ } else {
+ if (sockevent & PCCBB_SOCKET_EVENT_CSTS) {
+ DPRINTF((" cstsevent occures, 0x%08x\n",
+ sc->sc_socketreg->socket_state));
+ }
+ if (sockevent & PCCBB_SOCKET_EVENT_POWER) {
+ DPRINTF((" pwrevent occures, 0x%08x\n",
+ sc->sc_socketreg->socket_state));
+ }
+ }
+
+ return;
+}
+
+/************************************************************************/
+/* Power functions */
+/************************************************************************/
+
+static int
+pccbb_detect_voltage(struct pccbb_softc *sc)
+{
+ u_int32_t psr;
+ int vol = CARD_UKN_CARD;
+
+ psr = sc->sc_socketreg->socket_state;
+
+ if (psr & PCCBB_SOCKET_STAT_5VCARD) {
+ vol |= CARD_5V_CARD;
+ }
+ if (psr & PCCBB_SOCKET_STAT_3VCARD) {
+ vol |= CARD_3V_CARD;
+ }
+ if (psr & PCCBB_SOCKET_STAT_XVCARD) {
+ vol |= CARD_XV_CARD;
+ }
+ if (psr & PCCBB_SOCKET_STAT_YVCARD) {
+ vol |= CARD_YV_CARD;
+ }
+
+ return vol;
+}
+
+static int
+pccbb_power(device_t dev, int volts)
+{
+ u_int32_t status, sock_ctrl;
+ struct pccbb_softc *sc = device_get_softc(dev);
+
+ DEVPRINTF((sc->sc_dev, "pccbb_power: %s and %s [%x]\n",
+ (volts & CARD_VCCMASK) == CARD_VCC_UC ? "CARD_VCC_UC" :
+ (volts & CARD_VCCMASK) == CARD_VCC_5V ? "CARD_VCC_5V" :
+ (volts & CARD_VCCMASK) == CARD_VCC_3V ? "CARD_VCC_3V" :
+ (volts & CARD_VCCMASK) == CARD_VCC_XV ? "CARD_VCC_XV" :
+ (volts & CARD_VCCMASK) == CARD_VCC_YV ? "CARD_VCC_YV" :
+ (volts & CARD_VCCMASK) == CARD_VCC_0V ? "CARD_VCC_0V" :
+ "VCC-UNKNOWN",
+ (volts & CARD_VPPMASK) == CARD_VPP_UC ? "CARD_VPP_UC" :
+ (volts & CARD_VPPMASK) == CARD_VPP_12V ? "CARD_VPP_12V" :
+ (volts & CARD_VPPMASK) == CARD_VPP_VCC ? "CARD_VPP_VCC" :
+ (volts & CARD_VPPMASK) == CARD_VPP_0V ? "CARD_VPP_0V" :
+ "VPP-UNKNOWN",
+ volts));
+
+ status = sc->sc_socketreg->socket_state;
+ sock_ctrl = sc->sc_socketreg->socket_control;
+
+ switch (volts & CARD_VCCMASK) {
+ case CARD_VCC_UC:
+ break;
+ case CARD_VCC_5V:
+ if (PCCBB_SOCKET_STAT_5VCARD & status) { /* check 5 V card */
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VCCMASK;
+ sock_ctrl |= PCCBB_SOCKET_CTRL_VCC_5V;
+ } else {
+ device_printf(sc->sc_dev,
+ "BAD voltage request: no 5 V card\n");
+ }
+ break;
+ case CARD_VCC_3V:
+ if (PCCBB_SOCKET_STAT_3VCARD & status) {
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VCCMASK;
+ sock_ctrl |= PCCBB_SOCKET_CTRL_VCC_3V;
+ } else {
+ device_printf(sc->sc_dev,
+ "BAD voltage request: no 3.3 V card\n");
+ }
+ break;
+ case CARD_VCC_0V:
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VCCMASK;
+ break;
+ default:
+ return 0; /* power NEVER changed */
+ break;
+ }
+
+ switch (volts & CARD_VPPMASK) {
+ case CARD_VPP_UC:
+ break;
+ case CARD_VPP_0V:
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VPPMASK;
+ break;
+ case CARD_VPP_VCC:
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VPPMASK;
+ sock_ctrl |= ((sock_ctrl >> 4) & 0x07);
+ break;
+ case CARD_VPP_12V:
+ sock_ctrl &= ~PCCBB_SOCKET_CTRL_VPPMASK;
+ sock_ctrl |= PCCBB_SOCKET_CTRL_VPP_12V;
+ break;
+ }
+
+ sc->sc_socketreg->socket_control = sock_ctrl;
+ status = sc->sc_socketreg->socket_state;
+
+ {
+ int timeout = 20;
+ u_int32_t sockevent;
+ do {
+ DELAY(20*1000);
+ sockevent = sc->sc_socketreg->socket_event;
+ } while (!(sockevent & PCCBB_SOCKET_EVENT_POWER) &&
+ --timeout > 0);
+ /* reset event status */
+ sc->sc_socketreg->socket_event = sockevent;
+ if ( timeout < 0 ) {
+ printf ("VCC supply failed.\n");
+ return 0;
+ }
+ }
+ /* XXX
+ * delay 400 ms: thgough the standard defines that the Vcc set-up time
+ * is 20 ms, some PC-Card bridge requires longer duration.
+ */
+ DELAY(400*1000);
+
+ if (status & PCCBB_SOCKET_STAT_BADVCC) {
+ device_printf(sc->sc_dev,
+ "bad Vcc request. ctrl=0x%x, status=0x%x\n",
+ sock_ctrl ,status);
+ printf("pccbb_power: %s and %s [%x]\n",
+ (volts & CARD_VCCMASK) == CARD_VCC_UC ? "CARD_VCC_UC" :
+ (volts & CARD_VCCMASK) == CARD_VCC_5V ? "CARD_VCC_5V" :
+ (volts & CARD_VCCMASK) == CARD_VCC_3V ? "CARD_VCC_3V" :
+ (volts & CARD_VCCMASK) == CARD_VCC_XV ? "CARD_VCC_XV" :
+ (volts & CARD_VCCMASK) == CARD_VCC_YV ? "CARD_VCC_YV" :
+ (volts & CARD_VCCMASK) == CARD_VCC_0V ? "CARD_VCC_0V" :
+ "VCC-UNKNOWN",
+ (volts & CARD_VPPMASK) == CARD_VPP_UC ? "CARD_VPP_UC" :
+ (volts & CARD_VPPMASK) == CARD_VPP_12V ? "CARD_VPP_12V":
+ (volts & CARD_VPPMASK) == CARD_VPP_VCC ? "CARD_VPP_VCC":
+ (volts & CARD_VPPMASK) == CARD_VPP_0V ? "CARD_VPP_0V" :
+ "VPP-UNKNOWN",
+ volts);
+ return 0;
+ }
+ return 1; /* power changed correctly */
+}
+
+/************************************************************************/
+/* PCCBB methods */
+/************************************************************************/
+
+static int
+pccbb_cardbus_detect_card(device_t dev)
+{
+ struct pccbb_softc *sc = device_get_softc(dev);
+ u_int32_t sockstat = sc->sc_socketreg->socket_state;
+
+ if (sockstat & PCCBB_SOCKET_STAT_CB)
+ return pccbb_detect_voltage(sc);
+ return 0;
+}
+
+static int
+pccbb_cardbus_reset(device_t dev)
+{
+ struct pccbb_softc *sc = device_get_softc(dev);
+ u_int32_t bcr = pci_read_config(dev, PCCBBR_BRIDGECTRL, 2);
+ int delay_us;
+
+ delay_us = sc->sc_chipset == CB_RF5C47X ? 400*1000 : 20*1000;
+
+ bcr |= PCCBBM_BRIDGECTRL_RESET;
+ pci_write_config(dev, PCCBBR_BRIDGECTRL, bcr, 2);
+
+ DELAY(delay_us);
+
+ /* If a card exists, unreset it! */
+ if (sc->sc_flags & PCCBB_CARDATTACHED) {
+ bcr &= ~PCCBBM_BRIDGECTRL_RESET;
+ pci_write_config(dev, PCCBBR_BRIDGECTRL, bcr, 2);
+ DELAY(delay_us);
+ }
+ return 1;
+}
+
+
+/************************************************************************/
+/* Cardbus Resource */
+/************************************************************************/
+
+static int
+pccbb_cardbus_io_open(device_t dev, int win, u_int32_t start, u_int32_t end)
+{
+ int basereg;
+ int limitreg;
+
+ if ((win < 0) || (win > 1)) {
+ DEVPRINTF((dev,
+ "pccbb_cardbus_io_open: window out of range %d\n",
+ win));
+ return EINVAL;
+ }
+
+ basereg = win*8 + PCCBBR_IOBASE0;
+ limitreg = win*8 + PCCBBR_IOLIMIT0;
+
+ pci_write_config(dev, basereg, start, 4);
+ pci_write_config(dev, limitreg, end, 4);
+ return 0;
+}
+
+static int
+pccbb_cardbus_mem_open(device_t dev, int win, u_int32_t start, u_int32_t end)
+{
+ int basereg;
+ int limitreg;
+
+ if ((win < 0) || (win > 1)) {
+ DEVPRINTF((dev,
+ "pccbb_cardbus_mem_open: window out of range %d\n",
+ win));
+ return EINVAL;
+ }
+
+ basereg = win*8 + PCCBBR_MEMBASE0;
+ limitreg = win*8 + PCCBBR_MEMLIMIT0;
+
+ pci_write_config(dev, basereg, start, 4);
+ pci_write_config(dev, limitreg, end, 4);
+ return 0;
+}
+
+static void
+pccbb_cardbus_auto_open(struct pccbb_softc *sc, int type)
+{
+ u_int32_t starts[2];
+ u_int32_t ends[2];
+ struct pccbb_reslist *rle;
+ int align;
+
+ starts[0] = starts[1] = 0xffffffff;
+ ends[0] = ends[1] = 0;
+
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (rle->type != type)
+ ;
+ else if (starts[0] == 0xffffffff) {
+ starts[0] = rle->start;
+ ends[0] = rle->end;
+ rle->win = 0;
+ } else if (rle->end > ends[0] &&
+ rle->start - ends[0] < PCCBB_AUTO_OPEN_SMALLHOLE) {
+ ends[0] = rle->end;
+ rle->win = 0;
+ } else if (rle->start < starts[0] &&
+ starts[0] - rle->end < PCCBB_AUTO_OPEN_SMALLHOLE) {
+ starts[0] = rle->start;
+ rle->win = 0;
+ } else if (starts[1] == 0xffffffff) {
+ starts[1] = rle->start;
+ ends[1] = rle->end;
+ rle->win = 1;
+ } else if (rle->end > ends[1] &&
+ rle->start - ends[1] < PCCBB_AUTO_OPEN_SMALLHOLE) {
+ ends[1] = rle->end;
+ rle->win = 1;
+ } else if (rle->start < starts[1] &&
+ starts[1] - rle->end < PCCBB_AUTO_OPEN_SMALLHOLE) {
+ starts[1] = rle->start;
+ rle->win = 1;
+ } else {
+ u_int32_t diffs[2];
+
+ diffs[0] = diffs[1] = 0xffffffff;
+ if (rle->start > ends[0])
+ diffs[0] = rle->start - ends[0];
+ else if (rle->end < starts[0])
+ diffs[0] = starts[0] - rle->end;
+ if (rle->start > ends[1])
+ diffs[1] = rle->start - ends[1];
+ else if (rle->end < starts[1])
+ diffs[1] = starts[1] - rle->end;
+
+ rle->win = (diffs[0] <= diffs[1])?0:1;
+ if (rle->start > ends[rle->win])
+ ends[rle->win] = rle->end;
+ else if (rle->end < starts[rle->win])
+ starts[rle->win] = rle->start;
+ else
+ panic("pccbb_auto_open: Weird condition!\n");
+ }
+ }
+
+ if (type == SYS_RES_MEMORY)
+ align = PCCBB_MEMALIGN;
+ else if (type == SYS_RES_IOPORT)
+ align = PCCBB_IOALIGN;
+ else
+ align = 1;
+
+ if (starts[0] != 0xffffffff)
+ starts[0] -= starts[0] % align;
+ if (starts[1] != 0xffffffff)
+ starts[1] -= starts[1] % align;
+ if (ends[0] % align != 0)
+ ends[0] += align - ends[0]%align;
+ if (ends[1] % align != 0)
+ ends[1] += align - ends[1]%align;
+
+ if (type == SYS_RES_MEMORY) {
+ pccbb_cardbus_mem_open(sc->sc_dev, 0, starts[0], ends[0]);
+ pccbb_cardbus_mem_open(sc->sc_dev, 1, starts[1], ends[1]);
+ } else if (type == SYS_RES_IOPORT) {
+ pccbb_cardbus_io_open(sc->sc_dev, 0, starts[0], ends[0]);
+ pccbb_cardbus_io_open(sc->sc_dev, 1, starts[1], ends[1]);
+ }
+}
+
+static int
+pccbb_cardbus_activate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+ struct pccbb_reslist *rle;
+
+ if (type == SYS_RES_MEMORY || type == SYS_RES_IOPORT) {
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (type == rle->type && rid == rle->rid &&
+ child == rle->odev)
+ return bus_generic_activate_resource(
+ self, child, type, rid, r);
+ }
+ rle = malloc(sizeof(struct pccbb_reslist), M_DEVBUF, M_WAITOK);
+ rle->type = type;
+ rle->rid = rid;
+ rle->start = rman_get_start(r);
+ rle->end = rman_get_end(r);
+ rle->odev = child;
+ rle->win = -1;
+ SLIST_INSERT_HEAD(&sc->rl, rle, entries);
+
+ pccbb_cardbus_auto_open(sc, type);
+ }
+
+ return bus_generic_activate_resource(self, child, type, rid, r);
+}
+
+static int
+pccbb_cardbus_deactivate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+ struct pccbb_reslist *rle;
+
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (type == rle->type && rid == rle->rid &&
+ child == rle->odev) {
+ SLIST_REMOVE(&sc->rl, rle, pccbb_reslist, entries);
+ if (type == SYS_RES_IOPORT ||
+ type == SYS_RES_MEMORY)
+ pccbb_cardbus_auto_open(sc, type);
+ free(rle, M_DEVBUF);
+ break;
+ }
+ }
+ return bus_generic_deactivate_resource(self, child, type, rid, r);
+}
+
+static struct resource*
+pccbb_cardbus_alloc_resource(device_t self, device_t child, int type, int* rid,
+ u_long start, u_long end, u_long count,
+ u_int flags)
+{
+ if (type == SYS_RES_IRQ) {
+ struct pccbb_softc *sc = device_get_softc(self);
+ if (start == 0) {
+ start = end = rman_get_start(sc->sc_irq_res);
+ }
+ return bus_generic_alloc_resource(self, child, type, rid,
+ start, end, count, flags);
+ } else {
+ if (type == SYS_RES_MEMORY && start == 0 && end == ~0) {
+ start = CARDBUS_SYS_RES_MEMORY_START;
+ end = CARDBUS_SYS_RES_MEMORY_END;
+ } else if (type == SYS_RES_IOPORT && start == 0 && end == ~0) {
+ start = CARDBUS_SYS_RES_IOPORT_START;
+ end = CARDBUS_SYS_RES_IOPORT_END;
+ }
+ return bus_generic_alloc_resource(self, child, type, rid,
+ start, end, count, flags);
+ }
+}
+
+static int
+pccbb_cardbus_release_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r)
+{
+ return bus_generic_release_resource(self, child, type, rid, r);
+}
+
+/************************************************************************/
+/* PC Card Resources */
+/************************************************************************/
+
+static void
+pccbb_pcic_wait_ready(struct pccbb_softc *sc)
+{
+ int i;
+ DEVPRINTF((sc->sc_dev, "pccbb_pcic_wait_ready: status 0x%02x\n",
+ PCIC_READ(sc, PCIC_IF_STATUS)));
+ for (i = 0; i < 10000; i++) {
+ if (PCIC_READ(sc, PCIC_IF_STATUS) & PCIC_IF_STATUS_READY) {
+ return;
+ }
+ DELAY(500);
+ }
+ device_printf(sc->sc_dev, "ready never happened, status = %02x\n",
+ PCIC_READ(sc, PCIC_IF_STATUS));
+}
+
+#define PCIC_MEMINFO(NUM) { \
+ PCIC_SYSMEM_ADDR ## NUM ## _START_LSB, \
+ PCIC_SYSMEM_ADDR ## NUM ## _START_MSB, \
+ PCIC_SYSMEM_ADDR ## NUM ## _STOP_LSB, \
+ PCIC_SYSMEM_ADDR ## NUM ## _STOP_MSB, \
+ PCIC_CARDMEM_ADDR ## NUM ## _LSB, \
+ PCIC_CARDMEM_ADDR ## NUM ## _MSB, \
+ PCIC_ADDRWIN_ENABLE_MEM ## NUM ## , \
+}
+
+static struct mem_map_index_st {
+ int sysmem_start_lsb;
+ int sysmem_start_msb;
+ int sysmem_stop_lsb;
+ int sysmem_stop_msb;
+ int cardmem_lsb;
+ int cardmem_msb;
+ int memenable;
+} mem_map_index[] = {
+ PCIC_MEMINFO(0),
+ PCIC_MEMINFO(1),
+ PCIC_MEMINFO(2),
+ PCIC_MEMINFO(3),
+ PCIC_MEMINFO(4),
+};
+#undef PCIC_MEMINFO
+
+static void
+pccbb_pcic_do_mem_map(struct pccbb_softc *sc, int win)
+{
+ PCIC_WRITE(sc, mem_map_index[win].sysmem_start_lsb,
+ (sc->mem[win].addr >> PCIC_SYSMEM_ADDRX_SHIFT) & 0xff);
+ PCIC_WRITE(sc, mem_map_index[win].sysmem_start_msb,
+ ((sc->mem[win].addr >> (PCIC_SYSMEM_ADDRX_SHIFT + 8)) &
+ PCIC_SYSMEM_ADDRX_START_MSB_ADDR_MASK));
+
+ PCIC_WRITE(sc, mem_map_index[win].sysmem_stop_lsb,
+ ((sc->mem[win].addr + sc->mem[win].realsize - 1) >>
+ PCIC_SYSMEM_ADDRX_SHIFT) & 0xff);
+ PCIC_WRITE(sc, mem_map_index[win].sysmem_stop_msb,
+ (((sc->mem[win].addr + sc->mem[win].realsize - 1) >>
+ (PCIC_SYSMEM_ADDRX_SHIFT + 8)) &
+ PCIC_SYSMEM_ADDRX_STOP_MSB_ADDR_MASK) |
+ PCIC_SYSMEM_ADDRX_STOP_MSB_WAIT2);
+
+ PCIC_WRITE(sc, mem_map_index[win].cardmem_lsb,
+ (sc->mem[win].offset >> PCIC_CARDMEM_ADDRX_SHIFT) & 0xff);
+ PCIC_WRITE(sc, mem_map_index[win].cardmem_msb,
+ ((sc->mem[win].offset >> (PCIC_CARDMEM_ADDRX_SHIFT + 8)) &
+ PCIC_CARDMEM_ADDRX_MSB_ADDR_MASK) |
+ ((sc->mem[win].kind == PCCARD_MEM_ATTR) ?
+ PCIC_CARDMEM_ADDRX_MSB_REGACTIVE_ATTR : 0));
+
+ PCIC_MASK(sc, PCIC_ADDRWIN_ENABLE, | PCIC_ADDRWIN_ENABLE_MEMCS16
+ | mem_map_index[win].memenable);
+
+ DELAY(100);
+
+#ifdef CBB_DEBUG
+ {
+ int r1, r2, r3, r4, r5, r6;
+ r1 = PCIC_READ(sc, mem_map_index[win].sysmem_start_msb);
+ r2 = PCIC_READ(sc, mem_map_index[win].sysmem_start_lsb);
+ r3 = PCIC_READ(sc, mem_map_index[win].sysmem_stop_msb);
+ r4 = PCIC_READ(sc, mem_map_index[win].sysmem_stop_lsb);
+ r5 = PCIC_READ(sc, mem_map_index[win].cardmem_msb);
+ r6 = PCIC_READ(sc, mem_map_index[win].cardmem_lsb);
+ DPRINTF(("pccbb_pcic_do_mem_map window %d: %02x%02x %02x%02x "
+ "%02x%02x\n", win, r1, r2, r3, r4, r5, r6));
+ }
+#endif
+}
+
+static int
+pccbb_pcic_mem_map(struct pccbb_softc *sc, int kind,
+ struct resource *r, bus_addr_t card_addr, int *win)
+{
+ int i;
+
+ *win = -1;
+ for (i = 0; i < PCIC_MEM_WINS; i++) {
+ if ((sc->memalloc & (1 << i)) == 0) {
+ *win = i;
+ sc->memalloc |= (1 << i);
+ break;
+ }
+ }
+ if (*win == -1)
+ return (1);
+
+ card_addr = card_addr - card_addr % PCIC_MEM_PAGESIZE;
+
+ sc->mem[*win].memt = rman_get_bustag(r);
+ sc->mem[*win].memh = rman_get_bushandle(r);
+ sc->mem[*win].addr = rman_get_start(r);
+ sc->mem[*win].size = rman_get_end(r) - sc->mem[*win].addr + 1;
+ sc->mem[*win].realsize = sc->mem[*win].size + PCIC_MEM_PAGESIZE - 1;
+ sc->mem[*win].realsize = sc->mem[*win].realsize -
+ (sc->mem[*win].realsize % PCIC_MEM_PAGESIZE);
+ sc->mem[*win].offset = ((long)card_addr) -
+ ((long)(sc->mem[*win].addr));
+ sc->mem[*win].kind = kind;
+
+ DPRINTF(("pccbb_pcic_mem_map window %d bus %x+%x+%lx card addr %x\n",
+ *win, sc->mem[*win].addr, sc->mem[*win].size,
+ sc->mem[*win].offset, card_addr));
+
+ pccbb_pcic_do_mem_map(sc, *win);
+
+ return (0);
+}
+
+static void
+pccbb_pcic_mem_unmap(struct pccbb_softc *sc, int window)
+{
+ if (window >= PCIC_MEM_WINS)
+ panic("pccbb_pcic_mem_unmap: window out of range");
+
+ PCIC_MASK(sc, PCIC_ADDRWIN_ENABLE, & ~mem_map_index[window].memenable);
+
+ sc->memalloc &= ~(1 << window);
+}
+
+#define PCIC_IOINFO(NUM) { \
+ PCIC_IOADDR ## NUM ## _START_LSB, \
+ PCIC_IOADDR ## NUM ## _START_MSB, \
+ PCIC_IOADDR ## NUM ## _STOP_LSB, \
+ PCIC_IOADDR ## NUM ## _STOP_MSB, \
+ PCIC_ADDRWIN_ENABLE_IO ## NUM ## , \
+ PCIC_IOCTL_IO ## NUM ## _WAITSTATE \
+ | PCIC_IOCTL_IO ## NUM ## _ZEROWAIT \
+ | PCIC_IOCTL_IO ## NUM ## _IOCS16SRC_MASK \
+ | PCIC_IOCTL_IO ## NUM ## _DATASIZE_MASK, \
+ { \
+ PCIC_IOCTL_IO ## NUM ## _IOCS16SRC_CARD, \
+ PCIC_IOCTL_IO ## NUM ## _IOCS16SRC_DATASIZE \
+ | PCIC_IOCTL_IO ## NUM ## _DATASIZE_8BIT, \
+ PCIC_IOCTL_IO ## NUM ## _IOCS16SRC_DATASIZE \
+ | PCIC_IOCTL_IO ## NUM ## _DATASIZE_16BIT, \
+ } \
+}
+
+static struct io_map_index_st {
+ int start_lsb;
+ int start_msb;
+ int stop_lsb;
+ int stop_msb;
+ int ioenable;
+ int ioctlmask;
+ int ioctlbits[3]; /* indexed by PCCARD_WIDTH_* */
+} io_map_index[] = {
+ PCIC_IOINFO(0),
+ PCIC_IOINFO(1),
+};
+#undef PCIC_IOINFO
+
+static void pccbb_pcic_do_io_map(struct pccbb_softc *sc, int win)
+{
+ PCIC_WRITE(sc, io_map_index[win].start_lsb, sc->io[win].addr & 0xff);
+ PCIC_WRITE(sc, io_map_index[win].start_msb,
+ (sc->io[win].addr >> 8) & 0xff);
+
+ PCIC_WRITE(sc, io_map_index[win].stop_lsb,
+ (sc->io[win].addr + sc->io[win].size - 1) & 0xff);
+ PCIC_WRITE(sc, io_map_index[win].stop_msb,
+ ((sc->io[win].addr + sc->io[win].size - 1) >> 8) & 0xff);
+
+ PCIC_MASK2(sc, PCIC_IOCTL,
+ & ~io_map_index[win].ioctlmask,
+ | io_map_index[win].ioctlbits[sc->io[win].width]);
+
+ PCIC_MASK(sc, PCIC_ADDRWIN_ENABLE, | io_map_index[win].ioenable);
+}
+
+static int
+pccbb_pcic_io_map(struct pccbb_softc *sc, int width,
+ struct resource *r, bus_addr_t card_addr, int *win)
+{
+ int i;
+#ifdef CBB_DEBUG
+ static char *width_names[] = { "auto", "io8", "io16"};
+#endif
+
+ *win = -1;
+ for (i=0; i < PCIC_IO_WINS; i++) {
+ if ((sc->ioalloc & (1 << i)) == 0) {
+ *win = i;
+ sc->ioalloc |= (1 << i);
+ break;
+ }
+ }
+ if (*win == -1)
+ return (1);
+
+ sc->io[*win].iot = rman_get_bustag(r);
+ sc->io[*win].ioh = rman_get_bushandle(r);
+ sc->io[*win].addr = rman_get_start(r);
+ sc->io[*win].size = rman_get_end(r) - sc->io[*win].addr + 1;
+ sc->io[*win].flags = 0;
+ sc->io[*win].width = width;
+
+ DPRINTF(("pccbb_pcic_io_map window %d %s port %x+%x\n",
+ *win, width_names[width], sc->io[*win].addr,
+ sc->io[*win].size));
+
+ pccbb_pcic_do_io_map(sc, *win);
+
+ return (0);
+}
+
+static void
+pccbb_pcic_io_unmap(struct pccbb_softc *sc, int window)
+{
+ if (window >= PCIC_IO_WINS)
+ panic("pccbb_pcic_io_unmap: window out of range");
+
+ PCIC_MASK(sc, PCIC_ADDRWIN_ENABLE, & ~io_map_index[window].ioenable);
+
+ sc->ioalloc &= ~(1 << window);
+
+ sc->io[window].iot = 0;
+ sc->io[window].ioh = 0;
+ sc->io[window].addr = 0;
+ sc->io[window].size = 0;
+ sc->io[window].flags = 0;
+ sc->io[window].width = 0;
+}
+
+static int
+pccbb_pcic_activate_resource(device_t self, device_t child, int type, int rid,
+ struct resource *r)
+{
+ int err;
+ int win;
+ struct pccbb_reslist *rle;
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ switch (type) {
+ case SYS_RES_IOPORT:
+ err = pccbb_pcic_io_map(sc, 0, r, 0, &win);
+ if (err)
+ return err;
+ break;
+ case SYS_RES_MEMORY:
+ err = pccbb_pcic_mem_map(sc, 0, r, 0, &win);
+ if (err)
+ return err;
+ break;
+ default:
+ break;
+ }
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (type == rle->type && rid == rle->rid &&
+ child == rle->odev) {
+ rle->win = win;
+ break;
+ }
+ }
+ err = bus_generic_activate_resource(self, child, type, rid, r);
+ return (err);
+}
+
+static int
+pccbb_pcic_deactivate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+ int win;
+ struct pccbb_reslist *rle;
+
+ win = -1;
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (type == rle->type && rid == rle->rid &&
+ child == rle->odev) {
+ win = rle->win;
+ break;
+ }
+ }
+ if (win == -1)
+ return 1;
+
+ switch (type) {
+ case SYS_RES_IOPORT:
+ pccbb_pcic_io_unmap(sc, win);
+ break;
+ case SYS_RES_MEMORY:
+ pccbb_pcic_mem_unmap(sc, win);
+ break;
+ default:
+ break;
+ }
+ return bus_generic_deactivate_resource(self, child, type, rid, r);
+}
+
+static struct resource*
+pccbb_pcic_alloc_resource(device_t self, device_t child, int type, int* rid,
+ u_long start, u_long end, u_long count, u_int flags)
+{
+ struct resource *r = NULL;
+ struct pccbb_softc *sc = device_get_softc(self);
+ struct pccbb_reslist *rle;
+
+ /* Nearly default */
+ if (type == SYS_RES_MEMORY && start == 0 && end == ~0 && count != 1) {
+ start = 0xd0000; /* XXX */
+ end = 0xdffff;
+ }
+
+ if (type == SYS_RES_MEMORY)
+ flags = (flags & ~RF_ALIGNMENT_MASK)
+ | rman_make_alignment_flags(PCCBB_MEMALIGN);
+
+ r = bus_generic_alloc_resource(self, child, type, rid, start, end,
+ count, flags & ~RF_ACTIVE);
+ if (r == NULL)
+ return NULL;
+
+ rle = malloc(sizeof(struct pccbb_reslist), M_DEVBUF, M_WAITOK);
+ rle->type = type;
+ rle->rid = *rid;
+ rle->start = rman_get_start(r);
+ rle->end = rman_get_end(r);
+ rle->odev = child;
+ rle->win = -1;
+ SLIST_INSERT_HEAD(&sc->rl, rle, entries);
+
+ if (flags & RF_ACTIVE) {
+ if (bus_activate_resource(child, type, *rid, r) != 0) {
+ BUS_RELEASE_RESOURCE(self, child, type, *rid, r);
+ return NULL;
+ }
+ }
+
+ return r;
+}
+
+static int
+pccbb_pcic_release_resource(device_t self, device_t child, int type,
+ int rid, struct resource *res)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+ struct pccbb_reslist *rle;
+
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (type == rle->type && rid == rle->rid &&
+ child == rle->odev) {
+ SLIST_REMOVE(&sc->rl, rle, pccbb_reslist, entries);
+ free(rle, M_DEVBUF);
+ break;
+ }
+ }
+
+ return bus_generic_release_resource(self, child, type, rid, res);
+}
+
+/************************************************************************/
+/* PC Card methods */
+/************************************************************************/
+
+static int
+pccbb_pcic_set_res_flags(device_t self, device_t child, int type, int rid,
+ u_int32_t flags)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ DPRINTF(("%p %p %d %d %#x\n", self, child, type, rid, flags));
+ if (type != SYS_RES_MEMORY)
+ return (EINVAL);
+ sc->mem[rid].kind = PCCARD_MEM_ATTR;
+ pccbb_pcic_do_mem_map(sc, rid);
+ return 0;
+}
+
+static int
+pccbb_pcic_set_memory_offset(device_t self, device_t child, int rid,
+ u_int32_t offset)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+ int win;
+ struct pccbb_reslist *rle;
+
+ win = -1;
+ SLIST_FOREACH(rle, &sc->rl, entries) {
+ if (SYS_RES_MEMORY == rle->type && rid == rle->rid &&
+ child == rle->odev) {
+ win = rle->win;
+ break;
+ }
+ }
+ if (win == -1)
+ return 1;
+
+ offset = offset - offset % PCIC_MEM_PAGESIZE;
+ sc->mem[win].offset = ((long)offset) -
+ ((long)(sc->mem[win].addr));
+
+ pccbb_pcic_do_mem_map(sc, win);
+
+ return 0;
+}
+
+static int
+pccbb_pcic_enable_socket(device_t self, device_t child)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ DPRINTF(("pccbb_pcic_socket_enable:\n"));
+
+ /* power down/up the socket to reset */
+ {
+ int voltage = pccbb_detect_voltage(sc);
+
+ pccbb_power(self, CARD_VCC_0V | CARD_VPP_0V);
+ if (voltage & CARD_5V_CARD)
+ pccbb_power(self, CARD_VCC_5V | CARD_VPP_VCC);
+ else if (voltage & CARD_3V_CARD)
+ pccbb_power(self, CARD_VCC_3V | CARD_VPP_VCC);
+ else {
+ device_printf(self, "Unknown card voltage\n");
+ return ENXIO;
+ }
+ }
+
+ /* enable socket i/o */
+ PCIC_MASK(sc, PCIC_PWRCTL, | PCIC_PWRCTL_OE);
+
+ PCIC_WRITE(sc, PCIC_INTR, PCIC_INTR_ENABLE);
+ /* hold reset for 30ms */
+ DELAY(30*1000);
+ /* clear the reset flag */
+ PCIC_MASK(sc, PCIC_INTR, | PCIC_INTR_RESET);
+ /* wait 20ms as per pc card standard (r2.01) section 4.3.6 */
+ DELAY(20*1000);
+
+ pccbb_pcic_wait_ready(sc);
+
+ /* disable all address windows */
+ PCIC_WRITE(sc, PCIC_ADDRWIN_ENABLE, 0);
+
+ {
+ int cardtype;
+ CARD_GET_TYPE(child, &cardtype);
+ PCIC_MASK(sc, PCIC_INTR, | ((cardtype == PCCARD_IFTYPE_IO) ?
+ PCIC_INTR_CARDTYPE_IO :
+ PCIC_INTR_CARDTYPE_MEM));
+ DEVPRINTF((sc->sc_dev, "card type is %s\n",
+ (cardtype == PCCARD_IFTYPE_IO) ? "io" : "mem"));
+ }
+
+ /* reinstall all the memory and io mappings */
+ {
+ int win;
+
+ for (win = 0; win < PCIC_MEM_WINS; ++win) {
+ if (sc->memalloc & (1 << win)) {
+ pccbb_pcic_do_mem_map(sc, win);
+ }
+ }
+ for (win = 0; win < PCIC_IO_WINS; ++win) {
+ if (sc->ioalloc & (1 << win)) {
+ pccbb_pcic_do_io_map(sc, win);
+ }
+ }
+ }
+ return 0;
+}
+
+static void
+pccbb_pcic_disable_socket(device_t self, device_t child)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ DPRINTF(("pccbb_pcic_socket_disable\n"));
+
+ /* reset signal asserting... */
+ PCIC_MASK(sc, PCIC_INTR, & ~PCIC_INTR_RESET);
+ DELAY(2*1000);
+
+ /* power down the socket */
+ PCIC_MASK(sc, PCIC_PWRCTL, &~PCIC_PWRCTL_OE);
+ pccbb_power(self, CARD_VCC_0V | CARD_VPP_0V);
+
+ /* wait 300ms until power fails (Tpf). */
+ DELAY(300 * 1000);
+}
+
+/************************************************************************/
+/* Methods */
+/************************************************************************/
+
+
+static int
+pccbb_activate_resource(device_t self, device_t child, int type, int rid,
+ struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ if (sc->sc_flags & PCCBB_16BIT_CARD)
+ return pccbb_pcic_activate_resource(self, child, type, rid, r);
+ else
+ return pccbb_cardbus_activate_resource(self, child, type, rid,
+ r);
+}
+
+static int
+pccbb_deactivate_resource(device_t self, device_t child, int type,
+ int rid, struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ if (sc->sc_flags & PCCBB_16BIT_CARD)
+ return pccbb_pcic_deactivate_resource(self, child, type,
+ rid, r);
+ else
+ return pccbb_cardbus_deactivate_resource(self, child, type,
+ rid, r);
+}
+
+static struct resource*
+pccbb_alloc_resource(device_t self, device_t child, int type, int* rid,
+ u_long start, u_long end, u_long count, u_int flags)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ if (sc->sc_flags & PCCBB_16BIT_CARD)
+ return pccbb_pcic_alloc_resource(self, child, type, rid,
+ start, end, count, flags);
+ else
+ return pccbb_cardbus_alloc_resource(self, child, type, rid,
+ start, end, count, flags);
+}
+
+static int
+pccbb_release_resource(device_t self, device_t child, int type, int rid,
+ struct resource *r)
+{
+ struct pccbb_softc *sc = device_get_softc(self);
+
+ if (sc->sc_flags & PCCBB_16BIT_CARD)
+ return pccbb_pcic_release_resource(self, child, type,
+ rid, r);
+ else
+ return pccbb_cardbus_release_resource(self, child, type,
+ rid, r);
+}
+
+static int
+pccbb_maxslots(device_t dev)
+{
+ return 0;
+}
+
+static u_int32_t
+pccbb_read_config(device_t dev, int b, int s, int f,
+ int reg, int width)
+{
+ /*
+ * Pass through to the next ppb up the chain (i.e. our grandparent).
+ */
+ return PCIB_READ_CONFIG(device_get_parent(device_get_parent(dev)),
+ b, s, f, reg, width);
+}
+
+static void
+pccbb_write_config(device_t dev, int b, int s, int f,
+ int reg, u_int32_t val, int width)
+{
+ /*
+ * Pass through to the next ppb up the chain (i.e. our grandparent).
+ */
+ PCIB_WRITE_CONFIG(device_get_parent(device_get_parent(dev)),
+ b, s, f, reg, val, width);
+}
+
+static device_method_t pccbb_methods[] = {
+ /* Device interface */
+ DEVMETHOD(device_probe, pccbb_probe),
+ DEVMETHOD(device_attach, pccbb_attach),
+ DEVMETHOD(device_detach, bus_generic_detach),
+ DEVMETHOD(device_shutdown, bus_generic_shutdown),
+ DEVMETHOD(device_suspend, bus_generic_suspend),
+ DEVMETHOD(device_resume, bus_generic_resume),
+
+ /* bus methods */
+ DEVMETHOD(bus_print_child, bus_generic_print_child),
+ DEVMETHOD(bus_alloc_resource, pccbb_alloc_resource),
+ DEVMETHOD(bus_release_resource, pccbb_release_resource),
+ DEVMETHOD(bus_activate_resource, pccbb_activate_resource),
+ DEVMETHOD(bus_deactivate_resource, pccbb_deactivate_resource),
+ DEVMETHOD(bus_setup_intr, bus_generic_setup_intr),
+ DEVMETHOD(bus_teardown_intr, bus_generic_teardown_intr),
+
+ /* pcib compatibility interface */
+ DEVMETHOD(pcib_maxslots, pccbb_maxslots),
+ DEVMETHOD(pcib_read_config, pccbb_read_config),
+ DEVMETHOD(pcib_write_config, pccbb_write_config),
+
+ DEVMETHOD(pccbb_power_socket, pccbb_power),
+ DEVMETHOD(pccbb_detect_card, pccbb_cardbus_detect_card),
+ DEVMETHOD(pccbb_reset, pccbb_cardbus_reset),
+
+ DEVMETHOD(card_set_res_flags, pccbb_pcic_set_res_flags),
+ DEVMETHOD(card_set_memory_offset, pccbb_pcic_set_memory_offset),
+
+ DEVMETHOD(power_enable_socket, pccbb_pcic_enable_socket),
+ DEVMETHOD(power_disable_socket, pccbb_pcic_disable_socket),
+
+ {0,0}
+};
+
+static driver_t pccbb_driver = {
+ "pccbb",
+ pccbb_methods,
+ sizeof(struct pccbb_softc)
+};
+static devclass_t pccbb_devclass = {
+};
+DRIVER_MODULE(pccbb, pci, pccbb_driver, pccbb_devclass, 0, 0);
+
+
+SYSINIT(pccbb, SI_SUB_KTHREAD_IDLE, SI_ORDER_ANY, pccbb_start_threads, 0);
diff --git a/sys/dev/pccbb/pccbb_if.m b/sys/dev/pccbb/pccbb_if.m
new file mode 100644
index 0000000..2f3ddd3
--- /dev/null
+++ b/sys/dev/pccbb/pccbb_if.m
@@ -0,0 +1,69 @@
+#
+# Copyright (c) 2000,2001 Jonathan Chen.
+# All rights reserved.
+#
+# Redistribution and use in source and binary forms, with or without
+# modification, are permitted provided that the following conditions
+# are met:
+# 1. Redistributions of source code must retain the above copyright
+# notice, this list of conditions, and the following disclaimer,
+# without modification, immediately at the beginning of the file.
+# 2. Redistributions in binary form must reproduce the above copyright
+# notice, this list of conditions and the following disclaimer in
+# the documentation and/or other materials provided with the
+# distribution.
+#
+# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
+# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+# ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR
+# ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+# SUCH DAMAGE.
+#
+# $FreeBSD$
+#
+
+#include <sys/bus.h>
+
+INTERFACE pccbb;
+
+METHOD int power_socket {
+ device_t dev;
+ int command;
+};
+
+METHOD int detect_card {
+ device_t dev;
+};
+
+METHOD int reset {
+ device_t dev;
+};
+
+HEADER {
+/* result of detect_card */
+ #define CARD_UKN_CARD 0x00
+ #define CARD_5V_CARD 0x01
+ #define CARD_3V_CARD 0x02
+ #define CARD_XV_CARD 0x04
+ #define CARD_YV_CARD 0x08
+
+/* for power_socket */
+ #define CARD_VCC_UC 0x0000
+ #define CARD_VCC_3V 0x0001
+ #define CARD_VCC_XV 0x0002
+ #define CARD_VCC_YV 0x0003
+ #define CARD_VCC_0V 0x0004
+ #define CARD_VCC_5V 0x0005
+ #define CARD_VCCMASK 0x000f
+ #define CARD_VPP_UC 0x0000
+ #define CARD_VPP_VCC 0x0010
+ #define CARD_VPP_12V 0x0030
+ #define CARD_VPP_0V 0x0040
+ #define CARD_VPPMASK 0x00f0
+};
diff --git a/sys/dev/pccbb/pccbbreg.h b/sys/dev/pccbb/pccbbreg.h
new file mode 100644
index 0000000..9758335
--- /dev/null
+++ b/sys/dev/pccbb/pccbbreg.h
@@ -0,0 +1,188 @@
+/*
+ * Copyright (c) 2000,2001 Jonathan Chen.
+ * All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions
+ * are met:
+ * 1. Redistributions of source code must retain the above copyright
+ * notice, this list of conditions, and the following disclaimer,
+ * without modification, immediately at the beginning of the file.
+ * 2. Redistributions in binary form must reproduce the above copyright
+ * notice, this list of conditions and the following disclaimer in
+ * the documentation and/or other materials provided with the
+ * distribution.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
+ * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR
+ * ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ * SUCH DAMAGE.
+ *
+ * $FreeBSD$
+ */
+
+/*
+ * Register definitions for PCI to Cardbus Bridge chips
+ */
+
+
+/* PCI header registers */
+#define PCCBBR_SOCKBASE 0x10 /* len=4 */
+
+#define PCCBBR_MEMBASE0 0x1c /* len=4 */
+#define PCCBBR_MEMLIMIT0 0x20 /* len=4 */
+#define PCCBBR_MEMBASE1 0x24 /* len=4 */
+#define PCCBBR_MEMLIMIT1 0x28 /* len=4 */
+#define PCCBBR_IOBASE0 0x2c /* len=4 */
+#define PCCBBR_IOLIMIT0 0x30 /* len=4 */
+#define PCCBBR_IOBASE1 0x34 /* len=4 */
+#define PCCBBR_IOLIMIT1 0x38 /* len=4 */
+#define PCCBB_MEMALIGN 4096
+#define PCCBB_IOALIGN 4
+
+#define PCCBBR_INTRLINE 0x3c /* len=1 */
+#define PCCBBR_INTRPIN 0x3d /* len=1 */
+#define PCCBBR_BRIDGECTRL 0x3e /* len=2 */
+# define PCCBBM_BRIDGECTRL_MASTER_ABORT 0x0020
+# define PCCBBM_BRIDGECTRL_RESET 0x0040
+# define PCCBBM_BRIDGECTRL_INTR_IREQ_EN 0x0080
+# define PCCBBM_BRIDGECTRL_PREFETCH_0 0x0100
+# define PCCBBM_BRIDGECTRL_PREFETCH_1 0x0200
+# define PCCBBM_BRIDGECTRL_WRITE_POST_EN 0x0400
+ /* additional bit for RF5C46[567] */
+# define PCCBBM_BRIDGECTRL_RL_3E0_EN 0x0800
+# define PCCBBM_BRIDGECTRL_RL_3E2_EN 0x1000
+
+#define PCCBBR_LEGACY 0x44 /* len=4 */
+
+#define PCCBBR_CBCTRL 0x91 /* len=1 */
+ /* bits for TI 113X */
+# define PCCBBM_CBCTRL_113X_RI_EN 0x80
+# define PCCBBM_CBCTRL_113X_ZV_EN 0x40
+# define PCCBBM_CBCTRL_113X_PCI_IRQ_EN 0x20
+# define PCCBBM_CBCTRL_113X_PCI_INTR 0x10
+# define PCCBBM_CBCTRL_113X_PCI_CSC 0x08
+# define PCCBBM_CBCTRL_113X_PCI_CSC_D 0x04
+# define PCCBBM_CBCTRL_113X_SPEAKER_EN 0x02
+# define PCCBBM_CBCTRL_113X_INTR_DET 0x01
+ /* bits for TI 12XX */
+# define PCCBBM_CBCTRL_12XX_RI_EN 0x80
+# define PCCBBM_CBCTRL_12XX_ZV_EN 0x40
+# define PCCBBM_CBCTRL_12XX_AUD2MUX 0x04
+# define PCCBBM_CBCTRL_12XX_SPEAKER_EN 0x02
+# define PCCBBM_CBCTRL_12XX_INTR_DET 0x01
+#define PCCBBR_DEVCTRL 0x92 /* len=1 */
+# define PCCBBM_DEVCTRL_INT_SERIAL 0x04
+# define PCCBBM_DEVCTRL_INT_PCI 0x02
+
+#define PCCBBR_TOPIC_SOCKETCTRL 0x90
+# define PCCBBM_TOPIC_SOCKETCTRL_SCR_IRQSEL 0x00000001 /* PCI intr */
+
+#define PCCBBR_TOPIC_SLOTCTRL 0xa0
+# define PCCBBM_TOPIC_SLOTCTRL_SLOTON 0x00000080
+# define PCCBBM_TOPIC_SLOTCTRL_SLOTEN 0x00000040
+# define PCCBBM_TOPIC_SLOTCTRL_ID_LOCK 0x00000020
+# define PCCBBM_TOPIC_SLOTCTRL_ID_WP 0x00000010
+# define PCCBBM_TOPIC_SLOTCTRL_PORT_MASK 0x0000000c
+# define PCCBBM_TOPIC_SLOTCTRL_PORT_SHIFT 2
+# define PCCBBM_TOPIC_SLOTCTRL_OSF_MASK 0x00000003
+# define PCCBBM_TOPIC_SLOTCTRL_OSF_SHIFT 0
+# define PCCBBM_TOPIC_SLOTCTRL_INTB 0x00002000
+# define PCCBBM_TOPIC_SLOTCTRL_INTA 0x00001000
+# define PCCBBM_TOPIC_SLOTCTRL_INT_MASK 0x00003000
+# define PCCBBM_TOPIC_SLOTCTRL_CLOCK_MASK 0x00000c00
+# define PCCBBM_TOPIC_SLOTCTRL_CLOCK_2 0x00000800 /* PCI Clock/2 */
+# define PCCBBM_TOPIC_SLOTCTRL_CLOCK_1 0x00000400 /* PCI Clock */
+# define PCCBBM_TOPIC_SLOTCTRL_CLOCK_0 0x00000000 /* no clock */
+# define PCCBBM_TOPIC_SLOTCTRL_CARDBUS 0x80000000
+# define PCCBBM_TOPIC_SLOTCTRL_VS1 0x04000000
+# define PCCBBM_TOPIC_SLOTCTRL_VS2 0x02000000
+# define PCCBBM_TOPIC_SLOTCTRL_SWDETECT 0x01000000
+
+/* Socket definitions */
+#define PCCBB_SOCKET_EVENT_CSTS 0x01 /* Card Status Change */
+#define PCCBB_SOCKET_EVENT_CD1 0x02 /* Card Detect 1 */
+#define PCCBB_SOCKET_EVENT_CD2 0x04 /* Card Detect 2 */
+#define PCCBB_SOCKET_EVENT_CD 0x06 /* Card Detect all */
+#define PCCBB_SOCKET_EVENT_POWER 0x08 /* Power Cycle */
+
+#define PCCBB_SOCKET_MASK_CSTS 0x01 /* Card Status Change */
+#define PCCBB_SOCKET_MASK_CD 0x06 /* Card Detect */
+#define PCCBB_SOCKET_MASK_POWER 0x08 /* Power Cycle */
+
+#define PCCBB_SOCKET_STAT_CARDSTS 0x00000001 /* Card Status Change */
+#define PCCBB_SOCKET_STAT_CD1 0x00000002 /* Card Detect 1 */
+#define PCCBB_SOCKET_STAT_CD2 0x00000004 /* Card Detect 2 */
+#define PCCBB_SOCKET_STAT_CD 0x00000006 /* Card Detect all */
+#define PCCBB_SOCKET_STAT_PWRCYCLE 0x00000008 /* Power Cycle */
+#define PCCBB_SOCKET_STAT_16BIT 0x00000010 /* 16-bit Card */
+#define PCCBB_SOCKET_STAT_CB 0x00000020 /* Cardbus Card */
+#define PCCBB_SOCKET_STAT_IREQ 0x00000040 /* Ready */
+#define PCCBB_SOCKET_STAT_NOTCARD 0x00000080 /* Unrecognized Card */
+#define PCCBB_SOCKET_STAT_DATALOST 0x00000100 /* Data Lost */
+#define PCCBB_SOCKET_STAT_BADVCC 0x00000200 /* Bad VccRequest */
+#define PCCBB_SOCKET_STAT_5VCARD 0x00000400 /* 5 V Card */
+#define PCCBB_SOCKET_STAT_3VCARD 0x00000800 /* 3.3 V Card */
+#define PCCBB_SOCKET_STAT_XVCARD 0x00001000 /* X.X V Card */
+#define PCCBB_SOCKET_STAT_YVCARD 0x00002000 /* Y.Y V Card */
+#define PCCBB_SOCKET_STAT_5VSOCK 0x10000000 /* 5 V Socket */
+#define PCCBB_SOCKET_STAT_3VSOCK 0x20000000 /* 3.3 V Socket */
+#define PCCBB_SOCKET_STAT_XVSOCK 0x40000000 /* X.X V Socket */
+#define PCCBB_SOCKET_STAT_YVSOCK 0x80000000 /* Y.Y V Socket */
+
+#define PCCBB_SOCKET_FORCE_BADVCC 0x0200 /* Bad Vcc Request */
+
+#define PCCBB_SOCKET_CTRL_VPPMASK 0x07
+#define PCCBB_SOCKET_CTRL_VPP_OFF 0x00
+#define PCCBB_SOCKET_CTRL_VPP_12V 0x01
+#define PCCBB_SOCKET_CTRL_VPP_5V 0x02
+#define PCCBB_SOCKET_CTRL_VPP_3V 0x03
+#define PCCBB_SOCKET_CTRL_VPP_XV 0x04
+#define PCCBB_SOCKET_CTRL_VPP_YV 0x05
+
+#define PCCBB_SOCKET_CTRL_VCCMASK 0x70
+#define PCCBB_SOCKET_CTRL_VCC_OFF 0x00
+#define PCCBB_SOCKET_CTRL_VCC_5V 0x20
+#define PCCBB_SOCKET_CTRL_VCC_3V 0x30
+#define PCCBB_SOCKET_CTRL_VCC_XV 0x40
+#define PCCBB_SOCKET_CTRL_VCC_YV 0x50
+
+#define PCCBB_SOCKET_CTRL_STOPCLK 0x80
+
+
+/* Vendor/Device IDs */
+#define PCI_DEVICE_ID_PCIC_OZ6729 0x67291217ul
+#define PCI_DEVICE_ID_PCIC_OZ6730 0x673A1217ul
+#define PCI_DEVICE_ID_PCIC_CLPD6729 0x11001013ul
+#define PCI_DEVICE_ID_PCIC_CLPD6832 0x11101013ul
+#define PCI_DEVICE_ID_PCIC_CLPD6833 0x11131013ul
+#define PCI_DEVICE_ID_PCIC_TI1130 0xac12104cul
+#define PCI_DEVICE_ID_PCIC_TI1131 0xac15104cul
+#define PCI_DEVICE_ID_PCIC_TI1211 0xac1e104cul
+#define PCI_DEVICE_ID_PCIC_TI1220 0xac17104cul
+#define PCI_DEVICE_ID_PCIC_TI1221 0xac19104cul
+#define PCI_DEVICE_ID_PCIC_TI1225 0xac1c104cul
+#define PCI_DEVICE_ID_PCIC_TI1250 0xac16104cul
+#define PCI_DEVICE_ID_PCIC_TI1251 0xac1d104cul
+#define PCI_DEVICE_ID_PCIC_TI1251B 0xac1f104cul
+#define PCI_DEVICE_ID_PCIC_TI1410 0xac50104cul
+#define PCI_DEVICE_ID_PCIC_TI1420 0xac51104cul
+#define PCI_DEVICE_ID_PCIC_TI1450 0xac1b104cul
+#define PCI_DEVICE_ID_PCIC_TI1451 0xac52104cul
+#define PCI_DEVICE_ID_TOSHIBA_TOPIC95 0x06031179ul
+#define PCI_DEVICE_ID_TOSHIBA_TOPIC95B 0x060a1179ul
+#define PCI_DEVICE_ID_TOSHIBA_TOPIC97 0x060f1179ul
+#define PCI_DEVICE_ID_TOSHIBA_TOPIC100 0x06171179ul
+#define PCI_DEVICE_ID_RICOH_RL5C465 0x04651180ul
+#define PCI_DEVICE_ID_RICOH_RL5C466 0x04661180ul
+#define PCI_DEVICE_ID_RICOH_RL5C475 0x04751180ul
+#define PCI_DEVICE_ID_RICOH_RL5C476 0x04761180ul
+#define PCI_DEVICE_ID_RICOH_RL5C477 0x04771180ul
+#define PCI_DEVICE_ID_RICOH_RL5C478 0x04781180ul
diff --git a/sys/dev/pccbb/pccbbvar.h b/sys/dev/pccbb/pccbbvar.h
new file mode 100644
index 0000000..0a22046
--- /dev/null
+++ b/sys/dev/pccbb/pccbbvar.h
@@ -0,0 +1,105 @@
+/*
+ * Copyright (c) 2000,2001 Jonathan Chen.
+ * All rights reserved.
+ *
+ * Redistribution and use in source and binary forms, with or without
+ * modification, are permitted provided that the following conditions
+ * are met:
+ * 1. Redistributions of source code must retain the above copyright
+ * notice, this list of conditions, and the following disclaimer,
+ * without modification, immediately at the beginning of the file.
+ * 2. Redistributions in binary form must reproduce the above copyright
+ * notice, this list of conditions and the following disclaimer in
+ * the documentation and/or other materials provided with the
+ * distribution.
+ *
+ * THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
+ * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ * ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE FOR
+ * ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ * SUCH DAMAGE.
+ *
+ * $FreeBSD$
+ */
+
+/*
+ * Structure definitions for the Cardbus Bridge driver
+ */
+
+struct intrhand {
+ void(*func)(void*arg);
+ void* arg;
+ STAILQ_ENTRY(intrhand) entries;
+};
+
+struct pccbb_socketreg {
+ u_int32_t socket_event;
+ u_int32_t socket_mask;
+ u_int32_t socket_state;
+ u_int32_t socket_force;
+ u_int32_t socket_control;
+ u_int32_t socket_power;
+};
+
+struct pccbb_reslist {
+ SLIST_ENTRY(pccbb_reslist) entries;
+ int type;
+ int rid;
+ u_int32_t start;
+ u_int32_t end;
+ device_t odev;
+ int win;
+};
+
+#define PCCBB_AUTO_OPEN_SMALLHOLE 0x100
+
+struct pccbb_softc {
+ device_t sc_dev;
+ struct resource *sc_base_res;
+ struct resource *sc_irq_res;
+ void *sc_intrhand;
+ struct pccbb_socketreg *sc_socketreg;
+ u_int32_t sc_flags;
+#define PCCBB_PCIC_IO_RELOC 0x01
+#define PCCBB_PCIC_MEM_32 0x02
+#define PCCBB_CARDSTATUS_BUSY 0x01000000
+#define PCCBB_CARDATTACHED 0x02000000
+#define PCCBB_16BIT_CARD 0x04000000
+#define PCCBB_INITIALCARD 0x08000000
+ int sc_chipset; /* chipset id */
+#define CB_UNKNOWN 0 /* NOT Cardbus-PCI bridge */
+#define CB_TI113X 1 /* TI PCI1130/1131 */
+#define CB_TI12XX 2 /* TI PCI1250/1220 */
+#define CB_RF5C47X 3 /* RICOH RF5C475/476/477 */
+#define CB_RF5C46X 4 /* RICOH RF5C465/466/467 */
+#define CB_TOPIC95 5 /* Toshiba ToPIC95 */
+#define CB_TOPIC95B 6 /* Toshiba ToPIC95B */
+#define CB_TOPIC97 7 /* Toshiba ToPIC97/100 */
+#define CB_CIRRUS 8 /* Cirrus Logic CLPD683x */
+ SLIST_HEAD(, pccbb_reslist) rl;
+
+ device_t sc_cbdev;
+ device_t sc_pccarddev;
+
+ /* PC Card stuff */
+ int memalloc;
+ struct pccard_mem_handle mem[PCIC_MEM_WINS];
+ int ioalloc;
+ struct pccard_io_handle io[PCIC_IO_WINS];
+
+ /* kthread staff */
+ struct proc *event_thread;
+};
+
+/* XXX: rman is dumb */
+#define CARDBUS_SYS_RES_MEMORY_START 0x18020000
+#define CARDBUS_SYS_RES_MEMORY_END 0xEFFFFFFF
+#define CARDBUS_SYS_RES_IOPORT_START 0x2000
+#define CARDBUS_SYS_RES_IOPORT_END 0xEFFF
+
OpenPOWER on IntegriCloud