summaryrefslogtreecommitdiffstats
path: root/sys/dev/pccbb
diff options
context:
space:
mode:
authorimp <imp@FreeBSD.org>2002-02-17 03:11:11 +0000
committerimp <imp@FreeBSD.org>2002-02-17 03:11:11 +0000
commit88a25257e9ceba246d683c669e10c42286190f3a (patch)
treebffefb1459f50caaa8bafb19d4d263641f00e994 /sys/dev/pccbb
parent3985693d095687c838e01df0861a4081f487ee0e (diff)
downloadFreeBSD-src-88a25257e9ceba246d683c669e10c42286190f3a.zip
FreeBSD-src-88a25257e9ceba246d683c669e10c42286190f3a.tar.gz
Bulk changes made during the BSDcon kernel summit and travel afterwards.
Appologies for making this one bulk commit, but I have tested all these changes together and don't want to break anything by trying to disentangle it. o Make debugging a sysctl/tunable o Remove flags word from yenta chip info, it is unused o Make 16-bit card I/O range and 32-bit card I/O range tunables o Start the rename of pccbb to cbb to match NetBSD by misc renames. o Kill the now bogus list of softcs to create kthread. Instead, just create the kthread in the attach routine. o Remove sc_ from some structure names. It isn't needed. o Refine chipset lookup code. o Match generic PCI <-> CardBus bridges. We specifically don't generically match PCI PCMCIA bridges because they are not, with one exception, yenta devices. o Add some comments about the why we need to have a function table ala OLDCARD o The PCI interrupt routing by using the ExCA registers is needed for for all bridges, per the spec, not just TI ones. o Collapse TOPIC95 and TOPIC95B. o Using the ToPIC 97 and 100 datasheets, try to support these bridges better, but more work is needed. o Generally clarify some XXX comments and add them in a few places where things didn't look right to me. o Move interrupt generating register access until after we establish an ISR. o Add support for YV and XV cards. X and Y are numbers to be determined later (but maybe never). o factor powerup code for 16-bit and 32-bit cards. o When a card supports more than one voltage, prefer the lowest supported volage. Windows does this, and MS's design guides imply this is the right thing to do. o Document race between kthread_exit(0) and kldunload's unmapping of pages that John Baldwin and I discovered. o Debounce the CSC interrupt a little better. o When a 16-bit card is inserted when we don't have a pccard child, warn about it better. Ditto for 32-bit card. o Ack ALL the interrupt bits that we get, not just 0x1. o maybe a couple minor style nits corrected.
Diffstat (limited to 'sys/dev/pccbb')
-rw-r--r--sys/dev/pccbb/pccbb.c961
-rw-r--r--sys/dev/pccbb/pccbbreg.h256
-rw-r--r--sys/dev/pccbb/pccbbvar.h34
3 files changed, 669 insertions, 582 deletions
diff --git a/sys/dev/pccbb/pccbb.c b/sys/dev/pccbb/pccbb.c
index 0c09852..54b7fd4 100644
--- a/sys/dev/pccbb/pccbb.c
+++ b/sys/dev/pccbb/pccbb.c
@@ -47,12 +47,11 @@
#include <sys/systm.h>
#include <sys/errno.h>
#include <sys/kernel.h>
-#include <sys/kthread.h>
#include <sys/lock.h>
#include <sys/malloc.h>
#include <sys/mutex.h>
#include <sys/sysctl.h>
-
+#include <sys/kthread.h>
#include <sys/bus.h>
#include <machine/bus.h>
#include <sys/rman.h>
@@ -75,13 +74,8 @@
#include "card_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 DPRINTF(x) do { if (cbb_debug) printf x; } while (0)
+#define DEVPRINTF(x) do { if (cbb_debug) device_printf x; } while (0)
#define PCI_MASK_CONFIG(DEV,REG,MASK,SIZE) \
pci_write_config(DEV, REG, pci_read_config(DEV, REG, SIZE) MASK, SIZE)
@@ -90,107 +84,116 @@
pci_read_config(DEV, REG, SIZE) MASK1) MASK2, SIZE)
#define PCCBB_START_MEM 0x84000000
-#define PCCBB_START_IO 0x1000
-
-struct pccbb_sclist {
- struct pccbb_softc *sc;
- STAILQ_ENTRY(pccbb_sclist) entries;
-};
-
-static STAILQ_HEAD(, pccbb_sclist) softcs;
-static int softcs_init = 0;
+#define PCCBB_START_32_IO 0x1000
+#define PCCBB_START_16_IO 0x100
struct yenta_chipinfo {
uint32_t yc_id;
const char *yc_name;
int yc_chiptype;
- int yc_flags;
} yc_chipsets[] = {
/* Texas Instruments chips */
- {PCI_DEVICE_ID_PCIC_TI1031, "TI1031 PCI-PCCard Bridge", CB_TI113X, 0},
- {PCI_DEVICE_ID_PCIC_TI1130, "TI1130 PCI-CardBus Bridge", CB_TI113X, 0},
- {PCI_DEVICE_ID_PCIC_TI1131, "TI1131 PCI-CardBus Bridge", CB_TI113X, 0},
-
- {PCI_DEVICE_ID_PCIC_TI1210, "TI1210 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1211, "TI1211 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1220, "TI1220 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1221, "TI1221 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1225, "TI1225 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1250, "TI1250 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1251, "TI1251 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1251B,"TI1251B PCI-CardBus Bridge",CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1260, "TI1260 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1260B, "TI1260B PCI-CardBus Bridge", CB_TI12XX,
- 0},
- {PCI_DEVICE_ID_PCIC_TI1410, "TI1410 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1420, "TI1420 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1421, "TI1421 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1450, "TI1450 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI1451, "TI1451 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI4410, "TI4410 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI4450, "TI4450 PCI-CardBus Bridge", CB_TI12XX, 0},
- {PCI_DEVICE_ID_PCIC_TI4451, "TI4451 PCI-CardBus Bridge", CB_TI12XX, 0},
+ {PCI_DEVICE_ID_PCIC_TI1031, "TI1031 PCI-PC Card Bridge", CB_TI113X},
+ {PCI_DEVICE_ID_PCIC_TI1130, "TI1130 PCI-CardBus Bridge", CB_TI113X},
+ {PCI_DEVICE_ID_PCIC_TI1131, "TI1131 PCI-CardBus Bridge", CB_TI113X},
+
+ {PCI_DEVICE_ID_PCIC_TI1210, "TI1210 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1211, "TI1211 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1220, "TI1220 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1221, "TI1221 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1225, "TI1225 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1250, "TI1250 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1251, "TI1251 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1251B,"TI1251B PCI-CardBus Bridge",CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1260, "TI1260 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1260B,"TI1260B PCI-CardBus Bridge",CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1410, "TI1410 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1420, "TI1420 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1421, "TI1421 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1450, "TI1450 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI1451, "TI1451 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI4410, "TI4410 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI4450, "TI4450 PCI-CardBus Bridge", CB_TI12XX},
+ {PCI_DEVICE_ID_PCIC_TI4451, "TI4451 PCI-CardBus Bridge", CB_TI12XX},
/* Ricoh chips */
{PCI_DEVICE_ID_RICOH_RL5C465, "RF5C465 PCI-CardBus Bridge",
- CB_RF5C46X, 0},
+ CB_RF5C46X},
{PCI_DEVICE_ID_RICOH_RL5C466, "RF5C466 PCI-CardBus Bridge",
- CB_RF5C46X, 0},
+ CB_RF5C46X},
{PCI_DEVICE_ID_RICOH_RL5C475, "RF5C475 PCI-CardBus Bridge",
- CB_RF5C47X, 0},
+ CB_RF5C47X},
{PCI_DEVICE_ID_RICOH_RL5C476, "RF5C476 PCI-CardBus Bridge",
- CB_RF5C47X, 0},
+ CB_RF5C47X},
+ {PCI_DEVICE_ID_RICOH_RL5C477, "RF5C477 PCI-CardBus Bridge",
+ CB_RF5C47X},
{PCI_DEVICE_ID_RICOH_RL5C478, "RF5C478 PCI-CardBus Bridge",
- CB_RF5C47X, 0},
+ CB_RF5C47X},
/* Toshiba products */
{PCI_DEVICE_ID_TOSHIBA_TOPIC95, "ToPIC95 PCI-CardBus Bridge",
- CB_TOPIC95, 0},
+ CB_TOPIC95},
{PCI_DEVICE_ID_TOSHIBA_TOPIC95B, "ToPIC95B PCI-CardBus Bridge",
- CB_TOPIC95B, 0},
+ CB_TOPIC95},
{PCI_DEVICE_ID_TOSHIBA_TOPIC97, "ToPIC97 PCI-CardBus Bridge",
- CB_TOPIC97, 0},
+ CB_TOPIC97},
{PCI_DEVICE_ID_TOSHIBA_TOPIC100, "ToPIC100 PCI-CardBus Bridge",
- CB_TOPIC97, 0},
+ CB_TOPIC97},
/* Cirrus Logic */
{PCI_DEVICE_ID_PCIC_CLPD6832, "CLPD6832 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_CLPD6833, "CLPD6833 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_CLPD6834, "CLPD6834 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
/* 02Micro */
{PCI_DEVICE_ID_PCIC_OZ6832, "O2Mirco OZ6832/6833 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_OZ6860, "O2Mirco OZ6836/6860 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_OZ6872, "O2Mirco OZ6812/6872 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_OZ6912, "O2Mirco OZ6912/6972 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_OZ6922, "O2Mirco OZ6822 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
{PCI_DEVICE_ID_PCIC_OZ6933, "O2Mirco OZ6833 PCI-CardBus Bridge",
- CB_CIRRUS, 0},
+ CB_CIRRUS},
/* sentinel */
- {0 /* null id */, "unknown",
- CB_UNKNOWN, 0},
+ {0 /* null id */, "unknown", CB_UNKNOWN},
};
/* sysctl vars */
-SYSCTL_NODE(_hw, OID_AUTO, pccbb, CTLFLAG_RD, 0, "PCCBB parameters");
+SYSCTL_NODE(_hw, OID_AUTO, cbb, CTLFLAG_RD, 0, "CBB parameters");
/* There's no way to say TUNEABLE_LONG to get the right types */
u_long pccbb_start_mem = PCCBB_START_MEM;
-TUNABLE_INT("hw.pccbb.start_memory", (int *)&pccbb_start_mem);
-SYSCTL_ULONG(_hw_pccbb, OID_AUTO, start_mem, CTLFLAG_RD,
+TUNABLE_INT("hw.cbb.start_memory", (int *)&pccbb_start_mem);
+SYSCTL_ULONG(_hw_cbb, OID_AUTO, start_mem, CTLFLAG_RD,
&pccbb_start_mem, PCCBB_START_MEM,
"Starting address for memory allocations");
-static int pccbb_chipset(uint32_t pci_id, const char **namep, int *flagp);
+u_long pccbb_start_16_io = PCCBB_START_16_IO;
+TUNABLE_INT("hw.cbb.start_16_io", (int *)&pccbb_start_16_io);
+SYSCTL_ULONG(_hw_cbb, OID_AUTO, start_16_io, CTLFLAG_RD,
+ &pccbb_start_16_io, PCCBB_START_16_IO,
+ "Starting ioport for 16-bit cards");
+
+u_long pccbb_start_32_io = PCCBB_START_32_IO;
+TUNABLE_INT("hw.cbb.start_32_io", (int *)&pccbb_start_32_io);
+SYSCTL_ULONG(_hw_cbb, OID_AUTO, start_32_io, CTLFLAG_RD,
+ &pccbb_start_32_io, PCCBB_START_32_IO,
+ "Starting ioport for 32-bit cards");
+
+int cbb_debug = 0;
+TUNABLE_INT("hw.cbb.debug", &cbb_debug);
+SYSCTL_ULONG(_hw_cbb, OID_AUTO, debug, CTLFLAG_RD, &cbb_debug, 0,
+ "Verbose cardbus bridge debugging");
+
+static int pccbb_chipset(uint32_t pci_id, const char **namep);
static int pccbb_probe(device_t brdev);
static void pccbb_chipinit(struct pccbb_softc *sc);
static int pccbb_attach(device_t brdev);
@@ -200,8 +203,6 @@ static void pccbb_driver_added(device_t brdev, driver_t *driver);
static void pccbb_child_detached(device_t brdev, device_t child);
static int pccbb_card_reprobe(device_t brdev, device_t busdev);
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);
@@ -252,13 +253,13 @@ static void pccbb_write_config(device_t brdev, int b, int s, int f,
static __inline void
pccbb_set(struct pccbb_softc *sc, uint32_t reg, uint32_t val)
{
- bus_space_write_4(sc->sc_bst, sc->sc_bsh, reg, val);
+ bus_space_write_4(sc->bst, sc->bsh, reg, val);
}
static __inline uint32_t
pccbb_get(struct pccbb_softc *sc, uint32_t reg)
{
- return (bus_space_read_4(sc->sc_bst, sc->sc_bsh, reg));
+ return (bus_space_read_4(sc->bst, sc->bsh, reg));
}
static __inline void
@@ -335,7 +336,7 @@ pccbb_destroy_res(struct pccbb_softc *sc)
struct pccbb_reslist *rle;
while ((rle = SLIST_FIRST(&sc->rl)) != NULL) {
- device_printf(sc->sc_dev, "Danger Will Robinson: Resource "
+ device_printf(sc->dev, "Danger Will Robinson: Resource "
"left allocated! This is a bug... "
"(rid=%x, type=%d, addr=%lx)\n", rle->rid, rle->type,
rman_get_start(rle->res));
@@ -349,21 +350,14 @@ pccbb_destroy_res(struct pccbb_softc *sc)
/************************************************************************/
static int
-pccbb_chipset(uint32_t pci_id, const char **namep, int *flagp)
+pccbb_chipset(uint32_t pci_id, const char **namep)
{
- int loopend = sizeof(yc_chipsets)/sizeof(yc_chipsets[0]);
- struct yenta_chipinfo *ycp, *ycend;
- ycend = yc_chipsets + loopend;
+ struct yenta_chipinfo *ycp;
- for (ycp = yc_chipsets; ycp < ycend && pci_id != ycp->yc_id; ++ycp)
+ for (ycp = yc_chipsets; ycp->yc_id != 0 && pci_id != ycp->yc_id; ++ycp)
continue;
- 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);
}
@@ -371,51 +365,78 @@ static int
pccbb_probe(device_t brdev)
{
const char *name;
+ uint32_t progif;
+ uint32_t subclass;
- if (pccbb_chipset(pci_get_devid(brdev), &name, NULL) == CB_UNKNOWN)
- return (ENXIO);
- device_set_desc(brdev, name);
- return (0);
+ /*
+ * Do we know that we support the chipset? If so, then we
+ * accept the device.
+ */
+ if (pccbb_chipset(pci_get_devid(brdev), &name) != CB_UNKNOWN) {
+ device_set_desc(brdev, name);
+ return (0);
+ }
+
+ /*
+ * We do support generic CardBus bridges. All that we've seen
+ * to date have progif 0 (the Yenta spec, and successors mandate
+ * this). We do not support PCI PCMCIA bridges (with one exception)
+ * with this driver since they generally are I/O mapped. Those
+ * are supported by the pcic driver. This should help us be more
+ * future proof.
+ */
+ subclass = pci_get_subclass(brdev);
+ progif = pci_get_progif(brdev);
+ if (subclass == PCIS_BRIDGE_CARDBUS && progif == 0) {
+ device_set_desc(brdev, "PCI-CardBus Bridge");
+ return (0);
+ }
+ return (ENXIO);
}
+
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);
+ if (pci_read_config(sc->dev, PCIR_SECLAT_1, 1) < 0x20)
+ pci_write_config(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);
+ if (pci_read_config(sc->dev, PCIR_LATTIMER, 1) < 0x20)
+ pci_write_config(sc->dev, PCIR_LATTIMER, 0x20, 1);
/* Enable memory access */
- PCI_MASK_CONFIG(sc->sc_dev, PCIR_COMMAND,
+ PCI_MASK_CONFIG(sc->dev, PCIR_COMMAND,
| PCIM_CMD_MEMEN
| PCIM_CMD_PORTEN
| PCIM_CMD_BUSMASTEREN, 2);
/* disable Legacy IO */
- switch (sc->sc_chipset) {
+ switch (sc->chipset) {
case CB_RF5C46X:
- PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_BRIDGECTRL,
- & ~(PCCBBM_BRIDGECTRL_RL_3E0_EN |
- PCCBBM_BRIDGECTRL_RL_3E2_EN), 2);
+ PCI_MASK_CONFIG(sc->dev, CBBR_BRIDGECTRL,
+ & ~(CBBM_BRIDGECTRL_RL_3E0_EN |
+ CBBM_BRIDGECTRL_RL_3E2_EN), 2);
break;
default:
- pci_write_config(sc->sc_dev, PCCBBR_LEGACY, 0x0, 4);
+ pci_write_config(sc->dev, CBBR_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,
+ PCI_MASK2_CONFIG(sc->dev, CBBR_BRIDGECTRL,
+ & ~(CBBM_BRIDGECTRL_MASTER_ABORT |
+ CBBM_BRIDGECTRL_INTR_IREQ_EN),
+ | CBBM_BRIDGECTRL_WRITE_POST_EN,
2);
- /* XXX this should be a function table, ala OLDCARD. */
- switch (sc->sc_chipset) {
+ /*
+ * XXX this should be a function table, ala OLDCARD. This means
+ * that we could more easily support ISA interrupts for pccard
+ * cards if we had to.
+ */
+ switch (sc->chipset) {
case CB_TI113X:
/*
* The TI 1031, TI 1130 and TI 1131 all require another bit
@@ -423,41 +444,80 @@ pccbb_chipinit(struct pccbb_softc *sc)
* a bit for each of the CSC and Function interrupts we
* want routed.
*/
- PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_CBCTRL,
- | PCCBBM_CBCTRL_113X_PCI_INTR |
- PCCBBM_CBCTRL_113X_PCI_CSC | PCCBBM_CBCTRL_113X_PCI_IRQ_EN,
+ PCI_MASK_CONFIG(sc->dev, CBBR_CBCTRL,
+ | CBBM_CBCTRL_113X_PCI_INTR |
+ CBBM_CBCTRL_113X_PCI_CSC | CBBM_CBCTRL_113X_PCI_IRQ_EN,
1);
- PCI_MASK_CONFIG(sc->sc_dev, PCCBBR_DEVCTRL,
- & ~(PCCBBM_DEVCTRL_INT_SERIAL |
- PCCBBM_DEVCTRL_INT_PCI), 1);
- exca_write(&sc->exca, EXCA_INTR, EXCA_INTR_ENABLE);
- exca_write(&sc->exca, EXCA_CSC_INTR, 0);
+ PCI_MASK_CONFIG(sc->dev, CBBR_DEVCTRL,
+ & ~(CBBM_DEVCTRL_INT_SERIAL |
+ CBBM_DEVCTRL_INT_PCI), 1);
break;
- case CB_TI12XX:
- exca_write(&sc->exca, EXCA_INTR, EXCA_INTR_ENABLE);
- exca_write(&sc->exca, EXCA_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);
+ case CB_TOPIC97:
+ /*
+ * Disable Zoom Video, ToPIC 97, 100.
+ */
+ pci_write_config(sc->dev, CBBR_TOPIC_ZV_CONTROL, 0, 1);
+ /*
+ * ToPIC 97, 100
+ * At offset 0xa1: INTERRUPT CONTROL register
+ * 0x1: Turn on INT interrupts.
+ */
+ PCI_MASK_CONFIG(sc->dev, CBBR_TOPIC_INTCTRL,
+ | CBBM_TOPIC_INTCTRL_INTIRQSEL, 1);
+ goto topic_common;
+ case CB_TOPIC95:
+ /*
+ * SOCKETCTRL appears to be TOPIC 95/B specific
+ */
+ PCI_MASK_CONFIG(sc->dev, CBBR_TOPIC_SOCKETCTRL,
+ | CBBM_TOPIC_SOCKETCTRL_SCR_IRQSEL, 4);
+
+ topic_common:;
+ /*
+ * At offset 0xa0: SLOT CONTROL
+ * 0x80 Enable Cardbus Functionality
+ * 0x40 Enable Cardbus and PC Card registers
+ * 0x20 Lock ID in exca regs
+ * 0x10 Write protect ID in config regs
+ * Clear the rest of the bits, which defaults the slot
+ * in legacy mode to 0x3e0 and offset 0. (legacy
+ * mode is determined elsewhere)
+ */
+ pci_write_config(sc->dev, CBBR_TOPIC_SLOTCTRL,
+ CBBM_TOPIC_SLOTCTRL_SLOTON |
+ CBBM_TOPIC_SLOTCTRL_SLOTEN |
+ CBBM_TOPIC_SLOTCTRL_ID_LOCK |
+ CBBM_TOPIC_SLOTCTRL_ID_WP, 1);
+
+ /*
+ * At offset 0xa3 Card Detect Control Register
+ * 0x80 CARDBUS enbale
+ * 0x01 Cleared for hardware change detect
+ */
+ PCI_MASK2_CONFIG(sc->dev, CBBR_TOPIC_CDC,
+ | CBBM_TOPIC_CDC_CARDBUS,
+ & ~CBBM_TOPIC_CDC_SWDETECT, 4);
break;
}
+ /*
+ * Need to tell ExCA registers to route via PCI interrupts. There
+ * are two ways to do this. Once is to set INTR_ENABLE and the
+ * other is to set CSC to 0. Since both methods are mutually
+ * compatible, we do both.
+ */
+ exca_write(&sc->exca, EXCA_INTR, EXCA_INTR_ENABLE);
+ exca_write(&sc->exca, EXCA_CSC_INTR, 0);
+
/* 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);
+ pci_write_config(sc->dev, CBBR_MEMBASE0, 0xffffffff, 4);
+ pci_write_config(sc->dev, CBBR_MEMLIMIT0, 0, 4);
+ pci_write_config(sc->dev, CBBR_MEMBASE1, 0xffffffff, 4);
+ pci_write_config(sc->dev, CBBR_MEMLIMIT1, 0, 4);
+ pci_write_config(sc->dev, CBBR_IOBASE0, 0xffffffff, 4);
+ pci_write_config(sc->dev, CBBR_IOLIMIT0, 0, 4);
+ pci_write_config(sc->dev, CBBR_IOBASE1, 0xffffffff, 4);
+ pci_write_config(sc->dev, CBBR_IOLIMIT1, 0, 4);
}
static int
@@ -466,35 +526,34 @@ pccbb_attach(device_t brdev)
struct pccbb_softc *sc = (struct pccbb_softc *)device_get_softc(brdev);
int rid;
uint32_t sockbase;
- struct pccbb_sclist *sclist;
- if (!softcs_init) {
- softcs_init = 1;
- STAILQ_INIT(&softcs);
- }
- mtx_init(&sc->sc_mtx, device_get_nameunit(brdev), MTX_DEF);
- sc->sc_chipset = pccbb_chipset(pci_get_devid(brdev), NULL, &sc->sc_flags);
- sc->sc_dev = brdev;
- sc->sc_cbdev = NULL;
- sc->sc_pccarddev = NULL;
- sc->sc_secbus = pci_read_config(brdev, PCIR_SECBUS_2, 1);
- sc->sc_subbus = pci_read_config(brdev, PCIR_SUBBUS_2, 1);
+ mtx_init(&sc->mtx, device_get_nameunit(brdev), MTX_DEF);
+ sc->chipset = pccbb_chipset(pci_get_devid(brdev), NULL);
+ sc->dev = brdev;
+ sc->cbdev = NULL;
+ sc->pccarddev = NULL;
+ sc->secbus = pci_read_config(brdev, PCIR_SECBUS_2, 1);
+ sc->subbus = pci_read_config(brdev, PCIR_SUBBUS_2, 1);
SLIST_INIT(&sc->rl);
/*
* The PCI bus code should assign us memory in the absense
- * of the BIOS doing so. However, 'should' isn't 'is,' so we hack
- * up something here until the PCI code is up to snuff.
+ * of the BIOS doing so. However, 'should' isn't 'is,' so we kludge
+ * up something here until the PCI/acpi code properly assigns the
+ * resource.
*/
- rid = PCCBBR_SOCKBASE;
- sc->sc_base_res = bus_alloc_resource(brdev, SYS_RES_MEMORY, &rid,
+ rid = CBBR_SOCKBASE;
+ sc->base_res = bus_alloc_resource(brdev, SYS_RES_MEMORY, &rid,
0, ~0, 1, RF_ACTIVE);
- if (!sc->sc_base_res) {
+ if (!sc->base_res) {
/*
- * XXX EVILE HACK BAD THING! XXX
- * The pci bus device should do this for us.
- * Some BIOSes doesn't assign a memory space properly.
- * So we try to manually put one in...
+ * Generally, the BIOS will assign this memory for us.
+ * However, newer BIOSes do not because the MS design
+ * documents have mandated that this is for the OS
+ * to assign rather than the BIOS. This driver shouldn't
+ * be doing this, but until the pci bus code (or acpi)
+ * does this, we allow CardBus bridges to work on more
+ * machines.
*/
sockbase = pci_read_config(brdev, rid, 4);
if (sockbase < 0x100000 || sockbase >= 0xfffffff0) {
@@ -502,81 +561,85 @@ pccbb_attach(device_t brdev)
sockbase = pci_read_config(brdev, rid, 4);
sockbase = (sockbase & 0xfffffff0) &
-(sockbase & 0xfffffff0);
- sc->sc_base_res = bus_generic_alloc_resource(
+ sc->base_res = bus_generic_alloc_resource(
device_get_parent(brdev), brdev, SYS_RES_MEMORY,
&rid, pccbb_start_mem, ~0, sockbase,
RF_ACTIVE|rman_make_alignment_flags(sockbase));
- if (!sc->sc_base_res){
+ if (!sc->base_res) {
device_printf(brdev,
"Could not grab register memory\n");
- mtx_destroy(&sc->sc_mtx);
+ mtx_destroy(&sc->mtx);
return (ENOMEM);
}
- pci_write_config(brdev, PCCBBR_SOCKBASE,
- rman_get_start(sc->sc_base_res), 4);
+ pci_write_config(brdev, CBBR_SOCKBASE,
+ rman_get_start(sc->base_res), 4);
DEVPRINTF((brdev, "PCI Memory allocated: %08lx\n",
- rman_get_start(sc->sc_base_res)));
+ rman_get_start(sc->base_res)));
} else {
device_printf(brdev, "Could not map register memory\n");
- mtx_destroy(&sc->sc_mtx);
+ mtx_destroy(&sc->mtx);
return (ENOMEM);
}
}
- sc->sc_bst = rman_get_bustag(sc->sc_base_res);
- sc->sc_bsh = rman_get_bushandle(sc->sc_base_res);
+ sc->bst = rman_get_bustag(sc->base_res);
+ sc->bsh = rman_get_bushandle(sc->base_res);
exca_init(&sc->exca, brdev, &pccbb_pcic_write, &pccbb_pcic_read,
- sc->sc_bst, sc->sc_bsh, 0x800);
+ sc->bst, sc->bsh, 0x800);
pccbb_chipinit(sc);
- /* CSC Interrupt: Card detect interrupt on */
- pccbb_setb(sc, PCCBB_SOCKET_MASK, PCCBB_SOCKET_MASK_CD);
+ /* attach children */
+ sc->cbdev = device_add_child(brdev, "cardbus", -1);
+ if (sc->cbdev == NULL)
+ DEVPRINTF((brdev, "WARNING: cannot add cardbus bus.\n"));
+ else if (device_probe_and_attach(sc->cbdev) != 0) {
+ DEVPRINTF((brdev, "WARNING: cannot attach cardbus bus!\n"));
+ sc->cbdev = NULL;
+ }
- /* reset interrupt */
- pccbb_set(sc, PCCBB_SOCKET_EVENT, pccbb_get(sc, PCCBB_SOCKET_EVENT));
+ sc->pccarddev = device_add_child(brdev, "pccard", -1);
+ if (sc->pccarddev == NULL)
+ DEVPRINTF((brdev, "WARNING: cannot add pccard bus.\n"));
+ else if (device_probe_and_attach(sc->pccarddev) != 0) {
+ DEVPRINTF((brdev, "WARNING: cannot attach pccard bus.\n"));
+ sc->pccarddev = NULL;
+ }
/* Map and establish the interrupt. */
rid = 0;
- sc->sc_irq_res = bus_alloc_resource(brdev, SYS_RES_IRQ, &rid, 0, ~0, 1,
+ sc->irq_res = bus_alloc_resource(brdev, SYS_RES_IRQ, &rid, 0, ~0, 1,
RF_SHAREABLE | RF_ACTIVE);
- if (sc->sc_irq_res == NULL) {
+ if (sc->irq_res == NULL) {
printf("pccbb: Unable to map IRQ...\n");
- bus_release_resource(brdev, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
- sc->sc_base_res);
- mtx_destroy(&sc->sc_mtx);
+ bus_release_resource(brdev, SYS_RES_MEMORY, CBBR_SOCKBASE,
+ sc->base_res);
+ mtx_destroy(&sc->mtx);
return (ENOMEM);
}
- if (bus_setup_intr(brdev, sc->sc_irq_res, INTR_TYPE_AV, pccbb_intr, sc,
- &sc->sc_intrhand)) {
+ if (bus_setup_intr(brdev, sc->irq_res, INTR_TYPE_AV, pccbb_intr, sc,
+ &sc->intrhand)) {
device_printf(brdev, "couldn't establish interrupt");
- bus_release_resource(brdev, SYS_RES_IRQ, 0, sc->sc_irq_res);
- bus_release_resource(brdev, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
- sc->sc_base_res);
- mtx_destroy(&sc->sc_mtx);
+ bus_release_resource(brdev, SYS_RES_IRQ, 0, sc->irq_res);
+ bus_release_resource(brdev, SYS_RES_MEMORY, CBBR_SOCKBASE,
+ sc->base_res);
+ mtx_destroy(&sc->mtx);
return (ENOMEM);
}
- /* attach children */
- sc->sc_cbdev = device_add_child(brdev, "cardbus", -1);
- if (sc->sc_cbdev == NULL)
- DEVPRINTF((brdev, "WARNING: cannot add cardbus bus.\n"));
- else if (device_probe_and_attach(sc->sc_cbdev) != 0) {
- DEVPRINTF((brdev, "WARNING: cannot attach cardbus bus!\n"));
- sc->sc_cbdev = NULL;
- }
+ /* CSC Interrupt: Card detect interrupt on */
+ pccbb_setb(sc, CBB_SOCKET_MASK, CBB_SOCKET_MASK_CD);
- sc->sc_pccarddev = device_add_child(brdev, "pccard", -1);
- if (sc->sc_pccarddev == NULL)
- DEVPRINTF((brdev, "WARNING: cannot add pccard bus.\n"));
- else if (device_probe_and_attach(sc->sc_pccarddev) != 0) {
- DEVPRINTF((brdev, "WARNING: cannot attach pccard bus.\n"));
- sc->sc_pccarddev = NULL;
+ /* reset interrupt */
+ pccbb_set(sc, CBB_SOCKET_EVENT, pccbb_get(sc, CBB_SOCKET_EVENT));
+
+ /* Start the thread */
+ if (kthread_create(pccbb_event_thread, sc, &sc->event_thread, 0,
+ "%s%d", device_get_name(sc->dev), device_get_unit(sc->dev))) {
+ device_printf (sc->dev, "unable to create event thread.\n");
+ panic ("pccbb_create_event_thread");
}
- sclist = malloc(sizeof(struct pccbb_sclist), M_DEVBUF, M_WAITOK);
- sclist->sc = sc;
- STAILQ_INSERT_TAIL(&softcs, sclist, entries);
return (0);
}
@@ -602,13 +665,12 @@ pccbb_detach(device_t brdev)
if (error > 0)
return (ENXIO);
- mtx_lock(&sc->sc_mtx);
- bus_teardown_intr(brdev, sc->sc_irq_res, sc->sc_intrhand);
-
- sc->sc_flags |= PCCBB_KTHREAD_DONE;
- if (sc->sc_flags & PCCBB_KTHREAD_RUNNING) {
+ mtx_lock(&sc->mtx);
+ bus_teardown_intr(brdev, sc->irq_res, sc->intrhand);
+ sc->flags |= PCCBB_KTHREAD_DONE;
+ if (sc->flags & PCCBB_KTHREAD_RUNNING) {
wakeup(sc);
- mtx_unlock(&sc->sc_mtx);
+ mtx_unlock(&sc->mtx);
DEVPRINTF((brdev, "waiting for kthread exit..."));
error = tsleep(sc, PWAIT, "pccbb-detach-wait", 60 * hz);
if (error)
@@ -616,13 +678,13 @@ pccbb_detach(device_t brdev)
else
DPRINTF(("done\n"));
} else {
- mtx_unlock(&sc->sc_mtx);
+ mtx_unlock(&sc->mtx);
}
- bus_release_resource(brdev, SYS_RES_IRQ, 0, sc->sc_irq_res);
- bus_release_resource(brdev, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
- sc->sc_base_res);
- mtx_destroy(&sc->sc_mtx);
+ bus_release_resource(brdev, SYS_RES_IRQ, 0, sc->irq_res);
+ bus_release_resource(brdev, SYS_RES_MEMORY, CBBR_SOCKBASE,
+ sc->base_res);
+ mtx_destroy(&sc->mtx);
return (0);
}
@@ -632,22 +694,22 @@ pccbb_shutdown(device_t brdev)
struct pccbb_softc *sc = (struct pccbb_softc *)device_get_softc(brdev);
/* properly reset everything at shutdown */
- PCI_MASK_CONFIG(brdev, PCCBBR_BRIDGECTRL, |PCCBBM_BRIDGECTRL_RESET, 2);
+ PCI_MASK_CONFIG(brdev, CBBR_BRIDGECTRL, |CBBM_BRIDGECTRL_RESET, 2);
exca_clrb(&sc->exca, EXCA_INTR, EXCA_INTR_RESET);
- pccbb_set(sc, PCCBB_SOCKET_MASK, 0);
+ pccbb_set(sc, CBB_SOCKET_MASK, 0);
pccbb_power(brdev, CARD_VCC_0V | CARD_VPP_0V);
exca_write(&sc->exca, EXCA_ADDRWIN_ENABLE, 0);
- pci_write_config(brdev, PCCBBR_MEMBASE0, 0, 4);
- pci_write_config(brdev, PCCBBR_MEMLIMIT0, 0, 4);
- pci_write_config(brdev, PCCBBR_MEMBASE1, 0, 4);
- pci_write_config(brdev, PCCBBR_MEMLIMIT1, 0, 4);
- pci_write_config(brdev, PCCBBR_IOBASE0, 0, 4);
- pci_write_config(brdev, PCCBBR_IOLIMIT0, 0, 4);
- pci_write_config(brdev, PCCBBR_IOBASE1, 0, 4);
- pci_write_config(brdev, PCCBBR_IOLIMIT1, 0, 4);
+ pci_write_config(brdev, CBBR_MEMBASE0, 0, 4);
+ pci_write_config(brdev, CBBR_MEMLIMIT0, 0, 4);
+ pci_write_config(brdev, CBBR_MEMBASE1, 0, 4);
+ pci_write_config(brdev, CBBR_MEMLIMIT1, 0, 4);
+ pci_write_config(brdev, CBBR_IOBASE0, 0, 4);
+ pci_write_config(brdev, CBBR_IOLIMIT0, 0, 4);
+ pci_write_config(brdev, CBBR_IOBASE1, 0, 4);
+ pci_write_config(brdev, CBBR_IOLIMIT1, 0, 4);
pci_write_config(brdev, PCIR_COMMAND, 0, 2);
return (0);
}
@@ -697,21 +759,21 @@ pccbb_driver_added(device_t brdev, driver_t *driver)
DEVICE_IDENTIFY(driver, brdev);
device_get_children(brdev, &devlist, &numdevs);
wake = 0;
- sockstate = pccbb_get(sc, PCCBB_SOCKET_STATE);
+ sockstate = pccbb_get(sc, CBB_SOCKET_STATE);
for (tmp = 0; tmp < numdevs; tmp++) {
if (device_get_state(devlist[tmp]) == DS_NOTPRESENT &&
device_probe_and_attach(devlist[tmp]) == 0) {
if (devlist[tmp] == NULL)
/* NOTHING */;
else if (strcmp(driver->name, "cardbus") == 0) {
- sc->sc_cbdev = devlist[tmp];
- if (((sockstate & PCCBB_SOCKET_STAT_CD) == 0) &&
- (sockstate & PCCBB_SOCKET_STAT_CB))
+ sc->cbdev = devlist[tmp];
+ if (((sockstate & CBB_SOCKET_STAT_CD) == 0) &&
+ (sockstate & CBB_SOCKET_STAT_CB))
wake++;
} else if (strcmp(driver->name, "pccard") == 0) {
- sc->sc_pccarddev = devlist[tmp];
- if (((sockstate & PCCBB_SOCKET_STAT_CD) == 0) &&
- (sockstate & PCCBB_SOCKET_STAT_16BIT))
+ sc->pccarddev = devlist[tmp];
+ if (((sockstate & CBB_SOCKET_STAT_CD) == 0) &&
+ (sockstate & CBB_SOCKET_STAT_16BIT))
wake++;
} else
device_printf(brdev,
@@ -722,11 +784,11 @@ pccbb_driver_added(device_t brdev, driver_t *driver)
free(devlist, M_TEMP);
if (wake > 0) {
- if ((pccbb_get(sc, PCCBB_SOCKET_STATE) & PCCBB_SOCKET_STAT_CD)
+ if ((pccbb_get(sc, CBB_SOCKET_STATE) & CBB_SOCKET_STAT_CD)
== 0) {
- mtx_lock(&sc->sc_mtx);
+ mtx_lock(&sc->mtx);
wakeup(sc);
- mtx_unlock(&sc->sc_mtx);
+ mtx_unlock(&sc->mtx);
}
}
}
@@ -736,13 +798,13 @@ pccbb_child_detached(device_t brdev, device_t child)
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (child == sc->sc_cbdev)
- sc->sc_cbdev = NULL;
- else if (child == sc->sc_pccarddev)
- sc->sc_pccarddev = NULL;
+ if (child == sc->cbdev)
+ sc->cbdev = NULL;
+ else if (child == sc->pccarddev)
+ sc->pccarddev = NULL;
else
device_printf(brdev, "Unknown child detached: %s %p/%p\n",
- device_get_nameunit(child), sc->sc_cbdev, sc->sc_pccarddev);
+ device_get_nameunit(child), sc->cbdev, sc->pccarddev);
}
static int
@@ -752,20 +814,20 @@ pccbb_card_reprobe(device_t brdev, device_t busdev)
int wake = 0;
uint32_t sockstate;
- sockstate = pccbb_get(sc, PCCBB_SOCKET_STATE);
+ sockstate = pccbb_get(sc, CBB_SOCKET_STATE);
- if ((sockstate & PCCBB_SOCKET_STAT_CD) == 0) {
- if (busdev == sc->sc_cbdev &&
- (sockstate & PCCBB_SOCKET_STAT_CB))
+ if ((sockstate & CBB_SOCKET_STAT_CD) == 0) {
+ if (busdev == sc->cbdev &&
+ (sockstate & CBB_SOCKET_STAT_CB))
wake++;
- else if (busdev == sc->sc_pccarddev &&
- (sockstate & PCCBB_SOCKET_STAT_16BIT))
+ else if (busdev == sc->pccarddev &&
+ (sockstate & CBB_SOCKET_STAT_16BIT))
wake++;
if (wake > 0) {
- mtx_lock(&sc->sc_mtx);
+ mtx_lock(&sc->mtx);
wakeup(sc);
- mtx_unlock(&sc->sc_mtx);
+ mtx_unlock(&sc->mtx);
return (0);
}
return (EBUSY);
@@ -782,65 +844,48 @@ pccbb_event_thread(void *arg)
{
struct pccbb_softc *sc = arg;
uint32_t status;
+ int err;
+ /*
+ * We take out Giant here because we drop it in tsleep
+ * and need it for kthread_exit, which drops it
+ */
mtx_lock(&Giant);
+ sc->flags |= PCCBB_KTHREAD_RUNNING;
for(;;) {
- if (!(sc->sc_flags & PCCBB_KTHREAD_RUNNING)) {
- sc->sc_flags |= PCCBB_KTHREAD_RUNNING;
- } else {
- tsleep (sc, PWAIT, "pccbbev", 0);
- /*
- * Delay 1 second, make sure the user is done with
- * whatever he is doing. We tsleep on sc->sc_flags,
- * which should never be woken up.
- *
- * XXX Note: This can cause problems on card
- * removal. See OLDCARD's ISR for how you may
- * have to deal with the debouncing problem. The
- * crux of the issue is interrupts delivered to
- * the card after eject are unstable.
- */
- tsleep (&sc->sc_flags, PWAIT, "pccbbev", 1*hz);
- }
- mtx_lock(&sc->sc_mtx);
- if (sc->sc_flags & PCCBB_KTHREAD_DONE)
+ /*
+ * Wait until it has been 1s since the last time we
+ * get an interrupt.
+ */
+ tsleep (sc, PWAIT, "pccbbev", 0);
+ do {
+ err = tsleep (sc, PWAIT, "pccbbev", 1 * hz);
+ } while (err != EWOULDBLOCK &&
+ (sc->flags & PCCBB_KTHREAD_DONE) == 0);
+ mtx_lock(&sc->mtx);
+ if (sc->flags & PCCBB_KTHREAD_DONE)
break;
- status = pccbb_get(sc, PCCBB_SOCKET_STATE);
- if ((status & PCCBB_SOCKET_STAT_CD) == 0) {
+ status = pccbb_get(sc, CBB_SOCKET_STATE);
+ if ((status & CBB_SOCKET_STAT_CD) == 0)
pccbb_insert(sc);
- } else {
+ else
pccbb_removal(sc);
- }
- mtx_unlock(&sc->sc_mtx);
+ mtx_unlock(&sc->mtx);
}
- mtx_unlock(&sc->sc_mtx);
- sc->sc_flags &= ~PCCBB_KTHREAD_RUNNING;
+ mtx_unlock(&sc->mtx);
+ sc->flags &= ~PCCBB_KTHREAD_RUNNING;
wakeup(sc);
+ /*
+ * XXX I think there's a race here. If we wakeup in the other
+ * thread before kthread_exit is called and this routine returns,
+ * and that thread causes us to be unmapped, then we are setting
+ * ourselves up for a panic. Make sure that I check out
+ * jhb's crash.c for a fix.
+ */
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) {
- pccbb_create_event_thread(sclist->sc);
- }
-}
-
/************************************************************************/
/* Insert/removal */
/************************************************************************/
@@ -851,39 +896,59 @@ pccbb_insert(struct pccbb_softc *sc)
uint32_t sockevent, sockstate;
int timeout = 30;
+ /*
+ * Debounce interrupt. However, most of the debounce
+ * is done in the thread's timeout routines.
+ */
do {
- sockevent = pccbb_get(sc, PCCBB_SOCKET_EVENT);
- sockstate = pccbb_get(sc, PCCBB_SOCKET_STATE);
- } while (sockstate & PCCBB_SOCKET_STAT_CD && --timeout > 0);
+ sockevent = pccbb_get(sc, CBB_SOCKET_EVENT);
+ sockstate = pccbb_get(sc, CBB_SOCKET_STATE);
+ } while (sockstate & CBB_SOCKET_STAT_CD && --timeout > 0);
if (timeout < 0) {
- device_printf (sc->sc_dev, "insert timeout");
+ device_printf (sc->dev, "insert timeout");
return;
}
- DEVPRINTF((sc->sc_dev, "card inserted: event=0x%08x, state=%08x\n",
+ DEVPRINTF((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_16BIT_CARD;
- if (CARD_ATTACH_CARD(sc->sc_pccarddev) != 0)
- device_printf(sc->sc_dev, "card activation failed\n");
- } else if (sockstate & PCCBB_SOCKET_STAT_CB && sc->sc_cbdev != NULL) {
- sc->sc_flags &= ~PCCBB_16BIT_CARD;
- if (CARD_ATTACH_CARD(sc->sc_cbdev) != 0)
- device_printf(sc->sc_dev, "card activation failed\n");
+ if (sockstate & CBB_SOCKET_STAT_16BIT) {
+ if (sc->pccarddev != NULL) {
+ sc->flags |= PCCBB_16BIT_CARD;
+ if (CARD_ATTACH_CARD(sc->pccarddev) != 0)
+ device_printf(sc->dev,
+ "PC Card card activation failed\n");
+ } else {
+ device_printf(sc->dev,
+ "PC Card inserted, but no pccard bus.\n");
+ }
+ } else if (sockstate & CBB_SOCKET_STAT_CB) {
+ if (sc->cbdev != NULL) {
+ sc->flags &= ~PCCBB_16BIT_CARD;
+ if (CARD_ATTACH_CARD(sc->cbdev) != 0)
+ device_printf(sc->dev,
+ "CardBus card activation failed\n");
+ } else {
+ device_printf(sc->dev,
+ "CardBUS card inserted, but no cardbus bus.\n");
+ }
} else {
- device_printf (sc->sc_dev, "Unsupported card type detected\n");
+ /*
+ * We should power the card down, and try again a couple of
+ * times if this happens. XXX
+ */
+ device_printf (sc->dev, "Unsupported card type detected\n");
}
}
static void
pccbb_removal(struct pccbb_softc *sc)
{
- if (sc->sc_flags & PCCBB_16BIT_CARD && sc->sc_pccarddev != NULL)
- CARD_DETACH_CARD(sc->sc_pccarddev, DETACH_FORCE);
- else if ((!(sc->sc_flags & PCCBB_16BIT_CARD)) && sc->sc_cbdev != NULL)
- CARD_DETACH_CARD(sc->sc_cbdev, DETACH_FORCE);
+ if (sc->flags & PCCBB_16BIT_CARD && sc->pccarddev != NULL)
+ CARD_DETACH_CARD(sc->pccarddev, DETACH_FORCE);
+ else if ((!(sc->flags & PCCBB_16BIT_CARD)) && sc->cbdev != NULL)
+ CARD_DETACH_CARD(sc->cbdev, DETACH_FORCE);
pccbb_destroy_res(sc);
}
@@ -897,28 +962,31 @@ pccbb_intr(void *arg)
struct pccbb_softc *sc = arg;
uint32_t sockevent;
- if (!(sockevent = pccbb_get(sc, PCCBB_SOCKET_EVENT))) {
- /* not for me. */
- return;
- }
-
- /* reset bit */
- pccbb_setb(sc, PCCBB_SOCKET_EVENT, 0x01); /* XXXmagic */
+ /*
+ * This ISR needs work XXX
+ */
+ sockevent = pccbb_get(sc, CBB_SOCKET_EVENT);
+ if (sockevent) {
+ /* ack the interrupt */
+ pccbb_setb(sc, CBB_SOCKET_EVENT, sockevent);
- if (sockevent & PCCBB_SOCKET_EVENT_CD) {
- mtx_lock(&sc->sc_mtx);
- wakeup(sc);
- mtx_unlock(&sc->sc_mtx);
- } else {
- if (sockevent & PCCBB_SOCKET_EVENT_CSTS) {
- DPRINTF(("csts event occurred, state = 0x%08x\n",
- pccbb_get(sc, PCCBB_SOCKET_STATE)));
+ if (sockevent & CBB_SOCKET_EVENT_CD) {
+ mtx_lock(&sc->mtx);
+ wakeup(sc);
+ mtx_unlock(&sc->mtx);
+ }
+ if (sockevent & CBB_SOCKET_EVENT_CSTS) {
+ DPRINTF((" cstsevent occured: 0x%08x\n",
+ pccbb_get(sc, CBB_SOCKET_STATE)));
}
- if (sockevent & PCCBB_SOCKET_EVENT_POWER) {
- DPRINTF(("power event occurred, state = 0x%08x\n",
- pccbb_get(sc, PCCBB_SOCKET_STATE)));
+ if (sockevent & CBB_SOCKET_EVENT_POWER) {
+ DPRINTF((" pwrevent occured: 0x%08x\n",
+ pccbb_get(sc, CBB_SOCKET_STATE)));
}
+ /* Other bits? */
}
+
+ /* Call the interrupt if we still have the card */
}
/************************************************************************/
@@ -932,15 +1000,15 @@ pccbb_detect_voltage(device_t brdev)
uint32_t psr;
int vol = CARD_UKN_CARD;
- psr = pccbb_get(sc, PCCBB_SOCKET_STATE);
+ psr = pccbb_get(sc, CBB_SOCKET_STATE);
- if (psr & PCCBB_SOCKET_STAT_5VCARD)
+ if (psr & CBB_SOCKET_STAT_5VCARD)
vol |= CARD_5V_CARD;
- if (psr & PCCBB_SOCKET_STAT_3VCARD)
+ if (psr & CBB_SOCKET_STAT_3VCARD)
vol |= CARD_3V_CARD;
- if (psr & PCCBB_SOCKET_STAT_XVCARD)
+ if (psr & CBB_SOCKET_STAT_XVCARD)
vol |= CARD_XV_CARD;
- if (psr & PCCBB_SOCKET_STAT_YVCARD)
+ if (psr & CBB_SOCKET_STAT_YVCARD)
vol |= CARD_YV_CARD;
return (vol);
@@ -954,7 +1022,7 @@ pccbb_power(device_t brdev, int volts)
int timeout;
uint32_t sockevent;
- DEVPRINTF((sc->sc_dev, "pccbb_power: %s and %s [%x]\n",
+ DEVPRINTF((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" :
@@ -969,32 +1037,32 @@ pccbb_power(device_t brdev, int volts)
"VPP-UNKNOWN",
volts));
- status = pccbb_get(sc, PCCBB_SOCKET_STATE);
- sock_ctrl = pccbb_get(sc, PCCBB_SOCKET_CONTROL);
+ status = pccbb_get(sc, CBB_SOCKET_STATE);
+ sock_ctrl = pccbb_get(sc, CBB_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;
+ if (CBB_SOCKET_STAT_5VCARD & status) { /* check 5 V card */
+ sock_ctrl &= ~CBB_SOCKET_CTRL_VCCMASK;
+ sock_ctrl |= CBB_SOCKET_CTRL_VCC_5V;
} else {
- device_printf(sc->sc_dev,
+ device_printf(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;
+ if (CBB_SOCKET_STAT_3VCARD & status) {
+ sock_ctrl &= ~CBB_SOCKET_CTRL_VCCMASK;
+ sock_ctrl |= CBB_SOCKET_CTRL_VCC_3V;
} else {
- device_printf(sc->sc_dev,
+ device_printf(sc->dev,
"BAD voltage request: no 3.3 V card\n");
}
break;
case CARD_VCC_0V:
- sock_ctrl &= ~PCCBB_SOCKET_CTRL_VCCMASK;
+ sock_ctrl &= ~CBB_SOCKET_CTRL_VCCMASK;
break;
default:
return (0); /* power NEVER changed */
@@ -1005,23 +1073,23 @@ pccbb_power(device_t brdev, int volts)
case CARD_VPP_UC:
break;
case CARD_VPP_0V:
- sock_ctrl &= ~PCCBB_SOCKET_CTRL_VPPMASK;
+ sock_ctrl &= ~CBB_SOCKET_CTRL_VPPMASK;
break;
case CARD_VPP_VCC:
- sock_ctrl &= ~PCCBB_SOCKET_CTRL_VPPMASK;
+ sock_ctrl &= ~CBB_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;
+ sock_ctrl &= ~CBB_SOCKET_CTRL_VPPMASK;
+ sock_ctrl |= CBB_SOCKET_CTRL_VPP_12V;
break;
}
- if (pccbb_get(sc, PCCBB_SOCKET_CONTROL) == sock_ctrl)
+ if (pccbb_get(sc, CBB_SOCKET_CONTROL) == sock_ctrl)
return (1); /* no change necessary */
- pccbb_set(sc, PCCBB_SOCKET_CONTROL, sock_ctrl);
- status = pccbb_get(sc, PCCBB_SOCKET_STATE);
+ pccbb_set(sc, CBB_SOCKET_CONTROL, sock_ctrl);
+ status = pccbb_get(sc, CBB_SOCKET_STATE);
/*
* XXX This busy wait is bogus. We should wait for a power
@@ -1032,11 +1100,11 @@ pccbb_power(device_t brdev, int volts)
timeout = 20;
do {
DELAY(20*1000);
- sockevent = pccbb_get(sc, PCCBB_SOCKET_EVENT);
- } while (!(sockevent & PCCBB_SOCKET_EVENT_POWER) && --timeout > 0);
+ sockevent = pccbb_get(sc, CBB_SOCKET_EVENT);
+ } while (!(sockevent & CBB_SOCKET_EVENT_POWER) && --timeout > 0);
/* reset event status */
/* XXX should only reset EVENT_POWER */
- pccbb_set(sc, PCCBB_SOCKET_EVENT, sockevent);
+ pccbb_set(sc, CBB_SOCKET_EVENT, sockevent);
if (timeout < 0) {
printf ("VCC supply failed.\n");
return (0);
@@ -1050,8 +1118,8 @@ pccbb_power(device_t brdev, int volts)
*/
DELAY(400*1000);
- if (status & PCCBB_SOCKET_STAT_BADVCC) {
- device_printf(sc->sc_dev,
+ if (status & CBB_SOCKET_STAT_BADVCC) {
+ device_printf(sc->dev,
"bad Vcc request. ctrl=0x%x, status=0x%x\n",
sock_ctrl ,status);
printf("pccbb_power: %s and %s [%x]\n",
@@ -1073,6 +1141,35 @@ pccbb_power(device_t brdev, int volts)
return (1); /* power changed correctly */
}
+/*
+ * detect the voltage for the card, and set it. Since the power
+ * used is the square of the voltage, lower voltages is a big win
+ * and what Windows does (and what Microsoft prefers). The MS paper
+ * also talks about preferring the CIS entry as well.
+ */
+static int
+pccbb_do_power(device_t brdev)
+{
+ int voltage;
+
+ /* Prefer lowest voltage supported */
+ voltage = pccbb_detect_voltage(brdev);
+ pccbb_power(brdev, CARD_VCC_0V | CARD_VPP_0V);
+ if (voltage & CARD_YV_CARD)
+ pccbb_power(brdev, CARD_VCC_YV | CARD_VPP_VCC);
+ else if (voltage & CARD_XV_CARD)
+ pccbb_power(brdev, CARD_VCC_XV | CARD_VPP_VCC);
+ else if (voltage & CARD_3V_CARD)
+ pccbb_power(brdev, CARD_VCC_3V | CARD_VPP_VCC);
+ else if (voltage & CARD_5V_CARD)
+ pccbb_power(brdev, CARD_VCC_5V | CARD_VPP_VCC);
+ else {
+ device_printf(brdev, "Unknown card voltage\n");
+ return (ENXIO);
+ }
+ return (0);
+}
+
/************************************************************************/
/* Cardbus power functions */
/************************************************************************/
@@ -1083,16 +1180,16 @@ pccbb_cardbus_reset(device_t brdev)
struct pccbb_softc *sc = device_get_softc(brdev);
int delay_us;
- delay_us = sc->sc_chipset == CB_RF5C47X ? 400*1000 : 20*1000;
+ delay_us = sc->chipset == CB_RF5C47X ? 400*1000 : 20*1000;
- PCI_MASK_CONFIG(brdev, PCCBBR_BRIDGECTRL, |PCCBBM_BRIDGECTRL_RESET, 2);
+ PCI_MASK_CONFIG(brdev, CBBR_BRIDGECTRL, |CBBM_BRIDGECTRL_RESET, 2);
DELAY(delay_us);
/* If a card exists, unreset it! */
- if ((pccbb_get(sc, PCCBB_SOCKET_STATE) & PCCBB_SOCKET_STAT_CD) == 0) {
- PCI_MASK_CONFIG(brdev, PCCBBR_BRIDGECTRL,
- &~PCCBBM_BRIDGECTRL_RESET, 2);
+ if ((pccbb_get(sc, CBB_SOCKET_STATE) & CBB_SOCKET_STAT_CD) == 0) {
+ PCI_MASK_CONFIG(brdev, CBBR_BRIDGECTRL,
+ &~CBBM_BRIDGECTRL_RESET, 2);
DELAY(delay_us);
}
}
@@ -1101,24 +1198,15 @@ static int
pccbb_cardbus_power_enable_socket(device_t brdev, device_t child)
{
struct pccbb_softc *sc = device_get_softc(brdev);
- int voltage;
+ int err;
- if ((pccbb_get(sc, PCCBB_SOCKET_STATE) & PCCBB_SOCKET_STAT_CD) ==
- PCCBB_SOCKET_STAT_CD)
+ if ((pccbb_get(sc, CBB_SOCKET_STATE) & CBB_SOCKET_STAT_CD) ==
+ CBB_SOCKET_STAT_CD)
return (ENODEV);
- voltage = pccbb_detect_voltage(brdev);
-
- pccbb_power(brdev, CARD_VCC_0V | CARD_VPP_0V);
- if (voltage & CARD_5V_CARD)
- pccbb_power(brdev, CARD_VCC_5V | CARD_VPP_VCC);
- else if (voltage & CARD_3V_CARD)
- pccbb_power(brdev, CARD_VCC_3V | CARD_VPP_VCC);
- else {
- device_printf(brdev, "Unknown card voltage\n");
- return (ENXIO);
- }
-
+ err = pccbb_do_power(brdev);
+ if (err)
+ return (err);
pccbb_cardbus_reset(brdev);
return (0);
}
@@ -1146,8 +1234,8 @@ pccbb_cardbus_io_open(device_t brdev, int win, uint32_t start, uint32_t end)
return (EINVAL);
}
- basereg = win*8 + PCCBBR_IOBASE0;
- limitreg = win*8 + PCCBBR_IOLIMIT0;
+ basereg = win * 8 + CBBR_IOBASE0;
+ limitreg = win * 8 + CBBR_IOLIMIT0;
pci_write_config(brdev, basereg, start, 4);
pci_write_config(brdev, limitreg, end, 4);
@@ -1166,8 +1254,8 @@ pccbb_cardbus_mem_open(device_t brdev, int win, uint32_t start, uint32_t end)
return (EINVAL);
}
- basereg = win*8 + PCCBBR_MEMBASE0;
- limitreg = win*8 + PCCBBR_MEMLIMIT0;
+ basereg = win*8 + CBBR_MEMBASE0;
+ limitreg = win*8 + CBBR_MEMLIMIT0;
pci_write_config(brdev, basereg, start, 4);
pci_write_config(brdev, limitreg, end, 4);
@@ -1191,9 +1279,9 @@ pccbb_cardbus_auto_open(struct pccbb_softc *sc, int type)
ends[0] = ends[1] = 0;
if (type == SYS_RES_MEMORY)
- align = PCCBB_MEMALIGN;
+ align = CBB_MEMALIGN;
else if (type == SYS_RES_IOPORT)
- align = PCCBB_IOALIGN;
+ align = CBB_IOALIGN;
else
align = 1;
@@ -1201,7 +1289,7 @@ pccbb_cardbus_auto_open(struct pccbb_softc *sc, int type)
if (rle->type != type)
;
else if (rle->res == NULL) {
- device_printf(sc->sc_dev, "WARNING: Resource not reserved? "
+ device_printf(sc->dev, "WARNING: Resource not reserved? "
"(type=%d, addr=%lx)\n",
rle->type, rman_get_start(rle->res));
} else if (!(rman_get_flags(rle->res) & RF_ACTIVE)) {
@@ -1270,17 +1358,17 @@ pccbb_cardbus_auto_open(struct pccbb_softc *sc, int type)
}
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]);
- reg = pci_read_config(sc->sc_dev, PCCBBR_BRIDGECTRL, 2);
- reg &= ~(PCCBBM_BRIDGECTRL_PREFETCH_0|
- PCCBBM_BRIDGECTRL_PREFETCH_1);
- reg |= (prefetchable[0]?PCCBBM_BRIDGECTRL_PREFETCH_0:0)|
- (prefetchable[1]?PCCBBM_BRIDGECTRL_PREFETCH_1:0);
- pci_write_config(sc->sc_dev, PCCBBR_BRIDGECTRL, reg, 2);
+ pccbb_cardbus_mem_open(sc->dev, 0, starts[0], ends[0]);
+ pccbb_cardbus_mem_open(sc->dev, 1, starts[1], ends[1]);
+ reg = pci_read_config(sc->dev, CBBR_BRIDGECTRL, 2);
+ reg &= ~(CBBM_BRIDGECTRL_PREFETCH_0|
+ CBBM_BRIDGECTRL_PREFETCH_1);
+ reg |= (prefetchable[0]?CBBM_BRIDGECTRL_PREFETCH_0:0)|
+ (prefetchable[1]?CBBM_BRIDGECTRL_PREFETCH_1:0);
+ pci_write_config(sc->dev, CBBR_BRIDGECTRL, reg, 2);
} 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]);
+ pccbb_cardbus_io_open(sc->dev, 0, starts[0], ends[0]);
+ pccbb_cardbus_io_open(sc->dev, 1, starts[1], ends[1]);
}
}
@@ -1313,8 +1401,8 @@ pccbb_cardbus_deactivate_resource(device_t brdev, device_t child, int type,
}
static struct resource *
-pccbb_cardbus_alloc_resource(device_t brdev, device_t child, int type, int *rid,
- u_long start, u_long end, u_long count, uint flags)
+pccbb_cardbus_alloc_resource(device_t brdev, device_t child, int type,
+ int *rid, u_long start, u_long end, u_long count, uint flags)
{
struct pccbb_softc *sc = device_get_softc(brdev);
int tmp;
@@ -1322,7 +1410,7 @@ pccbb_cardbus_alloc_resource(device_t brdev, device_t child, int type, int *rid,
switch (type) {
case SYS_RES_IRQ:
- tmp = rman_get_start(sc->sc_irq_res);
+ tmp = rman_get_start(sc->irq_res);
if (start > tmp || end < tmp || count != 1) {
device_printf(child, "requested interrupt %ld-%ld,"
"count = %ld not supported by pccbb\n",
@@ -1332,8 +1420,8 @@ pccbb_cardbus_alloc_resource(device_t brdev, device_t child, int type, int *rid,
start = end = tmp;
break;
case SYS_RES_IOPORT:
- if (start <= PCCBB_START_IO)
- start = PCCBB_START_IO;
+ if (start <= pccbb_start_32_io)
+ start = pccbb_start_32_io;
if (end < start)
end = start;
break;
@@ -1386,21 +1474,14 @@ static int
pccbb_pcic_power_enable_socket(device_t brdev, device_t child)
{
struct pccbb_softc *sc = device_get_softc(brdev);
- int voltage;
+ int err;
DPRINTF(("pccbb_pcic_socket_enable:\n"));
/* power down/up the socket to reset */
- voltage = pccbb_detect_voltage(brdev);
- pccbb_power(brdev, CARD_VCC_0V | CARD_VPP_0V);
- if (voltage & CARD_5V_CARD)
- pccbb_power(brdev, CARD_VCC_5V | CARD_VPP_VCC);
- else if (voltage & CARD_3V_CARD)
- pccbb_power(brdev, CARD_VCC_3V | CARD_VPP_VCC);
- else {
- device_printf(brdev, "Unknown card voltage\n");
- return (ENXIO);
- }
+ err = pccbb_do_power(brdev);
+ if (err)
+ return (err);
exca_reset(&sc->exca, child);
return (0);
@@ -1434,7 +1515,7 @@ pccbb_power_enable_socket(device_t brdev, device_t child)
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
return (pccbb_pcic_power_enable_socket(brdev, child));
else
return (pccbb_cardbus_power_enable_socket(brdev, child));
@@ -1444,7 +1525,7 @@ static void
pccbb_power_disable_socket(device_t brdev, device_t child)
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
pccbb_pcic_power_disable_socket(brdev, child);
else
pccbb_cardbus_power_disable_socket(brdev, child);
@@ -1512,16 +1593,16 @@ pccbb_pcic_alloc_resource(device_t brdev, device_t child, int type, int *rid,
if (end < start)
end = start;
flags = (flags & ~RF_ALIGNMENT_MASK) |
- rman_make_alignment_flags(PCCBB_MEMALIGN);
+ rman_make_alignment_flags(CBB_MEMALIGN);
break;
case SYS_RES_IOPORT:
- if (start < 0x100)
- start = 0x100; /* XXX tweakable? */
+ if (start < pccbb_start_16_io)
+ start = pccbb_start_16_io;
if (end < start)
end = start;
break;
case SYS_RES_IRQ:
- tmp = rman_get_start(sc->sc_irq_res);
+ tmp = rman_get_start(sc->irq_res);
if (start > tmp || end < tmp || count != 1) {
device_printf(child, "requested interrupt %ld-%ld,"
"count = %ld not supported by pccbb\n",
@@ -1529,7 +1610,7 @@ pccbb_pcic_alloc_resource(device_t brdev, device_t child, int type, int *rid,
return (NULL);
}
flags |= RF_SHAREABLE;
- start = end = rman_get_start(sc->sc_irq_res);
+ start = end = rman_get_start(sc->irq_res);
break;
}
res = BUS_ALLOC_RESOURCE(device_get_parent(brdev), child, type, rid,
@@ -1613,7 +1694,7 @@ pccbb_activate_resource(device_t brdev, device_t child, int type, int rid,
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
return (pccbb_pcic_activate_resource(brdev, child, type, rid, r));
else
return (pccbb_cardbus_activate_resource(brdev, child, type, rid,
@@ -1626,7 +1707,7 @@ pccbb_deactivate_resource(device_t brdev, device_t child, int type,
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
return (pccbb_pcic_deactivate_resource(brdev, child, type,
rid, r));
else
@@ -1640,7 +1721,7 @@ pccbb_alloc_resource(device_t brdev, device_t child, int type, int *rid,
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
return (pccbb_pcic_alloc_resource(brdev, child, type, rid,
start, end, count, flags));
else
@@ -1654,7 +1735,7 @@ pccbb_release_resource(device_t brdev, device_t child, int type, int rid,
{
struct pccbb_softc *sc = device_get_softc(brdev);
- if (sc->sc_flags & PCCBB_16BIT_CARD)
+ if (sc->flags & PCCBB_16BIT_CARD)
return (pccbb_pcic_release_resource(brdev, child, type,
rid, r));
else
@@ -1669,7 +1750,7 @@ pccbb_read_ivar(device_t brdev, device_t child, int which, uintptr_t *result)
switch (which) {
case PCIB_IVAR_BUS:
- *result = sc->sc_secbus;
+ *result = sc->secbus;
return (0);
}
return (ENOENT);
@@ -1682,7 +1763,7 @@ pccbb_write_ivar(device_t brdev, device_t child, int which, uintptr_t value)
switch (which) {
case PCIB_IVAR_BUS:
- sc->sc_secbus = value;
+ sc->secbus = value;
break;
}
return (ENOENT);
@@ -1725,7 +1806,7 @@ pccbb_suspend(device_t self)
int error = 0;
struct pccbb_softc* sc = device_get_softc(self);
- bus_teardown_intr(self, sc->sc_irq_res, sc->sc_intrhand);
+ bus_teardown_intr(self, sc->irq_res, sc->intrhand);
error = bus_generic_suspend(self);
return (error);
}
@@ -1737,31 +1818,31 @@ pccbb_resume(device_t self)
struct pccbb_softc *sc = (struct pccbb_softc *)device_get_softc(self);
uint32_t tmp;
- pci_write_config(self, PCCBBR_SOCKBASE,
- rman_get_start(sc->sc_base_res), 4);
+ pci_write_config(self, CBBR_SOCKBASE, rman_get_start(sc->base_res), 4);
DEVPRINTF((self, "PCI Memory allocated: %08lx\n",
- rman_get_start(sc->sc_base_res)));
+ rman_get_start(sc->base_res)));
pccbb_chipinit(sc);
- /* CSC Interrupt: Card detect interrupt on */
- pccbb_setb(sc, PCCBB_SOCKET_MASK, PCCBB_SOCKET_MASK_CD);
-
- /* reset interrupt */
- tmp = pccbb_get(sc, PCCBB_SOCKET_EVENT);
- pccbb_set(sc, PCCBB_SOCKET_EVENT, tmp);
-
/* re-establish the interrupt. */
- if (bus_setup_intr(self, sc->sc_irq_res, INTR_TYPE_AV, pccbb_intr, sc,
- &sc->sc_intrhand)) {
+ if (bus_setup_intr(self, sc->irq_res, INTR_TYPE_AV, pccbb_intr, sc,
+ &sc->intrhand)) {
device_printf(self, "couldn't re-establish interrupt");
- bus_release_resource(self, SYS_RES_IRQ, 0, sc->sc_irq_res);
- bus_release_resource(self, SYS_RES_MEMORY, PCCBBR_SOCKBASE,
- sc->sc_base_res);
- mtx_destroy(&sc->sc_mtx);
- error = ENOMEM;
+ bus_release_resource(self, SYS_RES_IRQ, 0, sc->irq_res);
+ bus_release_resource(self, SYS_RES_MEMORY, CBBR_SOCKBASE,
+ sc->base_res);
+ sc->irq_res = NULL;
+ sc->base_res = NULL;
+ return (ENOMEM);
}
+ /* CSC Interrupt: Card detect interrupt on */
+ pccbb_setb(sc, CBB_SOCKET_MASK, CBB_SOCKET_MASK_CD);
+
+ /* reset interrupt */
+ tmp = pccbb_get(sc, CBB_SOCKET_EVENT);
+ pccbb_set(sc, CBB_SOCKET_EVENT, tmp);
+
/*
* Some BIOSes will not save the BARs for the pci chips, so we
* must do it ourselves. If the BAR is reset to 0 for an I/O
@@ -1771,18 +1852,12 @@ pccbb_resume(device_t self)
* Note: The PCI bus code should do this automatically for us on
* suspend/resume, but until it does, we have to cope.
*/
- if (pci_read_config(self, PCCBBR_SOCKBASE, 4) == 0)
- pci_write_config(self, PCCBBR_SOCKBASE,
- rman_get_start(sc->sc_base_res), 4);
+ if (pci_read_config(self, CBBR_SOCKBASE, 4) == 0)
+ pci_write_config(self, CBBR_SOCKBASE,
+ rman_get_start(sc->base_res), 4);
error = bus_generic_resume(self);
- /* wakeup thread */
- if (!error) {
- mtx_lock(&sc->sc_mtx);
- wakeup(sc);
- mtx_unlock(&sc->sc_mtx);
- }
return (error);
}
@@ -1833,5 +1908,3 @@ static driver_t pccbb_driver = {
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/pccbbreg.h b/sys/dev/pccbb/pccbbreg.h
index 6705ede..e22b056 100644
--- a/sys/dev/pccbb/pccbbreg.h
+++ b/sys/dev/pccbb/pccbbreg.h
@@ -34,133 +34,149 @@
/* 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
+#define CBBR_SOCKBASE 0x10 /* len=4 */
+
+#define CBBR_MEMBASE0 0x1c /* len=4 */
+#define CBBR_MEMLIMIT0 0x20 /* len=4 */
+#define CBBR_MEMBASE1 0x24 /* len=4 */
+#define CBBR_MEMLIMIT1 0x28 /* len=4 */
+#define CBBR_IOBASE0 0x2c /* len=4 */
+#define CBBR_IOLIMIT0 0x30 /* len=4 */
+#define CBBR_IOBASE1 0x34 /* len=4 */
+#define CBBR_IOLIMIT1 0x38 /* len=4 */
+#define CBB_MEMALIGN 4096
+#define CBB_IOALIGN 4
+
+#define CBBR_INTRLINE 0x3c /* len=1 */
+#define CBBR_INTRPIN 0x3d /* len=1 */
+#define CBBR_BRIDGECTRL 0x3e /* len=2 */
+# define CBBM_BRIDGECTRL_MASTER_ABORT 0x0020
+# define CBBM_BRIDGECTRL_RESET 0x0040
+# define CBBM_BRIDGECTRL_INTR_IREQ_EN 0x0080
+# define CBBM_BRIDGECTRL_PREFETCH_0 0x0100
+# define CBBM_BRIDGECTRL_PREFETCH_1 0x0200
+# define CBBM_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 CBBM_BRIDGECTRL_RL_3E0_EN 0x0800
+# define CBBM_BRIDGECTRL_RL_3E2_EN 0x1000
-#define PCCBBR_LEGACY 0x44 /* len=4 */
+#define CBBR_LEGACY 0x44 /* len=4 */
-#define PCCBBR_CBCTRL 0x91 /* len=1 */
+#define CBBR_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
+# define CBBM_CBCTRL_113X_RI_EN 0x80
+# define CBBM_CBCTRL_113X_ZV_EN 0x40
+# define CBBM_CBCTRL_113X_PCI_IRQ_EN 0x20
+# define CBBM_CBCTRL_113X_PCI_INTR 0x10
+# define CBBM_CBCTRL_113X_PCI_CSC 0x08
+# define CBBM_CBCTRL_113X_PCI_CSC_D 0x04
+# define CBBM_CBCTRL_113X_SPEAKER_EN 0x02
+# define CBBM_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 Clk/2 */
-# define PCCBBM_TOPIC_SLOTCTRL_CLOCK_1 0x00000400 /* PCI Clk */
-# 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
+# define CBBM_CBCTRL_12XX_RI_EN 0x80
+# define CBBM_CBCTRL_12XX_ZV_EN 0x40
+# define CBBM_CBCTRL_12XX_AUD2MUX 0x04
+# define CBBM_CBCTRL_12XX_SPEAKER_EN 0x02
+# define CBBM_CBCTRL_12XX_INTR_DET 0x01
+#define CBBR_DEVCTRL 0x92 /* len=1 */
+# define CBBM_DEVCTRL_INT_SERIAL 0x04
+# define CBBM_DEVCTRL_INT_PCI 0x02
+
+/* ToPIC 95 ONLY */
+#define CBBR_TOPIC_SOCKETCTRL 0x90
+# define CBBM_TOPIC_SOCKETCTRL_SCR_IRQSEL 0x00000001 /* PCI intr */
+/* ToPIC 97, 100 */
+#define CBBR_TOPIC_ZV_CONTROL 0x9c /* 1 byte */
+# define CBBM_TOPIC_ZVC_ENABLE 0x1
+
+/* TOPIC 95+ */
+#define CBBR_TOPIC_SLOTCTRL 0xa0 /* 1 byte */
+# define CBBM_TOPIC_SLOTCTRL_SLOTON 0x80
+# define CBBM_TOPIC_SLOTCTRL_SLOTEN 0x40
+# define CBBM_TOPIC_SLOTCTRL_ID_LOCK 0x20
+# define CBBM_TOPIC_SLOTCTRL_ID_WP 0x10
+# define CBBM_TOPIC_SLOTCTRL_PORT_MASK 0x0c
+# define CBBM_TOPIC_SLOTCTRL_PORT_SHIFT 2
+# define CBBM_TOPIC_SLOTCTRL_OSF_MASK 0x03
+# define CBBM_TOPIC_SLOTCTRL_OSF_SHIFT 0
+
+/* TOPIC 95+ */
+#define CBBR_TOPIC_INTCTRL 0xa1 /* 1 byte */
+# define CBBM_TOPIC_INTCTRL_INTB 0x20
+# define CBBM_TOPIC_INTCTRL_INTA 0x10
+# define CBBM_TOPIC_INTCTRL_INT_MASK 0x30
+/* The following bits may be for ToPIC 95 only */
+# define CBBM_TOPIC_INTCTRL_CLOCK_MASK 0x0c
+# define CBBM_TOPIC_INTCTRL_CLOCK_2 0x08 /* PCI Clk/2 */
+# define CBBM_TOPIC_INTCTRL_CLOCK_1 0x04 /* PCI Clk */
+# define CBBM_TOPIC_INTCTRL_CLOCK_0 0x00 /* no clock */
+/* ToPIC97, 100 defines the following bits */
+# define CBBM_TOPIC_INTCTRL_STSIRQNP 0x04
+# define CBBM_TOPIC_INTCTRL_IRQNP 0x02
+# define CBBM_TOPIC_INTCTRL_INTIRQSEL 0x01
+
+/* TOPIC 95+ */
+#define CBBR_TOPIC_CDC 0xa3 /* 1 byte */
+# define CBBM_TOPIC_CDC_CARDBUS 0x80
+# define CBBM_TOPIC_CDC_VS1 0x04
+# define CBBM_TOPIC_CDC_VS2 0x02
+# define CBBM_TOPIC_CDC_SWDETECT 0x01
/* 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
+#define CBB_SOCKET_EVENT_CSTS 0x01 /* Card Status Change */
+#define CBB_SOCKET_EVENT_CD1 0x02 /* Card Detect 1 */
+#define CBB_SOCKET_EVENT_CD2 0x04 /* Card Detect 2 */
+#define CBB_SOCKET_EVENT_CD 0x06 /* Card Detect all */
+#define CBB_SOCKET_EVENT_POWER 0x08 /* Power Cycle */
+
+#define CBB_SOCKET_MASK_CSTS 0x01 /* Card Status Change */
+#define CBB_SOCKET_MASK_CD 0x06 /* Card Detect */
+#define CBB_SOCKET_MASK_POWER 0x08 /* Power Cycle */
+
+#define CBB_SOCKET_STAT_CARDSTS 0x00000001 /* Card Status Change */
+#define CBB_SOCKET_STAT_CD1 0x00000002 /* Card Detect 1 */
+#define CBB_SOCKET_STAT_CD2 0x00000004 /* Card Detect 2 */
+#define CBB_SOCKET_STAT_CD 0x00000006 /* Card Detect all */
+#define CBB_SOCKET_STAT_PWRCYCLE 0x00000008 /* Power Cycle */
+#define CBB_SOCKET_STAT_16BIT 0x00000010 /* 16-bit Card */
+#define CBB_SOCKET_STAT_CB 0x00000020 /* Cardbus Card */
+#define CBB_SOCKET_STAT_IREQ 0x00000040 /* Ready */
+#define CBB_SOCKET_STAT_NOTCARD 0x00000080 /* Unrecognized Card */
+#define CBB_SOCKET_STAT_DATALOST 0x00000100 /* Data Lost */
+#define CBB_SOCKET_STAT_BADVCC 0x00000200 /* Bad VccRequest */
+#define CBB_SOCKET_STAT_5VCARD 0x00000400 /* 5 V Card */
+#define CBB_SOCKET_STAT_3VCARD 0x00000800 /* 3.3 V Card */
+#define CBB_SOCKET_STAT_XVCARD 0x00001000 /* X.X V Card */
+#define CBB_SOCKET_STAT_YVCARD 0x00002000 /* Y.Y V Card */
+#define CBB_SOCKET_STAT_5VSOCK 0x10000000 /* 5 V Socket */
+#define CBB_SOCKET_STAT_3VSOCK 0x20000000 /* 3.3 V Socket */
+#define CBB_SOCKET_STAT_XVSOCK 0x40000000 /* X.X V Socket */
+#define CBB_SOCKET_STAT_YVSOCK 0x80000000 /* Y.Y V Socket */
+
+#define CBB_SOCKET_FORCE_BADVCC 0x0200 /* Bad Vcc Request */
+
+#define CBB_SOCKET_CTRL_VPPMASK 0x07
+#define CBB_SOCKET_CTRL_VPP_OFF 0x00
+#define CBB_SOCKET_CTRL_VPP_12V 0x01
+#define CBB_SOCKET_CTRL_VPP_5V 0x02
+#define CBB_SOCKET_CTRL_VPP_3V 0x03
+#define CBB_SOCKET_CTRL_VPP_XV 0x04
+#define CBB_SOCKET_CTRL_VPP_YV 0x05
+
+#define CBB_SOCKET_CTRL_VCCMASK 0x70
+#define CBB_SOCKET_CTRL_VCC_OFF 0x00
+#define CBB_SOCKET_CTRL_VCC_5V 0x20
+#define CBB_SOCKET_CTRL_VCC_3V 0x30
+#define CBB_SOCKET_CTRL_VCC_XV 0x40
+#define CBB_SOCKET_CTRL_VCC_YV 0x50
+
+#define CBB_SOCKET_CTRL_STOPCLK 0x80
#include <dev/pccbb/pccbbdevid.h>
-#define PCCBB_SOCKET_EVENT 0x00
-#define PCCBB_SOCKET_MASK 0x04
-#define PCCBB_SOCKET_STATE 0x08
-#define PCCBB_SOCKET_FORCE 0x0c
-#define PCCBB_SOCKET_CONTROL 0x10
-#define PCCBB_SOCKET_POWER 0x14
+#define CBB_SOCKET_EVENT 0x00
+#define CBB_SOCKET_MASK 0x04
+#define CBB_SOCKET_STATE 0x08
+#define CBB_SOCKET_FORCE 0x0c
+#define CBB_SOCKET_CONTROL 0x10
+#define CBB_SOCKET_POWER 0x14
diff --git a/sys/dev/pccbb/pccbbvar.h b/sys/dev/pccbb/pccbbvar.h
index 2453187a..80cf178 100644
--- a/sys/dev/pccbb/pccbbvar.h
+++ b/sys/dev/pccbb/pccbbvar.h
@@ -53,37 +53,35 @@ struct pccbb_reslist {
#define PCCBB_AUTO_OPEN_SMALLHOLE 0x100
struct pccbb_softc {
- device_t sc_dev;
+ device_t dev;
struct exca_softc exca;
- struct resource *sc_base_res;
- struct resource *sc_irq_res;
- void *sc_intrhand;
- bus_space_tag_t sc_bst;
- bus_space_handle_t sc_bsh;
- u_int8_t sc_secbus;
- u_int8_t sc_subbus;
- struct mtx sc_mtx;
- u_int32_t sc_flags;
+ struct resource *base_res;
+ struct resource *irq_res;
+ void *intrhand;
+ bus_space_tag_t bst;
+ bus_space_handle_t bsh;
+ u_int8_t secbus;
+ u_int8_t subbus;
+ struct mtx mtx;
+ u_int32_t flags;
#define PCCBB_16BIT_CARD 0x02000000
#define PCCBB_KTHREAD_RUNNING 0x04000000
#define PCCBB_KTHREAD_DONE 0x08000000
- int sc_chipset; /* chipset id */
+ int 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_CIRRUS 5 /* Cirrus Logic CLPD683x */
+#define CB_TOPIC95 6 /* Toshiba ToPIC95 */
#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;
+ device_t cbdev;
+ device_t pccarddev;
- /* kthread staff */
- struct proc *event_thread;
+ struct proc *event_thread;
};
/* result of detect_card */
OpenPOWER on IntegriCloud